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

Go to the source code of this file.

Functions/Subroutines

subroutine mnwarn (COPT, CORG, CMES)
 

Function/Subroutine Documentation

◆ mnwarn()

subroutine mnwarn ( character  COPT,
character, dimension(*)  CORG,
character, dimension(*)  CMES 
)

Definition at line 10 of file mnwarn.f.

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

Referenced by mncont(), mncros(), mncuve(), mnderi(), mnhes1(), mnhess(), mnline(), mnmigr(), mnmnot(), mnparm(), mnpint(), mnpsdf(), and mnset().

10 C If COPT='W', CMES is a WARning message from CORG.
11 C If COPT='D', CMES is a DEBug message from CORG.
12 C If SET WARnings is in effect (the default), this routine
13 C prints the warning message CMES coming from CORG.
14 C If SET NOWarnings is in effect, the warning message is
15 C stored in a circular buffer of length MAXMES.
16 C If called with CORG=CMES='SHO', it prints the messages in
17 C the circular buffer, FIFO, and empties the buffer.
18 *
19 * $Id: d506dp.inc,v 1.1.1.1 1996/03/07 14:31:32 mclareni Exp $
20 *
21 * $Log: d506dp.inc,v $
22 * Revision 1.1.1.1 1996/03/07 14:31:32 mclareni
23 * Minuit
24 *
25 *
26 *
27 *
28 * d506dp.inc
29 *
30 C ************ DOUBLE PRECISION VERSION *************
31  IMPLICIT DOUBLE PRECISION (a-h,o-z)
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  CHARACTER copt*1, corg*(*), cmes*(*), ctyp*7
81  parameter(maxmes=10)
82  CHARACTER origin(maxmes,2)*10, warmes(maxmes,2)*60
83  common/mn7wrc/origin, warmes
84  common/mn7wri/nfcwar(maxmes,2),icirc(2)
85  CHARACTER englsh*20
86 C
87  IF (corg(1:3).EQ.'SHO' .AND. cmes(1:3).EQ.'SHO') GO TO 200
88 C Either print warning or put in buffer
89  IF (copt .EQ. 'W') THEN
90  ityp = 1
91  IF (lwarn) THEN
92  WRITE (isyswr,'(A,A/A,A)') ' MINUIT WARNING IN ',corg,
93  + ' ============== ',cmes
94  RETURN
95  ENDIF
96  ELSE
97  ityp = 2
98  IF (lrepor) THEN
99  WRITE (isyswr,'(A,A/A,A)') ' MINUIT DEBUG FOR ',corg,
100  + ' ============== ',cmes
101  RETURN
102  ENDIF
103  ENDIF
104 C if appropriate flag is off, fill circular buffer
105  IF (nwrmes(ityp) .EQ. 0) icirc(ityp) = 0
106  nwrmes(ityp) = nwrmes(ityp) + 1
107  icirc(ityp) = icirc(ityp) + 1
108  IF (icirc(ityp) .GT. maxmes) icirc(ityp) = 1
109  ic = icirc(ityp)
110  origin(ic,ityp) = corg
111  warmes(ic,ityp) = cmes
112  nfcwar(ic,ityp) = nfcn
113  RETURN
114 C
115 C 'SHO WARnings', ask if any suppressed mess in buffer
116  200 CONTINUE
117  IF (copt .EQ. 'W') THEN
118  ityp = 1
119  ctyp = 'WARNING'
120  ELSE
121  ityp = 2
122  ctyp = '*DEBUG*'
123  ENDIF
124  IF (nwrmes(ityp) .GT. 0) THEN
125  englsh = ' WAS SUPPRESSED. '
126  IF (nwrmes(ityp) .GT. 1) englsh = 'S WERE SUPPRESSED.'
127  WRITE (isyswr,'(/1X,I5,A,A,A,A/)') nwrmes(ityp),
128  + ' MINUIT ',ctyp,' MESSAGE', englsh
129  nm = nwrmes(ityp)
130  ic = 0
131  IF (nm .GT. maxmes) THEN
132  WRITE (isyswr,'(A,I2,A)') ' ONLY THE MOST RECENT ',
133  + maxmes,' WILL BE LISTED BELOW.'
134  nm = maxmes
135  ic = icirc(ityp)
136  ENDIF
137  WRITE (isyswr,'(A)') ' CALLS ORIGIN MESSAGE'
138  DO 300 i= 1, nm
139  ic = ic + 1
140  IF (ic .GT. maxmes) ic = 1
141  WRITE (isyswr,'(1X,I6,1X,A,1X,A)')
142  + nfcwar(ic,ityp),origin(ic,ityp),warmes(ic,ityp)
143  300 CONTINUE
144  nwrmes(ityp) = 0
145  WRITE (isyswr,'(1H )')
146  ENDIF
147  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
nodes i
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
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
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: