Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pyfscr.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pyfscr.f
1 
2 C*********************************************************************
3 
4 C...PYFSCR
5 C...Performs colour annealing.
6 C...MSTP(95) : CR Type
7 C... = 1 : old cut-and-paste reconnections, handled in PYMIHK
8 C... = 2 : Type I(no gg loops); hadron-hadron only
9 C... = 3 : Type I(no gg loops); all beams
10 C... = 4 : Type II(gg loops) ; hadron-hadron only
11 C... = 5 : Type II(gg loops) ; all beams
12 C... = 6 : Type S ; hadron-hadron only
13 C... = 7 : Type S ; all beams
14 C...Types I and II are described in Sandhoff+Skands, in hep-ph/0604120.
15 C...Type S is driven by starting only from free triplets, not octets.
16 C...A string piece remains unchanged with probability
17 C... PKEEP = (1-PARP(78))**N
18 C...This scaling corresponds to each string piece having to go through
19 C...N other ones, each with probability PARP(78) for reconnection, where
20 C...N is here chosen simply as the number of multiple interactions,
21 C...for a rough scaling with the general level of activity.
22 
23  SUBROUTINE pyfscr(IP)
24 C...Double precision and integer declarations.
25  IMPLICIT DOUBLE PRECISION(a-h, o-z)
26  INTEGER pyk,pychge,pycomp
27 C...Commonblocks.
28  common/pyjets/n,npad,k(4000,5),p(4000,5),v(4000,5)
29  common/pydat1/mstu(200),paru(200),mstj(200),parj(200)
30  common/pypars/mstp(200),parp(200),msti(200),pari(200)
31  common/pydat2/kchg(500,4),pmas(500,4),parf(2000),vckm(4,4)
32  common/pyint1/mint(400),vint(400)
33 C...The common block of colour tags.
34  common/pyctag/nct,mct(4000,2)
35  SAVE /pyjets/,/pydat1/,/pydat2/,/pyint1/,/pyctag/,
36  &/pypars/
37 C...MCN: Temporary storage of new colour tags
38  DOUBLE PRECISION mcn(4000,2)
39 
40 C...Function to give four-product.
41  four(i,j)=p(i,4)*p(j,4)
42  & -p(i,1)*p(j,1)-p(i,2)*p(j,2)-p(i,3)*p(j,3)
43 
44 C...Check valid range of MSTP(95), local copy
45  IF (mstp(95).LE.1.OR.mstp(95).GE.8) RETURN
46  mstp95=mod(mstp(95),10)
47 C...Set whether CR allowed inside resonance systems or not
48 C...(not implemented yet)
49 C MRESCR=1
50 C IF (MSTP(95).GE.10) MRESCR=0
51 
52 C...Check whether colour tags already defined
53  IF (mint(33).EQ.0) THEN
54 C...Erase any existing colour tags for this event
55  DO 100 i=1,n
56  mct(i,1)=0
57  mct(i,2)=0
58  100 CONTINUE
59 C...Create colour tags for this event
60  DO 120 i=1,n
61  IF (k(i,1).EQ.3) THEN
62  DO 110 kcs=4,5
63  kcsin=kcs
64  IF (mct(i,kcsin-3).EQ.0) THEN
65  CALL pycttr(i,kcsin,i)
66  ENDIF
67  110 CONTINUE
68  ENDIF
69  120 CONTINUE
70 C...Instruct PYPREP to use colour tags
71  mint(33)=1
72  ENDIF
73 
74 C...For MSTP(95) even, only apply to hadron-hadron
75  IF (mod(mstp(95),2).EQ.0) THEN
76  ka1=iabs(mint(11))
77  ka2=iabs(mint(12))
78  IF (ka1.LT.100.OR.ka2.LT.100) goto 9999
79  ENDIF
80 
81 C...Initialize new tag array (but do not delete old yet)
82  lct=nct
83  DO 130 i=max(1,ip),n
84  mcn(i,1)=0
85  mcn(i,2)=0
86  130 CONTINUE
87 
88 C...For each final-state dipole, check whether string should be
89 C...preserved.
90  DO 150 ict=1,nct
91  ic=0
92  ia=0
93  DO 140 i=max(1,ip),n
94  IF (k(i,1).EQ.3.AND.mct(i,1).EQ.ict) ic=i
95  IF (k(i,1).EQ.3.AND.mct(i,2).EQ.ict) ia=i
96  140 CONTINUE
97  IF (ic.NE.0.AND.ia.NE.0) THEN
98 C...Chiefly consider large strings.
99  pkeep=(1d0-parp(78))**mint(31)
100  IF (pyr(0).LE.pkeep) THEN
101  lct=lct+1
102  mcn(ic,1)=lct
103  mcn(ia,2)=lct
104  ENDIF
105  ENDIF
106  150 CONTINUE
107 
108 C...Loop over event record, starting from IP
109 C...(Ignore junctions for now.)
110  nloop=0
111  160 nloop=nloop+1
112  mcimax=0
113  mcjmax=0
114  rlmax=0d0
115  ilmax=0
116  jlmax=0
117  DO 230 i=max(1,ip),n
118  IF (k(i,1).NE.3) goto 230
119 C...Check colour charge
120  mci=kchg(pycomp(k(i,2)),2)*isign(1,k(i,2))
121  IF (mci.EQ.0) goto 230
122 C...For Seattle algorithm, only start from partons with one dangling
123 C...colour tag
124  IF (mstp(95).EQ.6.OR.mstp(95).EQ.7) THEN
125  IF (mci.EQ.2.AND.mcn(i,1).EQ.0.AND.mcn(i,2).EQ.0) goto 230
126  ENDIF
127 C... Find optimal partner
128  jlopt=0
129  mcjopt=0
130  mbropt=0
131  mggopt=0
132  rlopt=1d19
133 C...Loop over I colour/anticolour, check whether already connected
134  170 DO 220 icl=1,2
135  IF (mcn(i,icl).NE.0) goto 220
136  IF (icl.EQ.1.AND.mci.EQ.-1) goto 220
137  IF (icl.EQ.2.AND.mci.EQ.1) goto 220
138 C...Check whether this is a dangling colour tag (ie to junction!)
139  ifound=0
140  DO 180 j=max(1,ip),n
141  IF (k(j,1).EQ.3.AND.mct(j,3-icl).EQ.mct(i,icl)) ifound=1
142  180 CONTINUE
143  IF (ifound.EQ.0) goto 220
144  DO 210 j=max(1,ip),n
145  IF (k(j,1).NE.3.OR.i.EQ.j) goto 210
146 C...Do not make direct connections between partons in same Beam Remnant
147  mbrstr=0
148  IF (k(i,3).LE.2.AND.k(j,3).LE.2.AND.k(i,3).EQ.k(j,3))
149  & mbrstr=1
150 C...Check colour charge
151  mcj=kchg(pycomp(k(j,2)),2)*isign(1,k(j,2))
152  IF (mcj.EQ.0.OR.(mcj.EQ.mci.AND.mci.NE.2)) goto 210
153 C...Check for gluon loops
154  mggstr=0
155  IF (mcj.EQ.2.AND.mci.EQ.2) THEN
156  icla=3-icl
157  IF (mcn(i,icla).EQ.mcn(j,icl).AND.mstp(95).LE.3.AND.
158  & mcn(i,icla).NE.0) mggstr=1
159  ENDIF
160 C...Loop over J colour/anticolour, check whether already connected
161  DO 200 jcl=1,2
162  IF (mcn(j,jcl).NE.0) goto 200
163  IF (jcl.EQ.icl) goto 200
164  IF (jcl.EQ.1.AND.mcj.EQ.-1) goto 200
165  IF (jcl.EQ.2.AND.mcj.EQ.1) goto 200
166 C...Check whether this is a dangling colour tag (ie to junction!)
167  ifound=0
168  DO 190 j2=max(1,ip),n
169  IF (k(j2,1).EQ.3.AND.mct(j2,3-jcl).EQ.mct(j,jcl))
170  & ifound=1
171  190 CONTINUE
172  IF (ifound.EQ.0) goto 200
173 C...Save connection with smallest lambda measure
174 C...If best so far was a BR string and this is not, also save.
175 C...If best so far was a gg string and this is not, also save.
176  rl=four(i,j)
177  IF (rl.LT.rlopt.OR.(rl.EQ.rlopt.AND.pyr(0).LE.0.5d0)
178  & .OR.(mbropt.EQ.1.AND.mbrstr.EQ.0)
179  & .OR.(mggopt.EQ.1.AND.mggstr.EQ.0)) THEN
180  rlopt=rl
181  jlopt=j
182  icopt=icl
183  jcopt=jcl
184  mcjopt=mcj
185  mbropt=mbrstr
186  mggopt=mggstr
187  ENDIF
188  200 CONTINUE
189  210 CONTINUE
190  220 CONTINUE
191  IF (jlopt.NE.0) THEN
192 C...Save pair with largest RLOPT so far
193  IF (rlopt.GE.rlmax) THEN
194  rlmax=rlopt
195  ilmax=i
196  jlmax=jlopt
197  icmax=icopt
198  jcmax=jcopt
199  mcjmax=mcjopt
200  mcimax=mci
201  ENDIF
202  ENDIF
203  230 CONTINUE
204 C...Save and iterate
205  IF (ilmax.GT.0) THEN
206  lct=lct+1
207  mcn(ilmax,icmax)=lct
208  mcn(jlmax,jcmax)=lct
209  IF (nloop.LE.2*(n-ip)) THEN
210  goto 160
211  ELSE
212  CALL pyerrm(31,' PYFSCR: infinite loop in color annealing')
213  CALL pystop(11)
214  ENDIF
215  ELSE
216 C...Save and exit. First check for leftover gluon(s)
217  DO 260 i=max(1,ip),n
218 C...Check colour charge
219  mci=kchg(pycomp(k(i,2)),2)*isign(1,k(i,2))
220  IF (k(i,1).NE.3.OR.mci.NE.2) goto 260
221  IF(mcn(i,1).EQ.0.AND.mcn(i,2).EQ.0) THEN
222 C...Decide where to put left-over gluon (minimal insertion)
223  ilmax=0
224  rlmax=1d19
225  DO 250 kct=nct+1,lct
226  DO 240 it=max(1,ip),n
227  IF (it.EQ.i.OR.k(it,1).NE.3) goto 240
228  IF (mcn(it,1).EQ.kct) ic=it
229  IF (mcn(it,2).EQ.kct) ia=it
230  240 CONTINUE
231  rl=four(ic,i)*four(ia,i)
232  IF (rl.LT.rlmax) THEN
233  rlmax=rl
234  icmax=ic
235  iamax=ia
236  ENDIF
237  250 CONTINUE
238  lct=lct+1
239  mcn(i,1)=mcn(icmax,1)
240  mcn(i,2)=lct
241  mcn(icmax,1)=lct
242  ENDIF
243  260 CONTINUE
244  DO 270 i=max(1,ip),n
245 C...Do not erase parton shower colour history
246  IF (k(i,1).NE.3) goto 270
247 C...Check colour charge
248  mci=kchg(pycomp(k(i,2)),2)*isign(1,k(i,2))
249  IF (mci.EQ.0) goto 270
250  IF (mcn(i,1).NE.0) mct(i,1)=mcn(i,1)
251  IF (mcn(i,2).NE.0) mct(i,2)=mcn(i,2)
252  270 CONTINUE
253  ENDIF
254 
255  9999 RETURN
256  END