Skip to content

Commit 6fa9287

Browse files
committed
Export minpack API via bind(c)
1 parent 8479bd3 commit 6fa9287

File tree

5 files changed

+938
-8
lines changed

5 files changed

+938
-8
lines changed

fpm.toml

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -46,3 +46,8 @@ main = "test_lmdif.f90"
4646
name = "test_lmstr"
4747
source-dir = "test"
4848
main = "test_lmstr.f90"
49+
50+
[[test]]
51+
name = "c-test"
52+
source-dir = "test/api"
53+
main = "tester.c"

include/minpack.h

Lines changed: 356 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,356 @@
1+
#ifdef __cplusplus
2+
#define MINPACK_EXTERN extern "C"
3+
#else
4+
#define MINPACK_EXTERN extern
5+
#endif
6+
7+
MINPACK_EXTERN double
8+
minpack_dpmpar(int /* i */);
9+
10+
typedef void (*minpack_func)(
11+
int /* n */,
12+
const double* /* x */,
13+
double* /* fvec */,
14+
int* /* iflag */,
15+
void* /* udata */);
16+
17+
/*
18+
* the purpose of hybrd is to find a zero of a system of
19+
* n nonlinear functions in n variables by a modification
20+
* of the powell hybrid method. the user must provide a
21+
* subroutine which calculates the functions. the jacobian is
22+
* then calculated by a forward-difference approximation.
23+
*/
24+
MINPACK_EXTERN void
25+
minpack_hybrd(
26+
minpack_func /* fcn */,
27+
int /* n */,
28+
double* /* x */,
29+
double* /* fvec */,
30+
double /* xtol */,
31+
int /* maxfev */,
32+
int /* ml */,
33+
int /* mu */,
34+
double /* epsfcn */,
35+
double* /* diag */,
36+
int /* mode */,
37+
double /* factor */,
38+
int /* nprint */,
39+
int* /* info */,
40+
int* /* nfev */,
41+
double* /* fjac */,
42+
int /* ldfjac */,
43+
double* /* r */,
44+
int /* lr */,
45+
double* /* qtf */,
46+
double* /* wa1 */,
47+
double* /* wa2 */,
48+
double* /* wa3 */,
49+
double* /* wa4 */,
50+
void* /* udata */);
51+
52+
/*
53+
* the purpose of hybrd1 is to find a zero of a system of
54+
* n nonlinear functions in n variables by a modification
55+
* of the powell hybrid method. this is done by using the
56+
* more general nonlinear equation solver hybrd. the user
57+
* must provide a subroutine which calculates the functions.
58+
* the jacobian is then calculated by a forward-difference
59+
* approximation.
60+
*/
61+
MINPACK_EXTERN void
62+
minpack_hybrd1(
63+
minpack_func /* fcn */,
64+
int /* n */,
65+
double* /* x */,
66+
double* /* fvec */,
67+
double /* tol */,
68+
int* /* info */,
69+
double* /* wa */,
70+
int /* lwa */,
71+
void* /* udata */);
72+
73+
typedef void (*minpack_fcn_hybrj)(
74+
int /* n */,
75+
const double* /* x */,
76+
double* /* fvec */,
77+
double* /* fjac */,
78+
int /* ldfjac */,
79+
int* /* iflag */,
80+
void* /* udata */);
81+
82+
/*
83+
* the purpose of hybrj is to find a zero of a system of
84+
* n nonlinear functions in n variables by a modification
85+
* of the powell hybrid method. the user must provide a
86+
* subroutine which calculates the functions and the jacobian.
87+
*/
88+
MINPACK_EXTERN void
89+
minpack_hybrj(
90+
minpack_fcn_hybrj /* fcn */,
91+
int /* n */,
92+
double* /* x */,
93+
double* /* fvec */,
94+
double* /* fjac */,
95+
int /* ldfjac */,
96+
double /* xtol */,
97+
int /* maxfev */,
98+
double* /* diag */,
99+
int /* mode */,
100+
double /* factor */,
101+
int /* nprint */,
102+
int* /* info */,
103+
int* /* nfev */,
104+
int* /* njev */,
105+
double* /* r */,
106+
int /* lr */,
107+
double* /* qtf */,
108+
double* /* wa1 */,
109+
double* /* wa2 */,
110+
double* /* wa3 */,
111+
double* /* wa4 */,
112+
void* /* udata */);
113+
114+
/*
115+
* The purpose of hybrj1 is to find a zero of a system of
116+
* n nonlinear functions in n variables by a modification
117+
* of the powell hybrid method. this is done by using the
118+
* more general nonlinear equation solver hybrj. the user
119+
* must provide a subroutine which calculates the functions
120+
* and the jacobian.
121+
*/
122+
MINPACK_EXTERN void
123+
minpack_hybrj1(
124+
minpack_fcn_hybrj /* fcn */,
125+
int /* n */,
126+
double* /* x */,
127+
double* /* fvec */,
128+
double* /* fjac */,
129+
int /* ldfjac */,
130+
double /* tol */,
131+
int* /* info */,
132+
double* /* wa */,
133+
int /* lwa */,
134+
void* /* udata */);
135+
136+
typedef void (*minpack_fcn_lmder)(
137+
int /* m */,
138+
int /* n */,
139+
const double* /* x */,
140+
double* /* fvec */,
141+
double* /* fjac */,
142+
int /* ldfjac */,
143+
int* /* iflag */,
144+
void* /* udata */);
145+
146+
/*
147+
* the purpose of lmder is to minimize the sum of the squares of
148+
* m nonlinear functions in n variables by a modification of
149+
* the levenberg-marquardt algorithm. the user must provide a
150+
* subroutine which calculates the functions and the jacobian.
151+
*/
152+
MINPACK_EXTERN void
153+
minpack_lmder(
154+
minpack_fcn_lmder /* fcn */,
155+
int /* m */,
156+
int /* n */,
157+
double* /* x */,
158+
double* /* fvec */,
159+
double* /* fjac */,
160+
int /* ldfjac */,
161+
double /* ftol */,
162+
double /* xtol */,
163+
double /* gtol */,
164+
int /* maxfev */,
165+
double* /* diag */,
166+
int /* mode */,
167+
double /* factor */,
168+
int /* nprint */,
169+
int* /* info */,
170+
int* /* nfev */,
171+
int* /* njev */,
172+
int* /* ipvt */,
173+
double* /* qtf */,
174+
double* /* wa1 */,
175+
double* /* wa2 */,
176+
double* /* wa3 */,
177+
double* /* wa4 */,
178+
void* /* udata */);
179+
180+
/*
181+
* the purpose of lmder1 is to minimize the sum of the squares of
182+
* m nonlinear functions in n variables by a modification of the
183+
* levenberg-marquardt algorithm. this is done by using the more
184+
* general least-squares solver lmder. the user must provide a
185+
* subroutine which calculates the functions and the jacobian.
186+
*/
187+
void minpack_lmder1(
188+
minpack_fcn_lmder /* fcn */,
189+
int /* m */,
190+
int /* n */,
191+
double /* *x */,
192+
double /* *fvec */,
193+
double /* *fjac */,
194+
int /* ldfjac */,
195+
double /* tol */,
196+
int /* *info */,
197+
int /* *ipvt */,
198+
double /* *wa */,
199+
int /* lwa */,
200+
void* /* udata */);
201+
202+
typedef void (*minpack_func2)(
203+
int /* m */,
204+
int /* n */,
205+
const double* /* x */,
206+
double* /* fvec */,
207+
int* /* iflag */,
208+
void* /* udata */);
209+
210+
/*
211+
* the purpose of lmdif is to minimize the sum of the squares of
212+
* m nonlinear functions in n variables by a modification of
213+
* the levenberg-marquardt algorithm. the user must provide a
214+
* subroutine which calculates the functions. the jacobian is
215+
* then calculated by a forward-difference approximation.
216+
*/
217+
MINPACK_EXTERN void
218+
minpack_lmdif(
219+
minpack_func2 /* fcn */,
220+
int /* m */,
221+
int /* n */,
222+
double* /* x */,
223+
double* /* fvec */,
224+
double /* ftol */,
225+
double /* xtol */,
226+
double /* gtol */,
227+
int /* maxfev */,
228+
double /* epsfcn */,
229+
double* /* diag */,
230+
int /* mode */,
231+
double /* factor */,
232+
int /* nprint */,
233+
int* /* info */,
234+
int* /* nfev */,
235+
double* /* fjac */,
236+
int /* ldfjac */,
237+
int* /* ipvt */,
238+
double* /* qtf */,
239+
double* /* wa1 */,
240+
double* /* wa2 */,
241+
double* /* wa3 */,
242+
double* /* wa4 */,
243+
void* /* udata */);
244+
245+
/*
246+
* the purpose of lmdif1 is to minimize the sum of the squares of
247+
* m nonlinear functions in n variables by a modification of the
248+
* levenberg-marquardt algorithm. this is done by using the more
249+
* general least-squares solver lmdif. the user must provide a
250+
* subroutine which calculates the functions. the jacobian is
251+
* then calculated by a forward-difference approximation.
252+
*/
253+
void minpack_lmdif1(
254+
minpack_func2 /* fcn */,
255+
int /* m */,
256+
int /* n */,
257+
double* /* x */,
258+
double* /* fvec */,
259+
double /* tol */,
260+
int* /* info */,
261+
int* /* iwa */,
262+
double* /* wa */,
263+
int /* lwa */,
264+
void* /* udata */);
265+
266+
typedef void (*minpack_fcn_lmstr)(
267+
int /* m */,
268+
int /* n */,
269+
const double* /* x */,
270+
double* /* fvec */,
271+
double* /* fjrow */,
272+
int* /* iflag */,
273+
void* /* udata */);
274+
275+
/*
276+
* the purpose of lmstr is to minimize the sum of the squares of
277+
* m nonlinear functions in n variables by a modification of
278+
* the levenberg-marquardt algorithm which uses minimal storage.
279+
* the user must provide a subroutine which calculates the
280+
* functions and the rows of the jacobian.
281+
*/
282+
MINPACK_EXTERN void
283+
minpack_lmstr(
284+
minpack_fcn_lmstr /* fcn */,
285+
int /* m */,
286+
int /* n */,
287+
double* /* x */,
288+
double* /* fvec */,
289+
double* /* fjac */,
290+
int /* ldfjac */,
291+
double /* ftol */,
292+
double /* xtol */,
293+
double /* gtol */,
294+
int /* maxfev */,
295+
double* /* diag */,
296+
int /* mode */,
297+
double /* factor */,
298+
int /* nprint */,
299+
int* /* info */,
300+
int* /* nfev */,
301+
int* /* njev */,
302+
int* /* ipvt */,
303+
double* /* qtf */,
304+
double* /* wa1 */,
305+
double* /* wa2 */,
306+
double* /* wa3 */,
307+
double* /* wa4 */,
308+
void* /* udata */);
309+
310+
/*
311+
* the purpose of lmstr1 is to minimize the sum of the squares of
312+
* m nonlinear functions in n variables by a modification of
313+
* the levenberg-marquardt algorithm which uses minimal storage.
314+
* this is done by using the more general least-squares solver
315+
* lmstr. the user must provide a subroutine which calculates
316+
* the functions and the rows of the jacobian.
317+
*/
318+
MINPACK_EXTERN void
319+
minpack_lmstr1(
320+
minpack_fcn_lmstr /* fcn */,
321+
int /* m */,
322+
int /* n */,
323+
double* /* x */,
324+
double* /* fvec */,
325+
double* /* fjac */,
326+
int /* ldfjac */,
327+
double /* tol */,
328+
int* /* info */,
329+
int* /* ipvt */,
330+
double* /* wa */,
331+
int /* lwa */,
332+
void* /* udata */);
333+
334+
/*
335+
* this subroutine checks the gradients of m nonlinear functions
336+
* in n variables, evaluated at a point x, for consistency with
337+
* the functions themselves.
338+
*
339+
* the subroutine does not perform reliably if cancellation or
340+
* rounding errors cause a severe loss of significance in the
341+
* evaluation of a function. therefore, none of the components
342+
* of x should be unusually small (in particular, zero) or any
343+
* other value which may cause loss of significance.
344+
*/
345+
MINPACK_EXTERN void
346+
minpack_chkder(
347+
int /* m */,
348+
int /* n */,
349+
const double* /* x */,
350+
const double* /* fvec */,
351+
const double* /* fjac */,
352+
int /* ldfjac */,
353+
double* /* xp */,
354+
const double* /* fvecp */,
355+
int /* mode */,
356+
double* /* err */);

0 commit comments

Comments
 (0)