Merge lp:~maddevelopers/mg5amcnlo/phase_space_stuff into lp:~maddevelopers/mg5amcnlo/2.5.1

Proposed by Rikkert Frederix
Status: Merged
Merged at revision: 328
Proposed branch: lp:~maddevelopers/mg5amcnlo/phase_space_stuff
Merge into: lp:~maddevelopers/mg5amcnlo/2.5.1
Diff against target: 1352 lines (+533/-337)
7 files modified
Template/NLO/SubProcesses/genps_fks.f (+359/-276)
Template/NLO/SubProcesses/mint-integrator2.f (+49/-24)
Template/NLO/SubProcesses/mint.inc (+2/-2)
Template/NLO/SubProcesses/setcuts.f (+101/-34)
Template/NLO/SubProcesses/symmetry_fks_test_MC.f (+10/-1)
Template/NLO/SubProcesses/symmetry_fks_test_ME.f (+8/-0)
Template/NLO/SubProcesses/symmetry_fks_v3.f (+4/-0)
To merge this branch: bzr merge lp:~maddevelopers/mg5amcnlo/phase_space_stuff
Reviewer Review Type Date Requested Status
marco zaro Approve
Review via email: mp+307291@code.launchpad.net

Description of the change

Slight improvement in the phase-space generation for NLO processes. Also, a bit of factorising of that code to make it slightly simpler.

To post a comment you must log in.
Revision history for this message
marco zaro (marco-zaro) wrote :

Hi Rik,
I am looking at this merge, and I have a bunch of questions. Are your changes supposed to improve the performances of the code? Do the changes include the resonance-aware subtraction?
Thanks,
Marco

review: Needs Information
Revision history for this message
Rikkert Frederix (frederix) wrote :

Hi Marco,

It's just a phase-space optimisation. It doesn't include the resonance aware stuff. But for processes with competing resonances it is working slightly more efficient than the old way of doing things. It's not a great improvement, though.

Cheers,
Rik

Revision history for this message
marco zaro (marco-zaro) wrote :

Ciao Rik,
i have checked g g > h > 4 leptons in the heft model and the results are the same as with the stanadrd branch (within uncertainties). Timings are also similar, i think you can do the merge.

cheers,
Marco

review: Approve

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'Template/NLO/SubProcesses/genps_fks.f'
2--- Template/NLO/SubProcesses/genps_fks.f 2015-10-07 18:25:55 +0000
3+++ Template/NLO/SubProcesses/genps_fks.f 2016-09-30 09:38:53 +0000
4@@ -168,8 +168,8 @@
5 & ,ionebody,fksmass,nbranch
6 c Conflicting BW stuff
7 integer cBW_level_max,cBW(-nexternal:-1),cBW_level(-nexternal:-1)
8- double precision cBW_mass(-nexternal:-1,-1:1),
9- & cBW_width(-nexternal:-1,-1:1)
10+ double precision cBW_mass(-1:1,-nexternal:-1),
11+ & cBW_width(-1:1,-nexternal:-1)
12 common/c_conflictingBW/cBW_mass,cBW_width,cBW_level_max,cBW
13 $ ,cBW_level
14
15@@ -251,13 +251,13 @@
16 if(nt_channel.eq.0 .and. qwidth(-ns_channel-1).ne.0.d0 .and.
17 $ cBW(-ns_channel-1).ne.2)then
18 c Generate tau according to a Breit-Wiger function
19- call generate_tau_BW(stot,x(ndim-4),qmass(-ns_channel-1)
20- $ ,qwidth(-ns_channel-1),cBW(-ns_channel-1),cBW_mass(
21- $ -ns_channel-1,1),cBW_width(-ns_channel-1,1),tau_born
22- $ ,xjac0)
23+ call generate_tau_BW(stot,ndim-4,x(ndim-4),qmass(
24+ $ -ns_channel-1),qwidth(-ns_channel-1),cBW(-ns_channel
25+ $ -1),cBW_mass(-1, -ns_channel-1),cBW_width(-1,
26+ $ -ns_channel-1),tau_born,xjac0)
27 else
28-c not a Breit Wigner
29- call generate_tau(x(ndim-4),tau_born,xjac0)
30+c not a Breit Wigner
31+ call generate_tau(stot,ndim-4,x(ndim-4),tau_born,xjac0)
32 endif
33 endif
34 c Generate the rapditity of the Born system
35@@ -313,7 +313,8 @@
36 c
37 c Start by generating all the invariant masses of the s-channels
38 call generate_inv_mass_sch(ns_channel,itree,m,sqrtshat_born
39- & ,totmass,qwidth,qmass,cBW,cBW_mass,cBW_width,s,x,xjac0,pass)
40+ $ ,totmass,qwidth,qmass,cBW,cBW_level,cBW_mass,cBW_width,s,x
41+ $ ,xjac0,pass)
42 if (.not.pass) goto 222
43 c If only s-channels, also set the p1+p2 s-channel
44 if (nt_channel .eq. 0 .and. nincoming .eq. 2) then
45@@ -328,8 +329,8 @@
46 c Next do the T-channel branchings
47 c
48 if (nt_channel.ne.0) then
49- call generate_t_channel_branchings(ns_channel,nbranch,itree,m,s
50- & ,x,pb,xjac0,xpswgt0,pass)
51+ call generate_t_channel_branchings(ns_channel,nbranch,itree
52+ $ ,m,s,x,pb,xjac0,xpswgt0,pass)
53 if (.not.pass) goto 222
54 endif
55 c
56@@ -1107,8 +1108,8 @@
57 costh_i_fks=y_ij_fks+(1-y_ij_fks**2)*xi_i_fks/sqrt(cffC2)
58 if(abs(costh_i_fks).gt.1.d0)costh_i_fks=y_ij_fks
59 else
60- costh_i_fks=(x3len_fks_mother**2-x3len_j_fks**2+x3len_i_fks**2)/
61- & (2*x3len_fks_mother*x3len_i_fks)
62+ costh_i_fks=(x3len_fks_mother**2-x3len_j_fks**2+x3len_i_fks**2)
63+ $ /(2*x3len_fks_mother*x3len_i_fks)
64 if(abs(costh_i_fks).gt.1.d0+qtiny)then
65 write(*,*)'Fatal error #8 in one_tree',
66 & costh_i_fks,xi_i_fks,y_ij_fks,xmrec2
67@@ -1425,7 +1426,6 @@
68 c insert here further importance sampling towards xi_i_hat->0
69 xi_i_hat=sstiny+(1-sstiny)*x(1)**2
70 endif
71-c$$$ xi_i_fks=xi_i_hat*xiimax
72 xi_i_fks=xiimin+(xiimax-xiimin)*xi_i_hat
73 elseif( (icountevts.eq.-100.or.abs(icountevts).eq.1) .and.
74 & (colltest.and.xi_i_fks_fix.ne.-2.d0) .and.
75@@ -1771,8 +1771,8 @@
76 end
77
78
79- subroutine generate_tau_BW(stot,x,mass,width,cBW,BWmass,BWwidth
80- $ ,tau,jac)
81+ subroutine generate_tau_BW(stot,idim,x,mass,width,cBW,BWmass
82+ $ ,BWwidth,tau,jac)
83 implicit none
84 real*8 pi
85 parameter (pi=3.1415926535897932d0)
86@@ -1780,9 +1780,10 @@
87 parameter (nsamp=1)
88 include 'run.inc'
89 include 'genps.inc'
90- integer cBW,icount
91+ integer cBW,icount,idim
92 data icount /0/
93- double precision stot,x,tau,jac,mass,width,BWmass,BWwidth,m,w,a,b
94+ double precision stot,x,tau,jac,mass,width,m,w,a,b,BWmass(-1:1)
95+ $ ,BWwidth(-1:1),s,s_mass
96 double precision smax,smin,xm02,stemp,bwmdpl,bwmdmn,bwfmpl,bwfmmn
97 double precision bwdelf,xbwmass3,bwfunc,x0
98 external xmwmass3,bwfunc
99@@ -1792,154 +1793,54 @@
100 & ,tau_lower_bound
101 common/ctau_lower_bound/tau_Born_lower_bound
102 & ,tau_lower_bound_resonance,tau_lower_bound
103- if (cBW.eq.1 .and. width.gt.0d0 .and. BWwidth.gt.0d0) then
104-c conflicting Breit-Wigner
105-c use the ratio of the widths to determine which is the most-likely
106-c one to go on-shell
107- a=1d0-width/(width+BWwidth)
108-c use the mass separation to determine which region of phase-space
109-c should be generated by which BW
110- if (BWmass.le.mass) then
111- write (*,*) 'Error in generate_tau_BW #1',mass,BWmass
112- stop
113- endif
114- b=(BWmass-mass)/(width+BWwidth)
115- b=mass+b*width
116- b=b**2
117- if (x.lt.0.5d0) then
118-c the resonace BW
119- m=mass
120- w=width
121- x0=x*2d0
122- jac=jac*2d0
123- smax=b
124- smin=tau_Born_lower_bound*stot
125- else
126-c the alternative "BW". It's a rather flat distribution peaked above
127-c BWmass: we can use the normal generate_tau with the
128-c 'tau_lower_bound_resonance' equal to the BW mass, and
129-c 'tau_lower_bound' equal to the parameter 'b' (with the correct
130-c normalization)
131- x0=2d0*x-1d0
132- jac=jac*2d0
133-c save default tau's
134- tau_lower_bound_resonance_save=tau_lower_bound_resonance
135- tau_Born_lower_bound_save=tau_Born_lower_bound
136- tau_lower_bound_save=tau_lower_bound
137-c overwrite the tau's
138- tau_Born_lower_bound=b/stot
139- tau_lower_bound=tau_Born_lower_bound
140- tau_lower_bound_resonance=BWmass**2/stot
141-c Generate tau
142- call generate_tau(x0,tau,jac)
143-c restore default tau's
144- tau_lower_bound_resonance=tau_lower_bound_resonance_save
145- tau_Born_lower_bound=tau_Born_lower_bound_save
146- tau_lower_bound=tau_lower_bound_save
147- return ! tau and jac generate: exit this function
148- endif
149- elseif (cBW.eq.0) then
150-c Normal Breit-Wigner
151- m=mass
152- w=width
153- x0=x
154+ if (cBW.eq.1 .and. width.gt.0d0 .and. BWwidth(1).gt.0d0) then
155+ smin=tau_Born_lower_bound*stot
156 smax=stot
157- smin=tau_Born_lower_bound*stot
158+ s_mass=smin
159+ call trans_x(5,idim,x,smin,smax,s_mass,mass,width,BWmass(
160+ $ -1),BWwidth(-1),jac,s)
161+ tau=s/stot
162+ jac=jac/stot
163 else
164- write (*,*) 'Error in generate_tau_BW #2',cBW
165- stop
166+ smin=tau_Born_lower_bound*stot
167+ smax=stot
168+ s_mass=smin
169+ call trans_x(3,idim,x,smin,smax,s_mass,mass,width,BWmass(
170+ $ -1),BWwidth(-1),jac,s)
171+ tau=s/stot
172+ jac=jac/stot
173 endif
174- xm02=m**2
175- bwmdpl=smax-xm02
176- bwmdmn=xm02-smin
177- bwfmpl=atan(bwmdpl/(m*w))
178- bwfmmn=atan(bwmdmn/(m*w))
179- bwdelf=(bwfmpl+bwfmmn)/pi
180- stemp=xbwmass3(x0,xm02,w,bwdelf,bwfmmn)
181- jac=jac*bwdelf/bwfunc(stemp,xm02,w)
182- tau=stemp/stot
183- jac=jac/stot
184 return
185 end
186
187
188- subroutine generate_tau(x,tau,jac)
189+ subroutine generate_tau(stot,idim,x,tau,jac)
190 double precision x,tau,jac
191 double precision roH,roHs,fract,ximax0,ximin0,tmp,fract1,fract2
192- & ,roHj
193- integer nsamp
194+ & ,roHj,stot,s,dum,dum3(-1:1),smin,smax,s_mass
195+ integer nsamp,idim
196 parameter (nsamp=1)
197 double precision tau_Born_lower_bound,tau_lower_bound_resonance
198- & ,tau_lower_bound
199+ & ,tau_lower_bound,tiny
200+ parameter (tiny=1d-8)
201 common/ctau_lower_bound/tau_Born_lower_bound
202 & ,tau_lower_bound_resonance,tau_lower_bound
203 character*4 abrv
204 common /to_abrv/ abrv
205-c The only possible order for the lower bounds on tau is as follows:
206-c tau_Born_lower_bound <= tau_lower_bound <= tau_lower_bound_resonance
207-c If the order is different, we should quit.
208- if ( tau_Born_lower_bound.ge.tau_lower_bound+1d8 .or.
209- & tau_Born_lower_bound.ge.tau_lower_bound_resonance+1d8 .or.
210- & tau_lower_bound.ge.tau_lower_bound_resonance+1d8 ) then
211- write (*,*) 'Errors on the tau_Born_lower_bound'
212- & ,tau_Born_lower_bound,tau_lower_bound
213- & ,tau_lower_bound_resonance
214- stop
215- endif
216- roH=tau_Born_lower_bound
217- roHj=tau_lower_bound
218- roHs=tau_lower_bound_resonance
219-c User x below 'fract1' for phase-space region below jet cut-off
220- if (tau_lower_bound.le.tau_Born_lower_bound +1d-8) then
221- fract1=0d0
222- else
223- fract1=0.05d0
224- endif
225-c User x between 'fract1' and 'fract2' for phase-space region between
226-c jet and soft cut-off
227- if(tau_lower_bound_resonance.le.tau_lower_bound + 1d-8)then
228- fract2=0.0d0
229- else
230- fract2=0.05d0
231- endif
232- if (x.lt.fract1) then
233-c Use x^2 importance sampling below jet cut-off
234- if (fract1.lt.1d-5) then
235- write (*,*) 'fract1 is too small'
236- stop
237- endif
238- tau=roHj-(roHj-roH)*(1d0-x/fract1)**2
239- if (tau.le.1d-8) tau=1d-8 ! avoid numerical pathologies
240- jac=jac*(roHj-roH)*2d0*(1d0-x/fract1)/fract1
241- if (abrv.eq.'grid') then
242-c If we are setting-up the integration grids, using 'grid' (i.e. only
243-c the Born), we have to make sure that we have a viable PS point also
244-c when tau_born < tau_lower_bound. Simply set tau equal to the lower
245-c bound. Don't worry about putting a correct Jacobian, because the
246-c 'grid' cross section is non-physical anyway. We can use the Jacobian
247-c to enhance a bit the region close to the cut (and compensate for the
248-c Jacobian above, which goes in the other direction).
249- tau=roHj+1d-8
250- jac=jac*(x/fract1)**2
251- endif
252- elseif (x.lt.fract1+fract2) then
253-c Flat grid below soft cut-off
254- if (fract2.lt.1d-5) then
255- write (*,*) 'fract2 is too small'
256- stop
257- endif
258- tau=roHj-(roHs-roHj)*(fract1-x)/fract2
259- jac=jac*(roHs-roHj)/fract2
260- else
261-c Use 1/x^(nsamp) importance sampling above soft cut-off
262- fract=fract1+fract2
263- ximax0 = roHs**(-nsamp)
264- ximin0 = 1.d0
265- tmp = ximin0 +(1d0-(x-fract)/(1d0-fract))*(ximax0-ximin0)
266- tau = tmp**(-1/dble(nsamp))
267- jac= jac/nsamp*tau**(nsamp+1)*
268- & (ximax0-ximin0)/(1d0-fract)
269- endif
270+ smin=tau_born_lower_bound*stot
271+ smax=stot
272+ s_mass=tau_lower_bound_resonance*stot
273+ if (s_mass.gt.smin+tiny) then
274+ call trans_x(2,idim,x,smin,smax,s_mass,dum,dum
275+ $ ,dum3,dum3,jac,s)
276+ elseif(abs(s_mass-smin).lt.tiny) then
277+ call trans_x(7,idim,x,smin,smax,s_mass,dum,dum
278+ $ ,dum3,dum3,jac,s)
279+ else
280+ write (*,*) 'ERROR #39 in genps_fks.f',s_mass,smin
281+ endif
282+ tau=s/stot
283+ jac=jac/stot
284 return
285 end
286
287@@ -1985,7 +1886,8 @@
288
289
290 subroutine generate_inv_mass_sch(ns_channel,itree,m,sqrtshat_born
291- & ,totmass,qwidth,qmass,cBW,cBW_mass,cBW_width,s,x,xjac0,pass)
292+ $ ,totmass,qwidth,qmass,cBW,cBW_level,cBW_mass,cBW_width,s,x
293+ $ ,xjac0,pass)
294 implicit none
295 real*8 pi
296 parameter (pi=3.1415926535897932d0)
297@@ -1997,24 +1899,27 @@
298 double precision s(-max_branch:max_particles)
299 double precision sqrtshat_born,totmass,xjac0
300 integer itree(2,-max_branch:-1)
301- integer i,j,nsamp
302- parameter (nsamp=1)
303+ integer i,j,ii,order(-nexternal:0)
304 double precision smin,smax,xm02,bwmdpl,bwmdmn,bwfmpl,bwfmmn,bwdelf
305 & ,totalmass,tmp,ximin0,ximax0
306 double precision xbwmass3,bwfunc
307 external xbwmass3,bwfunc
308 logical pass
309 integer cBW_level_max,cBW(-nexternal:-1),cBW_level(-nexternal:-1)
310- double precision cBW_mass(-nexternal:-1,-1:1),
311- & cBW_width(-nexternal:-1,-1:1)
312+ double precision cBW_mass(-1:1,-nexternal:-1),
313+ & cBW_width(-1:1,-nexternal:-1)
314 double precision b(-1:1),x0
315- double precision s_mass(-nexternal:-1),xi,fract
316+ double precision s_mass(-nexternal:nexternal),xi,fract,vol_new
317+ $ ,shat,x_new
318 parameter (fract=0.1d0)
319 common/to_phase_space_s_channel/s_mass
320 pass=.true.
321 totalmass=totmass
322- do i = -1,-ns_channel,-1
323-c Generate invariant masses for all s-channel branchings of the Born
324+ do ii = -1,-ns_channel,-1
325+c Randomize the order with which to generate the s-channel masses:
326+ call sChan_order(ns_channel,order)
327+ i=order(ii)
328+c Generate invariant masses for all s-channel branchings of the Born
329 smin = (m(itree(1,i))+m(itree(2,i)))**2
330 smax = (sqrtshat_born-totalmass+sqrt(smin))**2
331 if(smax.lt.smin.or.smax.lt.0.d0.or.smin.lt.0.d0)then
332@@ -2026,139 +1931,67 @@
333 if(qwidth(i).ne.0.d0 .and. cBW(i).ne.2)then
334 c Breit Wigner
335 if (cBW(i).eq.1 .and.
336- & cBW_width(i,1).gt.0d0 .and. cBW_width(i,-1).gt.0d0) then
337+ & cBW_width(1,i).gt.0d0 .and. cBW_width(-1,i).gt.0d0) then
338 c conflicting BW on both sides
339- do j=-1,1,2
340- b(j)=(cBW_mass(i,j)-qmass(i))/
341- & (qwidth(i)+cBW_width(i,j))
342- b(j)=qmass(i)+b(j)*qwidth(i)
343- b(j)=b(j)**2
344- enddo
345- if (x(-i).lt.1d0/3d0) then
346- x0=3d0*x(-i)
347- s(i)=(b(-1)-smin)*x0+smin
348- xjac0=3d0*xjac0*(b(-1)-smin)
349- elseif (x(-i).gt.1d0/3d0 .and. x(-i).lt.2d0/3d0) then
350- x0=3d0*x(-i)-1d0
351- xm02=qmass(i)**2
352- bwmdpl=b(1)-xm02
353- bwmdmn=xm02-b(-1)
354- bwfmpl=atan(bwmdpl/(qmass(i)*qwidth(i)))
355- bwfmmn=atan(bwmdmn/(qmass(i)*qwidth(i)))
356- bwdelf=(bwfmpl+bwfmmn)/pi
357- s(i)=xbwmass3(x0,xm02,qwidth(i),bwdelf
358- & ,bwfmmn)
359- xjac0=3d0*xjac0*bwdelf/bwfunc(s(i),xm02,qwidth(i))
360- else
361- x0=3d0*x(-i)-2d0
362- s(i)=(smax-b(1))*x0+b(1)
363- xjac0=3d0*xjac0*(smax-b(1))
364- endif
365- elseif (cBW(i).eq.1.and.cBW_width(i,1).gt.0d0) then
366+ call trans_x(6,-i,x(-i),smin,smax,s_mass(i),qmass(i)
367+ $ ,qwidth(i),cBW_mass(-1,i),cBW_width(-1,i),xjac0
368+ $ ,s(i))
369+ elseif (cBW(i).eq.1.and.cBW_width(1,i).gt.0d0) then
370 c conflicting BW with alternative mass larger
371- b(1)=(cBW_mass(i,1)-qmass(i))/
372- & (qwidth(i)+cBW_width(i,1))
373- b(1)=qmass(i)+b(1)*qwidth(i)
374- b(1)=b(1)**2
375- if (x(-i).lt.0.5d0) then
376- x0=2d0*x(-i)
377- xm02=qmass(i)**2
378- bwmdpl=b(1)-xm02
379- bwmdmn=xm02-smin
380- bwfmpl=atan(bwmdpl/(qmass(i)*qwidth(i)))
381- bwfmmn=atan(bwmdmn/(qmass(i)*qwidth(i)))
382- bwdelf=(bwfmpl+bwfmmn)/pi
383- s(i)=xbwmass3(x0,xm02,qwidth(i),bwdelf
384- & ,bwfmmn)
385- xjac0=2d0*xjac0*bwdelf/bwfunc(s(i),xm02,qwidth(i))
386- else
387- x0=2d0*x(-i)-1d0
388- s(i)=(smax-b(1))*x0+b(1)
389- xjac0=2d0*xjac0*(smax-b(1))
390- endif
391- elseif (cBW(i).eq.1.and.cBW_width(i,-1).gt.0d0) then
392+ call trans_x(5,-i,x(-i),smin,smax,s_mass(i),qmass(i)
393+ $ ,qwidth(i),cBW_mass(-1,i),cBW_width(-1,i),xjac0
394+ $ ,s(i))
395+ elseif (cBW(i).eq.1.and.cBW_width(-1,i).gt.0d0) then
396 c conflicting BW with alternative mass smaller
397- b(-1)=(cBW_mass(i,-1)-qmass(i))/
398- & (qwidth(i)+cBW_width(i,-1)) ! b(-1) is negative here
399- b(-1)=qmass(i)+b(-1)*qwidth(i)
400- b(-1)=b(-1)**2
401-
402- if (b(-1).gt.smax) then
403- s(i)=(smax-smin)*x(-i)+smin
404- xjac0=xjac0*(smax-smin)
405- elseif (x(-i).lt.0.5d0) then
406- x0=2d0*x(-i)
407- s(i)=(b(-1)-smin)*x0+smin
408- xjac0=2d0*xjac0*(b(-1)-smin)
409- else
410- x0=2d0*x(-i)-1d0
411- xm02=qmass(i)**2
412- bwmdpl=smax-xm02
413- bwmdmn=xm02-b(-1)
414- bwfmpl=atan(bwmdpl/(qmass(i)*qwidth(i)))
415- bwfmmn=atan(bwmdmn/(qmass(i)*qwidth(i)))
416- bwdelf=(bwfmpl+bwfmmn)/pi
417- s(i)=xbwmass3(x0,xm02,qwidth(i),bwdelf
418- & ,bwfmmn)
419- xjac0=2d0*xjac0*bwdelf/bwfunc(s(i),xm02,qwidth(i))
420- endif
421+ call trans_x(4,-i,x(-i),smin,smax,s_mass(i),qmass(i)
422+ $ ,qwidth(i),cBW_mass(-1,i),cBW_width(-1,i),xjac0
423+ $ ,s(i))
424 else
425 c normal BW
426- xm02=qmass(i)**2
427- bwmdpl=smax-xm02
428- bwmdmn=xm02-smin
429- bwfmpl=atan(bwmdpl/(qmass(i)*qwidth(i)))
430- bwfmmn=atan(bwmdmn/(qmass(i)*qwidth(i)))
431- bwdelf=(bwfmpl+bwfmmn)/pi
432- s(i)=xbwmass3(x(-i),xm02,qwidth(i),bwdelf
433- & ,bwfmmn)
434- xjac0=xjac0*bwdelf/bwfunc(s(i),xm02,qwidth(i))
435+ call trans_x(3,-i,x(-i),smin,smax,s_mass(i),qmass(i)
436+ $ ,qwidth(i),cBW_mass(-1,i),cBW_width(-1,i),xjac0
437+ $ ,s(i))
438 endif
439 else
440 c not a Breit Wigner
441 if (smin.eq.0d0 .and. s_mass(i).eq.0d0) then
442 c no lower limit on invariant mass from cuts or final state masses:
443 c use flat distribution
444- s(i) = (smax-smin)*x(-i)+smin
445- xjac0 = xjac0*(smax-smin)
446+ call trans_x(1,-i,x(-i),smin,smax,s_mass(i),qmass(i)
447+ $ ,qwidth(i),cBW_mass(-1,i),cBW_width(-1,i),xjac0
448+ $ ,s(i))
449 elseif (smin.ge.s_mass(i) .and. smin.gt.0d0) then
450 c A lower limit on smin, which is larger than lower limit from cuts
451-c or masses. Use 1/x^nsamp importance sampling
452- ximax0 = smin**(-nsamp)
453- ximin0 = smax**(-nsamp)
454- tmp = ximin0 +(1d0-x(-i))*(ximax0-ximin0)
455- s(i) = tmp**(-1/dble(nsamp))
456- xjac0= xjac0/nsamp*s(i)**(nsamp+1)*(ximax0-ximin0)
457+c or masses. Use 1/x importance sampling
458+ call trans_x(7,-i,x(-i),smin,smax,s_mass(i),qmass(i)
459+ $ ,qwidth(i),cBW_mass(-1,i),cBW_width(-1,i),xjac0
460+ $ ,s(i))
461 elseif (smin.lt.s_mass(i) .and. s_mass(i).gt.0d0) then
462 c Use flat grid between smin and s_mass(i), and 1/x^nsamp above
463 c s_mass(i)
464- if (x(-i).lt.fract) then
465- xi=x(-i)/fract ! between 0 and 1
466- xjac0=xjac0/fract
467- s(i) = (s_mass(i)-smin)*xi+smin
468- xjac0 = xjac0*(s_mass(i)-smin)
469- else
470- xi=(x(-i)-fract)/(1d0-fract) ! between 0 and 1
471- xjac0=xjac0/(1d0-fract)
472- ximax0 = s_mass(i)**(-nsamp)
473- ximin0 = smax**(-nsamp)
474- tmp = ximin0 +(1d0-xi)*(ximax0-ximin0)
475- s(i) = tmp**(-1/dble(nsamp))
476- xjac0= xjac0/nsamp*s(i)**(nsamp+1)*(ximax0-ximin0)
477- endif
478+ call trans_x(2,-i,x(-i),smin,smax,s_mass(i),qmass(i)
479+ $ ,qwidth(i),cBW_mass(-1,i),cBW_width(-1,i),xjac0
480+ $ ,s(i))
481 else
482 write (*,*) "ERROR in genps_fks.f:"/
483- $ /" cannot set s-channel without BW"
484+ $ /" cannot set s-channel without BW",i,smin,s_mass(i)
485 stop 1
486 endif
487 endif
488 c If numerical inaccuracy, quit loop
489- if (xjac0 .lt. 0d0) then
490+ if (xjac0.le.0d0) then
491+ if ((xjac0.gt.-400d0 .or. xjac0.le.-500d0) .and.
492+ $ xjac0.ne.0d0)then
493+ write (*,*) 'WARNING #31 in genps_fks.f',i,s(i),smin,smax
494+ $ ,xjac0
495+ endif
496 xjac0 = -6
497 pass=.false.
498 return
499 endif
500- if (s(i) .lt. smin) then
501+ if (s(i).lt.smin .or. s(i).gt.smax) then
502+ write (*,*) 'WARNING #32 in genps_fks.f',i,s(i),smin,smax,x(
503+ $ -i)
504 xjac0=-5
505 pass=.false.
506 return
507@@ -2170,6 +2003,8 @@
508 totalmass=totalmass+m(i)-
509 & m(itree(1,i))-m(itree(2,i))
510 if ( totalmass.gt.sqrtshat_born )then
511+ write (*,*) 'WARNING #33 in genps_fks.f',i,totalmass
512+ $ ,sqrtshat_born,s(i)
513 xjac0 = -4
514 pass=.false.
515 return
516@@ -2180,7 +2015,7 @@
517
518
519 subroutine generate_t_channel_branchings(ns_channel,nbranch,itree
520- & ,m,s,x,pb,xjac0,xpswgt0,pass)
521+ $ ,m,s,x,pb,xjac0,xpswgt0,pass)
522 c First we need to determine the energy of the remaining particles this
523 c is essentially in place of the cos(theta) degree of freedom we have
524 c with the s channel decay sequence
525@@ -2198,15 +2033,20 @@
526 logical pass
527 c
528 double precision totalmass,smin,smax,s1,ma2,mbq,m12,mnq,tmin,tmax
529- & ,t,tmax_temp,phi
530- integer i,ibranch
531+ & ,t,tmax_temp,phi,dum,dum3(-1:1),s_m,tm,tiny
532+ parameter (tiny=1d-8)
533+ integer i,ibranch,idim
534 double precision lambda,dot
535 external lambda,dot
536+ double precision s_mass(-nexternal:nexternal)
537+ common/to_phase_space_s_channel/s_mass
538 c
539 pass=.true.
540 totalmass=0d0
541+ s_m=0d0
542 do ibranch = -ns_channel-1,-nbranch,-1
543 totalmass=totalmass+m(itree(2,ibranch))
544+ s_m=s_m+sqrt(s_mass(itree(2,ibranch)))
545 enddo
546 m(-ns_channel-1) = dsqrt(S(-nbranch))
547 c
548@@ -2215,7 +2055,7 @@
549 c t-channel propagator down to the initial-state particle found at the end
550 c of the t-channel line.
551 do ibranch = -ns_channel-1,-nbranch+2,-1
552- totalmass=totalmass-m(itree(2,ibranch))
553+ totalmass=totalmass-m(itree(2,ibranch))
554 smin = totalmass**2
555 smax = (m(ibranch) - m(itree(2,ibranch)))**2
556 if (smin .gt. smax) then
557@@ -2223,9 +2063,26 @@
558 pass=.false.
559 return
560 endif
561- m(ibranch-1)=dsqrt((smax-smin)*
562- & x(nbranch-1+(-ibranch)*2)+smin)
563- xjac0 = xjac0*(smax-smin)
564+ idim=(nbranch-1+(-ibranch)*2)
565+ s_m=s_m-sqrt(s_mass(itree(2,ibranch)))
566+ if (abs(smin-s_m**2).lt.tiny) then
567+ call trans_x(1,idim,x(idim),smin,smax,s_m**2,dum
568+ $ ,dum,dum3(-1),dum3(-1),xjac0,s1)
569+ else
570+ call trans_x(1,idim,x(idim),smin,smax,s_m**2,dum
571+ $ ,dum,dum3(-1),dum3(-1),xjac0,s1)
572+ endif
573+ if (xjac0.le.0d0) then
574+ if ((xjac0.gt.-400d0 .or. xjac0.le.-500d0) .and.
575+ $ xjac0.ne.0d0)then
576+ write (*,*) 'WARNING #31a in genps_fks.f',ibranch,s1
577+ $ ,smin,smax,s_m**2,xjac0
578+ endif
579+ xjac0 = -6
580+ pass=.false.
581+ return
582+ endif
583+ m(ibranch-1)=sqrt(s1)
584 if (m(ibranch-1)**2.lt.smin.or.m(ibranch-1)**2.gt.smax
585 & .or.m(ibranch-1).ne.m(ibranch-1)) then
586 xjac0=-1d0
587@@ -2256,10 +2113,21 @@
588 m12 = m(itree(2,ibranch))**2
589 mnq = m(ibranch-1)**2
590 call yminmax(s1,t,m12,ma2,mbq,mnq,tmin,tmax)
591- tmax_temp = tmax
592- t = (tmax_temp-tmin)*x(-ibranch)+tmin
593- xjac0=xjac0*(tmax_temp-tmin)
594+ call trans_x(1,-ibranch,x(-ibranch),-tmax,-tmin,s_mass(ibranch)
595+ $ ,dum,dum,dum3(-1),dum3(-1),xjac0,tm)
596+ if (xjac0.le.0d0) then
597+ if ((xjac0.gt.-400d0 .or. xjac0.le.-500d0) .and.
598+ $ xjac0.ne.0d0)then
599+ write (*,*) 'WARNING #31b in genps_fks.f',ibranch,tm
600+ $ ,-tmax,-tmin,xjac0
601+ endif
602+ xjac0 = -6
603+ pass=.false.
604+ return
605+ endif
606+ t=-tm
607 if (t .lt. tmin .or. t .gt. tmax) then
608+ write (*,*) "WARNING #35 in genps_fks.f",t,tmin,tmax
609 xjac0=-3d0
610 pass=.false.
611 return
612@@ -2395,3 +2263,218 @@
613 endif
614 return
615 end
616+
617+
618+
619+ subroutine trans_x(itype,idim,x,smin,smax,s_mass,qmass,qwidth
620+ $ ,cBW_mass,cBW_width,jac,s)
621+c Given the input random number 'x', returns the corresponding value of
622+c the invariant mass squared 's'.
623+c
624+c itype=1: flat transformation
625+c itype=2: flat between 0 and s_mass/stot, 1/x above
626+c itype=3: Breit-Wigner
627+c itype=4: Conflicting BW, with alternative mass smaller
628+c itype=5: Conflicting BW, with alternative mass larger
629+c itype=6: Conflicting BW on both sides
630+c
631+ implicit none
632+ include 'nexternal.inc'
633+ include 'run.inc' ! ebeam
634+c ARGUMENTS
635+ integer itype,idim
636+ double precision x,smin,smax,s_mass,qmass,qwidth,cBW_mass(-1:1)
637+ $ ,cBW_width(-1:1),jac,s
638+c LOCAL
639+ double precision tmp,vol_new,x_min,x_max,x_new,fract,x_mass,xg,A
640+ $ ,B,C,D,E,F,G,bs(-1:1),maxi,mini
641+ integer j
642+c
643+ if (itype.eq.1) then
644+c flat transformation:
645+ A=smax-smin
646+ B=smin
647+ s=A*x+B
648+ jac=jac*A
649+ elseif (itype.eq.2) then
650+ fract=0.25d0
651+ if (s_mass.eq.0d0) then
652+ write (*,*) 's_mass is zero',itype,idim
653+ endif
654+ if (x.lt.fract) then
655+c flat transformation:
656+ if (s_mass.lt.smin) then
657+ jac=-421d0
658+ return
659+ endif
660+ maxi=min(s_mass,smax)
661+ A=(maxi-smin)/fract
662+ B=smin
663+ s=A*x+B
664+ jac=jac*A
665+ else
666+c S=A/(B-x) transformation:
667+ if (s_mass.gt.smax) then
668+ jac=-422d0
669+ return
670+ endif
671+ mini=max(s_mass,smin)
672+ A=mini*smax*(1d0-fract)/(smax-mini)
673+ B=(smax-fract*mini)/(smax-mini)
674+ s=A/(B-x)
675+ jac=jac*s**2/A
676+ endif
677+ elseif(itype.eq.3) then
678+c Normal Breit-Wigner, i.e.
679+c \int_smin^smax ds g(s)/((s-qmass^2)^2-qmass^2*qwidth^2) =
680+c \int_0^1 dx g(s(x))
681+ A=atan((qmass-smin/qmass)/qwidth)
682+ B=atan((qmass-smax/qmass)/qwidth)
683+ s=qmass*(qmass-qwidth*tan(A-(A-B)*x))
684+ jac=jac*qmass*qwidth*(A-B)/(cos(A-(A-B)*x))**2
685+ elseif(itype.eq.4) then
686+c Conflicting BW, with alternative mass smaller than current
687+c mass. That is, we need to throw also many events at smaller masses
688+c than the peak of the current BW. Split 'x' at 'bs(-1)', using a
689+c flat distribution below the split, and a BW above the split.
690+ fract=0.3d0
691+ bs(-1)=(cBW_mass(-1)-qmass)/
692+ & (qwidth+cBW_width(-1)) ! bs(-1) is negative here
693+ bs(-1)=qmass+bs(-1)*qwidth
694+ bs(-1)=bs(-1)**2
695+ if (x.lt.fract) then
696+ if(smin.gt.bs(-1)) then
697+ jac=-441d0
698+ return
699+ endif
700+ maxi=min(bs(-1),smax)
701+ A=(maxi-smin)/fract
702+ B=smin
703+ s=A*x+B
704+ jac=jac*A
705+ else
706+ if(smax.lt.bs(-1)) then
707+ jac=-442d0
708+ return
709+ endif
710+ mini=max(bs(-1),smin)
711+ A=atan((qmass-mini/qmass)/qwidth)
712+ B=atan((qmass-smax/qmass)/qwidth)
713+ C=((1d0-x)*A+(x-fract)*B)/(1d0-fract)
714+ s=qmass*(qmass-qwidth*tan(C))
715+ jac=jac*qmass*qwidth*(A-B)/((cos(C))**2*(1d0-fract))
716+ endif
717+ elseif(itype.eq.5) then
718+c Conflicting BW, with alternative mass larger than current
719+c mass. That is, we need to throw also many events at larger masses
720+c than the peak of the current BW. Split 'x' at 'bs(1)' and the
721+c alternative mass. Use a BW below bs(1), a flat distribution
722+c between bs(1) and the alternative mass, and a 1/x above the
723+c alternative mass.
724+ fract=0.35d0
725+ bs(1)=(cBW_mass(1)-qmass)/
726+ & (qwidth+cBW_width(1))
727+ bs(1)=qmass+bs(1)*qwidth
728+ bs(1)=bs(1)**2
729+ if (x.lt.fract) then
730+ if(smin.gt.bs(1)) then
731+ jac=-451d0
732+ return
733+ endif
734+ maxi=min(bs(1),smax)
735+ A=atan((qmass-smin/qmass)/qwidth)
736+ B=atan((qmass-maxi/qmass)/qwidth)
737+ C=((B-A)*x+fract*A)/fract
738+ s=qmass*(qmass-qwidth*tan(C))
739+ jac=jac*qmass*qwidth*(A-B)/((cos(C))**2*fract)
740+ elseif (x.lt.1d0-fract) then
741+ if(smin.gt.cBW_mass(1)**2 .or. smax.lt.bs(1)) then
742+ jac=-452d0
743+ return
744+ endif
745+ maxi=min(cBW_mass(1)**2,smax)
746+ mini=max(bs(1),smin)
747+ A=(maxi-mini)/(1d0-2d0*fract)
748+ B=((1d0-fract)*mini-fract*maxi)/(1d0-2d0*fract)
749+ s=A*x+B
750+ jac=jac*A
751+ else
752+ if(smax.lt.cBW_mass(1)**2) then
753+ jac=-453d0
754+ return
755+ endif
756+ mini=max(cBW_mass(1)**2,smin)
757+ A=mini*smax*fract/(smax-mini)
758+ B=(smax-(1d0-fract)*mini)/(smax-mini)
759+ s=A/(B-x)
760+ jac=jac*s**2/A
761+ endif
762+ elseif(itype.eq.6) then
763+ fract=0.3d0
764+c Conflicting BW on both sides. Use flat below bs(-1); BW between
765+c bs(-1) and bs(1); flat between bs(1) and alternative mass; and 1/x
766+c above alternative mass.
767+ do j=-1,1,2
768+ bs(j)=(cBW_mass(j)-qmass)/
769+ & (qwidth+cBW_width(j))
770+ bs(j)=qmass+bs(j)*qwidth
771+ bs(j)=bs(j)**2
772+ enddo
773+ if (x.lt.fract) then
774+ if(smin.gt.bs(-1)) then
775+ jac=-461d0
776+ return
777+ endif
778+ maxi=min(bs(-1),smax)
779+ A=(maxi-smin)/fract
780+ B=smin
781+ s=A*x+B
782+ jac=jac*A
783+ elseif(x.lt.1d0-fract) then
784+ if(smin.gt.bs(1) .or. smax.lt.bs(-1)) then
785+ jac=-462d0
786+ return
787+ endif
788+ maxi=min(bs(1),smax)
789+ mini=max(bs(-1),smin)
790+ A=atan((qmass-mini/qmass)/qwidth)
791+ B=atan((qmass-maxi/qmass)/qwidth)
792+ C=((1d0-fract-x)*A+(x-fract)*B)/(1d0-2d0*fract)
793+ s=qmass*(qmass-qwidth*tan(C))
794+ jac=-jac*qmass*qwidth*(B-A)/((cos(C))**2*(1d0-2d0*fract))
795+ elseif(x.lt.1d0-fract/2d0) then
796+ if(smin.gt.cBW_mass(1)**2 .or. smax.lt.bs(1)) then
797+ jac=-463d0
798+ return
799+ endif
800+ maxi=min(cBW_mass(1)**2,smax)
801+ mini=max(bs(1),smin)
802+ A=2d0*(maxi-mini)/fract
803+ B=2d0*maxi-mini-2d0*(maxi-mini)/fract
804+ s=A*x+B
805+ jac=jac*A
806+ else
807+ if(smax.lt.cBW_mass(1)**2) then
808+ jac=-464d0
809+ return
810+ endif
811+ mini=max(cBW_mass(1)**2,smin)
812+ A=mini*smax*fract/(2d0*(smax-mini))
813+ B=(smax-(1d0-fract/2d0)*mini)/(smax-mini)
814+ s=A/(B-x)
815+ jac=jac*s**2/A
816+ endif
817+ elseif (itype.eq.7) then
818+c S=A/(B-x) transformation:
819+ if (smin.le.0d0) then
820+ jac=-471d0
821+ return
822+ endif
823+ A=smin*smax/(smax-smin)
824+ B=smax/(smax-smin)
825+ s=A/(B-x)
826+ jac=jac*s**2/A
827+ endif
828+ return
829+ end
830+
831
832=== modified file 'Template/NLO/SubProcesses/mint-integrator2.f'
833--- Template/NLO/SubProcesses/mint-integrator2.f 2015-11-20 15:07:40 +0000
834+++ Template/NLO/SubProcesses/mint-integrator2.f 2016-09-30 09:38:53 +0000
835@@ -96,6 +96,8 @@
836 double precision average_virtual,virtual_fraction
837 common/c_avg_virt/average_virtual,virtual_fraction
838 character*13 title(nintegrals)
839+ logical new_point
840+ common /c_new_point/ new_point
841 data title(1)/'ABS integral '/
842 data title(2)/'Integral '/
843 data title(3)/'Virtual '/
844@@ -237,6 +239,7 @@
845 c Loop over PS points
846 2 kpoint_iter=kpoint_iter+1
847 do kpoint=1,ncalls
848+ new_point=.true.
849 c find random x, and its random cell
850 do kdim=1,ndim
851 kfold(kdim)=1
852@@ -258,7 +261,7 @@
853 ifirst=0
854 1 continue
855 vol=1
856-c compute jacobian ('vol') for the PS point
857+c c convert 'flat x' ('rand') to 'vegas x' ('x') and include jacobian ('vol')
858 do kdim=1,ndim
859 nintcurr=nint_used/ifold(kdim)
860 icell(kdim)=ncell(kdim)+(kfold(kdim)-1)*nintcurr
861@@ -360,7 +363,8 @@
862 endif
863 c Goto beginning of loop over PS points until enough points have found
864 c that pass cuts.
865- if (non_zero_point(1).lt.ncalls .and. double_events) goto 2
866+ if (non_zero_point(1).lt.int(0.99*ncalls)
867+ & .and. double_events) goto 2
868
869 c Iteration done. Update the accumulated results and print them to the
870 c screen
871@@ -652,36 +656,54 @@
872 include "mint.inc"
873 integer ninter,nhits(nintervals)
874 real * 8 xacc(0:nintervals),xgrid(0:nintervals)
875- real * 8 xn(nintervals),r,tiny,xl,xu,nl,nu
876+ real * 8 xn(nintervals),r,tiny,xl,xu,nl,nu,sum
877 parameter ( tiny=1d-8 )
878 integer kint,jint
879-c Use the same smoothing as in VEGAS uses for the grids (i.e. use the
880-c average of the central and the two neighbouring grid points):
881- xl=xacc(1)
882- xu=xacc(2)
883- xacc(1)=(xl+xu)/2d0
884- nl=nhits(1)
885- nu=nhits(2)
886- nhits(1)=nint((nl+nu)/2d0)
887- do kint=2,ninter-1
888- xacc(kint)=xl+xu
889- xl=xu
890- xu=xacc(kint+1)
891- xacc(kint)=(xacc(kint)+xu)/3d0
892- nhits(kint)=nl+nu
893- nl=nu
894- nu=nhits(kint+1)
895- nhits(kint)=nint((nhits(kint)+nu)/3d0)
896+c Use the same smoothing as in VEGAS uses for the grids, i.e. use the
897+c average of the central and the two neighbouring grid points: (Only do
898+c this if we are already at the maximum intervals, because the doubling
899+c of the grids also includes a smoothing).
900+ if (ninter.eq.nintervals) then
901+ xl=xacc(1)
902+ xu=xacc(2)
903+ xacc(1)=(xl+xu)/2d0
904+ nl=nhits(1)
905+ nu=nhits(2)
906+ nhits(1)=nint((nl+nu)/2d0)
907+ do kint=2,ninter-1
908+ xacc(kint)=xl+xu
909+ xl=xu
910+ xu=xacc(kint+1)
911+ xacc(kint)=(xacc(kint)+xu)/3d0
912+ nhits(kint)=nl+nu
913+ nl=nu
914+ nu=nhits(kint+1)
915+ nhits(kint)=nint((nhits(kint)+nu)/3d0)
916+ enddo
917+ xacc(ninter)=(xu+xl)/2d0
918+ nhits(ninter)=nint((nu+nl)/2d0)
919+ endif
920+c
921+ sum=0d0
922+ do kint=1,ninter
923+ if (nhits(kint).ne.0) then
924+ xacc(kint)=abs(xacc(kint))/nhits(kint)
925+ sum=sum+xacc(kint)
926+ endif
927 enddo
928- xacc(ninter)=(xu+xl)/2d0
929- nhits(ninter)=nint((nu+nl)/2d0)
930 c
931 do kint=1,ninter
932 c xacc (xerr) already contains a factor equal to the interval size
933 c Thus the integral of rho is performed by summing up
934 if(nhits(kint).ne.0) then
935- xacc(kint)= xacc(kint-1)
936- # + abs(xacc(kint))/nhits(kint)
937+c take logarithm to help convergence (taken from LO dsample.f)
938+ if (xacc(kint).ne.sum) then
939+ xacc(kint)=((xacc(kint)/sum-1d0)/
940+ & log(xacc(kint)/sum))**1.5
941+ else
942+ xacc(kint)=1d0
943+ endif
944+ xacc(kint)= xacc(kint-1) + abs(xacc(kint))
945 else
946 xacc(kint)=xacc(kint-1)
947 endif
948@@ -791,6 +813,8 @@
949 common/c_avg_virt/average_virtual,virtual_fraction
950 save icalls,mcalls,icalls_virt,mcalls_virt,xmmm,icalls_nz
951 $ ,icalls_virt_nz
952+ logical new_point
953+ common /c_new_point/ new_point
954 if(imode.eq.0) then
955 do kdim=1,ndim
956 nintcurr=nintervals/ifold(kdim)
957@@ -844,6 +868,7 @@
958 stop
959 endif
960 10 continue
961+ new_point=.true.
962 if (vn.eq.1) then
963 icalls_virt=icalls_virt+1
964 elseif(vn.eq.2 .or. vn.eq.3) then
965
966=== modified file 'Template/NLO/SubProcesses/mint.inc'
967--- Template/NLO/SubProcesses/mint.inc 2013-11-22 15:49:06 +0000
968+++ Template/NLO/SubProcesses/mint.inc 2016-09-30 09:38:53 +0000
969@@ -4,11 +4,11 @@
970 c where 'n' is smaller or equal to 'min_it'.
971
972 integer nintervals,ndimmax,nintegrals,nintervals_virt
973- parameter (nintervals=32,ndimmax=60,nintegrals=6,
974+ parameter (nintervals=64,ndimmax=60,nintegrals=6,
975 & nintervals_virt=8)
976
977 integer min_inter,min_it0,min_it1,max_it,max_points
978- data min_inter /4/
979+ data min_inter /8/
980 data min_it0 /4/
981 data min_it1 /5/
982 data max_it /100/
983
984=== modified file 'Template/NLO/SubProcesses/setcuts.f'
985--- Template/NLO/SubProcesses/setcuts.f 2015-12-16 16:13:10 +0000
986+++ Template/NLO/SubProcesses/setcuts.f 2016-09-30 09:38:53 +0000
987@@ -156,9 +156,9 @@
988 INTEGER NFKSPROCESS
989 COMMON/C_NFKSPROCESS/NFKSPROCESS
990 double precision taumin(fks_configs),taumin_s(fks_configs)
991- & ,taumin_j(fks_configs),stot
992+ & ,taumin_j(fks_configs),stot,xk(-nexternal:0)
993 save taumin,taumin_s,taumin_j,stot
994- integer i,j,k,d1,d2,iFKS
995+ integer i,j,k,d1,d2,iFKS,nt
996 double precision xm(-nexternal:nexternal),xm1,xm2,xmi
997 double precision xw(-nexternal:nexternal),xw1,xw2,xwi
998 integer tsign,j_fks
999@@ -173,16 +173,16 @@
1000 integer cBW_FKS_level_max(fks_configs),
1001 & cBW_FKS(fks_configs,-nexternal:-1),
1002 & cBW_FKS_level(fks_configs,-nexternal:-1)
1003- double precision cBW_FKS_mass(fks_configs,-nexternal:-1,-1:1),
1004- & cBW_FKS_width(fks_configs,-nexternal:-1,-1:1)
1005+ double precision cBW_FKS_mass(fks_configs,-1:1,-nexternal:-1),
1006+ & cBW_FKS_width(fks_configs,-1:1,-nexternal:-1)
1007 save cBW_FKS_level_max,cBW_FKS,cBW_FKS_level,cBW_FKS_mass
1008 $ ,cBW_FKS_width
1009 integer cBW_level_max,cBW(-nexternal:-1),cBW_level(-nexternal:-1)
1010- double precision cBW_mass(-nexternal:-1,-1:1),
1011- & cBW_width(-nexternal:-1,-1:1)
1012+ double precision cBW_mass(-1:1,-nexternal:-1),
1013+ & cBW_width(-1:1,-nexternal:-1)
1014 common/c_conflictingBW/cBW_mass,cBW_width,cBW_level_max,cBW
1015 $ ,cBW_level
1016- double precision s_mass(-nexternal:-1)
1017+ double precision s_mass(-nexternal:nexternal)
1018 $ ,s_mass_FKS(fks_configs,-nexternal:nexternal)
1019 save s_mass_FKS
1020 common/to_phase_space_s_channel/s_mass
1021@@ -359,9 +359,10 @@
1022 c Also find the minimum lower bound if all internal s-channel particles
1023 c were on-shell
1024 tsign=-1
1025+ nt=0
1026 do i=-1,-(nexternal-3),-1 ! All propagators
1027 if ( itree(1,i) .eq. 1 .or. itree(1,i) .eq. 2 ) tsign=1
1028- if (tsign.eq.-1) then ! Only s-channels
1029+ if (tsign.eq.-1) then ! s-channels
1030 d1=itree(1,i)
1031 d2=itree(2,i)
1032 c If daughter is a jet, we should treat the ptj as a mass. Except if
1033@@ -388,22 +389,31 @@
1034 c subtract the daughters, because they are already included above or in
1035 c the previous iteration of the loop
1036 taumin_s(iFKS)=taumin_s(iFKS)+xm(i)-xm1-xm2
1037- else
1038- xm(i)=0d0
1039+ else ! t-channels
1040+ if (i.eq.-(nexternal-3)) then
1041+ xm(i)=0d0
1042+ cycle
1043+ endif
1044+ nt=nt+1
1045+ d1=itree(2,i) ! only use 2nd daughter (which is the outgoing one)
1046+ xm1=xm(d1)
1047+ if (nt.gt.1) xm1=max(xm1,xk(nt-1))
1048+ xk(nt)=xm1
1049+ j=i-1 ! this is the closest to p2
1050+ d2=itree(2,j)
1051+ xm2=xm(d2)
1052+ xm(i)=min(xm1,xm2)
1053 endif
1054 enddo
1055-
1056+
1057 cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
1058 c Determine the "minimal" s-channel invariant masses
1059 do i=nincoming+1,nexternal-1
1060 s_mass_FKS(iFKS,i)=xm(i)**2
1061 enddo
1062- do i=-1,-(nexternal-3),-1 ! All propagators
1063- if ( itree(1,i) .eq. 1 .or. itree(1,i) .eq. 2 ) exit ! only s-channels
1064- s_mass_FKS(iFKS,i)=(sqrt(s_mass_FKS(iFKS,itree(1,i)))
1065- $ +sqrt(s_mass_FKS(iFKS,itree(2,i))))**2
1066+ do i=-1,-(nexternal-3),-1 ! All propagators
1067+ s_mass_FKS(iFKS,i)=xm(i)**2
1068 enddo
1069-
1070 cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
1071 c Determine the conflicting Breit-Wigner's. Note that xm(i) contains the
1072 c mass of the BW
1073@@ -413,10 +423,10 @@
1074 cBW_FKS_level_max(iFKS)=0
1075 t_channel=0
1076 do i=-1,-(nexternal-3),-1 ! All propagators
1077- cBW_FKS_mass(iFKS,i,1)=0d0
1078- cBW_FKS_width(iFKS,i,1)=0d0
1079- cBW_FKS_mass(iFKS,i,-1)=0d0
1080- cBW_FKS_width(iFKS,i,-1)=0d0
1081+ cBW_FKS_mass(iFKS,1,i)=0d0
1082+ cBW_FKS_width(iFKS,1,i)=0d0
1083+ cBW_FKS_mass(iFKS,-1,i)=0d0
1084+ cBW_FKS_width(iFKS,-1,i)=0d0
1085 masslow(i)=9d99
1086 widthlow(i)=0d0
1087 if ( itree(1,i).eq.1 .or. itree(1,i).eq.2 ) t_channel=i
1088@@ -442,10 +452,10 @@
1089 cBW_FKS_level_max(iFKS)=max(cBW_FKS_level_max(iFKS)
1090 $ ,cBW_FKS_level(iFKS,i))
1091 c Set here the mass (and width) of the alternative mass; it's the
1092-c sum of daughter masses. (3rd argument is '1', because this
1093+c sum of daughter masses. (2nd argument is '1', because this
1094 c alternative mass is LARGER than the resonance mass).
1095- cBW_FKS_mass(iFKS,i,1)=xm(i)
1096- cBW_FKS_width(iFKS,i,1)=xw(i)
1097+ cBW_FKS_mass(iFKS,1,i)=xm(i)
1098+ cBW_FKS_width(iFKS,1,i)=xw(i)
1099 endif
1100 c set the daughters also as conflicting (recursively)
1101 masslow(i)=pmass(i,iconfig)
1102@@ -472,9 +482,9 @@
1103 if (pwidth(itree(k,j),iconfig).eq.0d0 .or.
1104 $ masslow(itree(k,j)).ge.pmass(itree(k,j)
1105 $ ,iconfig)) cycle
1106- cBW_FKS_mass(iFKS,itree(k,j),-1)=
1107+ cBW_FKS_mass(iFKS,-1,itree(k,j))=
1108 $ masslow(itree(k,j))
1109- cBW_FKS_width(iFKS,itree(k,j),-1)=
1110+ cBW_FKS_width(iFKS,-1,itree(k,j))=
1111 $ widthlow(itree(k,j))
1112 enddo
1113 enddo
1114@@ -503,8 +513,8 @@
1115 if (itree(2,i).gt.0) cycle
1116 if (cBW_FKS(iFKS,itree(2,i)).ne.2) then
1117 cBW_FKS(iFKS,itree(2,i))=1
1118- cBW_FKS_mass(iFKS,itree(2,i),-1)=sqrt(stot)/2d0
1119- cBW_FKS_width(iFKS,itree(2,i),-1)=xw(itree(2,i))
1120+ cBW_FKS_mass(iFKS,-1,itree(2,i))=sqrt(stot)/2d0
1121+ cBW_FKS_width(iFKS,-1,itree(2,i))=xw(itree(2,i))
1122 endif
1123 enddo
1124 endif
1125@@ -543,14 +553,71 @@
1126 cBW(i)=cBW_FKS(nFKSprocess,i)
1127 cBW_level(i)=cBW_FKS_level(nFKSprocess,i)
1128 do j=-1,1,2
1129- cBW_mass(i,j)=cBW_FKS_mass(nFKSprocess,i,j)
1130- cBW_width(i,j)=cBW_FKS_width(nFKSprocess,i,j)
1131+ cBW_mass(j,i)=cBW_FKS_mass(nFKSprocess,j,i)
1132+ cBW_width(j,i)=cBW_FKS_width(nFKSprocess,j,i)
1133 enddo
1134+ enddo
1135+ do i=-nexternal,nexternal
1136 s_mass(i)=s_mass_FKS(nFKSprocess,i)
1137 enddo
1138 cBW_level_max=cBW_FKS_level_max(nFKSprocess)
1139-
1140- return
1141- end
1142-
1143-
1144+ return
1145+ end
1146+
1147+
1148+ subroutine sChan_order(ns_channel,order)
1149+ implicit none
1150+ include 'nexternal.inc'
1151+ include 'maxparticles.inc'
1152+ include 'maxconfigs.inc'
1153+ include 'mint.inc'
1154+ double precision pmass(-nexternal:0,lmaxconfigs)
1155+ double precision pwidth(-nexternal:0,lmaxconfigs)
1156+ integer pow(-nexternal:0,lmaxconfigs)
1157+ integer itree(2,-max_branch:-1),iconfig
1158+ common /to_itree/itree,iconfig
1159+ logical new_point
1160+ common /c_new_point/new_point
1161+ double precision ran2,rnd
1162+ integer i,j,order(-nexternal:0),ipos,ns_channel,npos
1163+ $ ,pos(nexternal),ord(-nexternal:0)
1164+ logical done(-nexternal:nexternal)
1165+ external ran2
1166+ save ord
1167+ if (.not. new_point) then
1168+ do j=-1,-ns_channel,-1
1169+ order(j)=ord(j)
1170+ enddo
1171+ return
1172+ endif
1173+ do i=-ns_channel,0
1174+ done(i)=.false.
1175+ enddo
1176+ do i=1,nexternal
1177+ done(i)=.true.
1178+ enddo
1179+ do j=-1,-ns_channel,-1
1180+ npos=0
1181+ do i=-1,-ns_channel,-1
1182+ if((.not. done(i)) .and.
1183+ & done(itree(1,i)) .and. done(itree(2,i))) then
1184+ npos=npos+1
1185+ pos(npos)=i
1186+ endif
1187+ enddo
1188+ if (npos.gt.1) then
1189+ rnd=ran2()
1190+ ipos=min(int(rnd*npos)+1,npos)
1191+ ord(j)=pos(ipos)
1192+ done(pos(ipos))=.true.
1193+ elseif (npos.eq.1) then
1194+ ord(j)=pos(npos)
1195+ done(pos(npos))=.true.
1196+ else
1197+ write (*,*) 'ERROR in sChan_order',npos
1198+ endif
1199+ order(j)=ord(j)
1200+ enddo
1201+ new_point=.false.
1202+ return
1203+ end
1204
1205=== modified file 'Template/NLO/SubProcesses/symmetry_fks_test_MC.f'
1206--- Template/NLO/SubProcesses/symmetry_fks_test_MC.f 2016-06-03 09:49:40 +0000
1207+++ Template/NLO/SubProcesses/symmetry_fks_test_MC.f 2016-09-30 09:38:53 +0000
1208@@ -159,7 +159,10 @@
1209 common /cshowerscale2/shower_S_scale,shower_H_scale,ref_H_scale
1210 & ,pt_hardness
1211
1212-c integer icomp
1213+ logical new_point
1214+ common /c_new_point/new_point
1215+
1216+c integer icomp
1217 c
1218 c DATA
1219 c
1220@@ -342,6 +345,7 @@
1221 do jj=1,ndim
1222 x(jj)=ran2()
1223 enddo
1224+ new_point=.true.
1225 call generate_momenta(ndim,iconfig,wgt,x,p)
1226 calculatedBorn=.false.
1227 do while (( wgt.lt.0 .or. p(0,1).le.0d0 .or. p_born(0,1).le.0d0
1228@@ -349,6 +353,7 @@
1229 do jj=1,ndim
1230 x(jj)=ran2()
1231 enddo
1232+ new_point=.true.
1233 wgt=1d0
1234 call generate_momenta(ndim,iconfig,wgt,x,p)
1235 calculatedBorn=.false.
1236@@ -388,12 +393,14 @@
1237 do jj=1,ndim
1238 x(jj)=ran2()
1239 enddo
1240+ new_point=.true.
1241 call generate_momenta(ndim,iconfig,wgt,x,p)
1242 do while (( wgt.lt.0 .or. p(0,1).le.0d0) .and. ntry.lt.1000)
1243 wgt=1d0
1244 do jj=1,ndim
1245 x(jj)=ran2()
1246 enddo
1247+ new_point=.true.
1248 call generate_momenta(ndim,iconfig,wgt,x,p)
1249 ntry=ntry+1
1250 enddo
1251@@ -535,12 +542,14 @@
1252 do jj=1,ndim
1253 x(jj)=ran2()
1254 enddo
1255+ new_point=.true.
1256 call generate_momenta(ndim,iconfig,wgt,x,p)
1257 do while (( wgt.lt.0 .or. p(0,1).le.0d0) .and. ntry.lt.1000)
1258 wgt=1d0
1259 do jj=1,ndim
1260 x(jj)=ran2()
1261 enddo
1262+ new_point=.true.
1263 call generate_momenta(ndim,iconfig,wgt,x,p)
1264 ntry=ntry+1
1265 enddo
1266
1267=== modified file 'Template/NLO/SubProcesses/symmetry_fks_test_ME.f'
1268--- Template/NLO/SubProcesses/symmetry_fks_test_ME.f 2016-06-03 09:49:40 +0000
1269+++ Template/NLO/SubProcesses/symmetry_fks_test_ME.f 2016-09-30 09:38:53 +0000
1270@@ -139,6 +139,8 @@
1271 LOGICAL IS_A_PH(NEXTERNAL)
1272 COMMON /TO_SPECISA/IS_A_J,IS_A_LP,IS_A_LM,IS_A_PH
1273
1274+ logical new_point
1275+ common /c_new_point/new_point
1276 c integer icomp
1277 c
1278 c DATA
1279@@ -289,6 +291,7 @@
1280 do jj=1,ndim
1281 x(jj)=ran2()
1282 enddo
1283+ new_point=.true.
1284 call generate_momenta(ndim,iconfig,wgt,x,p)
1285 calculatedBorn=.false.
1286 do while (( wgt.lt.0 .or. p(0,1).le.0d0 .or. p_born(0,1).le.0d0
1287@@ -296,6 +299,7 @@
1288 do jj=1,ndim
1289 x(jj)=ran2()
1290 enddo
1291+ new_point=.true.
1292 wgt=1d0
1293 call generate_momenta(ndim,iconfig,wgt,x,p)
1294 calculatedBorn=.false.
1295@@ -334,12 +338,14 @@
1296 do jj=1,ndim
1297 x(jj)=ran2()
1298 enddo
1299+ new_point=.true.
1300 call generate_momenta(ndim,iconfig,wgt,x,p)
1301 do while (( wgt.lt.0 .or. p(0,1).le.0d0) .and. ntry.lt.1000)
1302 wgt=1d0
1303 do jj=1,ndim
1304 x(jj)=ran2()
1305 enddo
1306+ new_point=.true.
1307 call generate_momenta(ndim,iconfig,wgt,x,p)
1308 ntry=ntry+1
1309 enddo
1310@@ -460,12 +466,14 @@
1311 do jj=1,ndim
1312 x(jj)=ran2()
1313 enddo
1314+ new_point=.true.
1315 call generate_momenta(ndim,iconfig,wgt,x,p)
1316 do while (( wgt.lt.0 .or. p(0,1).le.0d0) .and. ntry.lt.1000)
1317 wgt=1d0
1318 do jj=1,ndim
1319 x(jj)=ran2()
1320 enddo
1321+ new_point=.true.
1322 call generate_momenta(ndim,iconfig,wgt,x,p)
1323 ntry=ntry+1
1324 enddo
1325
1326=== modified file 'Template/NLO/SubProcesses/symmetry_fks_v3.f'
1327--- Template/NLO/SubProcesses/symmetry_fks_v3.f 2016-03-16 14:21:42 +0000
1328+++ Template/NLO/SubProcesses/symmetry_fks_v3.f 2016-09-30 09:38:53 +0000
1329@@ -125,6 +125,8 @@
1330 logical nbody
1331 common/cnbody/nbody
1332
1333+ logical new_point
1334+ common /c_new_point/new_point
1335 c-----
1336 c Begin Code
1337 c-----
1338@@ -210,12 +212,14 @@
1339 do j=1,ndim
1340 x(j)=ran2()
1341 enddo
1342+ new_point=.true.
1343 call generate_momenta(ndim,iconfig,wgt,x,p)
1344 do while ((.not.passcuts(p,rwgt) .or. wgt.lt.0 .or. p(0,1).le.0d0
1345 & .or. p_born(0,1).le.0d0) .and. ntry.lt.10000)
1346 do j=1,ndim
1347 x(j)=ran2()
1348 enddo
1349+ new_point=.true.
1350 wgt=1d0
1351 call generate_momenta(ndim,iconfig,wgt,x,p)
1352 ntry=ntry+1

Subscribers

People subscribed via source and target branches

to all changes: