]> git.uio.no Git - u/mrichter/AliRoot.git/blame - ISAJET/code/qcdt.F
Update rawdata format for trigger (Christian)
[u/mrichter/AliRoot.git] / ISAJET / code / qcdt.F
CommitLineData
0795afa3 1#include "isajet/pilot.h"
2 SUBROUTINE QCDT(J)
3C
4C Auxiliary routine for QCDJET. Calculate ZC and store in
5C ZZC(J). Generate new mass with ZC and store in PJSET(5,J).
6C
7C Must include 1/2 symmetry factor in GAMGG. No fix is needed
8C in QCDZ since GAMGG+2*GAMQQ is used as the normalization.
9C
10C Include GM, W+, W-, and Z0 radiation.
11C
12C Ver 7.20: Anomalous dimensions were coded incorrectly!
13C
14#if defined(CERNLIB_IMPNONE)
15 IMPLICIT NONE
16#endif
17#include "isajet/itapes.inc"
18#include "isajet/jetset.inc"
19#include "isajet/jwork.inc"
20#include "isajet/qcdpar.inc"
21#include "isajet/const.inc"
22#include "isajet/wcon.inc"
23#include "isajet/primar.inc"
24C
25 REAL AM0,AM1,AM2,AMASS,T0,T1,T2,ZC,B0,GAMEW,GAMQQ,GAMGG,GAM,GAMZC
26 REAL AM1W,AM2W,T1W,T2W,TERM,GB,PROB,RANF,RND,POW,AMNEW,AMOLD
27 REAL POWEW
28 INTEGER J,JTLV1,NF,IQ,JTABS,IW,JT0,JT1,IFL1,I
29 INTEGER JWTYPE(4)
30 DATA JWTYPE/10,80,-80,90/
31C
32C Set ZC = 0 and return for W+- or Z0
33C
34 JTABS=IABS(JTYPE(J))
35 IF(JTABS.GE.80.AND.JTABS.LE.90) THEN
36 ZZC(J)=0.
37 RETURN
38 ENDIF
39C
40C Calculate ZC
41C
42 AM0=PJSET(5,J)
43 JTLV1=JTYPE(J)
44 AM1=AMASS(JTLV1)+CUTJET
45 AM2=CUTJET
46 IF(AM1+AM2.GE.AM0) GO TO 300
47 T0=AM0**2
48 T1=AM1**2
49 T2=AM2**2
50 ZC=(T0-T1+T2-SQRT((T0-T1-T2)**2-4*T1*T2))/(2*T0)
51 ZZC(J)=ZC
52C Count light fermions
53 NF=3
54 DO 110 IQ=4,6
55 IF(AM0.LT.2*AMASS(IQ)) GO TO 120
56 NF=NF+1
57110 CONTINUE
58120 B0=11.-2.*NF/3.
59C
60C Calculate GAMMA(ZC) and GAMEW for quarks
61C
62 GAMEW=0.
63C
64C Initial gluon
65 IF(JTABS.EQ.9) THEN
66 GAMQQ=(1.-2.*ZC)*(1.-ZC*(1.-ZC))/3.
67 GAMGG=12.*ALOG((1.-ZC)/ZC)-9.*(1.-2.*ZC)-6.*GAMQQ
68 GAMGG=0.5*GAMGG
69 GAM=GAMGG+NF*GAMQQ
70C
71C Initial quark
72 ELSEIF(JTABS.LT.9) THEN
73 GAMZC=2.*ALOG((1-ZC)/ZC)-1.5*(1.-2.*ZC)
74 GAM=4./3.*GAMZC
75 GAMEW=ALFA/(2.*PI)*AQ(JTABS,1)**2*GAMZC
76 IF(AM0.GT.WMASS(4)) THEN
77 DO 130 IW=2,4
78 JT0=2*IABS(JTYPE(J))
79 IF(JTYPE(J).LT.0) JT0=JT0+1
80 JT1=MATCH(JT0,IW)
81 IF(JT1.EQ.0) GO TO 130
82 JT1=MATCH(JT1,4)
83 IFL1=JT1/2
84 AM1W=AMASS(IFL1)
85 AM2W=AMASS(JWTYPE(IW))
86 IF(AM1W+AM2W.GE.AM0) GO TO 130
87 T1W=AM1W**2
88 T2W=AM2W**2
89 ZC=(T0-T1W+T2W-SQRT((T0-T1W-T2W)**2-4*T1W*T2W))/(2*T0)
90 GAMZC=2.*ALOG((1-ZC)/ZC)-1.5*(1.-2.*ZC)
91 TERM=(AQ(JTABS,IW)**2+BQ(JTABS,IW)**2)*GAMZC
92 GAMEW=GAMEW+ALFA/(2.*PI)*TERM
93130 CONTINUE
94 ENDIF
95C
96C Initial diquark
97 ELSEIF(MOD(JTABS,100).EQ.0) THEN
98 GAM=8./3.*ALOG((1-ZC)/ZC)-2.*(1.-2.*ZC)
99C
100C Initial gluino
101 ELSEIF(JTABS.EQ.29) THEN
102 GAM=6.*ALOG((1.-ZC)/ZC)-9./2.*(1.-2.*ZC)
103C
104C Initial squark
105 ELSEIF(JTABS.GT.20.AND.JTABS.LT.29) THEN
106 GAM = 8./3.*(ALOG((1.-ZC)/ZC)-(1.-2.*ZC))
107 ENDIF
108C
109C Generate new mass
110C
111 GB=2*GAM/B0
112 PROB=(ALOG(AM1/ALAM)/ALOG(AM0/ALAM))**GB
113 PROB=PROB*(AM1/AM0)**(2.*GAMEW)
114 IF(PROB.GT.RANF()) GO TO 300
115 RND=RANF()
116 POW=(1.-(1.-PROB)*RND)**(1./GB)
117 AMNEW=ALAM*(AM0/ALAM)**POW
118C For quark, add effect of GM, W+-, Z0 radiation
119 IF(IABS(JTYPE(J)).LT.9) THEN
120 DO 200 I=1,NTRIES
121 AMOLD=AMNEW
122 POWEW=POW/((AMOLD/AM0)**(2.*GAMEW))**(1./GB)
123 AMNEW=ALAM*(AM0/ALAM)**POWEW
124 IF(ABS(AMNEW-AMOLD).LT.0.001*AMOLD) GO TO 210
125200 CONTINUE
126 ENDIF
127210 IF(AMNEW.LE.AM1) GO TO 300
128 PJSET(5,J)=AMNEW
129 RETURN
130C
131C Final parton -- set mass to physical value
132C
133300 PJSET(5,J)=AM1-CUTJET
134 JDCAY(J)=0
135 RETURN
136 END