COSMOS v7.655  COSMOSv7655
(AirShowerMC)
mnrazz.f
Go to the documentation of this file.
1 *
2 * $Id: mnrazz.F,v 1.1.1.1 1996/03/07 14:31:31 mclareni Exp $
3 *
4 * $Log: mnrazz.F,v $
5 * Revision 1.1.1.1 1996/03/07 14:31:31 mclareni
6 * Minuit
7 *
8 *
9  SUBROUTINE mnrazz(YNEW,PNEW,Y,JH,JL)
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 only by MNSIMP (and MNIMPR) to add a new point
25 CC and remove an old one from the current simplex, and get the
26 CC estimated distance to minimum.
27 CC
28 *
29 * $Id: d506cm.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
30 *
31 * $Log: d506cm.inc,v $
32 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
33 * Minuit
34 *
35 *
36 *
37 *
38 * d506cm.inc
39 *
40  parameter(mne=100 , mni=50)
41  parameter(mnihl=mni*(mni+1)/2)
42  CHARACTER*10 CPNAM
43  COMMON
44  1/mn7nam/ cpnam(mne)
45  2/mn7ext/ u(mne) ,alim(mne) ,blim(mne)
46  3/mn7err/ erp(mni) ,ern(mni) ,werr(mni) ,globcc(mni)
47  4/mn7inx/ nvarl(mne) ,niofex(mne),nexofi(mni)
48  5/mn7int/ x(mni) ,xt(mni) ,dirin(mni)
49  6/mn7fx2/ xs(mni) ,xts(mni) ,dirins(mni)
50  7/mn7der/ grd(mni) ,g2(mni) ,gstep(mni) ,gin(mne) ,dgrd(mni)
51  8/mn7fx3/ grds(mni) ,g2s(mni) ,gsteps(mni)
52  9/mn7fx1/ ipfix(mni) ,npfix
53  a/mn7var/ vhmat(mnihl)
54  b/mn7vat/ vthmat(mnihl)
55  c/mn7sim/ p(mni,mni+1),pstar(mni),pstst(mni) ,pbar(mni),prho(mni)
56 C
57  parameter(maxdbg=10, maxstk=10, maxcwd=20, maxp=30, maxcpt=101)
58  parameter(zero=0.0, one=1.0, half=0.5)
59  COMMON
60  d/mn7npr/ maxint ,npar ,maxext ,nu
61  e/mn7iou/ isysrd ,isyswr ,isyssa ,npagwd ,npagln ,newpag
62  e/mn7io2/ istkrd(maxstk) ,nstkrd ,istkwr(maxstk) ,nstkwr
63  f/mn7tit/ cfrom ,cstatu ,ctitl ,cword ,cundef ,cvrsn ,covmes
64  g/mn7flg/ isw(7) ,idbg(0:maxdbg) ,nblock ,icomnd
65  h/mn7min/ amin ,up ,edm ,fval3 ,epsi ,apsi ,dcovar
66  i/mn7cnv/ nfcn ,nfcnmx ,nfcnlc ,nfcnfr ,itaur,istrat,nwrmes(2)
67  j/mn7arg/ word7(maxp)
68  k/mn7log/ lwarn ,lrepor ,limset ,lnolim ,lnewmn ,lphead
69  l/mn7cns/ epsmac ,epsma2 ,vlimlo ,vlimhi ,undefi ,bigedm,updflt
70  m/mn7rpt/ xpt(maxcpt) ,ypt(maxcpt)
71  n/mn7cpt/ chpt(maxcpt)
72  o/mn7xcr/ xmidcr ,ymidcr ,xdircr ,ydircr ,ke1cr ,ke2cr
73  CHARACTER CTITL*50, CWORD*(maxcwd), CUNDEF*10, CFROM*8,
74  + cvrsn*6, covmes(0:3)*22, cstatu*10, chpt*1
75  LOGICAL LWARN, LREPOR, LIMSET, LNOLIM, LNEWMN, LPHEAD
76  dimension pnew(*), y(*)
77  DO 10 i=1,npar
78  10 p(i,jh) = pnew(i)
79  y(jh)=ynew
80  IF(ynew .LT. amin) THEN
81  DO 15 i=1,npar
82  15 x(i) = pnew(i)
83  CALL mninex(x)
84  amin = ynew
85  cstatu = 'PROGRESS '
86  jl=jh
87  ENDIF
88  jh = 1
89  nparp1 = npar+1
90  20 DO 25 j=2,nparp1
91  IF (y(j) .GT. y(jh)) jh = j
92  25 CONTINUE
93  edm = y(jh) - y(jl)
94  IF (edm .LE. zero) GO TO 45
95  DO 35 i= 1, npar
96  pbig = p(i,1)
97  plit = pbig
98  DO 30 j= 2, nparp1
99  IF (p(i,j) .GT. pbig) pbig = p(i,j)
100  IF (p(i,j) .LT. plit) plit = p(i,j)
101  30 CONTINUE
102  dirin(i) = pbig - plit
103  35 CONTINUE
104  40 RETURN
105  45 WRITE (isyswr, 1000) npar
106  GO TO 40
107  1000 FORMAT (' FUNCTION VALUE DOES NOT SEEM TO DEPEND ON ANY OF THE',
108  + i3,' VARIABLE PARAMETERS.' /10x,'VERIFY THAT STEP SIZES ARE',
109  + ' BIG ENOUGH AND CHECK FCN LOGIC.'/1x,79(1h*)/1x,79(1h*)/)
110  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
struct ob o[NpMax]
Definition: Zprivate.h:34
subroutine mninex(PINT)
Definition: mninex.f:10
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
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
subroutine mnrazz(YNEW, PNEW, Y, JH, JL)
Definition: mnrazz.f:10
!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