ECCE @ EIC Software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyhistat.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyhistat.f
1 
2 C***********************************************************************
3 
4  SUBROUTINE pyhistat(MSTAT)
5 
6 C...Prints out information about cross-sections, decay widths, branching
7 C...ratios, kinematical limits, status codes and parameter values.
8  common/ludat1/mstu(200),paru(200),mstj(200),parj(200)
9  SAVE /ludat1/
10  common/ludat2/kchg(500,3),pmas(500,4),parf(2000),vckm(4,4)
11  SAVE /ludat2/
12  common/ludat3/mdcy(500,3),mdme(2000,2),brat(2000),kfdp(2000,5)
13  SAVE /ludat3/
14  common/pyhisubs/msel,msub(200),kfin(2,-40:40),ckin(200)
15  SAVE /pyhisubs/
16  common/pyhipars/mstp(200),parp(200),msti(200),pari(200)
17  SAVE /pyhipars/
18  common/pyhiint1/mint(400),vint(400)
19  SAVE /pyhiint1/
20  common/pyhiint4/widp(21:40,0:40),wide(21:40,0:40),wids(21:40,3)
21  SAVE /pyhiint4/
22  common/pyhiint5/ngen(0:200,3),xsec(0:200,3)
23  SAVE /pyhiint5/
24  common/pyhiint6/proc(0:200)
25  CHARACTER proc*28
26  SAVE /pyhiint6/
27  CHARACTER chau*16,chpa(-40:40)*12,chin(2)*12,
28  &state(-1:5)*4,chkin(21)*18
29  DATA state/'----','off ','on ','on/+','on/-','on/1','on/2'/,
30  &chkin/' m_hard (GeV/c^2) ',' p_T_hard (GeV/c) ',
31  &'m_finite (GeV/c^2)',' y*_subsystem ',' y*_large ',
32  &' y*_small ',' eta*_large ',' eta*_small ',
33  &'cos(theta*)_large ','cos(theta*)_small ',' x_1 ',
34  &' x_2 ',' x_F ',' cos(theta_hard) ',
35  &'m''_hard (GeV/c^2) ',' tau ',' y* ',
36  &'cos(theta_hard^-) ','cos(theta_hard^+) ',' x_T^2 ',
37  &' tau'' '/
38 
39 C...Cross-sections.
40  IF(mstat.LE.1) THEN
41  WRITE(mstu(11),1000)
42  WRITE(mstu(11),1100)
43  WRITE(mstu(11),1200) 0,proc(0),ngen(0,3),ngen(0,1),xsec(0,3)
44  DO 100 i=1,200
45  IF(msub(i).NE.1) goto 100
46  WRITE(mstu(11),1200) i,proc(i),ngen(i,3),ngen(i,1),xsec(i,3)
47  100 CONTINUE
48  WRITE(mstu(11),1300) 1.-float(ngen(0,3))/
49  & max(1.,float(ngen(0,2)))
50 
51 C...Decay widths and branching ratios.
52  ELSEIF(mstat.EQ.2) THEN
53  DO 110 kf=-40,40
54  CALL luname(kf,chau)
55  110 chpa(kf)=chau(1:12)
56  WRITE(mstu(11),1400)
57  WRITE(mstu(11),1500)
58 C...Off-shell branchings.
59  DO 130 i=1,17
60  kc=i
61  IF(i.GE.9) kc=i+2
62  IF(i.EQ.17) kc=21
63  WRITE(mstu(11),1600) chpa(kc),0.,0.,state(mdcy(kc,1)),0.
64  DO 120 j=1,mdcy(kc,3)
65  idc=j+mdcy(kc,2)-1
66  120 IF(mdme(idc,2).EQ.102) WRITE(mstu(11),1700) chpa(kfdp(idc,1)),
67  & chpa(kfdp(idc,2)),0.,0.,state(mdme(idc,1)),0.
68  130 CONTINUE
69 C...On-shell decays.
70  DO 150 i=1,6
71  kc=i+22
72  IF(i.EQ.4) kc=32
73  IF(i.EQ.5) kc=37
74  IF(i.EQ.6) kc=40
75  IF(wide(kc,0).GT.0.) THEN
76  WRITE(mstu(11),1600) chpa(kc),widp(kc,0),1.,
77  & state(mdcy(kc,1)),1.
78  DO 140 j=1,mdcy(kc,3)
79  idc=j+mdcy(kc,2)-1
80  140 WRITE(mstu(11),1700) chpa(kfdp(idc,1)),chpa(kfdp(idc,2)),
81  & widp(kc,j),widp(kc,j)/widp(kc,0),state(mdme(idc,1)),
82  & wide(kc,j)/wide(kc,0)
83  ELSE
84  WRITE(mstu(11),1600) chpa(kc),widp(kc,0),1.,
85  & state(mdcy(kc,1)),0.
86  ENDIF
87  150 CONTINUE
88  WRITE(mstu(11),1800)
89 
90 C...Allowed incoming partons/particles at hard interaction.
91  ELSEIF(mstat.EQ.3) THEN
92  WRITE(mstu(11),1900)
93  CALL luname(mint(11),chau)
94  chin(1)=chau(1:12)
95  CALL luname(mint(12),chau)
96  chin(2)=chau(1:12)
97  WRITE(mstu(11),2000) chin(1),chin(2)
98  DO 160 kf=-40,40
99  CALL luname(kf,chau)
100  160 chpa(kf)=chau(1:12)
101  IF(mint(43).EQ.1) THEN
102  WRITE(mstu(11),2100) chpa(mint(11)),state(kfin(1,mint(11))),
103  & chpa(mint(12)),state(kfin(2,mint(12)))
104  ELSEIF(mint(43).EQ.2) THEN
105  WRITE(mstu(11),2100) chpa(mint(11)),state(kfin(1,mint(11))),
106  & chpa(-mstp(54)),state(kfin(2,-mstp(54)))
107  DO 170 i=-mstp(54)+1,-1
108  170 WRITE(mstu(11),2200) chpa(i),state(kfin(2,i))
109  DO 180 i=1,mstp(54)
110  180 WRITE(mstu(11),2200) chpa(i),state(kfin(2,i))
111  WRITE(mstu(11),2200) chpa(21),state(kfin(2,21))
112  ELSEIF(mint(43).EQ.3) THEN
113  WRITE(mstu(11),2100) chpa(-mstp(54)),state(kfin(1,-mstp(54))),
114  & chpa(mint(12)),state(kfin(2,mint(12)))
115  DO 190 i=-mstp(54)+1,-1
116  190 WRITE(mstu(11),2300) chpa(i),state(kfin(1,i))
117  DO 200 i=1,mstp(54)
118  200 WRITE(mstu(11),2300) chpa(i),state(kfin(1,i))
119  WRITE(mstu(11),2300) chpa(21),state(kfin(1,21))
120  ELSEIF(mint(43).EQ.4) THEN
121  DO 210 i=-mstp(54),-1
122  210 WRITE(mstu(11),2100) chpa(i),state(kfin(1,i)),chpa(i),
123  & state(kfin(2,i))
124  DO 220 i=1,mstp(54)
125  220 WRITE(mstu(11),2100) chpa(i),state(kfin(1,i)),chpa(i),
126  & state(kfin(2,i))
127  WRITE(mstu(11),2100) chpa(21),state(kfin(1,21)),chpa(21),
128  & state(kfin(2,21))
129  ENDIF
130  WRITE(mstu(11),2400)
131 
132 C...User-defined and derived limits on kinematical variables.
133  ELSEIF(mstat.EQ.4) THEN
134  WRITE(mstu(11),2500)
135  WRITE(mstu(11),2600)
136  shrmax=ckin(2)
137  IF(shrmax.LT.0.) shrmax=vint(1)
138  WRITE(mstu(11),2700) ckin(1),chkin(1),shrmax
139  pthmin=max(ckin(3),ckin(5))
140  pthmax=ckin(4)
141  IF(pthmax.LT.0.) pthmax=0.5*shrmax
142  WRITE(mstu(11),2800) ckin(3),pthmin,chkin(2),pthmax
143  WRITE(mstu(11),2900) chkin(3),ckin(6)
144  DO 230 i=4,14
145  230 WRITE(mstu(11),2700) ckin(2*i-1),chkin(i),ckin(2*i)
146  sprmax=ckin(32)
147  IF(sprmax.LT.0.) sprmax=vint(1)
148  WRITE(mstu(11),2700) ckin(31),chkin(13),sprmax
149  WRITE(mstu(11),3000)
150  WRITE(mstu(11),3100)
151  WRITE(mstu(11),2600)
152  DO 240 i=16,21
153  240 WRITE(mstu(11),2700) vint(i-5),chkin(i),vint(i+15)
154  WRITE(mstu(11),3000)
155 
156 C...Status codes and parameter values.
157  ELSEIF(mstat.EQ.5) THEN
158  WRITE(mstu(11),3200)
159  WRITE(mstu(11),3300)
160  DO 250 i=1,100
161  250 WRITE(mstu(11),3400) i,mstp(i),parp(i),100+i,mstp(100+i),
162  & parp(100+i)
163  ENDIF
164 
165 C...Formats for printouts.
166  1000 FORMAT('1',9('*'),1x,'PYHISTAT: Statistics on Number of ',
167  &'Events and Cross-sections',1x,9('*'))
168  1100 FORMAT(/1x,78('=')/1x,'I',34x,'I',28x,'I',12x,'I'/1x,'I',12x,
169  &'Subprocess',12x,'I',6x,'Number of points',6x,'I',4x,'Sigma',3x,
170  &'I'/1x,'I',34x,'I',28x,'I',12x,'I'/1x,'I',34('-'),'I',28('-'),
171  &'I',4x,'(mb)',4x,'I'/1x,'I',34x,'I',28x,'I',12x,'I'/1x,'I',1x,
172  &'N:o',1x,'Type',25x,'I',4x,'Generated',9x,'Tried',1x,'I',12x,
173  &'I'/1x,'I',34x,'I',28x,'I',12x,'I'/1x,78('=')/1x,'I',34x,'I',28x,
174  &'I',12x,'I')
175  1200 FORMAT(1x,'I',1x,i3,1x,a28,1x,'I',1x,i12,1x,i13,1x,'I',1x,1p,
176  &e10.3,1x,'I')
177  1300 FORMAT(1x,'I',34x,'I',28x,'I',12x,'I'/1x,78('=')//
178  &1x,'********* Fraction of events that fail fragmentation ',
179  &'cuts =',1x,f8.5,' *********'/)
180  1400 FORMAT('1',17('*'),1x,'PYHISTAT: Decay Widths and Branching ',
181  &'Ratios',1x,17('*'))
182  1500 FORMAT(/1x,78('=')/1x,'I',29x,'I',13x,'I',12x,'I',6x,'I',12x,'I'/
183  &1x,'I',1x,'Branching/Decay Channel',5x,'I',1x,'Width (GeV)',1x,
184  &'I',7x,'B.R.',1x,'I',1x,'Stat',1x,'I',2x,'Eff. B.R.',1x,'I'/1x,
185  &'I',29x,'I',13x,'I',12x,'I',6x,'I',12x,'I'/1x,78('='))
186  1600 FORMAT(1x,'I',29x,'I',13x,'I',12x,'I',6x,'I',12x,'I'/1x,'I',1x,
187  &a12,1x,'->',13x,'I',2x,1p,e10.3,0p,1x,'I',1x,1p,e10.3,0p,1x,'I',
188  &1x,a4,1x,'I',1x,1p,e10.3,0p,1x,'I')
189  1700 FORMAT(1x,'I',1x,a12,1x,'+',1x,a12,1x,'I',2x,1p,e10.3,0p,1x,'I',
190  &1x,1p,e10.3,0p,1x,'I',1x,a4,1x,'I',1x,1p,e10.3,0p,1x,'I')
191  1800 FORMAT(1x,'I',29x,'I',13x,'I',12x,'I',6x,'I',12x,'I'/1x,78('='))
192  1900 FORMAT('1',7('*'),1x,'PYHISTAT: Allowed Incoming Partons/',
193  &'Particles at Hard Interaction',1x,7('*'))
194  2000 FORMAT(/1x,78('=')/1x,'I',38x,'I',37x,'I'/1x,'I',1x,
195  &'Beam particle:',1x,a,10x,'I',1x,'Target particle:',1x,a,7x,
196  &'I'/1x,'I',38x,'I',37x,'I'/1x,'I',1x,'Content',9x,'State',16x,
197  &'I',1x,'Content',9x,'State',15x,'I'/1x,'I',38x,'I',37x,'I'/1x,
198  &78('=')/1x,'I',38x,'I',37x,'I')
199  2100 FORMAT(1x,'I',1x,a,5x,a,16x,'I',1x,a,5x,a,15x,'I')
200  2200 FORMAT(1x,'I',38x,'I',1x,a,5x,a,15x,'I')
201  2300 FORMAT(1x,'I',1x,a,5x,a,16x,'I',37x,'I')
202  2400 FORMAT(1x,'I',38x,'I',37x,'I'/1x,78('='))
203  2500 FORMAT('1',12('*'),1x,'PYHISTAT: User-Defined Limits on ',
204  &'Kinematical Variables',1x,12('*'))
205  2600 FORMAT(/1x,78('=')/1x,'I',76x,'I')
206  2700 FORMAT(1x,'I',16x,1p,e10.3,0p,1x,'<',1x,a,1x,'<',1x,1p,e10.3,0p,
207  &16x,'I')
208  2800 FORMAT(1x,'I',3x,1p,e10.3,0p,1x,'(',1p,e10.3,0p,')',1x,'<',1x,a,
209  &1x,'<',1x,1p,e10.3,0p,16x,'I')
210  2900 FORMAT(1x,'I',29x,a,1x,'=',1x,1p,e10.3,0p,16x,'I')
211  3000 FORMAT(1x,'I',76x,'I'/1x,78('='))
212  3100 FORMAT(////1x,5('*'),1x,
213  &'PYHISTAT: Derived Limits on Kinematical ',
214  &'Variables Used in Generation',1x,5('*'))
215  3200 FORMAT('1',12('*'),1x,'PYHISTAT: Summary of Status Codes and ',
216  &'Parameter Values',1x,12('*'))
217  3300 FORMAT(/3x,'I',4x,'MSTP(I)',9x,'PARP(I)',20x,'I',4x,'MSTP(I)',9x,
218  &'PARP(I)'/)
219  3400 FORMAT(1x,i3,5x,i6,6x,1p,e10.3,0p,18x,i3,5x,i6,6x,1p,e10.3)
220 
221  RETURN
222  END