]> git.uio.no Git - u/mrichter/AliRoot.git/blob - HIJING/hipyset1_35/luxjet_hijing.F
Updated VZERO source
[u/mrichter/AliRoot.git] / HIJING / hipyset1_35 / luxjet_hijing.F
1 * $Id$
2     
3 C*********************************************************************  
4     
5       SUBROUTINE LUXJET_HIJING(ECM,NJET,CUT)   
6     
7 C...Purpose: to select number of jets in matrix element approach.   
8 #include "ludat1_hijing.inc"
9       DIMENSION ZHUT(5) 
10     
11 C...Relative three-jet rate in Zhu second order parametrization.    
12       DATA ZHUT/3.0922, 6.2291, 7.4782, 7.8440, 8.2560/ 
13     
14 C...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     
18 C...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     
39 C...alpha_strong for R and R itself.    
40         ALSPI=(3./4.)*CF*ULALPS_HIJING(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     
51 C...alpha_strong for jet rate. Initial value for y cut. 
52         ALSPI=(3./4.)*CF*ULALPS_HIJING(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     
58 C...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     
70 C...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     
79 C...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   110     IF(ABS(CUT-0.01*IY).LT.0.0001) IZA=IY 
84           IF(IZA.NE.0) THEN 
85             ZHURAT=ZHUT(IZA)    
86           ELSE  
87             IZ=100.*CUT 
88             ZHURAT=ZHUT(IZ)+(100.*CUT-IZ)*(ZHUT(IZ+1)-ZHUT(IZ)) 
89           ENDIF 
90           PARJ(153)=ALSPI*PARJ(152)*ZHURAT  
91         ENDIF   
92     
93 C...Shift in second order three-jet cross-section with optimized Q^2.   
94         IF(MSTJ(111).EQ.1.AND.IABS(MSTJ(101)).GE.2.AND.MSTJ(101).NE.3.  
95      &  AND.CUT.LT.0.25) PARJ(153)=PARJ(153)+(33.-2.*MSTU(112))/12.*    
96      &  LOG(PARJ(169))*ALSPI*PARJ(152)  
97     
98 C...Parametrization of second order four-jet cross-section. 
99         IF(IABS(MSTJ(101)).LE.1.OR.CUT.GE.0.125) THEN   
100           PARJ(154)=0.  
101         ELSE    
102           CT=LOG(1./CUT-5.) 
103           IF(CUT.LE.0.018) THEN 
104             XQQGG=6.349-4.330*CT+0.8304*CT**2   
105             IF(MSTJ(109).EQ.2) XQQGG=(4./3.)**2*(3.035-2.091*CT+    
106      &      0.4059*CT**2)   
107             XQQQQ=1.25*(-0.1080+0.01486*CT+0.009364*CT**2)  
108             IF(MSTJ(109).EQ.2) XQQQQ=8.*XQQQQ   
109           ELSE  
110             XQQGG=-0.09773+0.2959*CT-0.2764*CT**2+0.08832*CT**3 
111             IF(MSTJ(109).EQ.2) XQQGG=(4./3.)**2*(-0.04079+0.1340*CT-    
112      &      0.1326*CT**2+0.04365*CT**3) 
113             XQQQQ=1.25*(0.003661-0.004888*CT-0.001081*CT**2+0.002093*   
114      &      CT**3)  
115             IF(MSTJ(109).EQ.2) XQQQQ=8.*XQQQQ   
116           ENDIF 
117           PARJ(154)=ALSPI**2*CT**2*(XQQGG+XQQQQ)/RQCD   
118           PARJ(155)=XQQQQ/(XQQGG+XQQQQ) 
119         ENDIF   
120     
121 C...If negative three-jet rate, change y' optimization parameter.   
122         IF(MSTJ(111).EQ.1.AND.PARJ(152)+PARJ(153).LT.0..AND.    
123      &  PARJ(169).LT.0.99) THEN 
124           PARJ(169)=MIN(1.,1.2*PARJ(169))   
125           Q2=PARJ(169)*ECM**2   
126           ALSPI=(3./4.)*CF*ULALPS_HIJING(Q2)/PARU(1)   
127           GOTO 100  
128         ENDIF   
129     
130 C...If too high cross-section, use harder cuts, or fail.    
131         IF(PARJ(152)+PARJ(153)+PARJ(154).GE.1) THEN 
132           IF(MSTJ(110).EQ.2.AND.CUT.GT.0.0499.AND.MSTJ(111).EQ.1.AND.   
133      &    PARJ(169).LT.0.99) THEN   
134             PARJ(169)=MIN(1.,1.2*PARJ(169)) 
135             Q2=PARJ(169)*ECM**2 
136             ALSPI=(3./4.)*CF*ULALPS_HIJING(Q2)/PARU(1) 
137             GOTO 100    
138           ELSEIF(MSTJ(110).EQ.2.AND.CUT.GT.0.0499) THEN 
139             CALL LUERRM_HIJING(26, 
140      &            '(LUXJET_HIJING:) no allowed y cut value for '/
141      $            /'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     
148 C...Scalar gluon (first order only).    
149       ELSE  
150         ALSPI=ULALPS_HIJING(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     
159 C...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_HIJING(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