Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyexec.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyexec.f
1 
2 C*********************************************************************
3 
4 C...PYEXEC
5 C...Administrates the fragmentation and decay chain.
6 
7  SUBROUTINE pyexec
8 
9 C...Double precision and integer declarations.
10  IMPLICIT DOUBLE PRECISION(a-h, o-z)
11  IMPLICIT INTEGER(i-n)
12  INTEGER pyk,pychge,pycomp
13 C...Commonblocks.
14  common/pyjets/n,npad,k(4000,5),p(4000,5),v(4000,5)
15  common/pydat1/mstu(200),paru(200),mstj(200),parj(200)
16  common/pydat2/kchg(500,4),pmas(500,4),parf(2000),vckm(4,4)
17  common/pydat3/mdcy(500,3),mdme(8000,2),brat(8000),kfdp(8000,5)
18  common/pyint1/mint(400),vint(400)
19  common/pyint4/mwid(500),wids(500,5)
20  SAVE /pyjets/,/pydat1/,/pydat2/,/pydat3/,/pyint1/,/pyint4/
21 C...Local array.
22  dimension ps(2,6),ijoin(100)
23 
24 C...Initialize and reset.
25  mstu(24)=0
26  IF(mstu(12).NE.12345) CALL pylist(0)
27  mstu(29)=0
28  mstu(31)=mstu(31)+1
29  mstu(1)=0
30  mstu(2)=0
31  mstu(3)=0
32  IF(mstu(17).LE.0) mstu(90)=0
33  mcons=1
34 
35 C...Sum up momentum, energy and charge for starting entries.
36  nsav=n
37  DO 110 i=1,2
38  DO 100 j=1,6
39  ps(i,j)=0d0
40  100 CONTINUE
41  110 CONTINUE
42  DO 130 i=1,n
43  IF(k(i,1).LE.0.OR.k(i,1).GT.10) goto 130
44  DO 120 j=1,4
45  ps(1,j)=ps(1,j)+p(i,j)
46  120 CONTINUE
47  ps(1,6)=ps(1,6)+pychge(k(i,2))
48  130 CONTINUE
49  paru(21)=ps(1,4)
50 
51 C...Start by all decays of coloured resonances involved in shower.
52  norig=n
53  DO 140 i=1,norig
54  IF(k(i,1).EQ.3) THEN
55  kc=pycomp(k(i,2))
56  IF(mwid(kc).NE.0.AND.kchg(kc,2).NE.0) CALL pyresd(i)
57  ENDIF
58  140 CONTINUE
59 
60 C...Prepare system for subsequent fragmentation/decay.
61  CALL pyprep(0)
62  IF(mint(51).NE.0) RETURN
63 
64 C...Loop through jet fragmentation and particle decays.
65  mbe=0
66  150 mbe=mbe+1
67  ip=0
68  160 ip=ip+1
69  kc=0
70  IF(k(ip,1).GT.0.AND.k(ip,1).LE.10) kc=pycomp(k(ip,2))
71  IF(kc.EQ.0) THEN
72 
73 C...Deal with any remaining undecayed resonance
74 C...(normally the task of PYEVNT, so seldom used).
75  ELSEIF(mwid(kc).NE.0) THEN
76  ibeg=ip
77  IF(kchg(kc,2).NE.0.AND.k(i,1).NE.3) THEN
78  ibeg=ip+1
79  170 ibeg=ibeg-1
80  IF(ibeg.GE.2.AND.k(ibeg,1).EQ.2) goto 170
81  IF(k(ibeg,1).NE.2) ibeg=ibeg+1
82  iend=ip-1
83  180 iend=iend+1
84  IF(iend.LT.n.AND.k(iend,1).EQ.2) goto 180
85  IF(iend.LT.n.AND.kchg(pycomp(k(iend,2)),2).EQ.0) goto 180
86  njoin=0
87  DO 190 i=ibeg,iend
88  IF(kchg(pycomp(k(iend,2)),2).NE.0) THEN
89  njoin=njoin+1
90  ijoin(njoin)=i
91  ENDIF
92  190 CONTINUE
93  ENDIF
94  CALL pyresd(ip)
95  CALL pyprep(ibeg)
96  IF(mint(51).NE.0) RETURN
97 
98 C...Particle decay if unstable and allowed. Save long-lived particle
99 C...decays until second pass after Bose-Einstein effects.
100  ELSEIF(kchg(kc,2).EQ.0) THEN
101  IF(mstj(21).GE.1.AND.mdcy(kc,1).GE.1.AND.(mstj(51).LE.0.OR.mbe
102  & .EQ.2.OR.pmas(kc,2).GE.parj(91).OR.iabs(k(ip,2)).EQ.311))
103  & CALL pydecy(ip)
104 
105 C...Decay products may develop a shower.
106  IF(mstj(92).GT.0) THEN
107  ip1=mstj(92)
108  qmax=sqrt(max(0d0,(p(ip1,4)+p(ip1+1,4))**2-(p(ip1,1)+p(ip1+1,
109  & 1))**2-(p(ip1,2)+p(ip1+1,2))**2-(p(ip1,3)+p(ip1+1,3))**2))
110  mint(33)=0
111  CALL pyshow(ip1,ip1+1,qmax)
112  CALL pyprep(ip1)
113  IF(mint(51).NE.0) RETURN
114  mstj(92)=0
115  ELSEIF(mstj(92).LT.0) THEN
116  ip1=-mstj(92)
117  mint(33)=0
118  CALL pyshow(ip1,-3,p(ip,5))
119  CALL pyprep(ip1)
120  IF(mint(51).NE.0) RETURN
121  mstj(92)=0
122  ENDIF
123 
124 C...Jet fragmentation: string or independent fragmentation.
125  ELSEIF(k(ip,1).EQ.1.OR.k(ip,1).EQ.2) THEN
126  mfrag=mstj(1)
127  IF(mfrag.GE.1.AND.k(ip,1).EQ.1) mfrag=2
128  IF(mstj(21).GE.2.AND.k(ip,1).EQ.2.AND.n.GT.ip) THEN
129  IF(k(ip+1,1).EQ.1.AND.k(ip+1,3).EQ.k(ip,3).AND.
130  & k(ip,3).GT.0.AND.k(ip,3).LT.ip) THEN
131  IF(kchg(pycomp(k(k(ip,3),2)),2).EQ.0) mfrag=min(1,mfrag)
132  ENDIF
133  ENDIF
134  IF(mfrag.EQ.1) CALL pystrf(ip)
135  IF(mfrag.EQ.2) CALL pyindf(ip)
136  IF(mfrag.EQ.2.AND.k(ip,1).EQ.1) mcons=0
137  IF(mfrag.EQ.2.AND.(mstj(3).LE.0.OR.mod(mstj(3),5).EQ.0)) mcons=0
138  ENDIF
139 
140 C...Loop back if enough space left in PYJETS and no error abort.
141  IF(mstu(24).NE.0.AND.mstu(21).GE.2) THEN
142  ELSEIF(ip.LT.n.AND.n.LT.mstu(4)-20-mstu(32)) THEN
143  goto 160
144  ELSEIF(ip.LT.n) THEN
145  CALL pyerrm(11,'(PYEXEC:) no more memory left in PYJETS')
146  ENDIF
147 
148 C...Include simple Bose-Einstein effect parametrization if desired.
149  IF(mbe.EQ.1.AND.mstj(51).GE.1) THEN
150  CALL pyboei(nsav)
151  goto 150
152  ENDIF
153 
154 C...Check that momentum, energy and charge were conserved.
155  DO 210 i=1,n
156  IF(k(i,1).LE.0.OR.k(i,1).GT.10) goto 210
157  DO 200 j=1,4
158  ps(2,j)=ps(2,j)+p(i,j)
159  200 CONTINUE
160  ps(2,6)=ps(2,6)+pychge(k(i,2))
161  210 CONTINUE
162  pdev=(abs(ps(2,1)-ps(1,1))+abs(ps(2,2)-ps(1,2))+abs(ps(2,3)-
163  &ps(1,3))+abs(ps(2,4)-ps(1,4)))/(1d0+abs(ps(2,4))+abs(ps(1,4)))
164  IF(mcons.EQ.1.AND.pdev.GT.paru(11)) CALL pyerrm(15,
165  &'(PYEXEC:) four-momentum was not conserved')
166  IF(mcons.EQ.1.AND.abs(ps(2,6)-ps(1,6)).GT.0.1d0) CALL pyerrm(15,
167  &'(PYEXEC:) charge was not conserved')
168 
169  RETURN
170  END