Back to home page

sPhenix code displayed by LXR

 
 

    


File indexing completed on 2025-08-05 08:15:44

0001     
0002 C*********************************************************************  
0003     
0004       SUBROUTINE LUXJET(ECM,NJET,CUT)   
0005     
0006 C...Purpose: to select number of jets in matrix element approach.   
0007       COMMON/LUDAT1/MSTU(200),PARU(200),MSTJ(200),PARJ(200) 
0008       SAVE /LUDAT1/ 
0009       DIMENSION ZHUT(5) 
0010     
0011 C...Relative three-jet rate in Zhu second order parametrization.    
0012       DATA ZHUT/3.0922, 6.2291, 7.4782, 7.8440, 8.2560/ 
0013     
0014 C...Trivial result for two-jets only, including parton shower.  
0015       IF(MSTJ(101).EQ.0.OR.MSTJ(101).EQ.5) THEN 
0016         CUT=0.  
0017     
0018 C...QCD and Abelian vector gluon theory: Q^2 for jet rate and R.    
0019       ELSEIF(MSTJ(109).EQ.0.OR.MSTJ(109).EQ.2) THEN 
0020         CF=4./3.    
0021         IF(MSTJ(109).EQ.2) CF=1.    
0022         IF(MSTJ(111).EQ.0) THEN 
0023           Q2=ECM**2 
0024           Q2R=ECM**2    
0025         ELSEIF(MSTU(111).EQ.0) THEN 
0026           PARJ(169)=MIN(1.,PARJ(129))   
0027           Q2=PARJ(169)*ECM**2   
0028           PARJ(168)=MIN(1.,MAX(PARJ(128),EXP(-12.*PARU(1)/  
0029      &    ((33.-2.*MSTU(112))*PARU(111))))) 
0030           Q2R=PARJ(168)*ECM**2  
0031         ELSE    
0032           PARJ(169)=MIN(1.,MAX(PARJ(129),(2.*PARU(112)/ECM)**2))    
0033           Q2=PARJ(169)*ECM**2   
0034           PARJ(168)=MIN(1.,MAX(PARJ(128),PARU(112)/ECM, 
0035      &    (2.*PARU(112)/ECM)**2))   
0036           Q2R=PARJ(168)*ECM**2  
0037         ENDIF   
0038     
0039 C...alpha_strong for R and R itself.    
0040         ALSPI=(3./4.)*CF*ULALPS(Q2R)/PARU(1)    
0041         IF(IABS(MSTJ(101)).EQ.1) THEN   
0042           RQCD=1.+ALSPI 
0043         ELSEIF(MSTJ(109).EQ.0) THEN 
0044           RQCD=1.+ALSPI+(1.986-0.115*MSTU(118))*ALSPI**2    
0045           IF(MSTJ(111).EQ.1) RQCD=MAX(1.,RQCD+(33.-2.*MSTU(112))/12.*   
0046      &    LOG(PARJ(168))*ALSPI**2)  
0047         ELSE    
0048           RQCD=1.+ALSPI-(3./32.+0.519*MSTU(118))*(4.*ALSPI/3.)**2   
0049         ENDIF   
0050     
0051 C...alpha_strong for jet rate. Initial value for y cut. 
0052         ALSPI=(3./4.)*CF*ULALPS(Q2)/PARU(1) 
0053         CUT=MAX(0.001,PARJ(125),(PARJ(126)/ECM)**2) 
0054         IF(IABS(MSTJ(101)).LE.1.OR.(MSTJ(109).EQ.0.AND.MSTJ(111).EQ.0)) 
0055      &  CUT=MAX(CUT,EXP(-SQRT(0.75/ALSPI))/2.)  
0056         IF(MSTJ(110).EQ.2) CUT=MAX(0.01,MIN(0.05,CUT))  
0057     
0058 C...Parametrization of first order three-jet cross-section. 
0059   100   IF(MSTJ(101).EQ.0.OR.CUT.GE.0.25) THEN  
0060           PARJ(152)=0.  
0061         ELSE    
0062           PARJ(152)=(2.*ALSPI/3.)*((3.-6.*CUT+2.*LOG(CUT))* 
0063      &    LOG(CUT/(1.-2.*CUT))+(2.5+1.5*CUT-6.571)*(1.-3.*CUT)+ 
0064      &    5.833*(1.-3.*CUT)**2-3.894*(1.-3.*CUT)**3+    
0065      &    1.342*(1.-3.*CUT)**4)/RQCD    
0066           IF(MSTJ(109).EQ.2.AND.(MSTJ(101).EQ.2.OR.MSTJ(101).LE.-2))    
0067      &    PARJ(152)=0.  
0068         ENDIF   
0069     
0070 C...Parametrization of second order three-jet cross-section.    
0071         IF(IABS(MSTJ(101)).LE.1.OR.MSTJ(101).EQ.3.OR.MSTJ(109).EQ.2.OR. 
0072      &  CUT.GE.0.25) THEN   
0073           PARJ(153)=0.  
0074         ELSEIF(MSTJ(110).LE.1) THEN 
0075           CT=LOG(1./CUT-2.) 
0076           PARJ(153)=ALSPI**2*CT**2*(2.419+0.5989*CT+0.6782*CT**2-   
0077      &    0.2661*CT**3+0.01159*CT**4)/RQCD  
0078     
0079 C...Interpolation in second/first order ratio for Zhu parametrization.  
0080         ELSEIF(MSTJ(110).EQ.2) THEN 
0081           IZA=0 
0082           DO 110 IY=1,5 
0083   110     IF(ABS(CUT-0.01*IY).LT.0.0001) IZA=IY 
0084           IF(IZA.NE.0) THEN 
0085             ZHURAT=ZHUT(IZA)    
0086           ELSE  
0087             IZ=100.*CUT 
0088             ZHURAT=ZHUT(IZ)+(100.*CUT-IZ)*(ZHUT(IZ+1)-ZHUT(IZ)) 
0089           ENDIF 
0090           PARJ(153)=ALSPI*PARJ(152)*ZHURAT  
0091         ENDIF   
0092     
0093 C...Shift in second order three-jet cross-section with optimized Q^2.   
0094         IF(MSTJ(111).EQ.1.AND.IABS(MSTJ(101)).GE.2.AND.MSTJ(101).NE.3.  
0095      &  AND.CUT.LT.0.25) PARJ(153)=PARJ(153)+(33.-2.*MSTU(112))/12.*    
0096      &  LOG(PARJ(169))*ALSPI*PARJ(152)  
0097     
0098 C...Parametrization of second order four-jet cross-section. 
0099         IF(IABS(MSTJ(101)).LE.1.OR.CUT.GE.0.125) THEN   
0100           PARJ(154)=0.  
0101         ELSE    
0102           CT=LOG(1./CUT-5.) 
0103           IF(CUT.LE.0.018) THEN 
0104             XQQGG=6.349-4.330*CT+0.8304*CT**2   
0105             IF(MSTJ(109).EQ.2) XQQGG=(4./3.)**2*(3.035-2.091*CT+    
0106      &      0.4059*CT**2)   
0107             XQQQQ=1.25*(-0.1080+0.01486*CT+0.009364*CT**2)  
0108             IF(MSTJ(109).EQ.2) XQQQQ=8.*XQQQQ   
0109           ELSE  
0110             XQQGG=-0.09773+0.2959*CT-0.2764*CT**2+0.08832*CT**3 
0111             IF(MSTJ(109).EQ.2) XQQGG=(4./3.)**2*(-0.04079+0.1340*CT-    
0112      &      0.1326*CT**2+0.04365*CT**3) 
0113             XQQQQ=1.25*(0.003661-0.004888*CT-0.001081*CT**2+0.002093*   
0114      &      CT**3)  
0115             IF(MSTJ(109).EQ.2) XQQQQ=8.*XQQQQ   
0116           ENDIF 
0117           PARJ(154)=ALSPI**2*CT**2*(XQQGG+XQQQQ)/RQCD   
0118           PARJ(155)=XQQQQ/(XQQGG+XQQQQ) 
0119         ENDIF   
0120     
0121 C...If negative three-jet rate, change y' optimization parameter.   
0122         IF(MSTJ(111).EQ.1.AND.PARJ(152)+PARJ(153).LT.0..AND.    
0123      &  PARJ(169).LT.0.99) THEN 
0124           PARJ(169)=MIN(1.,1.2*PARJ(169))   
0125           Q2=PARJ(169)*ECM**2   
0126           ALSPI=(3./4.)*CF*ULALPS(Q2)/PARU(1)   
0127           GOTO 100  
0128         ENDIF   
0129     
0130 C...If too high cross-section, use harder cuts, or fail.    
0131         IF(PARJ(152)+PARJ(153)+PARJ(154).GE.1) THEN 
0132           IF(MSTJ(110).EQ.2.AND.CUT.GT.0.0499.AND.MSTJ(111).EQ.1.AND.   
0133      &    PARJ(169).LT.0.99) THEN   
0134             PARJ(169)=MIN(1.,1.2*PARJ(169)) 
0135             Q2=PARJ(169)*ECM**2 
0136             ALSPI=(3./4.)*CF*ULALPS(Q2)/PARU(1) 
0137             GOTO 100    
0138           ELSEIF(MSTJ(110).EQ.2.AND.CUT.GT.0.0499) THEN 
0139             CALL LUERRM(26, 
0140      &      '(LUXJET:) no allowed y cut value for Zhu parametrization') 
0141           ENDIF 
0142           CUT=0.26*(4.*CUT)**(PARJ(152)+PARJ(153)+PARJ(154))**(-1./3.)  
0143           IF(MSTJ(110).EQ.2) CUT=MAX(0.01,MIN(0.05,CUT))    
0144           GOTO 100  
0145         ENDIF   
0146     
0147 C...Scalar gluon (first order only).    
0148       ELSE  
0149         ALSPI=ULALPS(ECM**2)/PARU(1)    
0150         CUT=MAX(0.001,PARJ(125),(PARJ(126)/ECM)**2,EXP(-3./ALSPI))  
0151         PARJ(152)=0.    
0152         IF(CUT.LT.0.25) PARJ(152)=(ALSPI/3.)*((1.-2.*CUT)*  
0153      &  LOG((1.-2.*CUT)/CUT)+0.5*(9.*CUT**2-1.))    
0154         PARJ(153)=0.    
0155         PARJ(154)=0.    
0156       ENDIF 
0157     
0158 C...Select number of jets.  
0159       PARJ(150)=CUT 
0160       IF(MSTJ(101).EQ.0.OR.MSTJ(101).EQ.5) THEN 
0161         NJET=2  
0162       ELSEIF(MSTJ(101).LE.0) THEN   
0163         NJET=MIN(4,2-MSTJ(101)) 
0164       ELSE  
0165         RNJ=RLU(0)  
0166         NJET=2  
0167         IF(PARJ(152)+PARJ(153)+PARJ(154).GT.RNJ) NJET=3 
0168         IF(PARJ(154).GT.RNJ) NJET=4 
0169       ENDIF 
0170     
0171       RETURN    
0172       END