COSMOS v7.655  COSMOSv7655
(AirShowerMC)
mnset.f
Go to the documentation of this file.
1 *
2 * $Id: mnset.F,v 1.2 1996/03/15 18:02:52 james Exp $
3 *
4 * $Log: mnset.F,v $
5 * Revision 1.2 1996/03/15 18:02:52 james
6 * Modified Files:
7 * mnderi.F eliminate possible division by zero
8 * mnexcm.F suppress print on STOP when print flag=-1
9 * set FVAL3 to flag if FCN already called with IFLAG=3
10 * mninit.F set version 96.03
11 * mnlims.F remove arguments, not needed
12 * mnmigr.F VLEN -> LENV in debug print statement
13 * mnparm.F move call to MNRSET to after NPAR redefined, to zero all
14 * mnpsdf.F eliminate possible division by zero
15 * mnscan.F suppress printout when print flag =-1
16 * mnset.F remove arguments in call to MNLIMS
17 * mnsimp.F fix CSTATU so status is PROGRESS only if new minimum
18 * mnvert.F eliminate possible division by zero
19 *
20 * Revision 1.1.1.1 1996/03/07 14:31:29 mclareni
21 * Minuit
22 *
23 *
24  SUBROUTINE mnset(FCN,FUTIL)
25 *
26 * $Id: d506dp.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
27 *
28 * $Log: d506dp.inc,v $
29 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
30 * Minuit
31 *
32 *
33 *
34 *
35 * d506dp.inc
36 *
37 C ************ DOUBLE PRECISION VERSION *************
38  IMPLICIT DOUBLE PRECISION (a-h,o-z)
39 CC Called from MNEXCM
40 CC Interprets the commands that start with SET and SHOW
41 CC
42 *
43 * $Id: d506cm.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
44 *
45 * $Log: d506cm.inc,v $
46 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
47 * Minuit
48 *
49 *
50 *
51 *
52 * d506cm.inc
53 *
54  parameter(mne=100 , mni=50)
55  parameter(mnihl=mni*(mni+1)/2)
56  CHARACTER*10 CPNAM
57  COMMON
58  1/mn7nam/ cpnam(mne)
59  2/mn7ext/ u(mne) ,alim(mne) ,blim(mne)
60  3/mn7err/ erp(mni) ,ern(mni) ,werr(mni) ,globcc(mni)
61  4/mn7inx/ nvarl(mne) ,niofex(mne),nexofi(mni)
62  5/mn7int/ x(mni) ,xt(mni) ,dirin(mni)
63  6/mn7fx2/ xs(mni) ,xts(mni) ,dirins(mni)
64  7/mn7der/ grd(mni) ,g2(mni) ,gstep(mni) ,gin(mne) ,dgrd(mni)
65  8/mn7fx3/ grds(mni) ,g2s(mni) ,gsteps(mni)
66  9/mn7fx1/ ipfix(mni) ,npfix
67  a/mn7var/ vhmat(mnihl)
68  b/mn7vat/ vthmat(mnihl)
69  c/mn7sim/ p(mni,mni+1),pstar(mni),pstst(mni) ,pbar(mni),prho(mni)
70 C
71  parameter(maxdbg=10, maxstk=10, maxcwd=20, maxp=30, maxcpt=101)
72  parameter(zero=0.0, one=1.0, half=0.5)
73  COMMON
74  d/mn7npr/ maxint ,npar ,maxext ,nu
75  e/mn7iou/ isysrd ,isyswr ,isyssa ,npagwd ,npagln ,newpag
76  e/mn7io2/ istkrd(maxstk) ,nstkrd ,istkwr(maxstk) ,nstkwr
77  f/mn7tit/ cfrom ,cstatu ,ctitl ,cword ,cundef ,cvrsn ,covmes
78  g/mn7flg/ isw(7) ,idbg(0:maxdbg) ,nblock ,icomnd
79  h/mn7min/ amin ,up ,edm ,fval3 ,epsi ,apsi ,dcovar
80  i/mn7cnv/ nfcn ,nfcnmx ,nfcnlc ,nfcnfr ,itaur,istrat,nwrmes(2)
81  j/mn7arg/ word7(maxp)
82  k/mn7log/ lwarn ,lrepor ,limset ,lnolim ,lnewmn ,lphead
83  l/mn7cns/ epsmac ,epsma2 ,vlimlo ,vlimhi ,undefi ,bigedm,updflt
84  m/mn7rpt/ xpt(maxcpt) ,ypt(maxcpt)
85  n/mn7cpt/ chpt(maxcpt)
86  o/mn7xcr/ xmidcr ,ymidcr ,xdircr ,ydircr ,ke1cr ,ke2cr
87  CHARACTER CTITL*50, CWORD*(maxcwd), CUNDEF*10, CFROM*8,
88  + cvrsn*6, covmes(0:3)*22, cstatu*10, chpt*1
89  LOGICAL LWARN, LREPOR, LIMSET, LNOLIM, LNEWMN, LPHEAD
90 C
91  EXTERNAL fcn,futil
92 C file characteristics for SET INPUT
93  LOGICAL LNAME
94  CHARACTER CFNAME*64, CMODE*16
95 C 'SET ' or 'SHOW', 'ON ' or 'OFF', 'SUPPRESSED' or 'REPORTED '
96  CHARACTER CKIND*4, COPT*3, CWARN*10
97 C explanation of print level numbers -1:3 and strategies 0:2
98  CHARACTER CPRLEV(-1:3)*34 ,CSTRAT(0:2)*44
99 C identification of debug options
100  parameter(numdbg = 6)
101  CHARACTER*40 CDBOPT(0:numdbg)
102 C things that can be set or shown
103  CHARACTER*10 CNAME(30)
104  DATA cname( 1)/'FCN value '/
105  DATA cname( 2)/'PARameters'/
106  DATA cname( 3)/'LIMits '/
107  DATA cname( 4)/'COVariance'/
108  DATA cname( 5)/'CORrelatio'/
109  DATA cname( 6)/'PRInt levl'/
110  DATA cname( 7)/'NOGradient'/
111  DATA cname( 8)/'GRAdient '/
112  DATA cname( 9)/'ERRor def '/
113  DATA cname(10)/'INPut file'/
114  DATA cname(11)/'WIDth page'/
115  DATA cname(12)/'LINes page'/
116  DATA cname(13)/'NOWarnings'/
117  DATA cname(14)/'WARnings '/
118  DATA cname(15)/'RANdom gen'/
119  DATA cname(16)/'TITle '/
120  DATA cname(17)/'STRategy '/
121  DATA cname(18)/'EIGenvalue'/
122  DATA cname(19)/'PAGe throw'/
123  DATA cname(20)/'MINos errs'/
124  DATA cname(21)/'EPSmachine'/
125  DATA cname(22)/'OUTputfile'/
126  DATA cname(23)/'BATch '/
127  DATA cname(24)/'INTeractiv'/
128  DATA cname(25)/'VERsion '/
129  DATA nname/25/
130 C options not intended for normal users
131  DATA cname(26)/'reserve '/
132  DATA cname(27)/'NODebug '/
133  DATA cname(28)/'DEBug '/
134  DATA cname(29)/'SHOw '/
135  DATA cname(30)/'SET '/
136  DATA nntot/30/
137 C
138  DATA cprlev(-1)/'-1: NO OUTPUT EXCEPT FROM "SHOW" '/
139  DATA cprlev( 0)/' 0: REDUCED OUTPUT '/
140  DATA cprlev( 1)/' 1: NORMAL OUTPUT '/
141  DATA cprlev( 2)/' 2: EXTRA OUTPUT FOR PROBLEM CASES'/
142  DATA cprlev( 3)/' 3: MAXIMUM OUTPUT '/
143 C
144  DATA cstrat( 0)/' 0: MINIMIZE THE NUMBER OF CALLS TO FUNCTION'/
145  DATA cstrat( 1)/' 1: TRY TO BALANCE SPEED AGAINST RELIABILITY'/
146  DATA cstrat( 2)/' 2: MAKE SURE MINIMUM TRUE, ERRORS CORRECT '/
147 C
148  DATA cdbopt(0)/'REPORT ALL EXCEPTIONAL CONDITIONS '/
149  DATA cdbopt(1)/'MNLINE: LINE SEARCH MINIMIZATION '/
150  DATA cdbopt(2)/'MNDERI: FIRST DERIVATIVE CALCULATIONS '/
151  DATA cdbopt(3)/'MNHESS: SECOND DERIVATIVE CALCULATIONS '/
152  DATA cdbopt(4)/'MNMIGR: COVARIANCE MATRIX UPDATES '/
153  DATA cdbopt(5)/'MNHES1: FIRST DERIVATIVE UNCERTAINTIES '/
154  DATA cdbopt(6)/'MNCONT: MNCONTOUR PLOT (MNCROS SEARCH) '/
155 C
156 C
157  DO 2 i= 1, nntot
158  IF (index(cword(4:10),cname(i)(1:3)) .GT. 0) GO TO 5
159  2 CONTINUE
160  i = 0
161  5 kname = i
162 C
163 C Command could be SET xxx, SHOW xxx, HELP SET or HELP SHOW
164  IF (index(cword(1:4),'HEL') .GT. 0) GO TO 2000
165  IF (index(cword(1:4),'SHO') .GT. 0) GO TO 1000
166  IF (index(cword(1:4),'SET') .EQ. 0) GO TO 1900
167 C ---
168  ckind = 'SET '
169 C . . . . . . . . . . set unknown
170  IF (kname .LE. 0) GO TO 1900
171 C . . . . . . . . . . set known
172  GO TO(3000, 20, 30, 40,3000, 60, 70, 80, 90, 100,
173  + 110, 120, 130, 140, 150, 160, 170,3000, 190,3000,
174  + 210, 220, 230, 240,3000,1900, 270, 280, 290, 300) , kname
175 C
176 C . . . . . . . . . . set param
177  20 CONTINUE
178  iprm = word7(1)
179  IF (iprm .GT. nu) GO TO 25
180  IF (iprm .LE. 0) GO TO 25
181  IF (nvarl(iprm) .LT. 0) GO TO 25
182  u(iprm) = word7(2)
183  CALL mnexin(x)
184  isw2 = isw(2)
185  CALL mnrset(1)
186 C Keep approximate covariance matrix, even if new param value
187  isw(2) = min(isw2,1)
188  cfrom = 'SET PARM'
189  nfcnfr = nfcn
190  cstatu = 'NEW VALUES'
191  GO TO 4000
192  25 WRITE (isyswr,'(A/)') ' UNDEFINED PARAMETER NUMBER. IGNORED.'
193  GO TO 4000
194 C . . . . . . . . . . set limits
195  30 CALL mnlims
196  GO TO 4000
197 C . . . . . . . . . . set covar
198  40 CONTINUE
199 C this command must be handled by MNREAD, and is not Fortran-callable
200  GO TO 3000
201 C . . . . . . . . . . set print
202  60 isw(5) = word7(1)
203  GO TO 4000
204 C . . . . . . . . . . set nograd
205  70 isw(3) = 0
206  GO TO 4000
207 C . . . . . . . . . . set grad
208  80 CALL mngrad(fcn,futil)
209  GO TO 4000
210 C . . . . . . . . . . set errdef
211  90 IF (word7(1) .EQ. up) GO TO 4000
212  IF (word7(1) .LE. zero) THEN
213  IF (up .EQ. updflt) GO TO 4000
214  up = updflt
215  ELSE
216  up = word7(1)
217  ENDIF
218  DO 95 i= 1, npar
219  ern(i) = 0.
220  95 erp(i) = 0.
221  CALL mnwerr
222  GO TO 4000
223 C . . . . . . . . . . set input
224 C This command must be handled by MNREAD. If it gets this far,
225 C it is illegal.
226  100 CONTINUE
227  GO TO 3000
228 C . . . . . . . . . . set width
229  110 npagwd = word7(1)
230  npagwd = max(npagwd,50)
231  GO TO 4000
232 C . . . . . . . . . . set lines
233  120 npagln = word7(1)
234  GO TO 4000
235 C . . . . . . . . . . set nowarn
236  130 lwarn = .false.
237  GO TO 4000
238 C . . . . . . . . . . set warn
239  140 lwarn = .true.
240  CALL mnwarn('W','SHO','SHO')
241  GO TO 4000
242 C . . . . . . . . . . set random
243  150 jseed = int(word7(1))
244  val = 3.
245  CALL mnrn15(val, jseed)
246  IF (isw(5) .GT. 0) WRITE (isyswr, 151) jseed
247  151 FORMAT (' MINUIT RANDOM NUMBER SEED SET TO ',i10)
248  GO TO 4000
249 C . . . . . . . . . . set title
250  160 CONTINUE
251 C this command must be handled by MNREAD, and is not Fortran-callable
252  GO TO 3000
253 C . . . . . . . . . set strategy
254  170 istrat = word7(1)
255  istrat = max(istrat,0)
256  istrat = min(istrat,2)
257  IF (isw(5) .GT. 0) GO TO 1172
258  GO TO 4000
259 C . . . . . . . . . set page throw
260  190 newpag = word7(1)
261  GO TO 1190
262 C . . . . . . . . . . set epsmac
263  210 IF (word7(1).GT.zero .AND. word7(1).LT.0.1) epsmac = word7(1)
264  epsma2 = sqrt(epsmac)
265  GO TO 1210
266 C . . . . . . . . . . set outputfile
267  220 CONTINUE
268  iunit = word7(1)
269  isyswr = iunit
270  istkwr(1) = iunit
271  IF (isw(5) .GE. 0) GO TO 1220
272  GO TO 4000
273 C . . . . . . . . . . set batch
274  230 isw(6) = 0
275  IF (isw(5) .GE. 0) GO TO 1100
276  GO TO 4000
277 C . . . . . . . . . . set interactive
278  240 isw(6) = 1
279  IF (isw(5) .GE. 0) GO TO 1100
280  GO TO 4000
281 C . . . . . . . . . . set nodebug
282  270 iset = 0
283  GO TO 281
284 C . . . . . . . . . . set debug
285  280 iset = 1
286  281 CONTINUE
287  idbopt = word7(1)
288  IF (idbopt .GT. numdbg) GO TO 288
289  IF (idbopt .GE. 0) THEN
290  idbg(idbopt) = iset
291  IF (iset .EQ. 1) idbg(0) = 1
292  ELSE
293 C SET DEBUG -1 sets all debug options
294  DO 285 id= 0, numdbg
295  285 idbg(id) = iset
296  ENDIF
297  lrepor = (idbg(0) .GE. 1)
298  CALL mnwarn('D','SHO','SHO')
299  GO TO 4000
300  288 WRITE (isyswr,289) idbopt
301  289 FORMAT (' UNKNOWN DEBUG OPTION',i6,' REQUESTED. IGNORED')
302  GO TO 4000
303 C . . . . . . . . . . set show
304  290 CONTINUE
305 C . . . . . . . . . . set set
306  300 CONTINUE
307  GO TO 3000
308 C -----------------------------------------------------
309  1000 CONTINUE
310 C at this point, CWORD must be 'SHOW'
311  ckind = 'SHOW'
312  IF (kname .LE. 0) GO TO 1900
313  GO TO (1010,1020,1030,1040,1050,1060,1070,1070,1090,1100,
314  + 1110,1120,1130,1130,1150,1160,1170,1180,1190,1200,
315  + 1210,1220,1100,1100,1250,1900,1270,1270,1290,1300),kname
316 C
317 C . . . . . . . . . . show fcn
318  1010 CONTINUE
319  IF (amin .EQ. undefi) CALL mnamin(fcn,futil)
320  CALL mnprin (0,amin)
321  GO TO 4000
322 C . . . . . . . . . . show param
323  1020 CONTINUE
324  IF (amin .EQ. undefi) CALL mnamin(fcn,futil)
325  CALL mnprin (5,amin)
326  GO TO 4000
327 C . . . . . . . . . . show limits
328  1030 CONTINUE
329  IF (amin .EQ. undefi) CALL mnamin(fcn,futil)
330  CALL mnprin (1,amin)
331  GO TO 4000
332 C . . . . . . . . . . show covar
333  1040 CALL mnmatu(1)
334  GO TO 4000
335 C . . . . . . . . . . show corre
336  1050 CALL mnmatu(0)
337  GO TO 4000
338 C . . . . . . . . . . show print
339  1060 CONTINUE
340  IF (isw(5) .LT.-1) isw(5) = -1
341  IF (isw(5) .GT. 3) isw(5) = 3
342  WRITE (isyswr,'(A)') ' ALLOWED PRINT LEVELS ARE:'
343  WRITE (isyswr,'(27X,A)') cprlev
344  WRITE (isyswr,1061) cprlev(isw(5))
345  1061 FORMAT (/' CURRENT PRINTOUT LEVEL IS ',a)
346  GO TO 4000
347 C . . . . . . . show nograd, grad
348  1070 CONTINUE
349  IF (isw(3) .LE. 0) THEN
350  WRITE (isyswr, 1081)
351  1081 FORMAT(' NOGRAD IS SET. DERIVATIVES NOT COMPUTED IN FCN.')
352  ELSE
353  WRITE (isyswr, 1082)
354  1082 FORMAT(' GRAD IS SET. USER COMPUTES DERIVATIVES IN FCN.')
355  ENDIF
356  GO TO 4000
357 C . . . . . . . . . . show errdef
358  1090 WRITE (isyswr, 1091) up
359  1091 FORMAT (' ERRORS CORRESPOND TO FUNCTION CHANGE OF',g13.5)
360  GO TO 4000
361 C . . . . . . . . . . show input,
362 C batch, or interactive
363  1100 CONTINUE
364  INQUIRE(unit=isysrd,named=lname,name=cfname)
365  cmode = 'BATCH MODE '
366  IF (isw(6) .EQ. 1) cmode = 'INTERACTIVE MODE'
367  IF (.NOT. lname) cfname='unknown'
368  WRITE (isyswr,1002) cmode,isysrd,cfname
369  1002 FORMAT (' INPUT NOW BEING READ IN ',a,' FROM UNIT NO.',i3/
370  + ' FILENAME: ',a)
371  GO TO 4000
372 C . . . . . . . . . . show width
373  1110 WRITE (isyswr,1111) npagwd
374  1111 FORMAT (10x,'PAGE WIDTH IS SET TO',i4,' COLUMNS')
375  GO TO 4000
376 C . . . . . . . . . . show lines
377  1120 WRITE (isyswr,1121) npagln
378  1121 FORMAT (10x,'PAGE LENGTH IS SET TO',i4,' LINES')
379  GO TO 4000
380 C . . . . . . .show nowarn, warn
381  1130 CONTINUE
382  cwarn = 'SUPPRESSED'
383  IF (lwarn) cwarn = 'REPORTED '
384  WRITE (isyswr,1141) cwarn
385  1141 FORMAT (' MINUIT WARNING MESSAGES ARE ',a)
386  IF (.NOT. lwarn) CALL mnwarn('W','SHO','SHO')
387  GO TO 4000
388 C . . . . . . . . . . show random
389  1150 val = 0.
390  CALL mnrn15(val,igrain)
391  ikseed = igrain
392  WRITE (isyswr, 1151) ikseed
393  1151 FORMAT (' MINUIT RNDM SEED IS CURRENTLY=',i10/)
394  val = 3.0
395  iseed = ikseed
396  CALL mnrn15(val,iseed)
397  GO TO 4000
398 C . . . . . . . . . show title
399  1160 WRITE (isyswr,'(A,A)') ' TITLE OF CURRENT TASK IS:',ctitl
400  GO TO 4000
401 C . . . . . . . show strategy
402  1170 WRITE (isyswr, '(A)') ' ALLOWED STRATEGIES ARE:'
403  WRITE (isyswr, '(20X,A)') cstrat
404  1172 WRITE (isyswr, 1175) cstrat(istrat)
405  1175 FORMAT (/' NOW USING STRATEGY ',a/)
406  GO TO 4000
407 C . . . . . show eigenvalues
408  1180 CONTINUE
409  iswsav = isw(5)
410  isw(5) = 3
411  IF (isw(2) .LT. 1) THEN
412  WRITE (isyswr,'(1X,A)') covmes(0)
413  ELSE
414  CALL mnpsdf
415  ENDIF
416  isw(5) = iswsav
417  GO TO 4000
418 C . . . . . show page throw
419  1190 WRITE (isyswr,'(A,I3)') ' PAGE THROW CARRIAGE CONTROL =',newpag
420  IF (newpag .EQ. 0)
421  + WRITE (isyswr,'(A)') ' NO PAGE THROWS IN MINUIT OUTPUT'
422  GO TO 4000
423 C . . . . . . show minos errors
424  1200 CONTINUE
425  DO 1202 ii= 1, npar
426  IF (erp(ii).GT.zero .OR. ern(ii).LT.zero) GO TO 1204
427  1202 CONTINUE
428  WRITE (isyswr,'(A)')
429  + ' THERE ARE NO MINOS ERRORS CURRENTLY VALID.'
430  GO TO 4000
431  1204 CONTINUE
432  CALL mnprin(4,amin)
433  GO TO 4000
434 C . . . . . . . . . show epsmac
435  1210 WRITE (isyswr,'(A,E12.3)')
436  + ' FLOATING-POINT NUMBERS ASSUMED ACCURATE TO',epsmac
437  GO TO 4000
438 C . . . . . . show outputfiles
439  1220 CONTINUE
440  WRITE (isyswr,'(A,I4)') ' MINUIT PRIMARY OUTPUT TO UNIT',isyswr
441  GO TO 4000
442 C . . . . . . show version
443  1250 CONTINUE
444  WRITE (isyswr,'(A,A)') ' THIS IS MINUIT VERSION:',cvrsn
445  GO TO 4000
446 C . . . . . . show nodebug, debug
447  1270 CONTINUE
448  DO 1285 id= 0, numdbg
449  copt = 'OFF'
450  IF (idbg(id) .GE. 1) copt = 'ON '
451  1285 WRITE (isyswr,1286) id, copt, cdbopt(id)
452  1286 FORMAT (10x,'DEBUG OPTION',i3,' IS ',a3,' :',a)
453  IF (.NOT. lrepor) CALL mnwarn('D','SHO','SHO')
454  GO TO 4000
455 C . . . . . . . . . . show show
456  1290 ckind = 'SHOW'
457  GO TO 2100
458 C . . . . . . . . . . show set
459  1300 ckind = 'SET '
460  GO TO 2100
461 C -----------------------------------------------------
462 C UNKNOWN COMMAND
463  1900 WRITE (isyswr, 1901) cword
464  1901 FORMAT (' THE COMMAND:',a10,' IS UNKNOWN.'/)
465  GO TO 2100
466 C -----------------------------------------------------
467 C HELP SHOW, HELP SET, SHOW SET, or SHOW SHOW
468  2000 ckind = 'SET '
469  IF (index(cword(4:10),'SHO') .GT. 0) ckind = 'SHOW'
470  2100 WRITE (isyswr, 2101) ckind,ckind, (cname(kk),kk=1,nname)
471  2101 FORMAT (' THE FORMAT OF THE ',a4,' COMMAND IS:'//
472  + 1x,a4,' xxx [numerical arguments if any]'//
473  + ' WHERE xxx MAY BE ONE OF THE FOLLOWING:'/
474  + (7x,6a12))
475  GO TO 4000
476 C -----------------------------------------------------
477 C ILLEGAL COMMAND
478  3000 WRITE (isyswr,'('' ABOVE COMMAND IS ILLEGAL. IGNORED'')')
479  4000 RETURN
480  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 mnwerr
Definition: mnwerr.f:10
subroutine mnlims
Definition: mnlims.f:25
subroutine mngrad(FCN, FUTIL)
Definition: mngrad.f:10
subroutine mnrset(IOPT)
Definition: mnrset.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
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
subroutine mnamin(FCN, FUTIL)
Definition: mnamin.f:10
********************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
struct ob o[NpMax]
Definition: Zprivate.h:34
subroutine mnpsdf
Definition: mnpsdf.f:25
dE dx *! Nuc Int sampling table d
Definition: cblkMuInt.h:130
nodes a
subroutine mnmatu(KODE)
Definition: mnmatu.f:10
subroutine mnset(FCN, FUTIL)
Definition: mnset.f:25
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
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 h
Definition: cblkMuInt.h:130
dE dx *! Nuc Int sampling table g
Definition: cblkMuInt.h:130
!onst int maxp
Definition: Zprivate.h:3
subroutine mnexin(PINT)
Definition: mnexin.f:10
subroutine mnwarn(COPT, CORG, CMES)
Definition: mnwarn.f:10
subroutine mnrn15(VAL, INSEED)
Definition: mnrn15.f:10
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