Merge lp:~maddevelopers/mg5amcnlo/fix_color_resonances into lp:~madteam/mg5amcnlo/trunk

Proposed by Johan Alwall
Status: Merged
Merged at revision: 198
Proposed branch: lp:~maddevelopers/mg5amcnlo/fix_color_resonances
Merge into: lp:~madteam/mg5amcnlo/trunk
Diff against target: 730 lines (+511/-86)
3 files modified
Template/SubProcesses/addmothers.f (+504/-84)
UpdateNotes.txt (+5/-0)
madgraph/VERSION (+2/-2)
To merge this branch: bzr merge lp:~maddevelopers/mg5amcnlo/fix_color_resonances
Reviewer Review Type Date Requested Status
Valentin Hirschi Needs Information
Olivier Mattelaer Approve
Review via email: mp+87184@code.launchpad.net

Description of the change

Ensure that intermediate resonances in the presence of triplet epsilon color operators downstream from the resonances will still get the correct color indices, based on the color of the initial state particles. This is further complicated by the possibility of multiparticle vertices, and necessitated a slightly modified treatment of the color for multiparticle vertices. All modifications are in addmothers.f.

To post a comment you must log in.
199. By Johan Alwall

Fixed stupid typos in addmothers.f

200. By Johan Alwall

Fixed octet t-channel, which was not fixed correctly before

201. By Johan Alwall

Almost finished addmothers, just need to remove the check that min and max are different

202. By Johan Alwall

I think I finally nailed it (at least no problems left with the process p p > t t~ j QED=2 QCD=3, t > b~ u~ mu+, t~ > b~ w- and vice versa)

203. By Johan Alwall

Updated VERSION

Revision history for this message
Olivier Mattelaer (olivier-mattelaer) wrote :

Excellent work :-)

review: Approve
Revision history for this message
Valentin Hirschi (valentin-hirschi) wrote :

Hi Johan,

I am not too aware of the bug this revision should fix but it sounds like a good thing ;)
However, I wanted to ask the following: have you tried to merge the trunk series2.0 into it to see if the unit and parallel test are still ok with your modification?

I have not really understood what level of the code your modification affects (You mentioned addmothers.f and I do not know any fortran code with this name, but there is definitely one function called like this in MG5, so I am not sure what you are referring to) and maybe they have nothing to do with any core code of MG5 and my question is irrelevant.

See you this friday at CERN I guess, cheers.

review: Needs Information
Revision history for this message
Johan Alwall (johan-alwall) wrote :

Hello Valentin,

> I am not too aware of the bug this revision should fix but it sounds like a
> good thing ;)

addmothers.f is in the Template/SubProcesses directory. Its job is to assign properties to intermediate on-shell resonances. It turns out that when you have baryon violating vertices with color epsilon^{ijk}, assigning the correct color indices to the intermediate resonances is a pure hell, especially if there are also multiparticle vertices in the model. Unfortunately, it is still necessary, in order for Pythia to correctly process the events. This revision (hopefully) ensures that intermediate resonances get the right color assignment in the presence of color epsilon^{ijk} for all relevant cases.

> However, I wanted to ask the following: have you tried to merge the trunk
> series2.0 into it to see if the unit and parallel test are still ok with your
> modification?

Unit and parallel tests are not testing MadEvent, so there can't be any problem. In any case, I thought at this point the 2.0 trunk is (supposed to be) identical to the present trunk, since none of our new developments have been merged yet.

> See you this friday at CERN I guess, cheers.

I'll be there on EVO.

All the best,
Johan

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'Template/SubProcesses/addmothers.f'
2--- Template/SubProcesses/addmothers.f 2011-11-14 05:50:15 +0000
3+++ Template/SubProcesses/addmothers.f 2012-01-16 09:52:10 +0000
4@@ -19,8 +19,8 @@
5 integer isym(nexternal,99), jsym
6 integer i,j,k,ida(2),ns,nres,ires,icl,ito2,idenpart,nc,ic
7 integer mo_color,da_color(2),itmp
8- integer ito(-nexternal+3:nexternal),iseed,maxcolor
9- integer icolalt(2,-nexternal+3:2*nexternal-3)
10+ integer ito(-nexternal+3:nexternal),iseed,maxcolor,maxorg
11+ integer icolalt(2,-nexternal+2:2*nexternal-3)
12 double precision qicl(-nexternal+3:2*nexternal-3), factpm
13 double precision xtarget
14 data iseed/0/
15@@ -35,7 +35,7 @@
16 double precision pmass(-nexternal:0,lmaxconfigs)
17 double precision pwidth(-nexternal:0,lmaxconfigs)
18 integer pow(-nexternal:0,lmaxconfigs)
19- logical first_time
20+ logical first_time,tchannel
21 save pmass,pwidth,pow
22 data first_time /.true./
23
24@@ -72,9 +72,9 @@
25 c common/to_colstats/ncols,ncolflow,ncolalt,icorg
26
27 double precision pt
28- integer get_color,elim_indices
29+ integer get_color,elim_indices,set_colmp,fix_tchannel_color
30 real ran1
31- external pt,ran1,get_color,elim_indices
32+ external pt,ran1,get_color,elim_indices,set_colmp,fix_tchannel_color
33
34 if (first_time) then
35 include 'props.inc'
36@@ -142,6 +142,9 @@
37
38 endif ! nc.gt.0
39
40+c Store original maxcolor to know if we have epsilon vertices
41+ maxorg=maxcolor
42+
43 c
44 c Get mother information from chosen graph
45 c
46@@ -149,22 +152,70 @@
47 c First check number of resonant s-channel propagators
48 ns=0
49 nres=0
50-
51+ tchannel=.false.
52 c Loop over propagators to find mother-daughter information
53- do i=-1,-nexternal+3,-1
54+ do i=-1,-nexternal+2,-1
55 c Daughters
56- ida(1)=iforest(1,i,iconfig)
57- ida(2)=iforest(2,i,iconfig)
58- do j=1,2
59- if(ida(j).gt.0) ida(j)=isym(ida(j),jsym)
60- enddo
61+ if(i.gt.-nexternal+2)then
62+ ida(1)=iforest(1,i,iconfig)
63+ ida(2)=iforest(2,i,iconfig)
64+ do j=1,2
65+ if(ida(j).gt.0) ida(j)=isym(ida(j),jsym)
66+ enddo
67+ endif
68 c Decide s- or t-channel
69- if(iabs(sprop(numproc,i,iconfig)).gt.0) then ! s-channel propagator
70+ if(i.gt.-nexternal+2.and.
71+ $ iabs(sprop(numproc,i,iconfig)).gt.0) then ! s-channel propagator
72 jpart(1,i)=sprop(numproc,i,iconfig)
73 ns=ns+1
74+ else if(nres.gt.0.and.maxcolor.gt.maxorg) then
75+c For t-channel propagators, just check that the colors are ok
76+ if(i.eq.-nexternal+2) then
77+c This is the final t-channel, combining with leg 2
78+ mo_color=0
79+ if(.not.tchannel)then
80+c There are no previous t-channels, so this is a combination of
81+c 2, 1 and the last s-channel
82+ ida(1)=1
83+ ida(2)=i+1
84+ else
85+c The daughter info is in iforest
86+ ida(1)=iforest(1,i,iconfig)
87+ ida(2)=iforest(2,i,iconfig)
88+ endif
89+c Reverse colors of t-channels to get right color ordering
90+ ncolmp=0
91+ ncolmp=set_colmp(ncolmp,icolmp,2,jpart,
92+ $ iforest(1,-max_branch,iconfig),icolalt,
93+ $ icolalt(2,2),icolalt(1,2))
94+ else
95+ jpart(1,i)=tprid(i,iconfig)
96+ mo_color=get_color(jpart(1,i))
97+ ncolmp=0
98+ endif
99+ if(mo_color.gt.1.and.
100+ $ mo_color.ne.3.and.mo_color.ne.8)then
101+ da_color(1)=get_color(jpart(1,ida(1)))
102+ da_color(2)=get_color(jpart(1,ida(2)))
103+ call write_error(da_color(1), da_color(2), mo_color)
104+ endif
105+c Set icolmp for daughters
106+ ncolmp=set_colmp(ncolmp,icolmp,ida(2),jpart,
107+ $ iforest(1,-max_branch,iconfig),icolalt,
108+ $ icolalt(1,ida(2)),icolalt(2,ida(2)))
109+c Reverse colors of t-channels to get right color ordering
110+ ncolmp=set_colmp(ncolmp,icolmp,ida(1),jpart,
111+ $ iforest(1,-max_branch,iconfig),icolalt,
112+ $ icolalt(2,ida(1)),icolalt(1,ida(1)))
113+c Fix t-channel color
114+c print *,'t-channel: ',i,ida(1),ida(2),mo_color
115+c print *,'colors: ',((icolmp(j,k),j=1,2),k=1,ncolmp)
116+ maxcolor=fix_tchannel_color(mo_color,maxcolor,
117+ $ ncolmp,icolmp,i,icolalt)
118+ tchannel=.true.
119+ cycle
120 else
121-c Don't care about t-channel propagators
122- goto 100
123+ goto 100
124 endif
125 c Set status codes for propagator
126 c if((igscl(0).ne.0.and.
127@@ -191,70 +242,43 @@
128 c endif
129 c Set color info for all s-channels
130 mo_color = get_color(jpart(1,i))
131- da_color(1) = get_color(jpart(1,ida(1)))
132- da_color(2) = get_color(jpart(1,ida(2)))
133- if(da_color(1).ne.2.and.da_color(2).lt.da_color(1).or.
134- $ da_color(2).eq.2)then
135-c Order daughters according to color, but always color 2 first
136- itmp=ida(1)
137- ida(1)=ida(2)
138- ida(2)=itmp
139- itmp=da_color(1)
140- da_color(1)=da_color(2)
141- da_color(2)=itmp
142- endif
143-c Reset list of color indices if not inside multipart. vertex
144-c (indicated by color 2)
145- if(da_color(1).ne.2)then
146- ncolmp=0
147- endif
148+c If inside multipart. vertex (indicated by color 2) cycle
149+c Set tentative mothers
150+ jpart(2,i) = 1
151+ jpart(3,i) = 2
152+c Set mother info for daughters
153+ do j=1,2
154+ jpart(2,ida(j)) = i
155+ jpart(3,ida(j)) = i
156+ enddo
157+ if(mo_color.eq.2) cycle
158+c Reset list of color indices
159+ ncolmp=0
160 c Add new color indices to list of color indices
161-c Note that color=2 means continued multiparticle index
162 do j=1,2
163- if(da_color(j).eq.2.or.da_color(j).eq.1) cycle
164- ncolmp=ncolmp+1
165- icolmp(1,ncolmp)=icolalt(1,ida(j))
166- icolmp(2,ncolmp)=icolalt(2,ida(j))
167-c Avoid color sextet-type negative indices
168- if(icolmp(1,ncolmp).lt.0)then
169- ncolmp=ncolmp+1
170- icolmp(2,ncolmp)=-icolmp(1,ncolmp-1)
171- icolmp(1,ncolmp-1)=0
172- icolmp(1,ncolmp)=0
173- elseif(icolmp(2,ncolmp).lt.0)then
174- ncolmp=ncolmp+1
175- icolmp(1,ncolmp)=-icolmp(2,ncolmp-1)
176- icolmp(2,ncolmp-1)=0
177- icolmp(2,ncolmp)=0
178- endif
179- if(ncolmp.gt.maxcolmp)
180- $ call write_error(1000,ncolmp,maxcolmp)
181+ ncolmp=set_colmp(ncolmp,icolmp,ida(j),jpart,
182+ $ iforest(1,-max_branch,iconfig),icolalt,
183+ $ icolalt(1,ida(j)),icolalt(2,ida(j)))
184 enddo
185-
186+c print *,'s-channel: ',i,mo_color,ida(1),ida(2)
187+c print *,'colors: ',((icolmp(j,k),j=1,2),k=1,ncolmp)
188 if(mo_color.eq.1) then ! color singlet
189- icolalt(1,i) = 0
190- icolalt(2,i) = 0
191+ maxcolor=elim_indices(0,0,ncolmp,icolmp,i,icolalt,maxcolor)
192 elseif(mo_color.eq.-3) then ! color anti-triplet
193- maxcolor=elim_indices(0,1,ncolmp,icolmp,icolalt(1,i),maxcolor)
194+ maxcolor=elim_indices(0,1,ncolmp,icolmp,i,icolalt,maxcolor)
195 elseif(mo_color.eq.3) then ! color triplet
196- maxcolor=elim_indices(1,0,ncolmp,icolmp,icolalt(1,i),maxcolor)
197+ maxcolor=elim_indices(1,0,ncolmp,icolmp,i,icolalt,maxcolor)
198 elseif(mo_color.eq.-6) then ! color anti-sextet
199- maxcolor=elim_indices(0,2,ncolmp,icolmp,icolalt(1,i),maxcolor)
200+ maxcolor=elim_indices(0,2,ncolmp,icolmp,i,icolalt,maxcolor)
201 elseif(mo_color.eq.6) then ! color sextet
202- maxcolor=elim_indices(2,0,ncolmp,icolmp,icolalt(1,i),maxcolor)
203+ maxcolor=elim_indices(2,0,ncolmp,icolmp,i,icolalt,maxcolor)
204 elseif(mo_color.eq.8) then ! color octet
205- maxcolor=elim_indices(1,1,ncolmp,icolmp,icolalt(1,i),maxcolor)
206- elseif(mo_color.ne.2) then ! 2 indicates multipart. vertex
207+ maxcolor=elim_indices(1,1,ncolmp,icolmp,i,icolalt,maxcolor)
208+ else ! 2 indicates multipart. vertex
209+ da_color(1) = get_color(jpart(1,ida(1)))
210+ da_color(2) = get_color(jpart(1,ida(2)))
211 call write_error(da_color(1), da_color(2), mo_color)
212 endif
213-c Set tentative mothers
214- jpart(2,i) = 1
215- jpart(3,i) = 2
216-c Set mother info for daughters
217- do j=1,2
218- jpart(2,ida(j)) = i
219- jpart(3,ida(j)) = i
220- enddo
221 c Just zero helicity info for intermediate states
222 jpart(7,i) = 0
223 enddo ! do i
224@@ -306,7 +330,9 @@
225 return
226 end
227
228+c *************************************
229 subroutine write_error(ida1,ida2,imo)
230+c *************************************
231 implicit none
232 integer ida1,ida2,imo
233
234@@ -332,8 +358,243 @@
235 999 write(*,*) 'error'
236 end
237
238+c *********************************************************************
239+ function set_colmp(ncolmp,icolmp,npart,jpart,forest,icol,icol1,icol2)
240+c *********************************************************************
241+ implicit none
242+ integer maxcolmp
243+ parameter(maxcolmp=20)
244+ include 'nexternal.inc'
245+ include 'genps.inc'
246+c Arguments
247+ integer set_colmp
248+ integer ncolmp,icolmp(2,*),npart,icol1,icol2
249+ integer icol(2,-nexternal+2:2*nexternal-3)
250+ integer jpart(7,-nexternal+3:2*nexternal-3)
251+ integer forest(2,-max_branch:-1)
252+c Local
253+ integer da_color(2),itmp,ida(2),icolor,ipart,i,j
254+ integer get_color,set1colmp
255+
256+ set_colmp=ncolmp
257+ icolor=get_color(jpart(1,npart))
258+ if(icolor.eq.1) return
259+ if(icolor.eq.2) then
260+c Multiparticle vertex - need to go through daughters and collect all colors
261+ ipart=npart
262+ do while(icolor.eq.2)
263+ ida(1)=forest(1,ipart)
264+ ida(2)=forest(2,ipart)
265+ da_color(1)=get_color(jpart(1,ida(1)))
266+ da_color(2)=get_color(jpart(1,ida(2)))
267+c print *,'iforest: ',ipart,ida(1),ida(2),da_color(1),da_color(2)
268+ if(da_color(1).ne.2.and.da_color(2).lt.da_color(1).or.
269+ $ da_color(2).eq.2)then
270+c Order daughters according to color, but always color 2 first
271+ itmp=ida(1)
272+ ida(1)=ida(2)
273+ ida(2)=itmp
274+ itmp=da_color(1)
275+ da_color(1)=da_color(2)
276+ da_color(2)=itmp
277+ endif
278+ do i=1,2
279+ if(da_color(i).ne.1.and.da_color(i).ne.2)then
280+ ncolmp=set1colmp(ncolmp,icolmp,icol(1,ida(i)),
281+ $ icol(2,ida(i)))
282+ endif
283+ enddo
284+ icolor=da_color(1)
285+ ipart=ida(1)
286+ enddo
287+ else
288+ ncolmp=set1colmp(ncolmp,icolmp,icol1,icol2)
289+ endif
290+ set_colmp=ncolmp
291+ return
292+ end
293+
294+c ******************************************************
295+ function set1colmp(ncolmp,icolmp,icol1,icol2)
296+c ******************************************************
297+ implicit none
298+c Arguments
299+ integer maxcolmp
300+ parameter(maxcolmp=20)
301+ integer set1colmp
302+ integer ncolmp,icolmp(2,*),icol1,icol2
303+
304+ ncolmp=ncolmp+1
305+ icolmp(1,ncolmp)=icol1
306+ icolmp(2,ncolmp)=icol2
307+c Avoid color sextet-type negative indices
308+ if(icolmp(1,ncolmp).lt.0)then
309+ ncolmp=ncolmp+1
310+ icolmp(2,ncolmp)=-icolmp(1,ncolmp-1)
311+ icolmp(1,ncolmp-1)=0
312+ icolmp(1,ncolmp)=0
313+ elseif(icolmp(2,ncolmp).lt.0)then
314+ ncolmp=ncolmp+1
315+ icolmp(1,ncolmp)=-icolmp(2,ncolmp-1)
316+ icolmp(2,ncolmp-1)=0
317+ icolmp(2,ncolmp)=0
318+ endif
319+ if(ncolmp.gt.maxcolmp)
320+ $ call write_error(1000,ncolmp,maxcolmp)
321+ set1colmp=ncolmp
322+ return
323+ end
324+
325+c********************************************************************
326+ function fix_tchannel_color(mo_color,maxcolor,ncolmp,icolmp,ires,
327+ $ icol)
328+c********************************************************************
329+c Successively eliminate identical pairwise color indices from the
330+c icolmp list, until only (max) one triplet and one antitriplet remains
331+c
332+
333+ implicit none
334+ include 'nexternal.inc'
335+ integer fix_tchannel_color
336+ integer mo_color,maxcolor,ncolmp,icolmp(2,*)
337+ integer ires,icol(2,-nexternal+2:2*nexternal-3)
338+ integer i,j,i3,i3bar,max3,max3bar,min3,min3bar,maxcol,mincol
339+
340+c Successively eliminate color indices in pairs until only the wanted
341+c indices remain
342+ do i=1,ncolmp
343+ do j=1,ncolmp
344+ if(icolmp(1,i).ne.0.and.icolmp(1,i).eq.icolmp(2,j)) then
345+ icolmp(1,i)=0
346+ icolmp(2,j)=0
347+ endif
348+ enddo
349+ enddo
350+
351+ i3=0
352+ i3bar=0
353+ icol(1,ires)=0
354+ icol(2,ires)=0
355+ min3=1000
356+ max3=0
357+ min3bar=1000
358+ max3bar=0
359+ do i=1,ncolmp
360+ if(icolmp(1,i).gt.0)then
361+ i3=i3+1
362+c color for t-channels needs to be reversed
363+ if(i3.eq.1) icol(2,ires)=icolmp(1,i)
364+ if(i3.eq.2) icol(1,ires)=-icolmp(1,i)
365+ if(icolmp(1,i).gt.max3) max3=icolmp(1,i)
366+ if(icolmp(1,i).lt.min3) min3=icolmp(1,i)
367+ endif
368+ if(icolmp(2,i).gt.0)then
369+ i3bar=i3bar+1
370+c color for t-channels needs to be reversed
371+ if(i3bar.eq.1) icol(1,ires)=icolmp(2,i)
372+ if(i3bar.eq.2) icol(2,ires)=-icolmp(2,i)
373+ if(icolmp(2,i).gt.max3bar) max3bar=icolmp(2,i)
374+ if(icolmp(2,i).lt.min3bar) min3bar=icolmp(2,i)
375+ endif
376+ enddo
377+
378+ if(mo_color.eq.0)then
379+ icol(1,ires)=0
380+ icol(2,ires)=0
381+ endif
382+
383+ fix_tchannel_color=maxcolor
384+ if(mo_color.le.1.and.i3.eq.0.and.i3bar.eq.0) return
385+ if(mo_color.eq.3.and.(i3.eq.1.and.i3bar.eq.0
386+ $ .or.i3bar.eq.1.and.i3.eq.0)) return
387+ if(mo_color.eq.8.and.i3.eq.1.and.i3bar.eq.1) return
388+
389+c Make sure that max and min don't come from the same octet
390+ call clean_max_min(icolmp,ncolmp,max3,min3,max3bar,min3bar,i3,i3bar)
391+
392+ if(mo_color.le.1.and.i3-i3bar.eq.2.or.
393+ $ mo_color.le.1.and.i3bar-i3.eq.2.or.
394+ $ mo_color.le.1.and.i3.eq.1.and.i3bar.eq.1) then
395+c Replace the maximum index with the minimum one everywhere
396+ maxcol=max(max3,max3bar)
397+ if(maxcol.eq.max3) then
398+ mincol=min3bar
399+ else
400+ mincol=min3
401+ endif
402+ do i=ires+1,-1
403+ do j=1,2
404+ if(icol(j,i).eq.maxcol)
405+ $ icol(j,i)=mincol
406+ enddo
407+ enddo
408+c print *,'Replaced ',maxcol,' by ',mincol
409+ elseif(mo_color.le.1.and.i3.eq.2.and.i3bar.eq.2) then
410+c Replace the maximum indices with the minimum ones everywhere
411+ do i=ires+1,-1
412+ do j=1,2
413+ if(icol(j,i).eq.max3bar)
414+ $ icol(j,i)=min3
415+ if(icol(j,i).eq.max3)
416+ $ icol(j,i)=min3bar
417+ enddo
418+ enddo
419+c print *,'Replaced ',max3bar,' by ',min3,' and ',max3,' by ',min3bar
420+ elseif(mo_color.le.1.and.mod(i3,3).eq.0.and.mod(i3bar,3).eq.0)then
421+c This is epsilon index - do nothing
422+ continue
423+ else if(mo_color.eq.3.and.mod(i3-i3bar,3).eq.2) then
424+c This is an epsilon index
425+ maxcolor=maxcolor+1
426+ icol(1,ires)=maxcolor
427+ icol(2,ires)=0
428+c print *,'Set mother color for ',ires,' to ',(icol(j,ires),j=1,2)
429+ else if(mo_color.eq.3.and.mod(i3bar-i3,3).eq.2) then
430+c This is an epsilon index
431+ maxcolor=maxcolor+1
432+ icol(1,ires)=0
433+ icol(2,ires)=maxcolor
434+c print *,'Set mother color for ',ires,' to ',(icol(j,ires),j=1,2)
435+ else if(mo_color.eq.3.and.(i3-i3bar.eq.1.or.i3bar-i3.eq.1).or.
436+ $ mo_color.eq.8.and.i3.eq.2.and.i3bar.eq.2) then
437+c Replace the maximum index with the minimum one everywhere
438+c (we don't know if we should replace i3 with i3bar or vice versa)
439+ maxcol=max(max3,max3bar)
440+ if(maxcol.eq.max3) then
441+ mincol=min3bar
442+ else
443+ mincol=min3
444+ endif
445+ do i=ires+1,-1
446+ do j=1,2
447+ if(icol(j,i).eq.maxcol)
448+ $ icol(j,i)=mincol
449+ enddo
450+ enddo
451+c Fix the color for ires (remember 3<->3bar for t-channels)
452+ icol(1,ires)=0
453+ icol(2,ires)=0
454+c print *,'Replaced ',maxcol,' by ',mincol
455+ if(max3.eq.maxcol)then
456+ if(i3-i3bar.ge.0) icol(2,ires)=min3
457+ if(i3bar-i3.ge.0) icol(1,ires)=max3bar
458+ else
459+ if(i3-i3bar.ge.0) icol(2,ires)=max3
460+ if(i3bar-i3.ge.0) icol(1,ires)=min3bar
461+ endif
462+c print *,'Set mother color for ',ires,' to ',(icol(j,ires),j=1,2)
463+ else
464+c Don't know how to deal with this
465+ call write_error(i3,i3bar,mo_color)
466+ endif
467+
468+ fix_tchannel_color=maxcolor
469+
470+ return
471+ end
472+
473 c*******************************************************************
474- function elim_indices(n3,n3bar,ncolmp,icolmp,icolres,maxcolor)
475+ function elim_indices(n3,n3bar,ncolmp,icolmp,ires,icol,maxcolor)
476 c*******************************************************************
477 c Successively eliminate identical pairwise color indices from the
478 c icolmp list, until only the wanted indices remain
479@@ -346,8 +607,10 @@
480 c
481
482 implicit none
483+ include 'nexternal.inc'
484 integer elim_indices
485- integer n3,n3bar,ncolmp,icolmp(2,*),icolres(2),maxcolor
486+ integer n3,n3bar,ncolmp,icolmp(2,*),maxcolor
487+ integer ires,icol(2,-nexternal+2:2*nexternal-3)
488 integer i,j,i3,i3bar
489
490 c Successively eliminate color indices in pairs until only the wanted
491@@ -363,40 +626,47 @@
492
493 i3=0
494 i3bar=0
495- icolres(1)=0
496- icolres(2)=0
497+ icol(1,ires)=0
498+ icol(2,ires)=0
499 do i=1,ncolmp
500 if(icolmp(1,i).gt.0)then
501 i3=i3+1
502- if(i3.eq.1) icolres(1)=icolmp(1,i)
503- if(i3.eq.2) icolres(2)=-icolmp(1,i)
504+ if(i3.eq.1) icol(1,ires)=icolmp(1,i)
505+ if(i3.eq.2) icol(2,ires)=-icolmp(1,i)
506 endif
507 if(icolmp(2,i).gt.0)then
508 i3bar=i3bar+1
509- if(i3bar.eq.1) icolres(2)=icolmp(2,i)
510- if(i3bar.eq.2) icolres(1)=-icolmp(2,i)
511+ if(i3bar.eq.1) icol(2,ires)=icolmp(2,i)
512+ if(i3bar.eq.2) icol(1,ires)=-icolmp(2,i)
513 endif
514 enddo
515
516+ if(n3.eq.0) icol(1,ires)=0
517+ if(n3bar.eq.0) icol(2,ires)=0
518+
519 if(i3.ne.n3.or.i3bar.ne.n3bar) then
520- if(n3.gt.0.and.n3bar.eq.0)then
521+ if(n3.gt.0.and.n3bar.eq.0.and.mod(i3bar+n3,3).eq.0)then
522 c This is an epsilon index interaction
523 maxcolor=maxcolor+1
524- icolres(1)=maxcolor
525- icolres(2)=0
526+ icol(1,ires)=maxcolor
527 if(n3.eq.2)then
528 maxcolor=maxcolor+1
529- icolres(2)=-maxcolor
530+ icol(2,ires)=-maxcolor
531 endif
532- elseif(n3bar.gt.0.and.n3.eq.0)then
533+ elseif(n3bar.gt.0.and.n3.eq.0.and.mod(i3+n3bar,3).eq.0)then
534 c This is an epsilonbar index interaction
535 maxcolor=maxcolor+1
536- icolres(1)=0
537- icolres(2)=maxcolor
538+ icol(2,ires)=maxcolor
539 if(n3.eq.2)then
540 maxcolor=maxcolor+1
541- icolres(1)=-maxcolor
542+ icol(1,ires)=-maxcolor
543 endif
544+ elseif(n3.gt.0.and.n3bar.eq.0.and.i3-i3bar.eq.n3.or.
545+ $ n3bar.gt.0.and.n3.eq.0.and.i3bar-i3.eq.n3bar.or.
546+ $ n3.eq.1.and.n3bar.eq.1.and.i3-i3bar.eq.0.or.
547+ $ n3.eq.0.and.n3bar.eq.0.and.i3-i3bar.eq.0)then
548+c We have a previous epsilon which gives the wrong pop-up index
549+ call fix_s_color_indices(n3,n3bar,i3,i3bar,ncolmp,icolmp,ires,icol)
550 else
551 c Don't know how to deal with this
552 call write_error(1001,n3,n3bar)
553@@ -407,3 +677,153 @@
554
555 return
556 end
557+
558+c*******************************************************************
559+ subroutine fix_s_color_indices(n3,n3bar,i3,i3bar,ncolmp,icolmp,
560+ $ ires,icol)
561+c*******************************************************************
562+c
563+c Fix color flow if some particle has got the wrong pop-up color
564+c due to epsilon-ijk vertices
565+c
566+
567+ implicit none
568+ include 'nexternal.inc'
569+ integer n3,n3bar,ncolmp,icolmp(2,*),maxcolor
570+ integer ires,icol(2,-nexternal+2:2*nexternal-3)
571+ integer i,j,i3,i3bar
572+ integer max_n3,max_n3bar,min_n3,min_n3bar,maxcol,mincol
573+
574+ max_n3=0
575+ max_n3bar=0
576+ min_n3=1000
577+ min_n3bar=1000
578+ do i=1,ncolmp
579+ if(icolmp(1,i).gt.max_n3)
580+ $ max_n3=icolmp(1,i)
581+ if(icolmp(2,i).gt.max_n3bar)
582+ $ max_n3bar=icolmp(2,i)
583+ if(icolmp(1,i).gt.0.and.icolmp(1,i).lt.min_n3)
584+ $ min_n3=icolmp(1,i)
585+ if(icolmp(2,i).gt.0.and.icolmp(2,i).lt.min_n3bar)
586+ $ min_n3bar=icolmp(2,i)
587+ enddo
588+
589+ icol(1,ires)=0
590+ icol(2,ires)=0
591+
592+c Make sure that max and min don't come from the same octet
593+ call clean_max_min(icolmp,ncolmp,max_n3,min_n3,
594+ $ max_n3bar,min_n3bar,i3,i3bar)
595+
596+ if(n3.eq.1.and.n3bar.eq.0.and.i3-i3bar.eq.n3.or.
597+ $ n3bar.eq.1.and.n3.eq.0.and.i3bar-i3.eq.n3bar.or.
598+ $ n3bar.eq.1.and.n3.eq.1.and.i3bar-i3.eq.0.or.
599+ $ n3bar.eq.0.and.n3.eq.0.and.i3bar-i3.eq.0)then
600+c Replace the highest 3bar-index with the lowest 3-index,
601+c and vice versa
602+ maxcol=max(max_n3,max_n3bar)
603+ if(maxcol.eq.max_n3) then
604+ mincol=min_n3bar
605+ else
606+ mincol=min_n3
607+ endif
608+ do i=ires,-1
609+ do j=1,2
610+ if(icol(j,i).eq.maxcol)
611+ $ icol(j,i)=mincol
612+ enddo
613+ enddo
614+c print *,'Replaced ',maxcol,' with ',mincol
615+ if(max_n3.eq.maxcol)then
616+ if(n3.eq.1) icol(1,ires)=min_n3
617+ if(n3bar.eq.1) icol(2,ires)=max_n3bar
618+ else
619+ if(n3.eq.1) icol(1,ires)=max_n3
620+ if(n3bar.eq.1) icol(2,ires)=min_n3bar
621+ endif
622+c print *,'Set mother color for ',ires,' to ',(icol(j,ires),j=1,2)
623+ else
624+c Don't know how to deal with this
625+ call write_error(1001,n3,n3bar)
626+ endif
627+ return
628+ end
629+
630+c*******************************************************************************
631+ subroutine clean_max_min(icolmp,ncolmp,max3,min3,max3bar,min3bar,i3,i3bar)
632+c*******************************************************************************
633+ implicit none
634+ integer ncolmp,icolmp(2,*)
635+ integer i,j,max3,max3bar,min3,min3bar,i3,i3bar
636+
637+c print *,'max/min3/3bar: ',max3,min3,max3bar,min3bar
638+
639+c Make sure that max and min don't come from the same octet
640+ do i=1,ncolmp
641+ if(icolmp(1,i).eq.max3.and.icolmp(2,i).eq.min3bar)then
642+ min3bar=1000
643+ do j=1,ncolmp
644+ if(j.eq.i) cycle
645+ if(icolmp(2,j).lt.min3bar) min3bar=icolmp(2,j)
646+ enddo
647+ endif
648+ if(icolmp(2,i).eq.max3bar.and.icolmp(1,i).eq.min3)then
649+ min3=1000
650+ do j=1,ncolmp
651+ if(j.eq.i) cycle
652+ if(icolmp(1,j).lt.min3) min3=icolmp(1,j)
653+ enddo
654+ endif
655+ enddo
656+
657+c print *,'max/min3/3bar: ',max3,min3,max3bar,min3bar
658+
659+c ...and that max and min are different
660+ if(i3.gt.1.and.max3.eq.min3.or.i3bar.gt.1.and.max3bar.eq.min3bar)then
661+ if(max3.gt.max3bar)then
662+c Need to change min3, while still ensuring that max3bar is ok
663+ max3bar=0
664+ min3=1000
665+ do i=1,ncolmp
666+ if(icolmp(2,i).gt.max3bar.and.icolmp(2,i).ne.min3bar)
667+ $ max3bar=icolmp(2,i)
668+ if(icolmp(1,i).lt.min3.and.icolmp(1,i).ne.max3)
669+ $ min3=icolmp(1,i)
670+ enddo
671+c Make sure that max3bar and min3 don't come from the same octet
672+ do i=1,ncolmp
673+ if(icolmp(2,i).eq.max3bar.and.icolmp(1,i).eq.min3)then
674+ min3=1000
675+ do j=1,ncolmp
676+ if(j.eq.i.or.icolmp(1,j).eq.max3) cycle
677+ if(icolmp(1,j).lt.min3) min3=icolmp(1,j)
678+ enddo
679+ endif
680+ enddo
681+ else
682+c Need to change min3bar, while still ensuring that max3 is ok
683+ max3=0
684+ min3bar=1000
685+ do i=1,ncolmp
686+ if(icolmp(1,i).gt.max3.and.icolmp(1,i).ne.min3)
687+ $ max3=icolmp(1,i)
688+ if(icolmp(2,i).lt.min3bar.and.icolmp(2,i).ne.max3bar)
689+ $ min3bar=icolmp(2,i)
690+ enddo
691+c Make sure that max3 and min3bar don't come from the same octet
692+ do i=1,ncolmp
693+ if(icolmp(1,i).eq.max3.and.icolmp(2,i).eq.min3bar)then
694+ min3bar=1000
695+ do j=1,ncolmp
696+ if(j.eq.i.or.icolmp(2,j).eq.max3bar) cycle
697+ if(icolmp(2,j).lt.min3bar) min3bar=icolmp(2,j)
698+ enddo
699+ endif
700+ enddo
701+ endif
702+ endif
703+
704+c print *,'max/min3/3bar: ',max3,min3,max3bar,min3bar
705+
706+ end
707
708=== modified file 'UpdateNotes.txt'
709--- UpdateNotes.txt 2011-12-25 12:39:55 +0000
710+++ UpdateNotes.txt 2012-01-16 09:52:10 +0000
711@@ -1,5 +1,10 @@
712 Update notes for MadGraph 5 (in reverse time order)
713
714+1.3.33 (01/01/12) JA: Revisited colors for propagators in addmothers.f
715+ to ensure that propagators get the correct color
716+ also from initial state particles (thanks to
717+ Michele Gabusi for forcing me to do this).
718+
719 1.3.32 (21/12/11) JA: Fixed a bug in the PDF reweighting routine,
720 which caused skewed eta distributions for
721 matched samples with pdfwgt=T. Thanks to Giulio
722
723=== modified file 'madgraph/VERSION'
724--- madgraph/VERSION 2011-12-21 01:15:14 +0000
725+++ madgraph/VERSION 2012-01-16 09:52:10 +0000
726@@ -1,2 +1,2 @@
727-version = 1.3.32
728-date = 2011-12-21
729+version = 1.3.33_beta4
730+date = 2012-01-16

Subscribers

People subscribed via source and target branches