COSMOS v7.655  COSMOSv7655
(AirShowerMC)
mnread.f File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine mnread (FCN, IFLGIN, IFLGUT, FUTIL)
 

Function/Subroutine Documentation

◆ mnread()

subroutine mnread ( external  FCN,
  IFLGIN,
  IFLGUT,
external  FUTIL 
)

Definition at line 10 of file mnread.f.

References a, b, c, d, e, f, false, g, h, softenpik::half, i, j, m, maxp, mncomd(), mnmatu(), mnpars(), mnprin(), mnseti(), mnstin(), n, o, p, parameter(), true, up(), x, xs, and z.

Referenced by minuit(), and mnintr().

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 CC Called from MINUIT. Reads all user input to MINUIT.
25 CC This routine is highly unstructured and defies normal logic.
26 CC
27 CC IFLGIN indicates the function originally requested:
28 CC = 1: read one-line title
29 CC 2: read parameter definitions
30 CC 3: read MINUIT commands
31 CC
32 CC IFLGUT= 1: reading terminated normally
33 CC 2: end-of-data on input
34 CC 3: unrecoverable read error
35 CC 4: unable to process parameter requests
36 CC 5: more than 100 incomprehensible commands
37 CC internally,
38 CC IFLGDO indicates the subfunction to be performed on the next
39 CC input record: 1: read a one-line title
40 CC 2: read a parameter definition
41 CC 3: read a command
42 CC 4: read in covariance matrix
43 CC for example, when IFLGIN=3, but IFLGDO=1, then it should read
44 CC a title, but this was requested by a command, not by MINUIT.
45 CC
46 *
47 * $Id: d506cm.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
48 *
49 * $Log: d506cm.inc,v $
50 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
51 * Minuit
52 *
53 *
54 *
55 *
56 * d506cm.inc
57 *
58  parameter(mne=100 , mni=50)
59  parameter(mnihl=mni*(mni+1)/2)
60  CHARACTER*10 cpnam
61  COMMON
62  1/mn7nam/ cpnam(mne)
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)
74 C
75  parameter(maxdbg=10, maxstk=10, maxcwd=20, maxp=30, maxcpt=101)
76  parameter(zero=0.0, one=1.0, half=0.5)
77  COMMON
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)
85  j/mn7arg/ word7(maxp)
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
94  EXTERNAL fcn,futil
95  CHARACTER crdbuf*80, cupbuf*10
96  CHARACTER cpromt(3)*40, clower*26, cupper*26
97  LOGICAL leof
98  DATA cpromt/' ENTER MINUIT TITLE, or "SET INPUT n" : ',
99  + ' ENTER MINUIT PARAMETER DEFINITION: ',
100  + ' ENTER MINUIT COMMAND: '/
101 C
102  DATA clower/'abcdefghijklmnopqrstuvwxyz'/
103  DATA cupper/'ABCDEFGHIJKLMNOPQRSTUVWXYZ'/
104 C
105  iflgut = 1
106  iflgdo = iflgin
107  leof = .false.
108  incomp = 0
109 C . . . . read next record
110  10 CONTINUE
111  IF (isw(6) .EQ. 1) THEN
112  WRITE (isyswr,'(A)') cpromt(iflgdo)
113  IF (iflgdo .EQ. 2) lphead = .false.
114  ENDIF
115  crdbuf = ' '
116  READ (isysrd,'(A)',err=500,end=45) crdbuf
117 C
118 C CUPBUF is the first few characters in upper case
119  cupbuf(1:10) = crdbuf(1:10)
120  DO 12 i= 1, 10
121  IF (crdbuf(i:i) .EQ. '''') GO TO 13
122  DO 11 ic= 1, 26
123  IF (crdbuf(i:i) .EQ. clower(ic:ic)) cupbuf(i:i)=cupper(ic:ic)
124  11 CONTINUE
125  12 CONTINUE
126  13 CONTINUE
127 C . . preemptive commands
128  leof = .false.
129  IF (index(cupbuf,'*EOF') .EQ. 1) THEN
130  WRITE (isyswr,'(A,I3)') ' *EOF ENCOUNTERED ON UNIT NO.',isysrd
131  lphead = .true.
132  GO TO 50
133  ENDIF
134  IF (index(cupbuf,'SET INP') .EQ. 1) THEN
135  icomnd = icomnd + 1
136  WRITE (isyswr, 21) icomnd,crdbuf(1:50)
137  21 FORMAT (' **********'/' **',i5,' **',a/' **********')
138  lphead = .true.
139  GO TO 50
140  ENDIF
141  GO TO 80
142 C . . hardware EOF on current ISYSRD
143  45 crdbuf = '*EOF '
144  WRITE (isyswr,'(A,I3)') ' END OF DATA ON UNIT NO.',isysrd
145 C or SET INPUT command
146  50 CONTINUE
147  CALL mnstin(crdbuf,ierr)
148  IF (ierr .EQ. 0) GO TO 10
149  IF (ierr .EQ. 2) THEN
150  IF (.NOT. leof) THEN
151  WRITE (isyswr,'(A,A/)') ' TWO CONSECUTIVE EOFs ON ',
152  + 'PRIMARY INPUT FILE WILL TERMINATE EXECUTION.'
153  leof = .true.
154  GO TO 10
155  ENDIF
156  ENDIF
157  iflgut = ierr
158  GO TO 900
159  80 IF (iflgdo .GT. 1) GO TO 100
160 C read title . . . . . IFLGDO = 1
161 C if title is 'SET TITLE', skip and read again
162  IF (index(cupbuf,'SET TIT') .EQ. 1) GO TO 10
163  CALL mnseti(crdbuf(1:50))
164  WRITE (isyswr,'(1X,A50)') ctitl
165  WRITE (isyswr,'(1X,78(1H*))')
166  lphead = .true.
167  IF (iflgin .EQ. iflgdo) GO TO 900
168  iflgdo = iflgin
169  GO TO 10
170 C data record is not a title.
171  100 CONTINUE
172  IF (iflgdo .GT. 2) GO TO 300
173 C expect parameter definitions. IFLGDO = 2
174 C if parameter def is 'PARAMETER', skip and read again
175  IF (index(cupbuf,'PAR') .EQ. 1) GO TO 10
176 C if line starts with SET TITLE, read a title first
177  IF (index(cupbuf,'SET TIT') .EQ. 1) THEN
178  iflgdo = 1
179  GO TO 10
180  ENDIF
181 C we really have parameter definitions now
182  CALL mnpars(crdbuf,icondp)
183  IF (icondp .EQ. 0) GO TO 10
184 C format error
185  IF (icondp .EQ. 1) THEN
186  IF (isw(6) .EQ. 1) THEN
187  WRITE (isyswr,'(A)') ' FORMAT ERROR. IGNORED. ENTER AGAIN.'
188  GO TO 10
189  ELSE
190  WRITE (isyswr,'(A)') ' ERROR IN PARAMETER DEFINITION'
191  iflgut = 4
192  GO TO 900
193  ENDIF
194  ENDIF
195 C ICONDP = 2 . . . end parameter requests
196  IF (isw(5).GE.0 .AND. isw(6).LT.1) WRITE (isyswr,'(4X,75(1H*))')
197  lphead = .true.
198  IF (iflgin .EQ. iflgdo) GO TO 900
199  iflgdo = iflgin
200  GO TO 10
201 C . . . . . IFLGDO = 3
202 C read commands
203  300 CONTINUE
204  CALL mncomd(fcn,crdbuf,icondn,futil)
205 CC ICONDN = 0: command executed normally
206 CC 1: command is blank, ignored
207 CC 2: command line unreadable, ignored
208 CC 3: unknown command, ignored
209 CC 4: abnormal termination (e.g., MIGRAD not converged)
210 CC 5: command is a request to read PARAMETER definitions
211 CC 6: 'SET INPUT' command
212 CC 7: 'SET TITLE' command
213 CC 8: 'SET COVAR' command
214 CC 9: reserved
215 CC 10: END command
216 CC 11: EXIT or STOP command
217 CC 12: RETURN command
218  IF (icondn .EQ. 2 .OR. icondn .EQ. 3) THEN
219  incomp = incomp + 1
220  IF (incomp .GT. 100) THEN
221  iflgut = 5
222  GO TO 900
223  ENDIF
224  ENDIF
225 C parameter
226  IF (icondn .EQ. 5) iflgdo = 2
227 C SET INPUT
228  IF (icondn .EQ. 6) GO TO 50
229 C SET TITLE
230  IF (icondn .EQ. 7) iflgdo = 1
231 C . . . . . . . . . . set covar
232  IF (icondn .EQ. 8) THEN
233  icomnd = icomnd + 1
234  WRITE (isyswr,405) icomnd,crdbuf(1:50)
235  405 FORMAT (1h ,10(1h*)/' **',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,3x)
240  isw(2) = 3
241  dcovar = 0.0
242  IF (isw(5) .GE. 0) CALL mnmatu(1)
243  IF (isw(5) .GE. 1) CALL mnprin(2,amin)
244  GO TO 10
245  ENDIF
246  IF (icondn .LT. 10) GO TO 10
247  GO TO 900
248 C . . . . error conditions
249  500 iflgut = 3
250  900 RETURN
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 mnseti(TIT)
Definition: mnseti.f:10
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
Definition: cblkElemag.h:7
real(4), dimension(:), allocatable, save h
Definition: cNRLAtmos.f:28
subroutine mnprin(INKODE, FVAL)
Definition: mnprin.f:10
subroutine mnstin(CRDBUF, IERR)
Definition: mnstin.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
subroutine mncomd(FCN, CRDBIN, ICONDN, FUTIL)
Definition: mncomd.f:10
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
struct ob o[NpMax]
Definition: Zprivate.h:34
subroutine mnpars(CRDBUF, ICONDN)
Definition: mnpars.f:10
dE dx *! Nuc Int sampling table d
Definition: cblkMuInt.h:130
subroutine mnmatu(KODE)
Definition: mnmatu.f:10
block data include Zlatfit h c fitting region data data data data data d0 data data d0 data data m
Definition: ZlatfitBD.h:35
real(4), save a
Definition: cNRLAtmos.f:20
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
Definition: cblkElemag.h:7
dE dx *! Nuc Int sampling table g
Definition: cblkMuInt.h:130
real(4), save b
Definition: cNRLAtmos.f:21
!onst int maxp
Definition: Zprivate.h:3
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
Here is the call graph for this function:
Here is the caller graph for this function: