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

Go to the source code of this file.

Functions/Subroutines

subroutine mninit (I1, I2, I3)
 

Function/Subroutine Documentation

◆ mninit()

subroutine mninit (   I1,
  I2,
  I3 
)

Definition at line 34 of file mninit.f.

References a, b, c, d, e, f, false, g, h, softenpik::half, i, j, m, maxp, mncler(), mntiny(), n, o, p, parameter(), true, up(), x, xs, and z.

Referenced by fitlat1(), fittime1(), fittran(), and minuit().

34 *
35 * $Id: d506dp.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
36 *
37 * $Log: d506dp.inc,v $
38 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
39 * Minuit
40 *
41 *
42 *
43 *
44 * d506dp.inc
45 *
46 C ************ DOUBLE PRECISION VERSION *************
47  IMPLICIT DOUBLE PRECISION (a-h,o-z)
48 CC This is the main initialization subroutine for MINUIT
49 CC It initializes some constants in common
50 CC (including the logical I/O unit nos.),
51 CC
52 *
53 * $Id: d506cm.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
54 *
55 * $Log: d506cm.inc,v $
56 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
57 * Minuit
58 *
59 *
60 *
61 *
62 * d506cm.inc
63 *
64  parameter(mne=100 , mni=50)
65  parameter(mnihl=mni*(mni+1)/2)
66  CHARACTER*10 cpnam
67  COMMON
68  1/mn7nam/ cpnam(mne)
69  2/mn7ext/ u(mne) ,alim(mne) ,blim(mne)
70  3/mn7err/ erp(mni) ,ern(mni) ,werr(mni) ,globcc(mni)
71  4/mn7inx/ nvarl(mne) ,niofex(mne),nexofi(mni)
72  5/mn7int/ x(mni) ,xt(mni) ,dirin(mni)
73  6/mn7fx2/ xs(mni) ,xts(mni) ,dirins(mni)
74  7/mn7der/ grd(mni) ,g2(mni) ,gstep(mni) ,gin(mne) ,dgrd(mni)
75  8/mn7fx3/ grds(mni) ,g2s(mni) ,gsteps(mni)
76  9/mn7fx1/ ipfix(mni) ,npfix
77  a/mn7var/ vhmat(mnihl)
78  b/mn7vat/ vthmat(mnihl)
79  c/mn7sim/ p(mni,mni+1),pstar(mni),pstst(mni) ,pbar(mni),prho(mni)
80 C
81  parameter(maxdbg=10, maxstk=10, maxcwd=20, maxp=30, maxcpt=101)
82  parameter(zero=0.0, one=1.0, half=0.5)
83  COMMON
84  d/mn7npr/ maxint ,npar ,maxext ,nu
85  e/mn7iou/ isysrd ,isyswr ,isyssa ,npagwd ,npagln ,newpag
86  e/mn7io2/ istkrd(maxstk) ,nstkrd ,istkwr(maxstk) ,nstkwr
87  f/mn7tit/ cfrom ,cstatu ,ctitl ,cword ,cundef ,cvrsn ,covmes
88  g/mn7flg/ isw(7) ,idbg(0:maxdbg) ,nblock ,icomnd
89  h/mn7min/ amin ,up ,edm ,fval3 ,epsi ,apsi ,dcovar
90  i/mn7cnv/ nfcn ,nfcnmx ,nfcnlc ,nfcnfr ,itaur,istrat,nwrmes(2)
91  j/mn7arg/ word7(maxp)
92  k/mn7log/ lwarn ,lrepor ,limset ,lnolim ,lnewmn ,lphead
93  l/mn7cns/ epsmac ,epsma2 ,vlimlo ,vlimhi ,undefi ,bigedm,updflt
94  m/mn7rpt/ xpt(maxcpt) ,ypt(maxcpt)
95  n/mn7cpt/ chpt(maxcpt)
96  o/mn7xcr/ xmidcr ,ymidcr ,xdircr ,ydircr ,ke1cr ,ke2cr
97  CHARACTER ctitl*50, cword*(maxcwd), cundef*10, cfrom*8,
98  + cvrsn*6, covmes(0:3)*22, cstatu*10, chpt*1
99  LOGICAL lwarn, lrepor, limset, lnolim, lnewmn, lphead
100 C
101  EXTERNAL intrac
102  LOGICAL intrac
103 C I/O unit numbers
104  isysrd = i1
105  isyswr = i2
106  istkwr(1) = isyswr
107  nstkwr = 1
108  isyssa = i3
109  nstkrd = 0
110 C version identifier
111  cvrsn = '96.03 '
112 C some CONSTANT constants in COMMON
113  maxint=mni
114  maxext=mne
115  undefi = -54321.
116  bigedm = 123456.
117  cundef = ')UNDEFINED'
118  covmes(0) = 'NO ERROR MATRIX '
119  covmes(1) = 'ERR MATRIX APPROXIMATE'
120  covmes(2) = 'ERR MATRIX NOT POS-DEF'
121  covmes(3) = 'ERROR MATRIX ACCURATE '
122 C some starting values in COMMON
123  nblock = 0
124  icomnd = 0
125  ctitl = cundef
126  cfrom = 'INPUT '
127  nfcnfr = nfcn
128  cstatu= 'INITIALIZE'
129  isw(3) = 0
130  isw(4) = 0
131  isw(5) = 1
132 C ISW(6)=0 for batch jobs, =1 for interactive jobs
133 C =-1 for originally interactive temporarily batch
134  isw(6) = 0
135  IF (intrac(dummy)) isw(6) = 1
136 C DEBUG options set to default values
137  DO 10 idb= 0, maxdbg
138  10 idbg(idb) = 0
139  lrepor = .false.
140  lwarn = .true.
141  limset = .false.
142  lnewmn = .false.
143  istrat = 1
144  itaur = 0
145 C default page dimensions and 'new page' carriage control integer
146  npagwd = 120
147  npagln = 56
148  newpag = 1
149  IF (isw(6) .GT. 0) THEN
150  npagwd = 80
151  npagln = 30
152  newpag = 0
153  ENDIF
154  up = 1.0
155  updflt = up
156 C determine machine accuracy epsmac
157  epstry = 0.5
158  DO 33 i= 1, 100
159  epstry = epstry * 0.5
160  epsp1 = one + epstry
161  CALL mntiny(epsp1, epsbak)
162  IF (epsbak .LT. epstry) GO TO 35
163  33 CONTINUE
164  epstry = 1.0e-7
165  epsmac = 4.0*epstry
166  WRITE (isyswr,'(A,A,E10.2)') ' MNINIT UNABLE TO DETERMINE',
167  + ' ARITHMETIC PRECISION. WILL ASSUME:',epsmac
168  35 epsmac = 8.0 * epstry
169  epsma2 = 2.0 * sqrt(epsmac)
170 C the vlims are a non-negligible distance from pi/2
171 C used by MNPINT to set variables "near" the physical limits
172  piby2 = 2.0*atan(1.0)
173  distnn = 8.0*sqrt(epsma2)
174  vlimhi = piby2 - distnn
175  vlimlo = -piby2 + distnn
176  CALL mncler
177  WRITE (isyswr,'(3A,I3,A,I3,A,E10.2)') ' MINUIT RELEASE ',cvrsn,
178  +' INITIALIZED. DIMENSIONS ',mne,'/',mni,' EPSMAC=',epsmac
179  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
subroutine mntiny(EPSP1, EPSBAK)
Definition: mntiny.f:10
nodes i
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
! 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
dE dx *! Nuc Int sampling table d
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
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: