Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyonia.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyonia.f
1 
2 C*********************************************************************
3 
4 C...PYONIA
5 C...Generates Upsilon and toponium decays into three gluons
6 C...or two gluons and a photon.
7 
8  SUBROUTINE pyonia(KFL,ECM)
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  common/pydat2/kchg(500,4),pmas(500,4),parf(2000),vckm(4,4)
18  SAVE /pyjets/,/pydat1/,/pydat2/
19 
20 C...Printout. Check input parameters.
21  IF(mstu(12).NE.12345) CALL pylist(0)
22  IF(kfl.LT.0.OR.kfl.GT.8) THEN
23  CALL pyerrm(16,'(PYONIA:) called with unknown flavour code')
24  IF(mstu(21).GE.1) RETURN
25  ENDIF
26  IF(ecm.LT.parj(127)+2.02d0*parf(101)) THEN
27  CALL pyerrm(16,'(PYONIA:) called with too small CM energy')
28  IF(mstu(21).GE.1) RETURN
29  ENDIF
30 
31 C...Initial e+e- and onium state (optional).
32  nc=0
33  IF(mstj(115).GE.2) THEN
34  nc=nc+2
35  CALL py1ent(nc-1,11,0.5d0*ecm,0d0,0d0)
36  k(nc-1,1)=21
37  CALL py1ent(nc,-11,0.5d0*ecm,paru(1),0d0)
38  k(nc,1)=21
39  ENDIF
40  kflc=iabs(kfl)
41  IF(mstj(115).GE.3.AND.kflc.GE.5) THEN
42  nc=nc+1
43  kf=110*kflc+3
44  mstu10=mstu(10)
45  mstu(10)=1
46  p(nc,5)=ecm
47  CALL py1ent(nc,kf,ecm,0d0,0d0)
48  k(nc,1)=21
49  k(nc,3)=1
50  mstu(10)=mstu10
51  ENDIF
52 
53 C...Choose x1 and x2 according to matrix element.
54  ntry=0
55  100 x1=pyr(0)
56  x2=pyr(0)
57  x3=2d0-x1-x2
58  IF(x3.GE.1d0.OR.((1d0-x1)/(x2*x3))**2+((1d0-x2)/(x1*x3))**2+
59  &((1d0-x3)/(x1*x2))**2.LE.2d0*pyr(0)) goto 100
60  ntry=ntry+1
61  njet=3
62  IF(mstj(101).LE.4) CALL py3ent(nc+1,21,21,21,ecm,x1,x3)
63  IF(mstj(101).GE.5) CALL py3ent(-(nc+1),21,21,21,ecm,x1,x3)
64 
65 C...Photon-gluon-gluon events. Small system modifications. Jet origin.
66  mstu(111)=mstj(108)
67  IF(mstj(108).EQ.2.AND.(mstj(101).EQ.0.OR.mstj(101).EQ.1))
68  &mstu(111)=1
69  paru(112)=parj(121)
70  IF(mstu(111).EQ.2) paru(112)=parj(122)
71  qf=0d0
72  IF(kflc.NE.0) qf=kchg(kflc,1)/3d0
73  rgam=7.2d0*qf**2*paru(101)/pyalps(ecm**2)
74  mk=0
75  ecmc=ecm
76  IF(pyr(0).GT.rgam/(1d0+rgam)) THEN
77  IF(1d0-max(x1,x2,x3).LE.max((parj(126)/ecm)**2,parj(125)))
78  & njet=2
79  IF(njet.EQ.2.AND.mstj(101).LE.4) CALL py2ent(nc+1,21,21,ecm)
80  IF(njet.EQ.2.AND.mstj(101).GE.5) CALL py2ent(-(nc+1),21,21,ecm)
81  ELSE
82  mk=1
83  ecmc=sqrt(1d0-x1)*ecm
84  IF(ecmc.LT.2d0*parj(127)) goto 100
85  k(nc+1,1)=1
86  k(nc+1,2)=22
87  k(nc+1,4)=0
88  k(nc+1,5)=0
89  IF(mstj(101).GE.5) k(nc+2,4)=mstu(5)*(nc+3)
90  IF(mstj(101).GE.5) k(nc+2,5)=mstu(5)*(nc+3)
91  IF(mstj(101).GE.5) k(nc+3,4)=mstu(5)*(nc+2)
92  IF(mstj(101).GE.5) k(nc+3,5)=mstu(5)*(nc+2)
93  njet=2
94  IF(ecmc.LT.4d0*parj(127)) THEN
95  mstu10=mstu(10)
96  mstu(10)=1
97  p(nc+2,5)=ecmc
98  CALL py1ent(nc+2,83,0.5d0*(x2+x3)*ecm,paru(1),0d0)
99  mstu(10)=mstu10
100  njet=0
101  ENDIF
102  ENDIF
103  DO 110 ip=nc+1,n
104  k(ip,3)=k(ip,3)+(mstj(115)/2)+(kflc/5)*(mstj(115)/3)*(nc-1)
105  110 CONTINUE
106 
107 C...Differential cross-sections. Upper limit for cross-section.
108  IF(mstj(106).EQ.1) THEN
109  sq2=sqrt(2d0)
110  hf1=1d0-parj(131)*parj(132)
111  hf3=parj(133)**2
112  ct13=(x1*x3-2d0*x1-2d0*x3+2d0)/(x1*x3)
113  st13=sqrt(1d0-ct13**2)
114  sigl=0.5d0*x3**2*((1d0-x2)**2+(1d0-x3)**2)*st13**2
115  sigu=(x1*(1d0-x1))**2+(x2*(1d0-x2))**2+(x3*(1d0-x3))**2-sigl
116  sigt=0.5d0*sigl
117  sigi=(sigl*ct13/st13+0.5d0*x1*x3*(1d0-x2)**2*st13)/sq2
118  sigmax=(2d0*hf1+hf3)*abs(sigu)+2d0*(hf1+hf3)*abs(sigl)+2d0*(hf1+
119  & 2d0*hf3)*abs(sigt)+2d0*sq2*(hf1+2d0*hf3)*abs(sigi)
120 
121 C...Angular orientation of event.
122  120 chi=paru(2)*pyr(0)
123  cthe=2d0*pyr(0)-1d0
124  phi=paru(2)*pyr(0)
125  cchi=cos(chi)
126  schi=sin(chi)
127  c2chi=cos(2d0*chi)
128  s2chi=sin(2d0*chi)
129  the=acos(cthe)
130  sthe=sin(the)
131  c2phi=cos(2d0*(phi-parj(134)))
132  s2phi=sin(2d0*(phi-parj(134)))
133  sig=((1d0+cthe**2)*hf1+sthe**2*c2phi*hf3)*sigu+2d0*(sthe**2*hf1-
134  & sthe**2*c2phi*hf3)*sigl+2d0*(sthe**2*c2chi*hf1+((1d0+cthe**2)*
135  & c2chi*c2phi-2d0*cthe*s2chi*s2phi)*hf3)*sigt-
136  & 2d0*sq2*(2d0*sthe*cthe*cchi*hf1-2d0*sthe*
137  & (cthe*cchi*c2phi-schi*s2phi)*hf3)*sigi
138  IF(sig.LT.sigmax*pyr(0)) goto 120
139  CALL pyrobo(nc+1,n,0d0,chi,0d0,0d0,0d0)
140  CALL pyrobo(nc+1,n,the,phi,0d0,0d0,0d0)
141  ENDIF
142 
143 C...Generate parton shower. Rearrange along strings and check.
144  IF(mstj(101).GE.5.AND.njet.GE.2) THEN
145  CALL pyshow(nc+mk+1,-njet,ecmc)
146  mstj14=mstj(14)
147  IF(mstj(105).EQ.-1) mstj(14)=-1
148  IF(mstj(105).GE.0) mstu(28)=0
149  CALL pyprep(0)
150  mstj(14)=mstj14
151  IF(mstj(105).GE.0.AND.mstu(28).NE.0) goto 100
152  ENDIF
153 
154 C...Generate fragmentation. Information for PYTABU:
155  IF(mstj(105).EQ.1) CALL pyexec
156  mstu(161)=110*kflc+3
157  mstu(162)=0
158 
159  RETURN
160  END