source: Sophya/trunk/SophyaExt/CodeMinuit/code/mnhelp.F@ 3302

Last change on this file since 3302 was 2403, checked in by cmv, 22 years ago

Creation du module de code source de MINUIT (CERNLIB) extrait par CMV

cmv 11/06/2003

File size: 25.6 KB
RevLine 
[2403]1*
2* $Id: mnhelp.F,v 1.1.1.1 2003-06-11 14:18:27 cmv Exp $
3*
4* $Log: not supported by cvs2svn $
5* Revision 1.2 1999/09/03 09:17:47 couet
6* - \Cind{} removed in the help of minuit. This was a Tex directive which very
7* likely has been forgotten during a Tex to f77 translation. This didn't
8* compile on RH6.
9*
10* Revision 1.1.1.1 1996/03/07 14:31:30 mclareni
11* Minuit
12*
13*
14#include "minuit/pilot.h"
15 SUBROUTINE MNHELP(COMD,LOUT)
16*.
17*. HELP routine for MINUIT interactive commands.
18*.
19*. COMD ='* ' prints a global help for all commands
20*. COMD =Command_name: print detailed help for one command.
21*. Note that at least 3 characters must be given for the command name.
22*.
23*. Author: Rene Brun
24* comments extracted from the MINUIT documentation file.
25*.
26 CHARACTER*(*) COMD
27 CHARACTER*3 CMD3
28*.
29*-- command name ASSUMED to be in upper case
30*__________________________________________________________________
31*--
32*-- Global HELP: Summary of all commands
33*-- ====================================
34*--
35 IF(COMD(1:1) .EQ. '*')THEN
36 WRITE(LOUT,10000)
37 WRITE(LOUT,10001)
38 GO TO 99
39 ENDIF
4010000 FORMAT(' ==>List of MINUIT Interactive commands:',/,
41 +' CLEar Reset all parameter names and values undefined',/,
42 +' CONtour Make contour map of the user function',/,
43 +' EXIT Exit from Interactive Minuit',/,
44 +' FIX Cause parameter(s) to remain constant',/,
45 +' HESse Calculate the Hessian or error matrix.',/,
46 +' IMPROVE Search for a new minimum around current minimum',/,
47 +' MIGrad Minimize by the method of Migrad',/,
48 +' MINImize MIGRAD + SIMPLEX method if Migrad fails',/,
49 +' MINOs Exact (non-linear) parameter error analysis')
5010001 FORMAT(' MNContour Calculate one MINOS function contour',/,
51 +' PARameter Define or redefine new parameters and values',/,
52 +' RELease Make previously FIXed parameters variable again',/,
53 +' REStore Release last parameter fixed',/,
54 +' SAVe Save current parameter values on a file',/,
55 +' SCAn Scan the user function by varying parameters',/,
56 +' SEEk Minimize by the method of Monte Carlo',/,
57 +' SET Set various MINUIT constants or conditions',/,
58 +' SHOw Show values of current constants or conditions',/,
59 +' SIMplex Minimize by the method of Simplex')
60*
61 CMD3=COMD(1:3)
62*__________________________________________________________________
63*--
64*-- Command CLEAR
65*-- =============
66*.
67 IF(CMD3.EQ.'CLE')THEN
68 WRITE(LOUT,10100)
69 GO TO 99
70 ENDIF
7110100 FORMAT(' ***>CLEAR',/,
72 +' Resets all parameter names and values to undefined.',/,
73 +' Must normally be followed by a PARameters command or ',/,
74 +' equivalent, in order to define parameter values.')
75*__________________________________________________________________
76*--
77*-- Command CONTOUR
78*-- ===============
79*.
80 IF(CMD3.EQ.'CON')THEN
81 WRITE(LOUT,10200)
82 GO TO 99
83 ENDIF
8410200 FORMAT(' ***>CONTOUR <par1> <par2> [devs] [ngrid]',/,
85 +' Instructs Minuit to trace contour lines of the user function',/,
86 +' with respect to the two parameters whose external numbers',/,
87 +' are <par1> and <par2>.',/,
88 +' Other variable parameters of the function, if any, will have',/,
89 +' their values fixed at the current values during the contour',/,
90 +' tracing. The optional parameter [devs] (default value 2.)',/,
91 +' gives the number of standard deviations in each parameter',/,
92 +' which should lie entirely within the plotting area.',/,
93 +' Optional parameter [ngrid] (default value 25 unless page',/,
94 +' size is too small) determines the resolution of the plot,',/,
95 +' i.e. the number of rows and columns of the grid at which the',/,
96 +' function will be evaluated. [See also MNContour.]')
97*__________________________________________________________________
98*--
99*-- Command END
100*-- ===========
101*.
102 IF(CMD3.EQ.'END')THEN
103 WRITE(LOUT,10300)
104 GO TO 99
105 ENDIF
10610300 FORMAT(' ***>END',/,
107 +' Signals the end of a data block (i.e., the end of a fit),',/,
108 +' and implies that execution should continue, because another',/,
109 +' Data Block follows. A Data Block is a set of Minuit data',/,
110 +' consisting of',/,
111 +' (1) A Title,',/,
112 +' (2) One or more Parameter Definitions,',/,
113 +' (3) A blank line, and',/,
114 +' (4) A set of Minuit Commands.',/,
115 +' The END command is used when more than one Data Block is to',/,
116 +' be used with the same FCN function. It first causes Minuit',/,
117 +' to issue a CALL FCN with IFLAG=3, in order to allow FCN to',/,
118 +' perform any calculations associated with the final fitted',/,
119 +' parameter values, unless a CALL FCN 3 command has already',/,
120 +' been executed at the current FCN value.')
121*__________________________________________________________________
122*.
123*--
124*-- Command EXIT
125*-- ============
126 IF(CMD3 .EQ.'EXI')THEN
127 WRITE(LOUT,10400)
128 GO TO 99
129 ENDIF
13010400 FORMAT(' ***>EXIT',/,
131 +' Signals the end of execution.',/,
132 +' The EXIT command first causes Minuit to issue a CALL FCN',/,
133 +' with IFLAG=3, to allow FCN to perform any calculations',/,
134 +' associated with the final fitted parameter values, unless a',/,
135 +' CALL FCN 3 command has already been executed.')
136*__________________________________________________________________
137*--
138*-- Command FIX
139*-- ===========
140*.
141 IF(CMD3.EQ.'FIX')THEN
142 WRITE(LOUT,10500)
143 GO TO 99
144 ENDIF
14510500 FORMAT(' ***>FIX} <parno> [parno] ... [parno]',/,
146 +' Causes parameter(s) <parno> to be removed from the list of',/,
147 +' variable parameters, and their value(s) will remain constant',/,
148 +' during subsequent minimizations, etc., until another command',/,
149 +' changes their value(s) or status.')
150*__________________________________________________________________
151*--
152*-- Command HESSE
153*-- =============
154*.
155 IF(CMD3.EQ.'HES')THEN
156 WRITE(LOUT,10600)
157 GO TO 99
158 ENDIF
15910600 FORMAT(' ***>HESse [maxcalls]',/,
160 +' Calculate, by finite differences, the Hessian or error matrix.',
161 +/,' That is, it calculates the full matrix of second derivatives'
162 +,/,' of the function with respect to the currently variable',/,
163 +' parameters, and inverts it, printing out the resulting error',/,
164 +' matrix. The optional argument [maxcalls] specifies the',/,
165 +' (approximate) maximum number of function calls after which',/,
166 +' the calculation will be stopped.')
167*__________________________________________________________________
168*--
169*-- Command IMPROVE
170*-- ===============
171*.
172 IF(CMD3.EQ.'IMP')THEN
173 WRITE(LOUT,10700)
174 GO TO 99
175 ENDIF
17610700 FORMAT(' ***>IMPROVE [maxcalls]',/,
177 +' If a previous minimization has converged, and the current',/,
178 +' values of the parameters therefore correspond to a local',/,
179 +' minimum of the function, this command requests a search for',/,
180 +' additional distinct local minima.',/,
181 +' The optional argument [maxcalls] specifies the (approximate)',/,
182 +' maximum number of function calls after which the calculation',/,
183 +' will be stopped.')
184*__________________________________________________________________
185*--
186*-- Command MIGRAD
187*-- ==============
188*.
189 IF(CMD3.EQ.'MIG')THEN
190 WRITE(LOUT,10800)
191 GO TO 99
192 ENDIF
19310800 FORMAT(' ***>MIGrad [maxcalls] [tolerance]',/,
194 +' Causes minimization of the function by the method of Migrad,',/,
195 +' the most efficient and complete single method, recommended',/,
196 +' for general functions (see also MINImize).',/,
197 +' The minimization produces as a by-product the error matrix',/,
198 +' of the parameters, which is usually reliable unless warning',/,
199 +' messages are produced.',/,
200 +' The optional argument [maxcalls] specifies the (approximate)',/,
201 +' maximum number of function calls after which the calculation',/,
202 +' will be stopped even if it has not yet converged.',/,
203 +' The optional argument [tolerance] specifies required tolerance',
204 +/,' on the function value at the minimum.',/,
205 +' The default tolerance is 0.1, and the minimization will stop',/,
206 +' when the estimated vertical distance to the minimum (EDM) is',/,
207 +' less than 0.001*[tolerance]*UP (see [SET ERRordef]).')
208*__________________________________________________________________
209*--
210*-- Command MINIMIZE
211*-- ================
212*.
213 IF(COMD(1:4).EQ.'MINI')THEN
214 WRITE(LOUT,10900)
215 GO TO 99
216 ENDIF
21710900 FORMAT(' ***>MINImize [maxcalls] [tolerance]',/,
218 +' Causes minimization of the function by the method of Migrad,',/,
219 +' as does the MIGrad command, but switches to the SIMplex method',
220 +/,' if Migrad fails to converge. Arguments are as for MIGrad.',/,
221 +' Note that command requires four characters to be unambiguous.')
222*__________________________________________________________________
223*--
224*-- Command MINOS
225*-- =============
226*.
227 IF(COMD(1:4).EQ.'MINO')THEN
228 WRITE(LOUT,11000)
229 GO TO 99
230 ENDIF
23111000 FORMAT(' ***>MINOs [maxcalls] [parno] [parno] ...',/,
232 +' Causes a Minos error analysis to be performed on the parameters'
233 +,/,' whose numbers [parno] are specified. If none are specified,',
234 +/,' Minos errors are calculated for all variable parameters.',/,
235 +' Minos errors may be expensive to calculate, but are very',/,
236 +' reliable since they take account of non-linearities in the',/,
237 +' problem as well as parameter correlations, and are in general',/
238 +' asymmetric.',/,
239 +' The optional argument [maxcalls] specifies the (approximate)',/,
240 +' maximum number of function calls per parameter requested,',/,
241 +' after which the calculation will stop for that parameter.')
242*__________________________________________________________________
243*--
244*-- Command MNCONTOUR
245*-- =================
246*.
247 IF(CMD3.EQ.'MNC')THEN
248 WRITE(LOUT,11100)
249 GO TO 99
250 ENDIF
25111100 FORMAT(' ***>MNContour <par1> <par2> [npts]',/,
252 +' Calculates one function contour of FCN with respect to',/,
253 +' parameters par1 and par2, with FCN minimized always with',/,
254 +' respect to all other NPAR-2 variable parameters (if any).',/,
255 +' Minuit will try to find npts points on the contour (default 20)'
256 +,/,' If only two parameters are variable at the time, it is not',
257 +/,' necessary to specify their numbers. To calculate more than',/,
258 +' one contour, it is necessary to SET ERRordef to the appropriate'
259 +,/,' value and issue the MNContour command for each contour.')
260*__________________________________________________________________
261*--
262*-- Command PARAMETER
263*-- =================
264*.
265 IF(CMD3.EQ.'PAR')THEN
266 WRITE(LOUT,11150)
267 GO TO 99
268 ENDIF
26911150 FORMAT(' ***>PARameters',/,
270 +' followed by one or more parameter definitions.',/,
271 +' Parameter definitions are of the form:',/,
272 +' <number> ''name'' <value> <step> [lolim] [uplim] ',/,
273 +' for example:',/,
274 +' 3 ''K width'' 1.2 0.1' ,/,
275 +' the last definition is followed by a blank line or a zero.')
276*__________________________________________________________________
277*--
278*-- Command RELEASE
279*-- ===============
280*.
281 IF(CMD3.EQ.'REL')THEN
282 WRITE(LOUT,11200)
283 GO TO 99
284 ENDIF
28511200 FORMAT(' ***>RELease <parno> [parno] ... [parno]',/,
286 +' If <parno> is the number of a previously variable parameter',/,
287 +' which has been fixed by a command: FIX <parno>, then that',/,
288 +' parameter will return to variable status. Otherwise a warning'
289 +,/,' message is printed and the command is ignored.',/,
290 +' Note that this command operates only on parameters which were',/
291 +' at one time variable and have been FIXed. It cannot make',/,
292 +' constant parameters variable; that must be done by redefining',/
293 +' the parameter with a PARameters command.')
294*__________________________________________________________________
295*--
296*-- Command RESTORE
297*-- ===============
298*.
299 IF(CMD3.EQ.'RES')THEN
300 WRITE(LOUT,11300)
301 GO TO 99
302 ENDIF
30311300 FORMAT(' ***>REStore [code]',/,
304 +' If no [code] is specified, this command restores all previously'
305 +,/,' FIXed parameters to variable status. If [code]=1, then only',
306 +/,' the last parameter FIXed is restored to variable status.',/,
307 +' If code is neither zero nor one, the command is ignored.')
308*__________________________________________________________________
309*--
310*-- Command RETURN
311*-- ==============
312*.
313 IF(CMD3.EQ.'RET')THEN
314 WRITE(LOUT,11400)
315 GO TO 99
316 ENDIF
31711400 FORMAT(' ***>RETURN',/,
318 +' Signals the end of a data block, and instructs Minuit to return'
319 +,/,' to the program which called it. The RETurn command first',/,
320 +' causes Minuit to CALL FCN with IFLAG=3, in order to allow FCN',/
321 +,' to perform any calculations associated with the final fitted',/
322 +,' parameter values, unless a CALL FCN 3 command has already been'
323 +,/,' executed at the current FCN value.')
324*__________________________________________________________________
325*--
326*-- Command SAVE
327*-- ============
328*.
329 IF(CMD3.EQ.'SAV')THEN
330 WRITE(LOUT,11500)
331 GO TO 99
332 ENDIF
33311500 FORMAT(' ***>SAVe',/,
334 +' Causes the current parameter values to be saved on a file in',/,
335 +' such a format that they can be read in again as Minuit',/,
336 +' parameter definitions. If the covariance matrix exists, it is',/
337 +,' also output in such a format. The unit number is by default 7,'
338 +,/,' or that specified by the user in his call to MINTIO or',/,
339 +' MNINIT. The user is responsible for opening the file previous'
340 +,/,' to issuing the [SAVe] command (except where this can be done'
341 +,/,' interactively).')
342*__________________________________________________________________
343*--
344*-- Command SCAN
345*-- ============
346*.
347 IF(CMD3.EQ.'SCA')THEN
348 WRITE(LOUT,11600)
349 GO TO 99
350 ENDIF
35111600 FORMAT(' ***>SCAn [parno] [numpts] [from] [to]',/,
352 +' Scans the value of the user function by varying parameter',/,
353 +' number [parno], leaving all other parameters fixed at the',/,
354 +' current value. If [parno] is not specified, all variable',/,
355 +' parameters are scanned in sequence.',/,
356 +' The number of points [numpts] in the scan is 40 by default,',/,
357 +' and cannot exceed 100. The range of the scan is by default',/,
358 +' 2 standard deviations on each side of the current best value,',
359 +/,' but can be specified as from [from] to [to].',/,
360 +' After each scan, if a new minimum is found, the best parameter'
361 +,/,' values are retained as start values for future scans or',/,
362 +' minimizations. The curve resulting from each scan is plotted',/
363 +,' on the output unit in order to show the approximate behaviour'
364 +,/,' of the function.',/,
365 +' This command is not intended for minimization, but is sometimes'
366 +,/,' useful for debugging the user function or finding a',/,
367 +' reasonable starting point.')
368*__________________________________________________________________
369*--
370*-- Command SEEK
371*-- ============
372*.
373 IF(CMD3.EQ.'SEE')THEN
374 WRITE(LOUT,11700)
375 GO TO 99
376 ENDIF
37711700 FORMAT(' ***>SEEk [maxcalls] [devs]',/,
378 +' Causes a Monte Carlo minimization of the function, by choosing',
379 +/,' random values of the variable parameters, chosen uniformly',/,
380 +' over a hypercube centered at the current best value.',/,
381 +' The region size is by default 3 standard deviations on each',/,
382 +' side, but can be changed by specifying the value of [devs].')
383*__________________________________________________________________
384*--
385*-- Command SET
386*-- ===========
387*.
388 IF(CMD3.EQ.'SET')THEN
389 WRITE(LOUT,11800)
390 WRITE(LOUT,11801)
391 WRITE(LOUT,11802)
392 WRITE(LOUT,11803)
393 WRITE(LOUT,11804)
394 WRITE(LOUT,11805)
395 WRITE(LOUT,11806)
396 WRITE(LOUT,11807)
397 WRITE(LOUT,11808)
398 WRITE(LOUT,11809)
399 WRITE(LOUT,11810)
400 WRITE(LOUT,11811)
401 WRITE(LOUT,11812)
402 WRITE(LOUT,11813)
403 WRITE(LOUT,11814)
404 WRITE(LOUT,11815)
405 WRITE(LOUT,11816)
406 WRITE(LOUT,11817)
407 GO TO 99
408 ENDIF
40911800 FORMAT(' ***>SET <option_name>',/,/,
410 +' SET BATch',/,
411 +' Informs Minuit that it is running in batch mode.',//,
412
413 +' SET EPSmachine <accuracy>',/,
414 +' Informs Minuit that the relative floating point arithmetic',/
415 +' precision is <accuracy>. Minuit determines the nominal',/,
416 +' precision itself, but the SET EPSmachine command can be',/,
417 +' used to override Minuit own determination, when the user',/,
418 +' knows that the FCN function value is not calculated to',/,
419 +' the nominal machine accuracy. Typical values of <accuracy>',/
420 +' are between 10**-5 and 10**-14.')
421
42211801 FORMAT(/,' SET ERRordef <up>',/,
423 +' Sets the value of UP (default value= 1.), defining parameter'
424 +,/,' errors. Minuit defines parameter errors as the change',/,
425 +' in parameter value required to change the function value',/,
426 +' by UP. Normally, for chisquared fits UP=1, and for negative'
427 +,/,' log likelihood, UP=0.5.')
428
42911802 FORMAT(/,' SET GRAdient [force]',/,
430 +' Informs Minuit that the user function is prepared to',/,
431 +' calculate its own first derivatives and return their values'
432 +,/,' in the array GRAD when IFLAG=2 (see specs of FCN).',/,
433 +' If [force] is not specified, Minuit will calculate',/,
434 +' the FCN derivatives by finite differences at the current',/,
435 +' point and compare with the user calculation at that point,'
436 +,/,' accepting the user values only if they agree.',/,
437 +' If [force]=1, Minuit does not do its own derivative',/,
438 +' calculation, and uses the derivatives calculated in FCN.')
439
44011803 FORMAT(/,' SET INPut [unitno] [filename]',/,
441 +' Causes Minuit, in data-driven mode only, to read subsequent',
442 +/,' commands (or parameter definitions) from a different input'
443 +,/,' file. If no [unitno] is specified, reading reverts to the'
444 +,/,' previous input file, assuming that there was one.',/,
445 +' If [unitno] is specified, and that unit has not been opened,'
446 +,/,' then Minuit attempts to open the file [filename]} if a',/,
447 +' name is specified. If running in interactive mode and',/,
448 +' [filename] is not specified and [unitno] is not opened,',/,
449 +' Minuit prompts the user to enter a file name.',/,
450 +' If the word REWIND is added to the command (note:no blanks',/
451 +' between INPUT and REWIND), the file is rewound before',/,
452 +' reading. Note that this command is implemented in standard',/
453 +' Fortran 77 and the results may depend on the system;',/,
454 +' for example, if a filename is given under VM/CMS, it must',/,
455 +' be preceeded by a slash.')
456
45711804 FORMAT(/,' SET INTeractive',/,
458 +' Informs Minuit that it is running interactively.')
459
46011805 FORMAT(/,' SET LIMits [parno] [lolim] [uplim]',/,
461 +' Allows the user to change the limits on one or all',/,
462 +' parameters. If no arguments are specified, all limits are',/,
463 +' removed from all parameters. If [parno] alone is specified,',
464 +/,' limits are removed from parameter [parno].',/,
465 +' If all arguments are specified, then parameter [parno] will',
466 +/,' be bounded between [lolim] and [uplim].',/,
467 +' Limits can be specified in either order, Minuit will take',/,
468 +' the smaller as [lolim] and the larger as [uplim].',/,
469 +' However, if [lolim] is equal to [uplim], an error condition',
470 +/,' results.')
471
47211806 FORMAT(/,' SET LINesperpage',/,
473 +' Sets the number of lines for one page of output.',/,
474 +' Default value is 24 for interactive mode')
475
47611807 FORMAT(/,' SET NOGradient',/,
477 +' The inverse of SET GRAdient, instructs Minuit not to',
478 +/,' use the first derivatives calculated by the user in FCN.')
479
48011808 FORMAT(/,' SET NOWarnings',/,
481 +' Supresses Minuit warning messages.')
482
48311809 FORMAT(/,' SET OUTputfile <unitno>',/,
484 +' Instructs Minuit to write further output to unit <unitno>.')
485
48611810 FORMAT(/,' SET PAGethrow <integer>',/,
487 +' Sets the carriage control character for ``new page'' to',/,
488 +' <integer>. Thus the value 1 produces a new page, and 0',/,
489 +' produces a blank line, on some devices (see TOPofpage)')
490
491
49211811 FORMAT(/,' SET PARameter <parno> <value>',/,
493 +' Sets the value of parameter <parno> to <value>.',/,
494 +' The parameter in question may be variable, fixed, or',/,
495 +' constant, but must be defined.')
496
49711812 FORMAT(/,' SET PRIntout <level>',/,
498 +' Sets the print level, determining how much output will be',/,
499 +' produced. Allowed values and their meanings are displayed',/,
500 +' after a SHOw PRInt command, and are currently <level>=:',/,
501 +' [-1] no output except from SHOW commands',/,
502 +' [0] minimum output',/,
503 +' [1] default value, normal output',/,
504 +' [2] additional output giving intermediate results.',/,
505 +' [3] maximum output, showing progress of minimizations.',/
506 +' Note: See also the SET WARnings command.')
507
50811813 FORMAT(/,' SET RANdomgenerator <seed>',/,
509 +' Sets the seed of the random number generator used in SEEk.',/
510 +' This can be any integer between 10000 and 900000000, for',/,
511 +' example one which was output from a SHOw RANdom command of',/
512 +' a previous run.')
513
51411814 FORMAT(/,' SET STRategy <level>',/,
515 +' Sets the strategy to be used in calculating first and second'
516 +,/,' derivatives and in certain minimization methods.',/,
517 +' In general, low values of <level> mean fewer function calls',
518 +/,' and high values mean more reliable minimization.',/,
519 +' Currently allowed values are 0, 1 (default), and 2.')
520
52111815 FORMAT(/,' SET TITle',/,
522 +' Informs Minuit that the next input line is to be considered',
523 +/,' the (new) title for this task or sub-task. This is for',/,
524 +' the convenience of the user in reading his output.')
525
52611816 FORMAT(/,' SET WARnings',/,
527 +' Instructs Minuit to output warning messages when suspicious',
528 +/,' conditions arise which may indicate unreliable results.',/
529 +' This is the default.')
530
53111817 FORMAT(/,' SET WIDthpage',/,
532 +' Informs Minuit of the output page width.',/,
533 +' Default values are 80 for interactive jobs')
534*__________________________________________________________________
535*--
536*-- Command SHOW
537*-- ============
538*.
539 IF(CMD3.EQ.'SHO')THEN
540 WRITE(LOUT,11900)
541 WRITE(LOUT,11901)
542 WRITE(LOUT,11902)
543 WRITE(LOUT,11903)
544 WRITE(LOUT,11904)
545 GO TO 99
546 ENDIF
54711900 FORMAT(' ***>SHOw <option_name>',/,
548 +' All SET XXXX commands have a corresponding SHOw XXXX command.',
549 +/,' In addition, the SHOw commands listed starting here have no',
550 +/,' corresponding SET command for obvious reasons.')
551
55211901 FORMAT(/,' SHOw CORrelations',/,
553 +' Calculates and prints the parameter correlations from the',/,
554 +' error matrix.')
555
55611902 FORMAT(/,' SHOw COVariance',/,
557 +' Prints the (external) covariance (error) matrix.')
558
55911903 FORMAT(/,' SHOw EIGenvalues',/,
560 +' Calculates and prints the eigenvalues of the covariance',/,
561 +' matrix.')
562
56311904 FORMAT(/,' SHOw FCNvalue',/,
564 +' Prints the current value of FCN.')
565*__________________________________________________________________
566*--
567*-- Command SIMPLEX
568*-- ===============
569*.
570 IF(CMD3.EQ.'SIM')THEN
571 WRITE(LOUT,12000)
572 GO TO 99
573 ENDIF
57412000 FORMAT(' ***>SIMplex [maxcalls] [tolerance]',/,
575 +' Performs a function minimization using the simplex method of',/
576 +' Nelder and Mead. Minimization terminates either when the',/,
577 +' function has been called (approximately) [maxcalls] times,',/,
578 +' or when the estimated vertical distance to minimum (EDM) is',/,
579 +' less than [tolerance].',/,
580 +' The default value of [tolerance] is 0.1*UP(see SET ERRordef).')
581*__________________________________________________________________
582*--
583*-- Command STANDARD
584*-- ================
585*.
586 IF(CMD3.EQ.'STA')THEN
587 WRITE(LOUT,12100)
588 GO TO 99
589 ENDIF
59012100 FORMAT(' ***>STAndard',/,
591 +' Causes Minuit to execute the Fortran instruction CALL STAND',/,
592 +' where STAND is a subroutine supplied by the user.')
593*__________________________________________________________________
594*--
595*-- Command STOP
596*-- ============
597*.
598 IF(CMD3.EQ.'STO')THEN
599 WRITE(LOUT,12200)
600 GO TO 99
601 ENDIF
60212200 FORMAT(' ***>STOP',/,
603 +' Same as EXIT.')
604*__________________________________________________________________
605*--
606*-- Command TOPOFPAGE
607*-- =================
608*.
609 IF(CMD3.EQ.'TOP')THEN
610 WRITE(LOUT,12300)
611 GO TO 99
612 ENDIF
61312300 FORMAT(' ***>TOPofpage',/,
614 +' Causes Minuit to write the character specified in a',/,
615 +' SET PAGethrow command (default = 1) to column 1 of the output'
616 +,/,' file, which may or may not position your output medium to',
617 +/,' the top of a page depending on the device and system.')
618*__________________________________________________________________
619*
620 WRITE(LOUT,13000)
62113000 FORMAT(' Unknown MINUIT command. Type HELP for list of commands.')
622*
623 99 RETURN
624 END
Note: See TracBrowser for help on using the repository browser.