]> git.uio.no Git - u/mrichter/AliRoot.git/blame - HIJING/hijing1_36/jetini.F
Typo in the calculation of procetile-target distance is corrected
[u/mrichter/AliRoot.git] / HIJING / hijing1_36 / jetini.F
CommitLineData
e74335a4 1* $Id$
2C
3C
4C
5C
6C
7 SUBROUTINE JETINI(JP,JT,I_TRIG)
8C*******Initialize PYTHIA for jet production**********************
9C I_TRIG=0: for normal processes
10C I_TRIG=1: for triggered processes
11C JP: sequence number of the projectile
12C JT: sequence number of the target
13C For A+A collisions, one has to initilize pythia
14C separately for each type of collisions, pp, pn,np and nn,
15C or hp and hn for hA collisions. In this subroutine we use the following
16C catalogue for different type of collisions:
17C h+h: h+h (I_TYPE=1)
18C h+A: h+p (I_TYPE=1), h+n (I_TYPE=2)
19C A+h: p+h (I_TYPE=1), n+h (I_TYPE=2)
20C A+A: p+p (I_TYPE=1), p+n (I_TYPE=2), n+p (I_TYPE=3), n+n (I_TYPE=4)
21C*****************************************************************
22 CHARACTER BEAM*16,TARG*16
23 DIMENSION XSEC0(8,0:200),COEF0(8,200,20),INI(8),
24 & MINT44(8),MINT45(8)
25#include "hijcrdn.inc"
26#include "hiparnt.inc"
27#include "histrng.inc"
28#include "hipyint.inc"
29C
30#include "ludat1_hijing.inc"
31#include "ludat3_hijing.inc"
32#include "pysubs_hijing.inc"
33#include "pypars_hijing.inc"
34#include "pyint1_hijing.inc"
35#include "pyint2_hijing.inc"
36#include "pyint5_hijing.inc"
37 DATA INI/8*0/I_LAST/-1/
38 SAVE
39C
57367a3d 40
e74335a4 41 IHNT2(11)=JP
42 IHNT2(12)=JT
43 IF(IHNT2(5).NE.0 .AND. IHNT2(6).NE.0) THEN
44 I_TYPE=1
45 ELSE IF(IHNT2(5).NE.0 .AND. IHNT2(6).EQ.0) THEN
46 I_TYPE=1
47 IF(NFT(JT,4).EQ.2112) I_TYPE=2
48 ELSE IF(IHNT2(5).EQ.0 .AND. IHNT2(6).NE.0) THEN
49 I_TYPE=1
50 IF(NFP(JP,4).EQ.2112) I_TYPE=2
51 ELSE
52 IF(NFP(JP,4).EQ.2212 .AND. NFT(JT,4).EQ.2212) THEN
53 I_TYPE=1
54 ELSE IF(NFP(JP,4).EQ.2212 .AND. NFT(JT,4).EQ.2112) THEN
55 I_TYPE=2
56 ELSE IF(NFP(JP,4).EQ.2112 .AND. NFT(JT,4).EQ.2212) THEN
57 I_TYPE=3
58 ELSE
59 I_TYPE=4
60 ENDIF
61 ENDIF
62c
63 IF(I_TRIG.NE.0) GO TO 160
64 IF(I_TRIG.EQ.I_LAST) GO TO 150
65 MSTP(2)=2
66c ********second order running alpha_strong
67 MSTP(33)=1
68 PARP(31)=HIPR1(17)
69C ********inclusion of K factor
70 MSTP(51)=3
71C ********Duke-Owens set 1 structure functions
72 MSTP(61)=1
73C ********INITIAL STATE RADIATION
74 MSTP(71)=1
75C ********FINAL STATE RADIATION
76 IF(IHPR2(2).EQ.0.OR.IHPR2(2).EQ.2) MSTP(61)=0
77 IF(IHPR2(2).EQ.0.OR.IHPR2(2).EQ.1) MSTP(71)=0
78c
79 MSTP(81)=0
80C ******** NO MULTIPLE INTERACTION
81 MSTP(82)=1
82C *******STRUCTURE OF MUTLIPLE INTERACTION
83 MSTP(111)=0
84C ********frag off(have to be done by local call)
85 IF(IHPR2(10).EQ.0) MSTP(122)=0
86C ********No printout of initialization information
87 PARP(81)=HIPR1(8)
88 CKIN(5)=HIPR1(8)
89 CKIN(3)=HIPR1(8)
90 CKIN(4)=HIPR1(9)
91 IF(HIPR1(9).LE.HIPR1(8)) CKIN(4)=-1.0
92 CKIN(9)=-10.0
93 CKIN(10)=10.0
94 MSEL=0
95 DO 100 ISUB=1,200
96 MSUB(ISUB)=0
97 100 CONTINUE
98 MSUB(11)=1
99 MSUB(12)=1
100 MSUB(13)=1
101 MSUB(28)=1
102 MSUB(53)=1
103 MSUB(68)=1
104 MSUB(81)=1
105 MSUB(82)=1
106 DO 110 J=1,MIN(8,MDCY(21,3))
107 110 MDME(MDCY(21,2)+J-1,1)=0
108 ISEL=4
109 IF(HINT1(1).GE.20.0 .and. IHPR2(18).EQ.1) ISEL=5
110 MDME(MDCY(21,2)+ISEL-1,1)=1
111C ********QCD subprocesses
112 MSUB(14)=1
113 MSUB(18)=1
114 MSUB(29)=1
115C ******* direct photon production
116 150 IF(INI(I_TYPE).NE.0) GO TO 800
117 GO TO 400
118C
119C *****triggered subprocesses, jet, photon, heavy quark and DY
120C
121 160 I_TYPE=4+I_TYPE
122 IF(I_TRIG.EQ.I_LAST) GO TO 260
123 PARP(81)=ABS(HIPR1(10))-0.25
124 CKIN(5)=ABS(HIPR1(10))-0.25
125 CKIN(3)=ABS(HIPR1(10))-0.25
126 CKIN(4)=ABS(HIPR1(10))+0.25
127 IF(HIPR1(10).LT.HIPR1(8)) CKIN(4)=-1.0
128c
129 MSEL=0
130 DO 101 ISUB=1,200
131 MSUB(ISUB)=0
132 101 CONTINUE
133 IF(IHPR2(3).EQ.1) THEN
134 MSUB(11)=1
135 MSUB(12)=1
136 MSUB(13)=1
137 MSUB(28)=1
138 MSUB(53)=1
139 MSUB(68)=1
140 MSUB(81)=1
141 MSUB(82)=1
142 MSUB(14)=1
143 MSUB(18)=1
144 MSUB(29)=1
145 DO 102 J=1,MIN(8,MDCY(21,3))
146 102 MDME(MDCY(21,2)+J-1,1)=0
147 ISEL=4
148 IF(HINT1(1).GE.20.0 .and. IHPR2(18).EQ.1) ISEL=5
149 MDME(MDCY(21,2)+ISEL-1,1)=1
150C ********QCD subprocesses
151 ELSE IF(IHPR2(3).EQ.2) THEN
152 MSUB(14)=1
153 MSUB(18)=1
154 MSUB(29)=1
155C ********Direct photon production
156c q+qbar->g+gamma,q+qbar->gamma+gamma, q+g->q+gamma
157 ELSE IF(IHPR2(3).EQ.3) THEN
158 CKIN(3)=MAX(0.0,HIPR1(10))
159 CKIN(5)=HIPR1(8)
160 PARP(81)=HIPR1(8)
161 MSUB(81)=1
162 MSUB(82)=1
163 DO 105 J=1,MIN(8,MDCY(21,3))
164 105 MDME(MDCY(21,2)+J-1,1)=0
165 ISEL=4
166 IF(HINT1(1).GE.20.0 .and. IHPR2(18).EQ.1) ISEL=5
167 MDME(MDCY(21,2)+ISEL-1,1)=1
168C **********Heavy quark production
169 ENDIF
170260 IF(INI(I_TYPE).NE.0) GO TO 800
171C
172C
173400 INI(I_TYPE)=1
174 IF(IHPR2(10).EQ.0) MSTP(122)=0
175 IF(NFP(JP,4).EQ.2212) THEN
176 BEAM='P'
177 ELSE IF(NFP(JP,4).EQ.-2212) THEN
178 BEAM='P~'
179 ELSE IF(NFP(JP,4).EQ.2112) THEN
180 BEAM='N'
181 ELSE IF(NFP(JP,4).EQ.-2112) THEN
182 BEAM='N~'
183 ELSE IF(NFP(JP,4).EQ.211) THEN
184 BEAM='PI+'
185 ELSE IF(NFP(JP,4).EQ.-211) THEN
186 BEAM='PI-'
187 ELSE IF(NFP(JP,4).EQ.321) THEN
188 BEAM='PI+'
189 ELSE IF(NFP(JP,4).EQ.-321) THEN
190 BEAM='PI-'
191 ELSE
192 WRITE(6,*) 'unavailable beam type', NFP(JP,4)
193 ENDIF
194 IF(NFT(JT,4).EQ.2212) THEN
195 TARG='P'
196 ELSE IF(NFT(JT,4).EQ.-2212) THEN
197 TARG='P~'
198 ELSE IF(NFT(JT,4).EQ.2112) THEN
199 TARG='N'
200 ELSE IF(NFT(JT,4).EQ.-2112) THEN
201 TARG='N~'
202 ELSE IF(NFT(JT,4).EQ.211) THEN
203 TARG='PI+'
204 ELSE IF(NFT(JT,4).EQ.-211) THEN
205 TARG='PI-'
206 ELSE IF(NFT(JT,4).EQ.321) THEN
207 TARG='PI+'
208 ELSE IF(NFT(JT,4).EQ.-321) THEN
209 TARG='PI-'
210 ELSE
211 WRITE(6,*) 'unavailable target type', NFT(JT,4)
212 ENDIF
213C
214 IHNT2(16)=1
215C ******************indicate for initialization use when
216C structure functions are called in PYTHIA
217C
218 CALL PYINIT_HIJING('CMS',BEAM,TARG,HINT1(1))
219 MINT4=MINT(44)
220 MINT5=MINT(45)
221 MINT44(I_TYPE)=MINT(44)
222 MINT45(I_TYPE)=MINT(45)
223 ATXS(0)=XSEC(0,1)
224 XSEC0(I_TYPE,0)=XSEC(0,1)
225 DO 500 I=1,200
226 ATXS(I)=XSEC(I,1)
227 XSEC0(I_TYPE,I)=XSEC(I,1)
228 DO 500 J=1,20
229 ATCO(I,J)=COEF(I,J)
230 COEF0(I_TYPE,I,J)=COEF(I,J)
231500 CONTINUE
232C
233 IHNT2(16)=0
234C
57367a3d 235 I_LAST=I_TRIG
e74335a4 236 RETURN
237C ********Store the initialization information for
238C late use
239C
240C
241800 MINT(44)=MINT44(I_TYPE)
242 MINT(45)=MINT45(I_TYPE)
243 MINT4=MINT(44)
244 MINT5=MINT(45)
245 XSEC(0,1)=XSEC0(I_TYPE,0)
246 ATXS(0)=XSEC(0,1)
247 DO 900 I=1,200
248 XSEC(I,1)=XSEC0(I_TYPE,I)
249 ATXS(I)=XSEC(I,1)
250 DO 900 J=1,20
251 COEF(I,J)=COEF0(I_TYPE,I,J)
252 ATCO(I,J)=COEF(I,J)
253900 CONTINUE
254 I_LAST=I_TRIG
255 MINT(11)=NFP(JP,4)
256 MINT(12)=NFT(JT,4)
257 RETURN
258 END