Merge lp:~maddevelopers/mg5amcnlo/3.0.1_4FS_merged3.0.2_latest into lp:~maddevelopers/mg5amcnlo/3.0.4

Proposed by marco zaro
Status: Merged
Merged at revision: 993
Proposed branch: lp:~maddevelopers/mg5amcnlo/3.0.1_4FS_merged3.0.2_latest
Merge into: lp:~maddevelopers/mg5amcnlo/3.0.4
Diff against target: 1762 lines (+744/-511)
21 files modified
Template/NLO/SubProcesses/fks_singular.f (+3/-1)
UpdateNotes.txt (+3/-5)
madgraph/iolibs/export_v4.py (+674/-4)
tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%CT_interface.f (+0/-11)
tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%loop_matrix.f (+1/-2)
tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%polynomial.f (+0/-36)
tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%CT_interface.f (+0/-11)
tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%loop_matrix.f (+1/-2)
tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%polynomial.f (+0/-36)
tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%CT_interface.f (+0/-302)
tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%loop_matrix.f (+1/-2)
tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%polynomial.f (+0/-37)
tests/input_files/IOTestsComparison/long_ML_SMQCD_default/dux_mumvmxg/%..%..%Source%MODEL%model_functions.f (+8/-8)
tests/input_files/IOTestsComparison/long_ML_SMQCD_default/gg_wmtbx/%..%..%Source%MODEL%model_functions.f (+8/-8)
tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/dux_mumvmxg/%..%..%Source%MODEL%model_functions.f (+8/-8)
tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/gg_wmtbx/%..%..%Source%MODEL%model_functions.f (+8/-8)
tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/gg_wmtbx/loop_CT_calls_1.f (+4/-4)
tests/input_files/IOTestsComparison/short_ML_SMQCD_LoopInduced/gg_hh/%..%..%Source%MODEL%model_functions.f (+8/-8)
tests/input_files/IOTestsComparison/short_ML_SMQCD_default/gg_ttx/%..%..%Source%MODEL%model_functions.f (+8/-8)
tests/input_files/IOTestsComparison/short_ML_SMQCD_optimized/gg_ttx/%..%..%Source%MODEL%model_functions.f (+8/-8)
tests/time_db (+1/-2)
To merge this branch: bzr merge lp:~maddevelopers/mg5amcnlo/3.0.1_4FS_merged3.0.2_latest
Reviewer Review Type Date Requested Status
Valentin Hirschi Pending
Rikkert Frederix Pending
Review via email: mp+389778@code.launchpad.net

Commit message

Enables the computation of EW corrections in the 4FS

Description of the change

the possibility of computing EW corrections in the 4FS is added, including in the complex-mass scheme.

To post a comment you must log in.
955. By marco zaro

merged with 3.0.4

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

Hello,
any opinion on this merge?
Thanks!
Marco

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

Could we put the model
loop_qcd_qed_sm_4FS
online and not shipped with MG5aMC?

We should avoid to have million of model shipped with MG5aMC.
You can add the model name in the auto-completion module such that we suggest to the user even if not present (and the model will automatically be downnloaded in that case).

For the rest I have no objection.

Cheers,

Olivier

PS: I can put the model online obviously

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

Hi Olivier,
I do not know how to put it online… So if you could do that, it would be very helpful!

Thanks a lot!

cheers,

marco

> On 1 Dec 2020, at 14:32, Olivier Mattelaer <email address hidden> wrote:
>
> Could we put the model
> loop_qcd_qed_sm_4FS
> online and not shipped with MG5aMC?
>
> We should avoid to have million of model shipped with MG5aMC.
> You can add the model name in the auto-completion module such that we suggest to the user even if not present (and the model will automatically be downnloaded in that case).
>
> For the rest I have no objection.
>
> Cheers,
>
> Olivier
>
> PS: I can put the model online obviously
> --
> https://code.launchpad.net/~maddevelopers/mg5amcnlo/3.0.1_4FS_merged3.0.2_latest/+merge/389778
> Your team MadDevelopers is subscribed to branch lp:~maddevelopers/mg5amcnlo/3.0.4.

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

Sure done:

Just for info, here is how to do it:

We have a special branch for that:
lp:~maddevelopers/mg5amcnlo/UFOmodel_db
where you can put the tarball in (and where you can modify it if needed)
and then you have to put in inside the database:
model_database.dat
then to check that everything is fine you can do
python check_database.py

then you push online wait (up to) one hour and the model is available online.

956. By olivier-mattelaer

remove loop_qcd_qed_sm_Gmu_4FS and loop_qcd_qed_sm_4FS from model directory -> put online

957. By marco zaro

merged with 3.0.4 rev 973

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

Hi,
if there is no comment on this, I will proceed with the merge tomorrow.

Ciao,

Marco

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

Hi Marco,

I'm currently trying to finalize the merge of 2.9.0 and 3.0.4.
So 3.0.4 is not working right now, I have a big no pole conservation issue.
So it might be better to stabilize 3.0.4 before doing additional merging.

I will keep you in touch when 3.0.4 will be back to a "stable" state

Cheers,

Olivier

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

Hi Olivier,
ok, I see, let me know

cheers,

Marco

> On 11 Feb 2021, at 09:57, Olivier Mattelaer <email address hidden> wrote:
>
> Hi Marco,
>
> I'm currently trying to finalize the merge of 2.9.0 and 3.0.4.
> So 3.0.4 is not working right now, I have a big no pole conservation issue.
> So it might be better to stabilize 3.0.4 before doing additional merging.
>
> I will keep you in touch when 3.0.4 will be back to a "stable" state
>
> Cheers,
>
> Olivier
> --
> https://code.launchpad.net/~maddevelopers/mg5amcnlo/3.0.1_4FS_merged3.0.2_latest/+merge/389778
> Your team MadDevelopers is subscribed to branch lp:~maddevelopers/mg5amcnlo/3.0.4.

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

Sorry i forgot to update you here.
You can move forward.

Olivier

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'Template/NLO/SubProcesses/fks_singular.f'
2--- Template/NLO/SubProcesses/fks_singular.f 2020-11-27 13:41:46 +0000
3+++ Template/NLO/SubProcesses/fks_singular.f 2021-01-08 10:23:48 +0000
4@@ -152,8 +152,10 @@
5 alphasbpow = orders(qcd_pos)/2
6 if (niglu.ne.0 .or. alphasbpow.ne.0) then
7 ! this contribution will end up with one extra power
8- ! of alpha_s
9+ ! of alpha_s. Check that we are including the corresponding
10+ ! order in the computation, otherwise skip the contribution
11 orders(qcd_pos) = orders(qcd_pos) + 2
12+ if (orders(qcd_pos).gt.nlo_orders(qcd_pos)) cycle
13
14 amp_split_6to5f_muf(orders_to_amp_split_pos(orders)) =
15 & alphas / 3d0 / pi * TF * dble(niglu) * amp_split(iamp)
16
17=== modified file 'UpdateNotes.txt'
18--- UpdateNotes.txt 2020-11-27 13:41:46 +0000
19+++ UpdateNotes.txt 2021-01-08 10:23:48 +0000
20@@ -1,10 +1,12 @@
21 Update notes for MadGraph5_aMC@NLO (in reverse time order)
22
23+
24 ** PARRALEL VERSION FOR EW branch **
25
26 3.0.4 (21/08/20)
27 ALL: include all changes up to 2.8.0 of the official release
28 ALL: pass to python3 by defauult
29+ DP+HS+MZ: Allow for the computation of NLO EW and complete NLO corrections in the 4FS
30 MZ+SC+ERN+CS: The code can be linked to PineAPPL (arXiv:2008.12789), making it possible
31 to generate PDF-independent fast-interploation grids including EW corrections.
32 This supersedes the interface to ApplGrid+aMCFast which was not working in v3
33@@ -22,7 +24,7 @@
34 3.0.3 (06/07/20)
35 include up to 2.7.3
36
37-3.0.2 (25/05/20)
38+3.0.2
39 include up to 2.7.2
40 MZ: better handling of zeros in color-linked borns
41 RF: improved the behaviour for integration channels that give zero cross section
42@@ -146,10 +148,6 @@
43 OM: Fix a Bug in pythia8 running on Ubuntu 18.04.4 machine
44 OM: Speed up standalone_cpp code by changing compilation flag
45
46-2.7.2(17/03/20)
47- OM: Fix a Bug in pythia8 running on Ubuntu 18.04.4 machine
48- OM: Speed up standalone_cpp code by changing compilation flag
49-
50 2.7.1.2(09/03/20)
51 OM: Fixing issue (wrong cross-section and differential cross-section) for
52 polarised sample when
53
54=== modified file 'madgraph/iolibs/export_v4.py'
55--- madgraph/iolibs/export_v4.py 2020-08-21 10:29:35 +0000
56+++ madgraph/iolibs/export_v4.py 2021-01-08 10:23:48 +0000
57@@ -6441,7 +6441,8 @@
58 if str(fct.name) not in ["complexconjugate", "re", "im", "sec",
59 "csc", "asec", "acsc", "theta_function", "cond",
60 "condif", "reglogp", "reglogm", "reglog", "recms", "arg", "cot",
61- "grreglog","regsqrt"]:
62+ "grreglog","regsqrt","B0F","sqrt_trajectory",
63+ "log_trajectory"]:
64 additional_fct.append(fct.name)
65
66 fsock = self.open('model_functions.inc', format='fortran')
67@@ -6454,6 +6455,9 @@
68 double complex grreglog
69 double complex recms
70 double complex arg
71+ double complex B0F
72+ double complex sqrt_trajectory
73+ double complex log_trajectory
74 %s
75 """ % "\n".join([" double complex %s" % i for i in additional_fct]))
76
77@@ -6468,6 +6472,9 @@
78 %(complex_mp_format)s mp_grreglog
79 %(complex_mp_format)s mp_recms
80 %(complex_mp_format)s mp_arg
81+ %(complex_mp_format)s mp_B0F
82+ %(complex_mp_format)s mp_sqrt_trajectory
83+ %(complex_mp_format)s mp_log_trajectory
84 %(additional)s
85 """ %\
86 {"additional": "\n".join([" %s mp_%s" % (self.mp_complex_format, i) for i in additional_fct]),
87@@ -6636,6 +6643,346 @@
88 endif
89 endif
90 end
91+
92+ module b0f_caching
93+
94+ type b0f_node
95+ double complex p2,m12,m22
96+ double complex value
97+ type(b0f_node),pointer::parent
98+ type(b0f_node),pointer::left
99+ type(b0f_node),pointer::right
100+ end type b0f_node
101+
102+ contains
103+
104+ subroutine b0f_search(item, head, find)
105+ implicit none
106+ type(b0f_node),pointer,intent(inout)::head,item
107+ logical,intent(out)::find
108+ type(b0f_node),pointer::item1
109+ integer::icomp
110+ find=.false.
111+ nullify(item%parent)
112+ nullify(item%left)
113+ nullify(item%right)
114+ if(.not.associated(head))then
115+ head => item
116+ return
117+ endif
118+ item1 => head
119+ do
120+ icomp=b0f_node_compare(item,item1)
121+ if(icomp.lt.0)then
122+ if(.not.associated(item1%left))then
123+ item1%left => item
124+ item%parent => item1
125+ exit
126+ else
127+ item1 => item1%left
128+ endif
129+ elseif(icomp.gt.0)then
130+ if(.not.associated(item1%right))then
131+ item1%right => item
132+ item%parent => item1
133+ exit
134+ else
135+ item1 => item1%right
136+ endif
137+ else
138+ find=.true.
139+ item%value=item1%value
140+ exit
141+ endif
142+ enddo
143+ return
144+ end
145+
146+ integer function b0f_node_compare(item1,item2) result(res)
147+ implicit none
148+ type(b0f_node),pointer,intent(in)::item1,item2
149+ res=complex_compare(item1%p2,item2%p2)
150+ if(res.ne.0)return
151+ res=complex_compare(item1%m22,item2%m22)
152+ if(res.ne.0)return
153+ res=complex_compare(item1%m12,item2%m12)
154+ return
155+ end
156+
157+ integer function real_compare(r1,r2) result(res)
158+ implicit none
159+ double precision r1,r2
160+ double precision maxr,diff
161+ double precision tiny
162+ parameter (tiny=-1d-14)
163+ maxr=max(abs(r1),abs(r2))
164+ diff=r1-r2
165+ if(maxr.le.1d-99.or.abs(diff)/max(maxr,1d-99).le.abs(tiny))then
166+ res=0
167+ return
168+ endif
169+ if(diff.gt.0d0)then
170+ res=1
171+ return
172+ else
173+ res=-1
174+ return
175+ endif
176+ end
177+
178+ integer function complex_compare(c1,c2) result(res)
179+ implicit none
180+ double complex c1,c2
181+ double precision r1,r2
182+ r1=dble(c1)
183+ r2=dble(c2)
184+ res=real_compare(r1,r2)
185+ if(res.ne.0)return
186+ r1=dimag(c1)
187+ r2=dimag(c2)
188+ res=real_compare(r1,r2)
189+ return
190+ end
191+
192+ end module b0f_caching
193+
194+ double complex function B0F(p2,m12,m22)
195+ use b0f_caching
196+ implicit none
197+ double complex p2,m12,m22
198+ double complex zero,TWOPII
199+ parameter (zero=(0.0d0,0.0d0))
200+ parameter (TWOPII=2.0d0*3.1415926535897932d0*(0.0d0,1.0d0))
201+ double precision M,M2,Ga,Ga2
202+ double precision tiny
203+ parameter (tiny=-1d-14)
204+ double complex logterms
205+ double complex log_trajectory
206+ logical use_caching
207+ parameter (use_caching=.true.)
208+ type(b0f_node),pointer::item
209+ type(b0f_node),pointer,save::b0f_bt
210+ integer init
211+ save init
212+ data init /0/
213+ logical find
214+ IF(m12.eq.zero)THEN
215+c it is a special case
216+c refer to Eq.(5.48) in arXiv:1804.10017
217+ M=DBLE(p2) ! M^2
218+ M2=DBLE(m22) ! M2^2
219+ IF(M.LT.tiny.OR.M2.LT.tiny)THEN
220+ WRITE(*,*)'ERROR:B0F is not well defined when M^2,M2^2<0'
221+ STOP
222+ ENDIF
223+ M=DSQRT(DABS(M))
224+ M2=DSQRT(DABS(M2))
225+ IF(M.EQ.0d0)THEN
226+ Ga=0d0
227+ ELSE
228+ Ga=-DIMAG(p2)/M
229+ ENDIF
230+ IF(M2.EQ.0d0)THEN
231+ Ga2=0d0
232+ ELSE
233+ Ga2=-DIMAG(m22)/M2
234+ ENDIF
235+ IF(p2.ne.m22.and.p2.ne.zero.and.m22.ne.zero)THEN
236+ b0f=(m22-p2)/p2*LOG((m22-p2)/m22)
237+ IF(M.GT.M2.and.Ga*M2.GT.Ga2*M)THEN
238+ b0f=b0f-TWOPII
239+ ENDIF
240+ RETURN
241+ ELSE
242+ WRITE(*,*)'ERROR:B0F is not supported for a simple form'
243+ STOP
244+ ENDIF
245+ ENDIF
246+c the general case
247+c trajectory method as advocated in arXiv:1804.10017 (Eq.(E.47))
248+ if(use_caching)then
249+ if(init.eq.0)then
250+ nullify(b0f_bt)
251+ init=1
252+ endif
253+ allocate(item)
254+ item%p2=p2
255+ item%m12=m12
256+ item%m22=m22
257+ find=.false.
258+ call b0f_search(item,b0f_bt,find)
259+ if(find)then
260+ b0f=item%value
261+ deallocate(item)
262+ return
263+ else
264+ logterms=log_trajectory(100,p2,m12,m22)
265+ b0f=-LOG(p2/m22)+logterms
266+ item%value=b0f
267+ return
268+ endif
269+ else
270+ logterms=log_trajectory(100,p2,m12,m22)
271+ b0f=-LOG(p2/m22)+logterms
272+ endif
273+ RETURN
274+ end
275+
276+ double complex function sqrt_trajectory(n_seg,p2,m12,m22)
277+c only needed when p2*m12*m22=\=0
278+ implicit none
279+ integer n_seg ! number of segments
280+ double complex p2,m12,m22
281+ double complex zero,one
282+ parameter (zero=(0.0d0,0.0d0),one=(1.0d0,0.0d0))
283+ double complex gamma0,gamma1
284+ double precision M,Ga,dGa,Ga_start
285+ double precision Gai,intersection
286+ double complex argim1,argi,p2i
287+ double complex gamma0i,gamma1i
288+ double precision tiny
289+ parameter (tiny=-1d-24)
290+ integer i
291+ double precision prefactor
292+ IF(ABS(p2*m12*m22).EQ.0d0)THEN
293+ WRITE(*,*)'ERROR:sqrt_trajectory works when p2*m12*m22/=0'
294+ STOP
295+ ENDIF
296+ M=DBLE(p2) ! M^2
297+ M=DSQRT(DABS(M))
298+ IF(M.EQ.0d0)THEN
299+ Ga=0d0
300+ ELSE
301+ Ga=-DIMAG(p2)/M
302+ ENDIF
303+c Eq.(5.37) in arXiv:1804.10017
304+ gamma0=one+m12/p2-m22/p2
305+ gamma1=m12/p2-dcmplx(0d0,1d0)*ABS(tiny)/p2
306+ IF(ABS(Ga).EQ.0d0)THEN
307+ sqrt_trajectory=SQRT(gamma0**2-4d0*gamma1)
308+ RETURN
309+ ENDIF
310+c segments from -DABS(tiny*Ga) to Ga
311+ Ga_start=-DABS(tiny*Ga)
312+ dGa=(Ga-Ga_start)/n_seg
313+ prefactor=1d0
314+ Gai=Ga_start
315+ p2i=dcmplx(M**2,-Gai*M)
316+ gamma0i=one+m12/p2i-m22/p2i
317+ gamma1i=m12/p2i-dcmplx(0d0,1d0)*ABS(tiny)/p2i
318+ argim1=gamma0i**2-4d0*gamma1i
319+ DO i=1,n_seg
320+ Gai=dGa*i+Ga_start
321+ p2i=dcmplx(M**2,-Gai*M)
322+ gamma0i=one+m12/p2i-m22/p2i
323+ gamma1i=m12/p2i-dcmplx(0d0,1d0)*ABS(tiny)/p2i
324+ argi=gamma0i**2-4d0*gamma1i
325+ IF(DIMAG(argi)*DIMAG(argim1).LT.0d0)THEN
326+ intersection=DIMAG(argim1)*(DBLE(argi)-DBLE(argim1))
327+ intersection=intersection/(DIMAG(argi)-DIMAG(argim1))
328+ intersection=intersection-DBLE(argim1)
329+ IF(intersection.GT.0d0)THEN
330+ prefactor=-prefactor
331+ ENDIF
332+ ENDIF
333+ argim1=argi
334+ ENDDO
335+ sqrt_trajectory=SQRT(gamma0**2-4d0*gamma1)*prefactor
336+ RETURN
337+ end
338+
339+ double complex function log_trajectory(n_seg,p2,m12,m22)
340+c sum of log terms appearing in Eq.(5.35) of arXiv:1804.10017
341+c only needed when p2*m12*m22=\=0
342+ implicit none
343+c 4 possible logarithms appearing in Eq.(5.35) of arXiv:1804.10017
344+c log(arg(i)) with arg(i) for i=1 to 4
345+c i=1: (ga_{+}-1)
346+c i=2: (ga_{-}-1)
347+c i=3: (ga_{+}-1)/ga_{+}
348+c i=4: (ga_{-}-1)/ga_{-}
349+ integer n_seg ! number of segments
350+ double complex p2,m12,m22
351+ double complex zero,one,half,TWOPII
352+ parameter (zero=(0.0d0,0.0d0),one=(1.0d0,0.0d0))
353+ parameter (half=(0.5d0,0.0d0))
354+ parameter (TWOPII=2.0d0*3.1415926535897932d0*(0.0d0,1.0d0))
355+ double complex gamma0,gammap,gammam,sqrtterm
356+ double precision M,Ga,dGa,Ga_start
357+ double precision Gai,intersection
358+ double complex argim1(4),argi(4),p2i,sqrttermi
359+ double complex gamma0i,gammapi,gammami
360+ double precision tiny
361+ parameter (tiny=-1d-14)
362+ integer i,j
363+ double complex addfactor(4)
364+ double complex sqrt_trajectory
365+ IF(ABS(p2*m12*m22).EQ.0d0)THEN
366+ WRITE(*,*)'ERROR:log_trajectory works when p2*m12*m22/=0'
367+ STOP
368+ ENDIF
369+ M=DBLE(p2) ! M^2
370+ M=DSQRT(DABS(M))
371+ IF(M.EQ.0d0)THEN
372+ Ga=0d0
373+ ELSE
374+ Ga=-DIMAG(p2)/M
375+ ENDIF
376+c Eq.(5.36-5.38) in arXiv:1804.10017
377+ sqrtterm=sqrt_trajectory(n_seg,p2,m12,m22)
378+ gamma0=one+m12/p2-m22/p2
379+ gammap=half*(gamma0+sqrtterm)
380+ gammam=half*(gamma0-sqrtterm)
381+ IF(ABS(Ga).EQ.0d0)THEN
382+ log_trajectory=-LOG(gammap-one)-LOG(gammam-one)+gammap*LOG((gammap-one)/gammap)+gammam*LOG((gammam-one)/gammam)
383+ RETURN
384+ ENDIF
385+c segments from -DABS(tiny*Ga) to Ga
386+ Ga_start=-DABS(tiny*Ga)
387+ dGa=(Ga-Ga_start)/n_seg
388+ addfactor(1:4)=zero
389+ Gai=Ga_start
390+ p2i=dcmplx(M**2,-Gai*M)
391+ sqrttermi=sqrt_trajectory(n_seg,p2i,m12,m22)
392+ gamma0i=one+m12/p2i-m22/p2i
393+ gammapi=half*(gamma0i+sqrttermi)
394+ gammami=half*(gamma0i-sqrttermi)
395+ argim1(1)=gammapi-one
396+ argim1(2)=gammami-one
397+ argim1(3)=(gammapi-one)/gammapi
398+ argim1(4)=(gammami-one)/gammami
399+ DO i=1,n_seg
400+ Gai=dGa*i+Ga_start
401+ p2i=dcmplx(M**2,-Gai*M)
402+ sqrttermi=sqrt_trajectory(n_seg,p2i,m12,m22)
403+ gamma0i=one+m12/p2i-m22/p2i
404+ gammapi=half*(gamma0i+sqrttermi)
405+ gammami=half*(gamma0i-sqrttermi)
406+ argi(1)=gammapi-one
407+ argi(2)=gammami-one
408+ argi(3)=(gammapi-one)/gammapi
409+ argi(4)=(gammami-one)/gammami
410+ DO j=1,4
411+ IF(DIMAG(argi(j))*DIMAG(argim1(j)).LT.0d0)THEN
412+ intersection=DIMAG(argim1(j))*(DBLE(argi(j))-DBLE(argim1(j)))
413+ intersection=intersection/(DIMAG(argi(j))-DIMAG(argim1(j)))
414+ intersection=intersection-DBLE(argim1(j))
415+ IF(intersection.GT.0d0)THEN
416+ IF(DIMAG(argim1(j)).LT.0)THEN
417+ addfactor(j)=addfactor(j)-TWOPII
418+ ELSE
419+ addfactor(j)=addfactor(j)+TWOPII
420+ ENDIF
421+ ENDIF
422+ ENDIF
423+ argim1(j)=argi(j)
424+ ENDDO
425+ ENDDO
426+ log_trajectory=-(LOG(gammap-one)+addfactor(1))-(LOG(gammam-one)+addfactor(2))
427+ log_trajectory=log_trajectory+gammap*(LOG((gammap-one)/gammap)+addfactor(3))
428+ log_trajectory=log_trajectory+gammam*(LOG((gammam-one)/gammam)+addfactor(4))
429+ RETURN
430+ end
431
432 double complex function arg(comnum)
433 implicit none
434@@ -6807,6 +7154,329 @@
435 endif
436 endif
437 end
438+
439+ module mp_b0f_caching
440+
441+ type mp_b0f_node
442+ %(complex_mp_format)s p2,m12,m22
443+ %(complex_mp_format)s value
444+ type(mp_b0f_node),pointer::parent
445+ type(mp_b0f_node),pointer::left
446+ type(mp_b0f_node),pointer::right
447+ end type mp_b0f_node
448+
449+ contains
450+
451+ subroutine mp_b0f_search(item, head, find)
452+ implicit none
453+ type(mp_b0f_node),pointer,intent(inout)::head,item
454+ logical,intent(out)::find
455+ type(mp_b0f_node),pointer::item1
456+ integer::icomp
457+ find=.false.
458+ nullify(item%%parent)
459+ nullify(item%%left)
460+ nullify(item%%right)
461+ if(.not.associated(head))then
462+ head => item
463+ return
464+ endif
465+ item1 => head
466+ do
467+ icomp=mp_b0f_node_compare(item,item1)
468+ if(icomp.lt.0)then
469+ if(.not.associated(item1%%left))then
470+ item1%%left => item
471+ item%%parent => item1
472+ exit
473+ else
474+ item1 => item1%%left
475+ endif
476+ elseif(icomp.gt.0)then
477+ if(.not.associated(item1%%right))then
478+ item1%%right => item
479+ item%%parent => item1
480+ exit
481+ else
482+ item1 => item1%%right
483+ endif
484+ else
485+ find=.true.
486+ item%%value=item1%%value
487+ exit
488+ endif
489+ enddo
490+ return
491+ end
492+
493+ integer function mp_b0f_node_compare(item1,item2) result(res)
494+ implicit none
495+ type(mp_b0f_node),pointer,intent(in)::item1,item2
496+ res=mp_complex_compare(item1%%p2,item2%%p2)
497+ if(res.ne.0)return
498+ res=mp_complex_compare(item1%%m22,item2%%m22)
499+ if(res.ne.0)return
500+ res=mp_complex_compare(item1%%m12,item2%%m12)
501+ return
502+ end
503+
504+ integer function mp_real_compare(r1,r2) result(res)
505+ implicit none
506+ %(real_mp_format)s r1,r2
507+ %(real_mp_format)s maxr,diff
508+ %(real_mp_format)s tiny
509+ parameter (tiny=-1.0e-14_16)
510+ maxr=max(abs(r1),abs(r2))
511+ diff=r1-r2
512+ if(maxr.le.1.0e-99_16.or.abs(diff)/max(maxr,1.0e-99_16).le.abs(tiny))then
513+ res=0
514+ return
515+ endif
516+ if(diff.gt.0.0e0_16)then
517+ res=1
518+ return
519+ else
520+ res=-1
521+ return
522+ endif
523+ end
524+
525+ integer function mp_complex_compare(c1,c2) result(res)
526+ implicit none
527+ %(complex_mp_format)s c1,c2
528+ %(real_mp_format)s r1,r2
529+ r1=real(c1,kind=16)
530+ r2=real(c2,kind=16)
531+ res=mp_real_compare(r1,r2)
532+ if(res.ne.0)return
533+ r1=imagpart(c1)
534+ r2=imagpart(c2)
535+ res=mp_real_compare(r1,r2)
536+ return
537+ end
538+
539+ end module mp_b0f_caching
540+
541+ %(complex_mp_format)s function mp_b0f(p2,m12,m22)
542+ use mp_b0f_caching
543+ implicit none
544+ %(complex_mp_format)s p2,m12,m22
545+ %(complex_mp_format)s zero,TWOPII
546+ parameter (zero=(0.0e0_16,0.0e0_16))
547+ parameter (TWOPII=2.0e0_16*3.14169258478796109557151794433593750e0_16*(0.0e0_16,1.0e0_16))
548+ %(real_mp_format)s M,M2,Ga,Ga2
549+ %(real_mp_format)s tiny
550+ parameter (tiny=-1.0e-14_16)
551+ %(complex_mp_format)s logterms
552+ %(complex_mp_format)s mp_log_trajectory
553+ logical use_caching
554+ parameter (use_caching=.true.)
555+ type(mp_b0f_node),pointer::item
556+ type(mp_b0f_node),pointer,save::b0f_bt
557+ integer init
558+ save init
559+ data init /0/
560+ logical find
561+ IF(m12.eq.zero)THEN
562+ M=real(p2,kind=16)
563+ M2=real(m22,kind=16)
564+ IF(M.LT.tiny.OR.M2.LT.tiny)THEN
565+ WRITE(*,*)'ERROR:MP_B0F is not well defined when M^2,M2^2<0'
566+ STOP
567+ ENDIF
568+ M=sqrt(abs(M))
569+ M2=sqrt(abs(M2))
570+ IF(M.EQ.0.0e0_16)THEN
571+ Ga=0.0e0_16
572+ ELSE
573+ Ga=-imagpart(p2)/M
574+ ENDIF
575+ IF(M2.EQ.0.0e0_16)THEN
576+ Ga2=0.0e0_16
577+ ELSE
578+ Ga2=-imagpart(m22)/M2
579+ ENDIF
580+ IF(p2.NE.m22.AND.p2.NE.zero.AND.m22.NE.zero)THEN
581+ mp_b0f=(m22-p2)/p2*log((m22-p2)/m22)
582+ IF(M.GT.M2.AND.Ga*M2.GT.Ga2*M)THEN
583+ mp_b0f=mp_b0f-TWOPII
584+ ENDIF
585+ RETURN
586+ ELSE
587+ WRITE(*,*)'ERROR:MP_B0F is not supported for a simple form'
588+ STOP
589+ ENDIF
590+ ENDIF
591+ if(use_caching)then
592+ if(init.eq.0)then
593+ nullify(b0f_bt)
594+ init=1
595+ endif
596+ allocate(item)
597+ item%%p2=p2
598+ item%%m12=m12
599+ item%%m22=m22
600+ find=.false.
601+ call mp_b0f_search(item, b0f_bt, find)
602+ if(find)then
603+ mp_b0f=item%%value
604+ deallocate(item)
605+ return
606+ else
607+ logterms=mp_log_trajectory(100,p2,m12,m22)
608+ mp_b0f=-LOG(p2/m22)+logterms
609+ item%%value=mp_b0f
610+ return
611+ endif
612+ else
613+ logterms=mp_log_trajectory(100,p2,m12,m22)
614+ mp_b0f=-LOG(p2/m22)+logterms
615+ endif
616+ RETURN
617+ end
618+
619+ %(complex_mp_format)s function mp_sqrt_trajectory(n_seg,p2,m12,m22)
620+ implicit none
621+ integer n_seg
622+ %(complex_mp_format)s p2,m12,m22
623+ %(complex_mp_format)s zero,one
624+ parameter (zero=(0.0e0_16,0.0e0_16),one=(1.0e0_16,0.0e0_16))
625+ %(complex_mp_format)s gamma0,gamma1
626+ %(real_mp_format)s M,Ga,dGa,Ga_start
627+ %(real_mp_format)s Gai,intersection
628+ %(complex_mp_format)s argim1,argi,p2i
629+ %(complex_mp_format)s gamma0i,gamma1i
630+ %(real_mp_format)s tiny
631+ parameter (tiny=-1.0e-24_16)
632+ integer i
633+ %(real_mp_format)s prefactor
634+ IF(ABS(p2*m12*m22).EQ.0.0e0_16)THEN
635+ WRITE(*,*)'ERROR:mp_sqrt_trajectory works when p2*m12*m22/=0'
636+ STOP
637+ ENDIF
638+ M=real(p2,kind=16)
639+ M=sqrt(abs(M))
640+ IF(M.EQ.0.0e0_16)THEN
641+ Ga=0.0e0_16
642+ ELSE
643+ Ga=-imagpart(p2)/M
644+ ENDIF
645+ gamma0=one+m12/p2-m22/p2
646+ gamma1=m12/p2-cmplx(0.0e0_16,1.0e0_16)*abs(tiny)/p2
647+ IF(abs(Ga).EQ.0.0e0_16)THEN
648+ mp_sqrt_trajectory=sqrt(gamma0**2-4.0e0_16*gamma1)
649+ RETURN
650+ ENDIF
651+ Ga_start=-abs(tiny*Ga)
652+ dGa=(Ga-Ga_start)/n_seg
653+ prefactor=1.0e0_16
654+ Gai=Ga_start
655+ p2i=cmplx(M**2,-Gai*M)
656+ gamma0i=one+m12/p2i-m22/p2i
657+ gamma1i=m12/p2i-cmplx(0.0e0_16,1.0e0_16)*abs(tiny)/p2i
658+ argim1=gamma0i**2-4.0e0_16*gamma1i
659+ DO i=1,n_seg
660+ Gai=dGa*i+Ga_start
661+ p2i=cmplx(M**2,-Gai*M)
662+ gamma0i=one+m12/p2i-m22/p2i
663+ gamma1i=m12/p2i-cmplx(0.0e0_16,1.0e0_16)*abs(tiny)/p2i
664+ argi=gamma0i**2-4.0e0_16*gamma1i
665+ IF(imagpart(argi)*imagpart(argim1).LT.0.0e0_16)THEN
666+ intersection=imagpart(argim1)*(real(argi,kind=16)-real(argim1,kind=16))
667+ intersection=intersection/(imagpart(argi)-imagpart(argim1))
668+ intersection=intersection-real(argim1,kind=16)
669+ IF(intersection.GT.0.0e0_16)THEN
670+ prefactor=-prefactor
671+ ENDIF
672+ ENDIF
673+ argim1=argi
674+ ENDDO
675+ mp_sqrt_trajectory=sqrt(gamma0**2-4.0e0_16*gamma1)*prefactor
676+ RETURN
677+ end
678+
679+ %(complex_mp_format)s function mp_log_trajectory(n_seg,p2,m12,m22)
680+ implicit none
681+ integer n_seg
682+ %(complex_mp_format)s p2,m12,m22
683+ %(complex_mp_format)s zero,one,half,TWOPII
684+ parameter (zero=(0.0e0_16,0.0e0_16),one=(1.0e0_16,0.0e0_16))
685+ parameter (half=(0.5e0_16,0.0e0_16))
686+ parameter (TWOPII=2.0e0_16*3.14169258478796109557151794433593750e0_16*(0.0e0_16,1.0e0_16))
687+ %(complex_mp_format)s gamma0,gammap,gammam,sqrtterm
688+ %(real_mp_format)s M,Ga,dGa,Ga_start
689+ %(real_mp_format)s Gai,intersection
690+ %(complex_mp_format)s argim1(4),argi(4),p2i,sqrttermi
691+ %(complex_mp_format)s gamma0i,gammapi,gammami
692+ %(real_mp_format)s tiny
693+ parameter (tiny=-1.0e-14_16)
694+ integer i,j
695+ %(complex_mp_format)s addfactor(4)
696+ %(complex_mp_format)s mp_sqrt_trajectory
697+ IF(abs(p2*m12*m22).eq.0.0e0_16)THEN
698+ WRITE(*,*)'ERROR:mp_log_trajectory works when p2*m12*m22/=0'
699+ STOP
700+ ENDIF
701+ M=real(p2,kind=16)
702+ M=sqrt(abs(M))
703+ IF(M.eq.0.0e0_16)THEN
704+ Ga=0.0e0_16
705+ ELSE
706+ Ga=-imagpart(p2)/M
707+ ENDIF
708+ sqrtterm=mp_sqrt_trajectory(n_seg,p2,m12,m22)
709+ gamma0=one+m12/p2-m22/p2
710+ gammap=half*(gamma0+sqrtterm)
711+ gammam=half*(gamma0-sqrtterm)
712+ IF(abs(Ga).EQ.0.0e0_16)THEN
713+ mp_log_trajectory=-LOG(gammap-one)-LOG(gammam-one)+gammap*LOG((gammap-one)/gammap)+gammam*LOG((gammam-one)/gammam)
714+ RETURN
715+ ENDIF
716+ Ga_start=-abs(tiny*Ga)
717+ dGa=(Ga-Ga_start)/n_seg
718+ addfactor(1:4)=zero
719+ Gai=Ga_start
720+ p2i=cmplx(M**2,-Gai*M)
721+ sqrttermi=mp_sqrt_trajectory(n_seg,p2i,m12,m22)
722+ gamma0i=one+m12/p2i-m22/p2i
723+ gammapi=half*(gamma0i+sqrttermi)
724+ gammami=half*(gamma0i-sqrttermi)
725+ argim1(1)=gammapi-one
726+ argim1(2)=gammami-one
727+ argim1(3)=(gammapi-one)/gammapi
728+ argim1(4)=(gammami-one)/gammami
729+ DO i=1,n_seg
730+ Gai=dGa*i+Ga_start
731+ p2i=cmplx(M**2,-Gai*M)
732+ sqrttermi=mp_sqrt_trajectory(n_seg,p2i,m12,m22)
733+ gamma0i=one+m12/p2i-m22/p2i
734+ gammapi=half*(gamma0i+sqrttermi)
735+ gammami=half*(gamma0i-sqrttermi)
736+ argi(1)=gammapi-one
737+ argi(2)=gammami-one
738+ argi(3)=(gammapi-one)/gammapi
739+ argi(4)=(gammami-one)/gammami
740+ DO j=1,4
741+ IF(imagpart(argi(j))*imagpart(argim1(j)).LT.0.0e0_16)THEN
742+ intersection=imagpart(argim1(j))*(real(argi(j),kind=16)-real(argim1(j),kind=16))
743+ intersection=intersection/(imagpart(argi(j))-imagpart(argim1(j)))
744+ intersection=intersection-real(argim1(j),kind=16)
745+ IF(intersection.GT.0.0e0_16)THEN
746+ IF(imagpart(argim1(j)).LT.0.0e0_16)THEN
747+ addfactor(j)=addfactor(j)-TWOPII
748+ ELSE
749+ addfactor(j)=addfactor(j)+TWOPII
750+ ENDIF
751+ ENDIF
752+ ENDIF
753+ argim1(j)=argi(j)
754+ ENDDO
755+ ENDDO
756+ mp_log_trajectory=-(LOG(gammap-one)+addfactor(1))-(LOG(gammam-one)+addfactor(2))
757+ mp_log_trajectory=mp_log_trajectory+gammap*(LOG((gammap-one)/gammap)+addfactor(3))
758+ mp_log_trajectory=mp_log_trajectory+gammam*(LOG((gammam-one)/gammam)+addfactor(4))
759+ RETURN
760+ end
761
762 %(complex_mp_format)s function mp_arg(comnum)
763 implicit none
764@@ -6838,8 +7508,8 @@
765 # already handle by default
766 if str(fct.name.lower()) not in ["complexconjugate", "re", "im", "sec", "csc", "asec", "acsc", "condif",
767 "theta_function", "cond", "reglog", "reglogp", "reglogm", "recms","arg",
768- "grreglog","regsqrt"] + done:
769- done.append(str(fct.name.lower()))
770+ "grreglog","regsqrt","B0F","sqrt_trajectory","log_trajectory"]:
771+
772 ufo_fct_template = """
773 double complex function %(name)s(%(args)s)
774 implicit none
775@@ -6876,7 +7546,7 @@
776 # already handle by default
777 if fct.name not in ["complexconjugate", "re", "im", "sec", "csc", "asec", "acsc","condif",
778 "theta_function", "cond", "reglog", "reglogp","reglogm", "recms","arg",
779- "grreglog","regsqrt"]:
780+ "grreglog","regsqrt","B0F","sqrt_trajectory","log_trajectory"]:
781
782 ufo_fct_template = """
783 %(complex_mp_format)s function mp_%(name)s(mp__%(args)s)
784
785=== modified file 'tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%CT_interface.f'
786--- tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%CT_interface.f 2020-11-27 13:41:46 +0000
787+++ tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%CT_interface.f 2021-01-08 10:23:48 +0000
788@@ -713,17 +713,6 @@
789 C CutTools is used
790 CALL CTLOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1,SQUAREDSOINDEX
791 $ ,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
792- ELSEIF (MLREDUCTIONLIB(I_LIB).EQ.6) THEN
793-C Ninja is used
794- IF (.NOT.DOING_QP) THEN
795- CALL NINJA_LOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1
796- $ ,SQUAREDSOINDEX,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
797- ELSE
798- WRITE(*,*) 'ERROR: Ninja should not be called in quadruple'
799- $ //' precision since the installed version considered does'
800- $ //' not support it.'
801- STOP 9
802- ENDIF
803 ELSE
804 C Tensor Integral Reduction is used
805 CALL TIRLOOP(SQUAREDSOINDEX,LOOPNUM,I_LIB,NLOOPLINE,PL,M2L
806
807=== modified file 'tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%loop_matrix.f'
808--- tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%loop_matrix.f 2020-11-27 13:41:46 +0000
809+++ tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%loop_matrix.f 2021-01-08 10:23:48 +0000
810@@ -245,7 +245,7 @@
811 C AVAILABLE OR NOT
812 LOGICAL LOOPLIBS_AVAILABLE(NLOOPLIB)
813 DATA LOOPLIBS_AVAILABLE/.TRUE.,.FALSE.,.TRUE.,.FALSE.,.FALSE.
814- $ ,.TRUE.,.TRUE./
815+ $ ,.FALSE.,.TRUE./
816 COMMON/LOOPLIBS_AV/ LOOPLIBS_AVAILABLE
817 C A FLAG TO DENOTE WHETHER THE CORRESPONDING DIRECTION TESTS
818 C AVAILABLE OR NOT IN THE LOOPLIBS
819@@ -1678,7 +1678,6 @@
820 C ech event
821 C
822 CALL CLEAR_TIR_CACHE()
823- CALL NINJA_CLEAR_INTEGRAL_CACHE()
824 CALL CLEAR_COLLIER_CACHE()
825 END
826
827
828=== modified file 'tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%polynomial.f'
829--- tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%polynomial.f 2020-08-21 10:29:35 +0000
830+++ tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_dxu_wp%V0_dxu_wp%polynomial.f 2021-01-08 10:23:48 +0000
831@@ -132,24 +132,6 @@
832
833 END
834
835- SUBROUTINE INVERT_MOMENTA_IN_POLYNOMIAL(NCOEFS,POLYNOMIAL)
836-C Just a handy subroutine to modify the coefficients for the
837-C tranformation q_loop -> -q_loop
838-C It is only used for the NINJA interface
839- USE POLYNOMIAL_CONSTANTS
840- IMPLICIT NONE
841-
842- INTEGER I, NCOEFS
843-
844- COMPLEX*16 POLYNOMIAL(0:NCOEFS-1)
845-
846- DO I=0,NCOEFS-1
847- IF (MOD(COEFTORANK_MAP(I),2).EQ.1) THEN
848- POLYNOMIAL(I)=-POLYNOMIAL(I)
849- ENDIF
850- ENDDO
851-
852- END
853
854 C Now the routines to update the wavefunctions
855
856@@ -251,24 +233,6 @@
857
858 END
859
860- SUBROUTINE MP_INVERT_MOMENTA_IN_POLYNOMIAL(NCOEFS,POLYNOMIAL)
861-C Just a handy subroutine to modify the coefficients for the
862-C tranformation q_loop -> -q_loop
863-C It is only used for the NINJA interface
864- USE POLYNOMIAL_CONSTANTS
865- IMPLICIT NONE
866-
867- INTEGER I, NCOEFS
868-
869- COMPLEX*32 POLYNOMIAL(0:NCOEFS-1)
870-
871- DO I=0,NCOEFS-1
872- IF (MOD(COEFTORANK_MAP(I),2).EQ.1) THEN
873- POLYNOMIAL(I)=-POLYNOMIAL(I)
874- ENDIF
875- ENDDO
876-
877- END
878
879 C Now the routines to update the wavefunctions
880
881
882=== modified file 'tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%CT_interface.f'
883--- tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%CT_interface.f 2020-11-27 13:41:46 +0000
884+++ tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%CT_interface.f 2021-01-08 10:23:48 +0000
885@@ -713,17 +713,6 @@
886 C CutTools is used
887 CALL CTLOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1,SQUAREDSOINDEX
888 $ ,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
889- ELSEIF (MLREDUCTIONLIB(I_LIB).EQ.6) THEN
890-C Ninja is used
891- IF (.NOT.DOING_QP) THEN
892- CALL NINJA_LOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1
893- $ ,SQUAREDSOINDEX,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
894- ELSE
895- WRITE(*,*) 'ERROR: Ninja should not be called in quadruple'
896- $ //' precision since the installed version considered does'
897- $ //' not support it.'
898- STOP 9
899- ENDIF
900 ELSE
901 C Tensor Integral Reduction is used
902 CALL TIRLOOP(SQUAREDSOINDEX,LOOPNUM,I_LIB,NLOOPLINE,PL,M2L
903
904=== modified file 'tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%loop_matrix.f'
905--- tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%loop_matrix.f 2020-11-27 13:41:46 +0000
906+++ tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%loop_matrix.f 2021-01-08 10:23:48 +0000
907@@ -245,7 +245,7 @@
908 C AVAILABLE OR NOT
909 LOGICAL LOOPLIBS_AVAILABLE(NLOOPLIB)
910 DATA LOOPLIBS_AVAILABLE/.TRUE.,.FALSE.,.TRUE.,.FALSE.,.FALSE.
911- $ ,.TRUE.,.TRUE./
912+ $ ,.FALSE.,.TRUE./
913 COMMON/LOOPLIBS_AV/ LOOPLIBS_AVAILABLE
914 C A FLAG TO DENOTE WHETHER THE CORRESPONDING DIRECTION TESTS
915 C AVAILABLE OR NOT IN THE LOOPLIBS
916@@ -1678,7 +1678,6 @@
917 C ech event
918 C
919 CALL CLEAR_TIR_CACHE()
920- CALL NINJA_CLEAR_INTEGRAL_CACHE()
921 CALL CLEAR_COLLIER_CACHE()
922 END
923
924
925=== modified file 'tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%polynomial.f'
926--- tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%polynomial.f 2020-08-21 10:29:35 +0000
927+++ tests/input_files/IOTestsComparison/IOExportFKSTest/test_ppw_fksall/%SubProcesses%P0_udx_wp%V0_udx_wp%polynomial.f 2021-01-08 10:23:48 +0000
928@@ -132,24 +132,6 @@
929
930 END
931
932- SUBROUTINE INVERT_MOMENTA_IN_POLYNOMIAL(NCOEFS,POLYNOMIAL)
933-C Just a handy subroutine to modify the coefficients for the
934-C tranformation q_loop -> -q_loop
935-C It is only used for the NINJA interface
936- USE POLYNOMIAL_CONSTANTS
937- IMPLICIT NONE
938-
939- INTEGER I, NCOEFS
940-
941- COMPLEX*16 POLYNOMIAL(0:NCOEFS-1)
942-
943- DO I=0,NCOEFS-1
944- IF (MOD(COEFTORANK_MAP(I),2).EQ.1) THEN
945- POLYNOMIAL(I)=-POLYNOMIAL(I)
946- ENDIF
947- ENDDO
948-
949- END
950
951 C Now the routines to update the wavefunctions
952
953@@ -251,24 +233,6 @@
954
955 END
956
957- SUBROUTINE MP_INVERT_MOMENTA_IN_POLYNOMIAL(NCOEFS,POLYNOMIAL)
958-C Just a handy subroutine to modify the coefficients for the
959-C tranformation q_loop -> -q_loop
960-C It is only used for the NINJA interface
961- USE POLYNOMIAL_CONSTANTS
962- IMPLICIT NONE
963-
964- INTEGER I, NCOEFS
965-
966- COMPLEX*32 POLYNOMIAL(0:NCOEFS-1)
967-
968- DO I=0,NCOEFS-1
969- IF (MOD(COEFTORANK_MAP(I),2).EQ.1) THEN
970- POLYNOMIAL(I)=-POLYNOMIAL(I)
971- ENDIF
972- ENDDO
973-
974- END
975
976 C Now the routines to update the wavefunctions
977
978
979=== modified file 'tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%CT_interface.f'
980--- tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%CT_interface.f 2020-08-21 10:06:33 +0000
981+++ tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%CT_interface.f 2021-01-08 10:23:48 +0000
982@@ -325,275 +325,6 @@
983
984
985
986-C ===========================================
987-C ===== Beginning of Ninja interface =====
988-C ===========================================
989-
990- SUBROUTINE MG5_1_NINJA_LOOP(NLOOPLINE,PL,M2L,RANK,RES,STABLE)
991-C
992-C Module used
993-C
994- USE MNINJA
995-C
996-C Generated by MadGraph5_aMC@NLO v. %(version)s, %(date)s
997-C By the MadGraph5_aMC@NLO Development Team
998-C Visit launchpad.net/madgraph5 and amcatnlo.web.cern.ch
999-C
1000-C Interface between MG5 and Ninja.
1001-C
1002-C Process: u u~ > u u~ [ virt = QCD ] @1
1003-C
1004-C
1005-C CONSTANTS
1006-C
1007- INTEGER NEXTERNAL
1008- PARAMETER (NEXTERNAL=4)
1009- LOGICAL CHECKPCONSERVATION
1010- PARAMETER (CHECKPCONSERVATION=.TRUE.)
1011- REAL*8 NORMALIZATION
1012- PARAMETER (NORMALIZATION = 1.D0/(16.D0*3.14159265358979323846D0*
1013- $ *2))
1014- INTEGER NLOOPGROUPS
1015- PARAMETER (NLOOPGROUPS=13)
1016-C These are constants related to the split orders
1017- INTEGER NSQUAREDSO
1018- PARAMETER (NSQUAREDSO=1)
1019- INCLUDE 'loop_max_coefs.inc'
1020-C
1021-C ARGUMENTS
1022-C
1023- INTEGER NLOOPLINE, RANK
1024- REAL*8 PL(0:3,NLOOPLINE)
1025- COMPLEX*16 M2L(NLOOPLINE)
1026- COMPLEX*16 RES(3)
1027- LOGICAL STABLE
1028-C
1029-C LOCAL VARIABLES
1030-C
1031- REAL*8 P_TMP(0:3,0:NLOOPLINE-1),ABSP_TMP(0:3)
1032- REAL*8 REF_P
1033- REAL*8 P_NINJA(0:3,NLOOPLINE)
1034- REAL*8 P_S_MAT(NLOOPLINE,0:3)
1035- COMPLEX*16 M2L_NINJA(NLOOPLINE)
1036- COMPLEX*16 NINJA_RES(0:2)
1037- COMPLEX*16 R1
1038- INTEGER NINJA_STATUS
1039- INTEGER I, J, K
1040- REAL*8 PDEN_DUMMY(0:3,NLOOPLINE-1)
1041-
1042- COMPLEX*16 S_MAT(NLOOPLINE,NLOOPLINE)
1043- REAL*8 REAL_S_MAT(NLOOPLINE,NLOOPLINE)
1044-
1045- INTEGER CURR_MAXCOEF
1046- COMPLEX*16, ALLOCATABLE :: TENSORCOEFS(:)
1047-
1048-C
1049-C GLOBAL VARIABLES
1050-C
1051- INCLUDE 'coupl.inc'
1052-
1053- LOGICAL CTINIT, TIRINIT, GOLEMINIT, SAMURAIINIT, NINJAINIT
1054- $ ,COLLIERINIT
1055- COMMON/REDUCTIONCODEINIT/CTINIT,TIRINIT,GOLEMINIT,SAMURAIINIT
1056- $ ,NINJAINIT,COLLIERINIT
1057-
1058- REAL*8 LSCALE
1059- INTEGER CTMODE
1060- COMMON/MG5_1_CT/LSCALE,CTMODE
1061-
1062- INTEGER ID,SQSOINDEX,R
1063- COMMON/MG5_1_LOOP/ID,SQSOINDEX,R
1064- COMPLEX*16 LOOPCOEFS(0:LOOPMAXCOEFS-1,NSQUAREDSO,NLOOPGROUPS)
1065- COMMON/MG5_1_LCOEFS/LOOPCOEFS
1066-
1067- LOGICAL FPE_IN_DP_REDUCTION, FPE_IN_QP_REDUCTION
1068- COMMON/MG5_1_FPE_IN_REDUCTION/FPE_IN_DP_REDUCTION,
1069- $ FPE_IN_QP_REDUCTION
1070-
1071-C ----------
1072-C BEGIN CODE
1073-C ----------
1074-
1075-C For the direction test, we must switch the direction in which
1076-C the loop is read for CTMode equal to 2 or 4.
1077- CALL MG5_1_SWITCH_ORDER(CTMODE,NLOOPLINE,PL,PDEN_DUMMY,M2L)
1078-
1079-C The CT initialization is also performed here if not done already
1080-C because it calls MPINIT of OneLOop which is necessary on some
1081-C system
1082- IF (CTINIT) THEN
1083- CTINIT=.FALSE.
1084- CALL MG5_1_INITCT()
1085- ENDIF
1086-
1087-C INITIALIZE NINJA IF NEEDED
1088- IF (NINJAINIT) THEN
1089- NINJAINIT=.FALSE.
1090- CALL MG5_1_INITNINJA()
1091- ENDIF
1092-
1093-C CONVERT THE MASSES TO BE COMPLEX
1094- DO I=1,NLOOPLINE
1095- M2L_NINJA(I)=M2L(I)
1096- ENDDO
1097-
1098-C CONVERT THE MOMENTA FLOWING IN THE LOOP LINES TO NINJA
1099-C CONVENTIONS
1100- DO I=0,3
1101- ABSP_TMP = 0.D0
1102- DO J=0,(NLOOPLINE-1)
1103- P_TMP(I,J)=0.D0
1104- ENDDO
1105- ENDDO
1106- DO I=0,3
1107- DO J=1,NLOOPLINE
1108- P_TMP(I,0)=P_TMP(I,0)+PL(I,J)
1109- ABSP_TMP(I) = ABSP_TMP(I)+ABS(PL(I,J))
1110- ENDDO
1111- ENDDO
1112- REF_P = MAX(ABSP_TMP(0), ABSP_TMP(1),ABSP_TMP(2),ABSP_TMP(3))
1113- DO I=0,3
1114- ABSP_TMP(I) = MAX(REF_P*1E-6, ABSP_TMP(I))
1115- ENDDO
1116-
1117- IF (CHECKPCONSERVATION.AND.REF_P.GT.1D-8) THEN
1118- IF ((P_TMP(0,0)/ABSP_TMP(0)).GT.1.D-6) THEN
1119- WRITE(*,*) 'energy is not conserved (flag:CT692)',P_TMP(0,0)
1120- STOP 'energy is not conserved (flag:CT692)'
1121- ELSEIF ((P_TMP(1,0)/ABSP_TMP(1)).GT.1.D-6) THEN
1122- WRITE(*,*) 'px is not conserved (flag:CT692)',P_TMP(1,0)
1123- STOP 'px is not conserved (flag:CT692)'
1124- ELSEIF ((P_TMP(2,0)/ABSP_TMP(2)).GT.1.D-6) THEN
1125- WRITE(*,*) 'py is not conserved (flag:CT692)',P_TMP(2,0)
1126- STOP 'py is not conserved (flag:CT692)'
1127- ELSEIF ((P_TMP(3,0)/ABSP_TMP(3)).GT.1.D-6) THEN
1128- WRITE(*,*) 'pz is not conserved (flag:CT692)',P_TMP(3,0)
1129- STOP 'pz is not conserved (flag:CT692)'
1130- ENDIF
1131- ENDIF
1132- DO I=0,3
1133- DO J=1,(NLOOPLINE-1)
1134- DO K=1,J
1135- P_TMP(I,J)=P_TMP(I,J)+PL(I,K)
1136- ENDDO
1137- ENDDO
1138- ENDDO
1139-C In Ninja, the loop line index starts at 1
1140- DO I=0,NLOOPLINE-1
1141- P_NINJA(0,I+1) = P_TMP(0,I)
1142- P_NINJA(1,I+1) = P_TMP(1,I)
1143- P_NINJA(2,I+1) = P_TMP(2,I)
1144- P_NINJA(3,I+1) = P_TMP(3,I)
1145- ENDDO
1146-
1147-C Number of coefficients for the current rank
1148- CURR_MAXCOEF = 0
1149- DO I=0,RANK
1150- CURR_MAXCOEF=CURR_MAXCOEF+(3+I)*(2+I)*(1+I)/6
1151- ENDDO
1152-C Now write the tensor coefficients for Ninja
1153-C It should never be allocated at this stage
1154- IF (.NOT. ALLOCATED(TENSORCOEFS)) THEN
1155- ALLOCATE(TENSORCOEFS(0:CURR_MAXCOEF-1))
1156- ENDIF
1157- DO I=0,CURR_MAXCOEF-1
1158- TENSORCOEFS(I) = LOOPCOEFS(I,SQSOINDEX,ID)
1159- ENDDO
1160-C The loop momentum is in fact q_loop -> -q_loop, so that the
1161-C coefficients must be changed accordingly
1162- CALL MG5_1_INVERT_MOMENTA_IN_POLYNOMIAL(CURR_MAXCOEF,TENSORCOEFS)
1163-
1164-C Compute the kinematic matrix
1165- DO J=1,NLOOPLINE
1166- DO I=0,3
1167- P_S_MAT(J,I)=P_NINJA(I,J)
1168- ENDDO
1169- ENDDO
1170- CALL MG5_1_BUILD_KINEMATIC_MATRIX(NLOOPLINE,P_S_MAT,M2L,S_MAT)
1171-
1172- DO I=1,NLOOPLINE
1173- DO J=1,NLOOPLINE
1174- REAL_S_MAT(I,J) = DBLE(S_MAT(I,J)+M2L(I)+M2L(J))
1175- ENDDO
1176- ENDDO
1177-
1178-C Below is the call specifying the kinematic matrix
1179- CALL NINJA_TENSOR_EVALUATE(TENSORCOEFS,NLOOPLINE,RANK,REAL_S_MAT
1180- $ ,P_NINJA,M2L,MU_R**2,NINJA_RES,R1,NINJA_STATUS)
1181-
1182-C Below is the call without specification of the kinematic matrix
1183-C call ninja_tensor_evaluate(TENSORCOEFS,NLOOPLINE,RANK,P_NINJA,M2L
1184-C ,MU_R**2,NINJA_RES,R1,NINJA_STATUS)
1185-
1186-C If a floating point exception was found in Ninja (e.g. exactly
1187-C zero gram. det.)
1188-C Then warn loop_matrix.f so that it will flag this kinematic
1189-C point as unstable no matter what.
1190- IF (NINJA_STATUS.EQ.NINJA_UNSTABLE_KINEMATICS) THEN
1191- FPE_IN_DP_REDUCTION = .TRUE.
1192- ENDIF
1193-
1194-C Make sure to deallocate the tensor of coefficients
1195- IF (ALLOCATED(TENSORCOEFS)) THEN
1196- DEALLOCATE(TENSORCOEFS)
1197- ENDIF
1198-
1199- RES(1)=NORMALIZATION*2.0D0*DBLE(NINJA_RES(0))
1200- RES(2)=NORMALIZATION*2.0D0*DBLE(NINJA_RES(1))
1201- RES(3)=NORMALIZATION*2.0D0*DBLE(NINJA_RES(2))
1202-C WRITE(*,*) 'Ninja: Loop ID',ID,' =',RES(1),RES(2),RES(3)
1203- END
1204-
1205-C
1206-C The Ninja version installed does not support quadruple precision
1207-C so that the corresponding subroutines are not output.
1208-C
1209-
1210- SUBROUTINE MG5_1_INITNINJA()
1211-C
1212-C Module used
1213-C
1214- USE MNINJA
1215-C
1216-C Initialization of Ninja
1217-C
1218-C LOCAL VARIABLES
1219-C
1220- INTEGER LOOPLIB
1221-C
1222-C GLOBAL VARIABLES
1223-C
1224- INCLUDE 'MadLoopParams.inc'
1225-C ----------
1226-C BEGIN CODE
1227-C ----------
1228-
1229-C LOOPLIB SET WHAT LIBRARY NINJA USES
1230-C 1 -> LOOPTOOLS
1231-C 2 -> AVH
1232-C 3 -> QCDLOOP
1233- IF (CTLOOPLIBRARY.EQ.1) THEN
1234- WRITE(*,*) 'Warning in Ninja initialization. LoopTools is not'
1235- $ //' supported by the Ninja interface. It will use OneLOop'
1236- $ //' instead.'
1237- LOOPLIB = 1
1238- ELSEIF (CTLOOPLIBRARY.EQ.3) THEN
1239- WRITE(*,*) 'Warning in Ninja initialization. LoopTools is not'
1240- $ //' supported by the Ninja interface. It will use OneLOop'
1241- $ //' instead.'
1242- LOOPLIB = 1
1243- ELSEIF (CTLOOPLIBRARY.EQ.2) THEN
1244- LOOPLIB = 1
1245- ELSE
1246- WRITE(*,*) 'Error in Ninja initialization. Loop library ID='
1247- $ ,CTLOOPLIBRARY,' is not supported. Change variable'
1248- $ //' CTLoopLibrary in MadLoopParams.dat.'
1249- STOP 1
1250- ENDIF
1251- CALL NINJA_SET_INTEGRAL_LIBRARY(LOOPLIB)
1252-
1253- END
1254-
1255 SUBROUTINE MG5_1_LOOP_4(W1, W2, W3, W4, M1, M2, M3, M4, RANK,
1256 $ SQUAREDSOINDEX, LOOPNUM)
1257 INTEGER NEXTERNAL
1258@@ -716,17 +447,6 @@
1259 C CutTools is used
1260 CALL MG5_1_CTLOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1
1261 $ ,SQUAREDSOINDEX,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
1262- ELSEIF (MLREDUCTIONLIB(I_LIB).EQ.6) THEN
1263-C Ninja is used
1264- IF (.NOT.DOING_QP) THEN
1265- CALL MG5_1_NINJA_LOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1
1266- $ ,SQUAREDSOINDEX,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
1267- ELSE
1268- WRITE(*,*) 'ERROR: Ninja should not be called in quadruple'
1269- $ //' precision since the installed version considered does'
1270- $ //' not support it.'
1271- STOP 9
1272- ENDIF
1273 ELSE
1274 C Tensor Integral Reduction is used
1275 CALL MG5_1_TIRLOOP(SQUAREDSOINDEX,LOOPNUM,I_LIB,NLOOPLINE,PL
1276@@ -861,17 +581,6 @@
1277 C CutTools is used
1278 CALL MG5_1_CTLOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1
1279 $ ,SQUAREDSOINDEX,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
1280- ELSEIF (MLREDUCTIONLIB(I_LIB).EQ.6) THEN
1281-C Ninja is used
1282- IF (.NOT.DOING_QP) THEN
1283- CALL MG5_1_NINJA_LOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1
1284- $ ,SQUAREDSOINDEX,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
1285- ELSE
1286- WRITE(*,*) 'ERROR: Ninja should not be called in quadruple'
1287- $ //' precision since the installed version considered does'
1288- $ //' not support it.'
1289- STOP 9
1290- ENDIF
1291 ELSE
1292 C Tensor Integral Reduction is used
1293 CALL MG5_1_TIRLOOP(SQUAREDSOINDEX,LOOPNUM,I_LIB,NLOOPLINE,PL
1294@@ -1004,17 +713,6 @@
1295 C CutTools is used
1296 CALL MG5_1_CTLOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1
1297 $ ,SQUAREDSOINDEX,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
1298- ELSEIF (MLREDUCTIONLIB(I_LIB).EQ.6) THEN
1299-C Ninja is used
1300- IF (.NOT.DOING_QP) THEN
1301- CALL MG5_1_NINJA_LOOP(NLOOPLINE,PL,M2L,RANK,LOOPRES(1
1302- $ ,SQUAREDSOINDEX,LOOPNUM),S(SQUAREDSOINDEX,LOOPNUM))
1303- ELSE
1304- WRITE(*,*) 'ERROR: Ninja should not be called in quadruple'
1305- $ //' precision since the installed version considered does'
1306- $ //' not support it.'
1307- STOP 9
1308- ENDIF
1309 ELSE
1310 C Tensor Integral Reduction is used
1311 CALL MG5_1_TIRLOOP(SQUAREDSOINDEX,LOOPNUM,I_LIB,NLOOPLINE,PL
1312
1313=== modified file 'tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%loop_matrix.f'
1314--- tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%loop_matrix.f 2020-08-21 10:29:35 +0000
1315+++ tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%loop_matrix.f 2021-01-08 10:23:48 +0000
1316@@ -244,7 +244,7 @@
1317 C AVAILABLE OR NOT
1318 LOGICAL LOOPLIBS_AVAILABLE(NLOOPLIB)
1319 DATA LOOPLIBS_AVAILABLE/.TRUE.,.FALSE.,.TRUE.,.FALSE.,.FALSE.
1320- $ ,.TRUE.,.TRUE./
1321+ $ ,.FALSE.,.TRUE./
1322 COMMON/MG5_1_LOOPLIBS_AV/ LOOPLIBS_AVAILABLE
1323 C A FLAG TO DENOTE WHETHER THE CORRESPONDING DIRECTION TESTS
1324 C AVAILABLE OR NOT IN THE LOOPLIBS
1325@@ -1679,7 +1679,6 @@
1326 C ech event
1327 C
1328 CALL MG5_1_CLEAR_TIR_CACHE()
1329- CALL NINJA_CLEAR_INTEGRAL_CACHE()
1330 CALL MG5_1_CLEAR_COLLIER_CACHE()
1331 END
1332
1333
1334=== modified file 'tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%polynomial.f'
1335--- tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%polynomial.f 2020-08-21 10:29:35 +0000
1336+++ tests/input_files/IOTestsComparison/TestCmdMatchBox/MatchBoxOutput/%TEST%SubProcesses%P1_uux_uux%polynomial.f 2021-01-08 10:23:48 +0000
1337@@ -133,24 +133,6 @@
1338
1339 END
1340
1341- SUBROUTINE MG5_1_INVERT_MOMENTA_IN_POLYNOMIAL(NCOEFS,POLYNOMIAL)
1342-C Just a handy subroutine to modify the coefficients for the
1343-C tranformation q_loop -> -q_loop
1344-C It is only used for the NINJA interface
1345- USE MG5_1_POLYNOMIAL_CONSTANTS
1346- IMPLICIT NONE
1347-
1348- INTEGER I, NCOEFS
1349-
1350- COMPLEX*16 POLYNOMIAL(0:NCOEFS-1)
1351-
1352- DO I=0,NCOEFS-1
1353- IF (MOD(COEFTORANK_MAP(I),2).EQ.1) THEN
1354- POLYNOMIAL(I)=-POLYNOMIAL(I)
1355- ENDIF
1356- ENDDO
1357-
1358- END
1359
1360 C Now the routines to update the wavefunctions
1361
1362@@ -253,25 +235,6 @@
1363
1364 END
1365
1366- SUBROUTINE MP_MG5_1_INVERT_MOMENTA_IN_POLYNOMIAL(NCOEFS
1367- $ ,POLYNOMIAL)
1368-C Just a handy subroutine to modify the coefficients for the
1369-C tranformation q_loop -> -q_loop
1370-C It is only used for the NINJA interface
1371- USE MG5_1_POLYNOMIAL_CONSTANTS
1372- IMPLICIT NONE
1373-
1374- INTEGER I, NCOEFS
1375-
1376- COMPLEX*32 POLYNOMIAL(0:NCOEFS-1)
1377-
1378- DO I=0,NCOEFS-1
1379- IF (MOD(COEFTORANK_MAP(I),2).EQ.1) THEN
1380- POLYNOMIAL(I)=-POLYNOMIAL(I)
1381- ENDIF
1382- ENDDO
1383-
1384- END
1385
1386 C Now the routines to update the wavefunctions
1387
1388
1389=== modified file 'tests/input_files/IOTestsComparison/long_ML_SMQCD_default/dux_mumvmxg/%..%..%Source%MODEL%model_functions.f'
1390--- tests/input_files/IOTestsComparison/long_ML_SMQCD_default/dux_mumvmxg/%..%..%Source%MODEL%model_functions.f 2020-08-21 10:06:33 +0000
1391+++ tests/input_files/IOTestsComparison/long_ML_SMQCD_default/dux_mumvmxg/%..%..%Source%MODEL%model_functions.f 2021-01-08 10:23:48 +0000
1392@@ -207,8 +207,8 @@
1393 COMPLEX*32 FUNCTION MP_REGLOG(ARG_IN)
1394 IMPLICIT NONE
1395 COMPLEX*32 TWOPII
1396- PARAMETER (TWOPII=2.0E0_16
1397- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1398+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1399+ $0_16*(0.0E0_16,1.0E0_16))
1400 COMPLEX*32 ARG_IN
1401 COMPLEX*32 ARG
1402 ARG=ARG_IN
1403@@ -228,8 +228,8 @@
1404 COMPLEX*32 FUNCTION MP_REGLOGP(ARG_IN)
1405 IMPLICIT NONE
1406 COMPLEX*32 TWOPII
1407- PARAMETER (TWOPII=2.0E0_16
1408- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1409+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1410+ $0_16*(0.0E0_16,1.0E0_16))
1411 COMPLEX*32 ARG_IN
1412 COMPLEX*32 ARG
1413 ARG=ARG_IN
1414@@ -254,8 +254,8 @@
1415 COMPLEX*32 FUNCTION MP_REGLOGM(ARG_IN)
1416 IMPLICIT NONE
1417 COMPLEX*32 TWOPII
1418- PARAMETER (TWOPII=2.0E0_16
1419- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1420+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1421+ $0_16*(0.0E0_16,1.0E0_16))
1422 COMPLEX*32 ARG_IN
1423 COMPLEX*32 ARG
1424 ARG=ARG_IN
1425@@ -294,8 +294,8 @@
1426 COMPLEX*32 FUNCTION MP_GRREGLOG(LOGSW,EXPR1_IN,EXPR2_IN)
1427 IMPLICIT NONE
1428 COMPLEX*32 TWOPII
1429- PARAMETER (TWOPII=2.0E0_16
1430- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1431+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1432+ $0_16*(0.0E0_16,1.0E0_16))
1433 COMPLEX*32 EXPR1_IN,EXPR2_IN
1434 COMPLEX*32 EXPR1,EXPR2
1435 REAL*16 LOGSW
1436
1437=== modified file 'tests/input_files/IOTestsComparison/long_ML_SMQCD_default/gg_wmtbx/%..%..%Source%MODEL%model_functions.f'
1438--- tests/input_files/IOTestsComparison/long_ML_SMQCD_default/gg_wmtbx/%..%..%Source%MODEL%model_functions.f 2020-08-21 10:06:33 +0000
1439+++ tests/input_files/IOTestsComparison/long_ML_SMQCD_default/gg_wmtbx/%..%..%Source%MODEL%model_functions.f 2021-01-08 10:23:48 +0000
1440@@ -207,8 +207,8 @@
1441 COMPLEX*32 FUNCTION MP_REGLOG(ARG_IN)
1442 IMPLICIT NONE
1443 COMPLEX*32 TWOPII
1444- PARAMETER (TWOPII=2.0E0_16
1445- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1446+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1447+ $0_16*(0.0E0_16,1.0E0_16))
1448 COMPLEX*32 ARG_IN
1449 COMPLEX*32 ARG
1450 ARG=ARG_IN
1451@@ -228,8 +228,8 @@
1452 COMPLEX*32 FUNCTION MP_REGLOGP(ARG_IN)
1453 IMPLICIT NONE
1454 COMPLEX*32 TWOPII
1455- PARAMETER (TWOPII=2.0E0_16
1456- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1457+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1458+ $0_16*(0.0E0_16,1.0E0_16))
1459 COMPLEX*32 ARG_IN
1460 COMPLEX*32 ARG
1461 ARG=ARG_IN
1462@@ -254,8 +254,8 @@
1463 COMPLEX*32 FUNCTION MP_REGLOGM(ARG_IN)
1464 IMPLICIT NONE
1465 COMPLEX*32 TWOPII
1466- PARAMETER (TWOPII=2.0E0_16
1467- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1468+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1469+ $0_16*(0.0E0_16,1.0E0_16))
1470 COMPLEX*32 ARG_IN
1471 COMPLEX*32 ARG
1472 ARG=ARG_IN
1473@@ -294,8 +294,8 @@
1474 COMPLEX*32 FUNCTION MP_GRREGLOG(LOGSW,EXPR1_IN,EXPR2_IN)
1475 IMPLICIT NONE
1476 COMPLEX*32 TWOPII
1477- PARAMETER (TWOPII=2.0E0_16
1478- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1479+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1480+ $0_16*(0.0E0_16,1.0E0_16))
1481 COMPLEX*32 EXPR1_IN,EXPR2_IN
1482 COMPLEX*32 EXPR1,EXPR2
1483 REAL*16 LOGSW
1484
1485=== modified file 'tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/dux_mumvmxg/%..%..%Source%MODEL%model_functions.f'
1486--- tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/dux_mumvmxg/%..%..%Source%MODEL%model_functions.f 2020-08-21 10:06:33 +0000
1487+++ tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/dux_mumvmxg/%..%..%Source%MODEL%model_functions.f 2021-01-08 10:23:48 +0000
1488@@ -207,8 +207,8 @@
1489 COMPLEX*32 FUNCTION MP_REGLOG(ARG_IN)
1490 IMPLICIT NONE
1491 COMPLEX*32 TWOPII
1492- PARAMETER (TWOPII=2.0E0_16
1493- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1494+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1495+ $0_16*(0.0E0_16,1.0E0_16))
1496 COMPLEX*32 ARG_IN
1497 COMPLEX*32 ARG
1498 ARG=ARG_IN
1499@@ -228,8 +228,8 @@
1500 COMPLEX*32 FUNCTION MP_REGLOGP(ARG_IN)
1501 IMPLICIT NONE
1502 COMPLEX*32 TWOPII
1503- PARAMETER (TWOPII=2.0E0_16
1504- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1505+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1506+ $0_16*(0.0E0_16,1.0E0_16))
1507 COMPLEX*32 ARG_IN
1508 COMPLEX*32 ARG
1509 ARG=ARG_IN
1510@@ -254,8 +254,8 @@
1511 COMPLEX*32 FUNCTION MP_REGLOGM(ARG_IN)
1512 IMPLICIT NONE
1513 COMPLEX*32 TWOPII
1514- PARAMETER (TWOPII=2.0E0_16
1515- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1516+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1517+ $0_16*(0.0E0_16,1.0E0_16))
1518 COMPLEX*32 ARG_IN
1519 COMPLEX*32 ARG
1520 ARG=ARG_IN
1521@@ -294,8 +294,8 @@
1522 COMPLEX*32 FUNCTION MP_GRREGLOG(LOGSW,EXPR1_IN,EXPR2_IN)
1523 IMPLICIT NONE
1524 COMPLEX*32 TWOPII
1525- PARAMETER (TWOPII=2.0E0_16
1526- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1527+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1528+ $0_16*(0.0E0_16,1.0E0_16))
1529 COMPLEX*32 EXPR1_IN,EXPR2_IN
1530 COMPLEX*32 EXPR1,EXPR2
1531 REAL*16 LOGSW
1532
1533=== modified file 'tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/gg_wmtbx/%..%..%Source%MODEL%model_functions.f'
1534--- tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/gg_wmtbx/%..%..%Source%MODEL%model_functions.f 2020-08-21 10:06:33 +0000
1535+++ tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/gg_wmtbx/%..%..%Source%MODEL%model_functions.f 2021-01-08 10:23:48 +0000
1536@@ -207,8 +207,8 @@
1537 COMPLEX*32 FUNCTION MP_REGLOG(ARG_IN)
1538 IMPLICIT NONE
1539 COMPLEX*32 TWOPII
1540- PARAMETER (TWOPII=2.0E0_16
1541- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1542+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1543+ $0_16*(0.0E0_16,1.0E0_16))
1544 COMPLEX*32 ARG_IN
1545 COMPLEX*32 ARG
1546 ARG=ARG_IN
1547@@ -228,8 +228,8 @@
1548 COMPLEX*32 FUNCTION MP_REGLOGP(ARG_IN)
1549 IMPLICIT NONE
1550 COMPLEX*32 TWOPII
1551- PARAMETER (TWOPII=2.0E0_16
1552- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1553+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1554+ $0_16*(0.0E0_16,1.0E0_16))
1555 COMPLEX*32 ARG_IN
1556 COMPLEX*32 ARG
1557 ARG=ARG_IN
1558@@ -254,8 +254,8 @@
1559 COMPLEX*32 FUNCTION MP_REGLOGM(ARG_IN)
1560 IMPLICIT NONE
1561 COMPLEX*32 TWOPII
1562- PARAMETER (TWOPII=2.0E0_16
1563- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1564+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1565+ $0_16*(0.0E0_16,1.0E0_16))
1566 COMPLEX*32 ARG_IN
1567 COMPLEX*32 ARG
1568 ARG=ARG_IN
1569@@ -294,8 +294,8 @@
1570 COMPLEX*32 FUNCTION MP_GRREGLOG(LOGSW,EXPR1_IN,EXPR2_IN)
1571 IMPLICIT NONE
1572 COMPLEX*32 TWOPII
1573- PARAMETER (TWOPII=2.0E0_16
1574- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1575+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1576+ $0_16*(0.0E0_16,1.0E0_16))
1577 COMPLEX*32 EXPR1_IN,EXPR2_IN
1578 COMPLEX*32 EXPR1,EXPR2
1579 REAL*16 LOGSW
1580
1581=== modified file 'tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/gg_wmtbx/loop_CT_calls_1.f'
1582--- tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/gg_wmtbx/loop_CT_calls_1.f 2020-08-21 10:06:33 +0000
1583+++ tests/input_files/IOTestsComparison/long_ML_SMQCD_optimized/gg_wmtbx/loop_CT_calls_1.f 2021-01-08 10:23:48 +0000
1584@@ -97,8 +97,8 @@
1585
1586 C CutTools call for loop numbers 1,33,73
1587 CALL ML5_0_LOOP_2(7,13,DCMPLX(ZERO),DCMPLX(MDL_MB),1,I_SO,1)
1588-C CutTools call for loop numbers
1589-C 2,6,121,122,127,128,109,110,111,115,116,117
1590+C CutTools call for loop numbers 2,6,121,122,127,128,109,110,111,11
1591+C 5,116,117
1592 CALL ML5_0_LOOP_2(6,14,DCMPLX(ZERO),DCMPLX(ZERO),2,I_SO,2)
1593 C CutTools call for loop numbers 3,106,107,108
1594 CALL ML5_0_LOOP_3(5,6,7,DCMPLX(ZERO),DCMPLX(ZERO),DCMPLX(MDL_MB)
1595@@ -209,8 +209,8 @@
1596 C CutTools call for loop numbers 47
1597 CALL ML5_0_LOOP_5(1,2,4,3,5,DCMPLX(ZERO),DCMPLX(ZERO)
1598 $ ,DCMPLX(MDL_MT),DCMPLX(MDL_MB),DCMPLX(ZERO),4,I_SO,40)
1599-C CutTools call for loop numbers
1600-C 48,51,123,124,125,126,129,130,131,132
1601+C CutTools call for loop numbers 48,51,123,124,125,126,129,130,131,
1602+C 132
1603 CALL ML5_0_LOOP_3(1,2,14,DCMPLX(ZERO),DCMPLX(ZERO),DCMPLX(ZERO)
1604 $ ,3,I_SO,41)
1605 C CutTools call for loop numbers 49
1606
1607=== modified file 'tests/input_files/IOTestsComparison/short_ML_SMQCD_LoopInduced/gg_hh/%..%..%Source%MODEL%model_functions.f'
1608--- tests/input_files/IOTestsComparison/short_ML_SMQCD_LoopInduced/gg_hh/%..%..%Source%MODEL%model_functions.f 2020-08-21 10:06:33 +0000
1609+++ tests/input_files/IOTestsComparison/short_ML_SMQCD_LoopInduced/gg_hh/%..%..%Source%MODEL%model_functions.f 2021-01-08 10:23:48 +0000
1610@@ -207,8 +207,8 @@
1611 COMPLEX*32 FUNCTION MP_REGLOG(ARG_IN)
1612 IMPLICIT NONE
1613 COMPLEX*32 TWOPII
1614- PARAMETER (TWOPII=2.0E0_16
1615- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1616+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1617+ $0_16*(0.0E0_16,1.0E0_16))
1618 COMPLEX*32 ARG_IN
1619 COMPLEX*32 ARG
1620 ARG=ARG_IN
1621@@ -228,8 +228,8 @@
1622 COMPLEX*32 FUNCTION MP_REGLOGP(ARG_IN)
1623 IMPLICIT NONE
1624 COMPLEX*32 TWOPII
1625- PARAMETER (TWOPII=2.0E0_16
1626- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1627+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1628+ $0_16*(0.0E0_16,1.0E0_16))
1629 COMPLEX*32 ARG_IN
1630 COMPLEX*32 ARG
1631 ARG=ARG_IN
1632@@ -254,8 +254,8 @@
1633 COMPLEX*32 FUNCTION MP_REGLOGM(ARG_IN)
1634 IMPLICIT NONE
1635 COMPLEX*32 TWOPII
1636- PARAMETER (TWOPII=2.0E0_16
1637- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1638+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1639+ $0_16*(0.0E0_16,1.0E0_16))
1640 COMPLEX*32 ARG_IN
1641 COMPLEX*32 ARG
1642 ARG=ARG_IN
1643@@ -294,8 +294,8 @@
1644 COMPLEX*32 FUNCTION MP_GRREGLOG(LOGSW,EXPR1_IN,EXPR2_IN)
1645 IMPLICIT NONE
1646 COMPLEX*32 TWOPII
1647- PARAMETER (TWOPII=2.0E0_16
1648- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1649+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1650+ $0_16*(0.0E0_16,1.0E0_16))
1651 COMPLEX*32 EXPR1_IN,EXPR2_IN
1652 COMPLEX*32 EXPR1,EXPR2
1653 REAL*16 LOGSW
1654
1655=== modified file 'tests/input_files/IOTestsComparison/short_ML_SMQCD_default/gg_ttx/%..%..%Source%MODEL%model_functions.f'
1656--- tests/input_files/IOTestsComparison/short_ML_SMQCD_default/gg_ttx/%..%..%Source%MODEL%model_functions.f 2020-08-21 10:06:33 +0000
1657+++ tests/input_files/IOTestsComparison/short_ML_SMQCD_default/gg_ttx/%..%..%Source%MODEL%model_functions.f 2021-01-08 10:23:48 +0000
1658@@ -207,8 +207,8 @@
1659 COMPLEX*32 FUNCTION MP_REGLOG(ARG_IN)
1660 IMPLICIT NONE
1661 COMPLEX*32 TWOPII
1662- PARAMETER (TWOPII=2.0E0_16
1663- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1664+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1665+ $0_16*(0.0E0_16,1.0E0_16))
1666 COMPLEX*32 ARG_IN
1667 COMPLEX*32 ARG
1668 ARG=ARG_IN
1669@@ -228,8 +228,8 @@
1670 COMPLEX*32 FUNCTION MP_REGLOGP(ARG_IN)
1671 IMPLICIT NONE
1672 COMPLEX*32 TWOPII
1673- PARAMETER (TWOPII=2.0E0_16
1674- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1675+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1676+ $0_16*(0.0E0_16,1.0E0_16))
1677 COMPLEX*32 ARG_IN
1678 COMPLEX*32 ARG
1679 ARG=ARG_IN
1680@@ -254,8 +254,8 @@
1681 COMPLEX*32 FUNCTION MP_REGLOGM(ARG_IN)
1682 IMPLICIT NONE
1683 COMPLEX*32 TWOPII
1684- PARAMETER (TWOPII=2.0E0_16
1685- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1686+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1687+ $0_16*(0.0E0_16,1.0E0_16))
1688 COMPLEX*32 ARG_IN
1689 COMPLEX*32 ARG
1690 ARG=ARG_IN
1691@@ -294,8 +294,8 @@
1692 COMPLEX*32 FUNCTION MP_GRREGLOG(LOGSW,EXPR1_IN,EXPR2_IN)
1693 IMPLICIT NONE
1694 COMPLEX*32 TWOPII
1695- PARAMETER (TWOPII=2.0E0_16
1696- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1697+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1698+ $0_16*(0.0E0_16,1.0E0_16))
1699 COMPLEX*32 EXPR1_IN,EXPR2_IN
1700 COMPLEX*32 EXPR1,EXPR2
1701 REAL*16 LOGSW
1702
1703=== modified file 'tests/input_files/IOTestsComparison/short_ML_SMQCD_optimized/gg_ttx/%..%..%Source%MODEL%model_functions.f'
1704--- tests/input_files/IOTestsComparison/short_ML_SMQCD_optimized/gg_ttx/%..%..%Source%MODEL%model_functions.f 2020-08-21 10:06:33 +0000
1705+++ tests/input_files/IOTestsComparison/short_ML_SMQCD_optimized/gg_ttx/%..%..%Source%MODEL%model_functions.f 2021-01-08 10:23:48 +0000
1706@@ -207,8 +207,8 @@
1707 COMPLEX*32 FUNCTION MP_REGLOG(ARG_IN)
1708 IMPLICIT NONE
1709 COMPLEX*32 TWOPII
1710- PARAMETER (TWOPII=2.0E0_16
1711- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1712+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1713+ $0_16*(0.0E0_16,1.0E0_16))
1714 COMPLEX*32 ARG_IN
1715 COMPLEX*32 ARG
1716 ARG=ARG_IN
1717@@ -228,8 +228,8 @@
1718 COMPLEX*32 FUNCTION MP_REGLOGP(ARG_IN)
1719 IMPLICIT NONE
1720 COMPLEX*32 TWOPII
1721- PARAMETER (TWOPII=2.0E0_16
1722- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1723+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1724+ $0_16*(0.0E0_16,1.0E0_16))
1725 COMPLEX*32 ARG_IN
1726 COMPLEX*32 ARG
1727 ARG=ARG_IN
1728@@ -254,8 +254,8 @@
1729 COMPLEX*32 FUNCTION MP_REGLOGM(ARG_IN)
1730 IMPLICIT NONE
1731 COMPLEX*32 TWOPII
1732- PARAMETER (TWOPII=2.0E0_16
1733- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1734+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1735+ $0_16*(0.0E0_16,1.0E0_16))
1736 COMPLEX*32 ARG_IN
1737 COMPLEX*32 ARG
1738 ARG=ARG_IN
1739@@ -294,8 +294,8 @@
1740 COMPLEX*32 FUNCTION MP_GRREGLOG(LOGSW,EXPR1_IN,EXPR2_IN)
1741 IMPLICIT NONE
1742 COMPLEX*32 TWOPII
1743- PARAMETER (TWOPII=2.0E0_16
1744- $ *3.14169258478796109557151794433593750E0_16*(0.0E0_16,1.0E0_16))
1745+ PARAMETER (TWOPII=2.0E0_16*3.14169258478796109557151794433593750E
1746+ $0_16*(0.0E0_16,1.0E0_16))
1747 COMPLEX*32 EXPR1_IN,EXPR2_IN
1748 COMPLEX*32 EXPR1,EXPR2
1749 REAL*16 LOGSW
1750
1751=== modified file 'tests/time_db'
1752--- tests/time_db 2020-11-27 13:41:46 +0000
1753+++ tests/time_db 2021-01-08 10:23:48 +0000
1754@@ -1230,5 +1230,4 @@
1755 <__main__.TestSuiteModified tests=[<tests.acceptance_tests.test_cmd_amcatnlo.TestMECmdShell testMethod=test_check_ppzjj>]> 59.9299731255
1756 <__main__.TestSuiteModified tests=[<tests.parallel_tests.test_cmd_amcatnlo.MECmdShell testMethod=test_short_check_generate_events_nlo_py6pt_fsr>]> 34.7858700752
1757 <__main__.TestSuiteModified tests=[<tests.unit_tests.loop.test_loop_helas_objects.LoopHelasMatrixElementTest testMethod=test_helas_diagrams_dxd_gz>]> 2.18089485168
1758-<__main__.TestSuiteModified tests=[<tests.parallel_tests.test_aloha.TestAlohaWriter testMethod=test_short_aloha_MP_mode>]> 0.0324759483337
1759-<__main__.TestSuiteModified tests=[None]> 0.019606828689575195
1760\ No newline at end of file
1761+<__main__.TestSuiteModified tests=[<tests.parallel_tests.test_aloha.TestAlohaWriter testMethod=test_short_aloha_MP_mode>]> 0.0324759483337
1762\ No newline at end of file

Subscribers

People subscribed via source and target branches

to all changes: