Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyevnw.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyevnw.f
1 
2 C*********************************************************************
3 
4 C...PYEVNW
5 C...Administers the generation of a high-pT event via calls to
6 C...a number of subroutines for the new multiple interactions and
7 C...showering framework.
8 
9  SUBROUTINE pyevnw
10 
11 C...Double precision and integer declarations.
12  IMPLICIT DOUBLE PRECISION(a-h, o-z)
13  IMPLICIT INTEGER(i-n)
14  INTEGER pyk,pychge,pycomp
15 C...Commonblocks.
16  common/pyjets/n,npad,k(4000,5),p(4000,5),v(4000,5)
17  common/pyctag/nct,mct(4000,2)
18  common/pydat1/mstu(200),paru(200),mstj(200),parj(200)
19  common/pydat2/kchg(500,4),pmas(500,4),parf(2000),vckm(4,4)
20  common/pydat3/mdcy(500,3),mdme(8000,2),brat(8000),kfdp(8000,5)
21  common/pypars/mstp(200),parp(200),msti(200),pari(200)
22  common/pyint1/mint(400),vint(400)
23  common/pyint2/iset(500),kfpr(500,2),coef(500,20),icol(40,4,2)
24  common/pyint4/mwid(500),wids(500,5)
25  common/pyint5/ngenpd,ngen(0:500,3),xsec(0:500,3)
26  common/pyintm/kfival(2,3),nmi(2),imi(2,800,2),nvc(2,-6:6),
27  & xassoc(2,-6:6,240),xpsvc(-6:6,-1:240),pvctot(2,-1:1),
28  & xmi(2,240),pt2mi(240),imisep(0:240)
29  SAVE /pyjets/,/pyctag/,/pydat1/,/pydat2/,/pydat3/,
30  & /pypars/,/pyint1/,/pyint2/,/pyint4/,/pyint5/,/pyintm/
31 C...Local arrays.
32  dimension vtx(4)
33 
34 C...Stop if no subprocesses on.
35  IF(mint(121).EQ.1.AND.msti(53).EQ.1) THEN
36  WRITE(mstu(11),5100)
37  CALL pystop(1)
38  ENDIF
39 
40 C...Initial values for some counters.
41  mstu(1)=0
42  mstu(2)=0
43  n=0
44  mint(5)=mint(5)+1
45  mint(7)=0
46  mint(8)=0
47  mint(30)=0
48  mint(83)=0
49  mint(84)=mstp(126)
50  mstu(24)=0
51  mstu70=0
52  mstj14=mstj(14)
53 C...Normally, use K(I,4:5) colour info rather than /PYCT/.
54  nct=0
55  mint(33)=0
56 
57 C...Let called routines know call is from PYEVNW (not PYEVNT).
58  mint(35)=3
59 
60 C...If variable energies: redo incoming kinematics and cross-section.
61  msti(61)=0
62  IF(mstp(171).EQ.1) THEN
63  CALL pyinki(1)
64  IF(msti(61).EQ.1) THEN
65  mint(5)=mint(5)-1
66  RETURN
67  ENDIF
68  IF(mint(121).GT.1) CALL pysave(3,1)
69  CALL pyxtot
70  ENDIF
71 
72 C...Loop over number of pileup events; check space left.
73  IF(mstp(131).LE.0) THEN
74  npile=1
75  ELSE
76  CALL pypile(2)
77  npile=mint(81)
78  ENDIF
79  DO 300 ipile=1,npile
80  IF(mint(84)+100.GE.mstu(4)) THEN
81  CALL pyerrm(11,
82  & '(PYEVNW:) no more space in PYJETS for pileup events')
83  IF(mstu(21).GE.1) goto 310
84  ENDIF
85  mint(82)=ipile
86 
87 C...Generate variables of hard scattering.
88  mint(51)=0
89  msti(52)=0
90  100 CONTINUE
91  IF(mint(51).NE.0.OR.mstu(24).NE.0) msti(52)=msti(52)+1
92  mint(31)=0
93  mint(39)=0
94  mint(36)=0
95  mint(51)=0
96  mint(57)=0
97  CALL pyrand
98  IF(msti(61).EQ.1) THEN
99  mint(5)=mint(5)-1
100  RETURN
101  ENDIF
102  IF(mint(51).EQ.2) RETURN
103  isub=mint(1)
104  IF(mstp(111).EQ.-1) goto 290
105 
106 C...Loopback point if PYPREP fails, especially for junction topologies.
107  nprep=0
108  mnt31s=mint(31)
109  110 nprep=nprep+1
110  mint(31)=mnt31s
111 
112  IF((isub.LE.90.OR.isub.GE.95).AND.isub.NE.99) THEN
113 C...Hard scattering (including low-pT):
114 C...reconstruct kinematics and colour flow of hard scattering.
115  mint31=mint(31)
116  120 mint(31)=mint31
117  mint(51)=0
118  CALL pyscat
119  IF(mint(51).EQ.1) goto 100
120  npartd=n
121  nfin=n
122 
123 C...Intertwined initial state showers and multiple interactions.
124 C...Force no IS showers if no pdfs defined: MSTP(61) -> 0 for PYEVOL.
125 C...Force no MI if cross section not known: MSTP(81) -> 0 for PYEVOL.
126  mstp61=mstp(61)
127  IF (mint(47).LT.2) mstp(61)=0
128  mstp81=mstp(81)
129  IF (mint(50).EQ.0) mstp(81)=0
130  IF ((mstp(61).GE.1.OR.mod(mstp(81),10).GE.0).AND.
131  & mint(111).NE.12) THEN
132 C...Absolute max pT2 scale for evolution: phase space limit.
133  pt2mxs=0.25d0*vint(2)
134 C...Check if more constrained by ISR and MI max scales:
135  pt2mxs=min(pt2mxs,max(vint(56),vint(62)))
136 C...Loopback point in case of failure in evolution.
137  loop=0
138  130 loop=loop+1
139  mint(51)=0
140  IF(loop.GT.100) THEN
141  CALL pyerrm(9,'(PYEVNW:) failed to evolve shower or '
142  & //'multiple interactions.')
143  mint(51)=1
144  RETURN
145  ENDIF
146 
147 C...Pre-initialization of interleaved MI/ISR/JI evolution, only done
148 C...once per event. (E.g. compute constants and save variables to be
149 C...restored later in case of failure.)
150  IF (loop.EQ.1) CALL pyevol(-1,dummy1,dummy2)
151 
152 C...Initialize interleaved MI/ISR/JI evolution.
153 C...PT2MAX: absolute upper limit for evolution - Initialization may
154 C... return a PT2MAX which is lower than this.
155 C...PT2MIN: absolute lower limit for evolution - Initialization may
156 C... return a PT2MIN which is larger than this (e.g. Lambda_QCD).
157  pt2max=pt2mxs
158  pt2min=0d0
159  CALL pyevol(0,pt2max,pt2min)
160  IF (mint(51).EQ.1) goto 130
161 
162 C...Perform interleaved MI/ISR/JI evolution from PT2MAX to PT2MIN.
163 C...In principle factorized, so can be stopped and restarted.
164 C...Example: stop/start at pT=10 GeV. (Commented out for now.)
165 C PT2MED=MAX(10D0**2,PT2MIN)
166 C CALL PYEVOL(1,PT2MAX,PT2MED)
167 C IF (MINT(51).EQ.1) GOTO 160
168 C PT2MAX=PT2MED
169  CALL pyevol(1,pt2max,pt2min)
170  IF (mint(51).EQ.1) goto 130
171 
172 C...Finalize interleaved MI/ISR/JI evolution.
173  CALL pyevol(2,pt2max,pt2min)
174  IF (mint(51).EQ.1) goto 130
175 
176  ENDIF
177  mstp(61)=mstp61
178  mstp(81)=mstp81
179  IF(mint(51).EQ.1) goto 100
180 C...(MINT(52) is actually obsolete in this routine. Set anyway
181 C...to ensure PYDOCU stable.)
182  mint(52)=n
183  mint(53)=n
184 
185 C...Beam remnants - new scheme.
186  140 IF(mint(50).EQ.1) THEN
187  IF (isub.EQ.95) mint(31)=1
188 
189 C...Beam remnant flavour and colour assignments - new scheme.
190  CALL pymihk
191  IF(mint(51).EQ.1.AND.mint(57).GE.1.AND.mint(57).LE.5)
192  & goto 120
193  IF(mint(51).EQ.1) goto 100
194 
195 C...Primordial kT and beam remnant momentum sharing - new scheme.
196  CALL pymirm
197  IF(mint(51).EQ.1.AND.mint(57).GE.1.AND.mint(57).LE.5)
198  & goto 120
199  IF(mint(51).EQ.1) goto 100
200  IF (isub.EQ.95) mint(31)=0
201  ELSEIF(mint(111).NE.12) THEN
202 C...Hadron remnants and primordial kT - old model.
203 C...Happens e.g. for direct photon on one side.
204  ipu1=imi(1,1,1)
205  ipu2=imi(2,1,1)
206  CALL pyremn(ipu1,ipu2)
207  IF(mint(51).EQ.1.AND.mint(57).GE.1.AND.mint(57).LE.5) goto
208  & 110
209  IF(mint(51).EQ.1) goto 100
210 C...PYREMN does not set colour tags for BRs, so needs to be done now.
211  DO 160 i=mint(53)+1,n
212  DO 150 kcs=4,5
213  ida=mod(k(i,kcs),mstu(5))
214  IF (ida.NE.0) THEN
215  mct(i,kcs-3)=mct(ida,6-kcs)
216  ELSE
217  mct(i,kcs-3)=0
218  ENDIF
219  150 CONTINUE
220  160 CONTINUE
221 C...Instruct PYPREP to use colour tags
222  mint(33)=1
223 
224  DO 360 mqgst=1,2
225  DO 350 i=mint(84)+1,n
226 
227 C...Look for coloured string endpoint, or (later) leftover gluon.
228  IF (k(i,1).NE.3) goto 350
229  kc=pycomp(k(i,2))
230  IF(kc.EQ.0) goto 350
231  kq=kchg(kc,2)
232  IF(kq.EQ.0.OR.(mqgst.EQ.1.AND.kq.EQ.2)) goto 350
233 
234 C... Pick up loose string end with no previous tag.
235  kcs=4
236  IF(kq*isign(1,k(i,2)).LT.0) kcs=5
237  IF(mct(i,kcs-3).NE.0) goto 350
238 
239  CALL pycttr(i,kcs,i)
240  IF(mint(51).NE.0) RETURN
241 
242  350 CONTINUE
243  360 CONTINUE
244 C...Now delete any colour processing information if set (since partons
245 C...otherwise not FS showered!)
246  DO 170 i=mint(84)+1,n
247  IF (i.LE.n) THEN
248  k(i,4)=mod(k(i,4),mstu(5)**2)
249  k(i,5)=mod(k(i,5),mstu(5)**2)
250  ENDIF
251  170 CONTINUE
252  ENDIF
253 
254 C...Showering of final state partons (optional).
255  alamsv=parj(81)
256  parj(81)=parp(72)
257  IF(mstp(71).GE.1.AND.iset(isub).GE.1.AND.iset(isub).LE.10)
258  & THEN
259  qmax=vint(55)
260  IF(iset(isub).EQ.2) qmax=sqrt(parp(71))*vint(55)
261  CALL pyptfs(1,qmax,0d0,ptgen)
262 C...External processes: handle successive showers.
263  ELSEIF(iset(isub).EQ.11) THEN
264  CALL pyadsh(nfin)
265  ENDIF
266  parj(81)=alamsv
267 
268 C...Allow possibility for user to abort event generation.
269  iveto=0
270  IF(ipile.EQ.1.AND.mstp(143).EQ.1) CALL pyveto(iveto) ! sm
271  IF(iveto.EQ.1) goto 100
272 
273 
274 C...Decay of final state resonances.
275  mint(32)=0
276  IF(mstp(41).GE.1.AND.iset(isub).LE.10) THEN
277  CALL pyresd(0)
278  IF(mint(51).NE.0) goto 100
279  ENDIF
280 
281  IF(mint(51).EQ.1) goto 100
282 
283  ELSEIF(isub.NE.99) THEN
284 C...Diffractive and elastic scattering.
285  CALL pydiff
286 
287  ELSE
288 C...DIS scattering (photon flux external).
289  CALL pydisg
290  IF(mint(51).EQ.1) goto 100
291  ENDIF
292 
293 C...Check that no odd resonance left undecayed.
294  mint(54)=n
295  IF(mstp(111).GE.1) THEN
296  nfix=n
297  DO 180 i=mint(84)+1,nfix
298  IF(k(i,1).GE.1.AND.k(i,1).LE.10.AND.k(i,2).NE.21.AND.
299  & k(i,2).NE.22) THEN
300  kca=pycomp(k(i,2))
301  IF(mwid(kca).NE.0.AND.mdcy(kca,1).GE.1) THEN
302  CALL pyresd(i)
303  IF(mint(51).EQ.1) goto 100
304  ENDIF
305  ENDIF
306  180 CONTINUE
307  ENDIF
308 
309 C...Boost hadronic subsystem to overall rest frame.
310 C..(Only relevant when photon inside lepton beam.)
311  IF(mint(141).NE.0.OR.mint(142).NE.0) CALL pygaga(4,wtgaga)
312 
313 C...Recalculate energies from momenta and masses (if desired).
314  IF(mstp(113).GE.1) THEN
315  DO 190 i=mint(83)+1,n
316  IF(k(i,1).GT.0.AND.k(i,1).LE.10) p(i,4)=sqrt(p(i,1)**2+
317  & p(i,2)**2+p(i,3)**2+p(i,5)**2)
318  190 CONTINUE
319  nrecal=n
320  ENDIF
321 
322 C...Colour reconnection before string formation
323  CALL pyfscr(mint(84)+1)
324 
325 C...Rearrange partons along strings, check invariant mass cuts.
326  mstu(28)=0
327  IF(mstp(111).LE.0) mstj(14)=-1
328  CALL pyprep(mint(84)+1)
329  mstj(14)=mstj14
330  IF(mint(51).EQ.1.AND.mstu(24).EQ.1) THEN
331  mstu(24)=0
332  goto 100
333  ENDIF
334  IF(mint(51).EQ.1) goto 110
335  IF(mstp(112).EQ.1.AND.mstu(28).EQ.3) goto 100
336  IF(mstp(125).EQ.0.OR.mstp(125).EQ.1) THEN
337  DO 220 i=mint(84)+1,n
338  IF(k(i,2).EQ.94) THEN
339  DO 210 i1=i+1,min(n,i+10)
340  IF(k(i1,3).EQ.i) THEN
341  k(i1,3)=mod(k(i1,4)/mstu(5),mstu(5))
342  IF(k(i1,3).EQ.0) THEN
343  DO 200 ii=mint(84)+1,i-1
344  IF(k(ii,2).EQ.k(i1,2)) THEN
345  IF(mod(k(ii,4),mstu(5)).EQ.i1.OR.
346  & mod(k(ii,5),mstu(5)).EQ.i1) k(i1,3)=ii
347  ENDIF
348  200 CONTINUE
349  IF(k(i+1,3).EQ.0) k(i+1,3)=k(i,3)
350  ENDIF
351  ENDIF
352  210 CONTINUE
353  ENDIF
354  220 CONTINUE
355  CALL pyedit(12)
356  CALL pyedit(14)
357  IF(mstp(125).EQ.0) CALL pyedit(15)
358  IF(mstp(125).EQ.0) mint(4)=0
359  DO 240 i=mint(83)+1,n
360  IF(k(i,1).EQ.11.AND.k(i,4).EQ.0.AND.k(i,5).EQ.0) THEN
361  DO 230 i1=i+1,n
362  IF(k(i1,3).EQ.i.AND.k(i,4).EQ.0) k(i,4)=i1
363  IF(k(i1,3).EQ.i) k(i,5)=i1
364  230 CONTINUE
365  ENDIF
366  240 CONTINUE
367  ENDIF
368 
369 C...Introduce separators between sections in PYLIST event listing.
370  IF(ipile.EQ.1.AND.mstp(125).LE.0) THEN
371  mstu70=1
372  mstu(71)=n
373  ELSEIF(ipile.EQ.1) THEN
374  mstu70=3
375  mstu(71)=2
376  mstu(72)=mint(4)
377  mstu(73)=n
378  ENDIF
379 
380 C...Go back to lab frame (needed for vertices, also in fragmentation).
381  CALL pyfram(1)
382 
383 C...Set nonvanishing production vertex (optional).
384  IF(mstp(151).EQ.1) THEN
385  DO 250 j=1,4
386  vtx(j)=parp(150+j)*sqrt(-2d0*log(max(1d-10,pyr(0))))*
387  & sin(paru(2)*pyr(0))
388  250 CONTINUE
389  DO 270 i=mint(83)+1,n
390  DO 260 j=1,4
391  v(i,j)=v(i,j)+vtx(j)
392  260 CONTINUE
393  270 CONTINUE
394  ENDIF
395 
396 C...Perform hadronization (if desired).
397  IF(mstp(111).GE.1) THEN
398  CALL pyexec
399  IF(mstu(24).NE.0) goto 100
400  ENDIF
401  IF(mstp(113).GE.1) THEN
402  DO 280 i=nrecal,n
403  IF(p(i,5).GT.0d0) p(i,4)=sqrt(p(i,1)**2+
404  & p(i,2)**2+p(i,3)**2+p(i,5)**2)
405  280 CONTINUE
406  ENDIF
407  IF(mstp(125).EQ.0.OR.mstp(125).EQ.1) CALL pyedit(14)
408 
409 C...Store event information and calculate Monte Carlo estimates of
410 C...subprocess cross-sections.
411  290 IF(ipile.EQ.1) CALL pydocu
412 
413 C...Set counters for current pileup event and loop to next one.
414  msti(41)=ipile
415  IF(ipile.GE.2.AND.ipile.LE.10) msti(40+ipile)=isub
416  IF(mstu70.LT.10) THEN
417  mstu70=mstu70+1
418  mstu(70+mstu70)=n
419  ENDIF
420  mint(83)=n
421  mint(84)=n+mstp(126)
422  IF(ipile.LT.npile) CALL pyfram(2)
423  300 CONTINUE
424 
425 C...Generic information on pileup events. Reconstruct missing history.
426  IF(mstp(131).EQ.1.AND.mstp(133).GE.1) THEN
427  pari(91)=vint(132)
428  pari(92)=vint(133)
429  pari(93)=vint(134)
430  IF(mstp(133).GE.2) pari(93)=pari(93)*xsec(0,3)/vint(131)
431  ENDIF
432  CALL pyedit(16)
433 
434 C...Transform to the desired coordinate frame.
435  310 CALL pyfram(mstp(124))
436  mstu(70)=mstu70
437  paru(21)=vint(1)
438 
439 C...Error messages
440  5100 FORMAT(1x,'Error: no subprocess switched on.'/
441  &1x,'Execution stopped.')
442 
443  RETURN
444  END