Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
py4jet.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file py4jet.f
1 
2 C*********************************************************************
3 
4 C...PY4JET
5 C...An interface from a four-parton generator to include
6 C...parton showers and hadronization.
7 
8  SUBROUTINE py4jet(PMAX,IRAD,ICOM)
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/pydat1/mstu(200),paru(200),mstj(200),parj(200)
17  SAVE /pyjets/,/pydat1/
18 C...Local arrays.
19  dimension ijoin(2),ptot(4),beta(3)
20 
21 C...Call PYHEPC to convert input from HEPEVT to PYJETS common.
22  IF(icom.EQ.0) THEN
23  mstu(28)=0
24  CALL pyhepc(2)
25  ENDIF
26 
27 C...Loop through entries and pick up all final partons.
28  i1=0
29  i2=0
30  i3=0
31  i4=0
32  DO 100 i=1,n
33  IF(k(i,1).LE.0.OR.k(i,1).GT.10) goto 100
34  kfa=iabs(k(i,2))
35  IF((kfa.GE.1.AND.kfa.LE.6).OR.kfa.EQ.21) THEN
36  IF(k(i,2).GT.0.AND.k(i,2).LE.6) THEN
37  IF(i1.EQ.0) THEN
38  i1=i
39  ELSEIF(i3.EQ.0) THEN
40  i3=i
41  ELSE
42  CALL pyerrm(16,'(PY4JET:) more than two quarks')
43  ENDIF
44  ELSEIF(k(i,2).LT.0) THEN
45  IF(i2.EQ.0) THEN
46  i2=i
47  ELSEIF(i4.EQ.0) THEN
48  i4=i
49  ELSE
50  CALL pyerrm(16,'(PY4JET:) more than two antiquarks')
51  ENDIF
52  ELSE
53  IF(i3.EQ.0) THEN
54  i3=i
55  ELSEIF(i4.EQ.0) THEN
56  i4=i
57  ELSE
58  CALL pyerrm(16,'(PY4JET:) more than two gluons')
59  ENDIF
60  ENDIF
61  ENDIF
62  100 CONTINUE
63 
64 C...Check that event is arranged according to conventions.
65  IF(i1.EQ.0.OR.i2.EQ.0.OR.i3.EQ.0.OR.i4.EQ.0) THEN
66  CALL pyerrm(16,'(PY4JET:) event contains too few partons')
67  ENDIF
68  IF(i2.LT.i1.OR.i3.LT.i2.OR.i4.LT.i3) THEN
69  CALL pyerrm(6,'(PY4JET:) partons arranged in wrong order')
70  ENDIF
71 
72 C...Check whether second pair are quarks or gluons.
73  IF(iabs(k(i3,2)).LT.10.AND.iabs(k(i4,2)).LT.10) THEN
74  iqg34=1
75  ELSEIF(k(i3,2).EQ.21.AND.k(i4,2).EQ.21) THEN
76  iqg34=2
77  ELSE
78  CALL pyerrm(16,'(PY4JET:) second parton pair inconsistent')
79  ENDIF
80 
81 C...Boost partons to their cm frame.
82  DO 110 j=1,4
83  ptot(j)=p(i1,j)+p(i2,j)+p(i3,j)+p(i4,j)
84  110 CONTINUE
85  ecm=sqrt(max(0d0,ptot(4)**2-ptot(1)**2-ptot(2)**2-ptot(3)**2))
86  DO 120 j=1,3
87  beta(j)=ptot(j)/ptot(4)
88  120 CONTINUE
89  CALL pyrobo(i1,i1,0d0,0d0,-beta(1),-beta(2),-beta(3))
90  CALL pyrobo(i2,i2,0d0,0d0,-beta(1),-beta(2),-beta(3))
91  CALL pyrobo(i3,i3,0d0,0d0,-beta(1),-beta(2),-beta(3))
92  CALL pyrobo(i4,i4,0d0,0d0,-beta(1),-beta(2),-beta(3))
93  nsav=n
94 
95 C...Decide and set up shower history for q qbar q' qbar' events.
96  IF(iqg34.EQ.1) THEN
97  w1=py4jtw(0,i1,i3,i4)
98  w2=py4jtw(0,i2,i3,i4)
99  IF(w1.GT.pyr(0)*(w1+w2)) THEN
100  CALL py4jts(0,i1,i3,i4,i2,qmax)
101  ELSE
102  CALL py4jts(0,i2,i3,i4,i1,qmax)
103  ENDIF
104 
105 C...Decide and set up shower history for q qbar g g events.
106  ELSE
107  w1=py4jtw(i1,i3,i2,i4)
108  w2=py4jtw(i1,i4,i2,i3)
109  w3=py4jtw(0,i3,i1,i4)
110  w4=py4jtw(0,i4,i1,i3)
111  w5=py4jtw(0,i3,i2,i4)
112  w6=py4jtw(0,i4,i2,i3)
113  w7=py4jtw(0,i1,i3,i4)
114  w8=py4jtw(0,i2,i3,i4)
115  wr=(w1+w2+w3+w4+w5+w6+w7+w8)*pyr(0)
116  IF(w1.GT.wr) THEN
117  CALL py4jts(i1,i3,i2,i4,0,qmax)
118  ELSEIF(w1+w2.GT.wr) THEN
119  CALL py4jts(i1,i4,i2,i3,0,qmax)
120  ELSEIF(w1+w2+w3.GT.wr) THEN
121  CALL py4jts(0,i3,i1,i4,i2,qmax)
122  ELSEIF(w1+w2+w3+w4.GT.wr) THEN
123  CALL py4jts(0,i4,i1,i3,i2,qmax)
124  ELSEIF(w1+w2+w3+w4+w5.GT.wr) THEN
125  CALL py4jts(0,i3,i2,i4,i1,qmax)
126  ELSEIF(w1+w2+w3+w4+w5+w6.GT.wr) THEN
127  CALL py4jts(0,i4,i2,i3,i1,qmax)
128  ELSEIF(w1+w2+w3+w4+w5+w6+w7.GT.wr) THEN
129  CALL py4jts(0,i1,i3,i4,i2,qmax)
130  ELSE
131  CALL py4jts(0,i2,i3,i4,i1,qmax)
132  ENDIF
133  ENDIF
134 
135 C...Boost back original partons and mark them as deleted.
136  CALL pyrobo(i1,i1,0d0,0d0,beta(1),beta(2),beta(3))
137  CALL pyrobo(i2,i2,0d0,0d0,beta(1),beta(2),beta(3))
138  CALL pyrobo(i3,i3,0d0,0d0,beta(1),beta(2),beta(3))
139  CALL pyrobo(i4,i4,0d0,0d0,beta(1),beta(2),beta(3))
140  k(i1,1)=k(i1,1)+10
141  k(i2,1)=k(i2,1)+10
142  k(i3,1)=k(i3,1)+10
143  k(i4,1)=k(i4,1)+10
144 
145 C...Rotate shower initiating partons to be along z axis.
146  phi=pyangl(p(nsav+1,1),p(nsav+1,2))
147  CALL pyrobo(nsav+1,nsav+6,0d0,-phi,0d0,0d0,0d0)
148  the=pyangl(p(nsav+1,3),p(nsav+1,1))
149  CALL pyrobo(nsav+1,nsav+6,-the,0d0,0d0,0d0,0d0)
150 
151 C...Set up copy of shower initiating partons as on mass shell.
152  DO 140 i=n+1,n+2
153  DO 130 j=1,5
154  k(i,j)=0
155  p(i,j)=0d0
156  v(i,j)=v(i1,j)
157  130 CONTINUE
158  k(i,1)=1
159  k(i,2)=k(i-6,2)
160  140 CONTINUE
161  IF(k(nsav+1,2).EQ.k(i1,2)) THEN
162  k(n+1,3)=i1
163  p(n+1,5)=p(i1,5)
164  k(n+2,3)=i2
165  p(n+2,5)=p(i2,5)
166  ELSE
167  k(n+1,3)=i2
168  p(n+1,5)=p(i2,5)
169  k(n+2,3)=i1
170  p(n+2,5)=p(i1,5)
171  ENDIF
172  pabs=sqrt(max(0d0,(ecm**2-p(n+1,5)**2-p(n+2,5)**2)**2-
173  &(2d0*p(n+1,5)*p(n+2,5))**2))/(2d0*ecm)
174  p(n+1,3)=pabs
175  p(n+1,4)=sqrt(pabs**2+p(n+1,5)**2)
176  p(n+2,3)=-pabs
177  p(n+2,4)=sqrt(pabs**2+p(n+2,5)**2)
178  n=n+2
179 
180 C...Decide whether to allow or not photon radiation in showers.
181 C...Connect up colours.
182  mstj(41)=2
183  IF(irad.EQ.0) mstj(41)=1
184  ijoin(1)=n-1
185  ijoin(2)=n
186  CALL pyjoin(2,ijoin)
187 
188 C...Decide on maximum virtuality and do parton shower.
189  IF(pmax.LT.parj(82)) THEN
190  pqmax=qmax
191  ELSE
192  pqmax=pmax
193  ENDIF
194  CALL pyshow(nsav+1,-100,pqmax)
195 
196 C...Rotate and boost back system.
197  CALL pyrobo(nsav+1,n,the,phi,beta(1),beta(2),beta(3))
198 
199 C...Do fragmentation and decays.
200  CALL pyexec
201 
202 C...Call PYHEPC to convert output from PYJETS to HEPEVT common.
203  IF(icom.EQ.0) THEN
204  mstu(28)=0
205  CALL pyhepc(1)
206  ENDIF
207 
208  RETURN
209  END