COSMOS v7.655  COSMOSv7655
(AirShowerMC)
minuit.f
Go to the documentation of this file.
1 *
2 * $Id: minuit.F,v 1.1.1.1 1996/03/07 14:31:28 mclareni Exp $
3 *
4 * $Log: minuit.F,v $
5 * Revision 1.1.1.1 1996/03/07 14:31:28 mclareni
6 * Minuit
7 *
8 *
9  SUBROUTINE minuit(FCN,FUTIL)
10 *
11 * $Id: d506dp.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
12 *
13 * $Log: d506dp.inc,v $
14 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
15 * Minuit
16 *
17 *
18 *
19 *
20 * d506dp.inc
21 *
22 C ************ DOUBLE PRECISION VERSION *************
23  IMPLICIT DOUBLE PRECISION (a-h,o-z)
24 *
25 * $Id: d506cm.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
26 *
27 * $Log: d506cm.inc,v $
28 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
29 * Minuit
30 *
31 *
32 *
33 *
34 * d506cm.inc
35 *
36  parameter(mne=100 , mni=50)
37  parameter(mnihl=mni*(mni+1)/2)
38  CHARACTER*10 CPNAM
39  COMMON
40  1/mn7nam/ cpnam(mne)
41  2/mn7ext/ u(mne) ,alim(mne) ,blim(mne)
42  3/mn7err/ erp(mni) ,ern(mni) ,werr(mni) ,globcc(mni)
43  4/mn7inx/ nvarl(mne) ,niofex(mne),nexofi(mni)
44  5/mn7int/ x(mni) ,xt(mni) ,dirin(mni)
45  6/mn7fx2/ xs(mni) ,xts(mni) ,dirins(mni)
46  7/mn7der/ grd(mni) ,g2(mni) ,gstep(mni) ,gin(mne) ,dgrd(mni)
47  8/mn7fx3/ grds(mni) ,g2s(mni) ,gsteps(mni)
48  9/mn7fx1/ ipfix(mni) ,npfix
49  a/mn7var/ vhmat(mnihl)
50  b/mn7vat/ vthmat(mnihl)
51  c/mn7sim/ p(mni,mni+1),pstar(mni),pstst(mni) ,pbar(mni),prho(mni)
52 C
53  parameter(maxdbg=10, maxstk=10, maxcwd=20, maxp=30, maxcpt=101)
54  parameter(zero=0.0, one=1.0, half=0.5)
55  COMMON
56  d/mn7npr/ maxint ,npar ,maxext ,nu
57  e/mn7iou/ isysrd ,isyswr ,isyssa ,npagwd ,npagln ,newpag
58  e/mn7io2/ istkrd(maxstk) ,nstkrd ,istkwr(maxstk) ,nstkwr
59  f/mn7tit/ cfrom ,cstatu ,ctitl ,cword ,cundef ,cvrsn ,covmes
60  g/mn7flg/ isw(7) ,idbg(0:maxdbg) ,nblock ,icomnd
61  h/mn7min/ amin ,up ,edm ,fval3 ,epsi ,apsi ,dcovar
62  i/mn7cnv/ nfcn ,nfcnmx ,nfcnlc ,nfcnfr ,itaur,istrat,nwrmes(2)
63  j/mn7arg/ word7(maxp)
64  k/mn7log/ lwarn ,lrepor ,limset ,lnolim ,lnewmn ,lphead
65  l/mn7cns/ epsmac ,epsma2 ,vlimlo ,vlimhi ,undefi ,bigedm,updflt
66  m/mn7rpt/ xpt(maxcpt) ,ypt(maxcpt)
67  n/mn7cpt/ chpt(maxcpt)
68  o/mn7xcr/ xmidcr ,ymidcr ,xdircr ,ydircr ,ke1cr ,ke2cr
69  CHARACTER CTITL*50, CWORD*(maxcwd), CUNDEF*10, CFROM*8,
70  + cvrsn*6, covmes(0:3)*22, cstatu*10, chpt*1
71  LOGICAL LWARN, LREPOR, LIMSET, LNOLIM, LNEWMN, LPHEAD
72 C
73 C CPNAM Parameter name (10 characters)
74 C U External (visible to user in FCN) value of parameter
75 C ALIM, BLIM Lower and upper parameter limits. If both zero, no limits.
76 C ERP,ERN Positive and negative MINOS errors, if calculated.
77 C WERR External parameter error (standard deviation, defined by UP)
78 C GLOBCC Global Correlation Coefficient
79 C NVARL =-1 if parameter undefined, =0 if constant,
80 C = 1 if variable without limits, =4 if variable with limits
81 C (Note that if parameter has been fixed, NVARL=1 or =4, and NIOFEX=0)
82 C NIOFEX Internal parameter number, or zero if not currently variable
83 C NEXOFI External parameter number for currently variable parameters
84 C X, XT Internal parameter values (X are sometimes saved in XT)
85 C DIRIN (Internal) step sizes for current step
86 C variables with names ending in ..S are saved values for fixed params
87 C VHMAT (Internal) error matrix stored as Half MATrix, since
88 C it is symmetric
89 C VTHMAT VHMAT is sometimes saved in VTHMAT, especially in MNMNOT
90 C
91 C ISW definitions:
92 C ISW(1) =0 normally, =1 means CALL LIMIT EXCEEDED
93 C ISW(2) =0 means no error matrix
94 C =1 means only approximate error matrix
95 C =2 means full error matrix, but forced pos-def.
96 C =3 means good normal full error matrix exists
97 C ISW(3) =0 if Minuit is calculating the first derivatives
98 C =1 if first derivatives calculated inside FCN
99 C ISW(4) =-1 if most recent minimization did not converge.
100 C = 0 if problem redefined since most recent minimization.
101 C =+1 if most recent minimization did converge.
102 C ISW(5) is the PRInt level. See SHO PRIntlevel
103 C ISW(6) = 0 for batch mode, =1 for interactive mode
104 C =-1 for originally interactive temporarily batch
105 C
106 C LWARN is true if warning messges are to be put out (default=true)
107 C SET WARN turns it on, set NOWarn turns it off
108 C LREPOR is true if exceptional conditions are put out (default=false)
109 C SET DEBUG turns it on, SET NODebug turns it off
110 C LIMSET is true if a parameter is up against limits (for MINOS)
111 C LNOLIM is true if there are no limits on any parameters (not yet used)
112 C LNEWMN is true if the previous process has unexpectedly improved FCN
113 C LPHEAD is true if a heading should be put out for the next parameter
114 C definition, false if a parameter has just been defined
115 C
116  EXTERNAL fcn,futil
117  CHARACTER*40 CWHYXT
118  DATA cwhyxt/'FOR UNKNOWN REASONS '/
119  DATA jsysrd,jsyswr,jsyssa/5,6,7/
120 C . . . . . . . . . . initialize minuit
121  WRITE (jsyswr,'(1X,75(1H*))')
122  CALL mninit (jsysrd,jsyswr,jsyssa)
123 C . . . . initialize new data block
124  100 CONTINUE
125  WRITE (isyswr,'(1X,75(1H*))')
126  nblock = nblock + 1
127  WRITE (isyswr,'(26X,A,I4)') 'MINUIT DATA BLOCK NO.',nblock
128  WRITE (isyswr,'(1X,75(1H*))')
129 C . . . . . . . . . . . set parameter lists to undefined
130  CALL mncler
131 C . . . . . . . . read title
132  CALL mnread(fcn,1,iflgut,futil)
133  IF (iflgut .EQ. 2) GO TO 500
134  IF (iflgut .EQ. 3) GO TO 600
135 C . . . . . . . . read parameters
136  CALL mnread(fcn,2,iflgut,futil)
137  IF (iflgut .EQ. 2) GO TO 500
138  IF (iflgut .EQ. 3) GO TO 600
139  IF (iflgut .EQ. 4) GO TO 700
140 C . . . . . . verify FCN not time-dependent
141  WRITE (isyswr,'(/A,A)') ' MINUIT: FIRST CALL TO USER FUNCTION,',
142  + ' WITH IFLAG=1'
143  nparx = npar
144  CALL mninex(x)
145  fzero = undefi
146  CALL fcn(nparx,gin,fzero,u,1,futil)
147  first = undefi
148  CALL fcn(nparx,gin,first,u,4,futil)
149  nfcn = 2
150  IF (fzero.EQ.undefi .AND. first.EQ.undefi) THEN
151  cwhyxt = 'BY ERROR IN USER FUNCTION. '
152  WRITE (isyswr,'(/A,A/)') ' USER HAS NOT CALCULATED FUNCTION',
153  + ' VALUE WHEN IFLAG=1 OR 4'
154  GO TO 800
155  ENDIF
156  amin = first
157  IF (first .EQ. undefi) amin=fzero
158  CALL mnprin(1,amin)
159  nfcn = 2
160  IF (first .EQ. fzero) GO TO 300
161  fnew = 0.0
162  CALL fcn(nparx,gin,fnew,u,4,futil)
163  IF (fnew .NE. amin) WRITE (isyswr,280) amin, fnew
164  280 FORMAT (/' MINUIT WARNING: PROBABLE ERROR IN USER FUNCTION.'/
165  + ' FOR FIXED VALUES OF PARAMETERS, FCN IS TIME-DEPENDENT'/
166  + ' F =',e22.14,' FOR FIRST CALL'/
167  + ' F =',e22.14,' FOR SECOND CALL.'/)
168  nfcn = 3
169  300 fval3 = 2.0*amin+1.0
170 C . . . . . . . . . . . read commands
171  CALL mnread(fcn,3,iflgut,futil)
172  IF (iflgut .EQ. 2) GO TO 500
173  IF (iflgut .EQ. 3) GO TO 600
174  IF (iflgut .EQ. 4) GO TO 700
175  cwhyxt = 'BY MINUIT COMMAND: '//cword
176  IF (index(cword,'STOP').GT. 0) GO TO 800
177  IF (index(cword,'EXI') .GT. 0) GO TO 800
178  IF (index(cword,'RET') .EQ. 0) GO TO 100
179  cwhyxt = 'AND RETURNS TO USER PROGRAM. '
180  WRITE (isyswr,'(A,A)') ' ..........MINUIT TERMINATED ',cwhyxt
181  RETURN
182 C . . . . . . stop conditions
183  500 CONTINUE
184  cwhyxt = 'BY END-OF-DATA ON PRIMARY INPUT FILE. '
185  GO TO 800
186  600 CONTINUE
187  cwhyxt = 'BY UNRECOVERABLE READ ERROR ON INPUT. '
188  GO TO 800
189  700 CONTINUE
190  cwhyxt = ': FATAL ERROR IN PARAMETER DEFINITIONS. '
191  800 WRITE (isyswr,'(A,A)') ' ..........MINUIT TERMINATED ',cwhyxt
192  stop
193 C
194 C ......................entry to set unit numbers - - - - - - - - - -
195  entry mintio(i1,i2,i3)
196  jsysrd = i1
197  jsyswr = i2
198  jsyssa = i3
199  RETURN
200  END
integer npitbl real *nx parameter(n=101, npitbl=46, nx=n-1) real *8 uconst
nodes z
block data include Zlatfit h c fitting region data data data data data d0 data data d0 data data h g *is for param c g data up(2, 1)/7.0d0/
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
nodes i
subroutine mnread(FCN, IFLGIN, IFLGUT, FUTIL)
Definition: mnread.f:10
subroutine minuit(FCN, FUTIL)
Definition: minuit.f:10
subroutine mnprin(INKODE, FVAL)
Definition: mnprin.f:10
! constants thru Cosmos real ! if multiplied to deg radian Torad ! light velocity m sec ! infinty ! kg m2 *Togpcm2 g cm2 ! g cm2 *Tokgpm2 kg m2 ! cm *Tom m ! m *Tocm cm ! g cm3 *Tokgpm3 kg m3 ! kg m3 *Togpcm3 g cm3 ! sec *Tonsec nsec ! Tesla m ! Avogadro *A2deninv ! mfp *n * xs
Definition: Zglobalc.h:18
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
subroutine mncler
Definition: mncler.f:10
struct ob o[NpMax]
Definition: Zprivate.h:34
subroutine mninex(PINT)
Definition: mninex.f:10
dE dx *! Nuc Int sampling table d
Definition: cblkMuInt.h:130
nodes a
dE dx *! Nuc Int sampling table b
Definition: cblkMuInt.h:130
block data include Zlatfit h c fitting region data data data data data d0 data data d0 data data m
Definition: ZlatfitBD.h:35
dE dx *! Nuc Int sampling table h
Definition: cblkMuInt.h:130
dE dx *! Nuc Int sampling table g
Definition: cblkMuInt.h:130
!onst int maxp
Definition: Zprivate.h:3
subroutine mninit(I1, I2, I3)
Definition: mninit.f:34
integer n
Definition: Zcinippxc.h:1
integer, parameter half
Definition: csoftenPiK.f:108
! structure defining a particle at production ! Basic idea of what is to be contained in ! the particle structue is that dynamical ones should be included those derivable from the particle code ! is not included ******************************************************type fmom momentum sequence union map real e endmap map real * x
Definition: Zptcl.h:21
dE dx *! Nuc Int sampling table f
Definition: cblkMuInt.h:130
dE dx *! Nuc Int sampling table c
Definition: cblkMuInt.h:130