COSMOS v7.655  COSMOSv7655
(AirShowerMC)
mnerrs.f
Go to the documentation of this file.
1 *
2 * $Id: mnerrs.F,v 1.1.1.1 1996/03/07 14:31:29 mclareni Exp $
3 *
4 * $Log: mnerrs.F,v $
5 * Revision 1.1.1.1 1996/03/07 14:31:29 mclareni
6 * Minuit
7 *
8 *
9  SUBROUTINE mnerrs(NUMBER,EPLUS,EMINUS,EPARAB,GCC)
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 by user, utility routine to get MINOS errors
25 CC If NUMBER is positive, then it is external parameter number,
26 CC if negative, it is -internal number.
27 CC values returned by MNERRS:
28 CC EPLUS, EMINUS are MINOS errors of parameter NUMBER,
29 CC EPARAB is 'parabolic' error (from error matrix).
30 CC (Errors not calculated are set = 0.)
31 CC GCC is global correlation coefficient from error matrix
32 *
33 * $Id: d506cm.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
34 *
35 * $Log: d506cm.inc,v $
36 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
37 * Minuit
38 *
39 *
40 *
41 *
42 * d506cm.inc
43 *
44  parameter(mne=100 , mni=50)
45  parameter(mnihl=mni*(mni+1)/2)
46  CHARACTER*10 CPNAM
47  COMMON
48  1/mn7nam/ cpnam(mne)
49  2/mn7ext/ u(mne) ,alim(mne) ,blim(mne)
50  3/mn7err/ erp(mni) ,ern(mni) ,werr(mni) ,globcc(mni)
51  4/mn7inx/ nvarl(mne) ,niofex(mne),nexofi(mni)
52  5/mn7int/ x(mni) ,xt(mni) ,dirin(mni)
53  6/mn7fx2/ xs(mni) ,xts(mni) ,dirins(mni)
54  7/mn7der/ grd(mni) ,g2(mni) ,gstep(mni) ,gin(mne) ,dgrd(mni)
55  8/mn7fx3/ grds(mni) ,g2s(mni) ,gsteps(mni)
56  9/mn7fx1/ ipfix(mni) ,npfix
57  a/mn7var/ vhmat(mnihl)
58  b/mn7vat/ vthmat(mnihl)
59  c/mn7sim/ p(mni,mni+1),pstar(mni),pstst(mni) ,pbar(mni),prho(mni)
60 C
61  parameter(maxdbg=10, maxstk=10, maxcwd=20, maxp=30, maxcpt=101)
62  parameter(zero=0.0, one=1.0, half=0.5)
63  COMMON
64  d/mn7npr/ maxint ,npar ,maxext ,nu
65  e/mn7iou/ isysrd ,isyswr ,isyssa ,npagwd ,npagln ,newpag
66  e/mn7io2/ istkrd(maxstk) ,nstkrd ,istkwr(maxstk) ,nstkwr
67  f/mn7tit/ cfrom ,cstatu ,ctitl ,cword ,cundef ,cvrsn ,covmes
68  g/mn7flg/ isw(7) ,idbg(0:maxdbg) ,nblock ,icomnd
69  h/mn7min/ amin ,up ,edm ,fval3 ,epsi ,apsi ,dcovar
70  i/mn7cnv/ nfcn ,nfcnmx ,nfcnlc ,nfcnfr ,itaur,istrat,nwrmes(2)
71  j/mn7arg/ word7(maxp)
72  k/mn7log/ lwarn ,lrepor ,limset ,lnolim ,lnewmn ,lphead
73  l/mn7cns/ epsmac ,epsma2 ,vlimlo ,vlimhi ,undefi ,bigedm,updflt
74  m/mn7rpt/ xpt(maxcpt) ,ypt(maxcpt)
75  n/mn7cpt/ chpt(maxcpt)
76  o/mn7xcr/ xmidcr ,ymidcr ,xdircr ,ydircr ,ke1cr ,ke2cr
77  CHARACTER CTITL*50, CWORD*(maxcwd), CUNDEF*10, CFROM*8,
78  + cvrsn*6, covmes(0:3)*22, cstatu*10, chpt*1
79  LOGICAL LWARN, LREPOR, LIMSET, LNOLIM, LNEWMN, LPHEAD
80 C
81  iex = number
82  IF (number .LT. 0) THEN
83  iin = -number
84  IF (iin .GT. npar) GO TO 900
85  iex = nexofi(iin)
86  ENDIF
87  IF (iex .GT. nu .OR. iex .LE. 0) GO TO 900
88  iin = niofex(iex)
89  IF (iin .LE. 0) GO TO 900
90 C IEX is external number, IIN is internal number
91  eplus = erp(iin)
92  IF (eplus.EQ.undefi) eplus=0.
93  eminus= ern(iin)
94  IF (eminus.EQ.undefi) eminus=0.
95  CALL mndxdi(x(iin),iin,dxdi)
96  ndiag = iin*(iin+1)/2
97  eparab = abs(dxdi*sqrt(abs(up*vhmat(ndiag))))
98 C global correlation coefficient
99  gcc = 0.
100  IF (isw(2) .LT. 2) GO TO 990
101  gcc = globcc(iin)
102  GO TO 990
103 C ERROR. parameter number not valid
104  900 eplus = 0.
105  eminus = 0.
106  eparab = 0.
107  gcc = 0.
108  990 RETURN
109  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
! 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 mnerrs(NUMBER, EPLUS, EMINUS, EPARAB, GCC)
Definition: mnerrs.f:10
struct ob o[NpMax]
Definition: Zprivate.h:34
subroutine mndxdi(PINT, IPAR, DXDI)
Definition: mndxdi.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
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