CONOPT
Loading...
Searching...
No Matches
coistart.f90
Go to the documentation of this file.
1!> @file coistart.f90
2!! @ingroup PUBLICAPI_FILES
3!! @brief public Fortran API source file
4
5!> @defgroup DEF_COI_SOLVE ""
6!! method for starting the solving process of CONOPT.
7
8!> @copydoc DEF_COI_SOLVE
9!!
10!! @param cntvect the control vector
11!!
12!! @ingroup UTILITY_ROUTINES_F90
13Integer Function coi_solve( CntVect )
14
15#if defined (dec_directives)
16!DEC$ ATTRIBUTES DLLEXPORT :: COI_Solve
17#if defined (itl)
18!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COI_Solve
19!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COI_SOLVE'::COI_Solve
20#endif
21#endif
22!
23! LOGICAL OPERATION
24! Basic entry point for CONOPT DLL
25!
26 Use conopt_utilities
27 IMPLICIT NONE
28
29 INTEGER, Dimension(NumCallBack), Intent(In Out) :: cntvect
30
31
32 Logical :: nolicense
33
34 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
35 coi_solve = corruptcntr
36 Return
37 Endif
38
39 If ( cntvect(indx_range) /= 0 ) then
40 coi_solve = rangeproblem
41 Return
42 Endif
43
44 nolicense = .false.
45 If ( nolicense ) Then
46 coi_solve = licenseproblem
47 Return
48 Endif
49
50 CALL coeai( cntvect )
51#if defined (write20)
52 close(20)
53#endif
54 coi_solve = cntvect(indx_error) ! Needs changing
55
56END Function coi_solve
57
58!> returns the version number. It can be used to ensure that the modeler is linked to the correct version of the
59!! CONOPT DLL.
60!!
61!! @param major major version number
62!! @param minor minor version number
63!! @param patch patch version number
64!!
65!! @ingroup UTILITY_ROUTINES_F90
66Subroutine coiget_version( major, minor, patch )
67#if defined (dec_directives)
68!DEC$ ATTRIBUTES DLLEXPORT :: COIGET_VERSION
69#if defined (itl)
70!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIGET_Version
71!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIGET_VERSION' :: COIGET_Version
72#endif
73#endif
74 Use conopt_utilities
75 IMPLICIT NONE
76 INTEGER, Intent(Out) :: major, minor, patch
77
78 major = 4
79 minor = 37
80 patch = 0
81
82END Subroutine coiget_version
83
84!> returns the maximum number of threads that can be used by CONOPT.
85!!
86!! If you are using multiple threads it may be necessary to know in advance how many threads CONOPT can use. If
87!! called inside a parallel loop, this method will return one---indicating that CONOPT cannot use multiple
88!! threads when CONOPT itself is called in parallel. Therefore, this method should be called in some sequential
89!! initialization code and not inside a function evaluation routine, that could be called in parallel.
90!!
91!! @param cntvect the control vector
92!!
93!! @ingroup UTILITY_ROUTINES_F90
94Integer Function coiget_maxthreads( CntVect )
95#if defined (dec_directives)
96!DEC$ ATTRIBUTES DLLEXPORT :: COIGET_MaxThreads
97#if defined (itl)
98!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIGET_MaxThreads
99!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIGET_MAXTHREADS'::COIGET_MaxThreads
100#endif
101#endif
102 Use conopt_utilities
103!$ Use OMP_Lib
104 Implicit None
105 Integer, dimension(NumCallBack) :: cntvect
106 Integer :: maxthreads
107
108 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
109 maxthreads = -1
110 Else
111 maxthreads = 1
112!$ If ( .not. OMP_IN_PARALLEL() ) Then
113!$ Maxthreads = OMP_GET_MAX_THREADS()
114!$ Endif
115 Endif
116 coiget_maxthreads = maxthreads
117
118End function coiget_maxthreads
119
120!> After a model has been solved this method will return the amount of heap memory used.
121!!
122!! @param cntvect the control vector
123!!
124!! @ingroup UTILITY_ROUTINES_F90
125Real*8 Function coiget_maxheapused( CntVect )
126#if defined (dec_directives)
127!DEC$ ATTRIBUTES DLLEXPORT :: COIGET_MaxHeapUsed
128#if defined (itl)
129!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIGET_MaxHeapUsed
130!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIGET_MAXHEAPUSED'::COIGET_MaxHeapUsed
131#endif
132#endif
133 Use conopt_utilities
134 Implicit None
135 Integer, dimension(NumCallBack) :: cntvect
136 Real(co_r) :: maxheapused
137
138 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
139 coiget_maxheapused = corruptcntr
140 Else
141 Call unpackreal( cntvect, indx_maxheapused, maxheapused )
142 coiget_maxheapused = maxheapused
143 Endif
144
145End function coiget_maxheapused
146
147!> returns the range errors that were encountered.
148!!
149!! @param cntvect the control vector
150!!
151!! @ingroup UTILITY_ROUTINES_F90
152Integer Function coiget_rangeerrors( CntVect )
153#if defined (dec_directives)
154!DEC$ ATTRIBUTES DLLEXPORT :: COIGET_RangeErrors
155#if defined (itl)
156!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIGET_RangeErrors
157!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIGET_RANGEERRORS'::COIGET_RangeErrors
158#endif
159#endif
160 Use conopt_utilities
161 Implicit None
162 Integer, dimension(NumCallBack) :: cntvect
163
164 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
165 coiget_rangeerrors = corruptcntr
166 Else
167 coiget_rangeerrors = cntvect(indx_range)
168 Endif
169
170End function coiget_rangeerrors
171
172!> returns the size the Control Vector must have, measured in standard Integer units.
173!!
174!! @ingroup THE_CONTROL_VECTOR_F90
175Integer Function coidef_size( )
176#if defined (dec_directives)
177!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Size
178#if defined (itl)
179!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Size
180!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_SIZE'::COIDEF_Size
181#endif
182#endif
183 USE conopt_utilities
184 coidef_size = numcallback
185End Function coidef_size
186
187!> initializes the Control Vector by placing default values in the various positions.
188!! @attention It must always be called.
189!!
190!! There is currently no error checking and this method will always return 0.
191!!
192!! If you have multiple models with multiple Control Vectors then you must call
193!! this method for each control vector. If you solve a sequence of different
194!! models then you can use the same Control Vector provided you initialize it with
195!! a call to this method between the solves.
196!!
197!! @param cntvect the control vector
198!!
199!! @ingroup THE_CONTROL_VECTOR_F90
200Integer Function coidef_ini( CntVect )
201#if defined (dec_directives)
202!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Ini
203#if defined (itl)
204!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Ini
205!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_INI'::COIDEF_Ini
206#endif
207#endif
208 USE conopt_utilities
209 Implicit None
210 Integer, dimension(NumCallBack) :: cntvect
211 Integer(CO_P) :: address
212 Character(Len=CO_Filelen) :: filename
213 Integer, External :: coidef_optfile
214#if defined (itl)
215!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Optfile
216!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_OPTFILE'::COIDEF_Optfile
217#endif
218!
219! Initialize the control vector to default values.
220! First the real values where we use a packing routine
221!
222 Call storereal( cntvect, indx_reslim , 1.0e6_co_r ) ! Give a lot of time
223 Call storereal( cntvect, indx_hessfac , 0.0_co_r ) ! Rvhess is by default 0
224 Call storereal( cntvect, indx_zeronoise , 0.0_co_r ) ! ZeroNoise = 0
225 Call storereal( cntvect, indx_maxheap , 0.0_co_r ) ! MaxHeap = 0 means no limit
226!
227! Integer sizes and options are initialized here:
228!
229 cntvect(indx_numvar) = -1 ! Undefined number of variables
230 cntvect(indx_numcon) = -1 ! Undefined number of constraints
231 cntvect(indx_numnz) = -1 ! Undefined number of nonzeros
232 cntvect(indx_numnlnz) = -1 ! Undefined number of nonlinear nonzeros
233 cntvect(indx_numhess) = -1 ! Undefined number of Hessian nonzeros
234 cntvect(indx_optdir) = 0 ! Undefined optimization direction: -1 = Minimize. +1 = Maximize
235 cntvect(indx_objtyp) = 0 ! Undefined objective type: +1 = variable, -1 = constraint
236 cntvect(indx_objindx) = -1 ! Undefined objective index
237 cntvect(indx_base) = -1 ! Undefined base index
238 cntvect(indx_fortran) = -1 ! Undefined Fortran/C interface
239 cntvect(indx_itlim) = 1000000 ! Many Interations
240 cntvect(indx_errlim) = 0 ! Function Evaluation Errors are not accepted
241 cntvect(indx_inistat) = 0 ! Status information is not provided
242 cntvect(indx_fvinclin) = 0 ! FDEval does not includes linear terms
243 cntvect(indx_fvforall) = 0 ! FDEval is not defined for all constraints
244 cntvect(indx_debugfv) = 0 ! No debugging of FDEval
245 cntvect(indx_maxsup) = -1 ! Default Limit on superbasics in reduced Hessian
246 cntvect(indx_range) = 0 ! There were no range problems in the COIDEF_XXX calls
247 cntvect(indx_square) = 0 ! Default not a square system
248 cntvect(indx_emptyrow) = 0 ! Default empty rows are not allowed
249 cntvect(indx_emptycol) = 0 ! Default empty columns are not allowed
250 cntvect(indx_debug2d) = 0 ! No debugging of the Hessian of Lagrangian
251 cntvect(indx_optorder) = 0 ! The option order is _Optfile first then _Option (1 is opposite order)
252 cntvect(indx_discont) = 0 ! The model is smooth and continuously differentiable
253 cntvect(indx_stdout) = 0 ! Default: We cannot write to standard out = write(*,*)
254 cntvect(indx_error) = 0 ! Default: There are no errors.
255 cntvect(indx_clearm) = 0 ! Default: do not clear memory after allocation
256 cntvect(indx_maxheapused) = 0 ! Maximum Memory used is not defined yet
257 cntvect(indx_threads) = 4 ! Default 4 threads
258 cntvect(indx_threadf) = 0 ! Default threads for FDEval is in Threads
259 cntvect(indx_thread2d) = 0 ! Default threads for 2DDir is in Threads
260 cntvect(indx_threadc) = 0 ! Default compatibility-threads is off.
261 cntvect(indx_licint1) = 987 ! Default no licence code
262 cntvect(indx_licint2) = 654 ! Default no licence code
263 cntvect(indx_licint3) = 321 ! Default no licence code
264 cntvect(indx_liccod1) = 123 ! Default no licence code
265 cntvect(indx_liccod2) = 456 ! Default no licence code
266 cntvect(indx_liccod3) = 789 ! Default no licence code
267 address = 0_co_p
268!
269! Initialize all callback addresses to 0
270!
271 Call storeaddr( cntvect, indx_readmatrix, address )
272 Call storeaddr( cntvect, indx_fdevalini , address )
273 Call storeaddr( cntvect, indx_fdeval , address )
274 Call storeaddr( cntvect, indx_fdevalend , address )
275 Call storeaddr( cntvect, indx_status , address )
276 Call storeaddr( cntvect, indx_solution , address )
277 Call storeaddr( cntvect, indx_message , address )
278 Call storeaddr( cntvect, indx_progress , address )
279 Call storeaddr( cntvect, indx_option , address )
280 Call storeaddr( cntvect, indx_errmsg , address )
281 Call storeaddr( cntvect, indx_triord , address )
282 Call storeaddr( cntvect, indx_fdinterval, address )
283 Call storeaddr( cntvect, indx_2ddirini , address )
284 Call storeaddr( cntvect, indx_2ddir , address )
285 Call storeaddr( cntvect, indx_2ddirend , address )
286 Call storeaddr( cntvect, indx_2ddirlagr , address )
287 Call storeaddr( cntvect, indx_2dlagrsize, address )
288 Call storeaddr( cntvect, indx_2dlagrstr , address )
289 Call storeaddr( cntvect, indx_2dlagrval , address )
290 Call storeaddr( cntvect, indx_usrmem , address )
291!
292! Add a few 'magic numbers' so we can check for an overwritten control
293! vector.
294!
295 cntvect(1) = numcallback
296 cntvect(numcallback) = numcallback
297!
298! Initialize the options file to blank. Needs the magic numbers first.
299!
300 filename = ' '
301 coidef_ini = coidef_optfile( cntvect, filename )
302
303End Function coidef_ini
304
305!> initialisation method for Fortran applications.
306!!
307!! This method will initialise the control vector and set the parameters associated with the base and array indices.
308!!
309!! @param cntvect the control vector
310!!
311!! @ingroup THE_CONTROL_VECTOR_F90
312!!
313Integer Function coidef_inifort( CntVect )
314#if defined (dec_directives)
315!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_IniFort
316#if defined (itl)
317!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_IniFort
318!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_INIFORT'::COIDEF_IniFort
319#endif
320#endif
321 USE conopt_utilities
322 Implicit None
323 Integer, dimension(NumCallBack) :: cntvect
324
325 Integer, External :: coidef_ini
326 Integer, External :: coidef_fortran
327 Integer, External :: coidef_base
328#if defined (itl)
329!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Ini
330!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_INI'::COIDEF_Ini
331!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Fortran
332!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_FORTRAN'::COIDEF_Fortran
333!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Base
334!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_BASE'::COIDEF_Base
335#endif
336 Integer :: i
337
338 coidef_inifort = coidef_ini( cntvect )
339 If ( coidef_inifort == 0 ) Then
340 i = coidef_base( cntvect, 1 )
341 i = coidef_fortran( cntvect )
342 Endif
343
344End Function coidef_inifort
345
346!> defines the number of variables in the model.
347!! @attention Mandatory routine. The number must be positive.
348!!
349!! defines the number of variables in the model. The number does not include
350!! any slack or artificial variables.
351!!
352!! @param cntvect the control vector
353!! @param numvar the number of variables
354!!
355!! @ingroup REGISTRATION_OF_SIZES_F90
356!!
357Integer Function coidef_numvar( CntVect, NumVar )
358#if defined (dec_directives)
359!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_NumVar
360#if defined (itl)
361!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_NumVar
362!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_NUMVAR'::COIDEF_NumVar
363#endif
364#endif
365 Use conopt_utilities
366 Implicit None
367 Integer, dimension(NumCallBack) :: cntvect
368 Integer :: numvar
369
370 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
371 coidef_numvar = corruptcntr
372 Elseif ( numvar < 0 ) Then
373 coidef_numvar = rangeproblem; cntvect(indx_range) = 1;
374#if defined (write20)
375 write(20,*) 'COIDEF_NumVar: Illegal argument. NumVar=',numvar
376#endif
377 Else
378 coidef_numvar = 0
379 cntvect(indx_numvar) = numvar
380 Endif
381
382End function coidef_numvar
383
384!> defines the number of constraints in the model.
385!!
386!! @attention Mandatory routine. The number must be positive.
387!!
388!! defines the number of constraints in the model. The number includes the
389!! objective function if the objective is defined as an expression (see
390!! coidef_objcon() and coidef_objvar()).
391!!
392!! @param cntvect the control vector
393!! @param numcon the number of constraints
394!!
395!! @ingroup REGISTRATION_OF_SIZES_F90
396!!
397Integer Function coidef_numcon( CntVect, NumCon )
398#if defined (dec_directives)
399!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_NumCon
400#if defined (itl)
401!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_NumCon
402!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_NUMCON'::COIDEF_NumCon
403#endif
404#endif
405 Use conopt_utilities
406 Implicit None
407 Integer, dimension(NumCallBack) :: cntvect
408 Integer :: numcon
409
410 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
411 coidef_numcon = corruptcntr
412 Elseif ( numcon < 0 ) Then
413 coidef_numcon = rangeproblem; cntvect(indx_range) = 1
414#if defined (write20)
415 write(20,*) 'COIDEF_NumCon: Illegal argument. NumCon=',numcon
416#endif
417 Else
418 coidef_numcon = 0
419 cntvect(indx_numcon) = numcon
420 Endif
421
422End function coidef_numcon
423
424!> defines the number of nonzero elements in the Jacobian.
425!!
426!! @attention Mandatory routine. The number must be positive.
427!!
428!! defines the number of nonzero elements in the Jacobian of the model (the
429!! matrix of first derivatives of all constraints with respect to all variables).
430!!
431!! @param cntvect the control vector
432!! @param numnz the number of nonzero elements
433!!
434!! @ingroup REGISTRATION_OF_SIZES_F90
435!!
436Integer Function coidef_numnz( CntVect, NumNz )
437#if defined (dec_directives)
438!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_NumNz
439#if defined (itl)
440!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_NumNz
441!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_NUMNZ'::COIDEF_NumNz
442#endif
443#endif
444 Use conopt_utilities
445 Implicit None
446 Integer, dimension(NumCallBack) :: cntvect
447 Integer :: numnz
448
449 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
450 coidef_numnz = corruptcntr
451 Elseif ( numnz < 0 ) Then
452 coidef_numnz = rangeproblem; cntvect(indx_range) = 1
453#if defined (write20)
454 write(20,*) 'COIDEF_NumNz: Illegal argument. NumNz=',numnz
455#endif
456 Else
457 coidef_numnz = 0
458 cntvect(indx_numnz) = numnz
459 Endif
460
461End function coidef_numnz
462
463!> defines the Number of Nonlinear Nonzeros.
464!!
465!! @attention Mandatory routine.
466!!
467!! defines the number of nonlinear nonzeros in the Jacobian. The number is zero
468!! if the model is linear and positive if the model is nonlinear.
469!!
470!! @param cntvect the control vector
471!! @param numnlnz the number of nonlinear nonzeros
472!!
473!! @ingroup REGISTRATION_OF_SIZES_F90
474!!
475Integer Function coidef_numnlnz( CntVect, NumNlNz )
476#if defined (dec_directives)
477!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_NumNlNz
478#if defined (itl)
479!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_NumNlNz
480!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_NUMNLNZ'::COIDEF_NumNlNz
481#endif
482#endif
483 Use conopt_utilities
484 Implicit None
485 Integer, dimension(NumCallBack) :: cntvect
486 Integer :: numnlnz
487
488 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
489 coidef_numnlnz = corruptcntr
490 Elseif ( numnlnz < 0 ) Then
491 coidef_numnlnz = rangeproblem; cntvect(indx_range) = 1
492#if defined (write20)
493 write(20,*) 'COIDEF_NumNlNz: Illegal argument. NumNlNz=',numnlnz
494#endif
495 Else
497 cntvect(indx_numnlnz) = numnlnz
498 Endif
499
500End function coidef_numnlnz
501
502!> defines the Number of Hessian Nonzeros.
503!!
504!! defines the number of nonzeros in the Hessian. The number is zero
505!! if the model is linear and positive if the model is nonlinear.
506!!
507!! @param cntvect the control vector
508!! @param numhess the number of nonzeros in Hessian
509!!
510!! @ingroup REGISTRATION_OF_SIZES_F90
511!!
512Integer Function coidef_numhess( CntVect, NumHess )
513#if defined (dec_directives)
514!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_NumHess
515#if defined (itl)
516!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_NumHess
517!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_NUMHESS'::COIDEF_NumHess
518#endif
519#endif
520 Use conopt_utilities
521 Implicit None
522 Integer, dimension(NumCallBack) :: cntvect
523 Integer :: numhess
524
525 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
526 coidef_numhess = corruptcntr
527 Elseif ( numhess < 0 ) Then
528 coidef_numhess = rangeproblem; cntvect(indx_range) = 1
529#if defined (write20)
530 write(20,*) 'COIDEF_NumHess: Illegal argument. NumHess=',numhess
531#endif
532 Else
534 cntvect(indx_numhess) = numhess
535 Endif
536
537End function coidef_numhess
538
539!> defines the Optimization Direction.
540!!
541!! defines the optimization direction. `OptDir = +1` defines maximization and
542!! `OptDir = -1` defines minimization. Setting an optimization direction is optional. If
543!! no optimization direction is set, the CONOPT will search for a feasible solution and
544!! then stop.
545!!
546!! @param cntvect the control vector
547!! @param optdir the optimization direction
548!!
549!! @ingroup REGISTRATION_OF_SIZES_F90
550!!
551Integer Function coidef_optdir( CntVect, OptDir )
552#if defined (dec_directives)
553!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_OptDir
554#if defined (itl)
555!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_OptDir
556!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_OPTDIR'::COIDEF_OptDir
557#endif
558#endif
559 Use conopt_utilities
560 Implicit None
561 Integer, dimension(NumCallBack) :: cntvect
562 Integer :: optdir
563
564 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
565 coidef_optdir = corruptcntr
566 Elseif ( optdir > 1 .or. optdir < -1 ) Then
567 coidef_optdir = rangeproblem; cntvect(indx_range) = 1
568#if defined (write20)
569 write(20,*) 'COIDEF_OptDir: Illegal argument. OptDir=',optdir
570#endif
571 Else
572 coidef_optdir = 0
573 cntvect(indx_optdir) = optdir
574 Endif
575
576End function coidef_optdir
577
578!> defines the Objective Variable.
579!!
580!! @param cntvect the control vector
581!! @param objvar the index of the objective variable
582!!
583!! @ingroup REGISTRATION_OF_SIZES_F90
584!!
585Integer Function coidef_objvar( CntVect, ObjVar )
586#if defined (dec_directives)
587!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ObjVar
588#if defined (itl)
589!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ObjVar
590!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_OBJVAR'::COIDEF_ObjVar
591#endif
592#endif
593 Use conopt_utilities
594 Implicit None
595 Integer, dimension(NumCallBack) :: cntvect
596 Integer :: objvar
597
598 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
599 coidef_objvar = corruptcntr
600 Elseif ( objvar < 0 ) Then
601 coidef_objvar = rangeproblem; cntvect(indx_range) = 1
602#if defined (write20)
603 write(20,*) 'COIDEF_ObjVar: Illegal argument. ObjVar=',objvar
604#endif
605 Else
606 coidef_objvar = 0
607 cntvect(indx_objindx) = objvar
608 cntvect(indx_objtyp ) = 1
609 Endif
610
611End function coidef_objvar
612
613!> defines the Objective Constraint.
614!!
615!! \note The constraint must be a Free Row, see argument `TYPE` in
616!! `ReadMatrix` in section \ref API_READMATRIX_F90 "ReadMatrix".
617!!
618!! If both an objective variable and constraint are set, the last one set will
619!! be used in the optimization. You can turn a previously defined objective off by defining variable
620!! or constraint 0 as the objective (Fortran notation) or variable or
621!! constraint -1 (C notation).
622!!
623!! @param cntvect the control vector
624!! @param objcon the index of the objective constraint
625!!
626!! @ingroup REGISTRATION_OF_SIZES_F90
627!!
628Integer Function coidef_objcon( CntVect, ObjCon )
629#if defined (dec_directives)
630!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ObjCon
631#if defined (itl)
632!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ObjCon
633!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_OBJCON'::COIDEF_ObjCon
634#endif
635#endif
636 Use conopt_utilities
637 Implicit None
638 Integer, dimension(NumCallBack) :: cntvect
639 Integer :: objcon
640
641 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
642 coidef_objcon = corruptcntr
643 Elseif ( objcon < 0 ) Then
644 coidef_objcon = rangeproblem; cntvect(indx_range) = 1
645#if defined (write20)
646 write(20,*) 'COIDEF_ObjCon: Illegal argument. ObjCon=',objcon
647#endif
648 Else
649 coidef_objcon = 0
650 cntvect(indx_objindx) = objcon
651 cntvect(indx_objtyp ) = -1
652 Endif
653
654End function coidef_objcon
655
656!> @defgroup DEF_COI_LICENSE ""
657!! define the License Information.
658!!
659!! The license consists of three integer codes and a string that defines the user.
660!! If the license is not defined or if it is incorrect then CONOPT will run in
661!! small-scale demo mode and it will only be able to solve small models.
662!!
663!! \if HIDDEN_DOC
664!! where the last argument must hold the length of `LicString`, e.g. <i>in the form
665!! of `strlen(LicString)`.</i> The length is added to conform to Fortran calling
666!! conventions.
667!! \endif
668!!
669!! @param licint1 the first license integer code
670!! @param licint2 the second license integer code
671!! @param licint3 the third license integer code
672!! @param licstring the license string
673
674!> @copydoc DEF_COI_LICENSE
675!! @param cntvect the control vector
676!!
677!! @ingroup REGISTRATION_OF_OPTIONS_F90
678!!
679Integer Function coidef_license( CntVect, LicInt1, LicInt2, LicInt3, LicString )
680#if defined (dec_directives)
681!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_License
682#if defined (itl)
683!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_License
684!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_LICENSE'::COIDEF_License
685#endif
686#endif
687 Use conopt_utilities
688 Implicit None
689 Integer, dimension(NumCallBack) :: cntvect
690 Character(len=*) :: licstring
691 Character(len=CO_LicLen) :: lictext
692 Integer :: licint1, licint2, licint3
693 Integer :: liccod1, liccod2, liccod3
694 Integer :: i, j
695 Character(len=8) date
696 Integer year, month, day
697
698 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
699 coidef_license = corruptcntr
700 Else
702 cntvect(indx_licint1) = licint1
703 cntvect(indx_licint2) = licint2
704 cntvect(indx_licint3) = licint3
705
706 call date_and_time( date ) ! Todays Date
707 read(date,"(I4,i2,i2)") year, month, day
708 liccod1 = 0
709 liccod2 = day + 30 * month + 360 * ( year-2000 )
710 liccod3 = 0
711 do i = 1, len(licstring)
712 liccod1 = liccod1 + ichar(licstring(i:i))*i
713 liccod3 = liccod3 + mod(ichar(licstring(i:i))*987,1048576)
714 enddo
715 lictext = licstring
716 i = indx_lictext
717 do j = 1, co_liclen, 4
718 Call packchar( lictext(j:j+3), cntvect(i) )
719 i = i + 1
720 enddo
721
722 cntvect(indx_liccod1) = liccod1
723 cntvect(indx_liccod2) = liccod2
724 cntvect(indx_liccod3) = liccod3
725 Endif
726
727End function coidef_license
728
729!> define the Base index for vectors.
730!!
731!! Some of the vectors that are passed between CONOPT and the callback routines
732!! point to other vectors. Examples are Row Indices and Start of Column pointers.
733!! You must define to CONOPT if you use Fortran conventions with 1 as the first
734!! element or C conventions with 0. The base will also determine how the index
735!! of the objective is interpreted.
736!!
737!! @param cntvect the control vector
738!! @param base the base index for vectors
739!!
740!! @ingroup REGISTRATION_OF_OPTIONS_F90
741!!
742Integer Function coidef_base( CntVect, Base )
743#if defined (dec_directives)
744!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_BASE
745#if defined (itl)
746!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Base
747!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_BASE'::COIDEF_Base
748#endif
749#endif
750 Use conopt_utilities
751 Implicit None
752 Integer, dimension(NumCallBack) :: cntvect
753 Integer :: base
754
755 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
756 coidef_base = corruptcntr
757 Elseif ( base < 0 .or. base > 1) Then
758 coidef_base = rangeproblem; cntvect(indx_range) = 1
759#if defined (write20)
760 write(20,*) 'COIDEF_Base: Illegal argument. NumBase=',base
761#endif
762 Else
763 coidef_base = 0
764 cntvect(indx_base) = base
765 Endif
766
767End function coidef_base
768
769!> define Fortran Conventions for Argument Passing.
770!!
771!! This is equivalent to calling coidef_base(1) in Fortran
772!! or COIDEF_Base(1) in C.
773!!
774!! @param cntvect the control vector
775!!
776!! @ingroup REGISTRATION_OF_OPTIONS_F90
777!!
778Integer Function coidef_fortran( CntVect )
779#if defined (dec_directives)
780!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Fortran
781#if defined (itl)
782!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Fortran
783!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_FORTRAN'::COIDEF_Fortran
784#endif
785#endif
786 Use conopt_utilities
787 Implicit None
788 Integer, dimension(NumCallBack) :: cntvect
789
790 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
791 coidef_fortran = corruptcntr
792 Else
794 cntvect(indx_fortran) = 1
795 Endif
796
797End function coidef_fortran
798
799!> define C Conventions for Argument Passing.
800!!
801!! This is equivalent to calling coidef_base(0) in Fortran
802!! or COIDEF_Base(0) in C.
803!!
804!! @param cntvect the control vector
805!!
806!! @ingroup REGISTRATION_OF_OPTIONS_F90
807!!
808Integer Function coidef_c( CntVect )
809#if defined (dec_directives)
810!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_C
811#if defined (itl)
812!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_C
813!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_C'::COIDEF_C
814#endif
815#endif
816 Use conopt_utilities
817 Implicit None
818 Integer, dimension(NumCallBack) :: cntvect
819
820 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
821 coidef_c = corruptcntr
822 Else
823 coidef_c = 0
824 cntvect(indx_fortran) = 0
825 Endif
826
827End function coidef_c
828
829!> @defgroup DEF_COI_ITLIM ""
830!! define the Iteration Limit.
831!!
832!! By default CONOPT uses an iteration limit of <b>1 million iterations</b>.
833!! This method can be used to set a new iteration limit.
834!!
835!! The call is optional.
836!!
837!! @param itlim the iteration limit
838
839!> @copydoc DEF_COI_ITLIM
840!! @param cntvect the control vector
841!!
842!! @ingroup REGISTRATION_OF_OPTIONS_F90
843!!
844Integer Function coidef_itlim( CntVect, ItLim )
845#if defined (dec_directives)
846!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ItLim
847#if defined (itl)
848!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ItLim
849!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_ITLIM'::COIDEF_ItLim
850#endif
851#endif
852 Use conopt_utilities
853 Implicit None
854 Integer, dimension(NumCallBack) :: cntvect
855 Integer :: itlim
856
857 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
858 coidef_itlim = corruptcntr
859 Elseif ( itlim < 0 ) Then
860 coidef_itlim = rangeproblem; cntvect(indx_range) = 1
861#if defined (write20)
862 write(20,*) 'COIDEF_ItLim: Illegal argument. ItLim=',itlim
863#endif
864 Else
865 coidef_itlim = 0
866 cntvect(indx_itlim) = itlim
867 Endif
868
869End function coidef_itlim
870
871!> @defgroup DEF_COI_ERRLIM ""
872!! define the Error Limit.
873!!
874!! The nonlinear functions may not be defined in all points, and the user written
875!! callback routine `FDEval` has an argument for
876!! telling CONOPT if a point is “bad”. CONOPT may try other points to avoid “bad”
877!! points up to a defined error limit (as specified by a call to this method). The default error limit is
878!! <b>zero</b>, i.e. CONOPT will by default stop if a “bad” point is encountered.
879!!
880!! The call is optional.
881!!
882!! @param errlim the error limit
883
884!> @copydoc DEF_COI_ERRLIM
885!! @param cntvect the control vector
886!!
887!! @ingroup REGISTRATION_OF_OPTIONS_F90
888!!
889Integer Function coidef_errlim( CntVect, ErrLim )
890#if defined (dec_directives)
891!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ErrLim
892#if defined (itl)
893!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ErrLim
894!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_ERRLIM'::COIDEF_ErrLim
895#endif
896#endif
897 Use conopt_utilities
898 Implicit None
899 Integer, dimension(NumCallBack) :: cntvect
900 Integer :: errlim
901
902 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
903 coidef_errlim = corruptcntr
904 Elseif ( errlim < 0 ) Then
905 coidef_errlim = rangeproblem; cntvect(indx_range) = 1
906#if defined (write20)
907 write(20,*) 'COIDEF_ErrLim: Illegal argument. ErrLim=',errlim
908#endif
909 Else
910 coidef_errlim = 0
911 cntvect(indx_errlim) = errlim
912 Endif
913
914End function coidef_errlim
915
916!> @defgroup DEF_COI_RESLIM ""
917!! define resource limit.
918!!
919!! CONOPT will by default allow the optimization to run for <b>1 million
920!! seconds</b>. A new limit can be set by a call to this method.
921!!
922!! \note `ResLim` is a double precision number.
923!!
924!! @param reslim the solve time limit in seconds
925
926!> @copydoc DEF_COI_RESLIM
927!! @param cntvect the control vector
928!!
929!! @ingroup REGISTRATION_OF_OPTIONS_F90
930!!
931Integer Function coidef_reslim( CntVect, ResLim )
932#if defined (dec_directives)
933!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ResLim
934#if defined (itl)
935!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ResLim
936!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_RESLIM'::COIDEF_ResLim
937#endif
938#endif
939 Use conopt_utilities
940 Implicit None
941 Integer, dimension(NumCallBack) :: cntvect
942 Real(co_r) :: reslim
943
944 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
945 coidef_reslim = corruptcntr
946 Elseif ( reslim < 0.0_co_r ) Then
947 coidef_reslim = rangeproblem; cntvect(indx_range) = 1
948#if defined (write20)
949 write(20,*) 'COIDEF_ResLim: Illegal argument. ResLim=',reslim
950#endif
951 Else
952 coidef_reslim = 0
953 Call storereal( cntvect, indx_reslim, reslim )
954 Endif
955
956End function coidef_reslim
957
958!> @defgroup DEF_COI_MAXHEAP ""
959!! define Limit on Heap Memory.
960!!
961!! By default CONOPT will allocate the memory it needs from the computers heap
962!! memory using `Allocate` or `malloc` calls. For very large models CONOPT may try
963!! to allocate more than the available physical memory and the responsiveness of
964!! the computer may suffer. This may not be acceptable in certain server
965!! environments. This method is used to define a limit on the amount of heap
966!! memory that CONOPT will allocate.
967!! If CONOPT reaches a point where it needs more memory than allowed it will try
968!! to continue without extra memory (if this is possible) or it will stop with an
969!! out of memory message and the sovle will return the value <b>113</b> or
970!! <b>114</b>.
971!!
972!! `MaxHeap` is measured in <b>MegaBytes</b>. A positive `MaxHeap` value indicates
973!! a limit while `Maxheap = 0.0` indicates that the limit is set by the physical
974!! memory or the virtual memory system on the machine. After you have solved a
975!! model you can query the amount of memory actually used with the
976!! coiget_maxheapused() or COIGET_MaxHeapUsed().
977!!
978!! The call is optional.
979!!
980!! @param maxheap the limit on heap memory
981
982!> @copydoc DEF_COI_MAXHEAP ""
983!! @param cntvect the control vector
984!!
985!! @ingroup REGISTRATION_OF_OPTIONS_F90
986!!
987Integer Function coidef_maxheap( CntVect, MaxHeap )
988#if defined (dec_directives)
989!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_MaxHeap
990#if defined (itl)
991!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_MaxHeap
992!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_MAXHEAP'::COIDEF_MaxHeap
993#endif
994#endif
995 Use conopt_utilities
996 Implicit None
997 Integer, dimension(NumCallBack) :: cntvect
998 Real(co_r) :: maxheap
999
1000 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1001 coidef_maxheap = corruptcntr
1002 Elseif ( maxheap < 0.0_co_r ) Then
1003 coidef_maxheap = rangeproblem; cntvect(indx_range) = 1
1004#if defined (write20)
1005 write(20,*) 'COIDEF_Maxheap: Illegal argument. Maxheap=',maxheap
1006#endif
1007 Else
1008 coidef_maxheap = 0
1009 Call storereal( cntvect, indx_maxheap, maxheap )
1010 Endif
1011
1012End function coidef_maxheap
1013
1014!> handling of the initial status values.
1015!!
1016!! CONOPT can take advantage of initial ‘Status’ information about the variables
1017!! and constraints. This is information of the type: Variable number \f$i\f$ is
1018!! basic, variable \f$j\f$ is superbasic, variable \f$k\f$ is at lower bound
1019!! etc.
1020!!
1021!! \note If you are going to provide Status information when building the model then
1022!! CONOPT must be informed a call to this method with the second argument
1023!! equal to 1 or 2 (depending on the definition you choose). You can turn it off
1024!! again with another call with the value 0 (the default initial value).
1025!!
1026!! @param cntvect the control vector
1027!! @param inistat the initial status
1028!!
1029!! @ingroup REGISTRATION_OF_OPTIONS_F90
1030!!
1031Integer Function coidef_inistat( CntVect, IniStat )
1032#if defined (dec_directives)
1033!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_IniStat
1034#if defined (itl)
1035!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_IniStat
1036!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_INISTAT'::COIDEF_IniStat
1037#endif
1038#endif
1039 Use conopt_utilities
1040 Implicit None
1041 Integer, dimension(NumCallBack) :: cntvect
1042 Integer :: inistat
1043
1044 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1045 coidef_inistat = corruptcntr
1046 Elseif ( inistat < 0 .or. inistat > 2 ) Then
1047 coidef_inistat = rangeproblem; cntvect(indx_range) = 1
1048#if defined (write20)
1049 write(20,*) 'COIDEF_IniStat: Illegal argument. IniStat=',inistat
1050#endif
1051 Else
1052 coidef_inistat = 0
1053 cntvect(indx_inistat) = inistat
1054 Endif
1055
1056End function coidef_inistat
1057
1058!> @defgroup DEF_COI_FVINCLIN ""
1059!! include the linear terms in function evaluations.
1060!!
1061!! CONOPT assumes that the function values returned by the user defined callback
1062!! routine `FDEval` only include nonlinear terms, i.e. terms that correspond to
1063!! variables that appear nonlinearly in the particular constraint.
1064!!
1065!! If you prefer your `FDEval` routine to return function values as the
1066!! sum of both linear and nonlinear terms then you must inform CONOPT by calling
1067!! this method with `FVincLin = 1`. `FVincLin = 0` will return CONOPT to
1068!! the default behavior.
1069!!
1070!! @param fvinclin the linear terms in functions
1071
1072!> @copydoc DEF_COI_FVINCLIN
1073!! @param cntvect the control vector
1074!!
1075!! @ingroup REGISTRATION_OF_OPTIONS_F90
1076!!
1077Integer Function coidef_fvinclin( CntVect, FVincLin )
1078#if defined (dec_directives)
1079!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_FVincLin
1080#if defined (itl)
1081!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_FVincLin
1082!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_FVINCLIN'::COIDEF_FVincLin
1083#endif
1084#endif
1085 Use conopt_utilities
1086 Implicit None
1087 Integer, dimension(NumCallBack) :: cntvect
1088 Integer :: fvinclin
1089
1090 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1091 coidef_fvinclin = corruptcntr
1092 Elseif ( fvinclin < 0 .or. fvinclin > 1) Then
1093 coidef_fvinclin = rangeproblem; cntvect(indx_range) = 1
1094#if defined (write20)
1095 write(20,*) 'COIDEF_FVincLin: Illegal argument. FVincLin=',fvinclin
1096#endif
1097 Else
1098 coidef_fvinclin = 0
1099 cntvect(indx_fvinclin) = fvinclin
1100 Endif
1101
1102End function coidef_fvinclin
1103
1104!> @defgroup DEF_COI_FVFORALL ""
1105!! call the FDEval for all constraints, including linear constraints.
1106!!
1107!! CONOPT will usually only call the user provided `FDEval` routine for
1108!! nonlinear constraints. However, some models may have constant terms included
1109!! in `FDEval` instead of in the right hand side, also for linear constraints.
1110!!
1111!! \note If your `FDEval` routine is programmed this way you must tell CONOPT to
1112!! call `FDEval` for all constraints, linear as well as nonlinear, by calling
1113!! this method with `FVforAll = 1`. Calling again with `FVforAll = 0` will
1114!! return CONOPT to its default behavior.
1115!!
1116!! @param fvforall the linear constraints in functions
1117
1118!> @copydoc DEF_COI_FVFORALL
1119!! @param cntvect the control vector
1120!!
1121!! @ingroup REGISTRATION_OF_OPTIONS_F90
1122!!
1123Integer Function coidef_fvforall( CntVect, FVforAll )
1124#if defined (dec_directives)
1125!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_FVforAll
1126#if defined (itl)
1127!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_FVforAll
1128!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_FVFORALL'::COIDEF_FVforAll
1129#endif
1130#endif
1131 Use conopt_utilities
1132 Implicit None
1133 Integer, dimension(NumCallBack) :: cntvect
1134 Integer :: fvforall
1135
1136 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1137 coidef_fvforall = corruptcntr
1138 Elseif ( fvforall < 0 .or. fvforall > 1 ) Then
1139 coidef_fvforall = rangeproblem; cntvect(indx_range) = 1
1140#if defined (write20)
1141 write(20,*) 'COIDEF_FVforAll: Illegal argument. FVforAll=',fvforall
1142#endif
1143 Else
1144 coidef_fvforall = 0
1145 cntvect(indx_fvforall) = fvforall
1146 Endif
1147
1148End function coidef_fvforall
1149
1150!> @defgroup DEF_COI_MAXSUP ""
1151!! limit on superbasics.
1152!!
1153!! CONOPT uses a reduced gradient algorithm and performs its optimization in a
1154!! space of “Superbasic” variables. It needs a square matrix of size the number of
1155!! superbasic variables for estimated second order information. Since this matrix
1156!! can be fairly large, CONOPT places a limit that by default is at least <b>500
1157!! rows and columns</b>. For larger models CONOPT reserves around <b>25% of the
1158!! memory</b> needed for other purposes to this matrix. If you have a model with
1159!! many superbasic variables it may be advantageous to increase this limit.
1160!!
1161!! \note If you provide second order information, through one of the `2DLagr`,
1162!! `2DDir`, or `2DDirLag` routines, then it is usually not worth while to increase
1163!! `MaxSup`.
1164!!
1165!! The limit can also be defined in an options file or options routine by setting
1166!! `LFNSUP`.
1167!!
1168!! @param maxsup the limit on superbasics
1169
1170!> @copydoc DEF_COI_MAXSUP
1171!! @param cntvect the control vector
1172!!
1173!! @ingroup REGISTRATION_OF_OPTIONS_F90
1174!!
1175Integer Function coidef_maxsup( CntVect, MaxSup )
1176#if defined (dec_directives)
1177!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_MaxSup
1178#if defined (itl)
1179!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_MaxSup
1180!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_MAXSUP'::COIDEF_MaxSup
1181#endif
1182#endif
1183 Use conopt_utilities
1184 Implicit None
1185 Integer, dimension(NumCallBack) :: cntvect
1186 Integer :: maxsup
1187
1188 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1189 coidef_maxsup = corruptcntr
1190 Elseif ( maxsup < -1 ) Then
1191 coidef_maxsup = rangeproblem; cntvect(indx_range) = 1
1192#if defined (write20)
1193 write(20,*) 'COIDEF_MaxSup: Illegal argument. MaxSup=',maxsup
1194#endif
1195 Else
1196 coidef_maxsup = 0
1197 cntvect(indx_maxsup) = maxsup
1198 Endif
1199
1200End function coidef_maxsup
1201
1202!> @defgroup DEF_COI_SQUARE ""
1203!! square models.
1204!!
1205!! CONOPT has a special routine for solve square sets of equations without an
1206!! objective function.
1207!!
1208!! @param square `Square = 1` informs CONOPT that the model is Square. `Square = 0` is the default used for an ordinary optimization model.
1209
1210!> @copydoc DEF_COI_SQUARE
1211!! @param cntvect the control vector
1212!!
1213!! @ingroup REGISTRATION_OF_OPTIONS_F90
1214!!
1215Integer Function coidef_square( CntVect, Square )
1216#if defined (dec_directives)
1217!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Square
1218#if defined (itl)
1219!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Square
1220!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_SQUARE'::COIDEF_Square
1221#endif
1222#endif
1223 Use conopt_utilities
1224 Implicit None
1225 Integer, dimension(NumCallBack) :: cntvect
1226 Integer :: square
1227
1228 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1229 coidef_square = corruptcntr
1230 Elseif ( square < 0 .or. square > 1 ) Then
1231 coidef_square = rangeproblem; cntvect(indx_range) = 1
1232#if defined (write20)
1233 write(20,*) 'COIDEF_Square: Illegal argument. Square=',square
1234#endif
1235 Else
1236 coidef_square = 0
1237 cntvect(indx_square) = square
1238 Endif
1239
1240End function coidef_square
1241
1242!> @defgroup DEF_COI_EMPTYROW ""
1243!! allow empty rows.
1244!!
1245!! CONOPT performs many tests on the input data and by default it does not allow
1246!! empty rows, i.e. constraints that do not depend on any variables. In some
1247!! modeling systems environments it can be useful to allow empty rows.
1248!!
1249!! @param emptyrow 1 allows empty rows, 0 is the default behavior.
1250
1251!> @copydoc DEF_COI_EMPTYROW
1252!! @param cntvect the control vector
1253!!
1254!! @ingroup REGISTRATION_OF_OPTIONS_F90
1255!!
1256Integer Function coidef_emptyrow( CntVect, EmptyRow )
1257#if defined (dec_directives)
1258!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_EmptyRow
1259#if defined (itl)
1260!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_EmptyRow
1261!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_EMPTYROW'::COIDEF_EmptyRow
1262#endif
1263#endif
1264 Use conopt_utilities
1265 Implicit None
1266 Integer, dimension(NumCallBack) :: cntvect
1267 Integer :: emptyrow
1268
1269 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1270 coidef_emptyrow = corruptcntr
1271 Elseif ( emptyrow < 0 .or. emptyrow > 1 ) Then
1272 coidef_emptyrow = rangeproblem; cntvect(indx_range) = 1
1273#if defined (write20)
1274 write(20,*) 'COIDEF_EmptyRow: Illegal argument. EmptyRow=',emptyrow
1275#endif
1276 Else
1277 coidef_emptyrow = 0
1278 cntvect(indx_emptyrow) = emptyrow
1279 Endif
1280
1281End function coidef_emptyrow
1282
1283!> @defgroup DEF_COI_EMPTYCOL ""
1284!! allow empty columns.
1285!!
1286!! CONOPT performs many tests on the input data and by default it does not allow
1287!! empty columns, i.e. variables that do not appear in any constraints. In some
1288!! modeling systems environments it can be useful to allow empty columns. To
1289!! bypass the usual tests you must inform CONOPT that empty columns should be
1290!! allowed.
1291!!
1292!! @param emptycol 1 allows empty columns, 0 is the default behaviour.
1293
1294!> @copydoc DEF_COI_EMPTYCOL
1295!! @param cntvect the control vector
1296!!
1297!! @ingroup REGISTRATION_OF_OPTIONS_F90
1298!!
1299Integer Function coidef_emptycol( CntVect, EmptyCol )
1300#if defined (dec_directives)
1301!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_EmptyCol
1302#if defined (itl)
1303!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_EmptyCol
1304!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_EMPTYCOL'::COIDEF_EmptyCol
1305#endif
1306#endif
1307 Use conopt_utilities
1308 Implicit None
1309 Integer, dimension(NumCallBack) :: cntvect
1310 Integer :: emptycol
1311
1312 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1313 coidef_emptycol = corruptcntr
1314 Elseif ( emptycol < 0 .or. emptycol > 1 ) Then
1315 coidef_emptycol = rangeproblem; cntvect(indx_range) = 1
1316#if defined (write20)
1317 write(20,*) 'COIDEF_EmptyCol: Illegal argument. EmptyCol=',emptycol
1318#endif
1319 Else
1320 coidef_emptycol = 0
1321 cntvect(indx_emptycol) = emptycol
1322 Endif
1323
1324End function coidef_emptycol
1325
1326!> @defgroup DEF_COI_DISCONT ""
1327!! allow discontinuous functions and derivatives.
1328!!
1329!! CONOPT assumes that all functions are smooth with smooth derivatives and that
1330!! these functions and derivatives can be computed with a noise level close to the
1331!! machine precision. CONOPT can also be used on models with non-smooth
1332!! derivatives, e.g. models with `ABS` or `MIN` or `MAX` functions, but the
1333!! algorithm will still work as if all functions and derivatives are smooth. A few
1334!! internal tests may fail for a model with discontinuous derivatives. The call will only
1335!! turn the tests off or on; it will not alter the optimization behavior.
1336!!
1337!! @param discont 1 allows discontinuous functions and derivatives, 0 is the default behaviour.
1338
1339!> @copydoc DEF_COI_DISCONT
1340!! @param cntvect the control vector
1341!!
1342!! @ingroup REGISTRATION_OF_OPTIONS_F90
1343!!
1344Integer Function coidef_discont( CntVect, DisCont )
1345#if defined (dec_directives)
1346!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_DisCont
1347#if defined (itl)
1348!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_DisCont
1349!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_DISCONT'::COIDEF_DisCont
1350#endif
1351#endif
1352 Use conopt_utilities
1353 Implicit None
1354 Integer, dimension(NumCallBack) :: cntvect
1355 Integer :: discont
1356
1357 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1358 coidef_discont = corruptcntr
1359 Elseif ( discont < 0 .or. discont > 1 ) Then
1360 coidef_discont = rangeproblem; cntvect(indx_range) = 1
1361#if defined (write20)
1362 write(20,*) 'COIDEF_DisCont: Illegal argument. DisCont=',discont
1363#endif
1364 Else
1365 coidef_discont = 0
1366 cntvect(indx_discont) = discont
1367 Endif
1368
1369End function coidef_discont
1370
1371!> factor for Hessian density relative to Jacobian density HessFac.
1372!!
1373!! CONOPT will not use the Hessian of the Lagrangian if it is too dense. The limit
1374!! on the number of nonzero Hessian elements (on an below the diagonal) is set to
1375!! `HessFac` times the number of nonlinear Jacobian elements,:vertical resize 120
1376!! and the default value of `HessFac` is 10. The assumption is
1377!! that computations involving a dense Hessian will be too expensive.
1378!!
1379!! The Hessian factor can also be defined by defining the option `RVHESS`.
1380!!
1381!! @param cntvect the control vector
1382!! @param hessfac the threshold factor for Hessian density relative to Jacobian density
1383!!
1384!! @ingroup REGISTRATION_OF_OPTIONS_F90
1385!!
1386Integer Function coidef_hessfac( CntVect, HessFac )
1387#if defined (dec_directives)
1388!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_HessFac
1389#if defined (itl)
1390!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_HessFac
1391!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_HESSFAC'::COIDEF_HessFac
1392#endif
1393#endif
1394 Use conopt_utilities
1395 Implicit None
1396 Integer, dimension(NumCallBack) :: cntvect
1397 Real(co_r) :: hessfac
1398
1399 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1400 coidef_hessfac = corruptcntr
1401 Elseif ( hessfac < 0.0_co_r ) Then
1402#if defined (write20)
1403 write(20,*) 'COIDEF_HessFac: Illegal argument. HessFac=',hessfac
1404#endif
1405 coidef_hessfac = rangeproblem; cntvect(indx_range) = 1
1406 Else
1407 coidef_hessfac = 0
1408 Call storereal( cntvect, indx_hessfac, hessfac )
1409 Endif
1410
1411End function coidef_hessfac
1412
1413!> @defgroup DEF_COI_DEBUGFV ""
1414!! turn Debugging of FDEval on and off.
1415!!
1416!! CONOPT has a Function and Derivative Debugger that can check if the function
1417!! values and derivatives computed by `FDEval` seem to be consistent and the
1418!! derivatives are consistent with the sparsity pattern of the Jacobian.
1419!!
1420!! The interpretation of `DebugFV` is:
1421!!
1422!! - <b>0:</b> No debugging (the default value)
1423!! - <b>-1:</b> Perform debugging in the initial point only.
1424!! - <b>+n:</b> Perform debugging every n’th iteration.
1425!!
1426!! The value can also be defined in an options file or options routine be setting
1427!! `LKDEBG`. Error messages and error return codes are described in
1428!! \ref API_ERROR_RETURN_CODES.
1429!!
1430!! @param debugfv the flag to enable debugging of function evaluations
1431
1432!> @copydoc DEF_COI_DEBUGFV
1433!! @param cntvect the control vector
1434!!
1435!! @ingroup REGISTRATION_OF_OPTIONS_F90
1436!!
1437Integer Function coidef_debugfv( CntVect, DebugFV )
1438#if defined (dec_directives)
1439!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_DebugFV
1440#if defined (itl)
1441!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_DebugFV
1442!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_DEBUGFV'::COIDEF_DebugFV
1443#endif
1444#endif
1445 Use conopt_utilities
1446 Implicit None
1447 Integer, dimension(NumCallBack) :: cntvect
1448 Integer :: debugfv
1449
1450 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1451 coidef_debugfv = corruptcntr
1452 Elseif ( debugfv < -1 ) Then
1453 coidef_debugfv = rangeproblem; cntvect(indx_range) = 1
1454#if defined (write20)
1455 write(20,*) 'COIDEF_DebugFV: Illegal argument. DebugFV=',debugfv
1456#endif
1457 Else
1458 coidef_debugfv = 0
1459 cntvect(indx_debugfv) = debugfv
1460 Endif
1461
1462End function coidef_debugfv
1463
1464!> @defgroup DEF_COI_DEBUG2D ""
1465!! turn debugging of 2nd derivatives on and off.
1466!!
1467!! CONOPT has a rudimentary routine for checking if the 2<sup>nd</sup> derivatives
1468!! computed by `2DLagr`, `2DDir`, or `2DDirLag` seem to be consistent with the
1469!! derivatives computed by `FDEval`.
1470!!
1471!! The interpretation of `Debug2D` is:
1472!!
1473!! - <b>0:</b> No debugging (the default value)
1474!! - <b>-1:</b> Perform debugging in the initial point only.
1475!! - <b>+n:</b> Perform debugging every n’th iteration.
1476!!
1477!! The value can also be defined in an options file or options routine be setting
1478!! `LKDEB2`. Error return codes and examples of messages can be found in
1479!! \ref API_ERROR_RETURN_CODES.
1480!!
1481!! @param debug2d the flag to enable the debugging of the second derivative evaulations
1482
1483!> @copydoc DEF_COI_DEBUG2D
1484!! @param cntvect the control vector
1485!!
1486!! @ingroup REGISTRATION_OF_OPTIONS_F90
1487!!
1488Integer Function coidef_debug2d( CntVect, Debug2D )
1489#if defined (dec_directives)
1490!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Debug2D
1491#if defined (itl)
1492!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Debug2D
1493!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_DEBUG2D'::COIDEF_Debug2D
1494#endif
1495#endif
1496 Use conopt_utilities
1497 Implicit None
1498 Integer, dimension(NumCallBack) :: cntvect
1499 Integer :: debug2d
1500
1501 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1502 coidef_debug2d = corruptcntr
1503 Elseif ( debug2d < -1 ) Then
1504 coidef_debug2d = rangeproblem; cntvect(indx_range) = 1
1505#if defined (write20)
1506 write(20,*) 'COIDEF_Debug2D: Illegal argument. Debug2D=',debug2d
1507#endif
1508 Else
1509 coidef_debug2d = 0
1510 cntvect(indx_debug2d) = debug2d
1511 Endif
1512
1513End function coidef_debug2d
1514
1515!> define zero noise level.
1516!!
1517!! CONOPT has a Function and Derivative Debugger that also tests whether variables that
1518!! should not appear in an equation actually have an influence on the function
1519!! value: the variables that should not appear are all perturbed by random amounts
1520!! and the function is called again. If the function changes by the slightest
1521!! amount, this must have been caused by one of the variables that should not
1522!! influence the equation, and an error has been identified.
1523!!
1524!! However, some implementations may give very small function changes as shown by
1525!! the following example: Equation \f$i\f$ depends on \f$\sum_{j \neq i}X(j)\f$.
1526!! Initially, compute \f$XS = \sum_{i}X(i)\f$ and the compute \f$XS-X(i)\f$ for
1527!! use in `Equation` \f$i\f$. Because of the round-off errors involved in
1528!! computing \f$XS-X(i)\f$, \f$X(i)\f$ may seem to appear in `Equation` \f$i\f$.
1529!! For these rare cases you may need to define a small <i>"zero noise level"</i>
1530!! and all derivatives less that this value will not be considered errors.
1531!! The default value is zero.
1532!!
1533!! @param cntvect the control vector
1534!! @param zeronoise the threshold for zero noise level in function derivatives
1535!!
1536!! @ingroup REGISTRATION_OF_OPTIONS_F90
1537!!
1538Integer Function coidef_zeronoise( CntVect, ZeroNoise )
1539#if defined (dec_directives)
1540!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ZeroNoise
1541#if defined (itl)
1542!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ZeroNoise
1543!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_ZERONOISE'::COIDEF_ZeroNoise
1544#endif
1545#endif
1546 Use conopt_utilities
1547 Implicit None
1548 Integer, dimension(NumCallBack) :: cntvect
1549 Real(co_r) :: zeronoise
1550
1551 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1552 coidef_zeronoise = corruptcntr
1553 Elseif ( zeronoise < 0.0_co_r ) Then
1554 coidef_zeronoise = rangeproblem; cntvect(indx_range) = 1
1555#if defined (write20)
1556 write(20,*) 'COIDEF_ZeroNoise: Illegal argument. ZeroNoise=',zeronoise
1557#endif
1558 Else
1560 Call storereal( cntvect, indx_zeronoise, zeronoise )
1561 Endif
1562
1563End function coidef_zeronoise
1564
1565!> @defgroup DEF_COI_THREADS ""
1566!! number of threads allowed internally in CONOPT.
1567!!
1568!! As discussed in \ref API_MULTI_THREADING CONOPT can use
1569!! multiple threads using the `OpenMP` standard. The multi-threading capability is
1570!! divided into three areas: <b>(1)</b> Internally in CONOPT, <b>(2)</b> during
1571!! function and derivative calls using the `FDEval` callback routine,
1572!! and <b>(3)</b> during directional 2<sup>nd</sup> derivative
1573!! calls using the 2DDir callback routine.
1574!!
1575!! This method is used to define how many threads can be used internally
1576!! in CONOPT. The argument `ThreadS` is interpreted as follows:
1577!!
1578!! - <b>ThreadS = 0:</b> use `MaxThread` threads, as many as the `OpenMP` system will allocate,
1579!! - <b>ThreadS = 1:</b> use one thread <i>(this is the default)</i>,
1580!! - <b>ThreadS > 1:</b> use `min(ThreadS,MaxThread)` threads.
1581!!
1582!! @param threads the number of threads allowed internally
1583
1584!> @copydoc DEF_COI_THREADS
1585!! @param cntvect the control vector
1586!!
1587!! @ingroup REGISTRATION_OF_OPTIONS_F90
1588!!
1589Integer Function coidef_threads( CntVect, Threads )
1590#if defined (dec_directives)
1591!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Threads
1592#if defined (itl)
1593!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Threads
1594!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_THREADS'::COIDEF_Threads
1595#endif
1596#endif
1597 Use conopt_utilities
1598 Implicit None
1599 Integer, dimension(NumCallBack) :: cntvect
1600 Integer :: threads
1601
1602 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1603 coidef_threads = corruptcntr
1604 Elseif ( threads < 0 ) Then
1605 coidef_threads = rangeproblem; cntvect(indx_range) = 1
1606#if defined (write20)
1607 write(20,*) 'COIDEF_Threads: Illegal argument. Threads=',threads
1608#endif
1609 Else
1610 coidef_threads = 0
1611 cntvect(indx_threads) = threads
1612 Endif
1613
1614End function coidef_threads
1615
1616!> @defgroup DEF_COI_THREADF ""
1617!! number of threads allowed for simultaneous `FDEval` calls.
1618!!
1619!! This method can be used to define how many threads can be used for
1620!! simultaneous `FDEval` calls. The argument `ThreadF` is interpreted as follows:
1621!!
1622!! - <b>ThreadF = 0:</b> use the same number of threads as internally in CONOPT
1623!! <i>(this is the default)</i>,
1624!!
1625!! - <b>ThreadF = 1:</b> use one thread,
1626!!
1627!! - <b>ThreadF > 1:</b> use `min(ThreadS,ThreadF)` threads.
1628!!
1629!! @param threadf the number of threads for simultaneous `FDEval` calls
1630
1631!> @copydoc DEF_COI_THREADF
1632!! @param cntvect the control vector
1633!!
1634!! @ingroup REGISTRATION_OF_OPTIONS_F90
1635!!
1636Integer Function coidef_threadf( CntVect, ThreadF )
1637#if defined (dec_directives)
1638!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ThreadF
1639#if defined (itl)
1640!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ThreadF
1641!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_THREADF'::COIDEF_ThreadF
1642#endif
1643#endif
1644 Use conopt_utilities
1645 Implicit None
1646 Integer, dimension(NumCallBack) :: cntvect
1647 Integer :: threadf
1648
1649 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1650 coidef_threadf = corruptcntr
1651 Elseif ( threadf < 0 ) Then
1652 coidef_threadf = rangeproblem; cntvect(indx_range) = 1
1653#if defined (write20)
1654 write(20,*) 'COIDEF_ThreadF: Illegal argument. ThreadF=',threadf
1655#endif
1656 Else
1657 coidef_threadf = 0
1658 cntvect(indx_threadf) = threadf
1659 Endif
1660
1661End function coidef_threadf
1662
1663!> @defgroup DEF_COI_THREAD2D ""
1664!! number of threads allowed for simultaneous `2DDir` calls.
1665!!
1666!! This method can be used to define how many threads can be used
1667!! for simultaneous `2DDir` calls. The argument `Thread2D` is interpreted as
1668!! follows:
1669!!
1670!! - <b>Thread2D = 0:</b> use the same number of threads as internally in CONOPT
1671!! <i>(this is the default)</i>,
1672!!
1673!! - <b>Thread2D = 1:</b> use one thread,
1674!!
1675!! - <b>Thread2D > 1:</b> use `min(Thread2D,ThreadF)` threads.
1676!!
1677!! @param thread2d the number of threads for simultaneous `2DDir` calls
1678
1679!> @copydoc DEF_COI_THREAD2D
1680!! @param cntvect the control vector
1681!!
1682!! @ingroup REGISTRATION_OF_OPTIONS_F90
1683!!
1684Integer Function coidef_thread2d( CntVect, Thread2D )
1685#if defined (dec_directives)
1686!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Thread2D
1687#if defined (itl)
1688!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Thread2D
1689!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_THREAD2D'::COIDEF_Thread2D
1690#endif
1691#endif
1692 Use conopt_utilities
1693 Implicit None
1694 Integer, dimension(NumCallBack) :: cntvect
1695 Integer :: thread2d
1696
1697 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1698 coidef_thread2d = corruptcntr
1699 Elseif ( thread2d < 0 ) Then
1700 coidef_thread2d = rangeproblem; cntvect(indx_range) = 1
1701#if defined (write20)
1702 write(20,*) 'COIDEF_Thread2D: Illegal argument. Thread2D=',thread2d
1703#endif
1704 Else
1705 coidef_thread2d = 0
1706 cntvect(indx_thread2d) = thread2d
1707 Endif
1708
1709End function coidef_thread2d
1710
1711!> @defgroup DEF_COI_THREADC ""
1712!! check for thread compatibility.
1713!!
1714!! When using multiple threads, the result of the execution is in most cases
1715!! independent of the number of threads. However, a few operations mostly related
1716!! to summations can create slightly different results depending on the number of
1717!! threads, and therefore the results may depend on the number of threads.
1718!! `ThreadC` can be used to force reproducible results. The execution is done as
1719!! if there were `ThreadC` threads independent of the actual number of `ThreadS`
1720!! <i>(`ThreadS` > `ThreadC`)</i>.
1721!!
1722!! This method can be used to define how many threads CONOPT should simulate.
1723!! The argument `ThreadC` is interpreted as follows:
1724!!
1725!! - <b>ThreadC = 0:</b> let the execution be controlled by `ThreadS` defined above,
1726!! - <b>ThreadC > 1:</b> simulate the use of `ThreadC > ThreadS` threads.
1727!!
1728!! <b>The upper bound on `ThreadC` is currently 8.</b>
1729!!
1730!! @param threadc the number of threads CONOPT should simulate
1731
1732!> @copydoc DEF_COI_THREADC
1733!! @param cntvect the control vector
1734!!
1735!! @ingroup REGISTRATION_OF_OPTIONS_F90
1736!!
1737Integer Function coidef_threadc( CntVect, ThreadC )
1738#if defined (dec_directives)
1739!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ThreadC
1740#if defined (itl)
1741!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ThreadC
1742!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_THREADC'::COIDEF_ThreadC
1743#endif
1744#endif
1745 Use conopt_utilities
1746 Implicit None
1747 Integer, dimension(NumCallBack) :: cntvect
1748 Integer :: threadc
1749
1750 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1751 coidef_threadc = corruptcntr
1752 Elseif ( threadc < 0 ) Then
1753 coidef_threadc = rangeproblem; cntvect(indx_range) = 1
1754#if defined (write20)
1755 write(20,*) 'COIDEF_ThreadC: Illegal argument. ThreadC=',threadc
1756#endif
1757 Else
1758 coidef_threadc = 0
1759 cntvect(indx_threadc) = threadc
1760 Endif
1761
1762End function coidef_threadc
1763
1764!> allow output to StdOut.
1765!!
1766!! CONOPT will by default not write to Standard Output or Fortran Write(*,*) to
1767!! avoid problems in certain Windowing environments. All communication goes via
1768!! callback routines. If there are errors during the initial setup of communication
1769!! it can sometimes be difficult to locate these errors. If you allow output to
1770!! Standard Output then CONOPT may provide some extra debugging information.
1771!!
1772!! @param cntvect the control vector
1773!! @param tostdout 1 to output to Standard Output, 0 to silence the output.
1774!!
1775!! @ingroup REGISTRATION_OF_OPTIONS_F90
1776!!
1777Integer Function coidef_stdout( CntVect, toStdOut )
1778#if defined (dec_directives)
1779!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_StdOut
1780#if defined (itl)
1781!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_StdOut
1782!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_STDOUT'::COIDEF_StdOut
1783#endif
1784#endif
1785 Use conopt_utilities
1786 Implicit None
1787 Integer, dimension(NumCallBack) :: cntvect
1788 Integer :: tostdout
1789
1790 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1791 coidef_stdout = corruptcntr
1792 Elseif ( tostdout < 0 .or. tostdout > 1 ) Then
1793 coidef_stdout = rangeproblem; cntvect(indx_range) = 1
1794#if defined (write20)
1795 write(20,*) 'COIDEF_StdOut: Illegal argument. StdOut=',tostdout
1796#endif
1797 Else
1798 coidef_stdout = 0
1799 cntvect(indx_stdout) = tostdout
1800 Endif
1801
1802End function coidef_stdout
1803
1804!> define Optfile / Option order.
1805!!
1806!! By default CONOPT will first process the options defined in a file, see
1807!! coidef_optfile(), and the process the options defined via
1808!! a call-back routine. This method is called to change this order.
1809!!
1810!! The interpretation of `OptOrder` is:
1811!! - <b>0:</b> Process option defined via the option file
1812!! before options defined via the options callback. <i>(default
1813!! value)</i>
1814!! - <b>1:</b> Process option defined via the options callback
1815!! before options defined via options file.
1816!!
1817!! @param cntvect the control vector
1818!! @param optorder Option processing order
1819!!
1820!! @ingroup REGISTRATION_OF_OPTIONS_F90
1821!!
1822Integer Function coidef_optorder( CntVect, OptOrder )
1823#if defined (dec_directives)
1824!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_OptOrder
1825#if defined (itl)
1826!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_OptOrder
1827!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_OPTORDER'::COIDEF_OptOrder
1828#endif
1829#endif
1830 Use conopt_utilities
1831 Implicit None
1832 Integer, dimension(NumCallBack) :: cntvect
1833 Integer :: optorder
1834
1835 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1836 coidef_optorder = corruptcntr
1837 Elseif ( optorder < 0 .OR. optorder > 1 ) Then
1838 coidef_optorder = rangeproblem; cntvect(indx_range) = 1
1839#if defined (write20)
1840 write(20,*) 'COIDEF_OptOrder: Illegal argument. OptOrder=',optorder
1841#endif
1842 Else
1843 coidef_optorder = 0
1844 cntvect(indx_optorder) = optorder
1845 Endif
1846
1847End function coidef_optorder
1848
1849!> @defgroup DEF_COI_CLEARM ""
1850!! ClearM
1851!!
1852!! @param clearm
1853
1854!> @copydoc DEF_COI_CLEARM
1855!! @param cntvect the control vector
1856!!
1857!! @ingroup REGISTRATION_OF_OPTIONS_F90
1858!!
1859Integer Function coidef_clearm( CntVect, ClearM )
1860#if defined (dec_directives)
1861!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ClearM
1862#if defined (itl)
1863!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ClearM
1864!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_CLEARM'::COIDEF_ClearM
1865#endif
1866#endif
1867 Use conopt_utilities
1868 Implicit None
1869 Integer, dimension(NumCallBack) :: cntvect
1870 Integer :: clearm
1871
1872 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1873 coidef_clearm = corruptcntr
1874 Elseif ( clearm < 0 .or. clearm > 1 ) Then
1875 coidef_clearm = rangeproblem; cntvect(indx_range) = 1
1876#if defined (write20)
1877 write(20,*) 'COIDEF_ClearM: Illegal argument. ClearM=',clearm
1878#endif
1879 Else
1880 coidef_clearm = 0
1881 cntvect(indx_clearm) = clearm
1882 Endif
1883
1884End function coidef_clearm
1885
1886!> define callback routine for defining an options file.
1887!!
1888!! It is possible to define an options file with user defined values for certain
1889!! options. To define an options file you must write a callback routine that gives
1890!! CONOPT the file name (see \ref API_OPTFILE_F90 "OptFile") and register this optional
1891!! routine with a call to coidef_optfile() before CONOPT is started. The name of
1892!! your version of `OptFile` must be declared as external and given to
1893!! coidef_optfile() as its second argument.
1894!!
1895!! \note By default the options defined via an option file are processed before the
1896!! options defined via the callback routine (see coidef_option()). The order can be changed with a call to coidef_optorder().
1897!!
1898!! For the definition of the `Optfile` callback function, see \ref API_OPTFILE_F90 "Optfile"
1899!!
1900!! @param cntvect the control vector
1901!! @param optfile the pointer to the `OptFile` routine for providing the options file name
1902!!
1903!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
1904!!
1905Integer Function coidef_optfile( CntVect, Optfile )
1906#if defined (dec_directives)
1907!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Optfile
1908#if defined (itl)
1909!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Optfile
1910!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_OPTFILE'::COIDEF_Optfile
1911#endif
1912#endif
1913 Use conopt_utilities
1914 Implicit None
1915 Character(Len=*) :: optfile
1916 Integer, dimension(NumCallBack) :: cntvect
1917 Character(Len=CO_Filelen) :: filename
1918 integer :: i,j
1919
1920 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1921 coidef_optfile = corruptcntr
1922 Else
1923 filename = optfile
1924 i = indx_optfile
1925 do j = 1, co_filelen, 4
1926 Call packchar( filename(j:j+3), cntvect(i) )
1927 i = i + 1
1928 enddo
1929 coidef_optfile = 0
1930 Endif
1931
1932End Function coidef_optfile
1933
1934!> define callback routine for providing the matrix data to CONOPT.
1935!!
1936!! CONOPT gets information about the structure of the model from a user written
1937!! callback routine referred to as `ReadMatrix`. You must register this routine with a call to
1938!! this method before CONOPT is started. The name
1939!! of your version of `ReadMatrix` must be declared as external.
1940!!
1941!! \note There is no type checking for the argument list on External functions in
1942!! Fortran, so you must be very careful.
1943!!
1944!! @param cntvect the control vector
1945!! @param coi_readmatrix the pointer to the user-defined `ReadMatrix` callback routine
1946!!
1947!! @ingroup REGISTRATION_OF_MANDATORY_CALLBACK_ROUTINES_F90
1948!!
1949Integer Function coidef_readmatrix( CntVect, COI_ReadMatrix )
1950#if defined (dec_directives)
1951!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ReadMatrix
1952#if defined (itl)
1953!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ReadMatrix
1954!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_READMATRIX'::COIDEF_ReadMatrix
1955#endif
1956#endif
1957 Use conopt_utilities
1958 Implicit None
1959 External coi_readmatrix
1960 Integer(CO_P) :: address
1961 Integer, dimension(NumCallBack) :: cntvect
1962
1963 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
1964 coidef_readmatrix = corruptcntr
1965 Else
1967 address = coi_addressofext( coi_readmatrix )
1968 Call storeaddr( cntvect, indx_readmatrix, address )
1969 Endif
1970
1971End Function coidef_readmatrix
1972
1973!> define callback routine to perform initialization tasks for the function and derivative evaluation.
1974!!
1975!! The nonlinear `FDEval` routine is usually called for several constraints in one
1976!! point before being called for constraints in another point. An optional user
1977!! provided `FDEvalIni` routine can be used to perform common tasks that are
1978!! needed in preparation for a new point. You must register this
1979!! routine with a call to this method before CONOPT is started. The name of
1980!! your version of `FDEvalIni` must be declared as external.
1981!!
1982!! @param cntvect the control vector
1983!! @param coi_fdevalini the pointer to the `FDEvalIni` routine for initializing data before nonlinear evaluations
1984!!
1985!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
1986!!
1987Integer Function coidef_fdevalini( CntVect, COI_FDEvalIni )
1988#if defined (dec_directives)
1989!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_FDEvalIni
1990#if defined (itl)
1991!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_FDEvalIni
1992!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_FDEVALINI'::COIDEF_FDEvalIni
1993#endif
1994#endif
1995 Use conopt_utilities
1996 Implicit None
1997 External coi_fdevalini
1998 Integer(CO_P) :: address
1999 Integer, dimension(NumCallBack) :: cntvect
2000
2001 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2002 coidef_fdevalini = corruptcntr
2003 Else
2005 address = coi_addressofext( coi_fdevalini )
2006 Call storeaddr( cntvect, indx_fdevalini, address )
2007 Endif
2008
2009End Function coidef_fdevalini
2010
2011!> define callback routine for performing function and derivative evaluations.
2012!!
2013!! CONOPT get information about the nonlinearities from a user written callback
2014!! routine referred to as `FDEval`. You
2015!! must register this routine with a call to this method before CONOPT is
2016!! started. The name of your version of `FDEval` must be declared as external.
2017!!
2018!! @param cntvect the control vector
2019!! @param coi_fdeval pointer to the user-defined `FDEval` callback routine
2020!!
2021!! @ingroup REGISTRATION_OF_MANDATORY_CALLBACK_ROUTINES_F90
2022!!
2023Integer Function coidef_fdeval( CntVect, COI_FDEval )
2024#if defined (dec_directives)
2025!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_FDEval
2026#if defined (itl)
2027!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_FDEval
2028!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_FDEVAL'::COIDEF_FDEval
2029#endif
2030#endif
2031 Use conopt_utilities
2032 Implicit None
2033 External coi_fdeval
2034 Integer(CO_P) :: address
2035 Integer, dimension(NumCallBack) :: cntvect
2036
2037 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2038 coidef_fdeval = corruptcntr
2039 Else
2040 coidef_fdeval = 0
2041 address = coi_addressofext( coi_fdeval )
2042 Call storeaddr( cntvect, indx_fdeval, address )
2043 Endif
2044
2045End Function coidef_fdeval
2046
2047!> define callback routine for the termination of the function and derivative evaluation.
2048!!
2049!! After the nonlinear `FDEval` routine has been called for several constraints in
2050!! one point an optional user provided `FDEvalEnd` routine can be used to perform
2051!! common cleanup tasks. If you want to use this possibility you must
2052!! register this routine with a call to this method before CONOPT is
2053!! started. The name of your version of `FDEvalEnd` must be declared as external.
2054!!
2055!! @param cntvect the control vector
2056!! @param coi_fdevalend the pointer to the `FDEvalEnd` routine for cleanup after nonlinear evaluations
2057!!
2058!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2059!!
2060Integer Function coidef_fdevalend( CntVect, COI_FdevalEnd )
2061#if defined (dec_directives)
2062!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_FdevalEnd
2063#if defined (itl)
2064!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_FDEvalEnd
2065!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_FDEVALEND'::COIDEF_FDEvalEnd
2066#endif
2067#endif
2068 Use conopt_utilities
2069 Implicit None
2070 External coi_fdevalend
2071 Integer(CO_P) :: address
2072 Integer, dimension(NumCallBack) :: cntvect
2073
2074 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2075 coidef_fdevalend = corruptcntr
2076 Else
2078 address = coi_addressofext( coi_fdevalend )
2079 Call storeaddr( cntvect, indx_fdevalend, address )
2080 Endif
2081
2082End Function coidef_fdevalend
2083
2084!> define callback routine for returning the completion status.
2085!!
2086!! When CONOPT has finished optimizing it informs the modeler about the status of
2087!! the solution: Optimal, Infeasible, Normal completion, Interrupted by function
2088!! evaluation errors etc. This is done by a call to a user written callback routine
2089!! referred to as `Status`. You must
2090!! register this routine with a call to this method before CONOPT is started.
2091!! The name of your version of `Status` must be declared as external.
2092!!
2093!! @param cntvect the control vector
2094!! @param coi_status pointer to the user-defined `Status` callback routine
2095!!
2096!! @ingroup REGISTRATION_OF_MANDATORY_CALLBACK_ROUTINES_F90
2097!!
2098Integer Function coidef_status( CntVect, COI_Status )
2099#if defined (dec_directives)
2100!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Status
2101#if defined (itl)
2102!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Status
2103!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_STATUS'::COIDEF_Status
2104#endif
2105#endif
2106 Use conopt_utilities
2107 Implicit None
2108 External coi_status
2109 Integer(CO_P) :: address
2110 Integer, dimension(NumCallBack) :: cntvect
2111
2112 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2113 coidef_status = corruptcntr
2114 Else
2115 coidef_status = 0
2116 address = coi_addressofext( coi_status )
2117 Call storeaddr( cntvect, indx_status, address )
2118 Endif
2119
2120End Function coidef_status
2121
2122!> define callback routine for returning the final solution values.
2123!!
2124!! After the user written callback Status has been called CONOPT will usually
2125!! (unless the Status indicates some serious error condition) call another user
2126!! written callback routine called `Solution` to inform the modeler about the
2127!! actual primal and dual solution values. You must register this routine with a call to
2128!! this method before CONOPT is started. The name of your version of
2129!! `Solution` must be declared as external.
2130!!
2131!! @param cntvect the control vector
2132!! @param coi_solution the pointer to the user-defined `Solution` callback routine
2133!!
2134!! @ingroup REGISTRATION_OF_MANDATORY_CALLBACK_ROUTINES_F90
2135!!
2136Integer Function coidef_solution( CntVect, COI_Solution )
2137#if defined (dec_directives)
2138!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Solution
2139#if defined (itl)
2140!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Solution
2141!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_SOLUTION'::COIDEF_Solution
2142#endif
2143#endif
2144 Use conopt_utilities
2145 Implicit None
2146 External coi_solution
2147 Integer(CO_P) :: address
2148 Integer, dimension(NumCallBack) :: cntvect
2149
2150 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2151 coidef_solution = corruptcntr
2152 Else
2153 coidef_solution = 0
2154 address = coi_addressofext( coi_solution )
2155 Call storeaddr( cntvect, indx_solution, address )
2156 Endif
2157
2158End Function coidef_solution
2159
2160!> define callback routine for handling messages returned during the solution process.
2161!!
2162!! Apart from the solution itself, CONOPT provides a number of messages about
2163!! progress and problems during the optimization. Most messages are provided in the
2164!! form of character strings that are passed as arguments to a user written
2165!! callback routine called `Message`. It is the modelers responsibility to handle
2166!! these messages. You must register this routine with a call
2167!! to this method before CONOPT is started. The name of your version of
2168!! `Message` must be declared as external.
2169!!
2170!! @param cntvect the control vector
2171!! @param coi_message the pointer to the user-defined `Message` callback routine
2172!!
2173!! @ingroup REGISTRATION_OF_MANDATORY_CALLBACK_ROUTINES_F90
2174!!
2175Integer Function coidef_message( CntVect, COI_Message )
2176#if defined (dec_directives)
2177!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Message
2178#if defined (itl)
2179!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Message
2180!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_MESSAGE'::COIDEF_Message
2181#endif
2182#endif
2183 Use conopt_utilities
2184 Implicit None
2185 External coi_message
2186 Integer(CO_P) :: address
2187 Integer, dimension(NumCallBack) :: cntvect
2188
2189 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2190 coidef_message = corruptcntr
2191 Else
2192 coidef_message = 0
2193 address = coi_addressofext( coi_message )
2194 Call storeaddr( cntvect, indx_message, address )
2195 Endif
2196
2197End Function coidef_message
2198
2199!> define callback routine for monitoring the algorithmic progress.
2200!!
2201!! If you would like to write your own iteration log then CONOPT can provide the
2202!! necessary information to a user written callback routine called `Progress`.
2203!! `Progress` can also be used to communicate a Stop messages back to CONOPT. If you
2204!! would like CONOPT to call your `Progress` routine you must register it with a
2205!! call to this method before CONOPT is started. The name of your version of
2206!! `Progress` must be declared as external.
2207!!
2208!! @param cntvect the control vector
2209!! @param coi_progress the pointer to the `Progress` routine for logging iteration progress or sending stop messages
2210!!
2211!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2212!!
2213Integer Function coidef_progress( CntVect, COI_Progress )
2214#if defined (dec_directives)
2215!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Progress
2216#if defined (itl)
2217!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Progress
2218!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_PROGRESS'::COIDEF_Progress
2219#endif
2220#endif
2221 Use conopt_utilities
2222 Implicit None
2223 External coi_progress
2224 Integer(CO_P) :: address
2225 Integer, dimension(NumCallBack) :: cntvect
2226
2227 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2228 coidef_progress = corruptcntr
2229 Else
2230 coidef_progress = 0
2231 address = coi_addressofext( coi_progress )
2232 Call storeaddr( cntvect, indx_progress, address )
2233 Endif
2234
2235End Function coidef_progress
2236
2237!> define callback routine for defining runtime options.
2238!!
2239!! An alternative or supplement to an options file is an option callback routine
2240!! that CONOPT calls repeatedly to get non-default option values. To use this
2241!! method you must write a callback routine that gives CONOPT the names and values
2242!! of the non default options and you must
2243!! register this optional routine with a call to this method before CONOPT is
2244!! started. The name of your version of Option must be declared as external.
2245!!
2246!! \note By default the options defined via an option file are processed before the options defined via the
2247!! callback routine.
2248!!
2249!! @param cntvect the control vector
2250!! @param coi_option the pointer to the `Option` routine for setting non-default option values
2251!!
2252!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2253!!
2254Integer Function coidef_option( CntVect, COI_Option )
2255#if defined (dec_directives)
2256!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_Option
2257#if defined (itl)
2258!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_Option
2259!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_OPTION'::COIDEF_Option
2260#endif
2261#endif
2262 Use conopt_utilities
2263 Implicit None
2264 External coi_option
2265 Integer(CO_P) :: address
2266 Integer, dimension(NumCallBack) :: cntvect
2267
2268 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2269 coidef_option = corruptcntr
2270 Else
2271 coidef_option = 0
2272 address = coi_addressofext( coi_option )
2273 Call storeaddr( cntvect, indx_option, address )
2274 Endif
2275
2276End Function coidef_option
2277
2278!> define callback routine for returning error messages for row, column or Jacobian elements.
2279!!
2280!! Certain messages, including error messages, refer to a particular variable
2281!! and/or constraint. The mandatory `ErrMsg` callback routine is used to format and
2282!! display these messages. If
2283!! you want to supply it you must register it with a call to this method before
2284!! CONOPT is started. The name of your version of `ErrMsg` must be declared as
2285!! external.
2286!!
2287!! @param cntvect the control vector
2288!! @param coi_errmsg pointer to the user-defined `ErrMsg` callback routine
2289!!
2290!! @ingroup REGISTRATION_OF_MANDATORY_CALLBACK_ROUTINES_F90
2291!!
2292Integer Function coidef_errmsg( CntVect, COI_ErrMsg )
2293#if defined (dec_directives)
2294!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_ErrMsg
2295#if defined (itl)
2296!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_ErrMsg
2297!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_ERRMSG'::COIDEF_ErrMsg
2298#endif
2299#endif
2300 Use conopt_utilities
2301 Implicit None
2302 External coi_errmsg
2303 Integer(CO_P) :: address
2304 Integer, dimension(NumCallBack) :: cntvect
2305
2306 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2307 coidef_errmsg = corruptcntr
2308 Else
2309 coidef_errmsg = 0
2310 address = coi_addressofext( coi_errmsg )
2311 Call storeaddr( cntvect, indx_errmsg, address )
2312 Endif
2313
2314End Function coidef_errmsg
2315
2316!> define callback routine for providing the triangular order information.
2317!!
2318!! During preprocessing of a model CONOPT can provide information about the
2319!! solution sequence of triangular parts of a model. This can be useful for
2320!! analyzing certain types of infeasibilities. If you want to use this feature you
2321!! must register a `TriOrd` callback routine with a call to this method before CONOPT is started. The
2322!! name of your version of `TriOrd` must be declared as external.
2323!!
2324!! @param cntvect the control vector
2325!! @param coi_triord the pointer to the `TriOrd` routine for analyzing the solution sequence of triangular parts.
2326!!
2327!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2328!!
2329Integer Function coidef_triord( CntVect, COI_TriOrd )
2330#if defined (dec_directives)
2331!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_TriOrd
2332#if defined (itl)
2333!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_TriOrd
2334!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_TRIORD'::COIDEF_TriOrd
2335#endif
2336#endif
2337 Use conopt_utilities
2338 Implicit None
2339 External coi_triord
2340 Integer(CO_P) :: address
2341 Integer, dimension(NumCallBack) :: cntvect
2342
2343 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2344 coidef_triord = corruptcntr
2345 Else
2346 coidef_triord = 0
2347 address = coi_addressofext( coi_triord )
2348 Call storeaddr( cntvect, indx_triord, address )
2349 Endif
2350
2351End Function coidef_triord
2352
2353!> define callback routine for performing function and derivative evaluations on intervals.
2354!!
2355!! During preprocessing CONOPT can take advantage of interval information for
2356!! function values and derivatives if this is available. If you can provide
2357!! interval information you can register an optional `FDInterval` function and
2358!! derivative evaluation callback routine with a call to this method before CONOPT is
2359!! started. The name of your version of `FDInterval` must be declared as external.
2360!!
2361!! @param cntvect the control vector
2362!! @param coi_fdinterval the pointer to the `FDInterval` routine for providing interval data for functions and derivatives
2363!!
2364!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2365!!
2366Integer Function coidef_fdinterval( CntVect, COI_FDInterval )
2367#if defined (dec_directives)
2368!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_FDInterval
2369#if defined (itl)
2370!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_FDInterval
2371!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_FDINTERVAL'::COIDEF_FDInterval
2372#endif
2373#endif
2374 Use conopt_utilities
2375 Implicit None
2376 External coi_fdinterval
2377 Integer(CO_P) :: address
2378 Integer, dimension(NumCallBack) :: cntvect
2379
2380 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2381 coidef_fdinterval = corruptcntr
2382 Else
2384 address = coi_addressofext( coi_fdinterval )
2385 Call storeaddr( cntvect, indx_fdinterval, address )
2386 Endif
2387
2388End Function coidef_fdinterval
2389
2390!> define callback routine for computing the second derivative for a constraint in a direction.
2391!!
2392!! CONOPT can take advantage of 2<sup>nd</sup> derivatives in various forms, as
2393!! discussed in the \ref API_DEFINING_SECOND_ORDER_INFO_F90 section. If you can provide
2394!! directional 2<sup>nd</sup> derivatives of the individual constraints then you
2395!! can register an optional `2DDir` callback routine with a call to this method before CONOPT is
2396!! started. The name of your version of `2DDir` must be declared as external.
2397!!
2398!! @param cntvect the control vector
2399!! @param coi_2ddir the pointer to the `2DDir` callback routine for supplying directional second derivatives of constraints
2400!!
2401!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2402!!
2403Integer Function coidef_2ddir( CntVect, COI_2DDir )
2404#if defined (dec_directives)
2405!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_2DDir
2406#if defined (itl)
2407!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_2DDir
2408!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_2DDIR'::COIDEF_2DDir
2409#endif
2410#endif
2411 Use conopt_utilities
2412 Implicit None
2413 External coi_2ddir
2414 Integer(CO_P) :: address
2415 Integer, dimension(NumCallBack) :: cntvect
2416
2417 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2418 coidef_2ddir = corruptcntr
2419 Else
2420 coidef_2ddir = 0
2421 address = coi_addressofext( coi_2ddir )
2422 Call storeaddr( cntvect, indx_2ddir, address )
2423 Endif
2424
2425End Function coidef_2ddir
2426
2427!> define callback routine for initializing the computation of second derivatives for a constraint in a direction.
2428!!
2429!! The `2DDir` routine defined above will be called in batches. First it will be
2430!! called in one point and with a given direction for all nonlinear constraints
2431!! except pre-triangular constraints and constraints with dual variables equal to
2432!! zero, then for the same constraints in the same point but with a different
2433!! direction, and later again in a new point with a new direction and possibly for
2434!! a different set of constraints (due to changes in the dual variables). If the
2435!! modeler would like to perform certain common tasks each time the point or the
2436!! direction changes then this can be done in a callback routine defined with
2437!! this method.
2438!! If you would like to provide this initialization routine then you can register an optional
2439!! `2DDirIni` callback routine with a call to this method before CONOPT is started. The name
2440!! of your version of `2DDirIni` must be declared as external.
2441!!
2442!! @param cntvect the control vector
2443!! @param coi_2ddirini the pointer to the `2DDirIni` callback routine for initializing tasks when the point or direction changes
2444!!
2445!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2446!!
2447Integer Function coidef_2ddirini( CntVect, COI_2DDirIni )
2448#if defined (dec_directives)
2449!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_2DDirIni
2450#if defined (itl)
2451!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_2DDirIni
2452!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_2DDIRINI'::COIDEF_2DDirIni
2453#endif
2454#endif
2455 Use conopt_utilities
2456 Implicit None
2457 External coi_2ddirini
2458 Integer(CO_P) :: address
2459 Integer, dimension(NumCallBack) :: cntvect
2460
2461 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2462 coidef_2ddirini = corruptcntr
2463 Else
2464 coidef_2ddirini = 0
2465 address = coi_addressofext( coi_2ddirini )
2466 Call storeaddr( cntvect, indx_2ddirini, address )
2467 Endif
2468
2469End Function coidef_2ddirini
2470
2471!> define callback routine for termination the computation of second derivatives for a constraint in a direction.
2472!!
2473!! After the `2DDir` routine defined above has been called for a number of
2474!! constraints in a particular point and in a particular direction the optional
2475!! `2DDirEnd` routine will be called if it has been defined by the modeler. in
2476!! batches. If the modeler would like to perform certain common cleanup tasks each
2477!! time the `2DDir` calls for a point or a direction have been finished then this
2478!! can be done in a callback routine defined with this method as discussed in
2479!! \ref API_2DDIREND_F90 "2DDirEnd section". If you would like to provide this
2480!! termination routine then you can register an optional `2DDirEnd` callback
2481!! routine with a call to
2482!! this method before CONOPT is started. The name of your version of
2483!! `2DDirEnd` must be declared as external.
2484!!
2485!! @param cntvect the control vector
2486!! @param coi_2ddirend the pointer to the `2DDirEnd` callback routine for cleanup after processing a point or direction
2487!!
2488!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2489!!
2490Integer Function coidef_2ddirend( CntVect, COI_2DDirEnd )
2491#if defined (dec_directives)
2492!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_2DDirEnd
2493#if defined (itl)
2494!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_2DDirEnd
2495!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_2DDIREND'::COIDEF_2DDirEnd
2496#endif
2497#endif
2498 Use conopt_utilities
2499 Implicit None
2500 External coi_2ddirend
2501 Integer(CO_P) :: address
2502 Integer, dimension(NumCallBack) :: cntvect
2503
2504 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2505 coidef_2ddirend = corruptcntr
2506 Else
2507 coidef_2ddirend = 0
2508 address = coi_addressofext( coi_2ddirend )
2509 Call storeaddr( cntvect, indx_2ddirend, address )
2510 Endif
2511
2512End Function coidef_2ddirend
2513
2514!> define callback routine for computing the second derivative of the Lagrangian in a direction.
2515!!
2516!! CONOPT can take advantage of 2<sup>nd</sup> derivatives in various forms as
2517!! discussed in \ref API_DEFINING_SECOND_ORDER_INFO_F90. If you can provide directional
2518!! 2<sup>nd</sup> derivatives of the Lagrangian then you can register an optional
2519!! `2DDirLagr` callback routine with a call to this method before CONOPT is started. The name
2520!! of your version of `2DDirLagr` must be declared as external.
2521!!
2522!! @param cntvect the control vector
2523!! @param coi_2ddirlagr the pointer to the `2DDirLagr` callback routine for supplying directional second derivatives of the Lagrangian
2524!!
2525!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2526!!
2527Integer Function coidef_2ddirlagr( CntVect, COI_2DDirLagr )
2528#if defined (dec_directives)
2529!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_2DDirLagr
2530#if defined (itl)
2531!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_2DDirLagr
2532!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_2DDIRLAGR'::COIDEF_2DDirLagr
2533#endif
2534#endif
2535 Use conopt_utilities
2536 Implicit None
2537 External coi_2ddirlagr
2538 Integer(CO_P) :: address
2539 Integer, dimension(NumCallBack) :: cntvect
2540
2541 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2542 coidef_2ddirlagr = corruptcntr
2543 Else
2545 address = coi_addressofext( coi_2ddirlagr )
2546 Call storeaddr( cntvect, indx_2ddirlagr, address )
2547 Endif
2548
2549End Function coidef_2ddirlagr
2550
2551Integer Function coidef_2dlagrsize( CntVect, COI_2DLagrSize )
2552#if defined (dec_directives)
2553!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_2DLagrSize
2554#if defined (itl)
2555!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_2DLagrSize
2556!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_2DLAGRSIZE'::COIDEF_2DLagrSize
2557#endif
2558#endif
2559 Use conopt_utilities
2560 Implicit None
2561 External coi_2dlagrsize
2562 Integer(CO_P) :: address
2563 Integer, dimension(NumCallBack) :: cntvect
2564
2565 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2566 coidef_2dlagrsize = corruptcntr
2567 Else
2569 address = coi_addressofext( coi_2dlagrsize )
2570 Call storeaddr( cntvect, indx_2dlagrsize, address )
2571 Endif
2572
2573End Function coidef_2dlagrsize
2574
2575!> define callback routine for providing the structure of the second derivatives of the Lagrangian.
2576!!
2577!! CONOPT can take advantage of 2<sup>nd</sup> derivatives in various forms,
2578!! including the Hessian of the Lagrangian and directional 2<sup>nd</sup>
2579!! derivatives. If you can provide the Hessian of the Lagrangian as a sparse
2580!! matrix, you can register the optional 2DLagrStr callback routine with a call to this method
2581!! before CONOPT is started. The name of your version of 2DLagrStr must be declared
2582!! as external.
2583!!
2584!! @param cntvect the control vector.
2585!! @param coi_2dlagrstr the pointer to the 2DLagrStr callback routine, which defines the structure of the Hessian of the Lagrangian.
2586!!
2587!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2588!!
2589Integer Function coidef_2dlagrstr( CntVect, COI_2DLagrStr )
2590#if defined (dec_directives)
2591!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_2DLagrStr
2592#if defined (itl)
2593!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_2DLagrStr
2594!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_2DLAGRSTR'::COIDEF_2DLagrStr
2595#endif
2596#endif
2597 Use conopt_utilities
2598 Implicit None
2599 External coi_2dlagrstr
2600 Integer(CO_P) :: address
2601 Integer, dimension(NumCallBack) :: cntvect
2602
2603 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2604 coidef_2dlagrstr = corruptcntr
2605 Else
2607 address = coi_addressofext( coi_2dlagrstr )
2608 Call storeaddr( cntvect, indx_2dlagrstr, address )
2609 Endif
2610
2611End Function coidef_2dlagrstr
2612
2613!> define callback routine for computing the values of the second derivatives of the Lagrangian.
2614!!
2615!! CONOPT can take advantage of 2<sup>nd</sup> derivatives in various forms,
2616!! including the Hessian of the Lagrangian and directional 2<sup>nd</sup>
2617!! derivatives. If you can provide the Hessian of the Lagrangian as a sparse
2618!! matrix, you can register the optional 2DLagrVal callback routine with a call to this method
2619!! before CONOPT is started. The name of your version of 2DLagrVal must be declared
2620!! as external.
2621!!
2622!! @param cntvect the control vector.
2623!! @param coi_2dlagrval the pointer to the 2DLagrVal callback routine, which provides the values of the Hessian of the Lagrangian.
2624!!
2625!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2626!!
2627Integer Function coidef_2dlagrval( CntVect, COI_2DLagrVal )
2628#if defined (dec_directives)
2629!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_2DLagrVal
2630#if defined (itl)
2631!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_2DLagrVal
2632!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_2DLAGRVAL'::COIDEF_2DLagrVal
2633#endif
2634#endif
2635 Use conopt_utilities
2636 Implicit None
2637 External coi_2dlagrval
2638 Integer(CO_P) :: address
2639 Integer, dimension(NumCallBack) :: cntvect
2640
2641 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2642 coidef_2dlagrval = corruptcntr
2643 Else
2645 address = coi_addressofext( coi_2dlagrval )
2646 Call storeaddr( cntvect, indx_2dlagrval, address )
2647 Endif
2648
2649End Function coidef_2dlagrval
2650
2651!> provides a pointer to user memory that is available in all callback functions. NOTE: this is not a callback function, but a
2652!! pointer to a data structure.
2653!!
2654!! Communication between the modeler’s main program and the callback routines can
2655!! take place via common blocks or global variables. For use in a thread safe
2656!! application CONOPT offers an alternative communication mechanism called `User
2657!! Memory`. The modeler can register a memory location (usually the address of the
2658!! start of a vector) as `User Memory` and CONOPT will provide this address to all
2659!! callback routines. You register `User Memory` by calling this method with
2660!! the `User Memory` as the second argument.
2661!!
2662!! @param cntvect the control vector
2663!! @param usrmem the user memory location for communication between the main program and callback routines
2664!!
2665!! @ingroup REGISTRATION_OF_OPTIONAL_CALLBACK_ROUTINES_F90
2666!!
2667Integer Function coidef_usrmem( CntVect, UsrMem )
2668#if defined (dec_directives)
2669!DEC$ ATTRIBUTES DLLEXPORT :: COIDEF_UsrMem
2670#if defined (itl)
2671!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: COIDEF_UsrMem
2672!DEC$ ATTRIBUTES DECORATE, ALIAS: 'COIDEF_USRMEM'::COIDEF_UsrMem
2673#endif
2674#endif
2675 Use conopt_utilities
2676 Implicit None
2677 Integer, Dimension(*) :: usrmem ! Should be pointer to void but using a Character may add an extra argument
2678 Integer(CO_P) :: address
2679 Integer, dimension(NumCallBack) :: cntvect
2680
2681 If ( cntvect(1) /= numcallback .or. cntvect(numcallback) /= numcallback) Then
2682 coidef_usrmem = corruptcntr
2683 Else
2684 coidef_usrmem = 0
2685 address = coi_addressofext( usrmem )
2686 Call storeaddr( cntvect, indx_usrmem, address )
2687 Endif
2688
2689End Function coidef_usrmem
integer function coidef_2dlagrsize(cntvect, coi_2dlagrsize)
program fvforall
Main program. A simple setup and call of CONOPT.
Definition fvforall.f90:14
program fvinclin
Main program. A simple setup and call of CONOPT.
Definition fvinclin.f90:14
integer function coidef_fdeval(cntvect, coi_fdeval)
define callback routine for performing function and derivative evaluations.
integer function coidef_errmsg(cntvect, coi_errmsg)
define callback routine for returning error messages for row, column or Jacobian elements.
integer function coidef_message(cntvect, coi_message)
define callback routine for handling messages returned during the solution process.
integer function coidef_readmatrix(cntvect, coi_readmatrix)
define callback routine for providing the matrix data to CONOPT.
integer function coidef_status(cntvect, coi_status)
define callback routine for returning the completion status.
integer function coidef_solution(cntvect, coi_solution)
define callback routine for returning the final solution values.
integer function coidef_2ddirini(cntvect, coi_2ddirini)
define callback routine for initializing the computation of second derivatives for a constraint in a ...
integer function coidef_2dlagrstr(cntvect, coi_2dlagrstr)
define callback routine for providing the structure of the second derivatives of the Lagrangian.
integer function coidef_2ddir(cntvect, coi_2ddir)
define callback routine for computing the second derivative for a constraint in a direction.
integer function coidef_option(cntvect, coi_option)
define callback routine for defining runtime options.
integer function coidef_fdevalini(cntvect, coi_fdevalini)
define callback routine to perform initialization tasks for the function and derivative evaluation.
integer function coidef_optfile(cntvect, optfile)
define callback routine for defining an options file.
integer function coidef_2ddirend(cntvect, coi_2ddirend)
define callback routine for termination the computation of second derivatives for a constraint in a d...
integer function coidef_usrmem(cntvect, usrmem)
provides a pointer to user memory that is available in all callback functions. NOTE: this is not a ca...
integer function coidef_triord(cntvect, coi_triord)
define callback routine for providing the triangular order information.
integer function coidef_2dlagrval(cntvect, coi_2dlagrval)
define callback routine for computing the values of the second derivatives of the Lagrangian.
integer function coidef_progress(cntvect, coi_progress)
define callback routine for monitoring the algorithmic progress.
integer function coidef_2ddirlagr(cntvect, coi_2ddirlagr)
define callback routine for computing the second derivative of the Lagrangian in a direction.
integer function coidef_fdevalend(cntvect, coi_fdevalend)
define callback routine for the termination of the function and derivative evaluation.
integer function coidef_fdinterval(cntvect, coi_fdinterval)
define callback routine for performing function and derivative evaluations on intervals.
integer function coidef_inistat(cntvect, inistat)
handling of the initial status values.
integer function coidef_threadf(cntvect, threadf)
number of threads allowed for simultaneous FDEval calls.
integer function coidef_stdout(cntvect, tostdout)
allow output to StdOut.
integer function coidef_discont(cntvect, discont)
allow discontinuous functions and derivatives.
integer function coidef_emptyrow(cntvect, emptyrow)
allow empty rows.
integer function coidef_threads(cntvect, threads)
number of threads allowed internally in CONOPT.
integer function coidef_emptycol(cntvect, emptycol)
allow empty columns.
integer function coidef_hessfac(cntvect, hessfac)
factor for Hessian density relative to Jacobian density HessFac.
integer function coidef_square(cntvect, square)
square models.
integer function coidef_debugfv(cntvect, debugfv)
turn Debugging of FDEval on and off.
integer function coidef_maxsup(cntvect, maxsup)
limit on superbasics.
integer function coidef_c(cntvect)
define C Conventions for Argument Passing.
Definition coistart.f90:809
integer function coidef_fvinclin(cntvect, fvinclin)
include the linear terms in function evaluations.
integer function coidef_debug2d(cntvect, debug2d)
turn debugging of 2nd derivatives on and off.
integer function coidef_itlim(cntvect, itlim)
define the Iteration Limit.
Definition coistart.f90:845
integer function coidef_zeronoise(cntvect, zeronoise)
define zero noise level.
integer function coidef_base(cntvect, base)
define the Base index for vectors.
Definition coistart.f90:743
integer function coidef_license(cntvect, licint1, licint2, licint3, licstring)
define the License Information.
Definition coistart.f90:680
integer function coidef_fvforall(cntvect, fvforall)
call the FDEval for all constraints, including linear constraints.
integer function coidef_threadc(cntvect, threadc)
check for thread compatibility.
integer function coidef_optorder(cntvect, optorder)
define Optfile / Option order.
integer function coidef_reslim(cntvect, reslim)
define resource limit.
Definition coistart.f90:932
integer function coidef_maxheap(cntvect, maxheap)
define Limit on Heap Memory. ""
Definition coistart.f90:988
integer function coidef_fortran(cntvect)
define Fortran Conventions for Argument Passing.
Definition coistart.f90:779
integer function coidef_thread2d(cntvect, thread2d)
number of threads allowed for simultaneous 2DDir calls.
integer function coidef_errlim(cntvect, errlim)
define the Error Limit.
Definition coistart.f90:890
integer function coidef_clearm(cntvect, clearm)
ClearM.
integer function coidef_numvar(cntvect, numvar)
defines the number of variables in the model.
Definition coistart.f90:358
integer function coidef_objcon(cntvect, objcon)
defines the Objective Constraint.
Definition coistart.f90:629
integer function coidef_numnz(cntvect, numnz)
defines the number of nonzero elements in the Jacobian.
Definition coistart.f90:437
integer function coidef_optdir(cntvect, optdir)
defines the Optimization Direction.
Definition coistart.f90:552
integer function coidef_numnlnz(cntvect, numnlnz)
defines the Number of Nonlinear Nonzeros.
Definition coistart.f90:476
integer function coidef_numhess(cntvect, numhess)
defines the Number of Hessian Nonzeros.
Definition coistart.f90:513
integer function coidef_numcon(cntvect, numcon)
defines the number of constraints in the model.
Definition coistart.f90:398
integer function coidef_objvar(cntvect, objvar)
defines the Objective Variable.
Definition coistart.f90:586
integer function coidef_size()
returns the size the Control Vector must have, measured in standard Integer units.
Definition coistart.f90:176
integer function coidef_ini(cntvect)
initializes the Control Vector by placing default values in the various positions.
Definition coistart.f90:201
integer function coidef_inifort(cntvect)
initialisation method for Fortran applications.
Definition coistart.f90:314
integer function coiget_maxthreads(cntvect)
returns the maximum number of threads that can be used by CONOPT.
Definition coistart.f90:95
real *8 function coiget_maxheapused(cntvect)
After a model has been solved this method will return the amount of heap memory used.
Definition coistart.f90:126
integer function coiget_rangeerrors(cntvect)
returns the range errors that were encountered.
Definition coistart.f90:153
subroutine coiget_version(major, minor, patch)
returns the version number. It can be used to ensure that the modeler is linked to the correct versio...
Definition coistart.f90:67
integer function coi_solve(cntvect)
method for starting the solving process of CONOPT.
Definition coistart.f90:14
program square
Main program. A simple setup and call of CONOPT.
Definition square.f90:17