|
|
|
@ -20,6 +20,156 @@ |
|
|
|
|
|
|
|
contains |
|
|
|
|
|
|
|
subroutine computeqtsubint(p, xx, qtsubout, muMult_in) |
|
|
|
use ieee_arithmetic |
|
|
|
use qtResummation |
|
|
|
use SCET |
|
|
|
use qqb_z_hardfun |
|
|
|
use Scalevar |
|
|
|
use MCFMSetupPlots |
|
|
|
use PDFerrors |
|
|
|
implicit none |
|
|
|
include 'src/Inc/mxdim.f' |
|
|
|
include 'src/Inc/mxpart.f' |
|
|
|
include 'src/Inc/npart.f' |
|
|
|
include 'src/Inc/nproc.f' |
|
|
|
include 'src/Inc/kpart.f' |
|
|
|
include 'src/Inc/kprocess.f' |
|
|
|
include 'src/Inc/nf.f' |
|
|
|
include 'src/Inc/energy.f' |
|
|
|
include 'src/Inc/dynamicscale.f' |
|
|
|
include 'src/Inc/constants.f' |
|
|
|
include 'src/Inc/initialscales.f' |
|
|
|
include 'src/Inc/xmin.f' |
|
|
|
include 'src/Inc/scale.f' |
|
|
|
include 'src/Inc/qcdcouple.f' |
|
|
|
include 'src/Inc/ewcharge.f' |
|
|
|
include 'src/Inc/ewcouple.f' |
|
|
|
|
|
|
|
real(dp), intent(in) :: p(mxpart,4) |
|
|
|
real(dp), optional :: muMult_in |
|
|
|
real(dp), intent(out) :: qtsubout |
|
|
|
real(dp), intent(in) :: xx(2) |
|
|
|
|
|
|
|
real(dp) :: muMult |
|
|
|
real(dp), allocatable :: xmsq(:) |
|
|
|
real(dp), allocatable :: results(:) |
|
|
|
|
|
|
|
real(dp) :: qsq |
|
|
|
real(dp) :: msqall(-nf:nf,-nf:nf,0:3) |
|
|
|
real(dp) :: msq(-nf:nf,-nf:nf) |
|
|
|
real(dp) :: hard(0:3) |
|
|
|
integer :: j,k, order |
|
|
|
real(dp) :: nfv, hard3(3) |
|
|
|
real(dp) :: twomass |
|
|
|
|
|
|
|
logical:: bin |
|
|
|
common/bin/bin |
|
|
|
|
|
|
|
if (present(muMult_in)) then |
|
|
|
muMult = muMult_in |
|
|
|
else |
|
|
|
muMult = 1._dp |
|
|
|
endif |
|
|
|
|
|
|
|
if (dynamicscale) then |
|
|
|
call scaleset(initscale*muMult, initfacscale*muMult, p) |
|
|
|
else |
|
|
|
call usescales(initscale*muMult, initfacscale*muMult) |
|
|
|
endif |
|
|
|
|
|
|
|
if (origkpart == ksnlo) then |
|
|
|
order = 1 |
|
|
|
elseif (origkpart == knnlo) then |
|
|
|
order = 2 |
|
|
|
elseif (origkpart == kn3lo) then |
|
|
|
order = 3 |
|
|
|
else |
|
|
|
write (*,*) __FILE__//": undefined kpart, line ", __LINE__ |
|
|
|
error stop |
|
|
|
endif |
|
|
|
|
|
|
|
if (kcase == kZ_only) then |
|
|
|
qsq = twomass(1,2,p)**2 |
|
|
|
|
|
|
|
! must not contain the axial singlet |
|
|
|
! contribution since it has no counterpart in the Z+jet |
|
|
|
! NNLO calculation |
|
|
|
call qqb_z_loop(p, musq, msqall, withaxsinglet=.false.) |
|
|
|
|
|
|
|
msqall(:,:,1) = msqall(:,:,1) * (as/4._dp/pi) |
|
|
|
msqall(:,:,2) = msqall(:,:,2) * (as/4._dp/pi)**2 |
|
|
|
msqall(:,:,3) = msqall(:,:,3) * (as/4._dp/pi)**3 |
|
|
|
elseif (kcase == kW_only) then |
|
|
|
qsq = twomass(1,2,p)**2 |
|
|
|
|
|
|
|
call hardqq3(qsq,musq,NfV,hard3) |
|
|
|
call qqb_w(p, msq) |
|
|
|
|
|
|
|
|
|
|
|
where(msq /= 0._dp) msqall(:,:,0) = msq(:,:) |
|
|
|
where(msq /= 0._dp) msqall(:,:,1) = hard3(1)*msq(:,:)*(as/2._dp/pi) |
|
|
|
where(msq /= 0._dp) msqall(:,:,2) = hard3(2)*msq(:,:)*(as/2._dp/pi)**2 |
|
|
|
where(msq /= 0._dp) msqall(:,:,3) = hard3(3)*msq(:,:)*(as/2._dp/pi)**3 |
|
|
|
|
|
|
|
else |
|
|
|
write (*,*) __FILE__//": undefined kcase, line ", __LINE__ |
|
|
|
error stop |
|
|
|
endif |
|
|
|
|
|
|
|
if (muMult == 1._dp) then |
|
|
|
|
|
|
|
allocate(xmsq(size(tcutarray)+1), source=0._dp) |
|
|
|
|
|
|
|
do j=-5,5; do k =-5,5 |
|
|
|
! cycle if no contribution through NLO |
|
|
|
if ( all(msqall(j,k,[0,1]) == 0._dp) ) cycle |
|
|
|
|
|
|
|
! coefficient in as/4/pi |
|
|
|
hard(0) = msqall(j,k,0) |
|
|
|
hard(1) = msqall(j,k,1) / msqall(j,k,0) / (as/4._dp/pi) |
|
|
|
hard(2) = msqall(j,k,2) / msqall(j,k,0) / (as/4._dp/pi)**2 |
|
|
|
hard(3) = msqall(j,k,3) / msqall(j,k,0) / (as/4._dp/pi)**3 |
|
|
|
|
|
|
|
call qtsubtraction(p, qsq, xx(1), xx(2), j, k, hard, & |
|
|
|
sqrt(musq), order, results) |
|
|
|
|
|
|
|
xmsq = xmsq + results |
|
|
|
|
|
|
|
enddo; enddo |
|
|
|
|
|
|
|
if (doMultitaucut) then |
|
|
|
scetreweight(:) = 0._dp |
|
|
|
if (xmsq(1) /= 0._dp) then |
|
|
|
scetreweight(:) = xmsq(2:size(tcutarray)+1) / xmsq(1) |
|
|
|
endif |
|
|
|
endif |
|
|
|
else ! we do scale variation |
|
|
|
allocate(xmsq(1), source=0._dp) |
|
|
|
|
|
|
|
do j=-5,5; do k =-5,5 |
|
|
|
! cycle if no contribution through NLO |
|
|
|
if ( all(msqall(j,k,[0,1]) == 0._dp) ) cycle |
|
|
|
|
|
|
|
! coefficient in as/4/pi |
|
|
|
hard(0) = msqall(j,k,0) |
|
|
|
hard(1) = msqall(j,k,1) / msqall(j,k,0) / (as/4._dp/pi) |
|
|
|
hard(2) = msqall(j,k,2) / msqall(j,k,0) / (as/4._dp/pi)**2 |
|
|
|
hard(3) = msqall(j,k,3) / msqall(j,k,0) / (as/4._dp/pi)**3 |
|
|
|
|
|
|
|
call qtsubtraction(p, qsq, xx(1), xx(2), j, k, hard, & |
|
|
|
sqrt(musq), order, results, muMult=muMult) |
|
|
|
|
|
|
|
xmsq = xmsq + results |
|
|
|
|
|
|
|
enddo; enddo |
|
|
|
|
|
|
|
endif |
|
|
|
|
|
|
|
qtsubout = xmsq(1) |
|
|
|
|
|
|
|
end subroutine computeqtsubint |
|
|
|
|
|
|
|
function qtsubint(r,wgt) |
|
|
|
use ieee_arithmetic |
|
|
|
use qtResummation |
|
|
|
@ -27,6 +177,7 @@ |
|
|
|
use qqb_z_hardfun |
|
|
|
use Scalevar |
|
|
|
use MCFMSetupPlots |
|
|
|
use PDFerrors |
|
|
|
implicit none |
|
|
|
include 'src/Inc/mxdim.f' |
|
|
|
include 'src/Inc/mxpart.f' |
|
|
|
@ -50,10 +201,11 @@ |
|
|
|
real(dp) :: p(mxpart,4), pjet(mxpart,4), pswt, xx(2) |
|
|
|
real(dp) :: val,flux,qsq |
|
|
|
real(dp) :: msqall(-nf:nf,-nf:nf,0:3) |
|
|
|
real(dp), allocatable :: results(:) |
|
|
|
real(dp), allocatable :: xmsq(:) |
|
|
|
real(dp) :: msq(-nf:nf,-nf:nf) |
|
|
|
real(dp) :: xmsq, xmsqMu |
|
|
|
real(dp) :: hard(0:3) |
|
|
|
integer :: j,k, order |
|
|
|
real(dp) :: nfv, hard3(3) |
|
|
|
|
|
|
|
! functions |
|
|
|
logical :: includedipole |
|
|
|
@ -68,8 +220,13 @@ |
|
|
|
qtsubint = 0._dp |
|
|
|
p(:,:) = 0._dp |
|
|
|
pjet(:,:) = 0._dp |
|
|
|
currentPDF = 0 |
|
|
|
|
|
|
|
if (doScalevar .and. bin) then |
|
|
|
scalereweight(:) = 1._dp |
|
|
|
endif |
|
|
|
|
|
|
|
if (any(nproc == [31,32])) then ! Z -> e e |
|
|
|
if (any(nproc == [1,6,31,32])) then ! Z -> e e or W -> e nu |
|
|
|
npart = 2 |
|
|
|
! generate phase space at zero pT |
|
|
|
if (gen_res(r,0._dp,p,pswt) .eqv. .false. ) then |
|
|
|
@ -107,70 +264,35 @@ |
|
|
|
call storeptilde(0,p) |
|
|
|
call getptildejet(0,pjet) |
|
|
|
|
|
|
|
if (dynamicscale) then |
|
|
|
call scaleset(initscale, initfacscale, p) |
|
|
|
else |
|
|
|
call usescales(initscale, initfacscale) |
|
|
|
endif |
|
|
|
|
|
|
|
flux = fbGeV2/(two*xx(1)*xx(2)*sqrts**2) |
|
|
|
|
|
|
|
if (origkpart == ksnlo) then |
|
|
|
order = 1 |
|
|
|
elseif (origkpart == knnlo) then |
|
|
|
order = 2 |
|
|
|
elseif (origkpart == kn3lo) then |
|
|
|
order = 3 |
|
|
|
else |
|
|
|
write (*,*) __FILE__//": undefined kpart, line ", __LINE__ |
|
|
|
error stop |
|
|
|
endif |
|
|
|
|
|
|
|
if (kcase == kZ_only) then |
|
|
|
qsq = twomass(1,2,p)**2 |
|
|
|
|
|
|
|
! must not contain the axial singlet |
|
|
|
! contribution since it has no counterpart in the Z+jet |
|
|
|
! NNLO calculation |
|
|
|
call qqb_z_loop(p, musq, msqall, withaxsinglet=.false.) |
|
|
|
! central value |
|
|
|
call computeqtsubint(p, xx, xmsq) |
|
|
|
|
|
|
|
msqall(:,:,1) = msqall(:,:,1) * (as/4._dp/pi) |
|
|
|
msqall(:,:,2) = msqall(:,:,2) * (as/4._dp/pi)**2 |
|
|
|
msqall(:,:,3) = msqall(:,:,3) * (as/4._dp/pi)**3 |
|
|
|
else |
|
|
|
write (*,*) __FILE__//": undefined kcase, line ", __LINE__ |
|
|
|
error stop |
|
|
|
if (doScalevar .and. bin) then |
|
|
|
if (xmsq /= 0._dp) then |
|
|
|
! multiplies by two |
|
|
|
call computeqtsubint(p, xx, xmsqMu, muMult_in=scalevarmult(1)) |
|
|
|
scalereweight(1) = xmsqMu / xmsq |
|
|
|
! divides by two |
|
|
|
call computeqtsubint(p, xx, xmsqMu, muMult_in=scalevarmult(2)) |
|
|
|
scalereweight(2) = xmsqMu / xmsq |
|
|
|
endif |
|
|
|
endif |
|
|
|
|
|
|
|
allocate(xmsq(size(tcutarray)+1), source=0._dp) |
|
|
|
|
|
|
|
do j=-5,5; do k =-5,5 |
|
|
|
! cycle if no contribution through NLO |
|
|
|
if ( all(msqall(j,k,[0,1]) == 0._dp) ) cycle |
|
|
|
|
|
|
|
! coefficient in as/4/pi |
|
|
|
hard(0) = msqall(j,k,0) |
|
|
|
hard(1) = msqall(j,k,1) / msqall(j,k,0) / (as/4._dp/pi) |
|
|
|
hard(2) = msqall(j,k,2) / msqall(j,k,0) / (as/4._dp/pi)**2 |
|
|
|
hard(3) = msqall(j,k,2) / msqall(j,k,0) / (as/4._dp/pi)**2 |
|
|
|
|
|
|
|
call qtsubtraction(p, qsq, xx(1), xx(2), j, k, hard, & |
|
|
|
sqrt(musq), order, 1._dp, results) |
|
|
|
|
|
|
|
xmsq = xmsq + results |
|
|
|
|
|
|
|
enddo; enddo |
|
|
|
|
|
|
|
flux = fbGeV2/(two*xx(1)*xx(2)*sqrts**2) |
|
|
|
qtsubint = flux*pswt*xmsq/BrnRat |
|
|
|
|
|
|
|
if (doMultitaucut) then |
|
|
|
scetreweight(:) = 0._dp |
|
|
|
if (xmsq(1) /= 0._dp) then |
|
|
|
scetreweight(:) = xmsq(2:size(tcutarray)+1) / xmsq(1) |
|
|
|
if ((maxPDFsets > 0) .and. bin) then |
|
|
|
pdfreweight(:) = 0._dp |
|
|
|
do j=1,maxPDFsets |
|
|
|
currentPDF = j |
|
|
|
if (doPDFAlphas) then |
|
|
|
call updateAlphas(scale) |
|
|
|
endif |
|
|
|
call computeqtsubint(p, xx, xmsq) |
|
|
|
pdfreweight(currentPDF) = (qtsubint - flux*pswt*xmsq/BrnRat)*wgt |
|
|
|
enddo |
|
|
|
endif |
|
|
|
|
|
|
|
qtsubint = flux*pswt*xmsq(1)/BrnRat |
|
|
|
|
|
|
|
val=qtsubint*wgt |
|
|
|
|
|
|
|
if (ieee_is_nan(val) .OR. ( .NOT. ieee_is_finite(val))) then |
|
|
|
@ -394,7 +516,6 @@ |
|
|
|
endif |
|
|
|
|
|
|
|
if (.not. passed_smallnew(p,npart,safety)) then |
|
|
|
999 continue |
|
|
|
resint = 0._dp |
|
|
|
return |
|
|
|
endif |
|
|
|
@ -491,6 +612,12 @@ |
|
|
|
call nplotter_new(pjet,val) |
|
|
|
endif |
|
|
|
|
|
|
|
return |
|
|
|
|
|
|
|
! alternate return |
|
|
|
999 continue |
|
|
|
resint = 0._dp |
|
|
|
return |
|
|
|
end function resint |
|
|
|
|
|
|
|
subroutine computeResint(r, p, p_born, qt, order, xx, resout, resexpout, muMultHard_in, muMultRes_in) |
|
|
|
@ -581,7 +708,12 @@ |
|
|
|
|
|
|
|
if (kcase == kW_only) then |
|
|
|
qsq = twomass(1,2,p)**2 |
|
|
|
if (order >= 7) then |
|
|
|
call hardqq3(qsq,musq,NfV,hard3) |
|
|
|
hard(1:2) = hard3(1:2) |
|
|
|
else |
|
|
|
call hardqq(qsq, musq, hard) |
|
|
|
endif |
|
|
|
if (boostBorn) then |
|
|
|
call qqb_w(p, msq) |
|
|
|
else |
|
|
|
@ -592,6 +724,10 @@ |
|
|
|
where(msq /= 0._dp) msqall(:,:,1) = hard(1)*msq(:,:)*(as/2._dp/pi) |
|
|
|
where(msq /= 0._dp) msqall(:,:,2) = hard(2)*msq(:,:)*(as/2._dp/pi)**2 |
|
|
|
|
|
|
|
if (order >= 7) then |
|
|
|
call hardqq3(qsq,musq,NfV,hard3) |
|
|
|
where(msq /= 0._dp) msqall(:,:,3) = hard3(3)*msq(:,:)*(as/2._dp/pi)**3 |
|
|
|
endif |
|
|
|
elseif (.false. .and. kcase == kZ_only) then |
|
|
|
qsq = twomass(1,2,p)**2 |
|
|
|
call hardqq(qsq, musq, hard) |
|
|
|
@ -1332,16 +1468,6 @@ |
|
|
|
if (pttwo(3,4,p) < 1.e-3_dp) goto 888 |
|
|
|
endif |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
!call smallnew(p,npart,*999) |
|
|
|
if (.false.) then |
|
|
|
888 continue |
|
|
|
resexpint = 0._dp |
|
|
|
return |
|
|
|
endif |
|
|
|
|
|
|
|
|
|
|
|
if (any(ieee_is_nan(p(1:npart+2,:)) .eqv. .true.)) then |
|
|
|
!write(6,*) 'Discarding NaN or infinite phase space point' |
|
|
|
resexpint = 0._dp |
|
|
|
@ -1469,6 +1595,18 @@ |
|
|
|
call nplotter_new(pjet,val) |
|
|
|
endif |
|
|
|
|
|
|
|
! boost for calculation of linPC at small qT |
|
|
|
if (resexp_linPC) then |
|
|
|
val = val / qt**3 |
|
|
|
endif |
|
|
|
|
|
|
|
return |
|
|
|
|
|
|
|
! alternate return |
|
|
|
888 continue |
|
|
|
resexpint = 0._dp |
|
|
|
return |
|
|
|
|
|
|
|
end function resexpint |
|
|
|
|
|
|
|
end module |
|
|
|
|