submodule (m_gencuts) m_gencuts_user implicit none ! we want to distinguish between multiple sets of cuts ! based on input file parameters; save them here logical, save :: ourfiducial = .false. !$omp threadprivate(ourfiducial) logical, save :: ourfiducial_tj = .false. !$omp threadprivate(ourfiducial_tj) logical, save :: ourfiducial_tjj = .false. !$omp threadprivate(ourfiducial_tjj) logical, save :: ourfiducial_tjjj = .false. !$omp threadprivate(ourfiducial_tjjj) logical, save :: bgzfiducial = .false. !$omp threadprivate(bgzfiducial) contains module function reweight_user(pjet) use types implicit none include 'src/Inc/mxpart.f' real(dp) :: reweight_user real(dp), intent(in) :: pjet(mxpart,4) real(dp) :: ptpure reweight_user = 1._dp end function module function gencuts_user(pjet, njets) use types use nplotter_singletop, only: tag_bjets, jet_bness, jet_has_mainb implicit none include 'src/Inc/mxpart.f' include 'src/Inc/runstring.f' include 'src/Inc/first.f' include 'src/Inc/mpicommon.f' logical :: gencuts_user real(dp), intent(in) :: pjet(mxpart,4) integer, intent(in) :: njets integer :: j real(dp) :: ptpure, etarappure integer :: numb logical :: good ! on first call the set of cuts is determined from the input file runstring ! bgzfiducial is a set of cuts to reproduce the results in the ! Berger, Gao, Zhu paper. The other cuts select individual top+n-jet bins. if (first) then ourfiducial = .false. ourfiducial_tj = .false. ourfiducial_tjj = .false. ourfiducial_tjjj = .false. bgzfiducial = .false. if (trim(runstring) == "ourfiducial") then ourfiducial = .true. if (rank == 0) write (*,*) "!!! OUR FIDUCIAL CUTS ENABLED !!!" elseif (trim(runstring) == "ourfiducial_tj") then ourfiducial_tj = .true. if (rank ==0) write (*,*) "!!! OUR FIDUCIAL TJ CUTS ENABLED !!!" elseif (trim(runstring) == "ourfiducial_tjj") then ourfiducial_tjj = .true. if (rank == 0) write (*,*) "!!! OUR FIDUCIAL TJJ CUTS ENABLED !!!" elseif (trim(runstring) == "ourfiducial_tjjj") then ourfiducial_tjjj = .true. if (rank == 0) write (*,*) "!!! OUR FIDUCIAL TJJJ CUTS ENABLED !!!" else bgzfiducial = .true. if (rank == 0) write (*,*) "!!! BGZ FIDUCIAL CUTS ENABLED !!!" endif first = .false. endif call tag_bjets(pjet) numb = count(jet_bness(1:njets) /= 0) ! at least one b jet if (numb < 1) then gencuts_user = .true. return endif if (ourfiducial) then ! at least one light jet if ( count(jet_bness(1:njets) == 0) < 1) then gencuts_user = .true. return endif ! if ((jet_bness(1) /= 0 .and. (abs(etarappure(pjet(5,:))) < 2.5d0)) .or. & ! (jet_bness(2) /= 0 .and. (abs(etarappure(pjet(6,:))) < 2.5d0)) .or. & ! (jet_bness(3) /= 0 .and. (abs(etarappure(pjet(7,:))) < 2.5d0)) .or. & ! (jet_bness(4) /= 0 .and. (abs(etarappure(pjet(8,:))) < 2.5d0)) & ! if ((jet_bness(1) /= 0 .and. (abs(etarappure(pjet(5,:))) < 2.5d0)) .or. & ! (jet_bness(2) /= 0 .and. (abs(etarappure(pjet(6,:))) < 2.5d0) ) & ! ) then ! ! good ! continue ! else ! gencuts_user = .true. ! return ! endif elseif (ourfiducial_tj) then ! tj final state if (njets /= 2) then gencuts_user = .true. return endif ! if ((jet_bness(1) /= 0 .and. (abs(etarappure(pjet(5,:))) < 2.5d0)) .or. & ! (jet_bness(2) /= 0 .and. (abs(etarappure(pjet(6,:))) < 2.5d0) ) & ! ) then ! ! good ! continue ! else ! gencuts_user = .true. ! return ! endif elseif (ourfiducial_tjj) then ! tjj final state if (njets /= 3) then gencuts_user = .true. return endif ! if ((jet_bness(1) /= 0 .and. (abs(etarappure(pjet(5,:))) < 2.5d0)) .or. & ! (jet_bness(2) /= 0 .and. (abs(etarappure(pjet(6,:))) < 2.5d0)) .or. & ! (jet_bness(3) /= 0 .and. (abs(etarappure(pjet(7,:))) < 2.5d0)) & ! ) then ! ! good ! continue ! else ! gencuts_user = .true. ! return ! endif elseif (ourfiducial_tjjj) then ! tjjj final state if (njets /= 4) then gencuts_user = .true. return endif ! if ((jet_bness(1) /= 0 .and. (abs(etarappure(pjet(5,:))) < 2.5d0)) .or. & ! (jet_bness(2) /= 0 .and. (abs(etarappure(pjet(6,:))) < 2.5d0)) .or. & ! (jet_bness(3) /= 0 .and. (abs(etarappure(pjet(7,:))) < 2.5d0)) .or. & ! (jet_bness(4) /= 0 .and. (abs(etarappure(pjet(8,:))) < 2.5d0)) & ! ) then ! ! good ! continue ! else ! gencuts_user = .true. ! return ! endif elseif (bgzfiducial) then if (njets /= 2) then gencuts_user = .true. return endif if (jet_bness(1) /= 0._dp .and. jet_bness(2) /= 0._dp) then if (ptpure(pjet(5,:)) > ptpure(pjet(6,:))) then if ( abs(etarappure(pjet(5,:))) > 2.4d0 ) then gencuts_user = .true. return endif else if ( abs(etarappure(pjet(6,:))) > 2.4d0 ) then gencuts_user = .true. return endif endif elseif (jet_bness(1) /= 0._dp) then if ( abs(etarappure(pjet(5,:))) > 2.4d0 ) then gencuts_user = .true. return endif elseif (jet_bness(2) /= 0._dp) then if ( abs(etarappure(pjet(6,:))) > 2.4d0 ) then gencuts_user = .true. return endif else gencuts_user = .true. return endif endif gencuts_user = .false. end function end submodule