]> git.uio.no Git - u/mrichter/AliRoot.git/blame - PYTHIA/jetset/luxjet.F
This commit was generated by cvs2svn to compensate for changes in r2,
[u/mrichter/AliRoot.git] / PYTHIA / jetset / luxjet.F
CommitLineData
fe4da5cc 1
2C*********************************************************************
3
4 SUBROUTINE LUXJET(ECM,NJET,CUT)
5
6C...Purpose: to select number of jets in matrix element approach.
7 COMMON/LUDAT1/MSTU(200),PARU(200),MSTJ(200),PARJ(200)
8 SAVE /LUDAT1/
9 DIMENSION ZHUT(5)
10
11C...Relative three-jet rate in Zhu second order parametrization.
12 DATA ZHUT/3.0922, 6.2291, 7.4782, 7.8440, 8.2560/
13
14C...Trivial result for two-jets only, including parton shower.
15 IF(MSTJ(101).EQ.0.OR.MSTJ(101).EQ.5) THEN
16 CUT=0.
17
18C...QCD and Abelian vector gluon theory: Q^2 for jet rate and R.
19 ELSEIF(MSTJ(109).EQ.0.OR.MSTJ(109).EQ.2) THEN
20 CF=4./3.
21 IF(MSTJ(109).EQ.2) CF=1.
22 IF(MSTJ(111).EQ.0) THEN
23 Q2=ECM**2
24 Q2R=ECM**2
25 ELSEIF(MSTU(111).EQ.0) THEN
26 PARJ(169)=MIN(1.,PARJ(129))
27 Q2=PARJ(169)*ECM**2
28 PARJ(168)=MIN(1.,MAX(PARJ(128),EXP(-12.*PARU(1)/
29 & ((33.-2.*MSTU(112))*PARU(111)))))
30 Q2R=PARJ(168)*ECM**2
31 ELSE
32 PARJ(169)=MIN(1.,MAX(PARJ(129),(2.*PARU(112)/ECM)**2))
33 Q2=PARJ(169)*ECM**2
34 PARJ(168)=MIN(1.,MAX(PARJ(128),PARU(112)/ECM,
35 & (2.*PARU(112)/ECM)**2))
36 Q2R=PARJ(168)*ECM**2
37 ENDIF
38
39C...alpha_strong for R and R itself.
40 ALSPI=(3./4.)*CF*ULALPS(Q2R)/PARU(1)
41 IF(IABS(MSTJ(101)).EQ.1) THEN
42 RQCD=1.+ALSPI
43 ELSEIF(MSTJ(109).EQ.0) THEN
44 RQCD=1.+ALSPI+(1.986-0.115*MSTU(118))*ALSPI**2
45 IF(MSTJ(111).EQ.1) RQCD=MAX(1.,RQCD+(33.-2.*MSTU(112))/12.*
46 & LOG(PARJ(168))*ALSPI**2)
47 ELSE
48 RQCD=1.+ALSPI-(3./32.+0.519*MSTU(118))*(4.*ALSPI/3.)**2
49 ENDIF
50
51C...alpha_strong for jet rate. Initial value for y cut.
52 ALSPI=(3./4.)*CF*ULALPS(Q2)/PARU(1)
53 CUT=MAX(0.001,PARJ(125),(PARJ(126)/ECM)**2)
54 IF(IABS(MSTJ(101)).LE.1.OR.(MSTJ(109).EQ.0.AND.MSTJ(111).EQ.0))
55 & CUT=MAX(CUT,EXP(-SQRT(0.75/ALSPI))/2.)
56 IF(MSTJ(110).EQ.2) CUT=MAX(0.01,MIN(0.05,CUT))
57
58C...Parametrization of first order three-jet cross-section.
59 100 IF(MSTJ(101).EQ.0.OR.CUT.GE.0.25) THEN
60 PARJ(152)=0.
61 ELSE
62 PARJ(152)=(2.*ALSPI/3.)*((3.-6.*CUT+2.*LOG(CUT))*
63 & LOG(CUT/(1.-2.*CUT))+(2.5+1.5*CUT-6.571)*(1.-3.*CUT)+
64 & 5.833*(1.-3.*CUT)**2-3.894*(1.-3.*CUT)**3+
65 & 1.342*(1.-3.*CUT)**4)/RQCD
66 IF(MSTJ(109).EQ.2.AND.(MSTJ(101).EQ.2.OR.MSTJ(101).LE.-2))
67 & PARJ(152)=0.
68 ENDIF
69
70C...Parametrization of second order three-jet cross-section.
71 IF(IABS(MSTJ(101)).LE.1.OR.MSTJ(101).EQ.3.OR.MSTJ(109).EQ.2.OR.
72 & CUT.GE.0.25) THEN
73 PARJ(153)=0.
74 ELSEIF(MSTJ(110).LE.1) THEN
75 CT=LOG(1./CUT-2.)
76 PARJ(153)=ALSPI**2*CT**2*(2.419+0.5989*CT+0.6782*CT**2-
77 & 0.2661*CT**3+0.01159*CT**4)/RQCD
78
79C...Interpolation in second/first order ratio for Zhu parametrization.
80 ELSEIF(MSTJ(110).EQ.2) THEN
81 IZA=0
82 DO 110 IY=1,5
83 IF(ABS(CUT-0.01*IY).LT.0.0001) IZA=IY
84 110 CONTINUE
85 IF(IZA.NE.0) THEN
86 ZHURAT=ZHUT(IZA)
87 ELSE
88 IZ=100.*CUT
89 ZHURAT=ZHUT(IZ)+(100.*CUT-IZ)*(ZHUT(IZ+1)-ZHUT(IZ))
90 ENDIF
91 PARJ(153)=ALSPI*PARJ(152)*ZHURAT
92 ENDIF
93
94C...Shift in second order three-jet cross-section with optimized Q^2.
95 IF(MSTJ(111).EQ.1.AND.IABS(MSTJ(101)).GE.2.AND.MSTJ(101).NE.3.
96 & AND.CUT.LT.0.25) PARJ(153)=PARJ(153)+(33.-2.*MSTU(112))/12.*
97 & LOG(PARJ(169))*ALSPI*PARJ(152)
98
99C...Parametrization of second order four-jet cross-section.
100 IF(IABS(MSTJ(101)).LE.1.OR.CUT.GE.0.125) THEN
101 PARJ(154)=0.
102 ELSE
103 CT=LOG(1./CUT-5.)
104 IF(CUT.LE.0.018) THEN
105 XQQGG=6.349-4.330*CT+0.8304*CT**2
106 IF(MSTJ(109).EQ.2) XQQGG=(4./3.)**2*(3.035-2.091*CT+
107 & 0.4059*CT**2)
108 XQQQQ=1.25*(-0.1080+0.01486*CT+0.009364*CT**2)
109 IF(MSTJ(109).EQ.2) XQQQQ=8.*XQQQQ
110 ELSE
111 XQQGG=-0.09773+0.2959*CT-0.2764*CT**2+0.08832*CT**3
112 IF(MSTJ(109).EQ.2) XQQGG=(4./3.)**2*(-0.04079+0.1340*CT-
113 & 0.1326*CT**2+0.04365*CT**3)
114 XQQQQ=1.25*(0.003661-0.004888*CT-0.001081*CT**2+0.002093*
115 & CT**3)
116 IF(MSTJ(109).EQ.2) XQQQQ=8.*XQQQQ
117 ENDIF
118 PARJ(154)=ALSPI**2*CT**2*(XQQGG+XQQQQ)/RQCD
119 PARJ(155)=XQQQQ/(XQQGG+XQQQQ)
120 ENDIF
121
122C...If negative three-jet rate, change y' optimization parameter.
123 IF(MSTJ(111).EQ.1.AND.PARJ(152)+PARJ(153).LT.0..AND.
124 & PARJ(169).LT.0.99) THEN
125 PARJ(169)=MIN(1.,1.2*PARJ(169))
126 Q2=PARJ(169)*ECM**2
127 ALSPI=(3./4.)*CF*ULALPS(Q2)/PARU(1)
128 GOTO 100
129 ENDIF
130
131C...If too high cross-section, use harder cuts, or fail.
132 IF(PARJ(152)+PARJ(153)+PARJ(154).GE.1) THEN
133 IF(MSTJ(110).EQ.2.AND.CUT.GT.0.0499.AND.MSTJ(111).EQ.1.AND.
134 & PARJ(169).LT.0.99) THEN
135 PARJ(169)=MIN(1.,1.2*PARJ(169))
136 Q2=PARJ(169)*ECM**2
137 ALSPI=(3./4.)*CF*ULALPS(Q2)/PARU(1)
138 GOTO 100
139 ELSEIF(MSTJ(110).EQ.2.AND.CUT.GT.0.0499) THEN
140 CALL LUERRM(26,
141 & '(LUXJET:) no allowed y cut value for Zhu parametrization')
142 ENDIF
143 CUT=0.26*(4.*CUT)**(PARJ(152)+PARJ(153)+PARJ(154))**(-1./3.)
144 IF(MSTJ(110).EQ.2) CUT=MAX(0.01,MIN(0.05,CUT))
145 GOTO 100
146 ENDIF
147
148C...Scalar gluon (first order only).
149 ELSE
150 ALSPI=ULALPS(ECM**2)/PARU(1)
151 CUT=MAX(0.001,PARJ(125),(PARJ(126)/ECM)**2,EXP(-3./ALSPI))
152 PARJ(152)=0.
153 IF(CUT.LT.0.25) PARJ(152)=(ALSPI/3.)*((1.-2.*CUT)*
154 & LOG((1.-2.*CUT)/CUT)+0.5*(9.*CUT**2-1.))
155 PARJ(153)=0.
156 PARJ(154)=0.
157 ENDIF
158
159C...Select number of jets.
160 PARJ(150)=CUT
161 IF(MSTJ(101).EQ.0.OR.MSTJ(101).EQ.5) THEN
162 NJET=2
163 ELSEIF(MSTJ(101).LE.0) THEN
164 NJET=MIN(4,2-MSTJ(101))
165 ELSE
166 RNJ=RLU(0)
167 NJET=2
168 IF(PARJ(152)+PARJ(153)+PARJ(154).GT.RNJ) NJET=3
169 IF(PARJ(154).GT.RNJ) NJET=4
170 ENDIF
171
172 RETURN
173 END