Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyxdif.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyxdif.f
1 
2 C*********************************************************************
3 
4 C...PYXDIF
5 C...Gives the angular orientation of events.
6 
7  SUBROUTINE pyxdif(NC,NJET,KFL,ECM,CHI,THE,PHI)
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  SAVE /pyjets/,/pydat1/,/pydat2/
18 
19 C...Charge. Factors depending on polarization for QED case.
20  qf=kchg(kfl,1)/3d0
21  poll=1d0-parj(131)*parj(132)
22  pold=parj(132)-parj(131)
23  IF(mstj(102).LE.1.OR.mstj(109).EQ.1) THEN
24  hf1=poll
25  hf2=0d0
26  hf3=parj(133)**2
27  hf4=0d0
28 
29 C...Factors depending on flavour, energy and polarization for QFD case.
30  ELSE
31  sff=1d0/(16d0*paru(102)*(1d0-paru(102)))
32  sfw=ecm**4/((ecm**2-parj(123)**2)**2+(parj(123)*parj(124))**2)
33  sfi=sfw*(1d0-(parj(123)/ecm)**2)
34  ae=-1d0
35  ve=4d0*paru(102)-1d0
36  af=sign(1d0,qf)
37  vf=af-4d0*qf*paru(102)
38  hf1=qf**2*poll-2d0*qf*vf*sfi*sff*(ve*poll-ae*pold)+
39  & (vf**2+af**2)*sfw*sff**2*((ve**2+ae**2)*poll-2d0*ve*ae*pold)
40  hf2=-2d0*qf*af*sfi*sff*(ae*poll-ve*pold)+2d0*vf*af*sfw*sff**2*
41  & (2d0*ve*ae*poll-(ve**2+ae**2)*pold)
42  hf3=parj(133)**2*(qf**2-2d0*qf*vf*sfi*sff*ve+(vf**2+af**2)*
43  & sfw*sff**2*(ve**2-ae**2))
44  hf4=-parj(133)**2*2d0*qf*vf*sfw*(parj(123)*parj(124)/ecm**2)*
45  & sff*ae
46  ENDIF
47 
48 C...Mass factor. Differential cross-sections for two-jet events.
49  sq2=sqrt(2d0)
50  qme=0d0
51  IF(mstj(103).GE.4.AND.iabs(mstj(101)).LE.1.AND.mstj(102).LE.1.AND.
52  &mstj(109).NE.1) qme=(2d0*pymass(kfl)/ecm)**2
53  IF(njet.EQ.2) THEN
54  sigu=4d0*sqrt(1d0-qme)
55  sigl=2d0*qme*sqrt(1d0-qme)
56  sigt=0d0
57  sigi=0d0
58  siga=0d0
59  sigp=4d0
60 
61 C...Kinematical variables. Reduce four-jet event to three-jet one.
62  ELSE
63  IF(njet.EQ.3) THEN
64  x1=2d0*p(nc+1,4)/ecm
65  x2=2d0*p(nc+3,4)/ecm
66  ELSE
67  ecmr=p(nc+1,4)+p(nc+4,4)+sqrt((p(nc+2,1)+p(nc+3,1))**2+
68  & (p(nc+2,2)+p(nc+3,2))**2+(p(nc+2,3)+p(nc+3,3))**2)
69  x1=2d0*p(nc+1,4)/ecmr
70  x2=2d0*p(nc+4,4)/ecmr
71  ENDIF
72 
73 C...Differential cross-sections for three-jet (or reduced four-jet).
74  xq=(1d0-x1)/(1d0-x2)
75  ct12=(x1*x2-2d0*x1-2d0*x2+2d0+qme)/sqrt((x1**2-qme)*(x2**2-qme))
76  st12=sqrt(1d0-ct12**2)
77  IF(mstj(109).NE.1) THEN
78  sigu=2d0*x1**2+x2**2*(1d0+ct12**2)-qme*(3d0+ct12**2-x1-x2)-
79  & qme*x1/xq+0.5d0*qme*((x2**2-qme)*st12**2-2d0*x2)*xq
80  sigl=(x2*st12)**2-qme*(3d0-ct12**2-2.5d0*(x1+x2)+x1*x2+qme)+
81  & 0.5d0*qme*(x1**2-x1-qme)/xq+0.5d0*qme*((x2**2-qme)*ct12**2-
82  & x2)*xq
83  sigt=0.5d0*(x2**2-qme-0.5d0*qme*(x2**2-qme)/xq)*st12**2
84  sigi=((1d0-0.5d0*qme*xq)*(x2**2-qme)*st12*ct12+
85  & qme*(1d0-x1-x2+0.5d0*x1*x2+0.5d0*qme)*st12/ct12)/sq2
86  siga=x2**2*st12/sq2
87  sigp=2d0*(x1**2-x2**2*ct12)
88 
89 C...Differential cross-sect for scalar gluons (no mass effects).
90  ELSE
91  x3=2d0-x1-x2
92  xt=x2*st12
93  ct13=sqrt(max(0d0,1d0-(xt/x3)**2))
94  sigu=(1d0-parj(171))*(x3**2-0.5d0*xt**2)+
95  & parj(171)*(x3**2-0.5d0*xt**2-4d0*(1d0-x1)*(1d0-x2)**2/x1)
96  sigl=(1d0-parj(171))*0.5d0*xt**2+
97  & parj(171)*0.5d0*(1d0-x1)**2*xt**2
98  sigt=(1d0-parj(171))*0.25d0*xt**2+
99  & parj(171)*0.25d0*xt**2*(1d0-2d0*x1)
100  sigi=-(0.5d0/sq2)*((1d0-parj(171))*xt*x3*ct13+
101  & parj(171)*xt*((1d0-2d0*x1)*x3*ct13-x1*(x1-x2)))
102  siga=(0.25d0/sq2)*xt*(2d0*(1d0-x1)-x1*x3)
103  sigp=x3**2-2d0*(1d0-x1)*(1d0-x2)/x1
104  ENDIF
105  ENDIF
106 
107 C...Upper bounds for differential cross-section.
108  hf1a=abs(hf1)
109  hf2a=abs(hf2)
110  hf3a=abs(hf3)
111  hf4a=abs(hf4)
112  sigmax=(2d0*hf1a+hf3a+hf4a)*abs(sigu)+2d0*(hf1a+hf3a+hf4a)*
113  &abs(sigl)+2d0*(hf1a+2d0*hf3a+2d0*hf4a)*abs(sigt)+2d0*sq2*
114  &(hf1a+2d0*hf3a+2d0*hf4a)*abs(sigi)+4d0*sq2*hf2a*abs(siga)+
115  &2d0*hf2a*abs(sigp)
116 
117 C...Generate angular orientation according to differential cross-sect.
118  100 chi=paru(2)*pyr(0)
119  cthe=2d0*pyr(0)-1d0
120  phi=paru(2)*pyr(0)
121  cchi=cos(chi)
122  schi=sin(chi)
123  c2chi=cos(2d0*chi)
124  s2chi=sin(2d0*chi)
125  the=acos(cthe)
126  sthe=sin(the)
127  c2phi=cos(2d0*(phi-parj(134)))
128  s2phi=sin(2d0*(phi-parj(134)))
129  sig=((1d0+cthe**2)*hf1+sthe**2*(c2phi*hf3-s2phi*hf4))*sigu+
130  &2d0*(sthe**2*hf1-sthe**2*(c2phi*hf3-s2phi*hf4))*sigl+
131  &2d0*(sthe**2*c2chi*hf1+((1d0+cthe**2)*c2chi*c2phi-2d0*cthe*s2chi*
132  &s2phi)*hf3-((1d0+cthe**2)*c2chi*s2phi+2d0*cthe*s2chi*c2phi)*hf4)*
133  &sigt-2d0*sq2*(2d0*sthe*cthe*cchi*hf1-2d0*sthe*(cthe*cchi*c2phi-
134  &schi*s2phi)*hf3+2d0*sthe*(cthe*cchi*s2phi+schi*c2phi)*hf4)*sigi+
135  &4d0*sq2*sthe*cchi*hf2*siga+2d0*cthe*hf2*sigp
136  IF(sig.LT.sigmax*pyr(0)) goto 100
137 
138  RETURN
139  END