Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyevnt.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyevnt.f
1 
2 C*********************************************************************
3 
4 C...PYEVNT
5 C...Administers the generation of a high-pT event via calls to
6 C...a number of subroutines.
7 
8  SUBROUTINE pyevnt
9 
10 C...Double precision and integer declarations.
11  IMPLICIT DOUBLE PRECISION(a-h, o-z)
12  IMPLICIT INTEGER(i-n)
13  INTEGER pyk,pychge,pycomp
14 C...Commonblocks.
15  common/pyjets/n,npad,k(4000,5),p(4000,5),v(4000,5)
16  common/pyctag/nct,mct(4000,2)
17  common/pydat1/mstu(200),paru(200),mstj(200),parj(200)
18  common/pydat2/kchg(500,4),pmas(500,4),parf(2000),vckm(4,4)
19  common/pydat3/mdcy(500,3),mdme(8000,2),brat(8000),kfdp(8000,5)
20  common/pypars/mstp(200),parp(200),msti(200),pari(200)
21  common/pyint1/mint(400),vint(400)
22  common/pyint2/iset(500),kfpr(500,2),coef(500,20),icol(40,4,2)
23  common/pyint4/mwid(500),wids(500,5)
24  common/pyint5/ngenpd,ngen(0:500,3),xsec(0:500,3)
25  SAVE /pyjets/,/pydat1/,/pyctag/,/pydat2/,/pydat3/,/pypars/,
26  &/pyint1/,/pyint2/,/pyint4/,/pyint5/
27 C...Local array.
28  dimension vtx(4)
29 
30 C...Optionally let PYEVNW do the whole job.
31  IF(mstp(81).GE.20) THEN
32  CALL pyevnw
33  RETURN
34  ENDIF
35 
36 C...Stop if no subprocesses on.
37  IF(mint(121).EQ.1.AND.msti(53).EQ.1) THEN
38  WRITE(mstu(11),5100)
39  CALL pystop(1)
40  ENDIF
41 
42 C...Initial values for some counters.
43  mstu(1)=0
44  mstu(2)=0
45  n=0
46  mint(5)=mint(5)+1
47  mint(7)=0
48  mint(8)=0
49  mint(30)=0
50  mint(83)=0
51  mint(84)=mstp(126)
52  mstu(24)=0
53  mstu70=0
54  mstj14=mstj(14)
55 C...Normally, use K(I,4:5) colour info rather than /PYCTAG/.
56  nct=0
57  mint(33)=0
58 
59 C...Let called routines know call is from PYEVNT (not PYEVNW).
60  mint(35)=1
61  IF (mstp(81).GE.10) mint(35)=2
62 
63 C...If variable energies: redo incoming kinematics and cross-section.
64  msti(61)=0
65  IF(mstp(171).EQ.1) THEN
66  CALL pyinki(1)
67  IF(msti(61).EQ.1) THEN
68  mint(5)=mint(5)-1
69  RETURN
70  ENDIF
71  IF(mint(121).GT.1) CALL pysave(3,1)
72  CALL pyxtot
73  ENDIF
74 
75 C...Loop over number of pileup events; check space left.
76  IF(mstp(131).LE.0) THEN
77  npile=1
78  ELSE
79  CALL pypile(2)
80  npile=mint(81)
81  ENDIF
82  DO 270 ipile=1,npile
83  IF(mint(84)+100.GE.mstu(4)) THEN
84  CALL pyerrm(11,
85  & '(PYEVNT:) no more space in PYJETS for pileup events')
86  IF(mstu(21).GE.1) goto 280
87  ENDIF
88  mint(82)=ipile
89 
90 C...Generate variables of hard scattering.
91  mint(51)=0
92  msti(52)=0
93  100 CONTINUE
94  IF(mint(51).NE.0.OR.mstu(24).NE.0) msti(52)=msti(52)+1
95  mint(31)=0
96  mint(39)=0
97  mint(51)=0
98  mint(57)=0
99  CALL pyrand
100  IF(msti(61).EQ.1) THEN
101  mint(5)=mint(5)-1
102  RETURN
103  ENDIF
104  IF(mint(51).EQ.2) RETURN
105  isub=mint(1)
106  IF(mstp(111).EQ.-1) goto 260
107 
108 C...Loopback point if PYPREP fails, especially for junction topologies.
109  nprep=0
110  mnt31s=mint(31)
111  110 nprep=nprep+1
112  mint(31)=mnt31s
113 
114  IF((isub.LE.90.OR.isub.GE.95).AND.isub.NE.99) THEN
115 C...Hard scattering (including low-pT):
116 C...reconstruct kinematics and colour flow of hard scattering.
117  mint31=mint(31)
118  120 mint(31)=mint31
119  mint(51)=0
120  CALL pyscat
121  IF(mint(51).EQ.1) goto 100
122  ipu1=mint(84)+1
123  ipu2=mint(84)+2
124  IF(isub.EQ.95) goto 140
125 
126 C...Reset statistics on activity in event.
127  DO 130 j=351,359
128  mint(j)=0
129  vint(j)=0d0
130  130 CONTINUE
131 
132 C...Showering of initial state partons (optional).
133  nfin=n
134  alamsv=parj(81)
135  parj(81)=parp(72)
136  IF(mstp(61).GE.1.AND.mint(47).GE.2.AND.mint(111).NE.12)
137  & CALL pysspa(ipu1,ipu2)
138  parj(81)=alamsv
139  IF(mint(51).EQ.1) goto 100
140 
141 C...Showering of final state partons (optional).
142  alamsv=parj(81)
143  parj(81)=parp(72)
144  IF(mstp(71).GE.1.AND.iset(isub).GE.2.AND.iset(isub).LE.10)
145  & THEN
146  ipu3=mint(84)+3
147  ipu4=mint(84)+4
148  IF(iset(isub).EQ.5) ipu4=-3
149  qmax=vint(55)
150  IF(iset(isub).EQ.2) qmax=sqrt(parp(71))*vint(55)
151  CALL pyshow(ipu3,ipu4,qmax)
152  ELSEIF(iset(isub).EQ.11) THEN
153  CALL pyadsh(nfin)
154  ENDIF
155  parj(81)=alamsv
156 
157 C...Allow possibility for user to abort event generation.
158  iveto=0
159  IF(ipile.EQ.1.AND.mstp(143).EQ.1) CALL pyveto(iveto)
160  IF(iveto.EQ.1) goto 100
161 
162 C...Decay of final state resonances.
163  mint(32)=0
164  IF(mstp(41).GE.1.AND.iset(isub).LE.10) CALL pyresd(0)
165  IF(mint(51).EQ.1) goto 100
166  mint(52)=n
167 
168 
169 C...Multiple interactions - PYTHIA 6.3 intermediate style.
170  140 IF(mstp(81).GE.10.AND.mint(50).EQ.1) THEN
171  IF(isub.EQ.95) mint(31)=mint(31)+1
172  CALL pymign(6)
173  IF(mint(51).EQ.1) goto 100
174  mint(53)=n
175 
176 C...Beam remnant flavour and colour assignments - new scheme.
177  CALL pymihk
178  IF(mint(51).EQ.1.AND.mint(57).GE.1.AND.mint(57).LE.5)
179  & goto 120
180  IF(mint(51).EQ.1) goto 100
181 
182 C...Primordial kT and beam remnant momentum sharing - new scheme.
183  CALL pymirm
184  IF(mint(51).EQ.1.AND.mint(57).GE.1.AND.mint(57).LE.5)
185  & goto 120
186  IF(mint(51).EQ.1) goto 100
187  IF(isub.EQ.95) mint(31)=mint(31)-1
188 
189 C...Multiple interactions - PYTHIA 6.2 style.
190  ELSEIF(mint(111).NE.12) THEN
191  IF (mstp(81).GE.1.AND.mint(50).EQ.1.AND.isub.NE.95) THEN
192  CALL pymult(6)
193  mint(53)=n
194  ENDIF
195 
196 C...Hadron remnants and primordial kT.
197  CALL pyremn(ipu1,ipu2)
198  IF(mint(51).EQ.1.AND.mint(57).GE.1.AND.mint(57).LE.5) goto
199  & 110
200  IF(mint(51).EQ.1) goto 100
201  ENDIF
202 
203  ELSEIF(isub.NE.99) THEN
204 C...Diffractive and elastic scattering.
205  CALL pydiff
206 
207  ELSE
208 C...DIS scattering (photon flux external).
209  CALL pydisg
210  IF(mint(51).EQ.1) goto 100
211  ENDIF
212 
213 C...Check that no odd resonance left undecayed.
214  mint(54)=n
215  IF(mstp(111).GE.1) THEN
216  nfix=n
217  DO 150 i=mint(84)+1,nfix
218  IF(k(i,1).GE.1.AND.k(i,1).LE.10.AND.k(i,2).NE.21.AND.
219  & k(i,2).NE.22) THEN
220  kca=pycomp(k(i,2))
221  IF(mwid(kca).NE.0.AND.mdcy(kca,1).GE.1) THEN
222  CALL pyresd(i)
223  IF(mint(51).EQ.1) goto 100
224  ENDIF
225  ENDIF
226  150 CONTINUE
227  ENDIF
228 
229 C...Boost hadronic subsystem to overall rest frame.
230 C..(Only relevant when photon inside lepton beam.)
231  IF(mint(141).NE.0.OR.mint(142).NE.0) CALL pygaga(4,wtgaga)
232 
233 C...Recalculate energies from momenta and masses (if desired).
234  IF(mstp(113).GE.1) THEN
235  DO 160 i=mint(83)+1,n
236  IF(k(i,1).GT.0.AND.k(i,1).LE.10) p(i,4)=sqrt(p(i,1)**2+
237  & p(i,2)**2+p(i,3)**2+p(i,5)**2)
238  160 CONTINUE
239  nrecal=n
240  ENDIF
241 
242 C...Colour reconnection before string formation
243  IF (mstp(95).GE.2) CALL pyfscr(mint(84)+1)
244 
245 C...Rearrange partons along strings, check invariant mass cuts.
246  mstu(28)=0
247  IF(mstp(111).LE.0) mstj(14)=-1
248  CALL pyprep(mint(84)+1)
249  mstj(14)=mstj14
250  IF(mint(51).EQ.1.AND.mstu(24).EQ.1) THEN
251  mstu(24)=0
252  goto 100
253  ENDIF
254  IF (mint(51).EQ.1.AND.nprep.LE.5) goto 110
255  IF (mint(51).EQ.1) goto 100
256  IF(mstp(112).EQ.1.AND.mstu(28).EQ.3) goto 100
257  IF(mstp(125).EQ.0.OR.mstp(125).EQ.1) THEN
258  DO 190 i=mint(84)+1,n
259  IF(k(i,2).EQ.94) THEN
260  DO 180 i1=i+1,min(n,i+10)
261  IF(k(i1,3).EQ.i) THEN
262  k(i1,3)=mod(k(i1,4)/mstu(5),mstu(5))
263  IF(k(i1,3).EQ.0) THEN
264  DO 170 ii=mint(84)+1,i-1
265  IF(k(ii,2).EQ.k(i1,2)) THEN
266  IF(mod(k(ii,4),mstu(5)).EQ.i1.OR.
267  & mod(k(ii,5),mstu(5)).EQ.i1) k(i1,3)=ii
268  ENDIF
269  170 CONTINUE
270  IF(k(i+1,3).EQ.0) k(i+1,3)=k(i,3)
271  ENDIF
272  ENDIF
273  180 CONTINUE
274  ENDIF
275  190 CONTINUE
276  CALL pyedit(12)
277  CALL pyedit(14)
278  IF(mstp(125).EQ.0) CALL pyedit(15)
279  IF(mstp(125).EQ.0) mint(4)=0
280  DO 210 i=mint(83)+1,n
281  IF(k(i,1).EQ.11.AND.k(i,4).EQ.0.AND.k(i,5).EQ.0) THEN
282  DO 200 i1=i+1,n
283  IF(k(i1,3).EQ.i.AND.k(i,4).EQ.0) k(i,4)=i1
284  IF(k(i1,3).EQ.i) k(i,5)=i1
285  200 CONTINUE
286  ENDIF
287  210 CONTINUE
288  ENDIF
289 
290 C...Introduce separators between sections in PYLIST event listing.
291  IF(ipile.EQ.1.AND.mstp(125).LE.0) THEN
292  mstu70=1
293  mstu(71)=n
294  ELSEIF(ipile.EQ.1) THEN
295  mstu70=3
296  mstu(71)=2
297  mstu(72)=mint(4)
298  mstu(73)=n
299  ENDIF
300 
301 C...Go back to lab frame (needed for vertices, also in fragmentation).
302  CALL pyfram(1)
303 
304 C...Set nonvanishing production vertex (optional).
305  IF(mstp(151).EQ.1) THEN
306  DO 220 j=1,4
307  vtx(j)=parp(150+j)*sqrt(-2d0*log(max(1d-10,pyr(0))))*
308  & sin(paru(2)*pyr(0))
309  220 CONTINUE
310  DO 240 i=mint(83)+1,n
311  DO 230 j=1,4
312  v(i,j)=v(i,j)+vtx(j)
313  230 CONTINUE
314  240 CONTINUE
315  ENDIF
316 
317 C...Perform hadronization (if desired).
318  IF(mstp(111).GE.1) THEN
319  CALL pyexec
320  IF(mstu(24).NE.0) goto 100
321  ENDIF
322  IF(mstp(113).GE.1) THEN
323  DO 250 i=nrecal,n
324  IF(p(i,5).GT.0d0) p(i,4)=sqrt(p(i,1)**2+
325  & p(i,2)**2+p(i,3)**2+p(i,5)**2)
326  250 CONTINUE
327  ENDIF
328  IF(mstp(125).EQ.0.OR.mstp(125).EQ.1) CALL pyedit(14)
329 
330 C...Store event information and calculate Monte Carlo estimates of
331 C...subprocess cross-sections.
332  260 IF(ipile.EQ.1) CALL pydocu
333 
334 C...Set counters for current pileup event and loop to next one.
335  msti(41)=ipile
336  IF(ipile.GE.2.AND.ipile.LE.10) msti(40+ipile)=isub
337  IF(mstu70.LT.10) THEN
338  mstu70=mstu70+1
339  mstu(70+mstu70)=n
340  ENDIF
341  mint(83)=n
342  mint(84)=n+mstp(126)
343  IF(ipile.LT.npile) CALL pyfram(2)
344  270 CONTINUE
345 
346 C...Generic information on pileup events. Reconstruct missing history.
347  IF(mstp(131).EQ.1.AND.mstp(133).GE.1) THEN
348  pari(91)=vint(132)
349  pari(92)=vint(133)
350  pari(93)=vint(134)
351  IF(mstp(133).GE.2) pari(93)=pari(93)*xsec(0,3)/vint(131)
352  ENDIF
353  CALL pyedit(16)
354 
355 C...Transform to the desired coordinate frame.
356  280 CALL pyfram(mstp(124))
357  mstu(70)=mstu70
358  paru(21)=vint(1)
359 
360 C...Error messages
361  5100 FORMAT(1x,'Error: no subprocess switched on.'/
362  &1x,'Execution stopped.')
363 
364  RETURN
365  END