9 SUBROUTINE mnread(FCN,IFLGIN,IFLGUT,FUTIL)
23 IMPLICIT DOUBLE PRECISION (
a-
h,
o-
z)
63 2/mn7ext/ u(mne) ,alim(mne) ,blim(mne)
64 3/mn7err/ erp(mni) ,ern(mni) ,werr(mni) ,globcc(mni)
65 4/mn7inx/ nvarl(mne) ,niofex(mne),nexofi(mni)
66 5/mn7int/
x(mni) ,xt(mni) ,dirin(mni)
67 6/mn7fx2/
xs(mni) ,xts(mni) ,dirins(mni)
68 7/mn7der/ grd(mni) ,g2(mni) ,gstep(mni) ,gin(mne) ,dgrd(mni)
69 8/mn7fx3/ grds(mni) ,g2s(mni) ,gsteps(mni)
70 9/mn7fx1/ ipfix(mni) ,npfix
71 a/mn7var/ vhmat(mnihl)
72 b/mn7vat/ vthmat(mnihl)
73 c/mn7sim/
p(mni,mni+1),pstar(mni),pstst(mni) ,pbar(mni),prho(mni)
75 parameter(maxdbg=10, maxstk=10, maxcwd=20,
maxp=30, maxcpt=101)
78 d/mn7npr/ maxint ,npar ,maxext ,nu
79 e/mn7iou/ isysrd ,isyswr ,isyssa ,npagwd ,npagln ,newpag
80 e/mn7io2/ istkrd(maxstk) ,nstkrd ,istkwr(maxstk) ,nstkwr
81 f/mn7tit/ cfrom ,cstatu ,ctitl ,cword ,cundef ,cvrsn ,covmes
82 g/mn7flg/ isw(7) ,idbg(0:maxdbg) ,nblock ,icomnd
83 h/mn7min/ amin ,
up ,edm ,fval3 ,epsi ,apsi ,dcovar
84 i/mn7cnv/ nfcn ,nfcnmx ,nfcnlc ,nfcnfr ,itaur,istrat,nwrmes(2)
86 k/mn7log/ lwarn ,lrepor ,limset ,lnolim ,lnewmn ,lphead
87 l/mn7cns/ epsmac ,epsma2 ,vlimlo ,vlimhi ,undefi ,bigedm,updflt
88 m/mn7rpt/ xpt(maxcpt) ,ypt(maxcpt)
89 n/mn7cpt/ chpt(maxcpt)
90 o/mn7xcr/ xmidcr ,ymidcr ,xdircr ,ydircr ,ke1cr ,ke2cr
91 CHARACTER CTITL*50, CWORD*(maxcwd), CUNDEF*10, CFROM*8,
92 + cvrsn*6, covmes(0:3)*22, cstatu*10, chpt*1
93 LOGICAL LWARN, LREPOR, LIMSET, LNOLIM, LNEWMN, LPHEAD
95 CHARACTER CRDBUF*80, CUPBUF*10
96 CHARACTER CPROMT(3)*40, CLOWER*26, CUPPER*26
98 DATA cpromt/
' ENTER MINUIT TITLE, or "SET INPUT n" : ',
99 +
' ENTER MINUIT PARAMETER DEFINITION: ',
100 +
' ENTER MINUIT COMMAND: '/
102 DATA clower/
'abcdefghijklmnopqrstuvwxyz'/
103 DATA cupper/
'ABCDEFGHIJKLMNOPQRSTUVWXYZ'/
111 IF (isw(6) .EQ. 1)
THEN 112 WRITE (isyswr,
'(A)') cpromt(iflgdo)
113 IF (iflgdo .EQ. 2) lphead = .
false.
116 READ (isysrd,
'(A)',err=500,end=45) crdbuf
119 cupbuf(1:10) = crdbuf(1:10)
121 IF (crdbuf(
i:
i) .EQ.
'''')
GO TO 13
123 IF (crdbuf(
i:
i) .EQ. clower(ic:ic)) cupbuf(
i:
i)=cupper(ic:ic)
129 IF (index(cupbuf,
'*EOF') .EQ. 1)
THEN 130 WRITE (isyswr,
'(A,I3)')
' *EOF ENCOUNTERED ON UNIT NO.',isysrd
134 IF (index(cupbuf,
'SET INP') .EQ. 1)
THEN 136 WRITE (isyswr, 21) icomnd,crdbuf(1:50)
137 21
FORMAT (
' **********'/
' **',i5,
' **',
a/
' **********')
144 WRITE (isyswr,
'(A,I3)')
' END OF DATA ON UNIT NO.',isysrd
148 IF (ierr .EQ. 0)
GO TO 10
149 IF (ierr .EQ. 2)
THEN 151 WRITE (isyswr,
'(A,A/)')
' TWO CONSECUTIVE EOFs ON ',
152 +
'PRIMARY INPUT FILE WILL TERMINATE EXECUTION.' 159 80
IF (iflgdo .GT. 1)
GO TO 100
162 IF (index(cupbuf,
'SET TIT') .EQ. 1)
GO TO 10
164 WRITE (isyswr,
'(1X,A50)') ctitl
165 WRITE (isyswr,
'(1X,78(1H*))')
167 IF (iflgin .EQ. iflgdo)
GO TO 900
172 IF (iflgdo .GT. 2)
GO TO 300
175 IF (index(cupbuf,
'PAR') .EQ. 1)
GO TO 10
177 IF (index(cupbuf,
'SET TIT') .EQ. 1)
THEN 182 CALL mnpars(crdbuf,icondp)
183 IF (icondp .EQ. 0)
GO TO 10
185 IF (icondp .EQ. 1)
THEN 186 IF (isw(6) .EQ. 1)
THEN 187 WRITE (isyswr,
'(A)')
' FORMAT ERROR. IGNORED. ENTER AGAIN.' 190 WRITE (isyswr,
'(A)')
' ERROR IN PARAMETER DEFINITION' 196 IF (isw(5).GE.0 .AND. isw(6).LT.1)
WRITE (isyswr,
'(4X,75(1H*))')
198 IF (iflgin .EQ. iflgdo)
GO TO 900
204 CALL mncomd(fcn,crdbuf,icondn,futil)
218 IF (icondn .EQ. 2 .OR. icondn .EQ. 3)
THEN 220 IF (incomp .GT. 100)
THEN 226 IF (icondn .EQ. 5) iflgdo = 2
228 IF (icondn .EQ. 6)
GO TO 50
230 IF (icondn .EQ. 7) iflgdo = 1
232 IF (icondn .EQ. 8)
THEN 234 WRITE (isyswr,405) icomnd,crdbuf(1:50)
235 405
FORMAT (1
h ,10(1
h*)/
' **',i5,
' **',
a)
236 WRITE (isyswr,
'(1H ,10(1H*))' )
237 npar2 = npar*(npar+1)/2
238 READ (isysrd,420,err=500,end=45) (vhmat(
i),
i=1,npar2)
239 420
FORMAT (bn,7e11.4,3
x)
242 IF (isw(5) .GE. 0)
CALL mnmatu(1)
243 IF (isw(5) .GE. 1)
CALL mnprin(2,amin)
246 IF (icondn .LT. 10)
GO TO 10
integer npitbl real *nx parameter(n=101, npitbl=46, nx=n-1) real *8 uconst
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
subroutine mnread(FCN, IFLGIN, IFLGUT, FUTIL)
block data cblkElemag data *AnihiE ! Eposi< 1 TeV, anihilation considered *X0/365.667/, ! radiation length of air in kg/m2 *Ecrit/81.e-3/, ! critical energy of air in GeV *MaxComptonE/1./, ! compton is considered below 1 GeV *MaxPhotoE/1.e-3/, ! above this, PhotoElectric effect neg. *MinPhotoProdE/153.e-3/, ! below 153 MeV, no gp --> hadrons ! scattering const not MeV *Knockon true
subroutine mnprin(INKODE, FVAL)
subroutine mnstin(CRDBUF, IERR)
! 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
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
subroutine mncomd(FCN, CRDBIN, ICONDN, FUTIL)
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
subroutine mnpars(CRDBUF, ICONDN)
dE dx *! Nuc Int sampling table d
dE dx *! Nuc Int sampling table b
block data include Zlatfit h c fitting region data data data data data d0 data data d0 data data m
block data cblkElemag data *AnihiE ! Eposi< 1 TeV, anihilation considered *X0/365.667/, ! radiation length of air in kg/m2 *Ecrit/81.e-3/, ! critical energy of air in GeV *MaxComptonE/1./, ! compton is considered below 1 GeV *MaxPhotoE/1.e-3/, ! above this, PhotoElectric effect neg. *MinPhotoProdE/153.e-3/, ! below 153 MeV, no gp --> hadrons ! scattering const not MeV *Knockon ! knockon is considered Obsolete *PhotoProd false
dE dx *! Nuc Int sampling table h
dE dx *! Nuc Int sampling table g
! 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
dE dx *! Nuc Int sampling table f
dE dx *! Nuc Int sampling table c