next up previous index
Next: Running Minuit in Data-driven Up: How to Use Minuit Previous: How to Use Minuit   Index

The Function FCN.

The user must always supply a Fortran subroutine which calculates the function value to be minimized or analyzed.


CALL FCN (NPAR,GRAD,FVAL,XVAL,IFLAG,FUTIL)

Input parameters
NPAR
number of currently variable parameters.
XVAL
vector of (constant and variable) parameters.
IFLAG
Indicates what is to be calculated (see example below).
FUTIL
Name of utilitary routine (if needed, it must be declared EXTERNAL and provided by the user).
Output parameters
FVAL
The calculated function value.
GRAD
The (optional) vector of first derivatives).

Note that when Minuit is being used through an intermediate package such as HBOOK or PAW, then the FCN may be supplied by the this package.

Example of FCN routine

        SUBROUTINE FCN(NPAR,GRAD,FVAL,XVAL,IFLAG,FUTIL)
        IMPLICIT DOUBLE PRECISION (A-H,O-Z)  !  for 32-bit machines
        DIMENSION GRAD(*),XVAL(*)
        EXTERNAL FUTIL   !    (if needed and supplied by user)
C-
        IF (IFLAG .EQ. 1)  THEN
C           read input data,
C           calculate any necessary constants, etc.
        ENDIF
        IF (IFLAG .EQ. 2)  THEN
C           calculate GRAD, the first derivatives of FVAL
C           (this is optional)
        ENDIF
C             Always calculate the value of the function, FVAL,
C             which is usually a chisquare or log likelihood.
C                  Optionally, calculation of FVAL may involve
        FTHEO = FUTIL(....)
C                  It is responsability of user to pass
C                  any parameter values needed by FUTIL,
C                  either through arguments, or in a COMMON block
         IF (IFLAG .EQ. 3)  THEN
C            will come here only after the fit is finished.
C            Perform any final calculations, output fitted data, etc.
        ENDIF
        RETURN
        END

The name of the subroutine may be chosen freely (in documentation we give it the generic name FCN) and must be declared EXTERNAL in the user's program which calls Minuit (in data-driven mode) or calls Minuit subroutines (in Fortran-callable mode). The meaning of the parameters XVAL is of course defined by the user, who uses the values of those parameters to calculate his function value. The starting values must be specified by the user (either by supplying parameter definitions from a file, or typing them at the terminal, in data-driven mode; or by calling subroutine MNPARM in Fortran-callable mode), and later values are determined by Minuit as it searches for the minimum or performs whatever analysis is requested by the user. FUTIL represents the name of a function or subroutine which may be defined and supplied by the user and called from FCN. If the user does not use the FUTIL feature, the last argument may be given as zero, but if used, the name of FUTIL must be declared EXTERNAL and a subprogram of that name must be supplied at loading time. It is possible, by giving them different names, to analyze several different FCNs in one job. However, one analysis must be completed before the next is started. In order to avoid interference between the analyses of two different FCNs, the user should call Minuit (in data-driven mode) or MNINIT (in Fortran-callable mode) each time a new FCN is to be studied.


next up previous index
Next: Running Minuit in Data-driven Up: How to Use Minuit Previous: How to Use Minuit   Index
Back to CERN | IT | ASD | CERN Program Library Home
MG (last mod. 1998-08-19)