COSMOS v7.655  COSMOSv7655
(AirShowerMC)
mnvert.f
Go to the documentation of this file.
1 *
2 * $Id: mnvert.F,v 1.2 1996/03/15 18:02:54 james Exp $
3 *
4 * $Log: mnvert.F,v $
5 * Revision 1.2 1996/03/15 18:02:54 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:32 mclareni
21 * Minuit
22 *
23 *
24  SUBROUTINE mnvert(A,L,M,N,IFAIL)
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 inverts a symmetric matrix. matrix is first scaled to
40 CC have all ones on the diagonal (equivalent to change of units)
41 CC but no pivoting is done since matrix is positive-definite.
42 CC
43 *
44 * $Id: d506cm.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
45 *
46 * $Log: d506cm.inc,v $
47 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
48 * Minuit
49 *
50 *
51 *
52 *
53 * d506cm.inc
54 *
55  parameter(mne=100 , mni=50)
56  parameter(mnihl=mni*(mni+1)/2)
57  CHARACTER*10 CPNAM
58  COMMON
59  1/mn7nam/ cpnam(mne)
60  2/mn7ext/ u(mne) ,alim(mne) ,blim(mne)
61  3/mn7err/ erp(mni) ,ern(mni) ,werr(mni) ,globcc(mni)
62  4/mn7inx/ nvarl(mne) ,niofex(mne),nexofi(mni)
63  5/mn7int/ x(mni) ,xt(mni) ,dirin(mni)
64  6/mn7fx2/ xs(mni) ,xts(mni) ,dirins(mni)
65  7/mn7der/ grd(mni) ,g2(mni) ,gstep(mni) ,gin(mne) ,dgrd(mni)
66  8/mn7fx3/ grds(mni) ,g2s(mni) ,gsteps(mni)
67  9/mn7fx1/ ipfix(mni) ,npfix
68  a/mn7var/ vhmat(mnihl)
69  b/mn7vat/ vthmat(mnihl)
70  c/mn7sim/ p(mni,mni+1),pstar(mni),pstst(mni) ,pbar(mni),prho(mni)
71 C
72  parameter(maxdbg=10, maxstk=10, maxcwd=20, maxp=30, maxcpt=101)
73  parameter(zero=0.0, one=1.0, half=0.5)
74  COMMON
75  d/mn7npr/ maxint ,npar ,maxext ,nu
76  e/mn7iou/ isysrd ,isyswr ,isyssa ,npagwd ,npagln ,newpag
77  e/mn7io2/ istkrd(maxstk) ,nstkrd ,istkwr(maxstk) ,nstkwr
78  f/mn7tit/ cfrom ,cstatu ,ctitl ,cword ,cundef ,cvrsn ,covmes
79  g/mn7flg/ isw(7) ,idbg(0:maxdbg) ,nblock ,icomnd
80  h/mn7min/ amin ,up ,edm ,fval3 ,epsi ,apsi ,dcovar
81  i/mn7cnv/ nfcn ,nfcnmx ,nfcnlc ,nfcnfr ,itaur,istrat,nwrmes(2)
82  j/mn7arg/ word7(maxp)
83  k/mn7log/ lwarn ,lrepor ,limset ,lnolim ,lnewmn ,lphead
84  l/mn7cns/ epsmac ,epsma2 ,vlimlo ,vlimhi ,undefi ,bigedm,updflt
85  m/mn7rpt/ xpt(maxcpt) ,ypt(maxcpt)
86  n/mn7cpt/ chpt(maxcpt)
87  o/mn7xcr/ xmidcr ,ymidcr ,xdircr ,ydircr ,ke1cr ,ke2cr
88  CHARACTER CTITL*50, CWORD*(maxcwd), CUNDEF*10, CFROM*8,
89  + cvrsn*6, covmes(0:3)*22, cstatu*10, chpt*1
90  LOGICAL LWARN, LREPOR, LIMSET, LNOLIM, LNEWMN, LPHEAD
91  dimension a(l,m) ,pp(mni), q(mni), s(mni)
92  ifail=0
93  IF (n .LT. 1) GO TO 100
94  IF (n .GT. maxint) GO TO 100
95 C scale matrix by sqrt of diag elements
96  DO 8 i=1,n
97  si = a(i,i)
98  IF (si) 100,100,8
99  8 s(i) = 1.0/sqrt(si)
100  DO 20 i= 1, n
101  DO 20 j= 1, n
102  20 a(i,j) = a(i,j) *s(i)*s(j)
103 C . . . start main loop . . . .
104  DO 65 i=1,n
105  k = i
106 C preparation for elimination step1
107  IF (a(k,k) .EQ. zero) GO TO 100
108  q(k)=1./a(k,k)
109  pp(k) = 1.0
110  a(k,k)=0.0
111  kp1=k+1
112  km1=k-1
113  IF(km1)100,50,40
114  40 DO 49 j=1,km1
115  pp(j)=a(j,k)
116  q(j)=a(j,k)*q(k)
117  49 a(j,k)=0.
118  50 IF(k-n)51,60,100
119  51 DO 59 j=kp1,n
120  pp(j)=a(k,j)
121  q(j)=-a(k,j)*q(k)
122  59 a(k,j)=0.0
123 C elimination proper
124  60 DO 65 j=1,n
125  DO 65 k=j,n
126  65 a(j,k)=a(j,k)+pp(j)*q(k)
127 C elements of left diagonal and unscaling
128  DO 70 j= 1, n
129  DO 70 k= 1, j
130  a(k,j) = a(k,j) *s(k)*s(j)
131  70 a(j,k) = a(k,j)
132  RETURN
133 C failure return
134  100 ifail=1
135  RETURN
136  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 mnvert(A, L, M, N, IFAIL)
Definition: mnvert.f:25
! 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
struct ob o[NpMax]
Definition: Zprivate.h:34
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