Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyxjet.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyxjet.f
1 
2 C*********************************************************************
3 
4 C...PYXJET
5 C...Selects number of jets in matrix element approach.
6 
7  SUBROUTINE pyxjet(ECM,NJET,CUT)
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/pydat1/mstu(200),paru(200),mstj(200),parj(200)
15  SAVE /pydat1/
16 C...Local array and data.
17  dimension zhut(5)
18  DATA zhut/3.0922d0, 6.2291d0, 7.4782d0, 7.8440d0, 8.2560d0/
19 
20 C...Trivial result for two-jets only, including parton shower.
21  IF(mstj(101).EQ.0.OR.mstj(101).EQ.5) THEN
22  cut=0d0
23 
24 C...QCD and Abelian vector gluon theory: Q^2 for jet rate and R.
25  ELSEIF(mstj(109).EQ.0.OR.mstj(109).EQ.2) THEN
26  cf=4d0/3d0
27  IF(mstj(109).EQ.2) cf=1d0
28  IF(mstj(111).EQ.0) THEN
29  q2=ecm**2
30  q2r=ecm**2
31  ELSEIF(mstu(111).EQ.0) THEN
32  parj(169)=min(1d0,parj(129))
33  q2=parj(169)*ecm**2
34  parj(168)=min(1d0,max(parj(128),exp(-12d0*paru(1)/
35  & ((33d0-2d0*mstu(112))*paru(111)))))
36  q2r=parj(168)*ecm**2
37  ELSE
38  parj(169)=min(1d0,max(parj(129),(2d0*paru(112)/ecm)**2))
39  q2=parj(169)*ecm**2
40  parj(168)=min(1d0,max(parj(128),paru(112)/ecm,
41  & (2d0*paru(112)/ecm)**2))
42  q2r=parj(168)*ecm**2
43  ENDIF
44 
45 C...alpha_strong for R and R itself.
46  alspi=(3d0/4d0)*cf*pyalps(q2r)/paru(1)
47  IF(iabs(mstj(101)).EQ.1) THEN
48  rqcd=1d0+alspi
49  ELSEIF(mstj(109).EQ.0) THEN
50  rqcd=1d0+alspi+(1.986d0-0.115d0*mstu(118))*alspi**2
51  IF(mstj(111).EQ.1) rqcd=max(1d0,rqcd+
52  & (33d0-2d0*mstu(112))/12d0*log(parj(168))*alspi**2)
53  ELSE
54  rqcd=1d0+alspi-(3d0/32d0+0.519d0*mstu(118))*(4d0*alspi/3d0)**2
55  ENDIF
56 
57 C...alpha_strong for jet rate. Initial value for y cut.
58  alspi=(3d0/4d0)*cf*pyalps(q2)/paru(1)
59  cut=max(0.001d0,parj(125),(parj(126)/ecm)**2)
60  IF(iabs(mstj(101)).LE.1.OR.(mstj(109).EQ.0.AND.mstj(111).EQ.0))
61  & cut=max(cut,exp(-sqrt(0.75d0/alspi))/2d0)
62  IF(mstj(110).EQ.2) cut=max(0.01d0,min(0.05d0,cut))
63 
64 C...Parametrization of first order three-jet cross-section.
65  100 IF(mstj(101).EQ.0.OR.cut.GE.0.25d0) THEN
66  parj(152)=0d0
67  ELSE
68  parj(152)=(2d0*alspi/3d0)*((3d0-6d0*cut+2d0*log(cut))*
69  & log(cut/(1d0-2d0*cut))+(2.5d0+1.5d0*cut-6.571d0)*
70  & (1d0-3d0*cut)+5.833d0*(1d0-3d0*cut)**2-3.894d0*
71  & (1d0-3d0*cut)**3+1.342d0*(1d0-3d0*cut)**4)/rqcd
72  IF(mstj(109).EQ.2.AND.(mstj(101).EQ.2.OR.mstj(101).LE.-2))
73  & parj(152)=0d0
74  ENDIF
75 
76 C...Parametrization of second order three-jet cross-section.
77  IF(iabs(mstj(101)).LE.1.OR.mstj(101).EQ.3.OR.mstj(109).EQ.2.OR.
78  & cut.GE.0.25d0) THEN
79  parj(153)=0d0
80  ELSEIF(mstj(110).LE.1) THEN
81  ct=log(1d0/cut-2d0)
82  parj(153)=alspi**2*ct**2*(2.419d0+0.5989d0*ct+0.6782d0*ct**2-
83  & 0.2661d0*ct**3+0.01159d0*ct**4)/rqcd
84 
85 C...Interpolation in second/first order ratio for Zhu parametrization.
86  ELSEIF(mstj(110).EQ.2) THEN
87  iza=0
88  DO 110 iy=1,5
89  IF(abs(cut-0.01d0*iy).LT.0.0001d0) iza=iy
90  110 CONTINUE
91  IF(iza.NE.0) THEN
92  zhurat=zhut(iza)
93  ELSE
94  iz=100d0*cut
95  zhurat=zhut(iz)+(100d0*cut-iz)*(zhut(iz+1)-zhut(iz))
96  ENDIF
97  parj(153)=alspi*parj(152)*zhurat
98  ENDIF
99 
100 C...Shift in second order three-jet cross-section with optimized Q^2.
101  IF(mstj(111).EQ.1.AND.iabs(mstj(101)).GE.2.AND.mstj(101).NE.3
102  & .AND.cut.LT.0.25d0) parj(153)=parj(153)+
103  & (33d0-2d0*mstu(112))/12d0*log(parj(169))*alspi*parj(152)
104 
105 C...Parametrization of second order four-jet cross-section.
106  IF(iabs(mstj(101)).LE.1.OR.cut.GE.0.125d0) THEN
107  parj(154)=0d0
108  ELSE
109  ct=log(1d0/cut-5d0)
110  IF(cut.LE.0.018d0) THEN
111  xqqgg=6.349d0-4.330d0*ct+0.8304d0*ct**2
112  IF(mstj(109).EQ.2) xqqgg=(4d0/3d0)**2*(3.035d0-2.091d0*ct+
113  & 0.4059d0*ct**2)
114  xqqqq=1.25d0*(-0.1080d0+0.01486d0*ct+0.009364d0*ct**2)
115  IF(mstj(109).EQ.2) xqqqq=8d0*xqqqq
116  ELSE
117  xqqgg=-0.09773d0+0.2959d0*ct-0.2764d0*ct**2+0.08832d0*ct**3
118  IF(mstj(109).EQ.2) xqqgg=(4d0/3d0)**2*(-0.04079d0+
119  & 0.1340d0*ct-0.1326d0*ct**2+0.04365d0*ct**3)
120  xqqqq=1.25d0*(0.003661d0-0.004888d0*ct-0.001081d0*ct**2+
121  & 0.002093d0*ct**3)
122  IF(mstj(109).EQ.2) xqqqq=8d0*xqqqq
123  ENDIF
124  parj(154)=alspi**2*ct**2*(xqqgg+xqqqq)/rqcd
125  parj(155)=xqqqq/(xqqgg+xqqqq)
126  ENDIF
127 
128 C...If negative three-jet rate, change y' optimization parameter.
129  IF(mstj(111).EQ.1.AND.parj(152)+parj(153).LT.0d0.AND.
130  & parj(169).LT.0.99d0) THEN
131  parj(169)=min(1d0,1.2d0*parj(169))
132  q2=parj(169)*ecm**2
133  alspi=(3d0/4d0)*cf*pyalps(q2)/paru(1)
134  goto 100
135  ENDIF
136 
137 C...If too high cross-section, use harder cuts, or fail.
138  IF(parj(152)+parj(153)+parj(154).GE.1) THEN
139  IF(mstj(110).EQ.2.AND.cut.GT.0.0499d0.AND.mstj(111).EQ.1.AND.
140  & parj(169).LT.0.99d0) THEN
141  parj(169)=min(1d0,1.2d0*parj(169))
142  q2=parj(169)*ecm**2
143  alspi=(3d0/4d0)*cf*pyalps(q2)/paru(1)
144  goto 100
145  ELSEIF(mstj(110).EQ.2.AND.cut.GT.0.0499d0) THEN
146  CALL pyerrm(26,
147  & '(PYXJET:) no allowed y cut value for Zhu parametrization')
148  ENDIF
149  cut=0.26d0*(4d0*cut)**(parj(152)+parj(153)+
150  & parj(154))**(-1d0/3d0)
151  IF(mstj(110).EQ.2) cut=max(0.01d0,min(0.05d0,cut))
152  goto 100
153  ENDIF
154 
155 C...Scalar gluon (first order only).
156  ELSE
157  alspi=pyalps(ecm**2)/paru(1)
158  cut=max(0.001d0,parj(125),(parj(126)/ecm)**2,exp(-3d0/alspi))
159  parj(152)=0d0
160  IF(cut.LT.0.25d0) parj(152)=(alspi/3d0)*((1d0-2d0*cut)*
161  & log((1d0-2d0*cut)/cut)+0.5d0*(9d0*cut**2-1d0))
162  parj(153)=0d0
163  parj(154)=0d0
164  ENDIF
165 
166 C...Select number of jets.
167  parj(150)=cut
168  IF(mstj(101).EQ.0.OR.mstj(101).EQ.5) THEN
169  njet=2
170  ELSEIF(mstj(101).LE.0) THEN
171  njet=min(4,2-mstj(101))
172  ELSE
173  rnj=pyr(0)
174  njet=2
175  IF(parj(152)+parj(153)+parj(154).GT.rnj) njet=3
176  IF(parj(154).GT.rnj) njet=4
177  ENDIF
178 
179  RETURN
180  END