Page MenuHomeHEPForge

No OneTemporary

This file is larger than 256 KB, so syntax highlighting was skipped.
Index: trunk/HiggsBounds-5/theo_manip.f90
===================================================================
--- trunk/HiggsBounds-5/theo_manip.f90 (revision 532)
+++ trunk/HiggsBounds-5/theo_manip.f90 (revision 533)
@@ -1,1531 +1,1538 @@
! This file is part of HiggsBounds
! -KW
!******************************************************************
module theo_manip
!******************************************************************
!use S95tables_type1
use usefulbits, only : ndat,np,Hneut,Hplus,theo,partR,hadroncolliderextras,pdesc
implicit none
type(hadroncolliderextras) :: tevS(1) ! OBSOLETE !
type(hadroncolliderextras) :: lhc7S(1) ! OBSOLETE !
type(hadroncolliderextras) :: lhc8S(1) ! OBSOLETE !
contains
!*******************************************************************
! NEW HB-5 routines:
!*******************************************************************
subroutine HB5_complete_theo
!*******************************************************************
use usefulbits, only : whichanalyses,whichinput,ndat,BRdirectinput
implicit none
if(np(Hneut)>0) then
select case(whichinput)
case('effC')
call HB5_csratios_from_effC ! (DONE, needs adjustments)
call HB5_cp_from_effC
if(.not.BRdirectinput) then
call HB5_br_from_effC
endif
case('SLHA')
call HB5_csratios_from_effC
call HB5_cp_from_effC
case('hadr')
case default
stop 'error in subroutine complete_theo (2): unknown whichinput!'
end select
endif
call complete_BRs
call check_dataset ! Checks consistency in BRs and total width
if(np(Hneut)>0)then
select case(whichanalyses)
case('onlyH','LandH','onlyP','list ')
! n.b. there's no LEP SM cross sections at the moment
call fill_theo_SM
case('onlyL')
case default
stop 'error in subroutine complete_theo (2): unknown whichinput!'
end select
endif
end subroutine HB5_complete_theo
!*******************************************************************
subroutine HB5_recalculate_theo_for_datapoint(n)
!*******************************************************************
! Does the same as complete_theo but just for the datapoint n.
use usefulbits, only : whichanalyses,whichinput,BRdirectinput
implicit none
integer, intent(in) :: n
if(np(Hneut)>0) then
select case(whichinput)
case('effC')
call HB5_csratios_from_effC_for_datapoint(n)
if(.not.BRdirectinput) then
call HB5_br_from_effC_for_datapoint(n)
endif
case('SLHA')
call HB5_csratios_from_effC_for_datapoint(n)
case('hadr','part')
case default
stop 'error in subroutine recalculate_theo_for_datapoint (1)'
end select
endif
call check_dataset ! Checks consistency in BRs and total width
if(np(Hneut)>0)then
select case(whichanalyses)
case('onlyH','LandH','onlyP','list ')
! n.b. there's no LEP SM cross sections at the moment
call fill_theo_SM_for_datapoint(n)
case('onlyL')
case default
stop 'error in subroutine recalculate_theo_for_datapoint (2)'
end select
endif
! DEBUGGING:
! write(*,*) '# --------- complete_theo debugging --------- #'
! write(*,*) 'XS(ggH)_norm at TeV: ', theo(1)%tev%XS_gg_hj_ratio
! write(*,*) 'XS(bbH)_norm at TeV: ', theo(1)%tev%XS_bb_hj_ratio
! write(*,*) 'XS(VBF)_norm at Tev: ', theo(1)%tev%XS_vbf_ratio
! write(*,*) 'XS(HZ)_norm at Tev: ', theo(1)%tev%XS_hjZ_ratio
! write(*,*) 'XS(HW)_norm at TeV: ', theo(1)%tev%XS_hjW_ratio
! write(*,*) 'XS(ttH)_norm at TeV: ', theo(1)%tev%XS_tthj_ratio
! write(*,*) 'XS(tH)_norm at TeV: ', theo(1)%tev%XS_thj_tchan_ratio
!
! write(*,*) 'XS(ggH)_norm at 7 TeV: ', theo(1)%lhc7%XS_gg_hj_ratio
! write(*,*) 'XS(bbH)_norm at 7 TeV: ', theo(1)%lhc7%XS_bb_hj_ratio
! write(*,*) 'XS(VBF)_norm at 7 Tev: ', theo(1)%lhc7%XS_vbf_ratio
! write(*,*) 'XS(HZ)_norm at 7 TeV: ', theo(1)%lhc7%XS_hjZ_ratio
! write(*,*) 'XS(HW)_norm at 7 TeV: ', theo(1)%lhc7%XS_hjW_ratio
! write(*,*) 'XS(ttH)_norm at 7 TeV: ', theo(1)%lhc7%XS_tthj_ratio
! write(*,*) 'XS(tH)_norm at 7 TeV: ', theo(1)%lhc7%XS_thj_tchan_ratio
!
! write(*,*) 'XS(ggH)_norm at 8 TeV: ', theo(1)%lhc8%XS_gg_hj_ratio
! write(*,*) 'XS(bbH)_norm at 8 TeV: ', theo(1)%lhc8%XS_bb_hj_ratio
! write(*,*) 'XS(VBF)_norm at 8 Tev: ', theo(1)%lhc8%XS_vbf_ratio
! write(*,*) 'XS(HZ)_norm at 8 TeV: ', theo(1)%lhc8%XS_hjZ_ratio
! write(*,*) 'XS(HW)_norm at 8 TeV: ', theo(1)%lhc8%XS_hjW_ratio
! write(*,*) 'XS(ttH)_norm at 8 TeV: ', theo(1)%lhc8%XS_tthj_ratio
! write(*,*) 'XS(tH)_norm at 8 TeV: ', theo(1)%lhc8%XS_thj_tchan_ratio
!
! write(*,*) 'XS(ggH)_norm at 13 TeV: ', theo(1)%lhc13%XS_gg_hj_ratio
! write(*,*) 'XS(bbH)_norm at 13 TeV: ', theo(1)%lhc13%XS_bb_hj_ratio
! write(*,*) 'XS(VBF)_norm at 13 Tev: ', theo(1)%lhc13%XS_vbf_ratio
! write(*,*) 'XS(HZ)_norm at 13 TeV: ', theo(1)%lhc13%XS_hjZ_ratio
! write(*,*) 'XS(HW)_norm at 13 TeV: ', theo(1)%lhc13%XS_hjW_ratio
! write(*,*) 'XS(ttH)_norm at 13 TeV: ', theo(1)%lhc13%XS_tthj_ratio
! write(*,*) 'XS(tH)_norm at 13 TeV: ', theo(1)%lhc13%XS_thj_tchan_ratio
! write(*,*) '# --------- end debugging --------- #'
! ------
end subroutine HB5_recalculate_theo_for_datapoint
!*******************************************************************
subroutine HB5_csratios_from_effC
! calls the subroutine csratios_from_effC_for_datapoint for each
! datapoint
!*****************************************************************
use usefulbits, only : ndat
implicit none
!--------------------------------------internal
integer :: jj
!---------------------------------------------
if(np(Hneut)<1) stop 'error in csratios_from_g2 (np(Hneut))'
do jj=1,ndat
call HB5_csratios_from_effC_for_datapoint(jj)
enddo
end subroutine HB5_csratios_from_effC
!******************************************************************
subroutine HB5_csratios_from_effC_for_datapoint(jj)
! uses the effective couplings contained in effC to calculate
! the hadronic cross section ratios
!*****************************************************************
use usefulbits, only : effC
use theory_colliderSfunctions ! TODO: this includes the ratio functions, needs to be cleaned!
use theory_XS_SM_functions
use S95tables, only : inrange
implicit none
integer, intent(in) :: jj
!--------------------------------------internal
integer :: i,j
double precision :: TEVSM_ZZ_contrib_to_VBF,TEVSM_WW_contrib_to_VBF
double precision :: Mhi
!---------------------------------------------
! relative contributuion of WW- and ZZ-fusion to VBF (in LO) for
! p p-bar collisions at SqrtS=1.96 TeV (calcuated by T. Figy with VBFNLO):s
TEVSM_ZZ_contrib_to_VBF=0.23D0
TEVSM_WW_contrib_to_VBF=0.77D0
do i=1,np(Hneut)
Mhi=theo(jj)%particle(Hneut)%M(i)
!---------------------------------------!
! LEP !
!---------------------------------------!
theo(jj)%lep%XS_hjZ_ratio(i) = effC(jj)%hjZZ(i)**2
theo(jj)%lep%XS_bbhj_ratio(i) = effC(jj)%hjbb_s(i)**2+effC(jj)%hjbb_p(i)**2
!n.b.: LEP tables with bbhj at the moment can not be applied to mixed CP Higgs
theo(jj)%lep%XS_tautauhj_ratio(i) = effC(jj)%hjtautau_s(i)**2+effC(jj)%hjtautau_p(i)**2
!n.b.: LEP tables with tautauhj at the moment can not be applied to mixed CP Higgs
!---------------------------------------!
! TEVATRON !
!---------------------------------------!
theo(jj)%tev%XS_gg_hj_ratio(i) = effC(jj)%hjgg(i)**2
theo(jj)%tev%XS_bb_hj_ratio(i) = effC(jj)%hjbb_s(i)**2 + effC(jj)%hjbb_p(i)**2
theo(jj)%tev%XS_hjb_ratio(i) = effC(jj)%hjbb_s(i)**2 + effC(jj)%hjbb_p(i)**2 ! still needed?
! calculate inclusive single Higgs production:
! n.b.: neglect cc,ss->hj for inclusive single Higgs production (in effC approximation)
if(inrange(Mhi,'TEV '))then
theo(jj)%tev%XS_hj_ratio(i) = ( theo(jj)%tev%XS_gg_hj_ratio(i)*XS_tev_gg_H_SM(Mhi) + &
& theo(jj)%tev%XS_bb_hj_ratio(i)*XS_tev_bb_H_SM(Mhi))/ &
& ( XS_tev_gg_H_SM(Mhi) + XS_tev_bb_H_SM(Mhi) )
else
theo(jj)%tev%XS_hj_ratio(i) = 0.0D0
endif
theo(jj)%tev%XS_vbf_ratio(i) = effC(jj)%hjWW(i)**2*TEVSM_WW_contrib_to_VBF &
& + effC(jj)%hjZZ(i)**2*TEVSM_ZZ_contrib_to_VBF
theo(jj)%tev%XS_tthj_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
theo(jj)%tev%XS_thj_tchan_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
theo(jj)%tev%XS_thj_schan_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
! n.b.: Tev tables for tthj at the moment can only use CP even Higgs
if(inrange(Mhi,'TEV '))then
! WARNING: This implementation is preliminary. Don't know how to treat a pseudoscalar
! Higgs-fermion coupling here (nobody has ever calculated this!).
theo(jj)%tev%XS_hjW_ratio(i) = ( &
& XS_WHcoeff(Mhi,'TEV ',1,.True.,.True.)*( effC(jj)%hjtt_s(i)**2 )+ &
& XS_WHcoeff(Mhi,'TEV ',2,.True.,.True.)*( effC(jj)%hjbb_s(i)**2 )+ &
& XS_WHcoeff(Mhi,'TEV ',3,.True.,.True.)* effC(jj)%hjWW(i)**2 + &
& XS_WHcoeff(Mhi,'TEV ',4,.True.,.True.)* effC(jj)%hjtt_s(i) * effC(jj)%hjWW(i) + &
& XS_WHcoeff(Mhi,'TEV ',5,.True.,.True.)* effC(jj)%hjbb_s(i) * effC(jj)%hjWW(i) + &
& XS_WHcoeff(Mhi,'TEV ',6,.True.,.True.)*( effC(jj)%hjtt_s(i) * effC(jj)%hjbb_s(i) ) &
& )/XS_WHcoeff(Mhi,'TEV ',7,.True.,.True.) ! TODO: Check correct units: pb vs fb?
theo(jj)%tev%XS_hjZ_ratio(i) = ( &
& XS_ZHcoeff(Mhi,'TEV ',1,.True.,.True.)*( effC(jj)%hjtt_s(i)**2 )+ &
& XS_ZHcoeff(Mhi,'TEV ',2,.True.,.True.)*( effC(jj)%hjbb_s(i)**2 )+ &
& XS_ZHcoeff(Mhi,'TEV ',3,.True.,.True.)* effC(jj)%hjZZ(i)**2 + &
& XS_ZHcoeff(Mhi,'TEV ',4,.True.,.True.)* effC(jj)%hjtt_s(i) * effC(jj)%hjZZ(i) + &
& XS_ZHcoeff(Mhi,'TEV ',5,.True.,.True.)* effC(jj)%hjbb_s(i) * effC(jj)%hjZZ(i) + &
& XS_ZHcoeff(Mhi,'TEV ',6,.True.,.True.)*( effC(jj)%hjtt_s(i) * effC(jj)%hjbb_s(i) ) &
& )/XS_ZHcoeff(Mhi,'TEV ',7,.True.,.True.) ! TODO: Check correct units: pb vs fb?
! write(*,*) 'XS_tev_HZ_SM(Mhi) = ', XS_tev_HZ_SM(Mhi)
else
theo(jj)%tev%XS_hjW_ratio(i) = 0.0D0
theo(jj)%tev%XS_hjZ_ratio(i) = 0.0D0
endif
!---------------------------------------!
! LHC 7 !
!---------------------------------------!
theo(jj)%lhc7%XS_gg_hj_ratio(i) = effC(jj)%hjgg(i)**2
theo(jj)%lhc7%XS_bb_hj_ratio(i) = effC(jj)%hjbb_s(i)**2 + effC(jj)%hjbb_p(i)**2
theo(jj)%lhc7%XS_hjb_ratio(i) = effC(jj)%hjbb_s(i)**2 + effC(jj)%hjbb_p(i)**2 ! still needed?
! calculate inclusive single Higgs production:
! n.b.: neglect cc,ss->hj for inclusive single Higgs production (in effC approximation)
if(inrange(Mhi,'LHC7 '))then
theo(jj)%lhc7%XS_hj_ratio(i) = ( theo(jj)%lhc7%XS_gg_hj_ratio(i)*XS_lhc7_gg_H_SM(Mhi) + &
& theo(jj)%lhc7%XS_bb_hj_ratio(i)*XS_lhc7_bb_H_SM(Mhi))/ &
& ( XS_lhc7_gg_H_SM(Mhi) + XS_lhc7_bb_H_SM(Mhi) )
else
theo(jj)%lhc7%XS_hj_ratio(i) = 0.0D0
endif
if(inrange(Mhi,'LHC7 '))then
theo(jj)%lhc7%XS_vbf_ratio(i) = effC(jj)%hjWW(i)**2*lhc7_rHVBF_WW(Mhi) + &
& effC(jj)%hjZZ(i)**2*lhc7_rHVBF_ZZ(Mhi)
else
theo(jj)%lhc7%XS_vbf_ratio(i) = 0.0D0
endif
theo(jj)%lhc7%XS_tthj_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
theo(jj)%lhc7%XS_thj_tchan_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
theo(jj)%lhc7%XS_thj_schan_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
! n.b.: lhc7 tables for tthj at the moment can only use CP even Higgs
if(inrange(Mhi,'LHC7 '))then
! if(Mhi.ge.10.0D0.and.Mhi.le.2000) then
! WARNING: This implementation is preliminary. Don't know how to treat a pseudoscalar
! Higgs-fermion coupling here (nobody has ever calculated this!).
theo(jj)%lhc7%XS_hjW_ratio(i) = ( &
& XS_WHcoeff(Mhi,'LHC7 ',1,.True.,.True.)*( effC(jj)%hjtt_s(i)**2 )+ &
& XS_WHcoeff(Mhi,'LHC7 ',2,.True.,.True.)*( effC(jj)%hjbb_s(i)**2 )+ &
& XS_WHcoeff(Mhi,'LHC7 ',3,.True.,.True.)* effC(jj)%hjWW(i)**2 + &
& XS_WHcoeff(Mhi,'LHC7 ',4,.True.,.True.)* effC(jj)%hjtt_s(i) * effC(jj)%hjWW(i) + &
& XS_WHcoeff(Mhi,'LHC7 ',5,.True.,.True.)* effC(jj)%hjbb_s(i) * effC(jj)%hjWW(i) + &
& XS_WHcoeff(Mhi,'LHC7 ',6,.True.,.True.)*( effC(jj)%hjtt_s(i) * effC(jj)%hjbb_s(i) ) &
& )/XS_WHcoeff(Mhi,'LHC7 ',7,.True.,.True.) ! TODO: Check correct units: pb vs fb?
theo(jj)%lhc7%XS_hjZ_ratio(i) = ( &
& XS_ZHcoeff(Mhi,'LHC7 ',1,.True.,.True.)*( effC(jj)%hjtt_s(i)**2 )+ &
& XS_ZHcoeff(Mhi,'LHC7 ',2,.True.,.True.)*( effC(jj)%hjbb_s(i)**2 )+ &
& XS_ZHcoeff(Mhi,'LHC7 ',3,.True.,.True.)* effC(jj)%hjZZ(i)**2 + &
& XS_ZHcoeff(Mhi,'LHC7 ',4,.True.,.True.)* effC(jj)%hjtt_s(i) * effC(jj)%hjZZ(i) + &
& XS_ZHcoeff(Mhi,'LHC7 ',5,.True.,.True.)* effC(jj)%hjbb_s(i) * effC(jj)%hjZZ(i) + &
& XS_ZHcoeff(Mhi,'LHC7 ',6,.True.,.True.)*( effC(jj)%hjtt_s(i) * effC(jj)%hjbb_s(i) ) &
& )/XS_ZHcoeff(Mhi,'LHC7 ',7,.True.,.True.) ! TODO: Check correct units: pb vs fb?
! write(*,*) 'XS_lhc7_HZ_SM(Mhi,.True.,.True.) = ', XS_lhc7_HZ_SM(Mhi,.True.,.True.)
else
theo(jj)%lhc7%XS_hjW_ratio(i) = 0.0D0
theo(jj)%lhc7%XS_hjZ_ratio(i) = 0.0D0
endif
!---------------------------------------!
! LHC 8 !
!---------------------------------------!
theo(jj)%lhc8%XS_gg_hj_ratio(i) = effC(jj)%hjgg(i)**2
theo(jj)%lhc8%XS_bb_hj_ratio(i) = effC(jj)%hjbb_s(i)**2 + effC(jj)%hjbb_p(i)**2
theo(jj)%lhc8%XS_hjb_ratio(i) = effC(jj)%hjbb_s(i)**2 + effC(jj)%hjbb_p(i)**2 ! still needed?
! calculate inclusive single Higgs production:
! n.b.: neglect cc,ss->hj for inclusive single Higgs production (in effC approximation)
if(inrange(Mhi,'LHC8 '))then
theo(jj)%lhc8%XS_hj_ratio(i) = ( theo(jj)%lhc8%XS_gg_hj_ratio(i)*XS_lhc8_gg_H_SM(Mhi) + &
& theo(jj)%lhc8%XS_bb_hj_ratio(i)*XS_lhc8_bb_H_SM(Mhi))/ &
& ( XS_lhc8_gg_H_SM(Mhi) + XS_lhc8_bb_H_SM(Mhi) )
else
theo(jj)%lhc8%XS_hj_ratio(i) = 0.0D0
endif
if(inrange(Mhi,'LHC8 '))then
theo(jj)%lhc8%XS_vbf_ratio(i) = effC(jj)%hjWW(i)**2*lhc8_rHVBF_WW(Mhi) + &
& effC(jj)%hjZZ(i)**2*lhc8_rHVBF_ZZ(Mhi)
else
theo(jj)%lhc8%XS_vbf_ratio(i) = 0.0D0
endif
theo(jj)%lhc8%XS_tthj_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
theo(jj)%lhc8%XS_thj_tchan_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
theo(jj)%lhc8%XS_thj_schan_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
! n.b.: lhc8 tables for tthj at the moment can only use CP even Higgs
if(inrange(Mhi,'LHC8 '))then
! if(Mhi.ge.10.0D0.and.Mhi.le.2000) then
! WARNING: This implementation is preliminary. Don't know how to treat a pseudoscalar
! Higgs-fermion coupling here (nobody has ever calculated this!).
theo(jj)%lhc8%XS_hjW_ratio(i) = ( &
& XS_WHcoeff(Mhi,'LHC8 ',1,.True.,.True.)*( effC(jj)%hjtt_s(i)**2 )+ &
& XS_WHcoeff(Mhi,'LHC8 ',2,.True.,.True.)*( effC(jj)%hjbb_s(i)**2 )+ &
& XS_WHcoeff(Mhi,'LHC8 ',3,.True.,.True.)* effC(jj)%hjWW(i)**2 + &
& XS_WHcoeff(Mhi,'LHC8 ',4,.True.,.True.)* effC(jj)%hjtt_s(i) * effC(jj)%hjWW(i) + &
& XS_WHcoeff(Mhi,'LHC8 ',5,.True.,.True.)* effC(jj)%hjbb_s(i) * effC(jj)%hjWW(i) + &
& XS_WHcoeff(Mhi,'LHC8 ',6,.True.,.True.)*( effC(jj)%hjtt_s(i) * effC(jj)%hjbb_s(i) ) &
& )/XS_WHcoeff(Mhi,'LHC8 ',7,.True.,.True.) ! TODO: Check correct units: pb vs fb?
theo(jj)%lhc8%XS_hjZ_ratio(i) = ( &
& XS_ZHcoeff(Mhi,'LHC8 ',1,.True.,.True.)*( effC(jj)%hjtt_s(i)**2 )+ &
& XS_ZHcoeff(Mhi,'LHC8 ',2,.True.,.True.)*( effC(jj)%hjbb_s(i)**2 )+ &
& XS_ZHcoeff(Mhi,'LHC8 ',3,.True.,.True.)* effC(jj)%hjZZ(i)**2 + &
& XS_ZHcoeff(Mhi,'LHC8 ',4,.True.,.True.)* effC(jj)%hjtt_s(i) * effC(jj)%hjZZ(i) + &
& XS_ZHcoeff(Mhi,'LHC8 ',5,.True.,.True.)* effC(jj)%hjbb_s(i) * effC(jj)%hjZZ(i) + &
& XS_ZHcoeff(Mhi,'LHC8 ',6,.True.,.True.)*( effC(jj)%hjtt_s(i) * effC(jj)%hjbb_s(i) ) &
& )/XS_ZHcoeff(Mhi,'LHC8 ',7,.True.,.True.) ! TODO: Check correct units: pb vs fb?
! write(*,*) 'ZHcoeff(8)', Mhi, XS_ZHcoeff(Mhi,'LHC8 ',1,.True.,.True.),&
! & XS_ZHcoeff(Mhi,'LHC8 ',2,.True.,.True.),&
! & XS_ZHcoeff(Mhi,'LHC8 ',3,.True.,.True.),&
! & XS_ZHcoeff(Mhi,'LHC8 ',4,.True.,.True.),&
! & XS_ZHcoeff(Mhi,'LHC8 ',5,.True.,.True.),&
! & XS_ZHcoeff(Mhi,'LHC8 ',6,.True.,.True.)
! write(*,*) 'XS_lhc8_HZ_SM(Mhi,.True.,.True.) = ', XS_lhc8_HZ_SM(Mhi,.True.,.True.)
else
theo(jj)%lhc8%XS_hjW_ratio(i) = 0.0D0
theo(jj)%lhc8%XS_hjZ_ratio(i) = 0.0D0
endif
!---------------------------------------!
! LHC 13 !
!---------------------------------------!
theo(jj)%lhc13%XS_gg_hj_ratio(i) = effC(jj)%hjgg(i)**2
theo(jj)%lhc13%XS_bb_hj_ratio(i) = effC(jj)%hjbb_s(i)**2 + effC(jj)%hjbb_p(i)**2
theo(jj)%lhc13%XS_hjb_ratio(i) = effC(jj)%hjbb_s(i)**2 + effC(jj)%hjbb_p(i)**2 ! still needed?
! calculate inclusive single Higgs production:
! n.b.: neglect cc,ss->hj for inclusive single Higgs production (in effC approximation)
if(inrange(Mhi,'LHC13'))then
theo(jj)%lhc13%XS_hj_ratio(i) = ( theo(jj)%lhc13%XS_gg_hj_ratio(i)*XS_lhc13_gg_H_SM(Mhi) + &
& theo(jj)%lhc13%XS_bb_hj_ratio(i)*XS_lhc13_bb_H_SM(Mhi))/ &
& ( XS_lhc13_gg_H_SM(Mhi) + XS_lhc13_bb_H_SM(Mhi) )
else
theo(jj)%lhc13%XS_hj_ratio(i) = 0.0D0
endif
if(inrange(Mhi,'LHC13'))then
theo(jj)%lhc13%XS_vbf_ratio(i) = effC(jj)%hjWW(i)**2*lhc13_rHVBF_WW(Mhi) + &
& effC(jj)%hjZZ(i)**2*lhc13_rHVBF_ZZ(Mhi)
else
theo(jj)%lhc13%XS_vbf_ratio(i) = 0.0D0
endif
theo(jj)%lhc13%XS_tthj_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
theo(jj)%lhc13%XS_thj_tchan_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
theo(jj)%lhc13%XS_thj_schan_ratio(i) = effC(jj)%hjtt_s(i)**2+effC(jj)%hjtt_p(i)**2
! n.b.: lhc13 tables for tthj at the moment can only use CP even Higgs
! write(*,*) 'inrange(Mhi,LHC13) = ' , inrange(Mhi,'LHC13')
if(inrange(Mhi,'LHC13')) then
! if(Mhi.ge.10.0D0.and.Mhi.le.2000) then
! WARNING: This implementation is preliminary. Don't know how to treat a pseudoscalar
! Higgs-fermion coupling here (nobody has ever calculated this!).
theo(jj)%lhc13%XS_hjW_ratio(i) = ( &
& XS_WHcoeff(Mhi,'LHC13',1,.True.,.True.)*( effC(jj)%hjtt_s(i)**2 )+ &
& XS_WHcoeff(Mhi,'LHC13',2,.True.,.True.)*( effC(jj)%hjbb_s(i)**2 )+ &
& XS_WHcoeff(Mhi,'LHC13',3,.True.,.True.)* effC(jj)%hjWW(i)**2 + &
& XS_WHcoeff(Mhi,'LHC13',4,.True.,.True.)* effC(jj)%hjtt_s(i) * effC(jj)%hjWW(i) + &
& XS_WHcoeff(Mhi,'LHC13',5,.True.,.True.)* effC(jj)%hjbb_s(i) * effC(jj)%hjWW(i) + &
& XS_WHcoeff(Mhi,'LHC13',6,.True.,.True.)*( effC(jj)%hjtt_s(i) * effC(jj)%hjbb_s(i) ) &
& )/XS_WHcoeff(Mhi,'LHC13',7,.True.,.True.) ! TODO: Check correct units: pb vs fb?
theo(jj)%lhc13%XS_hjZ_ratio(i) = ( &
& XS_ZHcoeff(Mhi,'LHC13',1,.True.,.True.)*( effC(jj)%hjtt_s(i)**2 )+ &
& XS_ZHcoeff(Mhi,'LHC13',2,.True.,.True.)*( effC(jj)%hjbb_s(i)**2 )+ &
& XS_ZHcoeff(Mhi,'LHC13',3,.True.,.True.)* effC(jj)%hjZZ(i)**2 + &
& XS_ZHcoeff(Mhi,'LHC13',4,.True.,.True.)* effC(jj)%hjtt_s(i) * effC(jj)%hjZZ(i) + &
& XS_ZHcoeff(Mhi,'LHC13',5,.True.,.True.)* effC(jj)%hjbb_s(i) * effC(jj)%hjZZ(i) + &
& XS_ZHcoeff(Mhi,'LHC13',6,.True.,.True.)*( effC(jj)%hjtt_s(i) * effC(jj)%hjbb_s(i) ) &
& )/XS_ZHcoeff(Mhi,'LHC13',7,.True.,.True.) ! TODO: Check correct units: pb vs fb?
! write(*,*) 'XS_lhc13_HZ_SM(Mhi,.True.,.True.) = ', XS_lhc13_HZ_SM(Mhi,.True.,.True.)
else
theo(jj)%lhc13%XS_hjW_ratio(i) = 0.0D0
theo(jj)%lhc13%XS_hjZ_ratio(i) = 0.0D0
endif
enddo
theo(jj)%lep%XS_hjhi_ratio=effC(jj)%hjhiZ**2! note only half of XS_hjhi_ratio is filled here
do j=2,np(Hneut)
do i=1,j-1
theo(jj)%lep%XS_hjhi_ratio(i,j) = theo(jj)%lep%XS_hjhi_ratio(j,i)
enddo
enddo
end subroutine HB5_csratios_from_effC_for_datapoint
!******************************************************************
subroutine HB5_cp_from_effC
! uses the effective couplings contained in effC to calculate the
! cp property of neutral higgs
!*****************************************************************
use usefulbits, only : effC,ndat,vsmall
implicit none
!--------------------------------------internal
integer :: i,jj
double precision :: max_hjff_s,max_hjff_p
!---------------------------------------------
if(np(Hneut)<1)stop 'error in cp_from_effC (np(Hneut))'
do jj=1,ndat
do i=1,np(Hneut)
max_hjff_s=max(effC(jj)%hjss_s(i),effC(jj)%hjcc_s(i),effC(jj)%hjbb_s(i), &
& effC(jj)%hjtt_s(i),effC(jj)%hjmumu_s(i),effC(jj)%hjtautau_s(i))
max_hjff_p=max(effC(jj)%hjss_p(i),effC(jj)%hjcc_p(i),effC(jj)%hjbb_p(i), &
& effC(jj)%hjtt_p(i),effC(jj)%hjmumu_p(i),effC(jj)%hjtautau_p(i))
if( max_hjff_p .lt. vsmall )then !CP even
theo(jj)%CP_value(i) = 1
elseif( max_hjff_s .lt. vsmall )then !CP odd
theo(jj)%CP_value(i) = -1
else !mixed CP
theo(jj)%CP_value(i) = 0
endif
enddo
enddo
end subroutine HB5_cp_from_effC
!******************************************************************
subroutine HB5_br_from_effC
! calls the subroutine br_from_effC_for_datapoint for each datapoint.
!*****************************************************************
use usefulbits, only : np,Hneut,ndat
implicit none
!--------------------------------------internal
integer :: jj
!---------------------------------------------
if(np(Hneut)<1)stop 'error in br_from_effC (np(Hneut))'
do jj=1,ndat
call HB5_br_from_effC_for_datapoint(jj)
enddo
end subroutine HB5_br_from_effC
!*****************************************************************
subroutine HB5_br_from_effC_for_datapoint(jj)
! uses the effective couplings contained in effC to calculate
! branching ratios
!*****************************************************************
use theory_BRfunctions
use S95tables, only : inrange
use usefulbits, only : effC,ms,mc,mt,mbmb,mmu,mtau,small
implicit none
integer, intent(in) :: jj
!--------------------------------------internal
integer :: i
double precision :: Mhi,GammaRat
!---------------------------------------------
do i=1,np(Hneut)
Mhi=theo(jj)%particle(Hneut)%M(i)
if(theo(jj)%particle(Hneut)%Mc(i).ge.small) Mhi=theo(jj)%particle(Hneut)%Mc(i)
theo(jj)%BR_hjss(i) = 0.0D0
theo(jj)%BR_hjcc(i) = 0.0D0
theo(jj)%BR_hjbb(i) = 0.0D0
theo(jj)%BR_hjmumu(i) = 0.0D0
theo(jj)%BR_hjtautau(i)= 0.0D0
theo(jj)%BR_hjWW(i) = 0.0D0
theo(jj)%BR_hjZZ(i) = 0.0D0
theo(jj)%BR_hjZga(i) = 0.0D0
theo(jj)%BR_hjgaga(i) = 0.0D0
theo(jj)%BR_hjgg(i) = 0.0D0
theo(jj)%BR_hjtt(i) = 0.0D0 ! HB5 NEW
if( inrange(Mhi,'SMBR') )then
GammaRat=theo(jj)%particle(Hneut)%GammaTot(i)/BRSM_GammaTot(Mhi)
! write(*,*) 'br_from_effC debugging: '
! write(*,*) 'i, Mh = ', i, Mhi
! write(*,*) 'GammaRat = ',GammaRat
! write(*,*) 'Couplings hss = ',effC(jj)%hjss_s(i)
! write(*,*) 'Couplings htt = ',effC(jj)%hjtt_s(i)
! write(*,*) 'Couplings hWW = ',effC(jj)%hjWW(i)
if(theo(jj)%particle(Hneut)%GammaTot(i).gt.0.0D0)then
theo(jj)%BR_hjss(i) = ( effC(jj)%hjss_s(i)**2 +effC(jj)%hjss_p(i)**2 *invbsq(ms, Mhi) ) *BRSM_Hss(Mhi) /GammaRat
theo(jj)%BR_hjcc(i) = ( effC(jj)%hjcc_s(i)**2 +effC(jj)%hjcc_p(i)**2 *invbsq(mc, Mhi) ) *BRSM_Hcc(Mhi) /GammaRat
theo(jj)%BR_hjbb(i) = ( effC(jj)%hjbb_s(i)**2 +effC(jj)%hjbb_p(i)**2 *invbsq(mbmb,Mhi) ) *BRSM_Hbb(Mhi) /GammaRat
theo(jj)%BR_hjtt(i) = ( effC(jj)%hjtt_s(i)**2 +effC(jj)%hjtt_p(i)**2 *invbsq(mt ,Mhi) ) *BRSM_Htoptop(Mhi) /GammaRat ! HB5 new
theo(jj)%BR_hjmumu(i) = ( effC(jj)%hjmumu_s(i)**2 +effC(jj)%hjmumu_p(i)**2 *invbsq(mmu, Mhi) ) *BRSM_Hmumu(Mhi) /GammaRat
theo(jj)%BR_hjtautau(i)= ( effC(jj)%hjtautau_s(i)**2+effC(jj)%hjtautau_p(i)**2*invbsq(mtau,Mhi) ) *BRSM_Htautau(Mhi) /GammaRat
theo(jj)%BR_hjWW(i) = effC(jj)%hjWW(i)**2 *BRSM_HWW(Mhi) /GammaRat
theo(jj)%BR_hjZZ(i) = effC(jj)%hjZZ(i)**2 *BRSM_HZZ(Mhi) /GammaRat
theo(jj)%BR_hjZga(i) = effC(jj)%hjZga(i)**2 *BRSM_HZga(Mhi) /GammaRat
theo(jj)%BR_hjgaga(i) = effC(jj)%hjgaga(i)**2 *BRSM_Hgaga(Mhi) /GammaRat
theo(jj)%BR_hjgg(i) = effC(jj)%hjgg(i)**2 *BRSM_Hgg(Mhi) /GammaRat
! write(*,*) 'BR h->ss = ',theo(jj)%BR_hjss(i), 'SM =',BRSM_Hss(Mhi)
! write(*,*) 'BR h->cc = ',theo(jj)%BR_hjcc(i), 'SM =',BRSM_Hcc(Mhi)
! write(*,*) 'BR h->bb = ',theo(jj)%BR_hjbb(i), 'SM =',BRSM_Hbb(Mhi)
! write(*,*) 'BR h->tt = ',theo(jj)%BR_hjtt(i), 'SM =',BRSM_Htoptop(Mhi)
! write(*,*) 'BR h->mumu = ',theo(jj)%BR_hjmumu(i), 'SM =',BRSM_Hmumu(Mhi)
! write(*,*) 'BR h->tautau = ',theo(jj)%BR_hjtautau(i), 'SM =',BRSM_Htautau(Mhi)
! write(*,*) 'BR h->WW = ',theo(jj)%BR_hjWW(i), 'SM =',BRSM_HWW(Mhi)
! write(*,*) 'BR h->ZZ = ',theo(jj)%BR_hjZZ(i), 'SM =',BRSM_HZZ(Mhi)
! write(*,*) 'BR h->gaga = ',theo(jj)%BR_hjgaga(i), 'SM =',BRSM_Hgaga(Mhi)
! write(*,*) 'BR h->gg = ',theo(jj)%BR_hjgg(i), 'SM =',BRSM_Hgg(Mhi)
! write(*,*) 'BR h->Zga = ',theo(jj)%BR_hjZga(i), 'SM =',BRSM_HZga(Mhi)
else
write(*,*)'at jj=',jj,'i=',i
write(*,*)'total decay width is less than or equal to zero:',theo(jj)%particle(Hneut)%GammaTot(i)
endif
endif
enddo
end subroutine HB5_br_from_effC_for_datapoint
!*****************************************************************
subroutine complete_BRs
implicit none
integer :: jj,i,j
! write(*,*) "# ------ complete_BRs debuggung -------#"
! copying over the (k,i,i) elements of BR_hkhjhi into BR_hjhihi.
do jj=1,ndat
do j=1,np(Hneut)
do i=1,np(Hneut)
theo(jj)%BR_hjhihi(j,i) = theo(jj)%BR_hkhjhi(j,i,i)
! write(*,"(a,I1,a,I1,a,I1,a,1E10.3)") "BR(h",j,"->h",i,"h",i,") = ",theo(jj)%BR_hjhihi(j,i)
! write(*,"(a,I1,a,I1,a,1E10.3)") "BR(h",j,"->h",i,"Z) = ",theo(jj)%BR_hjhiZ(j,i)
enddo
enddo
enddo
! write(*,*) "# ------ end debuggung -------#"
end subroutine complete_BRs
!*******************************************************************
! OLD HB-4 routines:
!******************************************************************
subroutine complete_theo ! OBSOLETE !
! This is the old routine (HB4 and earlier)
!decides what has to be done to the input and calls the appropriate
!subroutines
!******************************************************************
use usefulbits, only : whichanalyses,whichinput,ndat
implicit none
!--------------------------------------internal
integer :: i,j,jj
!----------------------------------------------
if(np(Hneut)>0)then !none if this is needed for the charged Higgs sector yet
select case(whichinput)
case('effC')
call csratios_from_g2
call cp_from_g2
call br_from_g2
case('SLHA')
call csratios_from_g2
call cp_from_g2
case('hadr','part')
case default
stop 'error in subroutine complete_theo (1)'
end select
do jj=1,ndat ! filling the other half of XS_hjhi_ratio
do j=2,np(Hneut)
do i=1,j-1
theo(jj)%lep%XS_hjhi_ratio(i,j) = theo(jj)%lep%XS_hjhi_ratio(j,i)
enddo
enddo
enddo
endif
call check_dataset !involves the charged Higgs sector
if(np(Hneut)>0)then !none if this is needed for the charged Higgs sector yet
select case(whichanalyses)
case('onlyH','LandH','onlyP','list ') ! everything which involves Tevatron and LHC tables
call fill_theo_SM ! n.b. there's no LEP SM cross sections at the moment
select case(whichinput)
case('part','effC','SLHA') ! everything except option 'hadr', where had XS ratios are inputted directly
call XS_from_partR
case('hadr')
case default
stop 'error in subroutine complete_theo (2)'
end select
case('onlyL')
case default
stop 'error in subroutine complete_theo (3)'
end select
endif
end subroutine complete_theo
!******************************************************************
subroutine recalculate_theo_for_datapoint(n) ! OBSOLETE !
! Does the same as complete_theo but just for the datapoint n.
use usefulbits, only : whichanalyses,whichinput
implicit none
integer, intent(in) :: n
if(np(Hneut)>0) then !none if this is needed for the charged Higgs sector yet
select case(whichinput)
case('effC')
call csratios_from_g2_for_datapoint(n)
call br_from_g2_for_datapoint(n)
case('SLHA')
call csratios_from_g2_for_datapoint(n)
case('hadr','part')
case default
stop 'error in subroutine recalculate_theo_for_datapoint (1)'
end select
endif
call check_dataset !involves the charged Higgs sector
if(np(Hneut)>0)then !none if this is needed for the charged Higgs sector yet
select case(whichanalyses)
case('onlyH','LandH','onlyP','list ') ! everything which involves Tevatron and LHC tables
call fill_theo_SM_for_datapoint(n) ! n.b. there's no LEP SM cross sections at the moment
select case(whichinput)
case('part','effC','SLHA') ! everything except option 'hadr', where had XS ratios are inputted directly
call XS_from_partR_for_datapoint(n)
case('hadr')
case default
stop 'error in subroutine recalculate_theo_for_datapoint (2)'
end select
case('onlyL')
case default
stop 'error in subroutine recalculate_theo_for_datapoint (3)'
end select
endif
end subroutine recalculate_theo_for_datapoint
!******************************************************************
subroutine csratios_from_g2 ! OBSOLETE !
! uses the effective couplings contained in g2 to calculate
! partonic cross section ratios, some hadronic cross section ratios
!*****************************************************************
use usefulbits, only : ndat
implicit none
!--------------------------------------internal
integer :: jj
!---------------------------------------------
if(np(Hneut)<1)stop 'error in csratios_from_g2 (np(Hneut))'
do jj=1,ndat
call csratios_from_g2_for_datapoint(jj)
enddo
end subroutine csratios_from_g2
!******************************************************************
subroutine csratios_from_g2_for_datapoint(jj) ! OBSOLETE !
! uses the effective couplings contained in g2 to calculate
! partonic cross section ratios, some hadronic cross section ratios
!*****************************************************************
use usefulbits, only : g2
use theory_colliderSfunctions
use S95tables, only : inrange
implicit none
integer, intent(in) :: jj
!--------------------------------------internal
integer :: i
double precision :: TEVSM_ZZ_contrib_to_VBF,TEVSM_WW_contrib_to_VBF
double precision :: Mhi
!---------------------------------------------
! relative contributuion of WW- and ZZ-fusion to VBF (in LO) for
! p p-bar collisions at SqrtS=1.96 TeV (calcuated by T. Figy with VBFNLO):s
TEVSM_ZZ_contrib_to_VBF=0.23D0
TEVSM_WW_contrib_to_VBF=0.77D0
do i=1,np(Hneut)
theo(jj)%lep%XS_hjZ_ratio(i) = g2(jj)%hjZZ(i)
theo(jj)%lep%XS_bbhj_ratio(i) = g2(jj)%hjbb_s(i)+g2(jj)%hjbb_p(i)!nb tables at the moment can not be applied to mixed CP Higgs
theo(jj)%lep%XS_tautauhj_ratio(i) = g2(jj)%hjtautau_s(i)+g2(jj)%hjtautau_p(i)!nb tables at the moment can not be applied to mixed CP Higgs
partR(jj)%bg_hjb(i) = g2(jj)%hjbb_s(i)+g2(jj)%hjbb_p(i)
theo(jj)%tev%XS_vbf_ratio(i) = g2(jj)%hjWW(i)*TEVSM_WW_contrib_to_VBF &
& + g2(jj)%hjZZ(i)*TEVSM_ZZ_contrib_to_VBF
theo(jj)%tev%XS_tthj_ratio(i) = g2(jj)%hjtoptop_s(i)+g2(jj)%hjtoptop_p(i) !nb tev tables at the moment can only use CP even Higgs
Mhi=theo(jj)%particle(Hneut)%M(i)
if(inrange(Mhi,'LHC7 '))then
theo(jj)%lhc7%XS_vbf_ratio(i) = g2(jj)%hjWW(i)*lhc7_rHVBF_WW(Mhi) &
& + g2(jj)%hjZZ(i)*lhc7_rHVBF_ZZ(Mhi)
else
theo(jj)%lhc7%XS_vbf_ratio(i) = 0.0D0
endif
theo(jj)%lhc7%XS_tthj_ratio(i) = g2(jj)%hjtoptop_s(i)+g2(jj)%hjtoptop_p(i) !nb no tables need this at the moment
! We are using 7 TeV ratios for VBF contribution from WW/ZZ at the moment also
! for LHC 8 TeV cross sections
if(inrange(Mhi,'LHC8 '))then
theo(jj)%lhc8%XS_vbf_ratio(i) = g2(jj)%hjWW(i)*lhc7_rHVBF_WW(Mhi) &
& + g2(jj)%hjZZ(i)*lhc7_rHVBF_ZZ(Mhi)
else
theo(jj)%lhc8%XS_vbf_ratio(i) = 0.0D0
endif
theo(jj)%lhc8%XS_tthj_ratio(i) = g2(jj)%hjtoptop_s(i)+g2(jj)%hjtoptop_p(i)
partR(jj)%qq_hjWp(:,i) = g2(jj)%hjWW(i)
partR(jj)%qq_hjWm(:,i) = g2(jj)%hjWW(i)
partR(jj)%gg_hj(i) = g2(jj)%hjgg(i)
partR(jj)%qq_hj(5,i) = g2(jj)%hjbb_s(i)+g2(jj)%hjbb_p(i)
partR(jj)%qq_hjZ(:,i) = g2(jj)%hjZZ(i)
partR(jj)%gg_hjZ(i) = g2(jj)%hjggZ(i)
enddo
theo(jj)%lep%XS_hjhi_ratio=g2(jj)%hjhiZ! note only half of XS_hjhi_ratio is filled here
end subroutine csratios_from_g2_for_datapoint
!******************************************************************
subroutine cp_from_g2 ! OBSOLETE !
! uses the effective couplings contained in g2 to calculate
! cp of neutral higgs
!*****************************************************************
use usefulbits, only : g2,ndat,vsmall
implicit none
!--------------------------------------internal
integer :: i,jj
double precision :: max_hjff_s,max_hjff_p
!---------------------------------------------
if(np(Hneut)<1)stop 'error in cp_from_g2 (np(Hneut))'
do jj=1,ndat
do i=1,np(Hneut)
max_hjff_s=max(g2(jj)%hjss_s(i),g2(jj)%hjcc_s(i),g2(jj)%hjbb_s(i), &
& g2(jj)%hjtoptop_s(i),g2(jj)%hjmumu_s(i),g2(jj)%hjtautau_s(i))
max_hjff_p=max(g2(jj)%hjss_p(i),g2(jj)%hjcc_p(i),g2(jj)%hjbb_p(i), &
& g2(jj)%hjtoptop_p(i),g2(jj)%hjmumu_p(i),g2(jj)%hjtautau_p(i))
if( max_hjff_p .lt. vsmall )then !CP even
theo(jj)%CP_value(i) = 1
elseif( max_hjff_s .lt. vsmall )then !CP odd
theo(jj)%CP_value(i) = -1
else !mixed CP
theo(jj)%CP_value(i) = 0
endif
enddo
enddo
end subroutine cp_from_g2
!******************************************************************
subroutine br_from_g2 ! OBSOLETE !
! uses the effective couplings contained in g2 to calculate
! branching ratios
!*****************************************************************
use usefulbits, only : np,Hneut,ndat
implicit none
!--------------------------------------internal
integer :: jj
!---------------------------------------------
if(np(Hneut)<1)stop 'error in br_from_g2 (np(Hneut))'
do jj=1,ndat
call br_from_g2_for_datapoint(jj)
enddo
end subroutine br_from_g2
!*****************************************************************
subroutine br_from_g2_for_datapoint(jj) ! OBSOLETE !
! uses the effective couplings contained in g2 to calculate
! branching ratios
!*****************************************************************
use theory_BRfunctions
use S95tables, only : inrange
use usefulbits, only : g2,ms,mc,mbmb,mmu,mtau,small
implicit none
integer, intent(in) :: jj
!--------------------------------------internal
integer :: i
double precision :: Mhi,GammaRat
!---------------------------------------------
do i=1,np(Hneut)
Mhi=theo(jj)%particle(Hneut)%M(i)
if(theo(jj)%particle(Hneut)%Mc(i).ge.small) Mhi=theo(jj)%particle(Hneut)%Mc(i)
theo(jj)%BR_hjss(i) = 0.0D0
theo(jj)%BR_hjcc(i) = 0.0D0
theo(jj)%BR_hjbb(i) = 0.0D0
theo(jj)%BR_hjmumu(i) = 0.0D0
theo(jj)%BR_hjtautau(i)= 0.0D0
theo(jj)%BR_hjWW(i) = 0.0D0
theo(jj)%BR_hjZZ(i) = 0.0D0
theo(jj)%BR_hjZga(i) = 0.0D0
theo(jj)%BR_hjgaga(i) = 0.0D0
theo(jj)%BR_hjgg(i) = 0.0D0
if( inrange(Mhi,'SMBR') )then
GammaRat=theo(jj)%particle(Hneut)%GammaTot(i)/BRSM_GammaTot(Mhi)
if(theo(jj)%particle(Hneut)%GammaTot(i).gt.0.0D0)then
theo(jj)%BR_hjss(i) = ( g2(jj)%hjss_s(i) +g2(jj)%hjss_p(i) *invbsq(ms, Mhi) ) *BRSM_Hss(Mhi) /GammaRat
theo(jj)%BR_hjcc(i) = ( g2(jj)%hjcc_s(i) +g2(jj)%hjcc_p(i) *invbsq(mc, Mhi) ) *BRSM_Hcc(Mhi) /GammaRat
theo(jj)%BR_hjbb(i) = ( g2(jj)%hjbb_s(i) +g2(jj)%hjbb_p(i) *invbsq(mbmb,Mhi) ) *BRSM_Hbb(Mhi) /GammaRat
theo(jj)%BR_hjmumu(i) = ( g2(jj)%hjmumu_s(i) +g2(jj)%hjmumu_p(i) *invbsq(mmu, Mhi) ) *BRSM_Hmumu(Mhi) /GammaRat
theo(jj)%BR_hjtautau(i)= ( g2(jj)%hjtautau_s(i)+g2(jj)%hjtautau_p(i)*invbsq(mtau,Mhi) ) *BRSM_Htautau(Mhi) /GammaRat
theo(jj)%BR_hjWW(i) = g2(jj)%hjWW(i) *BRSM_HWW(Mhi) /GammaRat
theo(jj)%BR_hjZZ(i) = g2(jj)%hjZZ(i) *BRSM_HZZ(Mhi) /GammaRat
theo(jj)%BR_hjZga(i) = g2(jj)%hjZga(i) *BRSM_HZga(Mhi) /GammaRat
theo(jj)%BR_hjgaga(i) = g2(jj)%hjgaga(i) *BRSM_Hgaga(Mhi) /GammaRat
theo(jj)%BR_hjgg(i) = g2(jj)%hjgg(i) *BRSM_Hgg(Mhi) /GammaRat
else
write(*,*)'at jj=',jj,'i=',i
write(*,*)'total decay width is less than or equal to zero:',theo(jj)%particle(Hneut)%GammaTot(i)
endif
endif
enddo
end subroutine br_from_g2_for_datapoint
!*****************************************************************
function invbsq(mf,mh)
implicit none
double precision,intent(in) :: mf,mh
double precision :: invbsq
if(mh>2.0D0*mf)then
invbsq=1.0D0/(1.0D0-4.0D0*(mf/mh)**2.0D0)
else
invbsq=0.0D0
endif
end function invbsq
!*****************************************************************
subroutine check_dataset
! checks each parameter point to determine whether the Higgs masses
! and branching ratios make sense
! Sets theo(jj)%gooddataset accordingly
!*****************************************************************
use usefulbits, only : theo,ndat,debug,np,vsmall
implicit none
!--------------------------------------internal
integer :: jj,kk,ll,mm,x
double precision :: testsumBR,testsumBR_t
double precision,allocatable :: testBR(:)
double precision :: fuzziness
- double precision, allocatable :: sumhjhi(:)
+ double precision, allocatable :: sumhjhi(:), sumhjHpi(:)
!---------------------------------------------
fuzziness = 0.01D0
!fuzziness = 100.0D0 ; write(*,*)'WARNING: fuzziness factor is far too high'
testsumBR =0.0D0
testsumBR_t =0.0D0
if(np(Hneut)>0)then
allocate(testBR(np(Hneut)))
allocate(sumhjhi(np(Hneut)))
+ allocate(sumhjHpi(np(Hneut)))
! testing to see if the dataset is ok
do jj=1,ndat
do kk=1,np(Hneut)
do ll=1,np(Hneut)
do mm=1,np(Hneut)
! write(*,'(a,I2,a,I2,a,I2,a,1F10.8)') "BR_hkhjhi(",kk,",",ll,",",mm,")=",theo(jj)%BR_hkhjhi(kk,ll,mm)
if(abs(theo(jj)%BR_hkhjhi(kk,ll,mm)-theo(jj)%BR_hkhjhi(kk,mm,ll)).gt.vsmall) then
if(theo(jj)%BR_hkhjhi(kk,ll,mm).lt.vsmall) then
theo(jj)%BR_hkhjhi(kk,ll,mm)=theo(jj)%BR_hkhjhi(kk,mm,ll)
! write(*,'(a,I2,a,I2,a,I2,a)') "WARNING: BR_hkhjhi is not symmetric. Correcting BR_hkhjhi(",&
! & kk,",",ll,",",mm,") element..."
else if(theo(jj)%BR_hkhjhi(kk,mm,ll).lt.vsmall) then
theo(jj)%BR_hkhjhi(kk,mm,ll)=theo(jj)%BR_hkhjhi(kk,ll,mm)
! write(*,'(a,I2,a,I2,a,I2,a)') "WARNING: BR_hkhjhi is not symmetric. Correcting BR_hkhjhi(",&
! & kk,",",mm,",",ll,") element..."
else
write(*,*) "WARNING: BR_hkhjhi is not symmetric."
endif
endif
enddo
enddo
enddo
sumhjhi = 0.0D0
do kk=lbound(theo(jj)%BR_hkhjhi,dim=1),ubound(theo(jj)%BR_hkhjhi,dim=1)
do ll=lbound(theo(jj)%BR_hkhjhi,dim=2),ubound(theo(jj)%BR_hkhjhi,dim=2)
do mm=lbound(theo(jj)%BR_hkhjhi,dim=3),ll
sumhjhi(kk) = sumhjhi(kk) + theo(jj)%BR_hkhjhi(kk,ll,mm)
! write(*,*) "kk,ll,mm, sumhjhi = ", kk, ll, mm, sumhjhi
enddo
enddo
enddo
+
+ sumhjHpi = 0.0D0
+ if(np(Hplus).gt.0) then
+ sumhjHpi = sum(theo(jj)%BR_hjHpiW,dim=2)
+ endif
testBR = theo(jj)%BR_hjss &
& + theo(jj)%BR_hjcc &
& + theo(jj)%BR_hjbb &
& + theo(jj)%BR_hjtt &
& + theo(jj)%BR_hjmumu &
& + theo(jj)%BR_hjtautau &
& + theo(jj)%BR_hjemu &
& + theo(jj)%BR_hjetau &
& + theo(jj)%BR_hjmutau &
& + theo(jj)%BR_hjWW &
& + theo(jj)%BR_hjZZ &
& + theo(jj)%BR_hjZga &
& + theo(jj)%BR_hjgg &
& + theo(jj)%BR_hjgaga &
- & + sum(theo(jj)%BR_hjhiZ,dim=2) &
- & + sumhjhi
+ & + sum(theo(jj)%BR_hjhiZ,dim=2) &
+ & + sumhjhi + sumhjHpi
! write(*,*) 'sumhjhi = ',sumhjhi
! write(*,*) 'sum(theo(jj)%BR_hjhiZ,dim=2) = ', sum(theo(jj)%BR_hjhiZ,dim=2)
! write(*,*) 'debug: testBR = ', testBR
testsumBR = maxval( testBR )
if( testsumBR .gt. 1.0D0+fuzziness )then
! if(debug)
write(*,*) 'warning: sum of BR for '//trim(adjustl(pdesc(Hneut)%long))//&
&' ',maxloc(testBR),' at line number=',jj,'is',testsumBR
write(*,*) 'BR(h',maxloc(testBR),'->WW)=',theo(jj)%BR_hjWW( maxloc(testBR) )
write(*,*) 'BR(h',maxloc(testBR),'->ZZ)=',theo(jj)%BR_hjZZ( maxloc(testBR) )
write(*,*) 'BR(h',maxloc(testBR),'->gg)=',theo(jj)%BR_hjgg( maxloc(testBR) )
write(*,*) 'BR(h',maxloc(testBR),'->gaga)=',theo(jj)%BR_hjgaga( maxloc(testBR) )
write(*,*) 'BR(h',maxloc(testBR),'->bb)=',theo(jj)%BR_hjbb( maxloc(testBR) )
write(*,*) 'BR(h',maxloc(testBR),'->tautau)=',theo(jj)%BR_hjtautau( maxloc(testBR) )
write(*,*) 'BR(h',maxloc(testBR),'->tt)=',theo(jj)%BR_hjtt( maxloc(testBR) )
write(*,*) 'BR(h',maxloc(testBR),'->hiZ)=',theo(jj)%BR_hjhiZ( maxloc(testBR),:)
write(*,*) 'sum(BR(h',maxloc(testBR),'->hjhi))=',sumhjhi( maxloc(testBR))
+ write(*,*) 'sum(BR(h',maxloc(testBR),'->HpjW))=',sumhjHpi( maxloc(testBR))
endif
enddo
deallocate(testBR)
endif
if(np(Hplus)>0)then
allocate(testBR(np(Hplus)))
do jj=1,ndat
testBR = theo(jj)%BR_Hpjcs &
& + theo(jj)%BR_Hpjcb &
& + theo(jj)%BR_Hpjtaunu
testsumBR = maxval( testBR )
testsumBR_t = theo(jj)%BR_tWpb &
& + sum(theo(jj)%BR_tHpjb,dim=1)
if( testsumBR .gt. 1.0D0+fuzziness )then
if(debug)write(*,*) 'warning: sum of BR for '//trim(adjustl(pdesc(Hplus)%long))//' at line number=',jj,'is',testsumBR
elseif( testsumBR_t .gt. 1.0D0+fuzziness )then
if(debug)write(*,*) 'warning: sum of BR for the top quark at jj=',jj,'is',testsumBR_t
endif
enddo
deallocate(testBR)
endif
do jj=1,ndat
theo(jj)%gooddataset=.True.
enddo
do x=1,ubound(np,dim=1)
if(np(x)>0)then
do jj=1,ndat
if( minval(theo(jj)%particle(x)%M).lt.0.0D0)then
theo(jj)%gooddataset=.False.
if(debug)write(*,*) 'warning: negative mass for '//trim(adjustl(pdesc(x)%long))//' at line number=',jj,theo(jj)%particle(x)%M
!elseif( testsumBR_hj .gt. (1.0D0+fuzziness) )then !i.e. branching ratios for one of the Higgs add up to more than 1+fuzziness
! !theo(jj)%gooddataset=.False.
elseif( .not. (sum(theo(jj)%particle(x)%M).ge.0.0D0) )then
theo(jj)%gooddataset=.False.
write(*,*) 'warning: mass is NaN for '//trim(adjustl(pdesc(x)%long))//' at line number=',jj,theo(jj)%particle(x)%M
elseif( minval(theo(jj)%particle(x)%GammaTot).lt.0.0D0)then
theo(jj)%gooddataset=.False.
if(debug)write(*,*) 'warning: negative total decay width for '//trim(adjustl(pdesc(x)%long))// &
& ' at line number=',jj,theo(jj)%particle(x)%GammaTot
!elseif( testsumBR_hj .gt. (1.0D0+fuzziness) )then !i.e. branching ratios for one of the Higgs add up to more than 1+fuzziness
! !theo(jj)%gooddataset=.False.
elseif( .not. (sum(theo(jj)%particle(x)%GammaTot).ge.0.0D0) )then
theo(jj)%gooddataset=.False.
if(debug)write(*,*) 'warning: total decay width is NaN for '//trim(adjustl(pdesc(x)%long))// &
& ' at line number=',jj,theo(jj)%particle(x)%GammaTot
endif
enddo
endif
enddo
end subroutine check_dataset
!*****************************************************************
subroutine fill_theo_SM
! fills the Standard Model part of theo
! We do this here to save computational time - these quantities will be
! needed a few times in subroutine calcfact_t1, so don't want to calculate them each time
!************************************************************
use theory_BRfunctions
use theory_XS_SM_functions
use usefulbits, only : ndat
use S95tables, only : inrange
implicit none
!--------------------------------------internal
integer :: n
!----------------------------------------------
if(np(Hneut)<1)stop 'error in subroutine fill_theo_SM (np(Hneut))'
do n=1,ndat
call fill_theo_SM_for_datapoint(n)
enddo
end subroutine fill_theo_SM
!*****************************************************************
subroutine fill_theo_SM_for_datapoint(n)
! fills the Standard Model part of theo
! We do this here to save computational time - these quantities will be
! needed a few times in subroutine calcfact_t1, so don't want to calculate them each time
!************************************************************
use theory_BRfunctions
use theory_XS_SM_functions
use usefulbits, only : theo,small
use S95tables, only : inrange
implicit none
integer, intent(in) :: n
!--------------------------------------internal
integer :: i
double precision :: Mhi
!----------------------------------------------
if(theo(n)%gooddataset) then
do i=1,np(Hneut)
Mhi=theo(n)%particle(Hneut)%M(i)
if(theo(n)%particle(Hneut)%Mc(i).ge.small) Mhi=theo(n)%particle(Hneut)%Mc(i)
! write(*,*) 'DEBUG HB - running fill_theo_SM_for_datapoint for theo_Mh = ', theo(n)%particle(Hneut)%M, &
! i, theo(n)%particle(Hneut)%M(i)
! write(*,*) 'DEBUG HB - running fill_theo_SM_for_datapoint for Mh = ', Mhi
! write(*,*) 'DEBUG HB - running fill_theo_SM_for_datapoint BRs = ', BRSM_HWW(Mhi)
if(inrange(Mhi,'SMBR'))then
theo(n)%BR_HWW_SM(i) = BRSM_HWW(Mhi)
theo(n)%BR_HZZ_SM(i) = BRSM_HZZ(Mhi)
theo(n)%BR_Hbb_SM(i) = BRSM_Hbb(Mhi)
theo(n)%BR_Htt_SM(i) = BRSM_Htoptop(Mhi) !HB-5 new
theo(n)%BR_Hcc_SM(i) = BRSM_Hcc(Mhi)
theo(n)%BR_Hss_SM(i) = BRSM_Hss(Mhi)
theo(n)%BR_Hmumu_SM(i) = BRSM_Hmumu(Mhi)
theo(n)%BR_Htautau_SM(i)= BRSM_Htautau(Mhi)
theo(n)%BR_HZga_SM(i) = BRSM_HZga(Mhi)
theo(n)%BR_Hgaga_SM(i) = BRSM_Hgaga(Mhi)
theo(n)%BR_Hgg_SM(i) = BRSM_Hgg(Mhi)
theo(n)%BR_Hjets_SM(i) = BRSM_Hss(Mhi)+BRSM_Hcc(Mhi)+BRSM_Hbb(Mhi)+BRSM_Hgg(Mhi)
theo(n)%GammaTot_SM(i) = BRSM_GammaTot(Mhi)
else
theo(n)%BR_HWW_SM(i) = 0.0D0
theo(n)%BR_HZZ_SM(i) = 0.0D0
theo(n)%BR_Hbb_SM(i) = 0.0D0
theo(n)%BR_Hcc_SM(i) = 0.0D0
theo(n)%BR_Hss_SM(i) = 0.0D0
theo(n)%BR_Hmumu_SM(i) = 0.0D0
theo(n)%BR_Htautau_SM(i) = 0.0D0
theo(n)%BR_HZga_SM(i) = 0.0D0
theo(n)%BR_Hgaga_SM(i) = 0.0D0
theo(n)%BR_Hgg_SM(i) = 0.0D0
theo(n)%BR_Hjets_SM(i) = 0.0D0
theo(n)%GammaTot_SM(i) = 0.0D0
endif
if(inrange(Mhi,'TEV '))then
theo(n)%tev%XS_HZ_SM(i) = XS_tev_HZ_SM(Mhi)
theo(n)%tev%XS_HW_SM(i) = XS_tev_HW_SM(Mhi)
theo(n)%tev%XS_H_SM(i) = XS_tev_gg_H_SM(Mhi)+XS_tev_bb_H_SM(Mhi)
theo(n)%tev%XS_gg_H_SM(i) = XS_tev_gg_H_SM(Mhi) !HB-5 new
theo(n)%tev%XS_bb_H_SM(i) = XS_tev_bb_H_SM(Mhi) !HB-5 new
theo(n)%tev%XS_vbf_SM(i)= XS_tev_vbf_SM(Mhi)
theo(n)%tev%XS_ttH_SM(i)= XS_tev_ttH_SM(Mhi)
theo(n)%tev%XS_tH_tchan_SM(i) = 0.0D0 !HB-5 new
theo(n)%tev%XS_tH_schan_SM(i) = 0.0D0 !HB-5 new
theo(n)%tev%XS_Hb_SM(i) = XS_tev_bg_Hb_SM(Mhi)
theo(n)%tev%XS_Hb_c1_SM(i) = XS_tev_bg_Hb_c1_SM(Mhi)
theo(n)%tev%XS_Hb_c2_SM(i) = XS_tev_bg_Hb_c2_SM(Mhi)
theo(n)%tev%XS_Hb_c3_SM(i) = XS_tev_bg_Hb_c3_SM(Mhi)
theo(n)%tev%XS_Hb_c4_SM(i) = XS_tev_bg_Hb_c4_SM(Mhi)
else
theo(n)%tev%XS_HW_SM(i) = 0.0D0
theo(n)%tev%XS_H_SM(i) = 0.0D0
theo(n)%tev%XS_gg_H_SM(i)= 0.0D0
theo(n)%tev%XS_bb_H_SM(i)= 0.0D0
theo(n)%tev%XS_HZ_SM(i) = 0.0D0
theo(n)%tev%XS_vbf_SM(i)= 0.0D0
theo(n)%tev%XS_ttH_SM(i)= 0.0D0
theo(n)%tev%XS_tH_tchan_SM(i) = 0.0D0
theo(n)%tev%XS_tH_tchan_SM(i) = 0.0D0
theo(n)%tev%XS_Hb_SM(i) = 0.0D0
theo(n)%tev%XS_Hb_c1_SM(i) = 0.0D0
theo(n)%tev%XS_Hb_c2_SM(i) = 0.0D0
theo(n)%tev%XS_Hb_c3_SM(i) = 0.0D0
theo(n)%tev%XS_Hb_c4_SM(i) = 0.0D0
endif
if(inrange(Mhi,'LHC7 '))then
theo(n)%lhc7%XS_HW_SM(i) = XS_lhc7_HW_SM(Mhi)
theo(n)%lhc7%XS_H_SM(i) = XS_lhc7_gg_H_SM(Mhi) + XS_lhc7_bb_H_SM(Mhi)
theo(n)%lhc7%XS_gg_H_SM(i) = XS_lhc7_gg_H_SM(Mhi) !HB-5 new
theo(n)%lhc7%XS_bb_H_SM(i) = XS_lhc7_bb_H_SM(Mhi) !HB-5 new
theo(n)%lhc7%XS_HZ_SM(i) = XS_lhc7_HZ_SM(Mhi)
theo(n)%lhc7%XS_vbf_SM(i)= XS_lhc7_vbf_SM(Mhi)
theo(n)%lhc7%XS_ttH_SM(i)= XS_lhc7_ttH_SM(Mhi)
theo(n)%lhc7%XS_tH_tchan_SM(i) = XS_lhc7_tH_tchan_SM(Mhi) !HB-5 new
theo(n)%lhc7%XS_tH_schan_SM(i) = XS_lhc7_tH_schan_SM(Mhi) !HB-5 new
else
theo(n)%lhc7%XS_HW_SM(i) = 0.0D0
theo(n)%lhc7%XS_H_SM(i) = 0.0D0
theo(n)%lhc7%XS_gg_H_SM(i)= 0.0D0
theo(n)%lhc7%XS_bb_H_SM(i)= 0.0D0
theo(n)%lhc7%XS_HZ_SM(i) = 0.0D0
theo(n)%lhc7%XS_vbf_SM(i)= 0.0D0
theo(n)%lhc7%XS_ttH_SM(i)= 0.0D0
theo(n)%lhc7%XS_tH_tchan_SM(i) = 0.0D0 !HB-5 new
theo(n)%lhc7%XS_tH_tchan_SM(i) = 0.0D0 !HB-5 new
endif
if(inrange(Mhi,'LHC8 '))then
theo(n)%lhc8%XS_HW_SM(i) = XS_lhc8_HW_SM(Mhi)
theo(n)%lhc8%XS_H_SM(i) = XS_lhc8_gg_H_SM(Mhi) + XS_lhc8_bb_H_SM(Mhi)
theo(n)%lhc8%XS_gg_H_SM(i) = XS_lhc8_gg_H_SM(Mhi) !HB-5 new
theo(n)%lhc8%XS_bb_H_SM(i) = XS_lhc8_bb_H_SM(Mhi) !HB-5 new
theo(n)%lhc8%XS_HZ_SM(i) = XS_lhc8_HZ_SM(Mhi)
theo(n)%lhc8%XS_vbf_SM(i)= XS_lhc8_vbf_SM(Mhi)
theo(n)%lhc8%XS_ttH_SM(i)= XS_lhc8_ttH_SM(Mhi)
theo(n)%lhc8%XS_tH_tchan_SM(i) = XS_lhc8_tH_tchan_SM(Mhi) !HB-5 new
theo(n)%lhc8%XS_tH_schan_SM(i) = XS_lhc8_tH_schan_SM(Mhi) !HB-5 new
else
theo(n)%lhc8%XS_HW_SM(i) = 0.0D0
theo(n)%lhc8%XS_H_SM(i) = 0.0D0
theo(n)%lhc8%XS_HZ_SM(i) = 0.0D0
theo(n)%lhc8%XS_vbf_SM(i)= 0.0D0
theo(n)%lhc8%XS_ttH_SM(i)= 0.0D0
theo(n)%lhc8%XS_tH_tchan_SM(i) = 0.0D0 !HB-5 new
theo(n)%lhc8%XS_tH_tchan_SM(i) = 0.0D0 !HB-5 new
endif
if(inrange(Mhi,'LHC13'))then
theo(n)%lhc13%XS_HW_SM(i) = XS_lhc13_HW_SM(Mhi)
theo(n)%lhc13%XS_H_SM(i) = XS_lhc13_gg_H_SM(Mhi) + XS_lhc13_bb_H_SM(Mhi)
theo(n)%lhc13%XS_gg_H_SM(i) = XS_lhc13_gg_H_SM(Mhi) !HB-5 new
theo(n)%lhc13%XS_bb_H_SM(i) = XS_lhc13_bb_H_SM(Mhi) !HB-5 new
theo(n)%lhc13%XS_HZ_SM(i) = XS_lhc13_HZ_SM(Mhi)
theo(n)%lhc13%XS_vbf_SM(i)= XS_lhc13_vbf_SM(Mhi)
theo(n)%lhc13%XS_ttH_SM(i)= XS_lhc13_ttH_SM(Mhi)
theo(n)%lhc13%XS_tH_tchan_SM(i) = XS_lhc13_tH_tchan_SM(Mhi) !HB-5 new
theo(n)%lhc13%XS_tH_schan_SM(i) = XS_lhc13_tH_schan_SM(Mhi) !HB-5 new
else
theo(n)%lhc13%XS_HW_SM(i) = 0.0D0
theo(n)%lhc13%XS_H_SM(i) = 0.0D0
theo(n)%lhc13%XS_HZ_SM(i) = 0.0D0
theo(n)%lhc13%XS_vbf_SM(i)= 0.0D0
theo(n)%lhc13%XS_ttH_SM(i)= 0.0D0
theo(n)%lhc13%XS_tH_tchan_SM(i) = 0.0D0 !HB-5 new
theo(n)%lhc13%XS_tH_tchan_SM(i) = 0.0D0 !HB-5 new
endif
enddo
endif
end subroutine fill_theo_SM_for_datapoint
!************************************************************
subroutine XS_from_partR ! OBSOLETE !
! turn partonic cross section ratios in to hadronic cross section
! ratios
! Subroutine is complicated by the fact that if e.g. all
! the partR(n)%qq_hjW partonic cross section ratios are equal,
! just want to use this value for the hadronic cross section
! ratio and not lose any accuracy by combining with the tevS
!************************************************************
use usefulbits, only : ndat
use S95tables, only : inrange
implicit none
!--------------------------------------internal
integer :: n
!----------------------------------------------
if(np(Hneut)<1)stop 'error in subroutine XS_from_partR (np(Hneut))'
do n=1,ndat
call XS_from_partR_for_datapoint(n)
enddo
end subroutine XS_from_partR
!******************************************************************
subroutine XS_from_partR_for_datapoint(n) ! OBSOLETE !
! turn partonic cross section ratios in to hadronic cross section
! ratios
! Subroutine is complicated by the fact that if e.g. all
! the partR(n)%qq_hjW partonic cross section ratios are equal,
! just want to use this value for the hadronic cross section
! ratio and not lose any accuracy by combining with the tevS
!************************************************************
use usefulbits, only : allocate_hadroncolliderextras_parts, &
& deallocate_hadroncolliderextras_parts
use S95tables, only : inrange
implicit none
integer, intent(in) :: n
!--------------------------------------internal
integer :: i
double precision :: Mhi
logical :: simple_partR
!----------------------------------------------
call allocate_hadroncolliderextras_parts(tevS)
call allocate_hadroncolliderextras_parts(lhc7S)
call allocate_hadroncolliderextras_parts(lhc8S)
if(theo(n)%gooddataset) then
do i=1,np(Hneut)
Mhi=theo(n)%particle(Hneut)%M(i)
call fill_tevS(i,Mhi)
call fill_lhc7S(i,Mhi)
call fill_lhc8S(i,Mhi)
!this if loop is here to make sure partR(n)%qq_hjWp(1,i).eq.0.0D0 is taken care of
if(partR(n)%qq_hjWp(1,i).eq.0.0D0)then
simple_partR=.False.
elseif( (( sum(abs( partR(n)%qq_hjWp(:,i) - partR(n)%qq_hjWp(1,i))) &
& + sum(abs( partR(n)%qq_hjWm(:,i) - partR(n)%qq_hjWp(1,i))) )/partR(n)%qq_hjWp(1,i)) .lt. 1.0D-5 )then
simple_partR=.True.
else
simple_partR=.False.
endif
if(simple_partR)then
theo(n)%tev%XS_hjW_ratio(i)=partR(n)%qq_hjWp(1,i)
theo(n)%lhc7%XS_hjW_ratio(i)=partR(n)%qq_hjWp(1,i)
theo(n)%lhc8%XS_hjW_ratio(i)=partR(n)%qq_hjWp(1,i)
else
theo(n)%tev%XS_hjW_ratio(i)= &
& sum( partR(n)%qq_hjWp(:,i)*tevS(1)%qq_hjWp(:,i) ) &
& + sum( partR(n)%qq_hjWm(:,i)*tevS(1)%qq_hjWm(:,i) )
theo(n)%lhc7%XS_hjW_ratio(i)= &
& sum( partR(n)%qq_hjWp(:,i)*lhc7S(1)%qq_hjWp(:,i) ) &
& + sum( partR(n)%qq_hjWm(:,i)*lhc7S(1)%qq_hjWm(:,i) )
theo(n)%lhc8%XS_hjW_ratio(i)= &
& sum( partR(n)%qq_hjWp(:,i)*lhc8S(1)%qq_hjWp(:,i) ) &
& + sum( partR(n)%qq_hjWm(:,i)*lhc8S(1)%qq_hjWm(:,i) )
endif
theo(n)%tev%XS_hj_ratio(i)= &
& partR(n)%gg_hj(i) *tevS(1)%gg_hj(i) &
& + sum( partR(n)%qq_hj(:,i) *tevS(1)%qq_hj(:,i) )
theo(n)%lhc7%XS_hj_ratio(i)= &
& partR(n)%gg_hj(i) *lhc7S(1)%gg_hj(i) &
& + sum( partR(n)%qq_hj(:,i) *lhc7S(1)%qq_hj(:,i) )
theo(n)%lhc8%XS_hj_ratio(i)= &
& partR(n)%gg_hj(i) *lhc8S(1)%gg_hj(i) &
& + sum( partR(n)%qq_hj(:,i) *lhc8S(1)%qq_hj(:,i) )
!this if loop is here to make sure partR(n)%qq_hjZ(1,i).eq.0.0D0 is taken care of
if(partR(n)%qq_hjZ(1,i).eq.0.0D0)then
simple_partR=.False.
elseif( (abs(sum( partR(n)%qq_hjZ(:,i) - partR(n)%qq_hjZ(1,i)))/partR(n)%qq_hjZ(1,i)).lt. 1.0D-5 )then
simple_partR=.True.
else
simple_partR=.False.
endif
if( simple_partR )then
theo(n)%tev%XS_hjZ_ratio(i) = partR(n)%qq_hjZ(1,i)
if(partR(n)%gg_hjZ(i) .le.0.0D0)then
theo(n)%lhc7%XS_hjZ_ratio(i)= partR(n)%qq_hjZ(1,i)
theo(n)%lhc8%XS_hjZ_ratio(i)= partR(n)%qq_hjZ(1,i)
else
theo(n)%lhc7%XS_hjZ_ratio(i)= &
& partR(n)%gg_hjZ(i) *lhc7S(1)%gg_hjZ(i) &
& + sum( partR(n)%qq_hjZ(:,i) *lhc7S(1)%qq_hjZ(:,i) )
theo(n)%lhc8%XS_hjZ_ratio(i)= &
& partR(n)%gg_hjZ(i) *lhc8S(1)%gg_hjZ(i) &
& + sum( partR(n)%qq_hjZ(:,i) *lhc8S(1)%qq_hjZ(:,i) )
endif
else
theo(n)%tev%XS_hjZ_ratio(i)= &
& partR(n)%gg_hjZ(i) *tevS(1)%gg_hjZ(i) &
& + sum( partR(n)%qq_hjZ(:,i) *tevS(1)%qq_hjZ(:,i) )
theo(n)%lhc7%XS_hjZ_ratio(i)= &
& partR(n)%gg_hjZ(i) *lhc7S(1)%gg_hjZ(i) &
& + sum( partR(n)%qq_hjZ(:,i) *lhc7S(1)%qq_hjZ(:,i) )
theo(n)%lhc8%XS_hjZ_ratio(i)= &
& partR(n)%gg_hjZ(i) *lhc8S(1)%gg_hjZ(i) &
& + sum( partR(n)%qq_hjZ(:,i) *lhc8S(1)%qq_hjZ(:,i) )
endif
theo(n)%tev%XS_hjb_ratio(i) = partR(n)%bg_hjb(i)
theo(n)%lhc7%XS_hjb_ratio(i)= partR(n)%bg_hjb(i)
theo(n)%lhc8%XS_hjb_ratio(i)= partR(n)%bg_hjb(i)
theo(n)%tev%XS_gg_hj_ratio(i) = partR(n)%gg_hj(i)
theo(n)%tev%XS_bb_hj_ratio(i) = partR(n)%bg_hjb(i)
theo(n)%lhc7%XS_gg_hj_ratio(i) = partR(n)%gg_hj(i)
theo(n)%lhc7%XS_bb_hj_ratio(i) = partR(n)%bg_hjb(i)
theo(n)%lhc8%XS_gg_hj_ratio(i) = partR(n)%gg_hj(i)
theo(n)%lhc8%XS_bb_hj_ratio(i) = partR(n)%bg_hjb(i)
enddo
endif
call deallocate_hadroncolliderextras_parts(lhc8S)
call deallocate_hadroncolliderextras_parts(lhc7S)
call deallocate_hadroncolliderextras_parts(tevS)
end subroutine XS_from_partR_for_datapoint
!******************************************************************
subroutine fill_tevS(j,Mhj) ! OBSOLETE !
! fills the elements of tevS using the functions in module theory_colliderSfunctions
!************************************************************
use theory_colliderSfunctions
use theory_XS_SM_functions
use S95tables, only : inrange
implicit none
!--------------------------------------internal
integer :: j
double precision :: Mhj
!----------------------------------------------
if(inrange(Mhj,'TEV '))then
tevS(1)%qq_hjWp(1,j)=tev_rHWpm_udb(Mhj)
tevS(1)%qq_hjWp(2,j)=tev_rHWpm_csb(Mhj)
tevS(1)%qq_hjWm(1,j)=tev_rHWpm_dub(Mhj)
tevS(1)%qq_hjWm(2,j)=tev_rHWpm_scb(Mhj)
!We now have a new gg->H SM function: Should use XS functions instead of r's
!For cross check with OB code changed this temporarily!
tevS(1)%gg_hj(j)=tev_rH_gg(Mhj)
!tevS(1)%gg_hj(j) =XS_tev_gg_H_SM(Mhj)/(XS_tev_gg_H_SM(Mhj)+XS_tev_bb_H_SM(Mhj))
tevS(1)%qq_hj(:,j)=0.0D0
tevS(1)%qq_hj(5,j)=tev_rH_bb(Mhj)
!tevS(1)%qq_hj(5,j)=XS_tev_bb_H_SM(Mhj)/(XS_tev_gg_H_SM(Mhj)+XS_tev_bb_H_SM(Mhj))
tevS(1)%gg_hjZ(j)=0.0D0
tevS(1)%qq_hjZ(1,j)=tev_rHZ_ddb(Mhj)
tevS(1)%qq_hjZ(2,j)=tev_rHZ_uub(Mhj)
tevS(1)%qq_hjZ(3,j)=tev_rHZ_ssb(Mhj)
tevS(1)%qq_hjZ(4,j)=tev_rHZ_ccb(Mhj)
tevS(1)%qq_hjZ(5,j)=tev_rHZ_bbb(Mhj)
if(abs(sum(tevS(1)%qq_hjWp(:,j))+sum(tevS(1)%qq_hjWm(:,j)) - 1.0D0) .gt. 1.0D-2)then
stop 'error in fill_tevS (a)'
elseif(abs(tevS(1)%gg_hj(j)+sum(tevS(1)%qq_hj(:,j)) - 1.0D0) .gt. 1.0D-2)then
stop 'error in fill_tevS (b)'
elseif(abs(tevS(1)%gg_hjZ(j)+sum(tevS(1)%qq_hjZ(:,j)) - 1.0D0) .gt. 1.0D-2)then
stop 'error in fill_tevS (c)'
endif
else
tevS(1)%qq_hjWp(:,j)=0.0D0
tevS(1)%qq_hjWm(:,j)=0.0D0
tevS(1)%gg_hj(j)=0.0D0
tevS(1)%qq_hj(:,j)=0.0D0
tevS(1)%gg_hjZ(j)=0.0D0
tevS(1)%qq_hjZ(:,j)=0.0D0
endif
end subroutine fill_tevS
!******************************************************************
subroutine fill_lhc7S(j,Mhj) ! OBSOLETE !
! fills the elements of lhc7S using the functions in module theory_colliderSfunctions
!************************************************************
use theory_colliderSfunctions
use theory_XS_SM_functions
use usefulbits, only : vsmall
use S95tables, only : inrange
implicit none
!--------------------------------------internal
integer :: j
double precision :: Mhj
!----------------------------------------------
if(inrange(Mhj,'LHC7 '))then
lhc7S(1)%gg_hj(j)=LHC7_rH_gg(Mhj)
lhc7S(1)%qq_hj(:,j)=0.0D0
lhc7S(1)%qq_hj(5,j)=LHC7_rH_bb(Mhj)
if(abs(lhc7S(1)%gg_hj(j)+sum(lhc7S(1)%qq_hj(:,j)) - 1.0D0) .gt. 1.0D-2)then
stop 'error in fill_lhc7S (b)'
endif
if(XS_lhc7_HW_SM(Mhj).lt.vsmall)then
lhc7S(1)%qq_hjWp(:,j)=0.0D0
lhc7S(1)%qq_hjWm(:,j)=0.0D0
else
lhc7S(1)%qq_hjWp(1,j)=LHC7_rHWp_udb(Mhj)
lhc7S(1)%qq_hjWp(2,j)=LHC7_rHWp_csb(Mhj)
lhc7S(1)%qq_hjWm(1,j)=LHC7_rHWm_dub(Mhj)
lhc7S(1)%qq_hjWm(2,j)=LHC7_rHWm_scb(Mhj)
if(abs(sum(lhc7S(1)%qq_hjWp(:,j))+sum(lhc7S(1)%qq_hjWm(:,j)) - 1.0D0) .gt. 1.0D-2)then
! write(*,*) "hello: ", Mhj
stop 'error in fill_lhc7S (a)'
endif
endif
if(XS_lhc7_HZ_SM(Mhj).lt.vsmall)then
lhc7S(1)%gg_hjZ(j)=0.0D0
lhc7S(1)%qq_hjZ(:,j)=0.0D0
else
lhc7S(1)%gg_hjZ(j)=LHC7_rHZ_gg(Mhj)
lhc7S(1)%qq_hjZ(1,j)=LHC7_rHZ_ddb(Mhj)
lhc7S(1)%qq_hjZ(2,j)=LHC7_rHZ_uub(Mhj)
lhc7S(1)%qq_hjZ(3,j)=LHC7_rHZ_ssb(Mhj)
lhc7S(1)%qq_hjZ(4,j)=LHC7_rHZ_ccb(Mhj)
lhc7S(1)%qq_hjZ(5,j)=LHC7_rHZ_bbb(Mhj)
if(abs(lhc7S(1)%gg_hjZ(j)+sum(lhc7S(1)%qq_hjZ(:,j)) - 1.0D0) .gt. 1.0D-2)then
stop 'error in fill_lhc7S (c)'
endif
endif
else
lhc7S(1)%qq_hjWp(:,j)=0.0D0
lhc7S(1)%qq_hjWm(:,j)=0.0D0
lhc7S(1)%gg_hj(j)=0.0D0
lhc7S(1)%qq_hj(:,j)=0.0D0
lhc7S(1)%gg_hjZ(j)=0.0D0
lhc7S(1)%qq_hjZ(:,j)=0.0D0
endif
end subroutine fill_lhc7S
!******************************************************************
subroutine fill_lhc8S(j,Mhj) ! OBSOLETE !
! fills the elements of lhc8S using the functions in module theory_colliderSfunctions
!************************************************************
use theory_colliderSfunctions
use theory_XS_SM_functions
use usefulbits, only : vsmall
use S95tables, only : inrange
implicit none
!--------------------------------------internal
integer :: j
double precision :: Mhj
!----------------------------------------------
if(inrange(Mhj,'LHC8 '))then
lhc8S(1)%gg_hj(j)=LHC8_rH_gg(Mhj)
lhc8S(1)%qq_hj(:,j)=0.0D0
lhc8S(1)%qq_hj(5,j)=LHC8_rH_bb(Mhj)
if(abs(lhc8S(1)%gg_hj(j)+sum(lhc8S(1)%qq_hj(:,j)) - 1.0D0) .gt. 1.0D-2)then
stop 'error in fill_lhc8S (b)'
endif
if(XS_lhc8_HW_SM(Mhj).lt.vsmall)then
lhc8S(1)%qq_hjWp(:,j)=0.0D0
lhc8S(1)%qq_hjWm(:,j)=0.0D0
else
lhc8S(1)%qq_hjWp(1,j)=LHC8_rHWp_udb(Mhj)
lhc8S(1)%qq_hjWp(2,j)=LHC8_rHWp_csb(Mhj)
lhc8S(1)%qq_hjWm(1,j)=LHC8_rHWm_dub(Mhj)
lhc8S(1)%qq_hjWm(2,j)=LHC8_rHWm_scb(Mhj)
if(abs(sum(lhc8S(1)%qq_hjWp(:,j))+sum(lhc8S(1)%qq_hjWm(:,j)) - 1.0D0) .gt. 1.0D-2)then
! write(*,*) Mhj,sum(lhc8S(1)%qq_hjWp(:,j)), sum(lhc8S(1)%qq_hjWm(:,j))
stop 'error in fill_lhc8S (a)'
endif
endif
if(XS_lhc8_HZ_SM(Mhj).lt.vsmall)then
lhc8S(1)%gg_hjZ(j)=0.0D0
lhc8S(1)%qq_hjZ(:,j)=0.0D0
else
lhc8S(1)%gg_hjZ(j)=LHC8_rHZ_gg(Mhj)
lhc8S(1)%qq_hjZ(1,j)=LHC8_rHZ_ddb(Mhj)
lhc8S(1)%qq_hjZ(2,j)=LHC8_rHZ_uub(Mhj)
lhc8S(1)%qq_hjZ(3,j)=LHC8_rHZ_ssb(Mhj)
lhc8S(1)%qq_hjZ(4,j)=LHC8_rHZ_ccb(Mhj)
lhc8S(1)%qq_hjZ(5,j)=LHC8_rHZ_bbb(Mhj)
if(abs(lhc8S(1)%gg_hjZ(j)+sum(lhc8S(1)%qq_hjZ(:,j)) - 1.0D0) .gt. 1.0D-2)then
stop 'error in fill_lhc8S (c)'
endif
endif
else
lhc8S(1)%qq_hjWp(:,j)=0.0D0
lhc8S(1)%qq_hjWm(:,j)=0.0D0
lhc8S(1)%gg_hj(j)=0.0D0
lhc8S(1)%qq_hj(:,j)=0.0D0
lhc8S(1)%gg_hjZ(j)=0.0D0
lhc8S(1)%qq_hjZ(:,j)=0.0D0
endif
end subroutine fill_lhc8S
!******************************************************************
end module theo_manip
!******************************************************************
Index: trunk/HiggsBounds-5/makefile.in
===================================================================
--- trunk/HiggsBounds-5/makefile.in (revision 532)
+++ trunk/HiggsBounds-5/makefile.in (revision 533)
@@ -1,132 +1,134 @@
CHISQMODS = extra_bits_for_chisquared.MOD
MODS = usefulbits.mod store_pathname.mod \
S95tables_type1.MOD S95tables_type2.MOD\
S95tables_type3.MOD \
interpolate.mod \
theory_colliderSfunctions.MOD theory_XS_SM_functions.MOD theory_BRfunctions.MOD \
likelihoods.MOD S95tables.mod \
PDGnumbering.mod string_manip.mod SLHA_manip.mod \
extra_bits_for_SLHA.mod \
extra_bits_for_web.MOD\
$(USECHISQMODS) \
input.MOD channels.MOD output.MOD theo_manip.mod \
tempMODS = $(MODS:.mod=.o)
OBJSbasic = $(tempMODS:.MOD=.o)
OBJScommandline = $(OBJSbasic) \
HiggsBounds.o
OBJSsubroutines = $(OBJSbasic) \
HiggsBounds_subroutines.o access_SM.o
.SUFFIXES: .exe .o .mod .f90 .F .F90 .MOD
#as advised in http://gcc.gnu.org/wiki/GfortranFAQ
%.o : %.mod
default: HiggsBounds
.f90.mod:
$(F90C) $(F90FLAGS) $(ADDITIONALDEFINE) -c $< -o $*.o
.f90.o:
$(F90C) $(F90FLAGS) $(ADDITIONALDEFINE) -c $< -o $*.o
.F90.MOD:
$(F90C) $(F90FLAGS) $(ADDITIONALDEFINE) -c $< -o $*.o
.F90.o:
$(F90C) $(F90FLAGS) $(ADDITIONALDEFINE) -c $< -o $*.o
.F.o:
$(F77C) -c $< -o $*.o
.mod.o:
$(F90C) $(F90FLAGS) -c $*.f90 -o $*.o
.MOD.o:
$(F90C) $(F90FLAGS) -c $*.F90 -o $*.o
HiggsBounds: HBwithSLHA libHB.a $(MODS) $(OBJScommandline) $(OBJSsubroutines)
$(F90C) $(F90FLAGS) $(OBJScommandline) -o $(EXE) $(HBLIBS)
$(F90C) $(F90FLAGS) AllAnalyses.F90 -o AllAnalyses $(HBLIBS)
rm -f Expt_tables/S95_t1.binary
rm -f Expt_tables/S95_t2.binary
rm -f Theory_tables/BRSM.binary
touch Expt_tables/S95_t1.binary
touch Expt_tables/S95_t2.binary
touch Expt_tables/CMS_tautau_llh.binary
touch Theory_tables/BRSM.binary
libHB: $(MODS) $(OBJSsubroutines)
ar -rv libHB.a $(OBJSsubroutines)
ranlib libHB.a
rm -f Expt_tables/S95_t1.binary
rm -f Expt_tables/S95_t2.binary
rm -f Theory_tables/BRSM.binary
touch Expt_tables/S95_t1.binary
touch Expt_tables/S95_t2.binary
touch Expt_tables/CMS_tautau_llh_1408.3316.binary
touch Theory_tables/BRSM.binary
libHB.a: libHB
HBwithFH: libHB.a
$(F90C) $(F90FLAGS) $(FHINCLUDE) example_programs/HBwithFH.F -o example_programs/HBwithFH $(FHLIBS) $(HBLIBS)
- $(F90C) $(F90FLAGS) $(FHINCLUDE) example_programs/HBwithFH_dm.F -o example_programs/HBwithFH_dm $(FHLIBS) $(HBLIBS)
$(F90C) $(F90FLAGS) $(FHINCLUDE) example_programs/HBSLHAinputblocksfromFH_extras.F example_programs/HBSLHAinputblocksfromFH.F90 -o example_programs/HBSLHAinputblocksfromFH $(FHLIBS) $(HBLIBS)
+# $(F90C) $(F90FLAGS) $(FHINCLUDE) example_programs/HBwithFH_dm.F -o example_programs/HBwithFH_dm $(FHLIBS) $(HBLIBS)
-HBwithCPsuperH: libHB.a
- $(F77C) example_programs/HBwithCPsuperH.f -o example_programs/HBwithCPsuperH $(CPSUPERHLIBS) $(HBLIBS)
- @echo 'now run ./HBwithCPsuperH < HBwithCPsuperH.input in the folder example_programs'
+# HBwithCPsuperH: libHB.a
+# $(F77C) example_programs/HBwithCPsuperH.f -o example_programs/HBwithCPsuperH $(CPSUPERHLIBS) $(HBLIBS)
+# @echo 'now run ./HBwithCPsuperH < HBwithCPsuperH.input in the folder example_programs'
HBweb: libHB.a HiggsBounds
@echo 'check that WEBVERSION is defined'
$(F90C) $(F90FLAGS) extract_SM_results_for_web.f90 -o extract_SM_results_for_web $(HBLIBS)
HBwithSLHA: libHB.a
$(F90C) $(F90FLAGS) example_programs/HBwithSLHA.F90 -o example_programs/HBwithSLHA $(HBLIBS)
HBwithLHClikelihood: libHB.a
$(F90C) $(F90FLAGS) example_programs/HBwithLHClikelihood.F90 -o example_programs/HBwithLHClikelihood $(HBLIBS)
HBchisq: libHB.a
$(F90C) $(F90FLAGS) example_programs/HBchisq.F90 -o example_programs/HBchisq $(HBLIBS)
$(F90C) $(F90FLAGS) example_programs/HBchisqwithSLHA.F90 -o example_programs/HBchisqwithSLHA $(HBLIBS)
-HB5_effC: libHB.a
- $(F90C) $(F90FLAGS) example_programs/HB5_effC.F90 -o example_programs/HB5_effC $(HBLIBS)
+# NEW HB5 examples:
-HB5withFH: libHB.a
- $(F90C) $(F90FLAGS) $(FHINCLUDE) example_programs/HB5withFH.F -o example_programs/HB5withFH $(FHLIBS) $(HBLIBS)
+HBeffC: libHB.a
+ $(F90C) $(F90FLAGS) example_programs/HBeffC.F90 -o example_programs/HBeffC $(HBLIBS)
+
+# HB5withFH: libHB.a
+# $(F90C) $(F90FLAGS) $(FHINCLUDE) example_programs/HB5withFH.F -o example_programs/HB5withFH $(FHLIBS) $(HBLIBS)
clean:
rm -f *.o *.mod *.MOD *.a
rm -f store_pathname.f90
hyperclean:
rm -f *.o *.mod *.MOD *.a *~
rm -f example_programs/*~
rm -f store_pathname.f90
rm -f example_programs/HBwithFH
rm -f example_programs/HBwithCPsuperH
rm -f example_programs/example-SM_vs_4thGen
rm -f extract_SM_results_for_web
rm -f HiggsBounds
# rm -f example_data/*results.dat
# rm -f example_data/*Key.dat
rm -f cs-ratios_sigma-bg-Hb/Tevatron*~
rm -f example_programs/example-4thGen-results.dat
rm -f example_programs/example-SM-results.dat
rm -f example_programs/Key.dat
rm -f example_programs/HBwithCPsuperH_effC.f
rm -f example_programs/HBwithFH_effC.F
rm -f example_programs/debug_channels.txt
rm -f example_programs/debug_predratio.txt
rm -f README_old
rm -f Expt_tables/*.binary
rm -f Theory_tables/*.binary
Index: trunk/HiggsBounds-5/usefulbits.f90
===================================================================
--- trunk/HiggsBounds-5/usefulbits.f90 (revision 532)
+++ trunk/HiggsBounds-5/usefulbits.f90 (revision 533)
@@ -1,1338 +1,1381 @@
! This file is part of HiggsBounds
! -KW
!******************************************************************
module usefulbits
!******************************************************************
implicit none
logical :: debug = .False.
logical :: full_dmth_variation = .True.
integer :: dmhsteps = 3
! Mass uncertainties smaller than 0.1 GeV are not considered
double precision :: small_mh = 0.1D0
logical :: run_HB_classic = .False.
! For the CMS likelihood extension
integer :: using_likelihood = 0
! For the LEP chisq extension:
logical :: chisqcut_at_mumax = .False.
! HB-5:
logical :: BRdirectinput = .False.
character(LEN=5) :: whichanalyses
character(LEN=4) :: whichinput
character(LEN=7) :: inputmethod = 'subrout'
character(LEN=9),parameter :: vers='5.0.2beta'
integer, parameter :: numres = 3
integer :: n_additional
character(len=300) :: infile1,infile2
integer,parameter :: file_id_common=10
integer,parameter :: file_id_common2=12
integer,parameter :: file_id_common3=133
integer,parameter :: file_id_common4=134
integer,parameter :: file_id_debug1=444
integer,parameter :: file_id_debug2=45
integer, allocatable :: analysislist(:)
integer, allocatable :: analysis_exclude_list(:)
!read from http://pdg.lbl.gov/ 22.10.2009
double precision,parameter :: mt=173.2D0
double precision,parameter :: ms=0.105D0
double precision,parameter :: mc=1.27D0
double precision,parameter :: mbmb=4.20D0
double precision,parameter :: mmu=105.7D-3
double precision,parameter :: mtau=1.777D0
double precision,parameter :: MZ=91.1876D0 !PDG 2009
double precision,parameter :: MW=80.398D0 !PDG 2009
double precision,parameter :: GF=1.16637D-5
double precision,parameter :: pi=3.14159265358979323846264338328D0
double precision,parameter :: alphas=0.118D0
double precision,parameter :: small=1.0D-6
double precision,parameter :: vsmall=1.0D-16
double precision,parameter :: vvsmall=1.0D-100
type particledescriptions
character(LEN=10) :: short
character(LEN=30) :: long
end type
! particle codes: (n.b. these are NOT pdg)
integer,parameter :: not_a_particle = 0
integer,parameter :: Hneut = 1 !either Mhi, Mh2 or Mh3 (says nothing about CP properties)
integer,parameter :: Hplus = 2 !single charged Higgs
integer,parameter :: Chineut = 3 !either neutralino1, neutralino2, neutralino3 or neutralino4
integer,parameter :: Chiplus = 4 !either chargino1 or chargino2
integer :: np(0:4)=1 !e.g np(Hneut) holds number of neutral Higgs considered
type(particledescriptions),allocatable :: pdesc(:)
!for subroutine version-------------------- (HB5: Removed!)
! type inputsubroutineinfo
! integer :: stat
! character(LEN=40) :: desc
! integer :: req
! end type
! type(inputsubroutineinfo),allocatable :: inputsub(:)
logical :: just_after_run
!associated with 'channels'----------------
integer :: ntot
type listprocesses
integer :: tlist,ttype
integer :: findi,findj
integer :: corresponding_clsb_table_element
end type
type(listprocesses), allocatable :: pr(:)
type(listprocesses), allocatable :: prsep(:,:)
!-------------------------------------------
!associated with 'input'--------------------
type particlemasses
double precision, allocatable :: M(:)
! Central value for mass with uncertainties
double precision, allocatable :: Mc(:)
double precision, allocatable :: GammaTot(:)
! Mass uncertainties (chi-2 test) used in HiggsSignals
double precision, allocatable :: dM(:)
! Mass uncertainties (variation) used in HiggsBounds
double precision, allocatable :: dMh(:)
end type
double precision, allocatable :: diffMhneut(:,:)
double precision, allocatable :: diffMhch(:,:)
double precision, allocatable :: dmn(:)
double precision, allocatable :: dmch(:)
integer ndmh
integer ndat
type lepdataset
double precision, allocatable :: XS_hjZ_ratio(:)
double precision, allocatable :: XS_bbhj_ratio(:)
double precision, allocatable :: XS_tautauhj_ratio(:)
double precision, allocatable :: XS_hjhi_ratio(:,:)
double precision, allocatable :: XS_HpjHmj_ratio(:)
double precision, allocatable :: XS_CpjCmj(:)
double precision, allocatable :: XS_NjNi(:,:)
end type
type hadroncolliderdataset
double precision, allocatable :: XS_hj_ratio(:)
double precision, allocatable :: XS_gg_hj_ratio(:) ! HB-5: for gluon fusion
double precision, allocatable :: XS_bb_hj_ratio(:) ! HB-5: for bb+Higgs production
double precision, allocatable :: XS_hjZ_ratio(:)
double precision, allocatable :: XS_hjW_ratio(:)
double precision, allocatable :: XS_hjb_ratio(:) ! still needed?
double precision, allocatable :: XS_tthj_ratio(:)
double precision, allocatable :: XS_vbf_ratio(:)
double precision, allocatable :: XS_thj_tchan_ratio(:) ! HB-5
double precision, allocatable :: XS_thj_schan_ratio(:) ! HB-5
double precision, allocatable :: XS_hjhi(:,:) ! HB-5
! SM reference cross section holders:
double precision, allocatable :: XS_HZ_SM(:)
double precision, allocatable :: XS_HW_SM(:)
double precision, allocatable :: XS_H_SM(:)
double precision, allocatable :: XS_gg_H_SM(:) ! HB-5
double precision, allocatable :: XS_bb_H_SM(:) ! HB-5
!double precision, allocatable :: XS_H_SM_9713(:),XS_H_SM_9674(:)
double precision, allocatable :: XS_ttH_SM(:)
double precision, allocatable :: XS_tH_tchan_SM(:) ! HB-5
double precision, allocatable :: XS_tH_schan_SM(:) ! HB-5
double precision, allocatable :: XS_vbf_SM(:)
! Higgs produced in association with b, where b is tagged, comes uncut and with various cuts
! see subroutines in theory_XS_SM_functions.f90 for details
double precision, allocatable :: XS_Hb_SM(:)
double precision, allocatable :: XS_Hb_c1_SM(:),XS_Hb_c2_SM(:), XS_Hb_c3_SM(:),XS_Hb_c4_SM(:)
! HB-5: Charged Higgs production cross sections (in pb)
double precision, allocatable :: XS_vbf_Hpj(:) ! for Hp_j production in VBF
- double precision, allocatable :: XS_Hpjtb(:) ! for Hp_j + t + b production
+ double precision, allocatable :: XS_Hpjtb(:) ! for Hp_j + t + b production
+ double precision, allocatable :: XS_Hpjcb(:) ! for Hp_j + c + b production
double precision, allocatable :: XS_Hpjbjet(:) ! for Hp_j + b + jet production
+ double precision, allocatable :: XS_Hpjcjet(:) ! for Hp_j + b + jet production
+ double precision, allocatable :: XS_Hpjjetjet(:) ! for Hp_j + jet + jet production
double precision, allocatable :: XS_HpjW(:) ! for Hp_j + W production
double precision, allocatable :: XS_HpjZ(:) ! for Hp_j + Z production
double precision, allocatable :: XS_HpjHmj(:) ! (j,i), for Hp_j Hm_j production
double precision, allocatable :: XS_Hpjhi(:,:) ! (j,i), for Hp_j h_i production
end type
type dataset
logical :: gooddataset
integer, allocatable :: CP_value(:)
double precision, allocatable :: additional(:)
type(particlemasses), allocatable :: particle(:)
double precision, allocatable :: BR_hjss(:),BR_hjcc(:)
double precision, allocatable :: BR_hjbb(:),BR_hjtt(:) !HB-5 new H->tt
double precision, allocatable :: BR_hjmumu(:),BR_hjtautau(:)
double precision, allocatable :: BR_hjinvisible(:)
double precision, allocatable :: BR_hjhihi(:,:) ! legacy HB-4
double precision, allocatable :: BR_hkhjhi(:,:,:) ! HB-5: for the decay h_k -> h_j h_i
double precision, allocatable :: BR_hjhiZ(:,:) ! HB-5: for the decay h_j -> h_i Z
double precision, allocatable :: BR_hjemu(:), BR_hjetau(:), BR_hjmutau(:) ! HB-5
+ double precision, allocatable :: BR_hjHpiW(:,:) ! HB-5: for the decay h_j -> Hp_i W
type(lepdataset) :: lep
!-------------------------------------------
double precision, allocatable :: BR_hjWW(:),BR_hjgaga(:)
double precision, allocatable :: BR_hjZga(:)
double precision, allocatable :: BR_hjZZ(:),BR_hjgg(:)
double precision :: BR_tWpb
double precision, allocatable :: BR_tHpjb(:)
double precision, allocatable :: BR_Hpjcs(:)
double precision, allocatable :: BR_Hpjcb(:)
double precision, allocatable :: BR_Hpjtaunu(:)
double precision, allocatable :: BR_Hpjtb(:) ! HB-5: for the decay Hp_j -> t b
double precision, allocatable :: BR_HpjWZ(:) ! HB-5: for the decay Hp_j -> W Z
double precision, allocatable :: BR_HpjhiW(:,:) ! HB-5: for the decay Hp_j -> h_i W
double precision, allocatable :: BR_CjqqNi(:,:)
double precision, allocatable :: BR_CjlnuNi(:,:)
double precision, allocatable :: BR_CjWNi(:,:)
double precision, allocatable :: BR_NjqqNi(:,:)
double precision, allocatable :: BR_NjZNi(:,:)
type(hadroncolliderdataset) :: tev
type(hadroncolliderdataset) :: lhc7
type(hadroncolliderdataset) :: lhc8
type(hadroncolliderdataset) :: lhc13 ! HB-5
! NEW(24/09/2014, TS):
! double precision, allocatable :: gg_hj_ratio(:)
! double precision, allocatable :: bb_hj_ratio(:)
double precision, allocatable :: BR_Htt_SM(:), BR_Hbb_SM(:) !HB-5 new H->tt
double precision, allocatable :: BR_Hcc_SM(:),BR_Hss_SM(:)
double precision, allocatable :: BR_Hmumu_SM(:),BR_Htautau_SM(:)
double precision, allocatable :: BR_HWW_SM(:),BR_HZZ_SM(:),BR_HZga_SM(:),BR_Hgaga_SM(:),BR_Hgg_SM(:)
double precision, allocatable :: BR_Hjets_SM(:)
double precision, allocatable :: GammaTot_SM(:)
!-------------------------------------------
end type
type(dataset), allocatable :: theo(:)
type sqcouplratio
double precision, allocatable :: hjss_s(:),hjss_p(:)
double precision, allocatable :: hjcc_s(:),hjcc_p(:)
double precision, allocatable :: hjbb_s(:),hjbb_p(:)
double precision, allocatable :: hjtoptop_s(:),hjtoptop_p(:) ! ToDo: Change name top -> t !
double precision, allocatable :: hjmumu_s(:),hjmumu_p(:)
double precision, allocatable :: hjtautau_s(:),hjtautau_p(:)
double precision, allocatable :: hjWW(:),hjZZ(:)
double precision, allocatable :: hjZga(:)
double precision, allocatable :: hjgaga(:),hjgg(:),hjggZ(:)
double precision, allocatable :: hjhiZ(:,:)
end type
type(sqcouplratio), allocatable :: g2(:)
! HB-5: NEW! -->
type couplratio
double precision, allocatable :: hjcc_s(:),hjcc_p(:)
double precision, allocatable :: hjss_s(:),hjss_p(:)
double precision, allocatable :: hjtt_s(:),hjtt_p(:)
double precision, allocatable :: hjbb_s(:),hjbb_p(:)
double precision, allocatable :: hjmumu_s(:),hjmumu_p(:)
double precision, allocatable :: hjtautau_s(:),hjtautau_p(:)
double precision, allocatable :: hjWW(:),hjZZ(:)
double precision, allocatable :: hjZga(:)
double precision, allocatable :: hjgaga(:),hjgg(:) !,hjggZ(:)
double precision, allocatable :: hjhiZ(:,:)
end type
! <--- !
type(couplratio), allocatable :: effC(:)
type hadroncolliderextras
!nq_hjWp,nq_hjWm,nq_hj,nq_hjZ are set in allocate_hadroncolliderextras_parts below
double precision, allocatable :: qq_hjWp(:,:)
integer :: nq_hjWp!=2 i.e. (u dbar), (c sbar) e.g. allocate(tR%qq_hjWp(tR%nq_hjWp,np(Hneut)))
double precision, allocatable :: qq_hjWm(:,:)
integer :: nq_hjWm!=2 i.e. (ubar d), (cbar s)
double precision, allocatable :: gg_hj(:)
double precision, allocatable :: qq_hj(:,:)
integer :: nq_hj!=5 i.e.(d dbar), (u ubar), (s sbar), (c cbar), (b bbar)
double precision, allocatable :: gg_hjZ(:)
double precision, allocatable :: qq_hjZ(:,:)
integer :: nq_hjZ!=5 i.e.(d dbar), (u ubar), (s sbar), (c cbar), (b bbar)
double precision, allocatable :: bg_hjb(:)
end type
type(hadroncolliderextras), allocatable :: partR(:)
!-------------------------------------------
!associated with 'output'--------------------
integer rep
type results
integer, allocatable :: chan(:)
double precision, allocatable :: obsratio(:)
double precision, allocatable :: predratio(:)
double precision, allocatable :: sfactor(:)
double precision, allocatable :: axis_i(:)
double precision, allocatable :: axis_j(:)
integer, allocatable :: allowed95(:)
integer, allocatable :: ncombined(:)
character(LEN=4), allocatable :: channelselection(:)
end type
type(results), allocatable :: res(:)
!--new in HB-4:
type fullresults
integer :: chan = 0
integer :: ncombined = 0
integer :: allowed95 = 1
double precision :: obsratio = 0.0D0
end type
type(fullresults), allocatable :: fullHBres(:)
integer, allocatable :: allocate_if_stats_required(:)
! Needed to store relevant information on next-to-most sensitive channels:
integer,allocatable :: HBresult_all(:,:), chan_all(:,:), ncombined_all(:,:)
double precision,allocatable :: obsratio_all(:,:),predratio_all(:,:)
!-------------------------------------------
contains
subroutine HiggsBounds_info
implicit none
write(*,*)
write(*,*)"~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
write(*,*)"~ ~"
write(*,*)"~ HiggsBounds "//adjustl(vers)//" ~"
write(*,*)"~ ~"
write(*,*)"~ Philip Bechtle, Daniel Dercks, Sven Heinemeyer, ~"
write(*,*)"~ Tim Stefaniak, Georg Weiglein ~"
write(*,*)"~ ~"
write(*,*)"~ arXiv:0811.4169, arXiv:1102.1898, ~"
write(*,*)"~ arXiv:1301.2345, arXiv:1311.0055 ~"
write(*,*)"~ arXiv:1507.06706, ~"
write(*,*)"~ http://higgsbounds.hepforge.org ~"
write(*,*)"~ ~"
write(*,*)"~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~"
write(*,*)
write(*,*)"HiggsBounds collects together results from "
write(*,*)
write(*,*)" * the LEP collaborations and LEP Higgs Working Group"
write(*,*)" * the CDF and D0 Collaborations"
write(*,*)" * the ATLAS and CMS Collaborations"
write(*,*)" * the program HDECAY (arXiv:hep-ph/9704448)"
write(*,*)" * the program VH@NNLO (arXiv:1210.5347)"
write(*,*)" * TeV4LHC Higgs Working Group report"
write(*,*)" (see arXiv:hep-ph/0612172 and ref. therein)"
write(*,*)" * LHC Higgs Cross Section Working Group"
write(*,*)" (arXiv:1101.0593, arXiv:1201.3084, arXiv:1307.1347,"
write(*,*)" arXiv:1610.07922 and ref. therein)"
write(*,*)
end subroutine HiggsBounds_info
!**********************************************************
function div(a,b,divlimit,div0res)
!**********************************************************
! be careful about using this - not a mathematical limit
double precision :: div
!--------------------------------------input
double precision :: a,b,divlimit,div0res
!-----------------------------------internal
double precision :: small1,small2
!-------------------------------------------
small1 = 1.0D-28
small2 = 1.0D-20
if(abs(b).gt.small1)then
div=a/b
elseif(abs(a).lt.small2)then
div=divlimit
if(div.lt.0)stop 'error type divA (see function div in module usefulbits)'
else
div=div0res
if(div.lt.0)stop 'error type divB (see function div in module usefulbits)'
endif
end function
!--TESTING
!**********************************************************
subroutine iselementofarray(value, array, output)
!**********************************************************
implicit none
!-------------------------------------input and output
double precision, intent(in) :: value
double precision, allocatable, dimension(:), intent(in) :: array
integer, intent(out) :: output
!---------------------------------------------internal
integer :: i
double precision :: small
!-----------------------------------------------------
small = 1.0D-20
output = -1
if(allocated(array)) then
do i=lbound(array,dim=1),ubound(array,dim=1)
if(abs(value-array(i)).le.small) output = 1
enddo
else
stop 'error: Passing an unallocated array to subroutine iselementofarray!'
endif
end subroutine iselementofarray
!----
!**********************************************************
subroutine fill_pdesc
!**********************************************************
integer :: x
if(ubound(np,dim=1).ne.4)stop 'error: have made a mistake in subroutine fill_pdesc (1)'
x=0
allocate( pdesc( ubound(np,dim=1) ) )
x=x+1
pdesc(x)%short='h'
pdesc(x)%long ='neutral Higgs boson'
x=x+1
pdesc(x)%short='hplus'
pdesc(x)%long ='charged Higgs boson'
x=x+1
pdesc(x)%short='N'
pdesc(x)%long ='neutralino'
x=x+1
pdesc(x)%short='C'
pdesc(x)%long ='chargino'
if(x.ne.ubound(np,dim=1))stop 'error: have made a mistake in subroutine fill_pdesc (2)'
end subroutine fill_pdesc
!**********************************************************
subroutine allocate_dataset_parts(d,n_addit)
!**********************************************************
implicit none
!-------------------------------------------
type(dataset) :: d(:)
!--------------------------------------input
integer, intent(in) :: n_addit
!-----------------------------------internal
integer :: n_add,x,y
integer, allocatable :: np_t(:)
!-------------------------------------------
allocate(np_t(lbound(np,dim=1):ubound(np,dim=1)))
np_t=np
do x=lbound(np_t,dim=1),ubound(np_t,dim=1)
if(np(x)>0)then
np_t(x)=np(x)
elseif(np(x).eq.0)then
np_t(x)=1
else
write(*,*)'np=',np
stop 'error in subroutine allocate_dataset_parts (1)'
endif
enddo
if(n_addit>0)then
n_add=n_addit
elseif(n_addit.eq.0)then
n_add=1
else
stop 'error in subroutine allocate_dataset_parts (2)'
endif
do x=lbound(d,dim=1),ubound(d,dim=1)
allocate(d(x)%additional(n_add))
allocate(d(x)%particle( ubound(np_t,dim=1) ))
do y= 1,ubound(np_t,dim=1)
allocate(d(x)%particle(y)%M( np_t(y) ))
allocate(d(x)%particle(y)%Mc( np_t(y) ))
allocate(d(x)%particle(y)%GammaTot( np_t(y) ))
allocate(d(x)%particle(y)%dM( np_t(y) ))
allocate(d(x)%particle(y)%dMh( np_t(y) ))
enddo
allocate(d(x)%lep%XS_hjZ_ratio( np_t(Hneut) ))
allocate(d(x)%lep%XS_bbhj_ratio( np_t(Hneut) ))
allocate(d(x)%lep%XS_tautauhj_ratio( np_t(Hneut) ))
allocate(d(x)%lep%XS_hjhi_ratio( np_t(Hneut),np_t(Hneut) ))
allocate(d(x)%lep%XS_HpjHmj_ratio( np_t(Hplus) ))
allocate(d(x)%lep%XS_CpjCmj( np_t(Chiplus) ))
allocate(d(x)%lep%XS_NjNi( np_t(Chineut),np_t(Chineut) ))
allocate(d(x)%BR_hjss( np_t(Hneut) ))
allocate(d(x)%BR_hjcc( np_t(Hneut) ))
allocate(d(x)%BR_hjbb( np_t(Hneut) ))
allocate(d(x)%BR_hjtt( np_t(Hneut) ))
allocate(d(x)%BR_hjmumu( np_t(Hneut) ))
allocate(d(x)%BR_hjtautau( np_t(Hneut) ))
allocate(d(x)%BR_hkhjhi( np_t(Hneut),np_t(Hneut),np_t(Hneut) ))
allocate(d(x)%BR_hjhihi( np_t(Hneut),np_t(Hneut) ))
- allocate(d(x)%BR_hjhiZ( np_t(Hneut),np_t(Hneut) ))
+ allocate(d(x)%BR_hjhiZ( np_t(Hneut),np_t(Hneut) ))
+ allocate(d(x)%BR_hjHpiW( np_t(Hneut),np_t(Hplus) ))
allocate(d(x)%BR_hjWW( np_t(Hneut) ))
allocate(d(x)%BR_hjZZ( np_t(Hneut) ))
allocate(d(x)%BR_hjZga( np_t(Hneut) ))
allocate(d(x)%BR_hjgaga( np_t(Hneut) ))
allocate(d(x)%BR_hjgg( np_t(Hneut) ))
allocate(d(x)%BR_hjinvisible( np_t(Hneut) ))
allocate(d(x)%BR_hjemu( np_t(Hneut) ))
allocate(d(x)%BR_hjetau( np_t(Hneut) ))
allocate(d(x)%BR_hjmutau( np_t(Hneut) ))
allocate(d(x)%BR_tHpjb( np_t(Hplus) ))
allocate(d(x)%BR_Hpjcs( np_t(Hplus) ))
allocate(d(x)%BR_Hpjcb( np_t(Hplus) ))
allocate(d(x)%BR_Hpjtaunu( np_t(Hplus) ))
allocate(d(x)%BR_Hpjtb( np_t(Hplus) ))
allocate(d(x)%BR_HpjWZ( np_t(Hplus) ))
allocate(d(x)%BR_HpjhiW( np_t(Hplus),np_t(Hneut) ))
allocate(d(x)%BR_CjqqNi( np_t(Chiplus),np_t(Chineut) ))
allocate(d(x)%BR_CjlnuNi( np_t(Chiplus),np_t(Chineut) ))
allocate(d(x)%BR_CjWNi( np_t(Chiplus),np_t(Chineut) ))
allocate(d(x)%BR_NjqqNi( np_t(Chineut),np_t(Chineut) ))
allocate(d(x)%BR_NjZNi( np_t(Chineut),np_t(Chineut) ))
allocate(d(x)%tev%XS_hjb_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_tthj_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_vbf_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_hjZ_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_hjW_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_hj_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_gg_hj_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_bb_hj_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_thj_tchan_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_thj_schan_ratio( np_t(Hneut) ))
allocate(d(x)%tev%XS_hjhi( np_t(Hneut),np_t(Hneut) ))
allocate(d(x)%tev%XS_vbf_Hpj( np_t(Hplus) ))
allocate(d(x)%tev%XS_Hpjtb( np_t(Hplus) ))
+ allocate(d(x)%tev%XS_Hpjcb( np_t(Hplus) ))
allocate(d(x)%tev%XS_Hpjbjet( np_t(Hplus) ))
+ allocate(d(x)%tev%XS_Hpjcjet( np_t(Hplus) ))
+ allocate(d(x)%tev%XS_Hpjjetjet( np_t(Hplus) ))
allocate(d(x)%tev%XS_HpjW( np_t(Hplus) ))
allocate(d(x)%tev%XS_HpjZ( np_t(Hplus) ))
allocate(d(x)%tev%XS_HpjHmj( np_t(Hplus) ))
allocate(d(x)%tev%XS_Hpjhi( np_t(Hplus), np_t(Hneut) ))
allocate(d(x)%lhc7%XS_hjb_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_tthj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_vbf_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_hjZ_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_hjW_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_hj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_gg_hj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_bb_hj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_thj_tchan_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_thj_schan_ratio( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_hjhi( np_t(Hneut),np_t(Hneut) ))
allocate(d(x)%lhc7%XS_vbf_Hpj( np_t(Hplus) ))
allocate(d(x)%lhc7%XS_Hpjtb( np_t(Hplus) ))
+ allocate(d(x)%lhc7%XS_Hpjcb( np_t(Hplus) ))
allocate(d(x)%lhc7%XS_Hpjbjet( np_t(Hplus) ))
+ allocate(d(x)%lhc7%XS_Hpjcjet( np_t(Hplus) ))
+ allocate(d(x)%lhc7%XS_Hpjjetjet( np_t(Hplus) ))
allocate(d(x)%lhc7%XS_HpjW( np_t(Hplus) ))
allocate(d(x)%lhc7%XS_HpjZ( np_t(Hplus) ))
allocate(d(x)%lhc7%XS_HpjHmj( np_t(Hplus) ))
allocate(d(x)%lhc7%XS_Hpjhi( np_t(Hplus), np_t(Hneut) ))
allocate(d(x)%lhc8%XS_hjb_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_tthj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_vbf_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_hjZ_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_hjW_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_hj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_gg_hj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_bb_hj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_thj_tchan_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_thj_schan_ratio( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_hjhi( np_t(Hneut),np_t(Hneut) ))
allocate(d(x)%lhc8%XS_vbf_Hpj( np_t(Hplus) ))
allocate(d(x)%lhc8%XS_Hpjtb( np_t(Hplus) ))
+ allocate(d(x)%lhc8%XS_Hpjcb( np_t(Hplus) ))
allocate(d(x)%lhc8%XS_Hpjbjet( np_t(Hplus) ))
+ allocate(d(x)%lhc8%XS_Hpjcjet( np_t(Hplus) ))
+ allocate(d(x)%lhc8%XS_Hpjjetjet( np_t(Hplus) ))
allocate(d(x)%lhc8%XS_HpjW( np_t(Hplus) ))
allocate(d(x)%lhc8%XS_HpjZ( np_t(Hplus) ))
allocate(d(x)%lhc8%XS_HpjHmj( np_t(Hplus) ))
allocate(d(x)%lhc8%XS_Hpjhi( np_t(Hplus), np_t(Hneut) ))
allocate(d(x)%lhc13%XS_hjb_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_tthj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_vbf_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_hjZ_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_hjW_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_hj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_gg_hj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_bb_hj_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_thj_tchan_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_thj_schan_ratio( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_hjhi( np_t(Hneut),np_t(Hneut) ))
allocate(d(x)%lhc13%XS_vbf_Hpj( np_t(Hplus) ))
allocate(d(x)%lhc13%XS_Hpjtb( np_t(Hplus) ))
+ allocate(d(x)%lhc13%XS_Hpjcb( np_t(Hplus) ))
allocate(d(x)%lhc13%XS_Hpjbjet( np_t(Hplus) ))
+ allocate(d(x)%lhc13%XS_Hpjcjet( np_t(Hplus) ))
+ allocate(d(x)%lhc13%XS_Hpjjetjet( np_t(Hplus) ))
allocate(d(x)%lhc13%XS_HpjW( np_t(Hplus) ))
allocate(d(x)%lhc13%XS_HpjZ( np_t(Hplus) ))
allocate(d(x)%lhc13%XS_HpjHmj( np_t(Hplus) ))
allocate(d(x)%lhc13%XS_Hpjhi( np_t(Hplus), np_t(Hneut) ))
allocate(d(x)%CP_value( np_t(Hneut) ))
do y= 1,ubound(np_t,dim=1)
d(x)%particle(y)%M =-1.0D0
d(x)%particle(y)%Mc =-1.0D0
d(x)%particle(y)%GammaTot =0.0D0
d(x)%particle(y)%dM =0.0D0
d(x)%particle(y)%dMh =0.0D0
enddo
d(x)%lep%XS_hjZ_ratio =0.0D0
d(x)%lep%XS_bbhj_ratio =0.0D0
d(x)%lep%XS_tautauhj_ratio =0.0D0
d(x)%lep%XS_hjhi_ratio =0.0D0
d(x)%lep%XS_HpjHmj_ratio =0.0D0
d(x)%lep%XS_CpjCmj =0.0D0
d(x)%lep%XS_NjNi =0.0D0
d(x)%BR_hjss =0.0D0
d(x)%BR_hjcc =0.0D0
d(x)%BR_hjbb =0.0D0
d(x)%BR_hjtt =0.0D0
d(x)%BR_hjmumu =0.0D0
d(x)%BR_hjtautau =0.0D0
d(x)%BR_hjWW =0.0D0
d(x)%BR_hjZZ =0.0D0
d(x)%BR_hjZga =0.0D0
d(x)%BR_hjgaga =0.0D0
d(x)%BR_hjgg =0.0D0
d(x)%BR_hjinvisible =0.0D0
d(x)%BR_hjhihi =0.0D0
d(x)%BR_hkhjhi =0.0D0
+ d(x)%BR_hjHpiW =0.0D0
d(x)%BR_tWpb =0.0D0
d(x)%BR_tHpjb =0.0D0
d(x)%BR_Hpjcs =0.0D0
d(x)%BR_Hpjcb =0.0D0
d(x)%BR_Hpjtaunu =0.0D0
d(x)%BR_Hpjtb =0.0D0
d(x)%BR_HpjWZ =0.0D0
d(x)%BR_HpjhiW =0.0D0
d(x)%BR_CjqqNi =0.0D0
d(x)%BR_CjlnuNi =0.0D0
d(x)%BR_CjWNi =0.0D0
d(x)%BR_NjqqNi =0.0D0
d(x)%BR_NjZNi =0.0D0
d(x)%tev%XS_hjb_ratio =0.0D0
d(x)%tev%XS_tthj_ratio =0.0D0
d(x)%tev%XS_vbf_ratio =0.0D0
d(x)%tev%XS_hj_ratio =0.0D0
d(x)%tev%XS_hjW_ratio =0.0D0
d(x)%tev%XS_hjZ_ratio =0.0D0
d(x)%tev%XS_gg_hj_ratio = 0.0D0
d(x)%tev%XS_bb_hj_ratio = 0.0D0
d(x)%tev%XS_thj_tchan_ratio = 0.0D0
d(x)%tev%XS_thj_schan_ratio = 0.0D0
d(x)%tev%XS_hjhi = 0.0D0
d(x)%tev%XS_vbf_Hpj =0.0D0
d(x)%tev%XS_Hpjtb =0.0D0
+ d(x)%tev%XS_Hpjcb =0.0D0
d(x)%tev%XS_Hpjbjet =0.0D0
+ d(x)%tev%XS_Hpjcjet =0.0D0
+ d(x)%tev%XS_Hpjjetjet =0.0D0
d(x)%tev%XS_HpjW =0.0D0
d(x)%tev%XS_HpjZ =0.0D0
d(x)%tev%XS_HpjHmj =0.0D0
d(x)%tev%XS_Hpjhi =0.0D0
d(x)%lhc7%XS_hjb_ratio =0.0D0
d(x)%lhc7%XS_tthj_ratio =0.0D0
d(x)%lhc7%XS_vbf_ratio =0.0D0
d(x)%lhc7%XS_hj_ratio =0.0D0
d(x)%lhc7%XS_hjW_ratio =0.0D0
d(x)%lhc7%XS_hjZ_ratio =0.0D0
d(x)%lhc7%XS_gg_hj_ratio = 0.0D0
d(x)%lhc7%XS_bb_hj_ratio = 0.0D0
d(x)%lhc7%XS_thj_tchan_ratio = 0.0D0
d(x)%lhc7%XS_thj_schan_ratio = 0.0D0
d(x)%lhc7%XS_hjhi = 0.0D0
d(x)%lhc7%XS_vbf_Hpj =0.0D0
d(x)%lhc7%XS_Hpjtb =0.0D0
+ d(x)%lhc7%XS_Hpjcb =0.0D0
d(x)%lhc7%XS_Hpjbjet =0.0D0
+ d(x)%lhc7%XS_Hpjcjet =0.0D0
+ d(x)%lhc7%XS_Hpjjetjet =0.0D0
d(x)%lhc7%XS_HpjW =0.0D0
d(x)%lhc7%XS_HpjZ =0.0D0
d(x)%lhc7%XS_HpjHmj =0.0D0
d(x)%lhc7%XS_Hpjhi =0.0D0
d(x)%lhc8%XS_hjb_ratio =0.0D0
d(x)%lhc8%XS_tthj_ratio =0.0D0
d(x)%lhc8%XS_vbf_ratio =0.0D0
d(x)%lhc8%XS_hj_ratio =0.0D0
d(x)%lhc8%XS_hjW_ratio =0.0D0
d(x)%lhc8%XS_hjZ_ratio =0.0D0
d(x)%lhc8%XS_gg_hj_ratio = 0.0D0
d(x)%lhc8%XS_bb_hj_ratio = 0.0D0
d(x)%lhc8%XS_thj_tchan_ratio = 0.0D0
d(x)%lhc8%XS_thj_schan_ratio = 0.0D0
d(x)%lhc8%XS_hjhi = 0.0D0
d(x)%lhc8%XS_vbf_Hpj =0.0D0
d(x)%lhc8%XS_Hpjtb =0.0D0
+ d(x)%lhc8%XS_Hpjcb =0.0D0
d(x)%lhc8%XS_Hpjbjet =0.0D0
+ d(x)%lhc8%XS_Hpjcjet =0.0D0
+ d(x)%lhc8%XS_Hpjjetjet =0.0D0
d(x)%lhc8%XS_HpjW =0.0D0
d(x)%lhc8%XS_HpjZ =0.0D0
d(x)%lhc8%XS_HpjHmj =0.0D0
d(x)%lhc8%XS_Hpjhi =0.0D0
d(x)%lhc13%XS_hjb_ratio =0.0D0
d(x)%lhc13%XS_tthj_ratio =0.0D0
d(x)%lhc13%XS_vbf_ratio =0.0D0
d(x)%lhc13%XS_hj_ratio =0.0D0
d(x)%lhc13%XS_hjW_ratio =0.0D0
d(x)%lhc13%XS_hjZ_ratio =0.0D0
d(x)%lhc13%XS_gg_hj_ratio = 0.0D0
d(x)%lhc13%XS_bb_hj_ratio = 0.0D0
d(x)%lhc13%XS_thj_tchan_ratio = 0.0D0
d(x)%lhc13%XS_thj_schan_ratio = 0.0D0
d(x)%lhc13%XS_hjhi = 0.0D0
d(x)%lhc13%XS_vbf_Hpj =0.0D0
d(x)%lhc13%XS_Hpjtb =0.0D0
+ d(x)%lhc13%XS_Hpjcb =0.0D0
d(x)%lhc13%XS_Hpjbjet =0.0D0
+ d(x)%lhc13%XS_Hpjcjet =0.0D0
+ d(x)%lhc13%XS_Hpjjetjet =0.0D0
d(x)%lhc13%XS_HpjW =0.0D0
d(x)%lhc13%XS_HpjZ =0.0D0
d(x)%lhc13%XS_HpjHmj =0.0D0
d(x)%lhc13%XS_Hpjhi =0.0D0
d(x)%additional =0.0D0
d(x)%CP_value=0
enddo
select case(whichanalyses)
case('onlyH','LandH','onlyP','list ')
do x=lbound(d,dim=1),ubound(d,dim=1)
allocate(d(x)%tev%XS_HZ_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_HW_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_H_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_ttH_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_vbf_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_gg_H_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_bb_H_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_tH_tchan_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_tH_schan_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_Hb_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_Hb_c1_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_Hb_c2_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_Hb_c3_SM( np_t(Hneut) ))
allocate(d(x)%tev%XS_Hb_c4_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_HZ_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_HW_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_H_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_ttH_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_vbf_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_gg_H_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_bb_H_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_tH_tchan_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_tH_schan_SM( np_t(Hneut) ))
allocate(d(x)%lhc7%XS_Hb_SM( np_t(Hneut) ))
! allocate(d(x)%lhc7%XS_Hb_c1_SM( np_t(Hneut) ))
! allocate(d(x)%lhc7%XS_Hb_c2_SM( np_t(Hneut) ))
! allocate(d(x)%lhc7%XS_Hb_c3_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_HZ_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_HW_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_H_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_ttH_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_vbf_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_gg_H_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_bb_H_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_tH_tchan_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_tH_schan_SM( np_t(Hneut) ))
allocate(d(x)%lhc8%XS_Hb_SM( np_t(Hneut) ))
! allocate(d(x)%lhc8%XS_Hb_c1_SM( np_t(Hneut) ))
! allocate(d(x)%lhc8%XS_Hb_c2_SM( np_t(Hneut) ))
! allocate(d(x)%lhc8%XS_Hb_c3_SM( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_HZ_SM( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_HW_SM( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_H_SM( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_ttH_SM( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_vbf_SM( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_gg_H_SM( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_bb_H_SM( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_tH_tchan_SM( np_t(Hneut) ))
allocate(d(x)%lhc13%XS_tH_schan_SM( np_t(Hneut) ))
! allocate(d(x)%lhc8%XS_Hb_SM( np_t(Hneut) ))
allocate(d(x)%BR_Hbb_SM( np_t(Hneut) ))
allocate(d(x)%BR_Hcc_SM( np_t(Hneut) ))
allocate(d(x)%BR_Hss_SM( np_t(Hneut) ))
allocate(d(x)%BR_Htt_SM( np_t(Hneut) ))
allocate(d(x)%BR_Hmumu_SM( np_t(Hneut) ))
allocate(d(x)%BR_Htautau_SM( np_t(Hneut) ))
allocate(d(x)%BR_HWW_SM( np_t(Hneut) ))
allocate(d(x)%BR_HZZ_SM( np_t(Hneut) ))
allocate(d(x)%BR_HZga_SM( np_t(Hneut) ))
allocate(d(x)%BR_Hgaga_SM( np_t(Hneut) ))
allocate(d(x)%BR_Hgg_SM( np_t(Hneut) ))
allocate(d(x)%BR_Hjets_SM( np_t(Hneut) ))
allocate(d(x)%GammaTot_SM( np_t(Hneut) ))
enddo
case('onlyL')
case default
stop 'error in allocate_dataset_parts (3)'
end select
deallocate(np_t)
end subroutine allocate_dataset_parts
!**********************************************************
subroutine allocate_sqcouplratio_parts(gsq)
! to use this, gsq must be an array
!**********************************************************
implicit none
!-------------------------------------------
type(sqcouplratio) :: gsq(:)
!-----------------------------------internal
integer :: x
integer :: nHiggsneut
!-------------------------------------------
if(np(Hneut)>0)then
nHiggsneut=np(Hneut)
elseif(np(Hneut).eq.0)then
nHiggsneut=1
else
stop 'error in subroutine allocate_sqcouplratio_parts (1)'
endif
do x=lbound(gsq,dim=1),ubound(gsq,dim=1)
allocate(gsq(x)%hjss_s(nHiggsneut) ,gsq(x)%hjss_p(nHiggsneut))
allocate(gsq(x)%hjcc_s(nHiggsneut) ,gsq(x)%hjcc_p(nHiggsneut))
allocate(gsq(x)%hjbb_s(nHiggsneut) ,gsq(x)%hjbb_p(nHiggsneut))
allocate(gsq(x)%hjtoptop_s(nHiggsneut),gsq(x)%hjtoptop_p(nHiggsneut))
allocate(gsq(x)%hjmumu_s(nHiggsneut) ,gsq(x)%hjmumu_p(nHiggsneut))
allocate(gsq(x)%hjtautau_s(nHiggsneut),gsq(x)%hjtautau_p(nHiggsneut))
allocate(gsq(x)%hjWW(nHiggsneut) ,gsq(x)%hjZZ(nHiggsneut) )
allocate(gsq(x)%hjZga(nHiggsneut) )
allocate(gsq(x)%hjgaga(nHiggsneut) ,gsq(x)%hjgg(nHiggsneut) )
allocate(gsq(x)%hjggZ(nHiggsneut) )
allocate(gsq(x)%hjhiZ(nHiggsneut,nHiggsneut) )
gsq(x)%hjss_s =0.0D0
gsq(x)%hjss_p =0.0D0
gsq(x)%hjcc_s =0.0D0
gsq(x)%hjcc_p =0.0D0
gsq(x)%hjbb_s =0.0D0
gsq(x)%hjbb_p =0.0D0
gsq(x)%hjtoptop_s =0.0D0
gsq(x)%hjtoptop_p =0.0D0
gsq(x)%hjmumu_s =0.0D0
gsq(x)%hjmumu_p =0.0D0
gsq(x)%hjtautau_s =0.0D0
gsq(x)%hjtautau_p =0.0D0
gsq(x)%hjWW =0.0D0
gsq(x)%hjZZ =0.0D0
gsq(x)%hjZga =0.0D0
gsq(x)%hjgaga =0.0D0
gsq(x)%hjgg =0.0D0
gsq(x)%hjggZ =0.0D0
gsq(x)%hjhiZ =0.0D0
enddo
end subroutine allocate_sqcouplratio_parts
!**********************************************************
subroutine allocate_couplratio_parts(g)
! to use this, gsq must be an array
!**********************************************************
implicit none
!-------------------------------------------
type(couplratio) :: g(:)
!-----------------------------------internal
integer :: x
integer :: nHiggsneut
!-------------------------------------------
if(np(Hneut)>0)then
nHiggsneut=np(Hneut)
elseif(np(Hneut).eq.0)then
nHiggsneut=1
else
stop 'error in subroutine allocate_couplratio_parts (1)'
endif
do x=lbound(g,dim=1),ubound(g,dim=1)
allocate(g(x)%hjss_s(nHiggsneut) ,g(x)%hjss_p(nHiggsneut))
allocate(g(x)%hjcc_s(nHiggsneut) ,g(x)%hjcc_p(nHiggsneut))
allocate(g(x)%hjbb_s(nHiggsneut) ,g(x)%hjbb_p(nHiggsneut))
allocate(g(x)%hjtt_s(nHiggsneut) ,g(x)%hjtt_p(nHiggsneut))
allocate(g(x)%hjmumu_s(nHiggsneut) ,g(x)%hjmumu_p(nHiggsneut))
allocate(g(x)%hjtautau_s(nHiggsneut),g(x)%hjtautau_p(nHiggsneut))
allocate(g(x)%hjWW(nHiggsneut) ,g(x)%hjZZ(nHiggsneut))
allocate(g(x)%hjZga(nHiggsneut))
allocate(g(x)%hjgaga(nHiggsneut) ,g(x)%hjgg(nHiggsneut))
! allocate(g(x)%hjggZ(nHiggsneut) )
allocate(g(x)%hjhiZ(nHiggsneut,nHiggsneut))
g(x)%hjss_s =0.0D0
g(x)%hjss_p =0.0D0
g(x)%hjcc_s =0.0D0
g(x)%hjcc_p =0.0D0
g(x)%hjbb_s =0.0D0
g(x)%hjbb_p =0.0D0
g(x)%hjtt_s =0.0D0
g(x)%hjtt_p =0.0D0
g(x)%hjmumu_s =0.0D0
g(x)%hjmumu_p =0.0D0
g(x)%hjtautau_s =0.0D0
g(x)%hjtautau_p =0.0D0
g(x)%hjWW =0.0D0
g(x)%hjZZ =0.0D0
g(x)%hjZga =0.0D0
g(x)%hjgaga =0.0D0
g(x)%hjgg =0.0D0
! g(x)%hjggZ =0.0D0
g(x)%hjhiZ =0.0D0
enddo
end subroutine allocate_couplratio_parts
! !**********************************************************
! subroutine deallocate_sqcouplratio_parts(gsq)
! !**********************************************************
! implicit none
! !--------------------------------------input
! type(sqcouplratio) :: gsq(:)
! !-----------------------------------internal
! integer :: x
! !-------------------------------------------
!
! do x=lbound(gsq,dim=1),ubound(gsq,dim=1)
! deallocate(gsq(x)%hjbb )
! deallocate(gsq(x)%hjtautau )
! deallocate(gsq(x)%hjWW )
! deallocate(gsq(x)%hjZZ )
! deallocate(gsq(x)%hjgaga )
! deallocate(gsq(x)%hjgg )
! deallocate(gsq(x)%hjggZ )
! deallocate(gsq(x)%hjhiZ )
! enddo
!
! end subroutine deallocate_sqcouplratio_parts
!
!**********************************************************
subroutine allocate_hadroncolliderextras_parts(tR)
!**********************************************************
implicit none
!-------------------------------------------
type(hadroncolliderextras) :: tR(:)
!-----------------------------------internal
integer :: x
integer :: nHiggsneut
!-------------------------------------------
if(np(Hneut)>0)then
nHiggsneut=np(Hneut)
elseif(np(Hneut).eq.0)then
nHiggsneut=1
else
stop 'error in subroutine allocate_hadroncolliderextras_parts (1)'
endif
tR%nq_hjWp=2 ! (u dbar), (c sbar) e.g
tR%nq_hjWm=2 ! (ubar d), (cbar s)
tR%nq_hj=5 !(d dbar), (u ubar), (s sbar), (c cbar), (b bbar)
tR%nq_hjZ=5 !(d dbar), (u ubar), (s sbar), (c cbar), (b bbar)
do x=lbound(tR,dim=1),ubound(tR,dim=1)
allocate(tR(x)%qq_hjWp(tR(x)%nq_hjWp,nHiggsneut))
allocate(tR(x)%qq_hjWm(tR(x)%nq_hjWm,nHiggsneut))
allocate(tR(x)%gg_hj(nHiggsneut))
allocate(tR(x)%qq_hj(tR(x)%nq_hj,nHiggsneut))
allocate(tR(x)%gg_hjZ(nHiggsneut))
allocate(tR(x)%qq_hjZ(tR(x)%nq_hjZ,nHiggsneut))
allocate(tR(x)%bg_hjb(nHiggsneut))
tR(x)%qq_hjWp =0.0D0
tR(x)%qq_hjWm =0.0D0
tR(x)%gg_hj =0.0D0
tR(x)%qq_hj =0.0D0
tR(x)%gg_hjZ =0.0D0
tR(x)%qq_hjZ =0.0D0
tR(x)%bg_hjb =0.0D0
enddo
end subroutine allocate_hadroncolliderextras_parts
!**********************************************************
subroutine deallocate_hadroncolliderextras_parts(tR)
!**********************************************************
implicit none
!--------------------------------------input
type(hadroncolliderextras) :: tR(:)
!-----------------------------------internal
integer :: x
!-------------------------------------------
do x=lbound(tR,dim=1),ubound(tR,dim=1)
deallocate(tR(x)%qq_hjWp)
deallocate(tR(x)%qq_hjWm)
deallocate(tR(x)%gg_hj)
deallocate(tR(x)%qq_hj)
deallocate(tR(x)%gg_hjZ)
deallocate(tR(x)%qq_hjZ)
deallocate(tR(x)%bg_hjb)
enddo
end subroutine deallocate_hadroncolliderextras_parts
!**********************************************************
subroutine deallocate_usefulbits
!**********************************************************
! deallocates theo,res (and everything inside)
! deallocates c,predratio,fact
!************************************************************
implicit none
!-----------------------------------internal
integer x,y
!-------------------------------------------
deallocate(pdesc)!allocated in fill_pdesc
!these are allocated in subroutine do_input
do x=lbound(theo,dim=1),ubound(theo,dim=1)
deallocate(theo(x)%additional)
do y= 1,ubound(np,dim=1)
deallocate(theo(x)%particle(y)%M)
deallocate(theo(x)%particle(y)%GammaTot)
deallocate(theo(x)%particle(y)%dM)
deallocate(theo(x)%particle(y)%dMh)
enddo
deallocate(theo(x)%particle)
deallocate(theo(x)%lep%XS_hjZ_ratio)
deallocate(theo(x)%lep%XS_bbhj_ratio)
deallocate(theo(x)%lep%XS_tautauhj_ratio)
deallocate(theo(x)%lep%XS_hjhi_ratio)
deallocate(theo(x)%lep%XS_HpjHmj_ratio)
deallocate(theo(x)%lep%XS_CpjCmj)
deallocate(theo(x)%lep%XS_NjNi)
deallocate(theo(x)%BR_hjss)
deallocate(theo(x)%BR_hjcc)
deallocate(theo(x)%BR_hjbb)
deallocate(theo(x)%BR_hjtt)
deallocate(theo(x)%BR_hjmumu)
deallocate(theo(x)%BR_hjtautau)
deallocate(theo(x)%BR_hjhihi)
deallocate(theo(x)%BR_hjhiZ)
deallocate(theo(x)%BR_hkhjhi)
+ deallocate(theo(x)%BR_hjHpiW)
deallocate(theo(x)%BR_hjWW)
deallocate(theo(x)%BR_hjZZ)
deallocate(theo(x)%BR_hjZga)
deallocate(theo(x)%BR_hjgaga)
deallocate(theo(x)%BR_hjgg)
deallocate(theo(x)%BR_hjinvisible)
deallocate(theo(x)%BR_tHpjb)
deallocate(theo(x)%BR_Hpjcs)
deallocate(theo(x)%BR_Hpjcb)
deallocate(theo(x)%BR_Hpjtaunu)
deallocate(theo(x)%BR_Hpjtb)
deallocate(theo(x)%BR_HpjWZ)
deallocate(theo(x)%BR_HpjhiW)
deallocate(theo(x)%BR_CjqqNi)
deallocate(theo(x)%BR_CjlnuNi)
deallocate(theo(x)%BR_CjWNi)
deallocate(theo(x)%BR_NjqqNi)
deallocate(theo(x)%BR_NjZNi)
deallocate(theo(x)%tev%XS_hjb_ratio)
deallocate(theo(x)%tev%XS_tthj_ratio)
deallocate(theo(x)%tev%XS_vbf_ratio)
deallocate(theo(x)%tev%XS_hjZ_ratio)
deallocate(theo(x)%tev%XS_hjW_ratio)
deallocate(theo(x)%tev%XS_hj_ratio)
deallocate(theo(x)%tev%XS_gg_hj_ratio)
deallocate(theo(x)%tev%XS_bb_hj_ratio)
deallocate(theo(x)%tev%XS_thj_tchan_ratio)
deallocate(theo(x)%tev%XS_thj_schan_ratio)
deallocate(theo(x)%tev%XS_hjhi)
deallocate(theo(x)%tev%XS_vbf_Hpj)
deallocate(theo(x)%tev%XS_Hpjtb)
+ deallocate(theo(x)%tev%XS_Hpjcb)
deallocate(theo(x)%tev%XS_Hpjbjet)
+ deallocate(theo(x)%tev%XS_Hpjcjet)
+ deallocate(theo(x)%tev%XS_Hpjjetjet)
deallocate(theo(x)%tev%XS_HpjW)
deallocate(theo(x)%tev%XS_HpjZ)
deallocate(theo(x)%tev%XS_HpjHmj)
deallocate(theo(x)%tev%XS_Hpjhi)
deallocate(theo(x)%lhc7%XS_hjb_ratio)
deallocate(theo(x)%lhc7%XS_tthj_ratio)
deallocate(theo(x)%lhc7%XS_vbf_ratio)
deallocate(theo(x)%lhc7%XS_hjZ_ratio)
deallocate(theo(x)%lhc7%XS_hjW_ratio)
deallocate(theo(x)%lhc7%XS_hj_ratio)
deallocate(theo(x)%lhc7%XS_gg_hj_ratio)
deallocate(theo(x)%lhc7%XS_bb_hj_ratio)
deallocate(theo(x)%lhc7%XS_thj_tchan_ratio)
deallocate(theo(x)%lhc7%XS_thj_schan_ratio)
deallocate(theo(x)%lhc7%XS_hjhi)
deallocate(theo(x)%lhc7%XS_vbf_Hpj)
deallocate(theo(x)%lhc7%XS_Hpjtb)
+ deallocate(theo(x)%lhc7%XS_Hpjcb)
deallocate(theo(x)%lhc7%XS_Hpjbjet)
+ deallocate(theo(x)%lhc7%XS_Hpjcjet)
+ deallocate(theo(x)%lhc7%XS_Hpjjetjet)
deallocate(theo(x)%lhc7%XS_HpjW)
deallocate(theo(x)%lhc7%XS_HpjZ)
deallocate(theo(x)%lhc7%XS_HpjHmj)
deallocate(theo(x)%lhc7%XS_Hpjhi)
deallocate(theo(x)%lhc8%XS_hjb_ratio)
deallocate(theo(x)%lhc8%XS_tthj_ratio)
deallocate(theo(x)%lhc8%XS_vbf_ratio)
deallocate(theo(x)%lhc8%XS_hjZ_ratio)
deallocate(theo(x)%lhc8%XS_hjW_ratio)
deallocate(theo(x)%lhc8%XS_hj_ratio)
deallocate(theo(x)%lhc8%XS_gg_hj_ratio)
deallocate(theo(x)%lhc8%XS_bb_hj_ratio)
deallocate(theo(x)%lhc8%XS_thj_tchan_ratio)
deallocate(theo(x)%lhc8%XS_thj_schan_ratio)
deallocate(theo(x)%lhc8%XS_hjhi)
deallocate(theo(x)%lhc8%XS_vbf_Hpj)
deallocate(theo(x)%lhc8%XS_Hpjtb)
+ deallocate(theo(x)%lhc8%XS_Hpjcb)
deallocate(theo(x)%lhc8%XS_Hpjbjet)
+ deallocate(theo(x)%lhc8%XS_Hpjcjet)
+ deallocate(theo(x)%lhc8%XS_Hpjjetjet)
deallocate(theo(x)%lhc8%XS_HpjW)
deallocate(theo(x)%lhc8%XS_HpjZ)
deallocate(theo(x)%lhc8%XS_HpjHmj)
deallocate(theo(x)%lhc8%XS_Hpjhi)
deallocate(theo(x)%lhc13%XS_hjb_ratio)
deallocate(theo(x)%lhc13%XS_tthj_ratio)
deallocate(theo(x)%lhc13%XS_vbf_ratio)
deallocate(theo(x)%lhc13%XS_hjZ_ratio)
deallocate(theo(x)%lhc13%XS_hjW_ratio)
deallocate(theo(x)%lhc13%XS_hj_ratio)
deallocate(theo(x)%lhc13%XS_gg_hj_ratio)
deallocate(theo(x)%lhc13%XS_bb_hj_ratio)
deallocate(theo(x)%lhc13%XS_thj_tchan_ratio)
deallocate(theo(x)%lhc13%XS_thj_schan_ratio)
deallocate(theo(x)%lhc13%XS_hjhi)
deallocate(theo(x)%lhc13%XS_vbf_Hpj)
deallocate(theo(x)%lhc13%XS_Hpjtb)
+ deallocate(theo(x)%lhc13%XS_Hpjcb)
deallocate(theo(x)%lhc13%XS_Hpjbjet)
+ deallocate(theo(x)%lhc13%XS_Hpjcjet)
+ deallocate(theo(x)%lhc13%XS_Hpjjetjet)
deallocate(theo(x)%lhc13%XS_HpjW)
deallocate(theo(x)%lhc13%XS_HpjZ)
deallocate(theo(x)%lhc13%XS_HpjHmj)
deallocate(theo(x)%lhc13%XS_Hpjhi)
!deallocate(theo(x)%inLEPrange_Hpj)
!deallocate(theo(x)%inTEVrange_Hpj)
deallocate(theo(x)%CP_value)
enddo
select case(whichanalyses)
case('onlyH','LandH','onlyP','list ')
do x=lbound(theo,dim=1),ubound(theo,dim=1)
deallocate(theo(x)%BR_Hbb_SM)
deallocate(theo(x)%BR_Hss_SM)
deallocate(theo(x)%BR_Hcc_SM)
deallocate(theo(x)%BR_Hmumu_SM)
deallocate(theo(x)%BR_Htautau_SM)
deallocate(theo(x)%BR_HWW_SM)
deallocate(theo(x)%BR_HZZ_SM)
deallocate(theo(x)%BR_HZga_SM)
deallocate(theo(x)%BR_Hgaga_SM)
deallocate(theo(x)%BR_Hgg_SM)
deallocate(theo(x)%BR_Hjets_SM)
deallocate(theo(x)%GammaTot_SM)
deallocate(theo(x)%tev%XS_HZ_SM)
deallocate(theo(x)%tev%XS_HW_SM)
deallocate(theo(x)%tev%XS_H_SM)
deallocate(theo(x)%tev%XS_gg_H_SM)
deallocate(theo(x)%tev%XS_bb_H_SM)
deallocate(theo(x)%tev%XS_ttH_SM)
deallocate(theo(x)%tev%XS_vbf_SM)
!deallocate(theo(x)%tev%XS_H_SM_9713)
!deallocate(theo(x)%tev%XS_H_SM_9674)
deallocate(theo(x)%tev%XS_tH_tchan_SM)
deallocate(theo(x)%tev%XS_tH_schan_SM)
deallocate(theo(x)%tev%XS_Hb_SM)
deallocate(theo(x)%tev%XS_Hb_c1_SM)
deallocate(theo(x)%tev%XS_Hb_c2_SM)
deallocate(theo(x)%tev%XS_Hb_c3_SM)
deallocate(theo(x)%tev%XS_Hb_c4_SM)
deallocate(theo(x)%lhc7%XS_HZ_SM)
deallocate(theo(x)%lhc7%XS_HW_SM)
deallocate(theo(x)%lhc7%XS_H_SM)
deallocate(theo(x)%lhc7%XS_gg_H_SM)
deallocate(theo(x)%lhc7%XS_bb_H_SM)
deallocate(theo(x)%lhc7%XS_ttH_SM)
deallocate(theo(x)%lhc7%XS_vbf_SM)
deallocate(theo(x)%lhc7%XS_tH_tchan_SM)
deallocate(theo(x)%lhc7%XS_tH_schan_SM)
deallocate(theo(x)%lhc7%XS_Hb_SM)
! deallocate(theo(x)%lhc7%XS_Hb_c1_SM)
! deallocate(theo(x)%lhc7%XS_Hb_c2_SM)
! deallocate(theo(x)%lhc7%XS_Hb_c3_SM)
deallocate(theo(x)%lhc8%XS_HZ_SM)
deallocate(theo(x)%lhc8%XS_HW_SM)
deallocate(theo(x)%lhc8%XS_H_SM)
deallocate(theo(x)%lhc8%XS_gg_H_SM)
deallocate(theo(x)%lhc8%XS_bb_H_SM)
deallocate(theo(x)%lhc8%XS_ttH_SM)
deallocate(theo(x)%lhc8%XS_vbf_SM)
deallocate(theo(x)%lhc8%XS_tH_tchan_SM)
deallocate(theo(x)%lhc8%XS_tH_schan_SM)
deallocate(theo(x)%lhc8%XS_Hb_SM)
! deallocate(theo(x)%lhc8%XS_Hb_c1_SM)
! deallocate(theo(x)%lhc8%XS_Hb_c2_SM)
! deallocate(theo(x)%lhc8%XS_Hb_c3_SM)
deallocate(theo(x)%lhc13%XS_HZ_SM)
deallocate(theo(x)%lhc13%XS_HW_SM)
deallocate(theo(x)%lhc13%XS_H_SM)
deallocate(theo(x)%lhc13%XS_gg_H_SM)
deallocate(theo(x)%lhc13%XS_bb_H_SM)
deallocate(theo(x)%lhc13%XS_ttH_SM)
deallocate(theo(x)%lhc13%XS_vbf_SM)
deallocate(theo(x)%lhc13%XS_tH_tchan_SM)
deallocate(theo(x)%lhc13%XS_tH_schan_SM)
enddo
case('onlyL')
case default
stop 'error in deallocate_usefulbits'
end select
deallocate(theo) !allocated in subroutine do_input
!allocated in subroutine setup_output
if(allocated(res)) then
do x=lbound(res,dim=1),ubound(res,dim=1)
deallocate(res(x)%chan)
deallocate(res(x)%obsratio)
deallocate(res(x)%predratio)
deallocate(res(x)%axis_i)
deallocate(res(x)%axis_j)
deallocate(res(x)%sfactor)
deallocate(res(x)%allowed95)
deallocate(res(x)%ncombined)
enddo
deallocate(res) !allocated in subroutine setup_output
endif
if (allocated(fullHBres)) then
deallocate(fullHBres)
endif
! call deallocate_sqcouplratio_parts(g2)
do x=lbound(g2,dim=1),ubound(g2,dim=1)
deallocate(g2(x)%hjss_s)
deallocate(g2(x)%hjss_p)
deallocate(g2(x)%hjcc_s)
deallocate(g2(x)%hjcc_p)
deallocate(g2(x)%hjbb_s)
deallocate(g2(x)%hjbb_p)
deallocate(g2(x)%hjtoptop_s)
deallocate(g2(x)%hjtoptop_p)
deallocate(g2(x)%hjmumu_s)
deallocate(g2(x)%hjmumu_p)
deallocate(g2(x)%hjtautau_s)
deallocate(g2(x)%hjtautau_p)
deallocate(g2(x)%hjWW)
deallocate(g2(x)%hjZZ)
deallocate(g2(x)%hjZga)
deallocate(g2(x)%hjgaga)
deallocate(g2(x)%hjgg)
deallocate(g2(x)%hjggZ)
deallocate(g2(x)%hjhiZ)
enddo
deallocate(g2)
do x=lbound(effC,dim=1),ubound(effC,dim=1)
deallocate(effC(x)%hjss_s)
deallocate(effC(x)%hjss_p)
deallocate(effC(x)%hjcc_s)
deallocate(effC(x)%hjcc_p)
deallocate(effC(x)%hjbb_s)
deallocate(effC(x)%hjbb_p)
deallocate(effC(x)%hjtt_s)
deallocate(effC(x)%hjtt_p)
deallocate(effC(x)%hjmumu_s)
deallocate(effC(x)%hjmumu_p)
deallocate(effC(x)%hjtautau_s)
deallocate(effC(x)%hjtautau_p)
deallocate(effC(x)%hjWW)
deallocate(effC(x)%hjZZ)
deallocate(effC(x)%hjZga)
deallocate(effC(x)%hjgaga)
deallocate(effC(x)%hjgg)
! deallocate(effC(x)%hjggZ)
deallocate(effC(x)%hjhiZ)
enddo
deallocate(effC)
!these are allocated in subroutine do_input
call deallocate_hadroncolliderextras_parts(partR)
deallocate(partR) !allocated in subroutine do_input
if(allocated(pr)) deallocate(pr) !allocated in subroutine fill_pr or fill_pr_select
if(allocated(prsep)) deallocate(prsep) !allocated in subroutine fill_pr or fill_pr_select
if(allocated(diffMhneut)) deallocate(diffMhneut)
if(allocated(diffMhch)) deallocate(diffMhch)
if(allocated(dmn)) deallocate(dmn)
if(allocated(dmch)) deallocate(dmch)
if(allocated(analysislist)) deallocate(analysislist)
if(allocated(analysis_exclude_list)) deallocate(analysis_exclude_list)
if(allocated(HBresult_all)) deallocate(HBresult_all)
if(allocated(chan_all)) deallocate(chan_all)
if(allocated(ncombined_all)) deallocate(ncombined_all)
if(allocated(obsratio_all)) deallocate(obsratio_all)
if(allocated(predratio_all)) deallocate(predratio_all)
end subroutine deallocate_usefulbits
!**********************************************************
end module usefulbits
!******************************************************************
Index: trunk/HiggsBounds-5/example_programs/HBwithFH_dm.F
===================================================================
--- trunk/HiggsBounds-5/example_programs/HBwithFH_dm.F (revision 532)
+++ trunk/HiggsBounds-5/example_programs/HBwithFH_dm.F (revision 533)
@@ -1,623 +0,0 @@
-*********************************************************************
-* HBwithFH_dm
-*
-* Updated demo program for HiggsBounds 4 using MSSM input from
-* FeynHiggs (FH version > 2.9.4 required)
-*
-* This program uses MSSM Higgs mass uncertainties from FH and
-* demonstrates how to obtain constraints from individual Higgs bosons
-*
-*********************************************************************
-
- program HBwithFH_dm
- implicit none
-
- integer error
-
-c used by FHHiggsCorr
- double precision MHiggs(4)
- double complex SAeff, UHiggs(3,3), ZHiggs(3,3)
-
-c used by FHSelectUZ:
- integer uzint, uzext, mfeff
-
-c used by FHCouplings:
-#include "FHCouplings.h"
- double complex couplings(ncouplings), couplingsms(ncouplingsms)
- double precision gammas(ngammas), gammasms(ngammasms)
- integer fast
-
-c used by FHHiggsProd:
- double precision sqrts, prodxs(nprodxs)
-
-c used by FHGetPara:
- integer nmfv
- double precision MSf(2,4,3),MASf(6,4), MCha(2), MNeu(4)
- double complex USf(2,2,4,3),UASf(6,6,4)
- double complex UCha(2,2), VCha(2,2), ZNeu(4,4)
- double complex DeltaMB
- double precision MGl
- double precision MHtree(4), SAtree
-
-c used by FHRetrieveSMPara:
- double precision invAlfa, AlfasMZ, GF
- double precision ME, MU, MD, MM, MC, MS, ML, MB
- double precision MW, MZ
- double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
-
-c used by initialize_HiggsBounds
- integer nHiggsneut,nHiggsplus
- parameter (nHiggsneut = 3)
- parameter (nHiggsplus = 1)
- character(LEN=5) whichanalyses
-
-c used by HiggsBounds_neutral_input_part
- double precision Mh(3),GammaTotal_hj(3)
- integer CP_value(3)
- double precision CS_lep_hjZ_ratio(3),
- & CS_lep_bbhj_ratio(3),CS_lep_tautauhj_ratio(3),
- & CS_lep_hjhi_ratio_nHbynH(3,3),
- & CS_gg_hj_ratio(3),CS_bb_hj_ratio(3),
- & CS_bg_hjb_ratio(3),
- & CS_ud_hjWp_ratio(3),CS_cs_hjWp_ratio(3),
- & CS_ud_hjWm_ratio(3),CS_cs_hjWm_ratio(3),
- & CS_gg_hjZ_ratio(3),
- & CS_dd_hjZ_ratio(3),CS_uu_hjZ_ratio(3),
- & CS_ss_hjZ_ratio(3),CS_cc_hjZ_ratio(3),
- & CS_bb_hjZ_ratio(3),
- & CS_tev_vbf_ratio(3),CS_tev_tthj_ratio(3),
- & CS_lhc7_vbf_ratio(3),CS_lhc7_tthj_ratio(3),
- & CS_lhc8_vbf_ratio(3),CS_lhc8_tthj_ratio(3),
- & BR_hjss(3),BR_hjcc(3),
- & BR_hjbb(3),BR_hjmumu(3),BR_hjtautau(3),
- & BR_hjWW(3),BR_hjZZ(3),BR_hjZga(3),
- & BR_hjgaga(3),BR_hjgg(3),
- & BR_hjinvisible(3),BR_hjhihi_nHbynH(3,3)
-
-c used by HiggsBounds_charged_input
- double precision Mhplus(1),GammaTotal_Hpj(1),
- & CS_lep_HpjHmj_ratio(1),
- & BR_tWpb,BR_tHpjb(1),
- & BR_Hpjcs(1),BR_Hpjcb(1),BR_Hpjtaunu(1)
-
-c used by FHUncertainties
- double precision DeltaMHiggs(4)
- double complex DeltaSAeff, DeltaUHiggs(3,3), DeltaZHiggs(3,3)
-
-c used by set_mass_uncertainties
- double precision dmhneut(nHiggsneut)
- double precision dmhch(nHiggsplus)
-
-c used by run_HiggsBounds
- integer HBresult(0:4),chan(0:4),ncombined(0:4)
- double precision obsratio(0:4)
-
-c misc:
- integer i,j,as,t
- double precision norm,CW2,Pi
- double precision
- & g2hjbb(3),g2hjWW(3),g2hjZZ(3),
- & g2hjgg(3),g2hjhiZ_nHbynH(3,3)
- double precision g2hjbb_s(3),g2hjbb_p(3)
- double precision g2hjtautau_s(3),g2hjtautau_p(3)
- integer sneutrino_lspcandidate_number
- logical invisible_lsp
- double precision lspcandidate_mass
-
- Pi = 3.1415926535897932384626433832795029D0
-
-* * * * * * * * * * * * * * * * * * * * *
-
-
-c The string 'whichanalyses' determines which subset of experimental
-c results are used. In this example, we've used the option 'LandH',
-c which instructs HiggsBounds to use tables of results
-c from LEP, Tevatron and LHC (i.e. the full set of
-c results supplied with HiggsBounds).
- whichanalyses='LandH'
-
-c The subroutine initialize_HiggsBounds reads in all necessary
-c tables etc.
-c It must be called before any of the other HiggsBounds subroutines.
- call initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses)
-
-c If you would like to perform scans over variables, the subroutine
-c initialize_HiggsBounds (and finish_HiggsBounds) should be called
-c outside the do-loops in order to save time.
-
-* * * * * * * * * * * * * * * * * * * * *
-
-c calls to FH subroutines:
-
-c the subroutines setFlags, setPara, setSLHA
-c are also contained in this file
- call setFlags
-
-* either use setPara to set the parameters directly
-* or use setSLHA to read them from an SLHA file
- call setPara
-c call setSLHA("tmp.slha")
-
-c Use this for FH < 2.9.5
-c call FHGetPara(error, nmfv, MASf, UASf,
- call FHGetPara(error, nmfv, MSf, USf, MASf, UASf,
- & MCha, UCha, VCha, MNeu, ZNeu, DeltaMB, MGl,
- & MHtree, SAtree)
- if( error .ne. 0 ) stop
-
- call FHHiggsCorr(error, MHiggs, SAeff, UHiggs, ZHiggs)
- if( error .ne. 0 ) stop
-
- call FHUncertainties(error, DeltaMHiggs, DeltaSAeff,
- & DeltaUHiggs, DeltaZHiggs)
- if( error .ne. 0 ) stop
-
- dMhneut(1) = DeltaMHiggs(1)
- dMhneut(2) = DeltaMHiggs(2)
- dMhneut(3) = DeltaMHiggs(3)
- dMhch(1) = DeltaMHiggs(4)
-
-c NOTE: we are setting uzint=uzext
- mfeff=1
- uzint=2
- uzext=2
- call FHSelectUZ(error, uzint, uzext, mfeff)
- if( error .ne. 0 ) stop
-
- fast=1
- call FHCouplings(error,
- & couplings, couplingsms, gammas, gammasms, fast)
- if( error .ne. 0 ) stop
-
-c We would like FH to calculate LHC cross sections
- sqrts=8.0D0
- call FHHiggsProd(error, sqrts, prodxs)
- if( error .ne. 0 ) stop
-
- call FHRetrieveSMPara(error,
- & invAlfa, AlfasMZ, GF,
- & ME, MU, MD, MM, MC, MS, ML, MB,
- & MW, MZ,
- & CKMlambda, CKMA, CKMrhobar, CKMetabar)
-
-* * * * * * * * * * * * * * * * * * * * *
-
-c Set variables needed by HiggsBounds (using results from FeynHiggs).
-c See HiggsBounds documentation for definition of variables used
-c as arguments to HiggsBounds_neutral_input_part and run_HiggsBounds
-c and FeynHiggs documentation for all other variables.
-
-c Note: It is slightly more accurate to use the subroutine HiggsBounds_neutral_input_part
-c rather than the subroutine HiggsBounds_neutral_input_effC because the SM branching ratios
-c used internally in HiggsBounds (from HDecay) are not identical to the SM branching
-c ratios used in FeynHiggs
-
- do i=1,3
- Mh(i)=MHiggs(i)
- GammaTotal_hj(i) = GammaTot(i)
-
- BR_hjss(i) = BR(H0FF(i,4,2,2))
- BR_hjcc(i) = BR(H0FF(i,3,2,2))
- BR_hjbb(i) = BR(H0FF(i,4,3,3))
- BR_hjmumu(i) = BR(H0FF(i,2,2,2))
- BR_hjtautau(i) = BR(H0FF(i,2,3,3))
-
- BR_hjWW(i) = BR(H0VV(i,4))
- BR_hjgaga(i) = BR(H0VV(i,1))
- BR_hjZga(i) = BR(H0VV(i,2))
- BR_hjZZ(i) = BR(H0VV(i,3))
- BR_hjgg(i) = BR(H0VV(i,5))
-
- if(GammaSM(H0FF(i,4,3,3)).le.0.0D0)then
- g2hjbb(i)=0.0D0
- else
- g2hjbb(i)=Gamma(H0FF(i,4,3,3))
- & /GammaSM(H0FF(i,4,3,3))
- endif
-
-c Note that this is currently equivalent to
-c g2hjbb(i)= bbh(i)/bbhSM(i)
-c g2hjbb(i)= btagbh(i)/btagbhSM(i)
-c as long as MH>80 GeV
-
- CS_bg_hjb_ratio(i) = g2hjbb(i)
- CS_bb_hj_ratio(i) = g2hjbb(i)
-
- g2hjbb_s(i)=(abs(RCoupling(H0FF(i,4,3,3))
- & /RCouplingSM(H0FF(i,4,3,3))+
- & LCoupling(H0FF(i,4,3,3))
- & /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
- g2hjbb_p(i)=(abs(RCoupling(H0FF(i,4,3,3))
- & /RCouplingSM(H0FF(i,4,3,3))-
- & LCoupling(H0FF(i,4,3,3))
- & /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
-
- g2hjtautau_s(i)=(abs(RCoupling(H0FF(i,2,3,3))
- & /RCouplingSM(H0FF(i,2,3,3))+
- & LCoupling(H0FF(i,2,3,3))
- & /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
- g2hjtautau_p(i)=(abs(RCoupling(H0FF(i,2,3,3))
- & /RCouplingSM(H0FF(i,2,3,3))-
- & LCoupling(H0FF(i,2,3,3))
- & /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
-
- if( g2hjbb_p(i).lt.1.0D-10)then
- CP_value(i) = 1
- elseif( g2hjbb_s(i).lt.1.0D-10)then
- CP_value(i) = -1
- else
- CP_value(i) = 0
- endif
-
- CS_lep_bbhj_ratio(i) = g2hjbb_s(i)+g2hjbb_p(i)
- CS_lep_tautauhj_ratio(i) = g2hjtautau_s(i)+g2hjtautau_p(i)
-
- g2hjWW(i)= dble( Coupling(H0VV(i,4))
- & / CouplingSM(H0VV(i,4)) )**2.0D0
- & + dimag( Coupling(H0VV(i,4))
- & / CouplingSM(H0VV(i,4)) )**2.0D0
-c Note that this is currently equivalent to
-c g2hjWW(i)= WhTev(i)/WhTevSM(i
-c g2hjWW(i)= qqhTev(i)/qqhTevSM(i)
-c as long as MH>80 GeV and uzint=uzext
-
- g2hjZZ(i)= dble( Coupling(H0VV(i,3))
- & / CouplingSM(H0VV(i,3)) )**2.0D0
- & + dimag( Coupling(H0VV(i,3))
- & / CouplingSM(H0VV(i,3)) )**2.0D0
-c Note that this is currently equivalent to
-c g2hjZZ(i)= ZhTev(i)/ZhTevSM(i)
-c as long as MH>80 GeV and uzint=uzext
-c It is also equivalent to g2hjWW(i)
-
- CS_lep_hjZ_ratio(i) = g2hjZZ(i)
-
- CS_gg_hjZ_ratio(i) = 0.0D0
- CS_dd_hjZ_ratio(i) = g2hjZZ(i)
- CS_uu_hjZ_ratio(i) = g2hjZZ(i)
- CS_ss_hjZ_ratio(i) = g2hjZZ(i)
- CS_cc_hjZ_ratio(i) = g2hjZZ(i)
- CS_bb_hjZ_ratio(i) = g2hjZZ(i)
-
- CS_ud_hjWp_ratio(i) = g2hjZZ(i)
- CS_cs_hjWp_ratio(i) = g2hjZZ(i)
- CS_ud_hjWm_ratio(i) = g2hjZZ(i)
- CS_cs_hjWm_ratio(i) = g2hjZZ(i)
-
- CS_tev_vbf_ratio(i) = g2hjZZ(i)
- CS_lhc7_vbf_ratio(i) = g2hjZZ(i)
- CS_lhc8_vbf_ratio(i) = g2hjZZ(i)
-
-
- if(tthSM(i).gt.0.0D0)then
- CS_tev_tthj_ratio(i) = tth(i)/tthSM(i)
- else
- CS_tev_tthj_ratio(i) = 0.0D0
- endif
-
- CS_lhc7_tthj_ratio(i) = CS_tev_tthj_ratio(i)
- CS_lhc8_tthj_ratio(i) = CS_tev_tthj_ratio(i)
-
-c tevatron gluon fusion XS is not calculated in FH is MH<90 geV
- if(Mh(i).gt.90.0001D0)then
- if(gghSM(i).gt.0.0D0)then
- CS_gg_hj_ratio(i) = ggh(i)/gghSM(i)
- else
- CS_gg_hj_ratio(i) = 0.0D0
- endif
- else
- if(GammaSM(H0VV(i,5)).le.0.0D0)then
- CS_gg_hj_ratio(i)=0.0D0
- else
- CS_gg_hj_ratio(i)= Gamma(H0VV(i,5))/GammaSM(H0VV(i,5))
- endif
- endif
-
- enddo
-
- norm=GF*sqrt(2.0D0)*MZ**2.0D0
-
- do j=1,3
- do i=1,3
- g2hjhiZ_nHbynH(j,i)= (
- & dble( Coupling(H0HV(j,i)) )**2.0D0
- & + dimag( Coupling(H0HV(j,i)) )**2.0D0
- & )
- & /norm
-
- CS_lep_hjhi_ratio_nHbynH(j,i) = g2hjhiZ_nHbynH(j,i)
-
- BR_hjhihi_nHbynH(j,i)=BR(H0HH(j,i,i))
- enddo
- enddo
-
-c higgs->neutralino1 neutralino1 contributes the invisible Higgs decay width
-c when neutralino1 or sneutrino is the LSP
-
- do i=1,3
- sneutrino_lspcandidate_number=0
- invisible_lsp=.True.
-
-c first determine whether lightest sneutrino is lighter than the lightest neutralino
-c
-c sneutrino_lspcandidate_number=0 indicates that lightest neutralino is
-c lighter than all the sneutrinos
- lspcandidate_mass=MNeu(1)
- do as=1,3
- if( MASf(as,1) .lt. lspcandidate_mass )then
- lspcandidate_mass=MASf(as,1)
- sneutrino_lspcandidate_number=as
- endif
- enddo
-
- if( MCha(1) .lt. lspcandidate_mass )then
- invisible_lsp=.False.
- elseif( MGl .lt. lspcandidate_mass )then
- invisible_lsp=.False.
- else
- do as=1,6
- do t=2,4
- if( MASf(as,t) .lt. lspcandidate_mass )then
- invisible_lsp=.False.
- endif
- enddo
- enddo
- endif
-
- if(invisible_lsp)then
- if(sneutrino_lspcandidate_number.eq.0)then
- BR_hjinvisible(i) = BR(H0NeuNeu(i,1,1))
- else
- BR_hjinvisible(i) = BR(H0SfSf(i,1,1,1,as))
- endif
- else
- BR_hjinvisible(i) = 0.0D0
- endif
- enddo
-
-* * * * * * * * * * * * * * * * * * * * *
-
-c Charged Higgs input
-
- Mhplus(1) = MHiggs(4)
- GammaTotal_Hpj(1) = GammaTot(4)
- CS_lep_HpjHmj_ratio(1) = 1.0D0
- BR_tWpb = BR( tBF(1) )
- BR_tHpjb(1) = BR( tBF(2) )
- BR_Hpjcs(1) = BR( HpFF(2,2,2) )
- BR_Hpjcb(1) = BR( HpFF(2,2,3) )
- BR_Hpjtaunu(1) = BR( HpFF(1,3,3) )
-
-* * * * * * * * * * * * * * * * * * * * *
-c calls to HiggsBounds_neutral_input_part,HiggsBounds_charged_input,
-c which give input to HiggsBounds
-
- print*,'calling HiggsBounds_neutral_input_part'
-
- call HiggsBounds_neutral_input_part(Mh,GammaTotal_hj,CP_value,
- & CS_lep_hjZ_ratio,
- & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio,
- & CS_lep_hjhi_ratio_nHbynH,
- & CS_gg_hj_ratio,CS_bb_hj_ratio,
- & CS_bg_hjb_ratio,
- & CS_ud_hjWp_ratio,CS_cs_hjWp_ratio,
- & CS_ud_hjWm_ratio,CS_cs_hjWm_ratio,
- & CS_gg_hjZ_ratio,
- & CS_dd_hjZ_ratio,CS_uu_hjZ_ratio,
- & CS_ss_hjZ_ratio,CS_cc_hjZ_ratio,
- & CS_bb_hjZ_ratio,
- & CS_tev_vbf_ratio,CS_tev_tthj_ratio,
- & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio,
- & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio,
- & BR_hjss,BR_hjcc,
- & BR_hjbb,BR_hjmumu,BR_hjtautau,
- & BR_hjWW,BR_hjZZ,BR_hjZga, BR_hjgaga,BR_hjgg,
- & BR_hjinvisible,BR_hjhihi_nHbynH )
-
- print*,'calling HiggsBounds_charged_input'
- call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj,
- & CS_lep_HpjHmj_ratio,
- & BR_tWpb,BR_tHpjb,
- & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu)
-
-
- print*,'calling HiggsBounds_set_mass_uncertainties'
- call HiggsBounds_set_mass_uncertainties(dmhneut,dmhch)
-
-* * * * * * * * * * * * * * * * * * * * *
-c call to run_HiggsBounds
- call run_HiggsBounds_full( HBresult,chan, obsratio,ncombined)
-
- print*,' '
- print*,'***************** HiggsBounds Results ******************'
- print*,' '
- print*,'Is this parameter point excluded by LEP, Tevatron'
- print*,'or LHC data?'
- print*, HBresult(0), ', where'
- print*,' 0 = yes, it is excluded'
- print*,' 1 = no, it has not been excluded'
- print*,' -1 = invalid parameter set'
- print*,' '
- print*,'The process with the highest statistical sensitivity'
- print*,'is'
- print*, chan(0),'(see Key.dat)'
- print*,'This process has a theoretical rate vs. limit of'
- print*, obsratio(0)
- print*,' '
- print*,'The number of Higgs which have contributed to the'
- print*,'theoretical rate of this process was'
- print*, ncombined(0)
- print*,' '
- print*,'The results for individual Higgs bosons was:'
- print*,' id Mass (with unc.) hbres chan obsratio ncomb'
- do i=1,4
- write(*,69) i, MHiggs(i), DeltaMHiggs(i), HBresult(i),
- & chan(i), obsratio(i), ncombined(i)
- enddo
- print*, ''
- print*,'See HiggsBounds documentation for more information.'
- print*,'**********************************************************'
- print*,' '
-
-69 format(I5,F10.2,'+-',F3.1 ' GeV',I7,I8,F11.3,I7)
-
-* * * * * * * * * * * * * * * * * * * * *
-c deallocates arrays used by HiggsBounds:
-
- call finish_HiggsBounds
-
- end
-
-
-************************************************************************
-
- subroutine setFlags
- implicit none
-
- integer mssmpart, fieldren, tanbren, higgsmix, p2approx
- integer looplevel, runningMT, botResum, tlCplxApprox
-
-c Using default (recommended) values of all FH flags
- parameter (mssmpart = 4)
- parameter (fieldren = 0)
- parameter (tanbren = 0)
- parameter (higgsmix = 2)
- parameter (p2approx = 0)
- parameter (looplevel = 2)
- parameter (runningMT = 1)
- parameter (botResum = 1)
- parameter (tlCplxApprox = 0)
-
- integer error
-
- call FHSetFlags(error, mssmpart, fieldren, tanbren,
- & higgsmix, p2approx, looplevel,
- & runningMT, botResum, tlCplxApprox)
- if( error .ne. 0 ) stop
- end
-
-************************************************************************
-
- subroutine setPara
- implicit none
-
- double precision invAlfa, AlfasMZ, GF
- double precision ME, MU, MD, MM, MC, MS, ML, MB, MZ, MW
- double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
- parameter (invAlfa = -1)
- parameter (AlfasMZ = -1)
- parameter (GF = -1)
- parameter (ME = -1)
- parameter (MU = -1)
- parameter (MD = -1)
- parameter (MM = -1)
- parameter (MC = -1)
- parameter (MS = -1)
- parameter (ML = -1)
- parameter (MB = -1)
- parameter (MW = -1)
- parameter (MZ = -1)
- parameter (CKMlambda = -1)
- parameter (CKMA = -1)
- parameter (CKMrhobar = -1)
- parameter (CKMetabar = -1)
-
- double precision MT, TB, MA0, MHp
- parameter (MT = 173.2)
- parameter (TB = 20.)
- parameter (MA0 = 300)
- parameter (MHp = -1)
-
- double precision MSusy
- double precision M3SL, M2SL, M1SL
- double precision M3SE, M2SE, M1SE
- double precision M3SQ, M2SQ, M1SQ
- double precision M3SU, M2SU, M1SU
- double precision M3SD, M2SD, M1SD
- parameter (MSusy = 1000)
- parameter (M3SL = MSusy)
- parameter (M2SL = M3SL)
- parameter (M1SL = M2SL)
- parameter (M3SE = MSusy)
- parameter (M2SE = M3SE)
- parameter (M1SE = M2SE)
- parameter (M3SQ = MSusy)
- parameter (M2SQ = M3SQ)
- parameter (M1SQ = M2SQ)
- parameter (M3SU = MSusy)
- parameter (M2SU = M3SU)
- parameter (M1SU = M2SU)
- parameter (M3SD = MSusy)
- parameter (M2SD = M3SD)
- parameter (M1SD = M2SD)
-
- double complex Atau, At, Ab
- double complex Amu, Ac, As
- double complex Ae, Au, Ad
- parameter (At = 0)
- parameter (Ab = At)
- parameter (Atau = At)
- parameter (Ac = At)
- parameter (As = Ab)
- parameter (Amu = Atau)
- parameter (Au = Ac)
- parameter (Ad = As)
- parameter (Ae = Amu)
-
- double complex MUE, M_1, M_2, M_3
- parameter (MUE = 200)
- parameter (M_1 = 0)
- parameter (M_2 = 200)
- parameter (M_3 = 800)
-
- double precision Qtau, Qt, Qb
- parameter (Qtau = 0)
- parameter (Qt = 0)
- parameter (Qb = 0)
-
- double precision scalefactor
- parameter (scalefactor = 1)
-
- integer error
-
- call FHSetSMPara(error,
- & invAlfa, AlfasMZ, GF,
- & ME, MU, MD, MM, MC, MS, ML, MB,
- & MW, MZ,
- & CKMlambda, CKMA, CKMrhobar, CKMetabar)
- if( error .ne. 0 ) stop
-
- call FHSetPara(error, scalefactor,
- & MT, TB, MA0, MHp,
- & M3SL, M3SE, M3SQ, M3SU, M3SD,
- & M2SL, M2SE, M2SQ, M2SU, M2SD,
- & M1SL, M1SE, M1SQ, M1SU, M1SD,
- & MUE,
- & Atau, At, Ab,
- & Amu, Ac, As,
- & Ae, Au, Ad,
- & M_1, M_2, M_3,
- & Qtau, Qt, Qb)
- if( error .ne. 0 ) stop
- end
-
-************************************************************************
-
- subroutine setSLHA(filename)
- implicit none
- character*(*) filename
-
-#include "SLHA.h"
-
- integer error
- double complex slhadata(nslhadata)
-
- call SLHARead(error, slhadata, filename, 1)
- if( error .ne. 0 ) stop
-
- call FHSetSLHA(error, slhadata)
- if( error .ne. 0 ) stop
- end
-
-
-
Index: trunk/HiggsBounds-5/example_programs/HB5withFH.F
===================================================================
--- trunk/HiggsBounds-5/example_programs/HB5withFH.F (revision 532)
+++ trunk/HiggsBounds-5/example_programs/HB5withFH.F (revision 533)
@@ -1,591 +0,0 @@
-*********************************************************************
-* HBwithFH
-*
-* Updated demo program for HiggsBounds 4 using MSSM input from
-* FeynHiggs (FH version > 2.9.4 required)
-*
-*********************************************************************
-
- program HB5withFH
- implicit none
-
- integer error
-
-c used by FHHiggsCorr
- double precision MHiggs(4)
- double complex SAeff, UHiggs(3,3), ZHiggs(3,3)
-
-c used by FHSelectUZ:
- integer uzint, uzext, mfeff
-
-c used by FHCouplings:
-#include "FHCouplings.h"
- double complex couplings(ncouplings), couplingsms(ncouplingsms)
- double precision gammas(ngammas), gammasms(ngammasms)
- integer fast
-
-c used by FHHiggsProd:
- double precision sqrts, prodxs(nprodxs)
-
-c used by FHGetPara:
- integer nmfv
-c This is for FH 2.10.x
- double precision MSf(2,5,3), MASf(6,5), MCha(2), MNeu(4)
- double complex USf(2,2,5,3), UASf(6,6,5)
- double complex UCha(2,2), VCha(2,2), ZNeu(4,4)
- double complex DeltaMB
- double precision MGl
- double precision MHtree(4), SAtree
-
-c used by FHRetrieveSMPara:
- double precision invAlfa, AlfasMZ, GF
- double precision ME, MU, MD, MM, MC, MS, ML, MB
- double precision MW, MZ
- double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
-
-c used by initialize_HiggsBounds
- integer nHiggsneut,nHiggsplus
- character(LEN=5) whichanalyses
-
-c used by HiggsBounds_neutral_input_hadr
- character(LEN=5) collider_str
- double precision Mh(3),GammaTotal_hj(3)
- integer CP_value(3)
- double precision CS_lep_hjZ_ratio(3),
- & CS_lep_bbhj_ratio(3),CS_lep_tautauhj_ratio(3),
- & CS_lep_hjhi_ratio(3,3),CS_hj_ratio(4,3),
- & CS_gg_hj_ratio(4,3),CS_bb_hj_ratio(4,3),
- & CS_hjW_ratio(4,3),CS_hjZ_ratio(4,3),
- & CS_vbf_ratio(4,3),CS_tthj_ratio(4,3),
- & CS_thj_tchan_ratio(4,3),CS_thj_schan_ratio(4,3),
- & CS_hjhi(4,3,3),
- & BR_hjss(3),BR_hjcc(3),
- & BR_hjbb(3),BR_hjtt(3),BR_hjmumu(3),BR_hjtautau(3),
- & BR_hjWW(3),BR_hjZZ(3),BR_hjZga(3),
- & BR_hjgaga(3),BR_hjgg(3),
- & BR_hjinvisible(3),BR_hkhjhi(3,3,3),
- & BR_hjhiZ(3,3),BR_hjemu(3),BR_hjetau(3),BR_hjmutau(3)
-
-c used by HiggsBounds_charged_input
- double precision Mhplus(1),GammaTotal_Hpj(1),
- & CS_lep_HpjHmj_ratio(1),
- & BR_tWpb,BR_tHpjb(1),BR_Hpjcs(1),BR_Hpjcb(1),BR_Hpjtaunu(1),
- & BR_Hpjtb(1),BR_HpjWZ(1),BR_HpjhiW(1,3),
- & CS_Hpjtb(4,1), CS_Hpjbjet(4,1), CS_HpjW(4,1),
- & CS_HpjZ(4,1), CS_vbf_Hpj(4,1), CS_HpjHmj(4,1), CS_Hpjhi(4,1,3)
-
-c used by run_HiggsBounds
- integer HBresult,chan,ncombined
- double precision obsratio
-
-c misc:
- integer i,j,k,as,t,collider
- double precision norm,CW2,Pi
- double precision
- & g2hjbb(3),g2hjWW(3),g2hjZZ(3),
- & g2hjgg(3),g2hjhiZ(3,3)
- double precision g2hjbb_s(3),g2hjbb_p(3)
- double precision g2hjtautau_s(3),g2hjtautau_p(3)
- integer sneutrino_lspcandidate_number
- logical invisible_lsp
- double precision lspcandidate_mass
-
- Pi = 3.1415926535897932384626433832795029D0
-
-* * * * * * * * * * * * * * * * * * * * *
-
-c Set number of neutral and charged Higgs bosons in the MSSM:
- nHiggsneut=3
- nHiggsplus=1
-
-c The string 'whichanalyses' determines which subset of experimental
-c results are used. In this example, we've used the option 'LandH',
-c which instructs HiggsBounds to use tables of results
-c from LEP, Tevatron and LHC (i.e. the full set of
-c results supplied with HiggsBounds).
- whichanalyses='LandH'
-
-c The subroutine initialize_HiggsBounds reads in all necessary
-c tables etc.
-c It must be called before any of the other HiggsBounds subroutines.
- call initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses)
-
-c If you would like to perform scans over variables, the subroutine
-c initialize_HiggsBounds (and finish_HiggsBounds) should be called
-c outside the do-loops in order to save time.
-
-* * * * * * * * * * * * * * * * * * * * *
-
-c calls to FH subroutines:
-
-c the subroutines setFlags, setPara, setSLHA
-c are also contained in this file
- call setFlags
-
-* either use setPara to set the parameters directly
-* or use setSLHA to read them from an SLHA file
- call setPara
-c call setSLHA("tmp.slha")
-
-c // User this line for FH < 2.9.5
-c call FHGetPara(error, nmfv, MASf, UASf,
- call FHGetPara(error, nmfv, MSf, USf,MASf, UASf,
- & MCha, UCha, VCha, MNeu, ZNeu, DeltaMB, MGl,
- & MHtree, SAtree)
- if( error .ne. 0 ) stop
-
- call FHHiggsCorr(error, MHiggs, SAeff, UHiggs, ZHiggs)
- if( error .ne. 0 ) stop
-
-c NOTE: we are setting uzint=uzext
- mfeff=1
- uzint=2
- uzext=2
- call FHSelectUZ(error, uzint, uzext, mfeff)
- if( error .ne. 0 ) stop
-
- fast=1
- call FHCouplings(error,
- & couplings, couplingsms, gammas, gammasms, fast)
- if( error .ne. 0 ) stop
-
- call FHRetrieveSMPara(error,
- & invAlfa, AlfasMZ, GF,
- & ME, MU, MD, MM, MC, MS, ML, MB,
- & MW, MZ,
- & CKMlambda, CKMA, CKMrhobar, CKMetabar)
-
-* * * * * * * * * * * * * * * * * * * * *
-
-c Set variables needed by HiggsBounds (using results from FeynHiggs).
-c See HiggsBounds documentation for definition of variables used
-c as arguments to HiggsBounds_neutral_input_part and run_HiggsBounds
-c and FeynHiggs documentation for all other variables.
-
-c Note: It is slightly more accurate to use the subroutine HiggsBounds_neutral_input_part
-c rather than the subroutine HiggsBounds_neutral_input_effC because the SM branching ratios
-c used internally in HiggsBounds (from HDecay) are not identical to the SM branching
-c ratios used in FeynHiggs
-
- do i=1,3
- Mh(i)=MHiggs(i)
- GammaTotal_hj(i) = GammaTot(i)
-
- BR_hjss(i) = BR(H0FF(i,4,2,2))
- BR_hjcc(i) = BR(H0FF(i,3,2,2))
- BR_hjbb(i) = BR(H0FF(i,4,3,3))
- BR_hjtt(i) = BR(H0FF(i,3,3,3))
- BR_hjmumu(i) = BR(H0FF(i,2,2,2))
- BR_hjtautau(i) = BR(H0FF(i,2,3,3))
- BR_hjemu(i) = BR(H0FF(i,2,1,2))
- BR_hjetau(i) = BR(H0FF(i,2,1,3))
- BR_hjmutau(i) = BR(H0FF(i,2,2,3))
-
- BR_hjWW(i) = BR(H0VV(i,4))
- BR_hjgaga(i) = BR(H0VV(i,1))
- BR_hjZga(i) = BR(H0VV(i,2))
- BR_hjZZ(i) = BR(H0VV(i,3))
- BR_hjgg(i) = BR(H0VV(i,5))
-
- do collider=1,4
-c We would like FH to calculate LHC cross sections
- select case(collider)
- case(1)
- sqrts=2.0D0
- case(2)
- sqrts=7.0D0
- case(3)
- sqrts=8.0D0
- case(4)
- sqrts=13.0D0
- end select
-
- call FHHiggsProd(error, sqrts, prodxs)
- if( error .ne. 0 ) stop
-
- CS_gg_hj_ratio(collider,i)=ggh(i)/gghSM(i)
- write(*,*) "i,collider,CS_gghj_ratio = ", i,collider,CS_gg_hj_ratio(collider,i),ggh(i),gghSM(i)
- CS_bb_hj_ratio(collider,i)=bbh(i)/bbhSM(i)
- write(*,*) "i,collider,CS_bbhj_ratio = ", i,collider,CS_bb_hj_ratio(collider,i),bbh(i),bbhSM(i)
- CS_hj_ratio(collider,i)=(ggh(i)+bbh(i))/(gghSM(i)+bbhSM(i))
- CS_hjW_ratio(collider,i)=Wh(i)/WhSM(i)
- write(*,*) "i,collider,CS_hjW_ratio = ", i,collider,CS_hjW_ratio(collider,i),Wh(i),WhSM(i)
- CS_hjZ_ratio(collider,i)=Zh(i)/ZhSM(i)
- write(*,*) "i,collider,CS_hjZ_ratio = ", i,collider,CS_hjZ_ratio(collider,i),Zh(i),ZhSM(i)
- CS_vbf_ratio(collider,i)=qqh(i)/qqhSM(i)
- write(*,*) "i,collider,CS_qqhj_ratio = ", i,collider,CS_vbf_ratio(collider,i),qqh(i),qqhSM(i)
- CS_tthj_ratio(collider,i)=tth(i)/tthSM(i)
- write(*,*) "i,collider,CS_tthj_ratio = ", i,collider,CS_tthj_ratio(collider,i),tth(i),tthSM(i)
- CS_thj_tchan_ratio(collider,i)=0.0D0! NOT CALCULATED YET BY FH
- CS_thj_schan_ratio(collider,i)=0.0D0! NOT CALCULATED YET BY FH
- do j=1,3
- CS_hjhi(collider,i,j) = 0.0D0 ! NOT CALCULATED YET BY FH
- enddo
-
- CS_Hpjtb(collider,1)=tHm2 ! Charged Higgs cross section
- write(*,*) "Charged Higgs, collider ", tHm2, collider
- enddo
- BR_HpjhiW(1,i)=BR(HpHV(i))
-
- g2hjbb_s(i)=(abs(RCoupling(H0FF(i,4,3,3))
- & /RCouplingSM(H0FF(i,4,3,3))+
- & LCoupling(H0FF(i,4,3,3))
- & /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
- g2hjbb_p(i)=(abs(RCoupling(H0FF(i,4,3,3))
- & /RCouplingSM(H0FF(i,4,3,3))-
- & LCoupling(H0FF(i,4,3,3))
- & /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
-
- g2hjtautau_s(i)=(abs(RCoupling(H0FF(i,2,3,3))
- & /RCouplingSM(H0FF(i,2,3,3))+
- & LCoupling(H0FF(i,2,3,3))
- & /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
- g2hjtautau_p(i)=(abs(RCoupling(H0FF(i,2,3,3))
- & /RCouplingSM(H0FF(i,2,3,3))-
- & LCoupling(H0FF(i,2,3,3))
- & /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
-
- if( g2hjbb_p(i).lt.1.0D-10)then
- CP_value(i) = 1
- elseif( g2hjbb_s(i).lt.1.0D-10)then
- CP_value(i) = -1
- else
- CP_value(i) = 0
- endif
-
- CS_lep_bbhj_ratio(i) = g2hjbb_s(i)+g2hjbb_p(i)
- CS_lep_tautauhj_ratio(i) = g2hjtautau_s(i)+g2hjtautau_p(i)
-
- g2hjWW(i)= dble( Coupling(H0VV(i,4))
- & / CouplingSM(H0VV(i,4)) )**2.0D0
- & + dimag( Coupling(H0VV(i,4))
- & / CouplingSM(H0VV(i,4)) )**2.0D0
-
- g2hjZZ(i)= dble( Coupling(H0VV(i,3))
- & / CouplingSM(H0VV(i,3)) )**2.0D0
- & + dimag( Coupling(H0VV(i,3))
- & / CouplingSM(H0VV(i,3)) )**2.0D0
-
- CS_lep_hjZ_ratio(i) = g2hjZZ(i)
-
- enddo
- norm=GF*sqrt(2.0D0)*MZ**2.0D0
-
- do j=1,3
- do i=1,3
- g2hjhiZ(j,i)= (
- & dble( Coupling(H0HV(j,i)) )**2.0D0
- & + dimag( Coupling(H0HV(j,i)) )**2.0D0
- & )
- & /norm
-
- CS_lep_hjhi_ratio(j,i) = g2hjhiZ(j,i)
-
- BR_hjhiZ(j,i)=BR(H0HV(j,i))
- do k=1,3
- BR_hkhjhi(k,j,i)=BR(H0HH(k,j,i))
- enddo
- enddo
- enddo
-
-c higgs->neutralino1 neutralino1 contributes the invisible Higgs decay width
-c when neutralino1 or sneutrino is the LSP
-
- do i=1,3
- sneutrino_lspcandidate_number=0
- invisible_lsp=.True.
-
-c first determine whether lightest sneutrino is lighter than the lightest neutralino
-c
-c sneutrino_lspcandidate_number=0 indicates that lightest neutralino is
-c lighter than all the sneutrinos
- lspcandidate_mass=MNeu(1)
- do as=1,3
- if( MASf(as,1) .lt. lspcandidate_mass )then
- lspcandidate_mass=MASf(as,1)
- sneutrino_lspcandidate_number=as
- endif
- enddo
-
- if( MCha(1) .lt. lspcandidate_mass )then
- invisible_lsp=.False.
- elseif( MGl .lt. lspcandidate_mass )then
- invisible_lsp=.False.
- else
- do as=1,6
- do t=2,4
- if( MASf(as,t) .lt. lspcandidate_mass )then
- invisible_lsp=.False.
- endif
- enddo
- enddo
- endif
-
- if(invisible_lsp)then
- if(sneutrino_lspcandidate_number.eq.0)then
- BR_hjinvisible(i) = BR(H0NeuNeu(i,1,1))
- else
- BR_hjinvisible(i) = BR(H0SfSf(i,1,1,1,as))
- endif
- else
- BR_hjinvisible(i) = 0.0D0
- endif
-
- enddo
-
-* * * * * * * * * * * * * * * * * * * * *
-
-c Charged Higgs input
-
- Mhplus(1) = MHiggs(4)
- GammaTotal_Hpj(1) = GammaTot(4)
- CS_lep_HpjHmj_ratio(1) = 1.0D0
- BR_tWpb = BR( tBF(1) )
- BR_tHpjb(1) = BR( tBF(2) )
- BR_Hpjcs(1) = BR( HpFF(2,2,2) )
- BR_Hpjcb(1) = BR( HpFF(2,2,3) )
- BR_Hpjtaunu(1) = BR( HpFF(1,3,3) )
- BR_Hpjtb(1) = BR( HpFF(2,3,3) )
- BR_HpjWZ(1) = 0.0D0 ! NOT CALCULATED BY FH (0 in the MSSM at tree-level)
-
-* * * * * * * * * * * * * * * * * * * * *
-
- write(*,*) "Higgs masses: ", Mh
-
- call HiggsBounds_set_mass_uncertainties((/2.0D0,0.0D0,0.0D0/), 0.0D0)
-
- print*,'calling HiggsBounds_neutral_input_hadr'
-
- call HB5_neutral_input_properties(Mh,GammaTotal_hj,CP_value)
-
- call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj,
- & CS_lep_HpjHmj_ratio,
- & BR_tWpb,BR_tHpjb,
- & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu,BR_Hpjtb,
- & BR_HpjWZ,BR_HpjhiW)
-
- call HB5_neutral_input_SMBR(BR_hjss,BR_hjcc,BR_hjbb,
- & BR_hjtt,BR_hjmumu,
- & BR_hjtautau,BR_hjWW,
- & BR_hjZZ,BR_hjZga,BR_hjgaga,
- & BR_hjgg)
-
- call HB5_neutral_input_nonSMBR(BR_hjinvisible,BR_hkhjhi,BR_hjhiZ,
- & BR_hjemu,BR_hjetau,BR_hjmutau)
- do collider=1,4
- select case(collider)
- case(1)
- collider_str = 'TEV '
- case(2)
- collider_str = 'LHC7 '
- case(3)
- collider_str = 'LHC8 '
- case(4)
- collider_str = 'LHC13'
- end select
-
- call HB5_neutral_input_hadr(collider_str,CS_hj_ratio(collider,:),
- & CS_gg_hj_ratio(collider,:),CS_bb_hj_ratio(collider,:),
- & CS_hjW_ratio(collider,:),CS_hjZ_ratio(collider,:),
- & CS_vbf_ratio(collider,:),CS_tthj_ratio(collider,:),
- & CS_thj_tchan_ratio(collider,:),CS_thj_schan_ratio(collider,:),
- & CS_hjhi(collider,:,:))
-
- call HB5_charged_input_hadr(collider_str,CS_Hpjtb(collider,:),
- & CS_Hpjbjet(collider,:), CS_HpjW(collider,:),
- & CS_HpjZ(collider,:), CS_vbf_Hpj(collider,:),
- & CS_HpjHmj(collider,:), CS_Hpjhi(collider,:,:))
-
- enddo
-
-
-* * * * * * * * * * * * * * * * * * * * *
-c call to run_HiggsBounds
- call run_HiggsBounds( HBresult,chan, obsratio, ncombined )
-
- print*,' '
- print*,'************* HiggsBounds Results **************'
- print*,' '
- print*,'Is this parameter point excluded by LEP, Tevatron'
- print*,'or LHC data?'
- print*, HBresult, ', where'
- print*,' 0 = yes, it is excluded'
- print*,' 1 = no, it has not been excluded'
- print*,' -1 = invalid parameter set'
- print*,' '
- print*,'The process with the highest statistical sensitivity'
- print*,'is'
- print*, chan,'(see Key.dat)'
- print*,'This process has a theoretical rate vs. limit of'
- print*, obsratio
- print*,' '
- print*,'The number of Higgs which have contributed to the'
- print*,'theoretical rate of this process was'
- print*, ncombined
- print*,' '
- print*,'See HiggsBounds documentation for more information.'
- print*,'****************************************************'
- print*,' '
-
-
-* * * * * * * * * * * * * * * * * * * * *
-c deallocates arrays used by HiggsBounds:
-
- call finish_HiggsBounds
-
- end
-
-
-************************************************************************
-
- subroutine setFlags
- implicit none
-
- integer mssmpart, fieldren, tanbren, higgsmix, p2approx
- integer looplevel, loglevel, runningMT, botResum, tlCplxApprox
-
-c Using default (recommended) values of all FH flags
- parameter (mssmpart = 4)
- parameter (fieldren = 0)
- parameter (tanbren = 0)
- parameter (higgsmix = 2)
- parameter (p2approx = 4)
- parameter (looplevel = 2)
- parameter (loglevel = 3)
- parameter (runningMT = 1)
- parameter (botResum = 1)
- parameter (tlCplxApprox = 0)
-
- integer error
-
- call FHSetFlags(error, mssmpart, fieldren, tanbren,
- & higgsmix, p2approx, looplevel, loglevel,
- & runningMT, botResum, tlCplxApprox)
- if( error .ne. 0 ) stop
- end
-
-************************************************************************
-
- subroutine setPara
- implicit none
-
- double precision invAlfa, AlfasMZ, GF
- double precision ME, MU, MD, MM, MC, MS, ML, MB, MZ, MW
- double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
- parameter (invAlfa = -1)
- parameter (AlfasMZ = -1)
- parameter (GF = -1)
- parameter (ME = -1)
- parameter (MU = -1)
- parameter (MD = -1)
- parameter (MM = -1)
- parameter (MC = -1)
- parameter (MS = -1)
- parameter (ML = -1)
- parameter (MB = -1)
- parameter (MW = -1)
- parameter (MZ = -1)
- parameter (CKMlambda = -1)
- parameter (CKMA = -1)
- parameter (CKMrhobar = -1)
- parameter (CKMetabar = -1)
-
- double precision MT, TB, MA0, MHp
- parameter (MT = 173.2)
- parameter (TB = 15.)
- parameter (MA0 = 500)
- parameter (MHp = -1)
-
- double precision MSusy
- double precision M3SL, M2SL, M1SL
- double precision M3SE, M2SE, M1SE
- double precision M3SQ, M2SQ, M1SQ
- double precision M3SU, M2SU, M1SU
- double precision M3SD, M2SD, M1SD
- parameter (MSusy = 1000)
- parameter (M3SL = MSusy)
- parameter (M2SL = M3SL)
- parameter (M1SL = M2SL)
- parameter (M3SE = MSusy)
- parameter (M2SE = M3SE)
- parameter (M1SE = M2SE)
- parameter (M3SQ = MSusy)
- parameter (M2SQ = M3SQ)
- parameter (M1SQ = M2SQ)
- parameter (M3SU = MSusy)
- parameter (M2SU = M3SU)
- parameter (M1SU = M2SU)
- parameter (M3SD = MSusy)
- parameter (M2SD = M3SD)
- parameter (M1SD = M2SD)
-
- double complex Atau, At, Ab
- double complex Amu, Ac, As
- double complex Ae, Au, Ad
- parameter (At = 1550)
- parameter (Ab = At)
- parameter (Atau = At)
- parameter (Ac = At)
- parameter (As = Ab)
- parameter (Amu = Atau)
- parameter (Au = Ac)
- parameter (Ad = As)
- parameter (Ae = Amu)
-
- double complex MUE, M_1, M_2, M_3
- parameter (MUE = 200)
- parameter (M_1 = 0)
- parameter (M_2 = 200)
- parameter (M_3 = 1500)
-
- double precision Qtau, Qt, Qb
- parameter (Qtau = 0)
- parameter (Qt = 0)
- parameter (Qb = 0)
-
- double precision scalefactor
- parameter (scalefactor = 1)
-
- integer error
-
- call FHSetSMPara(error,
- & invAlfa, AlfasMZ, GF,
- & ME, MU, MD, MM, MC, MS, ML, MB,
- & MW, MZ,
- & CKMlambda, CKMA, CKMrhobar, CKMetabar)
- if( error .ne. 0 ) stop
-
- call FHSetPara(error, scalefactor,
- & MT, TB, MA0, MHp,
- & M3SL, M3SE, M3SQ, M3SU, M3SD,
- & M2SL, M2SE, M2SQ, M2SU, M2SD,
- & M1SL, M1SE, M1SQ, M1SU, M1SD,
- & MUE,
- & Atau, At, Ab,
- & Amu, Ac, As,
- & Ae, Au, Ad,
- & M_1, M_2, M_3,
- & Qtau, Qt, Qb)
- if( error .ne. 0 ) stop
- end
-
-************************************************************************
-
- subroutine setSLHA(filename)
- implicit none
- character*(*) filename
-
-#include "SLHA.h"
-
- integer error
- double complex slhadata(nslhadata)
-
- call SLHARead(error, slhadata, filename, 1)
- if( error .ne. 0 ) stop
-
- call FHSetSLHA(error, slhadata)
- if( error .ne. 0 ) stop
- end
-
-
-
Index: trunk/HiggsBounds-5/example_programs/HBwithCPsuperH.f
===================================================================
--- trunk/HiggsBounds-5/example_programs/HBwithCPsuperH.f (revision 532)
+++ trunk/HiggsBounds-5/example_programs/HBwithCPsuperH.f (revision 533)
@@ -1,455 +0,0 @@
- PROGRAM CPsuperH2
-************************************************************************
-* This is modified version of the cpsuperh2.f file which is supplied with
-* CPsuperH2.2
-* (downloaded 07 July 2010
-* from http://www.hep.man.ac.uk/u/jslee/CPsuperH.html)
-* This file is part of the HiggsBounds distribution.
-************************************************************************
- IMPLICIT REAL*8(A-H,M,O-Z)
-*
-*-----------------------------------------------------------------------
-*+CDE HC_ COMMON BLOCKS:
- COMMON /HC_SMPARA/ AEM_H,ASMZ_H,MZ_H,SW_H,ME_H,MMU_H,MTAU_H,MDMT_H
- . ,MSMT_H,MBMT_H,MUMT_H,MCMT_H,MTPOLE_H,GAMW_H
- . ,GAMZ_H,EEM_H,ASMT_H,CW_H,TW_H,MW_H,GW_H,GP_H
- . ,V_H,GF_H,MTMT_H
-*
- COMMON /HC_RSUSYPARA/ TB_H,CB_H,SB_H,MQ3_H,MU3_H,MD3_H,ML3_H,ME3_H
-*
- COMPLEX*16 MU_H,M1_H,M2_H,M3_H,AT_H,AB_H,ATAU_H
- COMMON /HC_CSUSYPARA/ MU_H,M1_H,M2_H,M3_H,AT_H,AB_H,ATAU_H
-*
-*NEW COMMON BLOCKS for V2
-*
- REAL*8 RAUX_H(999)
- COMPLEX*16 CAUX_H(999)
- COMMON /HC_RAUX/ RAUX_H
- COMMON /HC_CAUX/ CAUX_H
- DATA NAUX_H/999/
-*-----------------------------------------------------------------------
-*ARRAYS:
- REAL*8 SMPARA_H(19),SSPARA_H(38)
- DATA NSMIN/19/
- DATA NSSIN/38/
-*
- INTEGER*8 IFLAG_H(100)
- DATA NFLAG/100/
-*
- REAL*8 HMASS_H(3),OMIX_H(3,3)
- REAL*8 STMASS_H(2),SBMASS_H(2),STAUMASS_H(2),SNU3MASS_H
- REAL*8 MC_H(2),MN_H(4)
- COMPLEX*16 STMIX_H(2,2),SBMIX_H(2,2),STAUMIX_H(2,2)
- COMPLEX*16 UL_H(2,2),UR_H(2,2),N_H(4,4)
-*
- COMPLEX*16 NHC_H(100,3) ! 100 = NCMAX
- REAL*8 SHC_H(100)
- COMPLEX*16 CHC_H(100)
- DATA NCMAX/100/
-*
- REAL*8 GAMBRN(101,3,3) ! 101 = IFLAG_H(20)+IFLAG_H(21)+1 = NMNH
-* ISMN =ISUSYN = 50
- REAL*8 GAMBRC(51,3) ! 51 = IFLAG_H(22)+IFLAG_H(23)+1 = NMCH
-* ISMC =ISUSYC = 25
- DATA NMNH/101/
- DATA NMCH/51/
-
-*-----------------------------------------------------------------------
-* * * * * * * * * * * * * * * * * * * * * * * *
-* used by initialize_HiggsBounds and run_HiggsBounds_part
-* HB input:
- integer nHiggsneut,nHiggsplus
- character*5 whichanalyses
-
- double precision Mh(3),GammaTotal_hj(3)
- integer CP_value(3)
- double precision CS_lep_hjZ_ratio(3),
- & CS_lep_bbhj_ratio(3),CS_lep_tautauhj_ratio(3),
- & CS_lep_hjhi_ratio_nHbynH(3,3),
- & CS_gg_hj_ratio(3),CS_bb_hj_ratio(3),
- & CS_bg_hjb_ratio(3),
- & CS_ud_hjWp_ratio(3),CS_cs_hjWp_ratio(3),
- & CS_ud_hjWm_ratio(3),CS_cs_hjWm_ratio(3),
- & CS_gg_hjZ_ratio(3),
- & CS_dd_hjZ_ratio(3),CS_uu_hjZ_ratio(3),
- & CS_ss_hjZ_ratio(3),CS_cc_hjZ_ratio(3),
- & CS_bb_hjZ_ratio(3),
- & CS_tev_vbf_ratio(3),CS_tev_tthj_ratio(3),
- & CS_lhc7_vbf_ratio(3),CS_lhc7_tthj_ratio(3),
- & BR_hjss(3),BR_hjcc(3),
- & BR_hjbb(3),BR_hjmumu(3),BR_hjtautau(3),
- & BR_hjWW(3),BR_hjZZ(3),BR_hjZga(3),
- & BR_hjgaga(3),BR_hjgg(3),
- & BR_hjinvisible(3),BR_hjhihi_nHbynH(3,3)
-
- double precision Mhplus(1),GammaTotal_Hpj(1),
- & CS_lep_HpjHmj_ratio(1),
- & BR_tWpb,BR_tHpjb(1),
- & BR_Hpjcs(1),BR_Hpjcb(1),BR_Hpjtaunu(1)
-
-* HB output:
- integer HBresult,chan,ncombined
- double precision obsratio
-* misc:
- integer i,j,n
- double precision betasq
- double precision
- & g2hjVV(3),g2hjbb(3),
- & g2hjhiZ_nHbynH(3,3),
- & max_hjff_s,max_hjff_p
- integer sneutrino_lspcandidate_number
- logical invisible_lsp
- double precision lspcandidate_mass
-
-c Set the number of Higgs bosons in the MSSM:
- nHiggsneut=3
- nHiggsplus=1
-
-c The string 'whichanalyses' determines which subset of experimental
-c results are used.
-c In this example, we've used the option 'onlyL',
-c which instructs HiggsBounds to use tables of results
-c from LEP only (i.e. no Tevatron or LHC results).
- whichanalyses='onlyL'
-
-c The subroutine initialize_HiggsBounds reads in all necessary
-c tables etc.
-c It must be called before calling the run_HiggsBounds_part subroutine.
-
- call initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses)
-
-c If you would like to perform scans over variables, the subroutine
-c initialize_HiggsBounds (and finish_HiggsBounds) should be called
-c outside the do-loops in order to save time.
-* * * * * * * * * * * * * * * * * * * * * * * *
-*-----------------------------------------------------------------------
-
-*=======================================================================
- CALL FILLINIT2(ISKIP_EDM
- .,NSMIN,NSSIN,SMPARA_H,SSPARA_H,NFLAG,IFLAG_H
- .,NCMAX,NHC_H,SHC_H,CHC_H,NMNH,GAMBRN,NMCH,GAMBRC)
-*=======================================================================
-*
-* To use other values for the input parameters than those in the "run"
-* file, one can specifiy them here. To scan the phase of, for example,
-* the gluino mass parameter M_3, one can do
-*
-* DO IVAR=0,72
-* SSPARA_H(10)=5.D0*DBLE(IVAR) ! Phi_3
-* print*,'Phi_3 = ',SSPARA_H(10)
-*
-* Don't forget commenting in "ENDDO ! IVAR" at the end of this block.
-*
-*-----------------------------------------------------------------------
-* For the \sqrt{s}-dependent propagators and the Higgs couplings to the
-* gluons and photons, the following should be specified. If not, the
-* value in FILLINIT2 is to be used:
-* RAUX_H(101)= ... ! \sqrt{s} for the subroutine FILLDHPG
-*-----------------------------------------------------------------------
-* One may skip the time-consuming EDM calculations by commenting in the
-* follwing line:
-* ISKIP_EDM=1
-*-----------------------------------------------------------------------
-*
- CALL FILLCPsuperH2(ISKIP_EDM
- .,NSMIN,NSSIN,SMPARA_H,SSPARA_H,NFLAG,IFLAG_H
- .,MCH,HMASS_H,OMIX_H
- .,STMASS_H,STMIX_H,SBMASS_H,SBMIX_H,STAUMASS_H,STAUMIX_H,SNU3MASS_H
- .,MC_H,UL_H,UR_H,MN_H,N_H,NCMAX,NHC_H,SHC_H,CHC_H
- .,NMNH,GAMBRN,NMCH,GAMBRC)
-*
-*Error messages:
-*--a stop or sbottom squared mass is negative
- IF(IFLAG_H(50).EQ.1) THEN
- print*,'ERROR! IFLAG_H(50) = ',IFLAG_H(50)
- IFLAG_H(50)=0
- GOTO 99
- ENDIF
-*
-*--the Higgs--boson mass matrix contains a complex or negative eigenvalue
- IF(IFLAG_H(51).EQ.1) THEN
- print*,'ERROR! IFLAG_H(51) = ',IFLAG_H(51)
- IFLAG_H(51)=0
- GOTO 99
- ENDIF
-*
-*--the diagonalization of the Higgs mass matrix is not successful
- IF(IFLAG_H(52).EQ.1) THEN
- print*,'ERROR! IFLAG_H(52) = ',IFLAG_H(52)
- IFLAG_H(52)=0
- GOTO 99
- ENDIF
-*
-*--the iteration resumming the threshold corrections is not convergent
- IF(IFLAG_H(54).EQ.1) THEN
- print*,'ERROR! IFLAG_H(54) = ',IFLAG_H(54)
- IFLAG_H(54)=0
- GOTO 99
- ENDIF
-*
-*--Yukawa coupling has a non--perturbative value: |h_{t,b}| > 2
- IF(IFLAG_H(55).EQ.1) THEN
- print*,'ERROR! IFLAG_H(55) = ',IFLAG_H(55)
- IFLAG_H(55)=0
- GOTO 99
- ENDIF
-*
-*-- 1 = a tau sneutrino or a stau squared mass is negative
-*-- 2 = tachyonic stop or sbottom
-*-- 3 = tachyonic scalar strange
- IF(IFLAG_H(56).GT.0) THEN
- IF(IFLAG_H(56).EQ.1) print*,'ERROR! IFLAG_H(56) = ',IFLAG_H(56)
- IF(IFLAG_H(56).EQ.2) print*,'ERROR! IFLAG_H(56) = ',IFLAG_H(56)
- IF(IFLAG_H(56).EQ.3) print*,'ERROR! IFLAG_H(56) = ',IFLAG_H(56)
- IFLAG_H(56)=0
- GOTO 99
- ENDIF
-*
-*--one of the magnitudes of the complex input parameters is negative
- IF(IFLAG_H(57).EQ.1) THEN
- print*,'ERROR! IFLAG_H(57) = ',IFLAG_H(57)
- IFLAG_H(57)=0
- GOTO 99
- ENDIF
-*
-*--the iterative method for the neutral Higgs-boson pole masses fails
- IF(IFLAG_H(60).EQ.1) THEN
- print*,'ERROR! IFLAG_H(60) = ',IFLAG_H(60)
- IFLAG_H(60)=0
- GOTO 99
- ENDIF
-*
-*-----------------------------------------------------------------------
-* Users may use the following subroutine for further analysis:
-*
-* CALL AURUN(ISKIP_EDM
-* .,NSMIN,NSSIN,SMPARA_H,SSPARA_H,NFLAG,IFLAG_H
-* .,MCH,HMASS_H,OMIX_H
-* .,STMASS_H,STMIX_H,SBMASS_H,SBMIX_H,STAUMASS_H,STAUMIX_H,SNU3MASS_H
-* .,MC_H,UL_H,UR_H,MN_H,N_H,NCMAX,NHC_H,SHC_H,CHC_H
-* .,NMNH,GAMBRN,NMCH,GAMBRC)
-*-----------------------------------------------------------------------
-
-c ------------------------------------------------------------------
-c Set variables needed by HiggsBounds (using results from CPsuperH).
-c See HiggsBounds documentation for definition of variables used
-c as arguments to run_HiggsBounds_part and CPsuperH
-c documentation for all other variables.
-
-c Note: It is slightly more accurate to use the subroutine run_HiggsBounds_part
-c rather than the subroutine run_HiggsBounds_effC because the SM branching ratios
-c used internally in HiggsBounds (from HDecay) are not identical to the SM branching
-c ratios used in CPsuperH
-
- do i=1,3
-
- Mh(i)=HMASS_H(i)
- GammaTotal_hj(i)=GAMBRN(IFLAG_H(20)+IFLAG_H(21)+1,1,i)
-
- BR_hjss(i) = GAMBRN(5,3,i)
- BR_hjcc(i) = GAMBRN(8,3,i)
- BR_hjbb(i) = GAMBRN(6,3,i)
- BR_hjmumu(i) = GAMBRN(2,3,i)
- BR_hjtautau(i) = GAMBRN(3,3,i)
- BR_hjWW(i) = GAMBRN(10,3,i)
- BR_hjZZ(i) = GAMBRN(11,3,i)
- BR_hjgaga(i) = GAMBRN(17,3,i)
- BR_hjgg(i) = GAMBRN(18,3,i)
-
- sneutrino_lspcandidate_number=0
- invisible_lsp=.True.
- lspcandidate_mass=MN_H(1)
-
- if( SNU3MASS_H .lt. lspcandidate_mass )then
- lspcandidate_mass=SNU3MASS_H
- sneutrino_lspcandidate_number=3
- endif
-
- if( MC_H(1) .lt. lspcandidate_mass )then !chargino
- invisible_lsp=.False.
- elseif( SSPara_H(9) .lt. lspcandidate_mass )then !gluino
- invisible_lsp=.False.
- elseif( STMASS_H(1) .lt. lspcandidate_mass )then !stop
- invisible_lsp=.False.
- elseif( SBMASS_H(1) .lt. lspcandidate_mass )then !sbottom
- invisible_lsp=.False.
- elseif( STAUMASS_H(1) .lt. lspcandidate_mass )then !stau
- invisible_lsp=.False.
- endif
-
- if(invisible_lsp)then
- if( sneutrino_lspcandidate_number.eq.0)then
- BR_hjinvisible(i)=GAMBRN(IFLAG_H(20)+1,3,i)
- elseif(sneutrino_lspcandidate_number.eq.3)then
- BR_hjinvisible(i)=GAMBRN(IFLAG_H(20)+27,3,i)
- endif
- else
- BR_hjinvisible(i)=0.0D0
- endif
-
-
-!this branching ratio is not calculated by CPsuperH, so we set it to zero
- BR_hjZga(i) = 0.0D0
-
- g2hjbb(i)=
- & abs(NHC_H(17,i))**2.0D0
- & + abs(NHC_H(18,i))**2.0D0
-
- CS_bg_hjb_ratio(i) = g2hjbb(i)
- CS_bb_hj_ratio(i) = g2hjbb(i)
- CS_lep_bbhj_ratio(i) = g2hjbb(i)
- CS_lep_tautauhj_ratio(i) =
- & abs(NHC_H(8,i))**2.0D0
- & + abs(NHC_H(9,i))**2.0D0
-
- g2hjVV(i)= abs(NHC_H(70,i))**2.0D0
-
- CS_lep_hjZ_ratio(i) = g2hjVV(i)
- CS_dd_hjZ_ratio(i) = g2hjVV(i)
- CS_uu_hjZ_ratio(i) = g2hjVV(i)
- CS_ss_hjZ_ratio(i) = g2hjVV(i)
- CS_cc_hjZ_ratio(i) = g2hjVV(i)
- CS_bb_hjZ_ratio(i) = g2hjVV(i)
- CS_ud_hjWp_ratio(i) = g2hjVV(i)
- CS_cs_hjWp_ratio(i) = g2hjVV(i)
- CS_ud_hjWm_ratio(i) = g2hjVV(i)
- CS_cs_hjWm_ratio(i) = g2hjVV(i)
- CS_tev_vbf_ratio(i) = g2hjVV(i)
- CS_lhc7_vbf_ratio(i) = g2hjVV(i)
-
- CS_gg_hjZ_ratio(i) = 0.0D0
-
- CS_tev_tthj_ratio(i) =
- & abs(NHC_H(26,i))**2.0D0
- & + abs(NHC_H(27,i))**2.0D0
- CS_lhc7_tthj_ratio(i) = CS_tev_tthj_ratio(i)
-c ------------------------------------------------------------------
-!note that this is an approximation
- CS_gg_hj_ratio(i) = GAMBRN(18,1,i)
- & /( SMBR_Hgg(Mh(i)) *SMGamma_h(Mh(i)) )
- if(SMGamma_h(Mh(i)).lt.0)then
- CS_gg_hj_ratio(i) = 0.0D0
- !it's ok to set this to zero, because Mh(i) is out of range anyway
- endif
-c ------------------------------------------------------------------
-
- BR_hjhihi_nHbynH(i,1)=GAMBRN(14,3,i)
- BR_hjhihi_nHbynH(i,2)=GAMBRN(16,3,i)
- BR_hjhihi_nHbynH(i,3)=0.0D0
-
- max_hjff_s=max(abs(NHC_H(14,i))**2.0D0,
- & abs(NHC_H(23,i))**2.0D0,
- & abs(NHC_H(17,i))**2.0D0,
- & abs(NHC_H(26,i))**2.0D0,
- & abs(NHC_H( 8,i))**2.0D0 )
-
- max_hjff_p=max(abs(NHC_H(15,i))**2.0D0,
- & abs(NHC_H(24,i))**2.0D0,
- & abs(NHC_H(18,i))**2.0D0,
- & abs(NHC_H(27,i))**2.0D0,
- & abs(NHC_H( 9,i))**2.0D0 )
-
- if( max_hjff_p .lt. 1.0D-16 )then !CP even
- CP_value(i) = 1
- elseif( max_hjff_s .lt. 1.0D-16 )then !CP odd
- CP_value(i) = -1
- else !mixed CP
- CP_value(i) = 0
- endif
-
- enddo
-
- do j=1,3
- do i=1,3
- if(i.lt.j)then
- g2hjhiZ_nHbynH(j,i)=g2hjVV(6-j-i)
- g2hjhiZ_nHbynH(i,j)=g2hjhiZ_nHbynH(j,i)
- else
- g2hjhiZ_nHbynH(j,i)=0.0D0
- endif
- enddo
- enddo
-
- do j=1,3
- do i=1,3
- CS_lep_hjhi_ratio_nHbynH(j,i) = g2hjhiZ_nHbynH(j,i)
- enddo
- enddo
-
- Mhplus(1)=SSPARA_H(2)
- GammaTotal_Hpj(1)=GAMBRC(IFLAG_H(22)+IFLAG_H(23)+1,1)
- CS_lep_HpjHmj_ratio(1)=1.0D0
- BR_Hpjcs(1) = GAMBRC(5,3)
- BR_Hpjtaunu(1) = GAMBRC(3,3)
-! this branching ratios is not calculated by CPsuperH, so set to zero:
- BR_Hpjcb(1) = 0.0D0
-! t-quark branching ratios are not calculated by CPsuperH, so set to zero:
- BR_tWpb = 0.0D0
- BR_tHpjb(1) = 0.0D0
-
-* * * * * * * * * * * * * * * * * * * * *
- call HiggsBounds_neutral_input_part(Mh,GammaTotal_hj,CP_value,
- & CS_lep_hjZ_ratio,
- & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio,
- & CS_lep_hjhi_ratio_nHbynH,
- & CS_gg_hj_ratio,CS_bb_hj_ratio,
- & CS_bg_hjb_ratio,
- & CS_ud_hjWp_ratio,CS_cs_hjWp_ratio,
- & CS_ud_hjWm_ratio,CS_cs_hjWm_ratio,
- & CS_gg_hjZ_ratio,
- & CS_dd_hjZ_ratio,CS_uu_hjZ_ratio,
- & CS_ss_hjZ_ratio,CS_cc_hjZ_ratio,
- & CS_bb_hjZ_ratio,
- & CS_tev_vbf_ratio,CS_tev_tthj_ratio,
- & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio,
- & BR_hjss,BR_hjcc,
- & BR_hjbb,BR_hjmumu,BR_hjtautau,
- & BR_hjWW,BR_hjZZ,BR_hjZga, BR_hjgaga,BR_hjgg,
- & BR_hjinvisible,BR_hjhihi_nHbynH )
-
- call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj,
- & CS_lep_HpjHmj_ratio,
- & BR_tWpb,BR_tHpjb,
- & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu)
-
- call run_HiggsBounds( HBresult,chan,
- & obsratio, ncombined )
-
-
- write(*,*)
- write(*,*)'************* HiggsBounds Results **************'
- write(*,*)
- write(*,*)'Is this parameter point excluded at 95% CL?'
- write(*,*) HBresult, ', where'
- write(*,*)' 0 = yes, it is excluded'
- write(*,*)' 1 = no, it has not been excluded'
- write(*,*)' -1 = invalid parameter set'
- write(*,*)
- write(*,*)'The process with the highest statistical sensitivity'
- write(*,*)'is'
- write(*,*) chan,'(see Key.dat)'
- write(*,*)'This process has a theoretical rate vs. limit of'
- write(*,*) obsratio
- write(*,*)
- write(*,*)'The number of Higgs bosons which have contributed to'
- write(*,*)'the theoretical rate of this process was'
- write(*,*) ncombined
- write(*,*)
- write(*,*)'See HiggsBounds documentation for more information.'
- write(*,*)'****************************************************'
- write(*,*)
-
- 99 CONTINUE
-*
-* ENDDO ! IVAR
-*=======================================================================
-
-c ------------------------------------------------------------------
-* * * * * * * * * * * * * * * * * * * * *
-c deallocates arrays used by HiggsBounds:
-
- call finish_HiggsBounds
-c ------------------------------------------------------------------
-
- STOP
- END
Index: trunk/HiggsBounds-5/example_programs/HB5_effC.F90
===================================================================
--- trunk/HiggsBounds-5/example_programs/HB5_effC.F90 (revision 532)
+++ trunk/HiggsBounds-5/example_programs/HB5_effC.F90 (revision 533)
@@ -1,214 +0,0 @@
-!--------------------------------------------------------------------------------------
-! This example program is part of HiggsBounds-5 (TS 22/11/2016).
-!--------------------------------------------------------------------------------------
-program HB5_effC
-! Testing the effective coupling approximation
-!--------------------------------------------------------------------------------------
- use usefulbits, only : analysislist
- implicit none
-
- integer :: nHzero, nHplus
- integer :: HBresult,chan,ncombined,chan2
- integer :: HBresult_tmp,chan_tmp,ncombined_tmp
- integer,parameter :: fileid=78, fileid2=80
- double precision :: obsratio,obsratio_tmp,predratio_tmp
- double precision :: SMGamma_h,GammaTotal(3)
- double precision :: Mh(3),ghjss_s(3),ghjss_p(3),ghjcc_s(3),ghjcc_p(3), &
-& ghjbb_s(3),ghjbb_p(3),ghjtt_s(3),ghjtt_p(3), &
-& ghjmumu_s(3),ghjmumu_p(3),ghjtautau_s(3),ghjtautau_p(3), &
-& ghjWW(3),ghjZZ(3),ghjZga(3),ghjgaga(3),ghjgg(3), &
-& ghjhiZ(3),BR_hkhjhi(3,3,3),BR_hjhiZ(3,3),BR_hjinvisible(3), &
-& BR_hjemu(3),BR_hjetau(3),BR_hjmutau(3)
- double precision :: Mhplus,GammaTotal_Hpj, &
- & CS_lep_HpjHmj_ratio, &
- & BR_tWpb,BR_tHpjb, &
- & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu, &
- & BR_Hpjtb,BR_HpjWZ,BR_HpjhiW(1,3)
- double precision :: dMhneut(3), dMhch(1)
- double precision :: CS_Hpjtb, CS_Hpjbjet,CS_HpjW,CS_HpjZ,CS_vbf_Hpj,CS_HpjHmj,&
- & CS_Hpjhi(1,3)
- double precision :: nonSMBR(3),sumiBR_hkhihj(3),sumiBR_hihjZ(3)
- character(len=100)::filename
- integer :: i,j,k
-
-! Allocate list of analyses ID numbers to include
-! and initialize with bogus (-1) numbers
-! allocate(analysislist(15))
-! do i=1,ubound(analysislist,1)
-! analysislist(i) = -1
-! enddo
-
-! analysislist(5) = 14011
-! analysislist(2) = 160312
-! analysislist(3) = 20160851
-! analysislist(4) = 20160852
-! analysislist(5) = 20160151
-! analysislist(6) = 20160152
-! analysislist(7) = 16002
-! analysislist(8) = 16029
-! analysislist(9) = 14013
-! analysislist(10) = 2016071
-! analysislist(11) = 20160741
-! analysislist(12) = 20160742
-! analysislist(13) = 2016062
-! analysislist(14) = 2016049
-! analysislist(3) = 044781
-! analysislist(4) = 044782
-! analysislist(1) = 011811
-! analysislist(2) = 011812
-! analysislist(15) = 6065
-! analysislist(3) = 2016059
-! analysislist(4) = 14022
-
- nHzero=3
- nHplus=1
-! theory_uncertainty_1s=1.5D0
-
-! call initialize_HiggsBounds(nHzero, nHplus, "list ")
- call initialize_HiggsBounds(nHzero, nHplus, "LandH")
-
-! do i=1,101
- Mh = (/ 125.0D0, 250.0D0, 340.0D0 /)
-
- dMhneut = (/ 2.0D0, 0.0D0, 0.0D0 /)
- dMhch = (/ 0.0D0 /)
-
-! non SM decays
- BR_hkhjhi = 0.0D0
- BR_hkhjhi(3,1,2) = 0.01D0
- BR_hkhjhi(3,2,1) = 0.00D0
- BR_hkhjhi(3,1,1) = 0.1D0
- BR_hjhiZ = 0.0D0
- BR_hjhiZ(3,2) = 0.1D0
- BR_hjhiZ(3,1) = 0.1D0
- BR_hjhiZ(2,1) = 0.4D0
- BR_hjemu = 0.0D0
- BR_hjetau = 0.0D0
- BR_hjmutau = 0.0D0
-! BR_hjmutau(1) = 0.01D0
- BR_hjinvisible=0d0
-
- do i=1,3
- sumiBR_hkhihj(i) = 0.0D0
- sumiBR_hihjZ(i) = 0.0D0
- do j=1,3
- do k=1,j
- sumiBR_hkhihj(i) = sumiBR_hkhihj(i) + BR_hkhjhi(i,j,k)
- enddo
- sumiBR_hihjZ(i) = sumiBR_hihjZ(i) + BR_hjhiZ(i,j)
- enddo
-
- nonSMBR(i) = BR_hjemu(i)+BR_hjetau(i)+BR_hjmutau(i)+ &
-& BR_hjinvisible(i)+sumiBR_hihjZ(i)+sumiBR_hkhihj(i)
- enddo
- ! For debugging:
-! BR_hkhjhi(3,2,1) = 0.0D0
- !
- do i=1,3
- GammaTotal(i)=SMGamma_h(Mh(i))/(1-nonSMBR(i))
-
- ghjss_s(i)=1.0d0
- ghjss_p(i)=0.0d0
- ghjcc_s(i)=1.0d0
- ghjcc_p(i)=0.0d0
- ghjbb_s(i)=1.0d0
- ghjbb_p(i)=0.0d0
- ghjtt_s(i)=1.0d0
- ghjtt_p(i)=0.0d0
- ghjmumu_s(i)=1.0d0
- ghjmumu_p(i)=0.0d0
- ghjtautau_s(i)=1.0d0
- ghjtautau_p(i)=0.0d0
- ghjWW(i)=1.0d0
- ghjZZ(i)=1.0d0
- ghjZga(i)=1d0
- ghjgaga(i)=1.0d0
- ghjgg(i)=1.0d0
- ghjhiZ(i)=0d0
- enddo
-
-! Charged Higgs input (random values)
- Mhplus = 55.0D0
- GammaTotal_Hpj = 1.0D0 ! Is this ever being used?
- CS_lep_HpjHmj_ratio = 1.0D0
- BR_tWpb=1.0D0
- BR_tHpjb=0.0D0
- BR_Hpjcs=0.2D0
- BR_Hpjcb=0.3D0
- BR_Hpjtaunu=0.5D0
- BR_Hpjtb=0.00D0
- BR_HpjWZ=0.00D0
- BR_HpjhiW(1,1)=0.0D0
- BR_HpjhiW(1,2)=0.0D0
- BR_HpjhiW(1,3)=0.0D0
-! CS are in pb
- CS_Hpjtb= 1.0D-02
- CS_Hpjbjet= 0.01D0
- CS_HpjW= 0.01D0
- CS_HpjZ= 0.01D0
- CS_vbf_Hpj= 0.01D0
- CS_HpjHmj= 0.01D0
- CS_Hpjhi(1,1) = 0.01D0
- CS_Hpjhi(1,2) = 0.005D0
- CS_Hpjhi(1,3) = 0.001D0
-
- call HB5_neutral_input_properties(Mh,GammaTotal)
-
- call HiggsBounds_set_mass_uncertainties(dMhneut, dMhch)
-
- call HB5_neutral_input_effC( &
- & ghjss_s,ghjss_p,ghjcc_s,ghjcc_p, &
- & ghjbb_s,ghjbb_p,ghjtt_s,ghjtt_p, &
- & ghjmumu_s,ghjmumu_p, &
- & ghjtautau_s,ghjtautau_p, &
- & ghjWW,ghjZZ,ghjZga, &
- & ghjgaga,ghjgg,ghjhiZ)
-
- call HB5_neutral_input_nonSMBR(BR_hjinvisible,BR_hkhjhi,BR_hjhiZ,&
- & BR_hjemu,BR_hjetau,BR_hjmutau)
-
- call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj, &
- & CS_lep_HpjHmj_ratio, &
- & BR_tWpb,BR_tHpjb, &
- & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu,BR_Hpjtb, &
- & BR_HpjWZ,BR_HpjhiW)
-
- call HB5_charged_input_hadr(13, CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
- & CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
-
-
- call run_HiggsBounds( HBresult, chan, obsratio, ncombined )
- write(*,*) '**********************************************************************'
- write(*,*) 'HiggsBounds main results'
- write(*,*) '**********************************************************************'
- write(*,'(A,1I5,A)') ' HBresult = ', HBresult, ' (0: excluded, 1: allowed)'
- write(*,'(A,1I5)') ' channel ID = ', chan
- write(*,'(A,1F8.3)') ' obsratio = ', obsratio
- write(*,'(A,1I5)') ' ncombined = ', ncombined
- write(*,*) '**********************************************************************'
- write(*,*) 'Ranking of most sensitive channels for each Higgs boson'
- write(*,*) '**********************************************************************'
- write(*,*) ' Higgs-no rank HBresult channel obsratio predratio ncombined'
- do i=1,4
- do j=1,3
- call HiggsBounds_get_most_sensitive_channels_per_Higgs(i,j,HBresult_tmp,chan_tmp,&
-& obsratio_tmp,predratio_tmp,ncombined_tmp)
- write(*,'(4I10,2F10.3,1I10)') i,j, HBresult_tmp, chan_tmp, obsratio_tmp,&
-& predratio_tmp, ncombined_tmp
- enddo
- enddo
- write(*,*) '**********************************************************************'
- write(*,*) 'Ranking of most sensitive channels (overall)'
- write(*,*) '**********************************************************************'
- write(*,*) ' rank HBresult channel obsratio predratio ncombined'
- do j=1,3
- call HiggsBounds_get_most_sensitive_channels(j,HBresult_tmp,chan_tmp,obsratio_tmp,&
-& predratio_tmp,ncombined_tmp)
- write(*,'(3I10,2F10.3,1I10)') j, HBresult_tmp, chan_tmp, obsratio_tmp,&
-& predratio_tmp, ncombined_tmp
- enddo
- write(*,*) '**********************************************************************'
-
- call finish_HiggsBounds
-
-end program HB5_effC
\ No newline at end of file
Index: trunk/HiggsBounds-5/example_programs/HBwithCPsuperH.input
===================================================================
--- trunk/HiggsBounds-5/example_programs/HBwithCPsuperH.input (revision 532)
+++ trunk/HiggsBounds-5/example_programs/HBwithCPsuperH.input (revision 533)
@@ -1,72 +0,0 @@
-128.D0 ! SMPARA( 1) = 1/AEM(MZ)
-0.1185D0 ! SMPARA( 2) = AS(MZ)
-91.187D0 ! SMPARA( 3) = MZ in GeV
-0.23117D0 ! SMPARA( 4) = sin^2\Theta_W
-0.5D-3 ! SMPARA( 5) = m_e in GeV
-0.1065D0 ! SMPARA( 6) = m_mu in GeV
-1.777D0 ! SMPARA( 7) = m_tau in GeV
-0.004D0 ! SMPARA( 8) = m_d (m_t) in GeV
-0.090D0 ! SMPARA( 9) = m_s (m_t) in GeV
-3.155D0 ! SMPARA(10) = m_b (m_t) in GeV
-0.002D0 ! SMPARA(11) = m_u (m_t) in GeV
-0.735D0 ! SMPARA(12) = m_c (m_t) in GeV
-174.3D0 ! SMPARA(13) = m_t^POLE in GeV
-2.118D0 ! SMPARA(14) = Gam_W in GeV
-2.4952D0 ! SMPARA(15) = Gam_Z in GeV
-0.2272D0 ! SMPARA(16) = lambda_CKM
-0.8180D0 ! SMPARA(17) = A_CKM
-0.2210D0 ! SMPARA(18) = rho^bar_CKM
-0.3400D0 ! SMPARA(19) = eta^bar_CKM
-5.0D0 ! SSPARA( 1) = tan\beta
-3.0D2 ! SSPARA( 2) = m_H^\pm^POLE in GeV
-2.0D3 ! SSPARA( 3) = |mu| in GeV
-0.0D2 ! SSPARA( 4) = Phi_mu in Degree
-0.5D2 ! SSPARA( 5) = |M_1| in GeV
-0.0D2 ! SSPARA( 6) = Phi_1 in Degree
-1.0D2 ! SSPARA( 7) = |M_2| in GeV
-0.0D2 ! SSPARA( 8) = Phi_2 in Degree
-1.0D3 ! SSPARA( 9) = |M_3| in GeV
-0.9D2 ! SSPARA(10) = Phi_3 in Degree
-0.5D3 ! SSPARA(11) = m_Q3 in GeV
-0.5D3 ! SSPARA(12) = m_U3 in GeV
-0.5D3 ! SSPARA(13) = m_D3 in GeV
-0.5D3 ! SSPARA(14) = m_L3 in GeV
-0.5D3 ! SSPARA(15) = m_E3 in GeV
-1.0D3 ! SSPARA(16) = |A_t| in GeV
-0.9D2 ! SSPARA(17) = Phi_{A_t} in Degree
-1.0D3 ! SSPARA(18) = |A_b| in GeV
-0.9D2 ! SSPARA(19) = Phi_{A_b} in Degree
-1.0D3 ! SSPARA(20) = |A_tau| in GeV
-0.9D2 ! SSPARA(21) = Phi_{A_tau} in Degree
-1.00D0 ! SSPARA(22) = Hierarchy factor between first 2 and third generations M_Q
-1.00D0 ! SSPARA(23) = Hierarchy factor between first 2 and third generations M_U
-1.00D0 ! SSPARA(24) = Hierarchy factor between first 2 and third generations M_D
-1.00D0 ! SSPARA(25) = Hierarchy factor between first 2 and third generations M_L
-1.00D0 ! SSPARA(26) = Hierarchy factor between first 2 and third generations M_E
-1.0D3 ! SSPARA(27) = |A_e| in GeV
-0.9D2 ! SSPARA(28) = Phi_{A_e} in Degree
-1.0D3 ! SSPARA(29) = |A_mu| in GeV
-0.9D2 ! SSPARA(30) = Phi_{A_mu} in Degree
-1.0D3 ! SSPARA(31) = |A_u| in GeV
-0.9D2 ! SSPARA(32) = Phi_{A_u} in Degree
-1.0D3 ! SSPARA(33) = |A_c| in GeV
-0.9D2 ! SSPARA(34) = Phi_{A_c} in Degree
-1.0D3 ! SSPARA(35) = |A_d| in GeV
-0.9D2 ! SSPARA(36) = Phi_{A_d} in Degree
-1.0D3 ! SSPARA(37) = |A_s| in GeV
-0.9D2 ! SSPARA(38) = Phi_{A_s} in Degree
-0 ! IFLAG_H(1) if 1, print input parameters
-1 ! IFLAG_H(2) if 1, print Higgs sector
-0 ! IFLAG_H(3) if 1, print sferimon sector
-0 ! IFLAG_H(4) if 1, print -ino sector
-0 ! IFLAG_H(5) if 6, print all couplings
-5 ! IFLAG_H(6) if 5, print neutral higgs decay widths and brs
-0 ! IFLAG_H(10) if 0, Include rad. corrections to t and b Yukawa couplings
-0 ! IFLAG_H(11) Pole mass(0) or Eff. Pot. mass(1)
-5 ! IFLAG_H(12) 5 or 0 for full improvement
-0 ! IFLAG_H(13) 1 Not to include the off-diagonal absorptive parts
-0 ! IFLAG_H(14) 1 to print FILLDHPG results
-0 ! IFLAG_H(16) 1 to print FILLBOBS results
-0 ! IFLAG_H(17) 1 to print b -> s gamma details
-0 ! IFLAG_H(18) 1 to print EDM results
-0 ! IFLAG_H(19) 1 to print fllmuon results
Index: trunk/HiggsBounds-5/example_programs/HBeffC.F90
===================================================================
--- trunk/HiggsBounds-5/example_programs/HBeffC.F90 (revision 0)
+++ trunk/HiggsBounds-5/example_programs/HBeffC.F90 (revision 533)
@@ -0,0 +1,222 @@
+!--------------------------------------------------------------------------------------
+! This example program is part of HiggsBounds-5 (TS 22/11/2016).
+!--------------------------------------------------------------------------------------
+program HBeffC
+! Testing the effective coupling approximation
+!--------------------------------------------------------------------------------------
+ use usefulbits, only : analysislist
+ implicit none
+
+ integer :: nHzero, nHplus
+ integer :: HBresult,chan,ncombined,chan2
+ integer :: HBresult_tmp,chan_tmp,ncombined_tmp
+ integer,parameter :: fileid=78, fileid2=80
+ double precision :: obsratio,obsratio_tmp,predratio_tmp
+ double precision :: SMGamma_h,GammaTotal(3)
+ double precision :: Mh(3),ghjss_s(3),ghjss_p(3),ghjcc_s(3),ghjcc_p(3), &
+& ghjbb_s(3),ghjbb_p(3),ghjtt_s(3),ghjtt_p(3), &
+& ghjmumu_s(3),ghjmumu_p(3),ghjtautau_s(3),ghjtautau_p(3), &
+& ghjWW(3),ghjZZ(3),ghjZga(3),ghjgaga(3),ghjgg(3), &
+& ghjhiZ(3),BR_hkhjhi(3,3,3),BR_hjhiZ(3,3),BR_hjinvisible(3), &
+& BR_hjemu(3),BR_hjetau(3),BR_hjmutau(3)
+ double precision :: Mhplus,GammaTotal_Hpj, &
+ & CS_lep_HpjHmj_ratio, &
+ & BR_tWpb,BR_tHpjb, &
+ & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu, &
+ & BR_Hpjtb,BR_HpjWZ,BR_HpjhiW(1,3), &
+ & BR_hjHpiW(3,1)
+ double precision :: dMhneut(3), dMhch(1)
+ double precision :: CS_Hpjtb,CS_Hpjcb,CS_Hpjbjet,CS_Hpjcjet,&
+ & CS_Hpjjetjet,CS_HpjW,CS_HpjZ,CS_vbf_Hpj,CS_HpjHmj,CS_Hpjhi(1,3)
+ double precision :: nonSMBR(3),sumiBR_hkhihj(3),sumiBR_hihjZ(3)
+ character(len=100)::filename
+ integer :: i,j,k
+
+! Allocate list of analyses ID numbers to include
+! and initialize with bogus (-1) numbers
+! allocate(analysislist(15))
+! do i=1,ubound(analysislist,1)
+! analysislist(i) = -1
+! enddo
+
+! analysislist(5) = 14011
+! analysislist(2) = 160312
+! analysislist(3) = 20160851
+! analysislist(4) = 20160852
+! analysislist(5) = 20160151
+! analysislist(6) = 20160152
+! analysislist(7) = 16002
+! analysislist(8) = 16029
+! analysislist(9) = 14013
+! analysislist(10) = 2016071
+! analysislist(11) = 20160741
+! analysislist(12) = 20160742
+! analysislist(13) = 2016062
+! analysislist(14) = 2016049
+! analysislist(3) = 044781
+! analysislist(4) = 044782
+! analysislist(1) = 011811
+! analysislist(2) = 011812
+! analysislist(15) = 6065
+! analysislist(3) = 2016059
+! analysislist(4) = 14022
+
+ nHzero=3
+ nHplus=1
+! theory_uncertainty_1s=1.5D0
+
+! call initialize_HiggsBounds(nHzero, nHplus, "list ")
+ call initialize_HiggsBounds(nHzero, nHplus, "LandH")
+
+! set the neutral Higgs masses and uncertainties
+ Mh = (/ 125.0D0, 250.0D0, 340.0D0 /)
+ dMhneut = (/ 2.0D0, 0.0D0, 0.0D0 /)
+
+! set some example non-SM neutral Higgs decays
+ BR_hkhjhi = 0.0D0
+ BR_hkhjhi(3,1,2) = 0.01D0
+ BR_hkhjhi(3,2,1) = 0.00D0
+ BR_hkhjhi(3,1,1) = 0.1D0
+ BR_hjhiZ = 0.0D0
+ BR_hjhiZ(3,2) = 0.1D0
+ BR_hjhiZ(3,1) = 0.1D0
+ BR_hjhiZ(2,1) = 0.4D0
+ BR_hjHpiW(1,1) = 0.0D0
+ BR_hjHpiW(2,1) = 0.1D0
+ BR_hjHpiW(3,1) = 0.0D0
+ BR_hjemu = 0.0D0
+ BR_hjetau = 0.0D0
+ BR_hjmutau = 0.0D0
+ BR_hjinvisible=0d0
+
+ do i=1,3
+ sumiBR_hkhihj(i) = 0.0D0
+ sumiBR_hihjZ(i) = 0.0D0
+ do j=1,3
+ do k=1,j
+ sumiBR_hkhihj(i) = sumiBR_hkhihj(i) + BR_hkhjhi(i,j,k)
+ enddo
+ sumiBR_hihjZ(i) = sumiBR_hihjZ(i) + BR_hjhiZ(i,j)
+ enddo
+
+ nonSMBR(i) = BR_hjemu(i)+BR_hjetau(i)+BR_hjmutau(i)+ &
+& BR_hjinvisible(i)+sumiBR_hihjZ(i)+sumiBR_hkhihj(i)+ &
+& BR_hjHpiW(i,1)
+ enddo
+
+!- Set some example values for the neutral Higgs effective couplings. Here,
+! as a toy example, set all Higgs couplings to the SM Higgs couplings.
+ do i=1,3
+ GammaTotal(i)=SMGamma_h(Mh(i))/(1-nonSMBR(i))
+
+ ghjss_s(i)=1.0d0
+ ghjss_p(i)=0.0d0
+ ghjcc_s(i)=1.0d0
+ ghjcc_p(i)=0.0d0
+ ghjbb_s(i)=1.0d0
+ ghjbb_p(i)=0.0d0
+ ghjtt_s(i)=1.0d0
+ ghjtt_p(i)=0.0d0
+ ghjmumu_s(i)=1.0d0
+ ghjmumu_p(i)=0.0d0
+ ghjtautau_s(i)=1.0d0
+ ghjtautau_p(i)=0.0d0
+ ghjWW(i)=1.0d0
+ ghjZZ(i)=1.0d0
+ ghjZga(i)=1d0
+ ghjgaga(i)=1.0d0
+ ghjgg(i)=1.0d0
+ ghjhiZ(i)=0d0
+ enddo
+
+! Charged Higgs input (example values)
+ Mhplus = 55.0D0
+ dMhch = (/ 0.0D0 /)
+ GammaTotal_Hpj = 1.0D0 ! This is not needed at the moment
+ CS_lep_HpjHmj_ratio = 1.0D0
+ BR_tWpb=1.0D0
+ BR_tHpjb=0.0D0
+ BR_Hpjcs=0.2D0
+ BR_Hpjcb=0.3D0
+ BR_Hpjtaunu=0.5D0
+ BR_Hpjtb=0.00D0
+ BR_HpjWZ=0.00D0
+ BR_HpjhiW(1,1)=0.0D0
+ BR_HpjhiW(1,2)=0.0D0
+ BR_HpjhiW(1,3)=0.0D0
+! Cross sections (CS) are in pb
+ CS_Hpjtb= 1.0D-02
+! For the following quantities there are currently no experimental searches:
+ CS_Hpjcb= 0.5D-02
+ CS_Hpjbjet= 1.0D-02
+ CS_Hpjcjet= 1.0D-02
+ CS_Hpjjetjet= 1.0D-03
+ CS_HpjW= 0.01D0
+ CS_HpjZ= 0.01D0
+ CS_vbf_Hpj= 0.01D0
+ CS_HpjHmj= 0.01D0
+ CS_Hpjhi(1,1) = 0.01D0
+ CS_Hpjhi(1,2) = 0.005D0
+ CS_Hpjhi(1,3) = 0.001D0
+
+ call HiggsBounds_neutral_input_properties(Mh,GammaTotal)
+
+ call HiggsBounds_set_mass_uncertainties(dMhneut, dMhch)
+
+ call HiggsBounds_neutral_input_effC( &
+ & ghjss_s,ghjss_p,ghjcc_s,ghjcc_p, &
+ & ghjbb_s,ghjbb_p,ghjtt_s,ghjtt_p, &
+ & ghjmumu_s,ghjmumu_p, &
+ & ghjtautau_s,ghjtautau_p, &
+ & ghjWW,ghjZZ,ghjZga, &
+ & ghjgaga,ghjgg,ghjhiZ)
+
+ call HiggsBounds_neutral_input_nonSMBR(BR_hjinvisible,BR_hkhjhi,BR_hjhiZ,&
+ & BR_hjemu,BR_hjetau,BR_hjmutau,BR_hjHpiW)
+
+ call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj, &
+ & CS_lep_HpjHmj_ratio, &
+ & BR_tWpb,BR_tHpjb, &
+ & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu,BR_Hpjtb, &
+ & BR_HpjWZ,BR_HpjhiW)
+
+ call HiggsBounds_charged_input_hadr(13, CS_Hpjtb, CS_Hpjcb, CS_Hpjbjet,&
+ & CS_Hpjcjet, CS_Hpjjetjet, CS_HpjW, CS_HpjZ,&
+ & CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
+
+
+ call run_HiggsBounds( HBresult, chan, obsratio, ncombined )
+ write(*,*) '**********************************************************************'
+ write(*,*) 'HiggsBounds main results'
+ write(*,*) '**********************************************************************'
+ write(*,'(A,1I5,A)') ' HBresult = ', HBresult, ' (0: excluded, 1: allowed)'
+ write(*,'(A,1I5)') ' channel ID = ', chan
+ write(*,'(A,1F8.3)') ' obsratio = ', obsratio
+ write(*,'(A,1I5)') ' ncombined = ', ncombined
+ write(*,*) '**********************************************************************'
+ write(*,*) 'Ranking of most sensitive channels for each Higgs boson'
+ write(*,*) '**********************************************************************'
+ write(*,*) ' Higgs-no rank HBresult channel obsratio predratio ncombined'
+ do i=1,4
+ do j=1,3
+ call HiggsBounds_get_most_sensitive_channels_per_Higgs(i,j,HBresult_tmp,chan_tmp,&
+& obsratio_tmp,predratio_tmp,ncombined_tmp)
+ write(*,'(4I10,2F10.3,1I10)') i,j, HBresult_tmp, chan_tmp, obsratio_tmp,&
+& predratio_tmp, ncombined_tmp
+ enddo
+ enddo
+ write(*,*) '**********************************************************************'
+ write(*,*) 'Ranking of most sensitive channels (overall)'
+ write(*,*) '**********************************************************************'
+ write(*,*) ' rank HBresult channel obsratio predratio ncombined'
+ do j=1,3
+ call HiggsBounds_get_most_sensitive_channels(j,HBresult_tmp,chan_tmp,obsratio_tmp,&
+& predratio_tmp,ncombined_tmp)
+ write(*,'(3I10,2F10.3,1I10)') j, HBresult_tmp, chan_tmp, obsratio_tmp,&
+& predratio_tmp, ncombined_tmp
+ enddo
+ write(*,*) '**********************************************************************'
+
+ call finish_HiggsBounds
+
+end program HBeffC
\ No newline at end of file
Index: trunk/HiggsBounds-5/example_programs/HBwithFH.F
===================================================================
--- trunk/HiggsBounds-5/example_programs/HBwithFH.F (revision 532)
+++ trunk/HiggsBounds-5/example_programs/HBwithFH.F (revision 533)
@@ -1,601 +1,591 @@
*********************************************************************
* HBwithFH
*
* Updated demo program for HiggsBounds 4 using MSSM input from
* FeynHiggs (FH version > 2.9.4 required)
*
*********************************************************************
program HBwithFH
implicit none
integer error
c used by FHHiggsCorr
double precision MHiggs(4)
double complex SAeff, UHiggs(3,3), ZHiggs(3,3)
c used by FHSelectUZ:
integer uzint, uzext, mfeff
c used by FHCouplings:
#include "FHCouplings.h"
double complex couplings(ncouplings), couplingsms(ncouplingsms)
double precision gammas(ngammas), gammasms(ngammasms)
integer fast
c used by FHHiggsProd:
double precision sqrts, prodxs(nprodxs)
c used by FHGetPara:
integer nmfv
c This is for FH 2.10.x
double precision MSf(2,5,3), MASf(6,5), MCha(2), MNeu(4)
double complex USf(2,2,5,3), UASf(6,6,5)
double complex UCha(2,2), VCha(2,2), ZNeu(4,4)
double complex DeltaMB
double precision MGl
double precision MHtree(4), SAtree
c used by FHRetrieveSMPara:
double precision invAlfa, AlfasMZ, GF
double precision ME, MU, MD, MM, MC, MS, ML, MB
double precision MW, MZ
double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
c used by initialize_HiggsBounds
integer nHiggsneut,nHiggsplus
character(LEN=5) whichanalyses
-c used by HiggsBounds_neutral_input_part
+c used by HiggsBounds_neutral_input_hadr
+C character(LEN=5) collider_str
double precision Mh(3),GammaTotal_hj(3)
- integer CP_value(3)
+ integer CP_value(3), collider_s
double precision CS_lep_hjZ_ratio(3),
& CS_lep_bbhj_ratio(3),CS_lep_tautauhj_ratio(3),
- & CS_lep_hjhi_ratio_nHbynH(3,3),
- & CS_gg_hj_ratio(3),CS_bb_hj_ratio(3),
- & CS_bg_hjb_ratio(3),
- & CS_ud_hjWp_ratio(3),CS_cs_hjWp_ratio(3),
- & CS_ud_hjWm_ratio(3),CS_cs_hjWm_ratio(3),
- & CS_gg_hjZ_ratio(3),
- & CS_dd_hjZ_ratio(3),CS_uu_hjZ_ratio(3),
- & CS_ss_hjZ_ratio(3),CS_cc_hjZ_ratio(3),
- & CS_bb_hjZ_ratio(3),
- & CS_tev_vbf_ratio(3),CS_tev_tthj_ratio(3),
- & CS_lhc7_vbf_ratio(3),CS_lhc7_tthj_ratio(3),
- & CS_lhc8_vbf_ratio(3),CS_lhc8_tthj_ratio(3),
+ & CS_lep_hjhi_ratio(3,3),CS_hj_ratio(4,3),
+ & CS_gg_hj_ratio(4,3),CS_bb_hj_ratio(4,3),
+ & CS_hjW_ratio(4,3),CS_hjZ_ratio(4,3),
+ & CS_vbf_ratio(4,3),CS_tthj_ratio(4,3),
+ & CS_thj_tchan_ratio(4,3),CS_thj_schan_ratio(4,3),
+ & CS_hjhi(4,3,3),
& BR_hjss(3),BR_hjcc(3),
- & BR_hjbb(3),BR_hjmumu(3),BR_hjtautau(3),
+ & BR_hjbb(3),BR_hjtt(3),BR_hjmumu(3),BR_hjtautau(3),
& BR_hjWW(3),BR_hjZZ(3),BR_hjZga(3),
& BR_hjgaga(3),BR_hjgg(3),
- & BR_hjinvisible(3),BR_hjhihi_nHbynH(3,3)
+ & BR_hjinvisible(3),BR_hkhjhi(3,3,3),
+ & BR_hjhiZ(3,3),BR_hjemu(3),BR_hjetau(3),BR_hjmutau(3)
c used by HiggsBounds_charged_input
double precision Mhplus(1),GammaTotal_Hpj(1),
& CS_lep_HpjHmj_ratio(1),
- & BR_tWpb,BR_tHpjb(1),
- & BR_Hpjcs(1),BR_Hpjcb(1),BR_Hpjtaunu(1)
+ & BR_tWpb,BR_tHpjb(1),BR_Hpjcs(1),BR_Hpjcb(1),BR_Hpjtaunu(1),
+ & BR_Hpjtb(1),BR_HpjWZ(1),BR_HpjhiW(1,3),
+ & CS_Hpjtb(4,1), CS_Hpjbjet(4,1), CS_HpjW(4,1),
+ & CS_HpjZ(4,1), CS_vbf_Hpj(4,1), CS_HpjHmj(4,1), CS_Hpjhi(4,1,3)
c used by run_HiggsBounds
integer HBresult,chan,ncombined
double precision obsratio
c misc:
- integer i,j,as,t
+ integer i,j,k,as,t,collider
double precision norm,CW2,Pi
double precision
& g2hjbb(3),g2hjWW(3),g2hjZZ(3),
- & g2hjgg(3),g2hjhiZ_nHbynH(3,3)
+ & g2hjgg(3),g2hjhiZ(3,3)
double precision g2hjbb_s(3),g2hjbb_p(3)
double precision g2hjtautau_s(3),g2hjtautau_p(3)
integer sneutrino_lspcandidate_number
logical invisible_lsp
double precision lspcandidate_mass
Pi = 3.1415926535897932384626433832795029D0
* * * * * * * * * * * * * * * * * * * * *
c Set number of neutral and charged Higgs bosons in the MSSM:
nHiggsneut=3
nHiggsplus=1
c The string 'whichanalyses' determines which subset of experimental
c results are used. In this example, we've used the option 'LandH',
c which instructs HiggsBounds to use tables of results
c from LEP, Tevatron and LHC (i.e. the full set of
c results supplied with HiggsBounds).
whichanalyses='LandH'
c The subroutine initialize_HiggsBounds reads in all necessary
c tables etc.
c It must be called before any of the other HiggsBounds subroutines.
call initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses)
c If you would like to perform scans over variables, the subroutine
c initialize_HiggsBounds (and finish_HiggsBounds) should be called
c outside the do-loops in order to save time.
* * * * * * * * * * * * * * * * * * * * *
c calls to FH subroutines:
c the subroutines setFlags, setPara, setSLHA
c are also contained in this file
call setFlags
* either use setPara to set the parameters directly
* or use setSLHA to read them from an SLHA file
call setPara
c call setSLHA("tmp.slha")
c // User this line for FH < 2.9.5
c call FHGetPara(error, nmfv, MASf, UASf,
call FHGetPara(error, nmfv, MSf, USf,MASf, UASf,
& MCha, UCha, VCha, MNeu, ZNeu, DeltaMB, MGl,
& MHtree, SAtree)
if( error .ne. 0 ) stop
call FHHiggsCorr(error, MHiggs, SAeff, UHiggs, ZHiggs)
if( error .ne. 0 ) stop
c NOTE: we are setting uzint=uzext
mfeff=1
uzint=2
uzext=2
call FHSelectUZ(error, uzint, uzext, mfeff)
if( error .ne. 0 ) stop
fast=1
call FHCouplings(error,
& couplings, couplingsms, gammas, gammasms, fast)
if( error .ne. 0 ) stop
-c We would like FH to calculate LHC cross sections
- sqrts=7.0D0
- call FHHiggsProd(error, sqrts, prodxs)
- if( error .ne. 0 ) stop
-
call FHRetrieveSMPara(error,
& invAlfa, AlfasMZ, GF,
& ME, MU, MD, MM, MC, MS, ML, MB,
& MW, MZ,
& CKMlambda, CKMA, CKMrhobar, CKMetabar)
* * * * * * * * * * * * * * * * * * * * *
c Set variables needed by HiggsBounds (using results from FeynHiggs).
c See HiggsBounds documentation for definition of variables used
c as arguments to HiggsBounds_neutral_input_part and run_HiggsBounds
c and FeynHiggs documentation for all other variables.
c Note: It is slightly more accurate to use the subroutine HiggsBounds_neutral_input_part
c rather than the subroutine HiggsBounds_neutral_input_effC because the SM branching ratios
c used internally in HiggsBounds (from HDecay) are not identical to the SM branching
c ratios used in FeynHiggs
do i=1,3
Mh(i)=MHiggs(i)
GammaTotal_hj(i) = GammaTot(i)
BR_hjss(i) = BR(H0FF(i,4,2,2))
BR_hjcc(i) = BR(H0FF(i,3,2,2))
BR_hjbb(i) = BR(H0FF(i,4,3,3))
+ BR_hjtt(i) = BR(H0FF(i,3,3,3))
BR_hjmumu(i) = BR(H0FF(i,2,2,2))
BR_hjtautau(i) = BR(H0FF(i,2,3,3))
+ BR_hjemu(i) = BR(H0FF(i,2,1,2))
+ BR_hjetau(i) = BR(H0FF(i,2,1,3))
+ BR_hjmutau(i) = BR(H0FF(i,2,2,3))
BR_hjWW(i) = BR(H0VV(i,4))
BR_hjgaga(i) = BR(H0VV(i,1))
BR_hjZga(i) = BR(H0VV(i,2))
BR_hjZZ(i) = BR(H0VV(i,3))
BR_hjgg(i) = BR(H0VV(i,5))
- if(GammaSM(H0FF(i,4,3,3)).le.0.0D0)then
- g2hjbb(i)=0.0D0
- else
- g2hjbb(i)=Gamma(H0FF(i,4,3,3))
- & /GammaSM(H0FF(i,4,3,3))
- endif
-
-c Note that this is currently equivalent to
-c g2hjbb(i)= bbh(i)/bbhSM(i)
-c g2hjbb(i)= btagbh(i)/btagbhSM(i)
-c as long as MH>80 GeV
-
- CS_bg_hjb_ratio(i) = g2hjbb(i)
- CS_bb_hj_ratio(i) = g2hjbb(i)
-
+ do collider=1,4
+c We would like FH to calculate LHC cross sections
+ select case(collider)
+ case(1)
+ sqrts=2.0D0
+ case(2)
+ sqrts=7.0D0
+ case(3)
+ sqrts=8.0D0
+ case(4)
+ sqrts=13.0D0
+ end select
+
+ call FHHiggsProd(error, sqrts, prodxs)
+ if( error .ne. 0 ) stop
+
+ CS_gg_hj_ratio(collider,i)=ggh(i)/gghSM(i)
+C write(*,*) "i,collider,CS_gghj_ratio = ", i,collider,CS_gg_hj_ratio(collider,i),ggh(i),gghSM(i)
+ CS_bb_hj_ratio(collider,i)=bbh(i)/bbhSM(i)
+C write(*,*) "i,collider,CS_bbhj_ratio = ", i,collider,CS_bb_hj_ratio(collider,i),bbh(i),bbhSM(i)
+ CS_hj_ratio(collider,i)=(ggh(i)+bbh(i))/(gghSM(i)+bbhSM(i))
+ CS_hjW_ratio(collider,i)=Wh(i)/WhSM(i)
+C write(*,*) "i,collider,CS_hjW_ratio = ", i,collider,CS_hjW_ratio(collider,i),Wh(i),WhSM(i)
+ CS_hjZ_ratio(collider,i)=Zh(i)/ZhSM(i)
+C write(*,*) "i,collider,CS_hjZ_ratio = ", i,collider,CS_hjZ_ratio(collider,i),Zh(i),ZhSM(i)
+ CS_vbf_ratio(collider,i)=qqh(i)/qqhSM(i)
+C write(*,*) "i,collider,CS_qqhj_ratio = ", i,collider,CS_vbf_ratio(collider,i),qqh(i),qqhSM(i)
+ CS_tthj_ratio(collider,i)=tth(i)/tthSM(i)
+C write(*,*) "i,collider,CS_tthj_ratio = ", i,collider,CS_tthj_ratio(collider,i),tth(i),tthSM(i)
+ CS_thj_tchan_ratio(collider,i)=0.0D0! NOT CALCULATED YET BY FH
+ CS_thj_schan_ratio(collider,i)=0.0D0! NOT CALCULATED YET BY FH
+ do j=1,3
+ CS_hjhi(collider,i,j) = 0.0D0 ! NOT CALCULATED YET BY FH
+ enddo
+
+ CS_Hpjtb(collider,1)=tHm2 ! Charged Higgs cross section
+C write(*,*) "Charged Higgs, collider ", tHm2, collider
+ enddo
+ BR_HpjhiW(1,i)=BR(HpHV(i))
+
g2hjbb_s(i)=(abs(RCoupling(H0FF(i,4,3,3))
& /RCouplingSM(H0FF(i,4,3,3))+
& LCoupling(H0FF(i,4,3,3))
& /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
g2hjbb_p(i)=(abs(RCoupling(H0FF(i,4,3,3))
& /RCouplingSM(H0FF(i,4,3,3))-
& LCoupling(H0FF(i,4,3,3))
& /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
g2hjtautau_s(i)=(abs(RCoupling(H0FF(i,2,3,3))
& /RCouplingSM(H0FF(i,2,3,3))+
& LCoupling(H0FF(i,2,3,3))
& /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
g2hjtautau_p(i)=(abs(RCoupling(H0FF(i,2,3,3))
& /RCouplingSM(H0FF(i,2,3,3))-
& LCoupling(H0FF(i,2,3,3))
& /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
if( g2hjbb_p(i).lt.1.0D-10)then
CP_value(i) = 1
elseif( g2hjbb_s(i).lt.1.0D-10)then
CP_value(i) = -1
else
CP_value(i) = 0
endif
CS_lep_bbhj_ratio(i) = g2hjbb_s(i)+g2hjbb_p(i)
CS_lep_tautauhj_ratio(i) = g2hjtautau_s(i)+g2hjtautau_p(i)
g2hjWW(i)= dble( Coupling(H0VV(i,4))
& / CouplingSM(H0VV(i,4)) )**2.0D0
& + dimag( Coupling(H0VV(i,4))
& / CouplingSM(H0VV(i,4)) )**2.0D0
-c Note that this is currently equivalent to
-c g2hjWW(i)= WhTev(i)/WhTevSM(i
-c g2hjWW(i)= qqhTev(i)/qqhTevSM(i)
-c as long as MH>80 GeV and uzint=uzext
g2hjZZ(i)= dble( Coupling(H0VV(i,3))
& / CouplingSM(H0VV(i,3)) )**2.0D0
& + dimag( Coupling(H0VV(i,3))
& / CouplingSM(H0VV(i,3)) )**2.0D0
-c Note that this is currently equivalent to
-c g2hjZZ(i)= ZhTev(i)/ZhTevSM(i)
-c as long as MH>80 GeV and uzint=uzext
-c It is also equivalent to g2hjWW(i)
CS_lep_hjZ_ratio(i) = g2hjZZ(i)
-
- CS_gg_hjZ_ratio(i) = 0.0D0
- CS_dd_hjZ_ratio(i) = g2hjZZ(i)
- CS_uu_hjZ_ratio(i) = g2hjZZ(i)
- CS_ss_hjZ_ratio(i) = g2hjZZ(i)
- CS_cc_hjZ_ratio(i) = g2hjZZ(i)
- CS_bb_hjZ_ratio(i) = g2hjZZ(i)
-
- CS_ud_hjWp_ratio(i) = g2hjZZ(i)
- CS_cs_hjWp_ratio(i) = g2hjZZ(i)
- CS_ud_hjWm_ratio(i) = g2hjZZ(i)
- CS_cs_hjWm_ratio(i) = g2hjZZ(i)
-
- CS_tev_vbf_ratio(i) = g2hjZZ(i)
- CS_lhc7_vbf_ratio(i) = g2hjZZ(i)
- CS_lhc8_vbf_ratio(i) = g2hjZZ(i)
-
-
- if(tthSM(i).gt.0.0D0)then
- CS_tev_tthj_ratio(i) = tth(i)/tthSM(i)
- else
- CS_tev_tthj_ratio(i) = 0.0D0
- endif
-
- CS_lhc7_tthj_ratio(i) = CS_tev_tthj_ratio(i)
- CS_lhc8_tthj_ratio(i) = CS_tev_tthj_ratio(i)
-
-c tevatron gluon fusion XS is not calculated in FH is MH<90 geV
- if(Mh(i).gt.90.0001D0)then
- if(gghSM(i).gt.0.0D0)then
- CS_gg_hj_ratio(i) = ggh(i)/gghSM(i)
- else
- CS_gg_hj_ratio(i) = 0.0D0
- endif
- else
- if(GammaSM(H0VV(i,5)).le.0.0D0)then
- CS_gg_hj_ratio(i)=0.0D0
- else
- CS_gg_hj_ratio(i)= Gamma(H0VV(i,5))/GammaSM(H0VV(i,5))
- endif
- endif
-
- enddo
- norm=GF*sqrt(2.0D0)*MZ**2.0D0
+ enddo
+ norm=GF*sqrt(2.0D0)*MZ**2.0D0
- do j=1,3
- do i=1,3
- g2hjhiZ_nHbynH(j,i)= (
+ do j=1,3
+ do i=1,3
+ g2hjhiZ(j,i)= (
& dble( Coupling(H0HV(j,i)) )**2.0D0
& + dimag( Coupling(H0HV(j,i)) )**2.0D0
& )
& /norm
- CS_lep_hjhi_ratio_nHbynH(j,i) = g2hjhiZ_nHbynH(j,i)
+ CS_lep_hjhi_ratio(j,i) = g2hjhiZ(j,i)
- BR_hjhihi_nHbynH(j,i)=BR(H0HH(j,i,i))
+ BR_hjhiZ(j,i)=BR(H0HV(j,i))
+ do k=1,3
+ BR_hkhjhi(k,j,i)=BR(H0HH(k,j,i))
+ enddo
+ enddo
enddo
- enddo
c higgs->neutralino1 neutralino1 contributes the invisible Higgs decay width
c when neutralino1 or sneutrino is the LSP
do i=1,3
sneutrino_lspcandidate_number=0
invisible_lsp=.True.
c first determine whether lightest sneutrino is lighter than the lightest neutralino
c
c sneutrino_lspcandidate_number=0 indicates that lightest neutralino is
c lighter than all the sneutrinos
lspcandidate_mass=MNeu(1)
do as=1,3
if( MASf(as,1) .lt. lspcandidate_mass )then
lspcandidate_mass=MASf(as,1)
sneutrino_lspcandidate_number=as
endif
enddo
if( MCha(1) .lt. lspcandidate_mass )then
invisible_lsp=.False.
elseif( MGl .lt. lspcandidate_mass )then
invisible_lsp=.False.
else
do as=1,6
do t=2,4
if( MASf(as,t) .lt. lspcandidate_mass )then
invisible_lsp=.False.
endif
enddo
enddo
endif
if(invisible_lsp)then
if(sneutrino_lspcandidate_number.eq.0)then
BR_hjinvisible(i) = BR(H0NeuNeu(i,1,1))
else
BR_hjinvisible(i) = BR(H0SfSf(i,1,1,1,as))
endif
else
BR_hjinvisible(i) = 0.0D0
endif
enddo
* * * * * * * * * * * * * * * * * * * * *
c Charged Higgs input
Mhplus(1) = MHiggs(4)
GammaTotal_Hpj(1) = GammaTot(4)
CS_lep_HpjHmj_ratio(1) = 1.0D0
BR_tWpb = BR( tBF(1) )
BR_tHpjb(1) = BR( tBF(2) )
BR_Hpjcs(1) = BR( HpFF(2,2,2) )
BR_Hpjcb(1) = BR( HpFF(2,2,3) )
BR_Hpjtaunu(1) = BR( HpFF(1,3,3) )
+ BR_Hpjtb(1) = BR( HpFF(2,3,3) )
+ BR_HpjWZ(1) = 0.0D0 ! NOT CALCULATED BY FH (0 in the MSSM at tree-level)
* * * * * * * * * * * * * * * * * * * * *
-c calls to HiggsBounds_neutral_input_part,HiggsBounds_charged_input,
-c which give input to HiggsBounds
- print*,'calling HiggsBounds_neutral_input_part'
+ write(*,*) "Higgs masses: ", Mh
+
+ call HiggsBounds_set_mass_uncertainties((/2.0D0,0.0D0,0.0D0/), 0.0D0)
+
+ print*,'calling HiggsBounds_neutral_input_hadr'
-C print*, CS_gg_hj_ratio
-C print*, CS_bb_hj_ratio
-C print*,MHiggs
-C print*,BR_hjhihi_nHbynH
-
-
- call HiggsBounds_neutral_input_part(Mh,GammaTotal_hj,CP_value,
- & CS_lep_hjZ_ratio,
- & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio,
- & CS_lep_hjhi_ratio_nHbynH,
- & CS_gg_hj_ratio,CS_bb_hj_ratio,
- & CS_bg_hjb_ratio,
- & CS_ud_hjWp_ratio,CS_cs_hjWp_ratio,
- & CS_ud_hjWm_ratio,CS_cs_hjWm_ratio,
- & CS_gg_hjZ_ratio,
- & CS_dd_hjZ_ratio,CS_uu_hjZ_ratio,
- & CS_ss_hjZ_ratio,CS_cc_hjZ_ratio,
- & CS_bb_hjZ_ratio,
- & CS_tev_vbf_ratio,CS_tev_tthj_ratio,
- & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio,
- & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio,
- & BR_hjss,BR_hjcc,
- & BR_hjbb,BR_hjmumu,BR_hjtautau,
- & BR_hjWW,BR_hjZZ,BR_hjZga, BR_hjgaga,BR_hjgg,
- & BR_hjinvisible,BR_hjhihi_nHbynH )
+ call HiggsBounds_neutral_input_properties(Mh,GammaTotal_hj,CP_value)
+
+ call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj,
+ & CS_lep_HpjHmj_ratio,
+ & BR_tWpb,BR_tHpjb,
+ & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu,BR_Hpjtb,
+ & BR_HpjWZ,BR_HpjhiW)
+
+ call HiggsBounds_neutral_input_SMBR(BR_hjss,BR_hjcc,BR_hjbb,
+ & BR_hjtt,BR_hjmumu,
+ & BR_hjtautau,BR_hjWW,
+ & BR_hjZZ,BR_hjZga,BR_hjgaga,
+ & BR_hjgg)
+
+ call HiggsBounds_neutral_input_nonSMBR(BR_hjinvisible,BR_hkhjhi,BR_hjhiZ,
+ & BR_hjemu,BR_hjetau,BR_hjmutau)
+ do collider=1,4
+ select case(collider)
+ case(1)
+ collider_s = 2
+ case(2)
+ collider_s = 7
+ case(3)
+ collider_s = 8
+ case(4)
+ collider_s = 13
+ end select
+
+ call HiggsBounds_neutral_input_hadr(collider_s,CS_hj_ratio(collider,:),
+ & CS_gg_hj_ratio(collider,:),CS_bb_hj_ratio(collider,:),
+ & CS_hjW_ratio(collider,:),CS_hjZ_ratio(collider,:),
+ & CS_vbf_ratio(collider,:),CS_tthj_ratio(collider,:),
+ & CS_thj_tchan_ratio(collider,:),CS_thj_schan_ratio(collider,:),
+ & CS_hjhi(collider,:,:))
+
+ call HiggsBounds_charged_input_hadr(collider_s,CS_Hpjtb(collider,:),
+ & CS_Hpjbjet(collider,:), CS_HpjW(collider,:),
+ & CS_HpjZ(collider,:), CS_vbf_Hpj(collider,:),
+ & CS_HpjHmj(collider,:), CS_Hpjhi(collider,:,:))
- print*,'calling HiggsBounds_charged_input'
- call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj,
- & CS_lep_HpjHmj_ratio,
- & BR_tWpb,BR_tHpjb,
- & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu)
-
+ enddo
+
* * * * * * * * * * * * * * * * * * * * *
c call to run_HiggsBounds
call run_HiggsBounds( HBresult,chan, obsratio, ncombined )
print*,' '
print*,'************* HiggsBounds Results **************'
print*,' '
print*,'Is this parameter point excluded by LEP, Tevatron'
print*,'or LHC data?'
print*, HBresult, ', where'
print*,' 0 = yes, it is excluded'
print*,' 1 = no, it has not been excluded'
print*,' -1 = invalid parameter set'
print*,' '
print*,'The process with the highest statistical sensitivity'
print*,'is'
print*, chan,'(see Key.dat)'
print*,'This process has a theoretical rate vs. limit of'
print*, obsratio
print*,' '
print*,'The number of Higgs which have contributed to the'
print*,'theoretical rate of this process was'
print*, ncombined
print*,' '
print*,'See HiggsBounds documentation for more information.'
print*,'****************************************************'
print*,' '
* * * * * * * * * * * * * * * * * * * * *
c deallocates arrays used by HiggsBounds:
call finish_HiggsBounds
end
************************************************************************
subroutine setFlags
implicit none
integer mssmpart, fieldren, tanbren, higgsmix, p2approx
- integer looplevel, runningMT, botResum, tlCplxApprox
+ integer looplevel, loglevel, runningMT, botResum, tlCplxApprox
c Using default (recommended) values of all FH flags
parameter (mssmpart = 4)
parameter (fieldren = 0)
parameter (tanbren = 0)
parameter (higgsmix = 2)
- parameter (p2approx = 0)
+ parameter (p2approx = 4)
parameter (looplevel = 2)
+ parameter (loglevel = 3)
parameter (runningMT = 1)
parameter (botResum = 1)
parameter (tlCplxApprox = 0)
integer error
call FHSetFlags(error, mssmpart, fieldren, tanbren,
- & higgsmix, p2approx, looplevel,
+ & higgsmix, p2approx, looplevel, loglevel,
& runningMT, botResum, tlCplxApprox)
if( error .ne. 0 ) stop
end
************************************************************************
subroutine setPara
implicit none
double precision invAlfa, AlfasMZ, GF
double precision ME, MU, MD, MM, MC, MS, ML, MB, MZ, MW
double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
parameter (invAlfa = -1)
parameter (AlfasMZ = -1)
parameter (GF = -1)
parameter (ME = -1)
parameter (MU = -1)
parameter (MD = -1)
parameter (MM = -1)
parameter (MC = -1)
parameter (MS = -1)
parameter (ML = -1)
parameter (MB = -1)
parameter (MW = -1)
parameter (MZ = -1)
parameter (CKMlambda = -1)
parameter (CKMA = -1)
parameter (CKMrhobar = -1)
parameter (CKMetabar = -1)
double precision MT, TB, MA0, MHp
parameter (MT = 173.2)
- parameter (TB = 5.)
+ parameter (TB = 15.)
parameter (MA0 = 500)
parameter (MHp = -1)
double precision MSusy
double precision M3SL, M2SL, M1SL
double precision M3SE, M2SE, M1SE
double precision M3SQ, M2SQ, M1SQ
double precision M3SU, M2SU, M1SU
double precision M3SD, M2SD, M1SD
parameter (MSusy = 1000)
parameter (M3SL = MSusy)
parameter (M2SL = M3SL)
parameter (M1SL = M2SL)
parameter (M3SE = MSusy)
parameter (M2SE = M3SE)
parameter (M1SE = M2SE)
parameter (M3SQ = MSusy)
parameter (M2SQ = M3SQ)
parameter (M1SQ = M2SQ)
parameter (M3SU = MSusy)
parameter (M2SU = M3SU)
parameter (M1SU = M2SU)
parameter (M3SD = MSusy)
parameter (M2SD = M3SD)
parameter (M1SD = M2SD)
double complex Atau, At, Ab
double complex Amu, Ac, As
double complex Ae, Au, Ad
- parameter (At = 2000)
+ parameter (At = 1550)
parameter (Ab = At)
parameter (Atau = At)
parameter (Ac = At)
parameter (As = Ab)
parameter (Amu = Atau)
parameter (Au = Ac)
parameter (Ad = As)
parameter (Ae = Amu)
double complex MUE, M_1, M_2, M_3
parameter (MUE = 200)
parameter (M_1 = 0)
parameter (M_2 = 200)
parameter (M_3 = 1500)
double precision Qtau, Qt, Qb
parameter (Qtau = 0)
parameter (Qt = 0)
parameter (Qb = 0)
double precision scalefactor
parameter (scalefactor = 1)
integer error
call FHSetSMPara(error,
& invAlfa, AlfasMZ, GF,
& ME, MU, MD, MM, MC, MS, ML, MB,
& MW, MZ,
& CKMlambda, CKMA, CKMrhobar, CKMetabar)
if( error .ne. 0 ) stop
call FHSetPara(error, scalefactor,
& MT, TB, MA0, MHp,
& M3SL, M3SE, M3SQ, M3SU, M3SD,
& M2SL, M2SE, M2SQ, M2SU, M2SD,
& M1SL, M1SE, M1SQ, M1SU, M1SD,
& MUE,
& Atau, At, Ab,
& Amu, Ac, As,
& Ae, Au, Ad,
& M_1, M_2, M_3,
& Qtau, Qt, Qb)
if( error .ne. 0 ) stop
end
************************************************************************
subroutine setSLHA(filename)
implicit none
character*(*) filename
#include "SLHA.h"
integer error
double complex slhadata(nslhadata)
call SLHARead(error, slhadata, filename, 1)
if( error .ne. 0 ) stop
call FHSetSLHA(error, slhadata)
if( error .ne. 0 ) stop
end
Index: trunk/HiggsBounds-5/example_programs/legacy/HBwithFH.F
===================================================================
--- trunk/HiggsBounds-5/example_programs/legacy/HBwithFH.F (revision 0)
+++ trunk/HiggsBounds-5/example_programs/legacy/HBwithFH.F (revision 533)
@@ -0,0 +1,601 @@
+*********************************************************************
+* HBwithFH
+*
+* Updated demo program for HiggsBounds 4 using MSSM input from
+* FeynHiggs (FH version > 2.9.4 required)
+*
+*********************************************************************
+
+ program HBwithFH
+ implicit none
+
+ integer error
+
+c used by FHHiggsCorr
+ double precision MHiggs(4)
+ double complex SAeff, UHiggs(3,3), ZHiggs(3,3)
+
+c used by FHSelectUZ:
+ integer uzint, uzext, mfeff
+
+c used by FHCouplings:
+#include "FHCouplings.h"
+ double complex couplings(ncouplings), couplingsms(ncouplingsms)
+ double precision gammas(ngammas), gammasms(ngammasms)
+ integer fast
+
+c used by FHHiggsProd:
+ double precision sqrts, prodxs(nprodxs)
+
+c used by FHGetPara:
+ integer nmfv
+c This is for FH 2.10.x
+ double precision MSf(2,5,3), MASf(6,5), MCha(2), MNeu(4)
+ double complex USf(2,2,5,3), UASf(6,6,5)
+ double complex UCha(2,2), VCha(2,2), ZNeu(4,4)
+ double complex DeltaMB
+ double precision MGl
+ double precision MHtree(4), SAtree
+
+c used by FHRetrieveSMPara:
+ double precision invAlfa, AlfasMZ, GF
+ double precision ME, MU, MD, MM, MC, MS, ML, MB
+ double precision MW, MZ
+ double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
+
+c used by initialize_HiggsBounds
+ integer nHiggsneut,nHiggsplus
+ character(LEN=5) whichanalyses
+
+c used by HiggsBounds_neutral_input_part
+ double precision Mh(3),GammaTotal_hj(3)
+ integer CP_value(3)
+ double precision CS_lep_hjZ_ratio(3),
+ & CS_lep_bbhj_ratio(3),CS_lep_tautauhj_ratio(3),
+ & CS_lep_hjhi_ratio_nHbynH(3,3),
+ & CS_gg_hj_ratio(3),CS_bb_hj_ratio(3),
+ & CS_bg_hjb_ratio(3),
+ & CS_ud_hjWp_ratio(3),CS_cs_hjWp_ratio(3),
+ & CS_ud_hjWm_ratio(3),CS_cs_hjWm_ratio(3),
+ & CS_gg_hjZ_ratio(3),
+ & CS_dd_hjZ_ratio(3),CS_uu_hjZ_ratio(3),
+ & CS_ss_hjZ_ratio(3),CS_cc_hjZ_ratio(3),
+ & CS_bb_hjZ_ratio(3),
+ & CS_tev_vbf_ratio(3),CS_tev_tthj_ratio(3),
+ & CS_lhc7_vbf_ratio(3),CS_lhc7_tthj_ratio(3),
+ & CS_lhc8_vbf_ratio(3),CS_lhc8_tthj_ratio(3),
+ & BR_hjss(3),BR_hjcc(3),
+ & BR_hjbb(3),BR_hjmumu(3),BR_hjtautau(3),
+ & BR_hjWW(3),BR_hjZZ(3),BR_hjZga(3),
+ & BR_hjgaga(3),BR_hjgg(3),
+ & BR_hjinvisible(3),BR_hjhihi_nHbynH(3,3)
+
+c used by HiggsBounds_charged_input
+ double precision Mhplus(1),GammaTotal_Hpj(1),
+ & CS_lep_HpjHmj_ratio(1),
+ & BR_tWpb,BR_tHpjb(1),
+ & BR_Hpjcs(1),BR_Hpjcb(1),BR_Hpjtaunu(1)
+
+c used by run_HiggsBounds
+ integer HBresult,chan,ncombined
+ double precision obsratio
+
+c misc:
+ integer i,j,as,t
+ double precision norm,CW2,Pi
+ double precision
+ & g2hjbb(3),g2hjWW(3),g2hjZZ(3),
+ & g2hjgg(3),g2hjhiZ_nHbynH(3,3)
+ double precision g2hjbb_s(3),g2hjbb_p(3)
+ double precision g2hjtautau_s(3),g2hjtautau_p(3)
+ integer sneutrino_lspcandidate_number
+ logical invisible_lsp
+ double precision lspcandidate_mass
+
+ Pi = 3.1415926535897932384626433832795029D0
+
+* * * * * * * * * * * * * * * * * * * * *
+
+c Set number of neutral and charged Higgs bosons in the MSSM:
+ nHiggsneut=3
+ nHiggsplus=1
+
+c The string 'whichanalyses' determines which subset of experimental
+c results are used. In this example, we've used the option 'LandH',
+c which instructs HiggsBounds to use tables of results
+c from LEP, Tevatron and LHC (i.e. the full set of
+c results supplied with HiggsBounds).
+ whichanalyses='LandH'
+
+c The subroutine initialize_HiggsBounds reads in all necessary
+c tables etc.
+c It must be called before any of the other HiggsBounds subroutines.
+ call initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses)
+
+c If you would like to perform scans over variables, the subroutine
+c initialize_HiggsBounds (and finish_HiggsBounds) should be called
+c outside the do-loops in order to save time.
+
+* * * * * * * * * * * * * * * * * * * * *
+
+c calls to FH subroutines:
+
+c the subroutines setFlags, setPara, setSLHA
+c are also contained in this file
+ call setFlags
+
+* either use setPara to set the parameters directly
+* or use setSLHA to read them from an SLHA file
+ call setPara
+c call setSLHA("tmp.slha")
+
+c // User this line for FH < 2.9.5
+c call FHGetPara(error, nmfv, MASf, UASf,
+ call FHGetPara(error, nmfv, MSf, USf,MASf, UASf,
+ & MCha, UCha, VCha, MNeu, ZNeu, DeltaMB, MGl,
+ & MHtree, SAtree)
+ if( error .ne. 0 ) stop
+
+ call FHHiggsCorr(error, MHiggs, SAeff, UHiggs, ZHiggs)
+ if( error .ne. 0 ) stop
+
+c NOTE: we are setting uzint=uzext
+ mfeff=1
+ uzint=2
+ uzext=2
+ call FHSelectUZ(error, uzint, uzext, mfeff)
+ if( error .ne. 0 ) stop
+
+ fast=1
+ call FHCouplings(error,
+ & couplings, couplingsms, gammas, gammasms, fast)
+ if( error .ne. 0 ) stop
+
+c We would like FH to calculate LHC cross sections
+ sqrts=7.0D0
+ call FHHiggsProd(error, sqrts, prodxs)
+ if( error .ne. 0 ) stop
+
+ call FHRetrieveSMPara(error,
+ & invAlfa, AlfasMZ, GF,
+ & ME, MU, MD, MM, MC, MS, ML, MB,
+ & MW, MZ,
+ & CKMlambda, CKMA, CKMrhobar, CKMetabar)
+
+* * * * * * * * * * * * * * * * * * * * *
+
+c Set variables needed by HiggsBounds (using results from FeynHiggs).
+c See HiggsBounds documentation for definition of variables used
+c as arguments to HiggsBounds_neutral_input_part and run_HiggsBounds
+c and FeynHiggs documentation for all other variables.
+
+c Note: It is slightly more accurate to use the subroutine HiggsBounds_neutral_input_part
+c rather than the subroutine HiggsBounds_neutral_input_effC because the SM branching ratios
+c used internally in HiggsBounds (from HDecay) are not identical to the SM branching
+c ratios used in FeynHiggs
+
+ do i=1,3
+ Mh(i)=MHiggs(i)
+ GammaTotal_hj(i) = GammaTot(i)
+
+ BR_hjss(i) = BR(H0FF(i,4,2,2))
+ BR_hjcc(i) = BR(H0FF(i,3,2,2))
+ BR_hjbb(i) = BR(H0FF(i,4,3,3))
+ BR_hjmumu(i) = BR(H0FF(i,2,2,2))
+ BR_hjtautau(i) = BR(H0FF(i,2,3,3))
+
+ BR_hjWW(i) = BR(H0VV(i,4))
+ BR_hjgaga(i) = BR(H0VV(i,1))
+ BR_hjZga(i) = BR(H0VV(i,2))
+ BR_hjZZ(i) = BR(H0VV(i,3))
+ BR_hjgg(i) = BR(H0VV(i,5))
+
+ if(GammaSM(H0FF(i,4,3,3)).le.0.0D0)then
+ g2hjbb(i)=0.0D0
+ else
+ g2hjbb(i)=Gamma(H0FF(i,4,3,3))
+ & /GammaSM(H0FF(i,4,3,3))
+ endif
+
+c Note that this is currently equivalent to
+c g2hjbb(i)= bbh(i)/bbhSM(i)
+c g2hjbb(i)= btagbh(i)/btagbhSM(i)
+c as long as MH>80 GeV
+
+ CS_bg_hjb_ratio(i) = g2hjbb(i)
+ CS_bb_hj_ratio(i) = g2hjbb(i)
+
+ g2hjbb_s(i)=(abs(RCoupling(H0FF(i,4,3,3))
+ & /RCouplingSM(H0FF(i,4,3,3))+
+ & LCoupling(H0FF(i,4,3,3))
+ & /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
+ g2hjbb_p(i)=(abs(RCoupling(H0FF(i,4,3,3))
+ & /RCouplingSM(H0FF(i,4,3,3))-
+ & LCoupling(H0FF(i,4,3,3))
+ & /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
+
+ g2hjtautau_s(i)=(abs(RCoupling(H0FF(i,2,3,3))
+ & /RCouplingSM(H0FF(i,2,3,3))+
+ & LCoupling(H0FF(i,2,3,3))
+ & /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
+ g2hjtautau_p(i)=(abs(RCoupling(H0FF(i,2,3,3))
+ & /RCouplingSM(H0FF(i,2,3,3))-
+ & LCoupling(H0FF(i,2,3,3))
+ & /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
+
+ if( g2hjbb_p(i).lt.1.0D-10)then
+ CP_value(i) = 1
+ elseif( g2hjbb_s(i).lt.1.0D-10)then
+ CP_value(i) = -1
+ else
+ CP_value(i) = 0
+ endif
+
+ CS_lep_bbhj_ratio(i) = g2hjbb_s(i)+g2hjbb_p(i)
+ CS_lep_tautauhj_ratio(i) = g2hjtautau_s(i)+g2hjtautau_p(i)
+
+ g2hjWW(i)= dble( Coupling(H0VV(i,4))
+ & / CouplingSM(H0VV(i,4)) )**2.0D0
+ & + dimag( Coupling(H0VV(i,4))
+ & / CouplingSM(H0VV(i,4)) )**2.0D0
+c Note that this is currently equivalent to
+c g2hjWW(i)= WhTev(i)/WhTevSM(i
+c g2hjWW(i)= qqhTev(i)/qqhTevSM(i)
+c as long as MH>80 GeV and uzint=uzext
+
+ g2hjZZ(i)= dble( Coupling(H0VV(i,3))
+ & / CouplingSM(H0VV(i,3)) )**2.0D0
+ & + dimag( Coupling(H0VV(i,3))
+ & / CouplingSM(H0VV(i,3)) )**2.0D0
+c Note that this is currently equivalent to
+c g2hjZZ(i)= ZhTev(i)/ZhTevSM(i)
+c as long as MH>80 GeV and uzint=uzext
+c It is also equivalent to g2hjWW(i)
+
+ CS_lep_hjZ_ratio(i) = g2hjZZ(i)
+
+ CS_gg_hjZ_ratio(i) = 0.0D0
+ CS_dd_hjZ_ratio(i) = g2hjZZ(i)
+ CS_uu_hjZ_ratio(i) = g2hjZZ(i)
+ CS_ss_hjZ_ratio(i) = g2hjZZ(i)
+ CS_cc_hjZ_ratio(i) = g2hjZZ(i)
+ CS_bb_hjZ_ratio(i) = g2hjZZ(i)
+
+ CS_ud_hjWp_ratio(i) = g2hjZZ(i)
+ CS_cs_hjWp_ratio(i) = g2hjZZ(i)
+ CS_ud_hjWm_ratio(i) = g2hjZZ(i)
+ CS_cs_hjWm_ratio(i) = g2hjZZ(i)
+
+ CS_tev_vbf_ratio(i) = g2hjZZ(i)
+ CS_lhc7_vbf_ratio(i) = g2hjZZ(i)
+ CS_lhc8_vbf_ratio(i) = g2hjZZ(i)
+
+
+ if(tthSM(i).gt.0.0D0)then
+ CS_tev_tthj_ratio(i) = tth(i)/tthSM(i)
+ else
+ CS_tev_tthj_ratio(i) = 0.0D0
+ endif
+
+ CS_lhc7_tthj_ratio(i) = CS_tev_tthj_ratio(i)
+ CS_lhc8_tthj_ratio(i) = CS_tev_tthj_ratio(i)
+
+c tevatron gluon fusion XS is not calculated in FH is MH<90 geV
+ if(Mh(i).gt.90.0001D0)then
+ if(gghSM(i).gt.0.0D0)then
+ CS_gg_hj_ratio(i) = ggh(i)/gghSM(i)
+ else
+ CS_gg_hj_ratio(i) = 0.0D0
+ endif
+ else
+ if(GammaSM(H0VV(i,5)).le.0.0D0)then
+ CS_gg_hj_ratio(i)=0.0D0
+ else
+ CS_gg_hj_ratio(i)= Gamma(H0VV(i,5))/GammaSM(H0VV(i,5))
+ endif
+ endif
+
+ enddo
+
+ norm=GF*sqrt(2.0D0)*MZ**2.0D0
+
+ do j=1,3
+ do i=1,3
+ g2hjhiZ_nHbynH(j,i)= (
+ & dble( Coupling(H0HV(j,i)) )**2.0D0
+ & + dimag( Coupling(H0HV(j,i)) )**2.0D0
+ & )
+ & /norm
+
+ CS_lep_hjhi_ratio_nHbynH(j,i) = g2hjhiZ_nHbynH(j,i)
+
+ BR_hjhihi_nHbynH(j,i)=BR(H0HH(j,i,i))
+ enddo
+ enddo
+
+c higgs->neutralino1 neutralino1 contributes the invisible Higgs decay width
+c when neutralino1 or sneutrino is the LSP
+
+ do i=1,3
+ sneutrino_lspcandidate_number=0
+ invisible_lsp=.True.
+
+c first determine whether lightest sneutrino is lighter than the lightest neutralino
+c
+c sneutrino_lspcandidate_number=0 indicates that lightest neutralino is
+c lighter than all the sneutrinos
+ lspcandidate_mass=MNeu(1)
+ do as=1,3
+ if( MASf(as,1) .lt. lspcandidate_mass )then
+ lspcandidate_mass=MASf(as,1)
+ sneutrino_lspcandidate_number=as
+ endif
+ enddo
+
+ if( MCha(1) .lt. lspcandidate_mass )then
+ invisible_lsp=.False.
+ elseif( MGl .lt. lspcandidate_mass )then
+ invisible_lsp=.False.
+ else
+ do as=1,6
+ do t=2,4
+ if( MASf(as,t) .lt. lspcandidate_mass )then
+ invisible_lsp=.False.
+ endif
+ enddo
+ enddo
+ endif
+
+ if(invisible_lsp)then
+ if(sneutrino_lspcandidate_number.eq.0)then
+ BR_hjinvisible(i) = BR(H0NeuNeu(i,1,1))
+ else
+ BR_hjinvisible(i) = BR(H0SfSf(i,1,1,1,as))
+ endif
+ else
+ BR_hjinvisible(i) = 0.0D0
+ endif
+
+ enddo
+
+* * * * * * * * * * * * * * * * * * * * *
+
+c Charged Higgs input
+
+ Mhplus(1) = MHiggs(4)
+ GammaTotal_Hpj(1) = GammaTot(4)
+ CS_lep_HpjHmj_ratio(1) = 1.0D0
+ BR_tWpb = BR( tBF(1) )
+ BR_tHpjb(1) = BR( tBF(2) )
+ BR_Hpjcs(1) = BR( HpFF(2,2,2) )
+ BR_Hpjcb(1) = BR( HpFF(2,2,3) )
+ BR_Hpjtaunu(1) = BR( HpFF(1,3,3) )
+
+* * * * * * * * * * * * * * * * * * * * *
+c calls to HiggsBounds_neutral_input_part,HiggsBounds_charged_input,
+c which give input to HiggsBounds
+
+ print*,'calling HiggsBounds_neutral_input_part'
+
+C print*, CS_gg_hj_ratio
+C print*, CS_bb_hj_ratio
+C print*,MHiggs
+C print*,BR_hjhihi_nHbynH
+
+
+ call HiggsBounds_neutral_input_part(Mh,GammaTotal_hj,CP_value,
+ & CS_lep_hjZ_ratio,
+ & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio,
+ & CS_lep_hjhi_ratio_nHbynH,
+ & CS_gg_hj_ratio,CS_bb_hj_ratio,
+ & CS_bg_hjb_ratio,
+ & CS_ud_hjWp_ratio,CS_cs_hjWp_ratio,
+ & CS_ud_hjWm_ratio,CS_cs_hjWm_ratio,
+ & CS_gg_hjZ_ratio,
+ & CS_dd_hjZ_ratio,CS_uu_hjZ_ratio,
+ & CS_ss_hjZ_ratio,CS_cc_hjZ_ratio,
+ & CS_bb_hjZ_ratio,
+ & CS_tev_vbf_ratio,CS_tev_tthj_ratio,
+ & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio,
+ & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio,
+ & BR_hjss,BR_hjcc,
+ & BR_hjbb,BR_hjmumu,BR_hjtautau,
+ & BR_hjWW,BR_hjZZ,BR_hjZga, BR_hjgaga,BR_hjgg,
+ & BR_hjinvisible,BR_hjhihi_nHbynH )
+
+ print*,'calling HiggsBounds_charged_input'
+ call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj,
+ & CS_lep_HpjHmj_ratio,
+ & BR_tWpb,BR_tHpjb,
+ & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu)
+
+
+* * * * * * * * * * * * * * * * * * * * *
+c call to run_HiggsBounds
+ call run_HiggsBounds( HBresult,chan, obsratio, ncombined )
+
+ print*,' '
+ print*,'************* HiggsBounds Results **************'
+ print*,' '
+ print*,'Is this parameter point excluded by LEP, Tevatron'
+ print*,'or LHC data?'
+ print*, HBresult, ', where'
+ print*,' 0 = yes, it is excluded'
+ print*,' 1 = no, it has not been excluded'
+ print*,' -1 = invalid parameter set'
+ print*,' '
+ print*,'The process with the highest statistical sensitivity'
+ print*,'is'
+ print*, chan,'(see Key.dat)'
+ print*,'This process has a theoretical rate vs. limit of'
+ print*, obsratio
+ print*,' '
+ print*,'The number of Higgs which have contributed to the'
+ print*,'theoretical rate of this process was'
+ print*, ncombined
+ print*,' '
+ print*,'See HiggsBounds documentation for more information.'
+ print*,'****************************************************'
+ print*,' '
+
+
+* * * * * * * * * * * * * * * * * * * * *
+c deallocates arrays used by HiggsBounds:
+
+ call finish_HiggsBounds
+
+ end
+
+
+************************************************************************
+
+ subroutine setFlags
+ implicit none
+
+ integer mssmpart, fieldren, tanbren, higgsmix, p2approx
+ integer looplevel, runningMT, botResum, tlCplxApprox
+
+c Using default (recommended) values of all FH flags
+ parameter (mssmpart = 4)
+ parameter (fieldren = 0)
+ parameter (tanbren = 0)
+ parameter (higgsmix = 2)
+ parameter (p2approx = 0)
+ parameter (looplevel = 2)
+ parameter (runningMT = 1)
+ parameter (botResum = 1)
+ parameter (tlCplxApprox = 0)
+
+ integer error
+
+ call FHSetFlags(error, mssmpart, fieldren, tanbren,
+ & higgsmix, p2approx, looplevel,
+ & runningMT, botResum, tlCplxApprox)
+ if( error .ne. 0 ) stop
+ end
+
+************************************************************************
+
+ subroutine setPara
+ implicit none
+
+ double precision invAlfa, AlfasMZ, GF
+ double precision ME, MU, MD, MM, MC, MS, ML, MB, MZ, MW
+ double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
+ parameter (invAlfa = -1)
+ parameter (AlfasMZ = -1)
+ parameter (GF = -1)
+ parameter (ME = -1)
+ parameter (MU = -1)
+ parameter (MD = -1)
+ parameter (MM = -1)
+ parameter (MC = -1)
+ parameter (MS = -1)
+ parameter (ML = -1)
+ parameter (MB = -1)
+ parameter (MW = -1)
+ parameter (MZ = -1)
+ parameter (CKMlambda = -1)
+ parameter (CKMA = -1)
+ parameter (CKMrhobar = -1)
+ parameter (CKMetabar = -1)
+
+ double precision MT, TB, MA0, MHp
+ parameter (MT = 173.2)
+ parameter (TB = 5.)
+ parameter (MA0 = 500)
+ parameter (MHp = -1)
+
+ double precision MSusy
+ double precision M3SL, M2SL, M1SL
+ double precision M3SE, M2SE, M1SE
+ double precision M3SQ, M2SQ, M1SQ
+ double precision M3SU, M2SU, M1SU
+ double precision M3SD, M2SD, M1SD
+ parameter (MSusy = 1000)
+ parameter (M3SL = MSusy)
+ parameter (M2SL = M3SL)
+ parameter (M1SL = M2SL)
+ parameter (M3SE = MSusy)
+ parameter (M2SE = M3SE)
+ parameter (M1SE = M2SE)
+ parameter (M3SQ = MSusy)
+ parameter (M2SQ = M3SQ)
+ parameter (M1SQ = M2SQ)
+ parameter (M3SU = MSusy)
+ parameter (M2SU = M3SU)
+ parameter (M1SU = M2SU)
+ parameter (M3SD = MSusy)
+ parameter (M2SD = M3SD)
+ parameter (M1SD = M2SD)
+
+ double complex Atau, At, Ab
+ double complex Amu, Ac, As
+ double complex Ae, Au, Ad
+ parameter (At = 2000)
+ parameter (Ab = At)
+ parameter (Atau = At)
+ parameter (Ac = At)
+ parameter (As = Ab)
+ parameter (Amu = Atau)
+ parameter (Au = Ac)
+ parameter (Ad = As)
+ parameter (Ae = Amu)
+
+ double complex MUE, M_1, M_2, M_3
+ parameter (MUE = 200)
+ parameter (M_1 = 0)
+ parameter (M_2 = 200)
+ parameter (M_3 = 1500)
+
+ double precision Qtau, Qt, Qb
+ parameter (Qtau = 0)
+ parameter (Qt = 0)
+ parameter (Qb = 0)
+
+ double precision scalefactor
+ parameter (scalefactor = 1)
+
+ integer error
+
+ call FHSetSMPara(error,
+ & invAlfa, AlfasMZ, GF,
+ & ME, MU, MD, MM, MC, MS, ML, MB,
+ & MW, MZ,
+ & CKMlambda, CKMA, CKMrhobar, CKMetabar)
+ if( error .ne. 0 ) stop
+
+ call FHSetPara(error, scalefactor,
+ & MT, TB, MA0, MHp,
+ & M3SL, M3SE, M3SQ, M3SU, M3SD,
+ & M2SL, M2SE, M2SQ, M2SU, M2SD,
+ & M1SL, M1SE, M1SQ, M1SU, M1SD,
+ & MUE,
+ & Atau, At, Ab,
+ & Amu, Ac, As,
+ & Ae, Au, Ad,
+ & M_1, M_2, M_3,
+ & Qtau, Qt, Qb)
+ if( error .ne. 0 ) stop
+ end
+
+************************************************************************
+
+ subroutine setSLHA(filename)
+ implicit none
+ character*(*) filename
+
+#include "SLHA.h"
+
+ integer error
+ double complex slhadata(nslhadata)
+
+ call SLHARead(error, slhadata, filename, 1)
+ if( error .ne. 0 ) stop
+
+ call FHSetSLHA(error, slhadata)
+ if( error .ne. 0 ) stop
+ end
+
+
+
Property changes on: trunk/HiggsBounds-5/example_programs/legacy/HBwithFH.F
___________________________________________________________________
Added: svn:executable
## -0,0 +1 ##
+*
\ No newline at end of property
Index: trunk/HiggsBounds-5/example_programs/legacy/HBwithFH_dm.F
===================================================================
--- trunk/HiggsBounds-5/example_programs/legacy/HBwithFH_dm.F (revision 0)
+++ trunk/HiggsBounds-5/example_programs/legacy/HBwithFH_dm.F (revision 533)
@@ -0,0 +1,623 @@
+*********************************************************************
+* HBwithFH_dm
+*
+* Updated demo program for HiggsBounds 4 using MSSM input from
+* FeynHiggs (FH version > 2.9.4 required)
+*
+* This program uses MSSM Higgs mass uncertainties from FH and
+* demonstrates how to obtain constraints from individual Higgs bosons
+*
+*********************************************************************
+
+ program HBwithFH_dm
+ implicit none
+
+ integer error
+
+c used by FHHiggsCorr
+ double precision MHiggs(4)
+ double complex SAeff, UHiggs(3,3), ZHiggs(3,3)
+
+c used by FHSelectUZ:
+ integer uzint, uzext, mfeff
+
+c used by FHCouplings:
+#include "FHCouplings.h"
+ double complex couplings(ncouplings), couplingsms(ncouplingsms)
+ double precision gammas(ngammas), gammasms(ngammasms)
+ integer fast
+
+c used by FHHiggsProd:
+ double precision sqrts, prodxs(nprodxs)
+
+c used by FHGetPara:
+ integer nmfv
+ double precision MSf(2,4,3),MASf(6,4), MCha(2), MNeu(4)
+ double complex USf(2,2,4,3),UASf(6,6,4)
+ double complex UCha(2,2), VCha(2,2), ZNeu(4,4)
+ double complex DeltaMB
+ double precision MGl
+ double precision MHtree(4), SAtree
+
+c used by FHRetrieveSMPara:
+ double precision invAlfa, AlfasMZ, GF
+ double precision ME, MU, MD, MM, MC, MS, ML, MB
+ double precision MW, MZ
+ double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
+
+c used by initialize_HiggsBounds
+ integer nHiggsneut,nHiggsplus
+ parameter (nHiggsneut = 3)
+ parameter (nHiggsplus = 1)
+ character(LEN=5) whichanalyses
+
+c used by HiggsBounds_neutral_input_part
+ double precision Mh(3),GammaTotal_hj(3)
+ integer CP_value(3)
+ double precision CS_lep_hjZ_ratio(3),
+ & CS_lep_bbhj_ratio(3),CS_lep_tautauhj_ratio(3),
+ & CS_lep_hjhi_ratio_nHbynH(3,3),
+ & CS_gg_hj_ratio(3),CS_bb_hj_ratio(3),
+ & CS_bg_hjb_ratio(3),
+ & CS_ud_hjWp_ratio(3),CS_cs_hjWp_ratio(3),
+ & CS_ud_hjWm_ratio(3),CS_cs_hjWm_ratio(3),
+ & CS_gg_hjZ_ratio(3),
+ & CS_dd_hjZ_ratio(3),CS_uu_hjZ_ratio(3),
+ & CS_ss_hjZ_ratio(3),CS_cc_hjZ_ratio(3),
+ & CS_bb_hjZ_ratio(3),
+ & CS_tev_vbf_ratio(3),CS_tev_tthj_ratio(3),
+ & CS_lhc7_vbf_ratio(3),CS_lhc7_tthj_ratio(3),
+ & CS_lhc8_vbf_ratio(3),CS_lhc8_tthj_ratio(3),
+ & BR_hjss(3),BR_hjcc(3),
+ & BR_hjbb(3),BR_hjmumu(3),BR_hjtautau(3),
+ & BR_hjWW(3),BR_hjZZ(3),BR_hjZga(3),
+ & BR_hjgaga(3),BR_hjgg(3),
+ & BR_hjinvisible(3),BR_hjhihi_nHbynH(3,3)
+
+c used by HiggsBounds_charged_input
+ double precision Mhplus(1),GammaTotal_Hpj(1),
+ & CS_lep_HpjHmj_ratio(1),
+ & BR_tWpb,BR_tHpjb(1),
+ & BR_Hpjcs(1),BR_Hpjcb(1),BR_Hpjtaunu(1)
+
+c used by FHUncertainties
+ double precision DeltaMHiggs(4)
+ double complex DeltaSAeff, DeltaUHiggs(3,3), DeltaZHiggs(3,3)
+
+c used by set_mass_uncertainties
+ double precision dmhneut(nHiggsneut)
+ double precision dmhch(nHiggsplus)
+
+c used by run_HiggsBounds
+ integer HBresult(0:4),chan(0:4),ncombined(0:4)
+ double precision obsratio(0:4)
+
+c misc:
+ integer i,j,as,t
+ double precision norm,CW2,Pi
+ double precision
+ & g2hjbb(3),g2hjWW(3),g2hjZZ(3),
+ & g2hjgg(3),g2hjhiZ_nHbynH(3,3)
+ double precision g2hjbb_s(3),g2hjbb_p(3)
+ double precision g2hjtautau_s(3),g2hjtautau_p(3)
+ integer sneutrino_lspcandidate_number
+ logical invisible_lsp
+ double precision lspcandidate_mass
+
+ Pi = 3.1415926535897932384626433832795029D0
+
+* * * * * * * * * * * * * * * * * * * * *
+
+
+c The string 'whichanalyses' determines which subset of experimental
+c results are used. In this example, we've used the option 'LandH',
+c which instructs HiggsBounds to use tables of results
+c from LEP, Tevatron and LHC (i.e. the full set of
+c results supplied with HiggsBounds).
+ whichanalyses='LandH'
+
+c The subroutine initialize_HiggsBounds reads in all necessary
+c tables etc.
+c It must be called before any of the other HiggsBounds subroutines.
+ call initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses)
+
+c If you would like to perform scans over variables, the subroutine
+c initialize_HiggsBounds (and finish_HiggsBounds) should be called
+c outside the do-loops in order to save time.
+
+* * * * * * * * * * * * * * * * * * * * *
+
+c calls to FH subroutines:
+
+c the subroutines setFlags, setPara, setSLHA
+c are also contained in this file
+ call setFlags
+
+* either use setPara to set the parameters directly
+* or use setSLHA to read them from an SLHA file
+ call setPara
+c call setSLHA("tmp.slha")
+
+c Use this for FH < 2.9.5
+c call FHGetPara(error, nmfv, MASf, UASf,
+ call FHGetPara(error, nmfv, MSf, USf, MASf, UASf,
+ & MCha, UCha, VCha, MNeu, ZNeu, DeltaMB, MGl,
+ & MHtree, SAtree)
+ if( error .ne. 0 ) stop
+
+ call FHHiggsCorr(error, MHiggs, SAeff, UHiggs, ZHiggs)
+ if( error .ne. 0 ) stop
+
+ call FHUncertainties(error, DeltaMHiggs, DeltaSAeff,
+ & DeltaUHiggs, DeltaZHiggs)
+ if( error .ne. 0 ) stop
+
+ dMhneut(1) = DeltaMHiggs(1)
+ dMhneut(2) = DeltaMHiggs(2)
+ dMhneut(3) = DeltaMHiggs(3)
+ dMhch(1) = DeltaMHiggs(4)
+
+c NOTE: we are setting uzint=uzext
+ mfeff=1
+ uzint=2
+ uzext=2
+ call FHSelectUZ(error, uzint, uzext, mfeff)
+ if( error .ne. 0 ) stop
+
+ fast=1
+ call FHCouplings(error,
+ & couplings, couplingsms, gammas, gammasms, fast)
+ if( error .ne. 0 ) stop
+
+c We would like FH to calculate LHC cross sections
+ sqrts=8.0D0
+ call FHHiggsProd(error, sqrts, prodxs)
+ if( error .ne. 0 ) stop
+
+ call FHRetrieveSMPara(error,
+ & invAlfa, AlfasMZ, GF,
+ & ME, MU, MD, MM, MC, MS, ML, MB,
+ & MW, MZ,
+ & CKMlambda, CKMA, CKMrhobar, CKMetabar)
+
+* * * * * * * * * * * * * * * * * * * * *
+
+c Set variables needed by HiggsBounds (using results from FeynHiggs).
+c See HiggsBounds documentation for definition of variables used
+c as arguments to HiggsBounds_neutral_input_part and run_HiggsBounds
+c and FeynHiggs documentation for all other variables.
+
+c Note: It is slightly more accurate to use the subroutine HiggsBounds_neutral_input_part
+c rather than the subroutine HiggsBounds_neutral_input_effC because the SM branching ratios
+c used internally in HiggsBounds (from HDecay) are not identical to the SM branching
+c ratios used in FeynHiggs
+
+ do i=1,3
+ Mh(i)=MHiggs(i)
+ GammaTotal_hj(i) = GammaTot(i)
+
+ BR_hjss(i) = BR(H0FF(i,4,2,2))
+ BR_hjcc(i) = BR(H0FF(i,3,2,2))
+ BR_hjbb(i) = BR(H0FF(i,4,3,3))
+ BR_hjmumu(i) = BR(H0FF(i,2,2,2))
+ BR_hjtautau(i) = BR(H0FF(i,2,3,3))
+
+ BR_hjWW(i) = BR(H0VV(i,4))
+ BR_hjgaga(i) = BR(H0VV(i,1))
+ BR_hjZga(i) = BR(H0VV(i,2))
+ BR_hjZZ(i) = BR(H0VV(i,3))
+ BR_hjgg(i) = BR(H0VV(i,5))
+
+ if(GammaSM(H0FF(i,4,3,3)).le.0.0D0)then
+ g2hjbb(i)=0.0D0
+ else
+ g2hjbb(i)=Gamma(H0FF(i,4,3,3))
+ & /GammaSM(H0FF(i,4,3,3))
+ endif
+
+c Note that this is currently equivalent to
+c g2hjbb(i)= bbh(i)/bbhSM(i)
+c g2hjbb(i)= btagbh(i)/btagbhSM(i)
+c as long as MH>80 GeV
+
+ CS_bg_hjb_ratio(i) = g2hjbb(i)
+ CS_bb_hj_ratio(i) = g2hjbb(i)
+
+ g2hjbb_s(i)=(abs(RCoupling(H0FF(i,4,3,3))
+ & /RCouplingSM(H0FF(i,4,3,3))+
+ & LCoupling(H0FF(i,4,3,3))
+ & /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
+ g2hjbb_p(i)=(abs(RCoupling(H0FF(i,4,3,3))
+ & /RCouplingSM(H0FF(i,4,3,3))-
+ & LCoupling(H0FF(i,4,3,3))
+ & /LCouplingSM(H0FF(i,4,3,3)))/2.0D0)**2.0D0
+
+ g2hjtautau_s(i)=(abs(RCoupling(H0FF(i,2,3,3))
+ & /RCouplingSM(H0FF(i,2,3,3))+
+ & LCoupling(H0FF(i,2,3,3))
+ & /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
+ g2hjtautau_p(i)=(abs(RCoupling(H0FF(i,2,3,3))
+ & /RCouplingSM(H0FF(i,2,3,3))-
+ & LCoupling(H0FF(i,2,3,3))
+ & /LCouplingSM(H0FF(i,2,3,3)))/2.0D0)**2.0D0
+
+ if( g2hjbb_p(i).lt.1.0D-10)then
+ CP_value(i) = 1
+ elseif( g2hjbb_s(i).lt.1.0D-10)then
+ CP_value(i) = -1
+ else
+ CP_value(i) = 0
+ endif
+
+ CS_lep_bbhj_ratio(i) = g2hjbb_s(i)+g2hjbb_p(i)
+ CS_lep_tautauhj_ratio(i) = g2hjtautau_s(i)+g2hjtautau_p(i)
+
+ g2hjWW(i)= dble( Coupling(H0VV(i,4))
+ & / CouplingSM(H0VV(i,4)) )**2.0D0
+ & + dimag( Coupling(H0VV(i,4))
+ & / CouplingSM(H0VV(i,4)) )**2.0D0
+c Note that this is currently equivalent to
+c g2hjWW(i)= WhTev(i)/WhTevSM(i
+c g2hjWW(i)= qqhTev(i)/qqhTevSM(i)
+c as long as MH>80 GeV and uzint=uzext
+
+ g2hjZZ(i)= dble( Coupling(H0VV(i,3))
+ & / CouplingSM(H0VV(i,3)) )**2.0D0
+ & + dimag( Coupling(H0VV(i,3))
+ & / CouplingSM(H0VV(i,3)) )**2.0D0
+c Note that this is currently equivalent to
+c g2hjZZ(i)= ZhTev(i)/ZhTevSM(i)
+c as long as MH>80 GeV and uzint=uzext
+c It is also equivalent to g2hjWW(i)
+
+ CS_lep_hjZ_ratio(i) = g2hjZZ(i)
+
+ CS_gg_hjZ_ratio(i) = 0.0D0
+ CS_dd_hjZ_ratio(i) = g2hjZZ(i)
+ CS_uu_hjZ_ratio(i) = g2hjZZ(i)
+ CS_ss_hjZ_ratio(i) = g2hjZZ(i)
+ CS_cc_hjZ_ratio(i) = g2hjZZ(i)
+ CS_bb_hjZ_ratio(i) = g2hjZZ(i)
+
+ CS_ud_hjWp_ratio(i) = g2hjZZ(i)
+ CS_cs_hjWp_ratio(i) = g2hjZZ(i)
+ CS_ud_hjWm_ratio(i) = g2hjZZ(i)
+ CS_cs_hjWm_ratio(i) = g2hjZZ(i)
+
+ CS_tev_vbf_ratio(i) = g2hjZZ(i)
+ CS_lhc7_vbf_ratio(i) = g2hjZZ(i)
+ CS_lhc8_vbf_ratio(i) = g2hjZZ(i)
+
+
+ if(tthSM(i).gt.0.0D0)then
+ CS_tev_tthj_ratio(i) = tth(i)/tthSM(i)
+ else
+ CS_tev_tthj_ratio(i) = 0.0D0
+ endif
+
+ CS_lhc7_tthj_ratio(i) = CS_tev_tthj_ratio(i)
+ CS_lhc8_tthj_ratio(i) = CS_tev_tthj_ratio(i)
+
+c tevatron gluon fusion XS is not calculated in FH is MH<90 geV
+ if(Mh(i).gt.90.0001D0)then
+ if(gghSM(i).gt.0.0D0)then
+ CS_gg_hj_ratio(i) = ggh(i)/gghSM(i)
+ else
+ CS_gg_hj_ratio(i) = 0.0D0
+ endif
+ else
+ if(GammaSM(H0VV(i,5)).le.0.0D0)then
+ CS_gg_hj_ratio(i)=0.0D0
+ else
+ CS_gg_hj_ratio(i)= Gamma(H0VV(i,5))/GammaSM(H0VV(i,5))
+ endif
+ endif
+
+ enddo
+
+ norm=GF*sqrt(2.0D0)*MZ**2.0D0
+
+ do j=1,3
+ do i=1,3
+ g2hjhiZ_nHbynH(j,i)= (
+ & dble( Coupling(H0HV(j,i)) )**2.0D0
+ & + dimag( Coupling(H0HV(j,i)) )**2.0D0
+ & )
+ & /norm
+
+ CS_lep_hjhi_ratio_nHbynH(j,i) = g2hjhiZ_nHbynH(j,i)
+
+ BR_hjhihi_nHbynH(j,i)=BR(H0HH(j,i,i))
+ enddo
+ enddo
+
+c higgs->neutralino1 neutralino1 contributes the invisible Higgs decay width
+c when neutralino1 or sneutrino is the LSP
+
+ do i=1,3
+ sneutrino_lspcandidate_number=0
+ invisible_lsp=.True.
+
+c first determine whether lightest sneutrino is lighter than the lightest neutralino
+c
+c sneutrino_lspcandidate_number=0 indicates that lightest neutralino is
+c lighter than all the sneutrinos
+ lspcandidate_mass=MNeu(1)
+ do as=1,3
+ if( MASf(as,1) .lt. lspcandidate_mass )then
+ lspcandidate_mass=MASf(as,1)
+ sneutrino_lspcandidate_number=as
+ endif
+ enddo
+
+ if( MCha(1) .lt. lspcandidate_mass )then
+ invisible_lsp=.False.
+ elseif( MGl .lt. lspcandidate_mass )then
+ invisible_lsp=.False.
+ else
+ do as=1,6
+ do t=2,4
+ if( MASf(as,t) .lt. lspcandidate_mass )then
+ invisible_lsp=.False.
+ endif
+ enddo
+ enddo
+ endif
+
+ if(invisible_lsp)then
+ if(sneutrino_lspcandidate_number.eq.0)then
+ BR_hjinvisible(i) = BR(H0NeuNeu(i,1,1))
+ else
+ BR_hjinvisible(i) = BR(H0SfSf(i,1,1,1,as))
+ endif
+ else
+ BR_hjinvisible(i) = 0.0D0
+ endif
+ enddo
+
+* * * * * * * * * * * * * * * * * * * * *
+
+c Charged Higgs input
+
+ Mhplus(1) = MHiggs(4)
+ GammaTotal_Hpj(1) = GammaTot(4)
+ CS_lep_HpjHmj_ratio(1) = 1.0D0
+ BR_tWpb = BR( tBF(1) )
+ BR_tHpjb(1) = BR( tBF(2) )
+ BR_Hpjcs(1) = BR( HpFF(2,2,2) )
+ BR_Hpjcb(1) = BR( HpFF(2,2,3) )
+ BR_Hpjtaunu(1) = BR( HpFF(1,3,3) )
+
+* * * * * * * * * * * * * * * * * * * * *
+c calls to HiggsBounds_neutral_input_part,HiggsBounds_charged_input,
+c which give input to HiggsBounds
+
+ print*,'calling HiggsBounds_neutral_input_part'
+
+ call HiggsBounds_neutral_input_part(Mh,GammaTotal_hj,CP_value,
+ & CS_lep_hjZ_ratio,
+ & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio,
+ & CS_lep_hjhi_ratio_nHbynH,
+ & CS_gg_hj_ratio,CS_bb_hj_ratio,
+ & CS_bg_hjb_ratio,
+ & CS_ud_hjWp_ratio,CS_cs_hjWp_ratio,
+ & CS_ud_hjWm_ratio,CS_cs_hjWm_ratio,
+ & CS_gg_hjZ_ratio,
+ & CS_dd_hjZ_ratio,CS_uu_hjZ_ratio,
+ & CS_ss_hjZ_ratio,CS_cc_hjZ_ratio,
+ & CS_bb_hjZ_ratio,
+ & CS_tev_vbf_ratio,CS_tev_tthj_ratio,
+ & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio,
+ & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio,
+ & BR_hjss,BR_hjcc,
+ & BR_hjbb,BR_hjmumu,BR_hjtautau,
+ & BR_hjWW,BR_hjZZ,BR_hjZga, BR_hjgaga,BR_hjgg,
+ & BR_hjinvisible,BR_hjhihi_nHbynH )
+
+ print*,'calling HiggsBounds_charged_input'
+ call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj,
+ & CS_lep_HpjHmj_ratio,
+ & BR_tWpb,BR_tHpjb,
+ & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu)
+
+
+ print*,'calling HiggsBounds_set_mass_uncertainties'
+ call HiggsBounds_set_mass_uncertainties(dmhneut,dmhch)
+
+* * * * * * * * * * * * * * * * * * * * *
+c call to run_HiggsBounds
+ call run_HiggsBounds_full( HBresult,chan, obsratio,ncombined)
+
+ print*,' '
+ print*,'***************** HiggsBounds Results ******************'
+ print*,' '
+ print*,'Is this parameter point excluded by LEP, Tevatron'
+ print*,'or LHC data?'
+ print*, HBresult(0), ', where'
+ print*,' 0 = yes, it is excluded'
+ print*,' 1 = no, it has not been excluded'
+ print*,' -1 = invalid parameter set'
+ print*,' '
+ print*,'The process with the highest statistical sensitivity'
+ print*,'is'
+ print*, chan(0),'(see Key.dat)'
+ print*,'This process has a theoretical rate vs. limit of'
+ print*, obsratio(0)
+ print*,' '
+ print*,'The number of Higgs which have contributed to the'
+ print*,'theoretical rate of this process was'
+ print*, ncombined(0)
+ print*,' '
+ print*,'The results for individual Higgs bosons was:'
+ print*,' id Mass (with unc.) hbres chan obsratio ncomb'
+ do i=1,4
+ write(*,69) i, MHiggs(i), DeltaMHiggs(i), HBresult(i),
+ & chan(i), obsratio(i), ncombined(i)
+ enddo
+ print*, ''
+ print*,'See HiggsBounds documentation for more information.'
+ print*,'**********************************************************'
+ print*,' '
+
+69 format(I5,F10.2,'+-',F3.1 ' GeV',I7,I8,F11.3,I7)
+
+* * * * * * * * * * * * * * * * * * * * *
+c deallocates arrays used by HiggsBounds:
+
+ call finish_HiggsBounds
+
+ end
+
+
+************************************************************************
+
+ subroutine setFlags
+ implicit none
+
+ integer mssmpart, fieldren, tanbren, higgsmix, p2approx
+ integer looplevel, runningMT, botResum, tlCplxApprox
+
+c Using default (recommended) values of all FH flags
+ parameter (mssmpart = 4)
+ parameter (fieldren = 0)
+ parameter (tanbren = 0)
+ parameter (higgsmix = 2)
+ parameter (p2approx = 0)
+ parameter (looplevel = 2)
+ parameter (runningMT = 1)
+ parameter (botResum = 1)
+ parameter (tlCplxApprox = 0)
+
+ integer error
+
+ call FHSetFlags(error, mssmpart, fieldren, tanbren,
+ & higgsmix, p2approx, looplevel,
+ & runningMT, botResum, tlCplxApprox)
+ if( error .ne. 0 ) stop
+ end
+
+************************************************************************
+
+ subroutine setPara
+ implicit none
+
+ double precision invAlfa, AlfasMZ, GF
+ double precision ME, MU, MD, MM, MC, MS, ML, MB, MZ, MW
+ double precision CKMlambda, CKMA, CKMrhobar, CKMetabar
+ parameter (invAlfa = -1)
+ parameter (AlfasMZ = -1)
+ parameter (GF = -1)
+ parameter (ME = -1)
+ parameter (MU = -1)
+ parameter (MD = -1)
+ parameter (MM = -1)
+ parameter (MC = -1)
+ parameter (MS = -1)
+ parameter (ML = -1)
+ parameter (MB = -1)
+ parameter (MW = -1)
+ parameter (MZ = -1)
+ parameter (CKMlambda = -1)
+ parameter (CKMA = -1)
+ parameter (CKMrhobar = -1)
+ parameter (CKMetabar = -1)
+
+ double precision MT, TB, MA0, MHp
+ parameter (MT = 173.2)
+ parameter (TB = 20.)
+ parameter (MA0 = 300)
+ parameter (MHp = -1)
+
+ double precision MSusy
+ double precision M3SL, M2SL, M1SL
+ double precision M3SE, M2SE, M1SE
+ double precision M3SQ, M2SQ, M1SQ
+ double precision M3SU, M2SU, M1SU
+ double precision M3SD, M2SD, M1SD
+ parameter (MSusy = 1000)
+ parameter (M3SL = MSusy)
+ parameter (M2SL = M3SL)
+ parameter (M1SL = M2SL)
+ parameter (M3SE = MSusy)
+ parameter (M2SE = M3SE)
+ parameter (M1SE = M2SE)
+ parameter (M3SQ = MSusy)
+ parameter (M2SQ = M3SQ)
+ parameter (M1SQ = M2SQ)
+ parameter (M3SU = MSusy)
+ parameter (M2SU = M3SU)
+ parameter (M1SU = M2SU)
+ parameter (M3SD = MSusy)
+ parameter (M2SD = M3SD)
+ parameter (M1SD = M2SD)
+
+ double complex Atau, At, Ab
+ double complex Amu, Ac, As
+ double complex Ae, Au, Ad
+ parameter (At = 0)
+ parameter (Ab = At)
+ parameter (Atau = At)
+ parameter (Ac = At)
+ parameter (As = Ab)
+ parameter (Amu = Atau)
+ parameter (Au = Ac)
+ parameter (Ad = As)
+ parameter (Ae = Amu)
+
+ double complex MUE, M_1, M_2, M_3
+ parameter (MUE = 200)
+ parameter (M_1 = 0)
+ parameter (M_2 = 200)
+ parameter (M_3 = 800)
+
+ double precision Qtau, Qt, Qb
+ parameter (Qtau = 0)
+ parameter (Qt = 0)
+ parameter (Qb = 0)
+
+ double precision scalefactor
+ parameter (scalefactor = 1)
+
+ integer error
+
+ call FHSetSMPara(error,
+ & invAlfa, AlfasMZ, GF,
+ & ME, MU, MD, MM, MC, MS, ML, MB,
+ & MW, MZ,
+ & CKMlambda, CKMA, CKMrhobar, CKMetabar)
+ if( error .ne. 0 ) stop
+
+ call FHSetPara(error, scalefactor,
+ & MT, TB, MA0, MHp,
+ & M3SL, M3SE, M3SQ, M3SU, M3SD,
+ & M2SL, M2SE, M2SQ, M2SU, M2SD,
+ & M1SL, M1SE, M1SQ, M1SU, M1SD,
+ & MUE,
+ & Atau, At, Ab,
+ & Amu, Ac, As,
+ & Ae, Au, Ad,
+ & M_1, M_2, M_3,
+ & Qtau, Qt, Qb)
+ if( error .ne. 0 ) stop
+ end
+
+************************************************************************
+
+ subroutine setSLHA(filename)
+ implicit none
+ character*(*) filename
+
+#include "SLHA.h"
+
+ integer error
+ double complex slhadata(nslhadata)
+
+ call SLHARead(error, slhadata, filename, 1)
+ if( error .ne. 0 ) stop
+
+ call FHSetSLHA(error, slhadata)
+ if( error .ne. 0 ) stop
+ end
+
+
+
Index: trunk/HiggsBounds-5/example_programs/legacy/HBwithCPsuperH.input
===================================================================
--- trunk/HiggsBounds-5/example_programs/legacy/HBwithCPsuperH.input (revision 0)
+++ trunk/HiggsBounds-5/example_programs/legacy/HBwithCPsuperH.input (revision 533)
@@ -0,0 +1,72 @@
+128.D0 ! SMPARA( 1) = 1/AEM(MZ)
+0.1185D0 ! SMPARA( 2) = AS(MZ)
+91.187D0 ! SMPARA( 3) = MZ in GeV
+0.23117D0 ! SMPARA( 4) = sin^2\Theta_W
+0.5D-3 ! SMPARA( 5) = m_e in GeV
+0.1065D0 ! SMPARA( 6) = m_mu in GeV
+1.777D0 ! SMPARA( 7) = m_tau in GeV
+0.004D0 ! SMPARA( 8) = m_d (m_t) in GeV
+0.090D0 ! SMPARA( 9) = m_s (m_t) in GeV
+3.155D0 ! SMPARA(10) = m_b (m_t) in GeV
+0.002D0 ! SMPARA(11) = m_u (m_t) in GeV
+0.735D0 ! SMPARA(12) = m_c (m_t) in GeV
+174.3D0 ! SMPARA(13) = m_t^POLE in GeV
+2.118D0 ! SMPARA(14) = Gam_W in GeV
+2.4952D0 ! SMPARA(15) = Gam_Z in GeV
+0.2272D0 ! SMPARA(16) = lambda_CKM
+0.8180D0 ! SMPARA(17) = A_CKM
+0.2210D0 ! SMPARA(18) = rho^bar_CKM
+0.3400D0 ! SMPARA(19) = eta^bar_CKM
+5.0D0 ! SSPARA( 1) = tan\beta
+3.0D2 ! SSPARA( 2) = m_H^\pm^POLE in GeV
+2.0D3 ! SSPARA( 3) = |mu| in GeV
+0.0D2 ! SSPARA( 4) = Phi_mu in Degree
+0.5D2 ! SSPARA( 5) = |M_1| in GeV
+0.0D2 ! SSPARA( 6) = Phi_1 in Degree
+1.0D2 ! SSPARA( 7) = |M_2| in GeV
+0.0D2 ! SSPARA( 8) = Phi_2 in Degree
+1.0D3 ! SSPARA( 9) = |M_3| in GeV
+0.9D2 ! SSPARA(10) = Phi_3 in Degree
+0.5D3 ! SSPARA(11) = m_Q3 in GeV
+0.5D3 ! SSPARA(12) = m_U3 in GeV
+0.5D3 ! SSPARA(13) = m_D3 in GeV
+0.5D3 ! SSPARA(14) = m_L3 in GeV
+0.5D3 ! SSPARA(15) = m_E3 in GeV
+1.0D3 ! SSPARA(16) = |A_t| in GeV
+0.9D2 ! SSPARA(17) = Phi_{A_t} in Degree
+1.0D3 ! SSPARA(18) = |A_b| in GeV
+0.9D2 ! SSPARA(19) = Phi_{A_b} in Degree
+1.0D3 ! SSPARA(20) = |A_tau| in GeV
+0.9D2 ! SSPARA(21) = Phi_{A_tau} in Degree
+1.00D0 ! SSPARA(22) = Hierarchy factor between first 2 and third generations M_Q
+1.00D0 ! SSPARA(23) = Hierarchy factor between first 2 and third generations M_U
+1.00D0 ! SSPARA(24) = Hierarchy factor between first 2 and third generations M_D
+1.00D0 ! SSPARA(25) = Hierarchy factor between first 2 and third generations M_L
+1.00D0 ! SSPARA(26) = Hierarchy factor between first 2 and third generations M_E
+1.0D3 ! SSPARA(27) = |A_e| in GeV
+0.9D2 ! SSPARA(28) = Phi_{A_e} in Degree
+1.0D3 ! SSPARA(29) = |A_mu| in GeV
+0.9D2 ! SSPARA(30) = Phi_{A_mu} in Degree
+1.0D3 ! SSPARA(31) = |A_u| in GeV
+0.9D2 ! SSPARA(32) = Phi_{A_u} in Degree
+1.0D3 ! SSPARA(33) = |A_c| in GeV
+0.9D2 ! SSPARA(34) = Phi_{A_c} in Degree
+1.0D3 ! SSPARA(35) = |A_d| in GeV
+0.9D2 ! SSPARA(36) = Phi_{A_d} in Degree
+1.0D3 ! SSPARA(37) = |A_s| in GeV
+0.9D2 ! SSPARA(38) = Phi_{A_s} in Degree
+0 ! IFLAG_H(1) if 1, print input parameters
+1 ! IFLAG_H(2) if 1, print Higgs sector
+0 ! IFLAG_H(3) if 1, print sferimon sector
+0 ! IFLAG_H(4) if 1, print -ino sector
+0 ! IFLAG_H(5) if 6, print all couplings
+5 ! IFLAG_H(6) if 5, print neutral higgs decay widths and brs
+0 ! IFLAG_H(10) if 0, Include rad. corrections to t and b Yukawa couplings
+0 ! IFLAG_H(11) Pole mass(0) or Eff. Pot. mass(1)
+5 ! IFLAG_H(12) 5 or 0 for full improvement
+0 ! IFLAG_H(13) 1 Not to include the off-diagonal absorptive parts
+0 ! IFLAG_H(14) 1 to print FILLDHPG results
+0 ! IFLAG_H(16) 1 to print FILLBOBS results
+0 ! IFLAG_H(17) 1 to print b -> s gamma details
+0 ! IFLAG_H(18) 1 to print EDM results
+0 ! IFLAG_H(19) 1 to print fllmuon results
Index: trunk/HiggsBounds-5/example_programs/legacy/HBwithCPsuperH.f
===================================================================
--- trunk/HiggsBounds-5/example_programs/legacy/HBwithCPsuperH.f (revision 0)
+++ trunk/HiggsBounds-5/example_programs/legacy/HBwithCPsuperH.f (revision 533)
@@ -0,0 +1,455 @@
+ PROGRAM CPsuperH2
+************************************************************************
+* This is modified version of the cpsuperh2.f file which is supplied with
+* CPsuperH2.2
+* (downloaded 07 July 2010
+* from http://www.hep.man.ac.uk/u/jslee/CPsuperH.html)
+* This file is part of the HiggsBounds distribution.
+************************************************************************
+ IMPLICIT REAL*8(A-H,M,O-Z)
+*
+*-----------------------------------------------------------------------
+*+CDE HC_ COMMON BLOCKS:
+ COMMON /HC_SMPARA/ AEM_H,ASMZ_H,MZ_H,SW_H,ME_H,MMU_H,MTAU_H,MDMT_H
+ . ,MSMT_H,MBMT_H,MUMT_H,MCMT_H,MTPOLE_H,GAMW_H
+ . ,GAMZ_H,EEM_H,ASMT_H,CW_H,TW_H,MW_H,GW_H,GP_H
+ . ,V_H,GF_H,MTMT_H
+*
+ COMMON /HC_RSUSYPARA/ TB_H,CB_H,SB_H,MQ3_H,MU3_H,MD3_H,ML3_H,ME3_H
+*
+ COMPLEX*16 MU_H,M1_H,M2_H,M3_H,AT_H,AB_H,ATAU_H
+ COMMON /HC_CSUSYPARA/ MU_H,M1_H,M2_H,M3_H,AT_H,AB_H,ATAU_H
+*
+*NEW COMMON BLOCKS for V2
+*
+ REAL*8 RAUX_H(999)
+ COMPLEX*16 CAUX_H(999)
+ COMMON /HC_RAUX/ RAUX_H
+ COMMON /HC_CAUX/ CAUX_H
+ DATA NAUX_H/999/
+*-----------------------------------------------------------------------
+*ARRAYS:
+ REAL*8 SMPARA_H(19),SSPARA_H(38)
+ DATA NSMIN/19/
+ DATA NSSIN/38/
+*
+ INTEGER*8 IFLAG_H(100)
+ DATA NFLAG/100/
+*
+ REAL*8 HMASS_H(3),OMIX_H(3,3)
+ REAL*8 STMASS_H(2),SBMASS_H(2),STAUMASS_H(2),SNU3MASS_H
+ REAL*8 MC_H(2),MN_H(4)
+ COMPLEX*16 STMIX_H(2,2),SBMIX_H(2,2),STAUMIX_H(2,2)
+ COMPLEX*16 UL_H(2,2),UR_H(2,2),N_H(4,4)
+*
+ COMPLEX*16 NHC_H(100,3) ! 100 = NCMAX
+ REAL*8 SHC_H(100)
+ COMPLEX*16 CHC_H(100)
+ DATA NCMAX/100/
+*
+ REAL*8 GAMBRN(101,3,3) ! 101 = IFLAG_H(20)+IFLAG_H(21)+1 = NMNH
+* ISMN =ISUSYN = 50
+ REAL*8 GAMBRC(51,3) ! 51 = IFLAG_H(22)+IFLAG_H(23)+1 = NMCH
+* ISMC =ISUSYC = 25
+ DATA NMNH/101/
+ DATA NMCH/51/
+
+*-----------------------------------------------------------------------
+* * * * * * * * * * * * * * * * * * * * * * * *
+* used by initialize_HiggsBounds and run_HiggsBounds_part
+* HB input:
+ integer nHiggsneut,nHiggsplus
+ character*5 whichanalyses
+
+ double precision Mh(3),GammaTotal_hj(3)
+ integer CP_value(3)
+ double precision CS_lep_hjZ_ratio(3),
+ & CS_lep_bbhj_ratio(3),CS_lep_tautauhj_ratio(3),
+ & CS_lep_hjhi_ratio_nHbynH(3,3),
+ & CS_gg_hj_ratio(3),CS_bb_hj_ratio(3),
+ & CS_bg_hjb_ratio(3),
+ & CS_ud_hjWp_ratio(3),CS_cs_hjWp_ratio(3),
+ & CS_ud_hjWm_ratio(3),CS_cs_hjWm_ratio(3),
+ & CS_gg_hjZ_ratio(3),
+ & CS_dd_hjZ_ratio(3),CS_uu_hjZ_ratio(3),
+ & CS_ss_hjZ_ratio(3),CS_cc_hjZ_ratio(3),
+ & CS_bb_hjZ_ratio(3),
+ & CS_tev_vbf_ratio(3),CS_tev_tthj_ratio(3),
+ & CS_lhc7_vbf_ratio(3),CS_lhc7_tthj_ratio(3),
+ & BR_hjss(3),BR_hjcc(3),
+ & BR_hjbb(3),BR_hjmumu(3),BR_hjtautau(3),
+ & BR_hjWW(3),BR_hjZZ(3),BR_hjZga(3),
+ & BR_hjgaga(3),BR_hjgg(3),
+ & BR_hjinvisible(3),BR_hjhihi_nHbynH(3,3)
+
+ double precision Mhplus(1),GammaTotal_Hpj(1),
+ & CS_lep_HpjHmj_ratio(1),
+ & BR_tWpb,BR_tHpjb(1),
+ & BR_Hpjcs(1),BR_Hpjcb(1),BR_Hpjtaunu(1)
+
+* HB output:
+ integer HBresult,chan,ncombined
+ double precision obsratio
+* misc:
+ integer i,j,n
+ double precision betasq
+ double precision
+ & g2hjVV(3),g2hjbb(3),
+ & g2hjhiZ_nHbynH(3,3),
+ & max_hjff_s,max_hjff_p
+ integer sneutrino_lspcandidate_number
+ logical invisible_lsp
+ double precision lspcandidate_mass
+
+c Set the number of Higgs bosons in the MSSM:
+ nHiggsneut=3
+ nHiggsplus=1
+
+c The string 'whichanalyses' determines which subset of experimental
+c results are used.
+c In this example, we've used the option 'onlyL',
+c which instructs HiggsBounds to use tables of results
+c from LEP only (i.e. no Tevatron or LHC results).
+ whichanalyses='onlyL'
+
+c The subroutine initialize_HiggsBounds reads in all necessary
+c tables etc.
+c It must be called before calling the run_HiggsBounds_part subroutine.
+
+ call initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses)
+
+c If you would like to perform scans over variables, the subroutine
+c initialize_HiggsBounds (and finish_HiggsBounds) should be called
+c outside the do-loops in order to save time.
+* * * * * * * * * * * * * * * * * * * * * * * *
+*-----------------------------------------------------------------------
+
+*=======================================================================
+ CALL FILLINIT2(ISKIP_EDM
+ .,NSMIN,NSSIN,SMPARA_H,SSPARA_H,NFLAG,IFLAG_H
+ .,NCMAX,NHC_H,SHC_H,CHC_H,NMNH,GAMBRN,NMCH,GAMBRC)
+*=======================================================================
+*
+* To use other values for the input parameters than those in the "run"
+* file, one can specifiy them here. To scan the phase of, for example,
+* the gluino mass parameter M_3, one can do
+*
+* DO IVAR=0,72
+* SSPARA_H(10)=5.D0*DBLE(IVAR) ! Phi_3
+* print*,'Phi_3 = ',SSPARA_H(10)
+*
+* Don't forget commenting in "ENDDO ! IVAR" at the end of this block.
+*
+*-----------------------------------------------------------------------
+* For the \sqrt{s}-dependent propagators and the Higgs couplings to the
+* gluons and photons, the following should be specified. If not, the
+* value in FILLINIT2 is to be used:
+* RAUX_H(101)= ... ! \sqrt{s} for the subroutine FILLDHPG
+*-----------------------------------------------------------------------
+* One may skip the time-consuming EDM calculations by commenting in the
+* follwing line:
+* ISKIP_EDM=1
+*-----------------------------------------------------------------------
+*
+ CALL FILLCPsuperH2(ISKIP_EDM
+ .,NSMIN,NSSIN,SMPARA_H,SSPARA_H,NFLAG,IFLAG_H
+ .,MCH,HMASS_H,OMIX_H
+ .,STMASS_H,STMIX_H,SBMASS_H,SBMIX_H,STAUMASS_H,STAUMIX_H,SNU3MASS_H
+ .,MC_H,UL_H,UR_H,MN_H,N_H,NCMAX,NHC_H,SHC_H,CHC_H
+ .,NMNH,GAMBRN,NMCH,GAMBRC)
+*
+*Error messages:
+*--a stop or sbottom squared mass is negative
+ IF(IFLAG_H(50).EQ.1) THEN
+ print*,'ERROR! IFLAG_H(50) = ',IFLAG_H(50)
+ IFLAG_H(50)=0
+ GOTO 99
+ ENDIF
+*
+*--the Higgs--boson mass matrix contains a complex or negative eigenvalue
+ IF(IFLAG_H(51).EQ.1) THEN
+ print*,'ERROR! IFLAG_H(51) = ',IFLAG_H(51)
+ IFLAG_H(51)=0
+ GOTO 99
+ ENDIF
+*
+*--the diagonalization of the Higgs mass matrix is not successful
+ IF(IFLAG_H(52).EQ.1) THEN
+ print*,'ERROR! IFLAG_H(52) = ',IFLAG_H(52)
+ IFLAG_H(52)=0
+ GOTO 99
+ ENDIF
+*
+*--the iteration resumming the threshold corrections is not convergent
+ IF(IFLAG_H(54).EQ.1) THEN
+ print*,'ERROR! IFLAG_H(54) = ',IFLAG_H(54)
+ IFLAG_H(54)=0
+ GOTO 99
+ ENDIF
+*
+*--Yukawa coupling has a non--perturbative value: |h_{t,b}| > 2
+ IF(IFLAG_H(55).EQ.1) THEN
+ print*,'ERROR! IFLAG_H(55) = ',IFLAG_H(55)
+ IFLAG_H(55)=0
+ GOTO 99
+ ENDIF
+*
+*-- 1 = a tau sneutrino or a stau squared mass is negative
+*-- 2 = tachyonic stop or sbottom
+*-- 3 = tachyonic scalar strange
+ IF(IFLAG_H(56).GT.0) THEN
+ IF(IFLAG_H(56).EQ.1) print*,'ERROR! IFLAG_H(56) = ',IFLAG_H(56)
+ IF(IFLAG_H(56).EQ.2) print*,'ERROR! IFLAG_H(56) = ',IFLAG_H(56)
+ IF(IFLAG_H(56).EQ.3) print*,'ERROR! IFLAG_H(56) = ',IFLAG_H(56)
+ IFLAG_H(56)=0
+ GOTO 99
+ ENDIF
+*
+*--one of the magnitudes of the complex input parameters is negative
+ IF(IFLAG_H(57).EQ.1) THEN
+ print*,'ERROR! IFLAG_H(57) = ',IFLAG_H(57)
+ IFLAG_H(57)=0
+ GOTO 99
+ ENDIF
+*
+*--the iterative method for the neutral Higgs-boson pole masses fails
+ IF(IFLAG_H(60).EQ.1) THEN
+ print*,'ERROR! IFLAG_H(60) = ',IFLAG_H(60)
+ IFLAG_H(60)=0
+ GOTO 99
+ ENDIF
+*
+*-----------------------------------------------------------------------
+* Users may use the following subroutine for further analysis:
+*
+* CALL AURUN(ISKIP_EDM
+* .,NSMIN,NSSIN,SMPARA_H,SSPARA_H,NFLAG,IFLAG_H
+* .,MCH,HMASS_H,OMIX_H
+* .,STMASS_H,STMIX_H,SBMASS_H,SBMIX_H,STAUMASS_H,STAUMIX_H,SNU3MASS_H
+* .,MC_H,UL_H,UR_H,MN_H,N_H,NCMAX,NHC_H,SHC_H,CHC_H
+* .,NMNH,GAMBRN,NMCH,GAMBRC)
+*-----------------------------------------------------------------------
+
+c ------------------------------------------------------------------
+c Set variables needed by HiggsBounds (using results from CPsuperH).
+c See HiggsBounds documentation for definition of variables used
+c as arguments to run_HiggsBounds_part and CPsuperH
+c documentation for all other variables.
+
+c Note: It is slightly more accurate to use the subroutine run_HiggsBounds_part
+c rather than the subroutine run_HiggsBounds_effC because the SM branching ratios
+c used internally in HiggsBounds (from HDecay) are not identical to the SM branching
+c ratios used in CPsuperH
+
+ do i=1,3
+
+ Mh(i)=HMASS_H(i)
+ GammaTotal_hj(i)=GAMBRN(IFLAG_H(20)+IFLAG_H(21)+1,1,i)
+
+ BR_hjss(i) = GAMBRN(5,3,i)
+ BR_hjcc(i) = GAMBRN(8,3,i)
+ BR_hjbb(i) = GAMBRN(6,3,i)
+ BR_hjmumu(i) = GAMBRN(2,3,i)
+ BR_hjtautau(i) = GAMBRN(3,3,i)
+ BR_hjWW(i) = GAMBRN(10,3,i)
+ BR_hjZZ(i) = GAMBRN(11,3,i)
+ BR_hjgaga(i) = GAMBRN(17,3,i)
+ BR_hjgg(i) = GAMBRN(18,3,i)
+
+ sneutrino_lspcandidate_number=0
+ invisible_lsp=.True.
+ lspcandidate_mass=MN_H(1)
+
+ if( SNU3MASS_H .lt. lspcandidate_mass )then
+ lspcandidate_mass=SNU3MASS_H
+ sneutrino_lspcandidate_number=3
+ endif
+
+ if( MC_H(1) .lt. lspcandidate_mass )then !chargino
+ invisible_lsp=.False.
+ elseif( SSPara_H(9) .lt. lspcandidate_mass )then !gluino
+ invisible_lsp=.False.
+ elseif( STMASS_H(1) .lt. lspcandidate_mass )then !stop
+ invisible_lsp=.False.
+ elseif( SBMASS_H(1) .lt. lspcandidate_mass )then !sbottom
+ invisible_lsp=.False.
+ elseif( STAUMASS_H(1) .lt. lspcandidate_mass )then !stau
+ invisible_lsp=.False.
+ endif
+
+ if(invisible_lsp)then
+ if( sneutrino_lspcandidate_number.eq.0)then
+ BR_hjinvisible(i)=GAMBRN(IFLAG_H(20)+1,3,i)
+ elseif(sneutrino_lspcandidate_number.eq.3)then
+ BR_hjinvisible(i)=GAMBRN(IFLAG_H(20)+27,3,i)
+ endif
+ else
+ BR_hjinvisible(i)=0.0D0
+ endif
+
+
+!this branching ratio is not calculated by CPsuperH, so we set it to zero
+ BR_hjZga(i) = 0.0D0
+
+ g2hjbb(i)=
+ & abs(NHC_H(17,i))**2.0D0
+ & + abs(NHC_H(18,i))**2.0D0
+
+ CS_bg_hjb_ratio(i) = g2hjbb(i)
+ CS_bb_hj_ratio(i) = g2hjbb(i)
+ CS_lep_bbhj_ratio(i) = g2hjbb(i)
+ CS_lep_tautauhj_ratio(i) =
+ & abs(NHC_H(8,i))**2.0D0
+ & + abs(NHC_H(9,i))**2.0D0
+
+ g2hjVV(i)= abs(NHC_H(70,i))**2.0D0
+
+ CS_lep_hjZ_ratio(i) = g2hjVV(i)
+ CS_dd_hjZ_ratio(i) = g2hjVV(i)
+ CS_uu_hjZ_ratio(i) = g2hjVV(i)
+ CS_ss_hjZ_ratio(i) = g2hjVV(i)
+ CS_cc_hjZ_ratio(i) = g2hjVV(i)
+ CS_bb_hjZ_ratio(i) = g2hjVV(i)
+ CS_ud_hjWp_ratio(i) = g2hjVV(i)
+ CS_cs_hjWp_ratio(i) = g2hjVV(i)
+ CS_ud_hjWm_ratio(i) = g2hjVV(i)
+ CS_cs_hjWm_ratio(i) = g2hjVV(i)
+ CS_tev_vbf_ratio(i) = g2hjVV(i)
+ CS_lhc7_vbf_ratio(i) = g2hjVV(i)
+
+ CS_gg_hjZ_ratio(i) = 0.0D0
+
+ CS_tev_tthj_ratio(i) =
+ & abs(NHC_H(26,i))**2.0D0
+ & + abs(NHC_H(27,i))**2.0D0
+ CS_lhc7_tthj_ratio(i) = CS_tev_tthj_ratio(i)
+c ------------------------------------------------------------------
+!note that this is an approximation
+ CS_gg_hj_ratio(i) = GAMBRN(18,1,i)
+ & /( SMBR_Hgg(Mh(i)) *SMGamma_h(Mh(i)) )
+ if(SMGamma_h(Mh(i)).lt.0)then
+ CS_gg_hj_ratio(i) = 0.0D0
+ !it's ok to set this to zero, because Mh(i) is out of range anyway
+ endif
+c ------------------------------------------------------------------
+
+ BR_hjhihi_nHbynH(i,1)=GAMBRN(14,3,i)
+ BR_hjhihi_nHbynH(i,2)=GAMBRN(16,3,i)
+ BR_hjhihi_nHbynH(i,3)=0.0D0
+
+ max_hjff_s=max(abs(NHC_H(14,i))**2.0D0,
+ & abs(NHC_H(23,i))**2.0D0,
+ & abs(NHC_H(17,i))**2.0D0,
+ & abs(NHC_H(26,i))**2.0D0,
+ & abs(NHC_H( 8,i))**2.0D0 )
+
+ max_hjff_p=max(abs(NHC_H(15,i))**2.0D0,
+ & abs(NHC_H(24,i))**2.0D0,
+ & abs(NHC_H(18,i))**2.0D0,
+ & abs(NHC_H(27,i))**2.0D0,
+ & abs(NHC_H( 9,i))**2.0D0 )
+
+ if( max_hjff_p .lt. 1.0D-16 )then !CP even
+ CP_value(i) = 1
+ elseif( max_hjff_s .lt. 1.0D-16 )then !CP odd
+ CP_value(i) = -1
+ else !mixed CP
+ CP_value(i) = 0
+ endif
+
+ enddo
+
+ do j=1,3
+ do i=1,3
+ if(i.lt.j)then
+ g2hjhiZ_nHbynH(j,i)=g2hjVV(6-j-i)
+ g2hjhiZ_nHbynH(i,j)=g2hjhiZ_nHbynH(j,i)
+ else
+ g2hjhiZ_nHbynH(j,i)=0.0D0
+ endif
+ enddo
+ enddo
+
+ do j=1,3
+ do i=1,3
+ CS_lep_hjhi_ratio_nHbynH(j,i) = g2hjhiZ_nHbynH(j,i)
+ enddo
+ enddo
+
+ Mhplus(1)=SSPARA_H(2)
+ GammaTotal_Hpj(1)=GAMBRC(IFLAG_H(22)+IFLAG_H(23)+1,1)
+ CS_lep_HpjHmj_ratio(1)=1.0D0
+ BR_Hpjcs(1) = GAMBRC(5,3)
+ BR_Hpjtaunu(1) = GAMBRC(3,3)
+! this branching ratios is not calculated by CPsuperH, so set to zero:
+ BR_Hpjcb(1) = 0.0D0
+! t-quark branching ratios are not calculated by CPsuperH, so set to zero:
+ BR_tWpb = 0.0D0
+ BR_tHpjb(1) = 0.0D0
+
+* * * * * * * * * * * * * * * * * * * * *
+ call HiggsBounds_neutral_input_part(Mh,GammaTotal_hj,CP_value,
+ & CS_lep_hjZ_ratio,
+ & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio,
+ & CS_lep_hjhi_ratio_nHbynH,
+ & CS_gg_hj_ratio,CS_bb_hj_ratio,
+ & CS_bg_hjb_ratio,
+ & CS_ud_hjWp_ratio,CS_cs_hjWp_ratio,
+ & CS_ud_hjWm_ratio,CS_cs_hjWm_ratio,
+ & CS_gg_hjZ_ratio,
+ & CS_dd_hjZ_ratio,CS_uu_hjZ_ratio,
+ & CS_ss_hjZ_ratio,CS_cc_hjZ_ratio,
+ & CS_bb_hjZ_ratio,
+ & CS_tev_vbf_ratio,CS_tev_tthj_ratio,
+ & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio,
+ & BR_hjss,BR_hjcc,
+ & BR_hjbb,BR_hjmumu,BR_hjtautau,
+ & BR_hjWW,BR_hjZZ,BR_hjZga, BR_hjgaga,BR_hjgg,
+ & BR_hjinvisible,BR_hjhihi_nHbynH )
+
+ call HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj,
+ & CS_lep_HpjHmj_ratio,
+ & BR_tWpb,BR_tHpjb,
+ & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu)
+
+ call run_HiggsBounds( HBresult,chan,
+ & obsratio, ncombined )
+
+
+ write(*,*)
+ write(*,*)'************* HiggsBounds Results **************'
+ write(*,*)
+ write(*,*)'Is this parameter point excluded at 95% CL?'
+ write(*,*) HBresult, ', where'
+ write(*,*)' 0 = yes, it is excluded'
+ write(*,*)' 1 = no, it has not been excluded'
+ write(*,*)' -1 = invalid parameter set'
+ write(*,*)
+ write(*,*)'The process with the highest statistical sensitivity'
+ write(*,*)'is'
+ write(*,*) chan,'(see Key.dat)'
+ write(*,*)'This process has a theoretical rate vs. limit of'
+ write(*,*) obsratio
+ write(*,*)
+ write(*,*)'The number of Higgs bosons which have contributed to'
+ write(*,*)'the theoretical rate of this process was'
+ write(*,*) ncombined
+ write(*,*)
+ write(*,*)'See HiggsBounds documentation for more information.'
+ write(*,*)'****************************************************'
+ write(*,*)
+
+ 99 CONTINUE
+*
+* ENDDO ! IVAR
+*=======================================================================
+
+c ------------------------------------------------------------------
+* * * * * * * * * * * * * * * * * * * * *
+c deallocates arrays used by HiggsBounds:
+
+ call finish_HiggsBounds
+c ------------------------------------------------------------------
+
+ STOP
+ END
Index: trunk/HiggsBounds-5/HiggsBounds_subroutines.F90
===================================================================
--- trunk/HiggsBounds-5/HiggsBounds_subroutines.F90 (revision 532)
+++ trunk/HiggsBounds-5/HiggsBounds_subroutines.F90 (revision 533)
@@ -1,2599 +1,2612 @@
! This file is part of HiggsBounds
! -KW
!************************************************************
subroutine initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses_in)
! This the first Higgsbounds subroutine that should be called
! by the user.
! It calls subroutines to read in the tables of Standard Model data,
! read in the tables of LEP, Tevatron and LHC data,
! set up lists of processes which should be checked against
! the experimental results, allocate arrays etc
! Arguments (input):
! * nHiggs= number of neutral Higgs in the model
! (see subroutine check_nH_nHplus in input.f90 for more details)
! * nHiggsplus= number of singly,positively charged Higgs in the model
! (see subroutine check_nH_nHplus in input.f90 for more details)
! * whichanalyses_in= which combination of experimental results to use
! (see subroutine check_whichanalyses in input.f90 for more details)
!************************************************************
use usefulbits, only : np,Hneut,Hplus,Chineut,Chiplus,debug,inputmethod, &
& theo,whichanalyses,HiggsBounds_info,just_after_run,BRdirectinput,&
& file_id_debug1,file_id_debug2,allocate_if_stats_required,run_HB_classic! ,inputsub
use input, only : setup_input,check_number_of_particles,check_whichanalyses
use S95tables, only : setup_S95tables,S95_t2
use likelihoods, only : setup_likelihoods
use theory_BRfunctions, only : setup_BRSM
use theory_XS_SM_functions, only : setup_XSSM
use channels, only : setup_channels
use output, only : setup_output
#ifdef enableCHISQ
use S95tables_type3, only : clsb_t3,fillt3needs_M2_gt_2M1
#endif
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
!#define FORFITTINO
implicit none
!--------------------------------------input
integer,intent(in) :: nHiggsneut
! integer,intent(in),optional :: nHiggsplus
! character(LEN=5),intent(in),optional :: whichanalyses_in
integer,intent(in) :: nHiggsplus
character(LEN=5),intent(in) :: whichanalyses_in
!-----------------------------------internal
integer :: i
logical :: messages
!-------------------------------------------
! if((.not.present(nHiggsplus)).or.(.not.present(whichanalyses_in)))then
!Actually, this doesn't work as I wanted it to
!because if initialize_HiggsBounds is called in the old way, the program
!usually just crashes..... but leaving it in for now, in case
!some compilers accept it
! call attempting_to_use_an_old_HB_version('init')
! endif
#ifdef FORFITTINO
write(*,*)'The arguments passed to initialize_HiggsBounds are:'
write(*,*)'nHiggsneut=',nHiggsneut
write(*,*)'nHiggsplus=',nHiggsplus
write(*,*)'whichanalyses_in=','~'//trim(adjustl(whichanalyses_in))//'~'
#endif
#ifdef DEBUGGING
debug=.True.
#else
debug=.False.
#endif
messages=debug.or.(inputmethod=='datfile')
! inputmethod='subrout' !('datfile' or 'website' are also possible, but not here)
np(Hneut)=nHiggsneut
np(Hplus)=nHiggsplus
np(Chineut)=0! do not change this without contacting us first!
np(Chiplus)=0! do not change this without contacting us first!
whichanalyses=whichanalyses_in
if(inputmethod=='subrout') then
if(allocated(theo))then
stop 'subroutine HiggsBounds_initialize has already been called once'
endif
if(messages)write(*,*)'doing other preliminary tasks...' ; call flush(6)
call setup_input
! allocate(inputsub( 4 )) !(1)np(Hneut)>0 (2)np(Hplus)>0 (3)np(Chineut)>0 (4)np(Chineut)>0 and np(Chiplus)>0
! | np
! |Hneu Hcha Chineut Chiplus
! | ==0 ==0 ==0 ==0
! inputsub(1)%desc='HiggsBounds_neutral_input_*'
! inputsub(1)%req=req( 0, 1, 1, 1)
! inputsub(2)%desc='HiggsBounds_charged_input'
! inputsub(2)%req=req( 1, 0, 1, 1)
! inputsub(3)%desc='SUSYBounds_neutralinoonly_input'
! inputsub(3)%req=req( 1, 1, 0, 1)
! inputsub(4)%desc='SUSYBounds_neutralinochargino_input'
! inputsub(4)%req=req( 1, 1, 0, 0)
! do i=1,ubound(inputsub,dim=1)
! inputsub(i)%stat=0
! enddo
endif
#ifndef WEBVERSION
if(inputmethod.ne.'datfile') call HiggsBounds_info
if (run_HB_classic.EQV..True.) then
PRINT *, "run_HB_classic=True - HiggsBounds is running in classic mode"
endif
#endif
if(messages)write(*,*)'reading in Standard Model tables...' ; call flush(6)
call setup_BRSM
call setup_XSSM
if(messages)write(*,*)'reading in S95tables...' ; call flush(6)
call setup_S95tables
if(messages)write(*,*)'reading in likelihoods...' ; call flush(6)
call setup_likelihoods
-!if(debug)write(*,*)'doing other preliminary tasks...' ; call flush(6)
-!call setup_input
if(messages)then
open(file_id_debug2,file='debug_predratio.txt')
open(file_id_debug1,file='debug_channels.txt')
endif
if(messages)write(*,*)'sorting out processes to be checked...'; call flush(6)
call setup_channels
if(messages)write(*,*)'preparing output arrays...' ; call flush(6)
call setup_output
#ifdef enableCHISQ
if(allocated(allocate_if_stats_required))then
call fillt3needs_M2_gt_2M1(clsb_t3,S95_t2)
endif
#endif
just_after_run=.False.
BRdirectinput=.False.
! contains
! ! | np
! ! |Hneu Hcha Chineut Chiplus
! ! | ==0 ==0 ==0 ==0
! function req(Hneu,Hcha, Chneu, Chcha)
! integer, intent(in) ::Hneu,Hcha, Chneu, Chcha
! integer :: req
!
! req=1
! if(np(Hneut)==0) req= Hneu * req
! if(np(Hplus)==0) req= Hcha * req
! if(np(Chineut)==0)req= Chneu * req
! if(np(Chiplus)==0)req= Chcha * req
!
! end function req
end subroutine initialize_HiggsBounds
!************************************************************
!************************************************************
! Version of initialize_HiggsBounds which takes an integer as
! the third argument. More useful for library linking to
! non-Fortran codes.
subroutine initialize_HiggsBounds_int(nHn,nHp,flag)
implicit none
integer nHn,nHp,flag
interface
subroutine initialize_HiggsBounds(nHiggsneut, nHiggsplus, whichanalyses_in)
integer,intent(in) :: nHiggsneut
integer,intent(in) :: nHiggsplus
character(LEN=5),intent(in) :: whichanalyses_in
! integer,intent(in),optional :: nHiggsplus
! character(LEN=5),intent(in),optional :: whichanalyses_in
end subroutine initialize_HiggsBounds
end interface
IF (flag.EQ.1) then
call initialize_HiggsBounds(nHn,nHp, "onlyL")
elseif (flag.EQ.2) then
call initialize_HiggsBounds(nHn,nHp, "onlyH")
elseif (flag.EQ.3) then
call initialize_HiggsBounds(nHn,nHp, "LandH")
elseif (flag.EQ.4) then
call initialize_HiggsBounds(nHn,nHp, "onlyP")
else
stop "Illegal value for flag in call to initialize_HB"
endif
end subroutine
!************************************************************
!************************************************************
subroutine attempting_to_use_an_old_HB_version(subroutineid)
use usefulbits, only : vers
character(len=4),intent(in) :: subroutineid
select case(subroutineid)
case('init')
write(*,*)'The subroutine initialize_HiggsBounds has been called with the'
write(*,*)'wrong number of arguments. It should be called as:'
write(*,*)'initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses)'
write(*,*)
write(*,*)'Note that in early versions of HiggsBounds (HB 1.*.*)'
write(*,*)'this subroutine was called as:'
write(*,*)'initialize_HiggsBounds(nHiggsneut,whichanalyses)'
write(*,*)
case('effC','part','hadr')
write(*,*)'The subroutine run_HiggsBounds_'//subroutineid//' has been discontinued in this'
write(*,*)'version of HiggsBounds.'
case default
stop 'wrong input to subroutine attempting_to_use_an_old_HB_version'
end select
write(*,*)'If you have code written for use with HB 1.*.*, you have two choices:'
write(*,*)
write(*,*)' (1) You can edit your code, such that it works with this'
write(*,*)' version of HiggsBounds (HB'//trim(adjustl(vers))//').'
write(*,*)' This has the advantage that you can test your model against many, many'
write(*,*)' more Higgs search limits , including charged Higgs search limits.'
write(*,*)' See the updated manual for more information.'
write(*,*)
write(*,*)' (2) You can download the most recent HB 1.*.* from the HiggsBounds'
write(*,*)' website. This contains the LEP Higgs search limits which are'
write(*,*)' generally the most useful when constraining new physics models.'
write(*,*)' We will continue to support this code.'
stop 'Incorrect call to a HiggsBounds subroutine.'
end subroutine attempting_to_use_an_old_HB_version
!************************************************************
subroutine HiggsBounds_input_SLHA(infile)
! This subroutine can be called by the user after subroutine initialize_HiggsBounds
! has been called.
! Arguments (input): SLHA filename
!************************************************************
use usefulbits, only : whichinput,infile1,theo,g2,effC,just_after_run, &
& np,Hneut,Hplus! ,inputsub
use extra_bits_for_SLHA
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
implicit none
!----------------------------------------input
character(len=300),intent(in) :: infile
!--------------------------------------internal
integer :: n
!----------------------------------------------
whichinput='SLHA'
! if(np(Hneut).gt.0)inputsub(Hneut)%stat=inputsub(Hneut)%stat+1
! if(np(Hplus).gt.0)inputsub(Hplus)%stat=inputsub(Hplus)%stat+1
! note: can't be used for charginos or neutralinos yet
n=1
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
infile1=infile
call getSLHAdata(theo(n),effC(n),infile1)
just_after_run=.False.
end subroutine HiggsBounds_input_SLHA
-!************************************************************
-subroutine HiggsBounds_neutral_input_effC(Mh,GammaTotal_hj, &
- & g2hjss_s,g2hjss_p,g2hjcc_s,g2hjcc_p, &
- & g2hjbb_s,g2hjbb_p,g2hjtoptop_s,g2hjtoptop_p, &
- & g2hjmumu_s,g2hjmumu_p, &
- & g2hjtautau_s,g2hjtautau_p, &
- & g2hjWW,g2hjZZ,g2hjZga, &
- & g2hjgaga,g2hjgg,g2hjggZ,g2hjhiZ_nHbynH, &
- & BR_hjinvisible,BR_hjhihi_nHbynH )
-! This subroutine can be called by the user after subroutine initialize_HiggsBounds
-! has been called.
-! Arguments (input): theoretical predictions (see manual for definitions)
+!************************************************************
+!
+! HB5 GENERAL INPUT ROUTINES
+!
+!************************************************************
+subroutine HiggsBounds_neutral_input_properties(Mh,GammaTotal_hj,CP_value)
+!************************************************************
+ use usefulbits, only : theo,np,Hneut,just_after_run!,inputsub
+
+#if defined(NAGf90Fortran)
+ use F90_UNIX_IO, only : flush
+#endif
+
+ implicit none
+ !----------------------------------------input
+ double precision,intent(in) :: Mh(np(Hneut)),GammaTotal_hj(np(Hneut)),CP_value(np(Hneut))
+ !--------------------------------------internal
+ integer :: n
+! integer :: subtype
+ !----------------------------------------------
+! subtype=1
+ n=1
+! inputsub(subtype)%stat=inputsub(subtype)%stat+1
+
+ if(.not.allocated(theo))then
+ stop 'subroutine HiggsBounds_initialize must be called first'
+ endif
+
+ if(np(Hneut).eq.0)then
+ write(*,*)'subroutine HiggsBounds_neutral_input_mass_width should'
+ write(*,*)'only be called if np(Hneut)>0'
+ stop 'error in subroutine HiggsBounds_neutral_input_mass_width'
+ endif
+
+ theo(n)%particle(Hneut)%M = Mh
+ theo(n)%particle(Hneut)%Mc = Mh
+ theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
+ theo(n)%CP_value = CP_value
+
+ just_after_run=.False.
+
+end subroutine HiggsBounds_neutral_input_properties
+!************************************************************
+subroutine HiggsBounds_neutral_input_effC( &
+ & ghjss_s,ghjss_p,ghjcc_s,ghjcc_p, &
+ & ghjbb_s,ghjbb_p,ghjtt_s,ghjtt_p, &
+ & ghjmumu_s,ghjmumu_p, &
+ & ghjtautau_s,ghjtautau_p, &
+ & ghjWW,ghjZZ,ghjZga, &
+ & ghjgaga,ghjgg,ghjhiZ)!, &
+! & BR_hjinvisible,BR_hjhihi_nHbynH)
+! New neutral Higgs effective coupling input routine.
+! BR's are set separately.
!************************************************************
- use usefulbits, only : theo,np,Hneut,g2,whichinput,just_after_run!,inputsub
+ use usefulbits, only : theo,np,Hneut,effC,whichinput,just_after_run!,inputsub
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
implicit none
!----------------------------------------input
- double precision,intent(in) :: Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) ), &
- & g2hjss_s( np(Hneut) ),g2hjss_p( np(Hneut) ),g2hjcc_s( np(Hneut) ),g2hjcc_p( np(Hneut) ), &
- & g2hjbb_s( np(Hneut) ),g2hjbb_p( np(Hneut) ),g2hjtoptop_s( np(Hneut) ),g2hjtoptop_p( np(Hneut) ),&
- & g2hjmumu_s( np(Hneut) ),g2hjmumu_p( np(Hneut) ), &
- & g2hjtautau_s( np(Hneut) ),g2hjtautau_p( np(Hneut) ), &
- & g2hjWW( np(Hneut) ),g2hjZZ( np(Hneut) ),g2hjZga( np(Hneut) ), &
- & g2hjgaga( np(Hneut) ),g2hjgg( np(Hneut) ),g2hjggZ( np(Hneut) ),g2hjhiZ_nHbynH(np(Hneut),np(Hneut)),&
- & BR_hjinvisible( np(Hneut) ),BR_hjhihi_nHbynH(np(Hneut),np(Hneut))
+ double precision,intent(in) :: &!Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) ),&
+ & ghjss_s( np(Hneut) ),ghjss_p( np(Hneut) ), &
+ & ghjcc_s( np(Hneut) ),ghjcc_p( np(Hneut) ), &
+ & ghjbb_s( np(Hneut) ),ghjbb_p( np(Hneut) ), &
+ & ghjtt_s( np(Hneut) ),ghjtt_p( np(Hneut) ), &
+ & ghjmumu_s( np(Hneut) ),ghjmumu_p( np(Hneut) ), &
+ & ghjtautau_s( np(Hneut) ),ghjtautau_p( np(Hneut) ), &
+ & ghjWW( np(Hneut) ),ghjZZ( np(Hneut) ),ghjZga( np(Hneut) ), &
+ & ghjgaga( np(Hneut) ),ghjgg( np(Hneut) ), &
+ & ghjhiZ(np(Hneut),np(Hneut))
+! & BR_hjinvisible( np(Hneut) ),BR_hjhihi_nHbynH(np(Hneut),np(Hneut))
!--------------------------------------internal
integer :: n
! integer :: subtype
!----------------------------------------------
whichinput='effC'
- ! subtype=1
- n=1
+! subtype=1
+ n=1
! inputsub(subtype)%stat=inputsub(subtype)%stat+1
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hneut).eq.0)then
write(*,*)'subroutine HiggsBounds_neutral_input_effC should'
write(*,*)'only be called if np(Hneut)>0'
stop 'error in subroutine HiggsBounds_neutral_input_effC'
endif
- theo(n)%particle(Hneut)%M = Mh
- theo(n)%particle(Hneut)%Mc = Mh
- theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
+! theo(n)%particle(Hneut)%M = Mh
+! theo(n)%particle(Hneut)%Mc = Mh
+! theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
- g2(n)%hjss_s = g2hjss_s
- g2(n)%hjss_p = g2hjss_p
- g2(n)%hjcc_s = g2hjcc_s
- g2(n)%hjcc_p = g2hjcc_p
- g2(n)%hjbb_s = g2hjbb_s
- g2(n)%hjbb_p = g2hjbb_p
- g2(n)%hjtoptop_s = g2hjtoptop_s
- g2(n)%hjtoptop_p = g2hjtoptop_p
- g2(n)%hjmumu_s = g2hjmumu_s
- g2(n)%hjmumu_p = g2hjmumu_p
- g2(n)%hjtautau_s = g2hjtautau_s
- g2(n)%hjtautau_p = g2hjtautau_p
+ effC(n)%hjss_s = ghjss_s
+ effC(n)%hjss_p = ghjss_p
+ effC(n)%hjcc_s = ghjcc_s
+ effC(n)%hjcc_p = ghjcc_p
+ effC(n)%hjbb_s = ghjbb_s
+ effC(n)%hjbb_p = ghjbb_p
+ effC(n)%hjtt_s = ghjtt_s
+ effC(n)%hjtt_p = ghjtt_p
+ effC(n)%hjmumu_s = ghjmumu_s
+ effC(n)%hjmumu_p = ghjmumu_p
+ effC(n)%hjtautau_s = ghjtautau_s
+ effC(n)%hjtautau_p = ghjtautau_p
- g2(n)%hjWW = g2hjWW
- g2(n)%hjZZ = g2hjZZ
- g2(n)%hjZga = g2hjZga
- g2(n)%hjgaga = g2hjgaga
- g2(n)%hjgg = g2hjgg
- g2(n)%hjggZ = g2hjggZ
+ effC(n)%hjWW = ghjWW
+ effC(n)%hjZZ = ghjZZ
+ effC(n)%hjZga = ghjZga
+ effC(n)%hjgaga = ghjgaga
+ effC(n)%hjgg = ghjgg
+! g2(n)%hjggZ = g2hjggZ
- g2(n)%hjhiZ = g2hjhiZ_nHbynH
+ effC(n)%hjhiZ = ghjhiZ
- theo(n)%BR_hjinvisible = BR_hjinvisible
- theo(n)%BR_hjhihi = BR_hjhihi_nHbynH
+! theo(n)%BR_hjinvisible = BR_hjinvisible
+! theo(n)%BR_hjhihi = BR_hjhihi_nHbynH
just_after_run=.False.
end subroutine HiggsBounds_neutral_input_effC
!************************************************************
-subroutine HiggsBounds_neutral_input_part(Mh,GammaTotal_hj,CP_value, &
- & CS_lep_hjZ_ratio, &
- & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio, &
- & CS_lep_hjhi_ratio_nHbynH, &
- & CS_gg_hj_ratio,CS_bb_hj_ratio, &
- & CS_bg_hjb_ratio, &
- & CS_ud_hjWp_ratio,CS_cs_hjWp_ratio, &
- & CS_ud_hjWm_ratio,CS_cs_hjWm_ratio, &
- & CS_gg_hjZ_ratio, &
- & CS_dd_hjZ_ratio,CS_uu_hjZ_ratio, &
- & CS_ss_hjZ_ratio,CS_cc_hjZ_ratio, &
- & CS_bb_hjZ_ratio, &
- & CS_tev_vbf_ratio,CS_tev_tthj_ratio, &
- & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio, &
- & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio, &
- & BR_hjss,BR_hjcc, &
- & BR_hjbb,BR_hjmumu,BR_hjtautau, &
- & BR_hjWW,BR_hjZZ,BR_hjZga, BR_hjgaga,BR_hjgg, &
- & BR_hjinvisible,BR_hjhihi_nHbynH )
-! This subroutine can be called by the user after subroutine initialize_HiggsBounds
-! has been called.
-! (see manual for full description)
+subroutine HiggsBounds_neutral_input_SMBR(BR_hjss,BR_hjcc,BR_hjbb, &
+ & BR_hjtt,BR_hjmumu, &
+ & BR_hjtautau,BR_hjWW, &
+ & BR_hjZZ,BR_hjZga,BR_hjgaga, &
+ & BR_hjgg)
+! Input for the SM branching ratios
!************************************************************
- use usefulbits, only : theo,np,Hneut,partR,whichinput,just_after_run!,inputsub
+ use usefulbits, only : theo,np,Hneut,whichinput,just_after_run,BRdirectinput
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
implicit none
!----------------------------------------input
- double precision,intent(in) :: Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) )
- integer,intent(in) ::CP_value( np(Hneut) )
- double precision,intent(in) :: CS_lep_hjZ_ratio( np(Hneut) ), &
- & CS_lep_bbhj_ratio( np(Hneut) ),CS_lep_tautauhj_ratio( np(Hneut) ), &
- & CS_lep_hjhi_ratio_nHbynH(np(Hneut),np(Hneut)), &
- & CS_gg_hj_ratio( np(Hneut) ),CS_bb_hj_ratio( np(Hneut) ), &
- & CS_bg_hjb_ratio( np(Hneut) ), &
- & CS_ud_hjWp_ratio( np(Hneut) ),CS_cs_hjWp_ratio( np(Hneut) ), &
- & CS_ud_hjWm_ratio( np(Hneut) ),CS_cs_hjWm_ratio( np(Hneut) ), &
- & CS_gg_hjZ_ratio( np(Hneut) ), &
- & CS_dd_hjZ_ratio( np(Hneut) ),CS_uu_hjZ_ratio( np(Hneut) ), &
- & CS_ss_hjZ_ratio( np(Hneut) ),CS_cc_hjZ_ratio( np(Hneut) ), &
- & CS_bb_hjZ_ratio( np(Hneut) ), &
- & CS_tev_vbf_ratio( np(Hneut) ),CS_tev_tthj_ratio( np(Hneut) ), &
- & CS_lhc7_vbf_ratio( np(Hneut) ),CS_lhc7_tthj_ratio( np(Hneut) ), &
- & CS_lhc8_vbf_ratio( np(Hneut) ),CS_lhc8_tthj_ratio( np(Hneut) ), &
- & BR_hjss( np(Hneut) ),BR_hjcc( np(Hneut) ), &
- & BR_hjbb( np(Hneut) ),BR_hjmumu( np(Hneut) ),BR_hjtautau( np(Hneut) ), &
- & BR_hjWW( np(Hneut) ),BR_hjZZ( np(Hneut) ),BR_hjZga( np(Hneut) ), &
- & BR_hjgaga( np(Hneut) ),BR_hjgg( np(Hneut) ), &
- & BR_hjinvisible( np(Hneut) ),BR_hjhihi_nHbynH(np(Hneut),np(Hneut))
- !---------------------------------------internal
+ double precision,intent(in) :: BR_hjss( np(Hneut) ),BR_hjcc( np(Hneut) ), &
+ & BR_hjbb( np(Hneut) ),BR_hjtt( np(Hneut) ), &
+ & BR_hjmumu( np(Hneut) ),BR_hjtautau( np(Hneut) ), &
+ & BR_hjWW( np(Hneut) ),BR_hjZZ( np(Hneut) ), &
+ & BR_hjZga( np(Hneut) ),BR_hjgaga( np(Hneut) ), &
+ & BR_hjgg( np(Hneut) )
+ !-------------------------------------internal
integer :: n
-! integer :: subtype
- !-----------------------------------------------
+ !---------------------------------------------
- whichinput='part'
-! subtype=1
n=1
-! inputsub(subtype)%stat=inputsub(subtype)%stat+1
-
+
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hneut).eq.0)then
- write(*,*)'subroutine HiggsBounds_neutral_input_part should'
+ write(*,*)'subroutine HiggsBounds_neutral_input_SMBR should'
write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HiggsBounds_neutral_input_part'
+ stop 'error in subroutine HiggsBounds_neutral_input_SMBR'
endif
+!
+ theo(n)%BR_hjss = BR_hjss
+ theo(n)%BR_hjcc = BR_hjcc
+ theo(n)%BR_hjbb = BR_hjbb
+ theo(n)%BR_hjtt = BR_hjtt
+ theo(n)%BR_hjmumu = BR_hjmumu
+ theo(n)%BR_hjtautau = BR_hjtautau
+ theo(n)%BR_hjWW = BR_hjWW
+ theo(n)%BR_hjZZ = BR_hjZZ
+ theo(n)%BR_hjZga = BR_hjZga
+ theo(n)%BR_hjgaga = BR_hjgaga
+ theo(n)%BR_hjgg = BR_hjgg
- theo(n)%particle(Hneut)%M = Mh
- theo(n)%particle(Hneut)%Mc = Mh
- theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
- theo(n)%CP_value = CP_value
- theo(n)%lep%XS_hjZ_ratio = CS_lep_hjZ_ratio
- theo(n)%lep%XS_bbhj_ratio = CS_lep_bbhj_ratio
- theo(n)%lep%XS_tautauhj_ratio = CS_lep_tautauhj_ratio
- theo(n)%lep%XS_hjhi_ratio = CS_lep_hjhi_ratio_nHbynH
- partR(n)%gg_hj = CS_gg_hj_ratio
- partR(n)%qq_hj(5,:) = CS_bb_hj_ratio
- partR(n)%bg_hjb = CS_bg_hjb_ratio
- partR(n)%qq_hjWp(1,:) = CS_ud_hjWp_ratio
- partR(n)%qq_hjWp(2,:) = CS_cs_hjWp_ratio
- partR(n)%qq_hjWm(1,:) = CS_ud_hjWm_ratio
- partR(n)%qq_hjWm(2,:) = CS_cs_hjWm_ratio
- partR(n)%gg_hjZ(:) = CS_gg_hjZ_ratio
- partR(n)%qq_hjZ(1,:) = CS_dd_hjZ_ratio
- partR(n)%qq_hjZ(2,:) = CS_uu_hjZ_ratio
- partR(n)%qq_hjZ(3,:) = CS_ss_hjZ_ratio
- partR(n)%qq_hjZ(4,:) = CS_cc_hjZ_ratio
- partR(n)%qq_hjZ(5,:) = CS_bb_hjZ_ratio
- theo(n)%tev%XS_vbf_ratio = CS_tev_vbf_ratio
- theo(n)%tev%XS_tthj_ratio = CS_tev_tthj_ratio
- theo(n)%lhc7%XS_vbf_ratio = CS_lhc7_vbf_ratio
- theo(n)%lhc7%XS_tthj_ratio= CS_lhc7_tthj_ratio
- theo(n)%lhc8%XS_vbf_ratio = CS_lhc8_vbf_ratio
- theo(n)%lhc8%XS_tthj_ratio= CS_lhc8_tthj_ratio
- theo(n)%BR_hjss = BR_hjss
- theo(n)%BR_hjcc = BR_hjcc
- theo(n)%BR_hjbb = BR_hjbb
- theo(n)%BR_hjmumu = BR_hjmumu
- theo(n)%BR_hjtautau = BR_hjtautau
- theo(n)%BR_hjWW = BR_hjWW
- theo(n)%BR_hjZZ = BR_hjZZ
- theo(n)%BR_hjZga = BR_hjZga
- theo(n)%BR_hjgaga = BR_hjgaga
- theo(n)%BR_hjgg = BR_hjgg
- theo(n)%BR_hjinvisible = BR_hjinvisible
- theo(n)%BR_hjhihi = BR_hjhihi_nHbynH
+ just_after_run=.False.
+ BRdirectinput=.True.
+
+end subroutine HiggsBounds_neutral_input_SMBR
+!************************************************************
+subroutine HiggsBounds_neutral_input_nonSMBR(BR_hjinvisible,BR_hkhjhi,BR_hjhiZ,&
+& BR_hjemu,BR_hjetau,BR_hjmutau,BR_hjHpiW)
+! Input for the non-SM branching ratios
+!************************************************************
+ use usefulbits, only : theo,np,Hneut,Hplus,whichinput,just_after_run!,inputsub
+
+#if defined(NAGf90Fortran)
+ use F90_UNIX_IO, only : flush
+#endif
+
+ implicit none
+
+ !----------------------------------------input
+ double precision,intent(in) :: BR_hjinvisible( np(Hneut) ), &
+ & BR_hkhjhi(np(Hneut),np(Hneut),np(Hneut)), &
+ & BR_hjhiZ(np(Hneut),np(Hneut)), &
+ & BR_hjemu(np(Hneut)),&
+ & BR_hjetau(np(Hneut)),&
+ & BR_hjmutau(np(Hneut))
+ double precision,intent(in) :: BR_hjHpiW(np(Hneut),np(Hplus))
+ !--------------------------------------internal
+ integer :: n
+ n=1
+
+ if(.not.allocated(theo))then
+ stop 'subroutine HiggsBounds_initialize must be called first'
+ endif
+
+ if(np(Hneut).eq.0)then
+ write(*,*)'subroutine HiggsBounds_neutral_input_nonSMBR should'
+ write(*,*)'only be called if np(Hneut)>0'
+ stop 'error in subroutine HiggsBounds_neutral_input_nonSMBR'
+ endif
+
+ theo(n)%BR_hjinvisible = BR_hjinvisible
+ theo(n)%BR_hkhjhi = BR_hkhjhi
+ theo(n)%BR_hjhiZ = BR_hjhiZ
+ theo(n)%BR_hjemu = BR_hjemu
+ theo(n)%BR_hjetau = BR_hjetau
+ theo(n)%BR_hjmutau = BR_hjmutau
+! write(*,*) "HiggsBounds_neutral_input_nonSMBR"
+! write(*,*) theo(n)%BR_hjHpiW
+
+! if(present(BR_hjHpiW)) then
+ theo(n)%BR_hjHpiW = BR_hjHpiW
+! endif
+
+
just_after_run=.False.
-end subroutine HiggsBounds_neutral_input_part
+end subroutine HiggsBounds_neutral_input_nonSMBR
!************************************************************
-subroutine HiggsBounds_neutral_input_hadr(Mh,GammaTotal_hj,CP_value, &
- & CS_lep_hjZ_ratio, &
- & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio, &
- & CS_lep_hjhi_ratio_nHbynH, &
- & CS_tev_hj_ratio ,CS_tev_hjb_ratio, &
- & CS_tev_hjW_ratio,CS_tev_hjZ_ratio, &
- & CS_tev_vbf_ratio,CS_tev_tthj_ratio, &
- & CS_lhc7_hj_ratio ,CS_lhc7_hjb_ratio, &
- & CS_lhc7_hjW_ratio,CS_lhc7_hjZ_ratio, &
- & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio, &
- & CS_lhc8_hj_ratio ,CS_lhc8_hjb_ratio, &
- & CS_lhc8_hjW_ratio,CS_lhc8_hjZ_ratio, &
- & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio, &
- & BR_hjss,BR_hjcc, &
- & BR_hjbb, &
- & BR_hjmumu, &
- & BR_hjtautau, &
- & BR_hjWW,BR_hjZZ,BR_hjZga,BR_hjgaga, &
- & BR_hjgg, BR_hjinvisible, &
- & BR_hjhihi_nHbynH )
-! This subroutine can be called by the user after subroutine initialize_HiggsBounds
-! has been called.
-! (see manual for full description)
+subroutine HiggsBounds_neutral_input_hadr(collider,CS_hj_ratio, &
+ & CS_gg_hj_ratio,CS_bb_hj_ratio, &
+ & CS_hjW_ratio,CS_hjZ_ratio, &
+ & CS_vbf_ratio,CS_tthj_ratio, &
+ & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
+ & CS_hjhi)
!************************************************************
- use usefulbits, only : theo,np,Hneut,whichinput,just_after_run!,inputsub
+ use usefulbits, only : theo,np,Hneut,whichinput,just_after_run,hadroncolliderdataset
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
implicit none
- !----------------------------------------input
- double precision,intent(in) :: Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) )
- integer,intent(in) :: CP_value( np(Hneut) )
- double precision,intent(in) :: CS_lep_hjZ_ratio( np(Hneut) ), &
- & CS_lep_bbhj_ratio( np(Hneut) ),CS_lep_tautauhj_ratio( np(Hneut) ), &
- & CS_lep_hjhi_ratio_nHbynH(np(Hneut),np(Hneut)), &
- & CS_tev_hj_ratio( np(Hneut) ) ,CS_tev_hjb_ratio( np(Hneut) ), &
- & CS_tev_hjW_ratio( np(Hneut) ) ,CS_tev_hjZ_ratio( np(Hneut) ), &
- & CS_tev_vbf_ratio( np(Hneut) ) ,CS_tev_tthj_ratio( np(Hneut)), &
- & CS_lhc7_hj_ratio( np(Hneut) ),CS_lhc7_hjb_ratio( np(Hneut) ), &
- & CS_lhc7_hjW_ratio( np(Hneut) ),CS_lhc7_hjZ_ratio( np(Hneut) ), &
- & CS_lhc7_vbf_ratio( np(Hneut) ),CS_lhc7_tthj_ratio( np(Hneut)), &
- & CS_lhc8_hj_ratio( np(Hneut) ),CS_lhc8_hjb_ratio( np(Hneut) ), &
- & CS_lhc8_hjW_ratio( np(Hneut) ),CS_lhc8_hjZ_ratio( np(Hneut) ), &
- & CS_lhc8_vbf_ratio( np(Hneut) ),CS_lhc8_tthj_ratio( np(Hneut)), &
- & BR_hjss( np(Hneut) ),BR_hjcc( np(Hneut) ), &
- & BR_hjbb( np(Hneut) ), &
- & BR_hjmumu( np(Hneut) ),BR_hjtautau( np(Hneut) ), &
- & BR_hjWW( np(Hneut) ),BR_hjZZ( np(Hneut) ), &
- & BR_hjZga( np(Hneut) ),BR_hjgaga( np(Hneut) ), &
- & BR_hjgg( np(Hneut) ), BR_hjinvisible( np(Hneut) ), &
- & BR_hjhihi_nHbynH(np(Hneut),np(Hneut))
+ double precision,intent(in) :: CS_hj_ratio( np(Hneut) ), &
+ & CS_gg_hj_ratio( np(Hneut) ),CS_bb_hj_ratio( np(Hneut) ), &
+ & CS_hjW_ratio( np(Hneut) ) ,CS_hjZ_ratio( np(Hneut) ), &
+ & CS_vbf_ratio( np(Hneut) ) ,CS_tthj_ratio( np(Hneut) ), &
+ & CS_thj_tchan_ratio( np(Hneut) ),CS_thj_schan_ratio( np(Hneut) ), &
+ & CS_hjhi( np(Hneut), np(Hneut) )
+ integer, intent(in) :: collider
!-------------------------------------internal
integer :: n
-! integer :: subtype
+! type(hadroncolliderdataset) :: dataset
!---------------------------------------------
-
whichinput='hadr'
-! subtype=1
n=1
-! inputsub(subtype)%stat=inputsub(subtype)%stat+1
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hneut).eq.0)then
write(*,*)'subroutine HiggsBounds_neutral_input_hadr should'
write(*,*)'only be called if np(Hneut)>0'
stop 'error in subroutine HiggsBounds_neutral_input_hadr'
endif
-! write(*,*) "DEBUG HB: before hadronic input. Mass is ",theo(n)%particle(Hneut)%M
+ select case(collider)
+ case(2)
+ call set_input(theo(n)%tev,CS_hj_ratio, &
+ & CS_gg_hj_ratio,CS_bb_hj_ratio, &
+ & CS_hjW_ratio,CS_hjZ_ratio, &
+ & CS_vbf_ratio,CS_tthj_ratio, &
+ & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
+ & CS_hjhi)
+ case(7)
+ call set_input(theo(n)%lhc7,CS_hj_ratio, &
+ & CS_gg_hj_ratio,CS_bb_hj_ratio, &
+ & CS_hjW_ratio,CS_hjZ_ratio, &
+ & CS_vbf_ratio,CS_tthj_ratio, &
+ & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
+ & CS_hjhi)
+ case(8)
+ call set_input(theo(n)%lhc8,CS_hj_ratio, &
+ & CS_gg_hj_ratio,CS_bb_hj_ratio, &
+ & CS_hjW_ratio,CS_hjZ_ratio, &
+ & CS_vbf_ratio,CS_tthj_ratio, &
+ & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
+ & CS_hjhi)
+ case(13)
+ call set_input(theo(n)%lhc13,CS_hj_ratio, &
+ & CS_gg_hj_ratio,CS_bb_hj_ratio, &
+ & CS_hjW_ratio,CS_hjZ_ratio, &
+ & CS_vbf_ratio,CS_tthj_ratio, &
+ & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
+ & CS_hjhi)
+ case default
+ stop 'wrong input for collider to subroutine HiggsBounds_neutral_input_hadr'
+ end select
+ just_after_run=.False.
+
+ contains
+
+ subroutine set_input(dataset,CS_hj_ratio, &
+ & CS_gg_hj_ratio,CS_bb_hj_ratio, &
+ & CS_hjW_ratio,CS_hjZ_ratio, &
+ & CS_vbf_ratio,CS_tthj_ratio, &
+ & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
+ & CS_hjhi)
- theo(n)%particle(Hneut)%M = Mh
- theo(n)%particle(Hneut)%Mc = Mh
- theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
- theo(n)%CP_value = CP_value
- theo(n)%lep%XS_hjZ_ratio = CS_lep_hjZ_ratio
- theo(n)%lep%XS_bbhj_ratio = CS_lep_bbhj_ratio
- theo(n)%lep%XS_tautauhj_ratio = CS_lep_tautauhj_ratio
- theo(n)%lep%XS_hjhi_ratio = CS_lep_hjhi_ratio_nHbynH
- theo(n)%tev%XS_hj_ratio = CS_tev_hj_ratio
- theo(n)%tev%XS_hjb_ratio = CS_tev_hjb_ratio
- theo(n)%tev%XS_hjW_ratio = CS_tev_hjW_ratio
- theo(n)%tev%XS_hjZ_ratio = CS_tev_hjZ_ratio
- theo(n)%tev%XS_vbf_ratio = CS_tev_vbf_ratio
- theo(n)%tev%XS_tthj_ratio = CS_tev_tthj_ratio
- theo(n)%lhc7%XS_hj_ratio = CS_lhc7_hj_ratio
- theo(n)%lhc7%XS_hjb_ratio = CS_lhc7_hjb_ratio
- theo(n)%lhc7%XS_hjW_ratio = CS_lhc7_hjW_ratio
- theo(n)%lhc7%XS_hjZ_ratio = CS_lhc7_hjZ_ratio
- theo(n)%lhc7%XS_vbf_ratio = CS_lhc7_vbf_ratio
- theo(n)%lhc7%XS_tthj_ratio = CS_lhc7_tthj_ratio
- theo(n)%lhc8%XS_hj_ratio = CS_lhc8_hj_ratio
- theo(n)%lhc8%XS_hjb_ratio = CS_lhc8_hjb_ratio
- theo(n)%lhc8%XS_hjW_ratio = CS_lhc8_hjW_ratio
- theo(n)%lhc8%XS_hjZ_ratio = CS_lhc8_hjZ_ratio
- theo(n)%lhc8%XS_vbf_ratio = CS_lhc8_vbf_ratio
- theo(n)%lhc8%XS_tthj_ratio = CS_lhc8_tthj_ratio
- theo(n)%BR_hjss = BR_hjss
- theo(n)%BR_hjcc = BR_hjcc
- theo(n)%BR_hjbb = BR_hjbb
- theo(n)%BR_hjmumu = BR_hjmumu
- theo(n)%BR_hjtautau = BR_hjtautau
- theo(n)%BR_hjWW = BR_hjWW
- theo(n)%BR_hjZZ = BR_hjZZ
- theo(n)%BR_hjZga = BR_hjZga
- theo(n)%BR_hjgaga = BR_hjgaga
- theo(n)%BR_hjgg = BR_hjgg
- theo(n)%BR_hjinvisible = BR_hjinvisible
- theo(n)%BR_hjhihi = BR_hjhihi_nHbynH
+ implicit none
+ double precision,intent(in) :: CS_hj_ratio( np(Hneut) ), &
+ & CS_gg_hj_ratio( np(Hneut) ),CS_bb_hj_ratio( np(Hneut) ), &
+ & CS_hjW_ratio( np(Hneut) ) ,CS_hjZ_ratio( np(Hneut) ), &
+ & CS_vbf_ratio( np(Hneut) ) ,CS_tthj_ratio( np(Hneut) ), &
+ & CS_thj_tchan_ratio( np(Hneut) ),CS_thj_schan_ratio( np(Hneut) ), &
+ & CS_hjhi( np(Hneut), np(Hneut) )
+ type(hadroncolliderdataset) :: dataset
+
+ dataset%XS_hj_ratio = CS_hj_ratio
+ dataset%XS_gg_hj_ratio = CS_gg_hj_ratio
+ dataset%XS_bb_hj_ratio = CS_bb_hj_ratio
+ dataset%XS_hjW_ratio = CS_hjW_ratio
+ dataset%XS_hjZ_ratio = CS_hjZ_ratio
+ dataset%XS_vbf_ratio = CS_vbf_ratio
+ dataset%XS_tthj_ratio = CS_tthj_ratio
+ dataset%XS_thj_tchan_ratio = CS_thj_tchan_ratio
+ dataset%XS_thj_schan_ratio = CS_thj_schan_ratio
+ dataset%XS_hjhi = CS_hjhi
- just_after_run=.False.
-
-! write(*,*) "DEBUG HB: filled hadronic input. Mass is ",theo(n)%particle(Hneut)%M
-
+ end subroutine set_input
+
end subroutine HiggsBounds_neutral_input_hadr
!************************************************************
subroutine HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj, &
& CS_lep_HpjHmj_ratio, &
& BR_tWpb,BR_tHpjb, &
& BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu,BR_Hpjtb, &
& BR_HpjWZ,BR_HpjhiW)
-! This subroutine can be called by the user after subroutine initialize_HiggsBounds
-! has been called.
+! This subroutine can be called by the user after subroutine
+! initialize_HiggsBounds has been called.
! Arguments (input): theoretical predictions (see manual for definitions)
+! HB-5: Extended input by charged Higgs decays to tb, WZ, hiW
!************************************************************
use usefulbits, only : theo,np,Hplus,Hneut,just_after_run!,inputsub
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
implicit none
!----------------------------------------input
double precision,intent(in) :: Mhplus( np(Hplus) ),GammaTotal_Hpj( np(Hplus) ), &
& CS_lep_HpjHmj_ratio( np(Hplus) ), &
& BR_tWpb,BR_tHpjb( np(Hplus) ), &
& BR_Hpjcs( np(Hplus) ),BR_Hpjcb( np(Hplus) ),BR_Hpjtaunu( np(Hplus) ), &
& BR_Hpjtb( np(Hplus) ),BR_HpjWZ( np(Hplus) )
- double precision,optional,intent(in) :: BR_HpjhiW(np(Hplus),np(Hneut))
+ double precision,intent(in) :: BR_HpjhiW(np(Hplus),np(Hneut))
!--------------------------------------internal
integer :: n
! integer :: j
! integer :: subtype
!----------------------------------------------
n=1
! subtype=2
! inputsub(subtype)%stat=inputsub(subtype)%stat+1
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hplus).eq.0)then
write(*,*)'subroutine HiggsBounds_charged_input should'
write(*,*)'only be called if np(Hplus)>0'
stop 'error in subroutine HiggsBounds_charged_input'
endif
theo(n)%particle(Hplus)%M = Mhplus
theo(n)%particle(Hplus)%Mc = Mhplus
theo(n)%particle(Hplus)%GammaTot= GammaTotal_Hpj
theo(n)%lep%XS_HpjHmj_ratio = CS_lep_HpjHmj_ratio
theo(n)%BR_tWpb = BR_tWpb
theo(n)%BR_tHpjb = BR_tHpjb
theo(n)%BR_Hpjcs = BR_Hpjcs
theo(n)%BR_Hpjcb = BR_Hpjcb
theo(n)%BR_Hpjtaunu = BR_Hpjtaunu
theo(n)%BR_Hpjtb = BR_Hpjtb
theo(n)%BR_HpjWZ = BR_HpjWZ
-
- if(present(BR_HpjhiW)) then
- theo(n)%BR_HpjhiW = BR_HpjhiW
-! do j=1,np(Hplus)
-! write(*,*) "theo(n)%BR_HpjhiW,j = ",theo(n)%BR_HpjhiW(j,:) , j
-! enddo
- endif
+ theo(n)%BR_HpjhiW = BR_HpjhiW
+! write(*,*) 'HiggsBounds_charged_input'
+! write(*,*) theo(n)%BR_HpjhiW
+! if(present(BR_HpjhiW_in)) then
+! write(*,*) "BR_HpjhiW given: ", BR_HpjhiW_in
+! theo(n)%BR_HpjhiW = BR_HpjhiW_in
+! else
+! if(np(Hneut).gt.0) then
+! theo(n)%BR_HpjhiW = 0.0D0
+! endif
+! endif
+! write(*,*) theo(n)%BR_HpjhiW
just_after_run=.False.
end subroutine HiggsBounds_charged_input
!************************************************************
+subroutine HiggsBounds_charged_input_hadr(collider, CS_Hpjtb, CS_Hpjcb, &
+& CS_Hpjbjet, CS_Hpjcjet, CS_Hpjjetjet, CS_HpjW, &
+& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
+! This subroutine can be called by the user after subroutine initialize_HiggsBounds
+! has been called.
+! Arguments (input): theoretical predictions (see manual for definitions)
+!************************************************************
+ use usefulbits, only : theo,np,Hplus,Hneut,just_after_run,hadroncolliderdataset!,inputsub
+
+#if defined(NAGf90Fortran)
+ use F90_UNIX_IO, only : flush
+#endif
+
+ implicit none
+
+ !----------------------------------------input
+ double precision,intent(in) :: CS_Hpjtb( np(Hplus) ), CS_Hpjcb( np(Hplus) ),&
+& CS_Hpjbjet( np(Hplus) ), CS_Hpjcjet( np(Hplus) ),&
+& CS_Hpjjetjet( np(Hplus) ), &
+& CS_HpjW( np(Hplus) ), CS_HpjZ( np(Hplus) ),&
+& CS_vbf_Hpj( np(Hplus) ), CS_HpjHmj( np(Hplus) )
+ integer, intent(in) :: collider
+ double precision,intent(in) :: CS_Hpjhi( np(Hplus),np(Hneut) )
+ !--------------------------------------internal
+ integer :: n
+ !----------------------------------------------
+ n=1
+
+ if(.not.allocated(theo))then
+ stop 'subroutine HiggsBounds_initialize must be called first'
+ endif
+
+ if(np(Hplus).eq.0)then
+ write(*,*)'subroutine HiggsBounds_charged_input should'
+ write(*,*)'only be called if np(Hplus)>0'
+ stop 'error in subroutine HiggsBounds_charged_input'
+ endif
+
+ select case(collider)
+ case(2)
+! if(present(CS_Hpjhi)) then
+ call set_input(theo(n)%tev,CS_Hpjtb, CS_Hpjcb, CS_Hpjbjet, &
+& CS_Hpjcjet, CS_Hpjjetjet, CS_HpjW, &
+& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
+! else
+! call set_input(theo(n)%tev,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
+! & CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj)
+! endif
+ case(7)
+! if(present(CS_Hpjhi)) then
+ call set_input(theo(n)%lhc7,CS_Hpjtb, CS_Hpjcb, CS_Hpjbjet, &
+& CS_Hpjcjet, CS_Hpjjetjet, CS_HpjW, &
+& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
+! else
+! call set_input(theo(n)%lhc7,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
+! & CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj)
+! endif
+ case(8)
+! if(present(CS_Hpjhi)) then
+ call set_input(theo(n)%lhc8,CS_Hpjtb, CS_Hpjcb, CS_Hpjbjet, &
+& CS_Hpjcjet, CS_Hpjjetjet, CS_HpjW, &
+& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
+! else
+! call set_input(theo(n)%lhc8,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
+! & CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj)
+! endif
+ case(13)
+! if(present(CS_Hpjhi)) then
+ call set_input(theo(n)%lhc13,CS_Hpjtb, CS_Hpjcb, CS_Hpjbjet, &
+& CS_Hpjcjet, CS_Hpjjetjet, CS_HpjW, &
+& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
+! else
+! call set_input(theo(n)%lhc13,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
+! & CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj)
+! endif
+ case default
+ stop 'wrong input for collider to subroutine HiggsBounds_charged_input_hadr'
+ end select
+
+ just_after_run=.False.
+
+ contains
+
+ subroutine set_input(dataset,CS_Hpjtb, CS_Hpjcb, CS_Hpjbjet, &
+& CS_Hpjcjet, CS_Hpjjetjet, CS_HpjW, &
+& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
+
+ double precision,intent(in) :: CS_Hpjtb( np(Hplus) ), CS_Hpjcb( np(Hplus) ),&
+& CS_Hpjbjet( np(Hplus) ), CS_Hpjcjet( np(Hplus) ),&
+& CS_Hpjjetjet( np(Hplus) ), &
+& CS_HpjW( np(Hplus) ), CS_HpjZ( np(Hplus) ),&
+& CS_vbf_Hpj( np(Hplus) ), CS_HpjHmj( np(Hplus) )
+ double precision,intent(in) :: CS_Hpjhi( np(Hplus),np(Hneut) )
+ type(hadroncolliderdataset) :: dataset
+
+ dataset%XS_Hpjtb = CS_Hpjtb
+ dataset%XS_Hpjcb = CS_Hpjcb
+ dataset%XS_Hpjbjet = CS_Hpjbjet
+ dataset%XS_Hpjcjet = CS_Hpjcjet
+ dataset%XS_Hpjjetjet = CS_Hpjjetjet
+ dataset%XS_vbf_Hpj = CS_vbf_Hpj
+ dataset%XS_HpjW = CS_HpjW
+ dataset%XS_HpjZ = CS_HpjZ
+ dataset%XS_HpjHmj = CS_HpjHmj
+! if(present(CS_Hpjhi)) then
+ dataset%XS_Hpjhi = CS_Hpjhi
+! endif
+
+ end subroutine set_input
+
+end subroutine HiggsBounds_charged_input_hadr
+!************************************************************
subroutine HiggsBounds_set_mass_uncertainties(dMhneut, dMhch)
+!************************************************************
! Assigns the mass uncertainties in the subroutine version.
!
use usefulbits, only : theo,np,Hneut,Hplus
implicit none
double precision, intent(in) :: dMhneut(np(Hneut))
double precision, intent(in) :: dMhch(np(Hplus))
theo(1)%particle(Hneut)%dMh = dMhneut
theo(1)%particle(Hplus)%dMh = dMhch
end subroutine HiggsBounds_set_mass_uncertainties
!************************************************************
subroutine get_mass_variation_param(n)
use usefulbits, only : theo,np,Hneut,Hplus,diffMhneut,diffMhch,ndmh,dmhsteps,small_mh
implicit none
integer, intent(in) :: n
double precision :: dMhneut(np(Hneut))
double precision :: dMhch(np(Hplus))
integer :: km(np(Hneut)+np(Hplus))
integer :: dm(dmhsteps**(np(Hneut)+np(Hplus)),np(Hneut)+np(Hplus))
integer i,j,k,kp
if(np(Hneut).gt.0) dMhneut = theo(n)%particle(Hneut)%dMh
if(np(Hplus).gt.0) dMhch = theo(n)%particle(Hplus)%dMh
if (modulo(dmhsteps,2).NE.1) then
stop 'Wrong number of steps in set_mass_uncertainty: must be odd (>=3)'
endif
ndmh = 0
do i=1,np(Hneut)
IF (dMhneut(i).GT.small_mh) THEN
ndmh = ndmh + 1
ENDIF
km(i)=-(dmhsteps-1)/2
enddo
do i=1,np(Hplus)
IF (dMhch(i).GT.small_mh) ndmh = ndmh + 1
km(i+np(Hneut))=-(dmhsteps-1)/2
enddo
IF (ndmh.EQ.0) THEN
RETURN
ENDIF
! print *, "Number of mass uncertainties: ", ndmh
if(allocated(diffMhneut)) deallocate(diffMhneut)
if(allocated(diffMhch)) deallocate(diffMhch)
allocate(diffMhneut(dmhsteps**(np(Hneut)+np(Hplus)),np(Hneut)))
allocate(diffMhch(dmhsteps**(np(Hneut)+np(Hplus)),np(Hplus)))
k = 1
do i=1,dmhsteps**ndmh
do j=1,ndmh
dm(i,j) = km(j)
enddo
km(k) = km(k)+1
do j=2,ndmh
IF (modulo(i,dmhsteps**(j-1)).EQ.0) THEN
km(j) = km(j)+1
km(j-1) = -1
ENDIF
ENDDO
enddo
do i=1,dmhsteps**ndmh
k=1
do j=1,np(Hneut)
IF (dMhneut(j).GT.small_mh) THEN
diffMhneut(i,j)=theo(n)%particle(Hneut)%M(j)+dm(i,k)*dMhneut(k)/((dmhsteps-1)/2)
k = k +1
ELSE
diffMhneut(i,j)=theo(n)%particle(Hneut)%M(j)
ENDIF
enddo
kp = k
do j=1,np(Hplus)
IF (dMhch(j).GT.small_mh) THEN
diffMhch(i,j)=theo(n)%particle(Hplus)%M(j)+dm(i,k)*dMhch(k-(kp-1))/((dmhsteps-1)/2)
k = k +1
ELSE
diffMhch(i,j)=theo(n)%particle(Hplus)%M(j)
ENDIF
enddo
! print *, i, (diffMhneut(i,j),j=1,np(Hneut)),(diffMhch(i,j),j=1,np(Hplus))
enddo
end subroutine get_mass_variation_param
subroutine SUSYBounds_neutralinoonly_input(MN,GammaTotal_N, &
& CS_NjNi, &
& BR_NjqqNi,BR_NjZNi &
& )
! This subroutine can be called by the user after subroutine initialize_HiggsBounds
! has been called.
! Arguments (input): theoretical predictions (see manual for definitions)
!************************************************************
use usefulbits, only : theo,np,Chineut,just_after_run!,inputsub,
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
implicit none
!----------------------------------------input
double precision,intent(in) :: MN( np(Chineut) ),GammaTotal_N( np(Chineut) ) , &
& CS_NjNi( np(Chineut),np(Chineut) ), &
& BR_NjqqNi( np(Chineut),np(Chineut) ),BR_NjZNi( np(Chineut),np(Chineut) )
!--------------------------------------internal
integer :: n
! integer :: subtype
!----------------------------------------------
n=1
! subtype=3
! inputsub(subtype)%stat=inputsub(subtype)%stat+1
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Chineut).eq.0)then
write(*,*)'subroutine SUSYBounds_neutralinoonly_input should'
write(*,*)'only be called if np(Chineut)>0'
stop 'error in SUSYBounds_neutralinoonly_input'
endif
theo(n)%particle(Chineut)%M = MN
theo(n)%particle(Chineut)%GammaTot= GammaTotal_N
theo(n)%lep%XS_NjNi = CS_NjNi
theo(n)%BR_NjqqNi = BR_NjqqNi
theo(n)%BR_NjZNi = BR_NjZNi
just_after_run=.False.
end subroutine SUSYBounds_neutralinoonly_input
!************************************************************
subroutine SUSYBounds_neutralinochargino_input(MC,GammaTotal_C, &
& CS_CpjCmj, &
& BR_CjqqNi, &
& BR_CjlnuNi, &
& BR_CjWNi &
& )
! This subroutine can be called by the user after subroutine initialize_HiggsBounds
! has been called.
! Arguments (input): theoretical predictions (see manual for definitions)
!************************************************************
use usefulbits, only : theo,np,Chineut,Chiplus,just_after_run!,inputsub
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
implicit none
!----------------------------------------input
double precision,intent(in) :: MC( np(Chiplus) ),GammaTotal_C( np(Chiplus) ), &
& CS_CpjCmj( np(Chiplus) ), &
& BR_CjqqNi( np(Chiplus),np(Chineut) ), &
& BR_CjlnuNi( np(Chiplus),np(Chineut) ), &
& BR_CjWNi( np(Chiplus),np(Chineut) )
!--------------------------------------internal
integer :: n
integer :: subtype
!----------------------------------------------
n=1
! subtype=4
! inputsub(subtype)%stat=inputsub(subtype)%stat+1
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if((np(Chineut).eq.0).or.(np(Chiplus).eq.0))then
write(*,*)'subroutine SUSYBounds_neutralinochargino_input should'
write(*,*)'only be called if np(Chineut)>0 and np(Chiplus)>0'
stop 'error in subroutine SUSYBounds_neutralinochargino_input'
endif
theo(n)%particle(Chineut)%M = MC
theo(n)%particle(Chineut)%GammaTot= GammaTotal_C
theo(n)%lep%XS_CpjCmj = CS_CpjCmj
theo(n)%BR_CjqqNi = BR_CjqqNi
theo(n)%BR_CjlnuNi = BR_CjlnuNi
theo(n)%BR_CjWNi = BR_CjWNi
just_after_run=.False.
end subroutine SUSYBounds_neutralinochargino_input
!************************************************************
subroutine run_HiggsBounds(HBresult, chan, obsratio, ncombined)
! This subroutine can be called by the user after HiggsBounds_initialize has been called.
! The input routines, where required, should be called before calling run_HiggsBounds.
! It takes theoretical predictions for a particular parameter point
! in the model and calls subroutines which compare these predictions
! to the experimental limits
! Arguments (output):
! * HBresult = 1 if point is unexcluded, 0 if excluded, -1 if parameter point is invalid
! * chan = number of channel predicted to have the highest statistical sensitivity, as defined in Key.dat
! * obsratio = ratio of the theoretical rate to the observed limit for this channel
! * ncombined = number of Higgs combined in order to calculate this obsratio
! (see manual for more precise definitions))
! (TS 30/01/2012): Note, that if many data points are tested at the same time (as for
! inputmethod==datfiles), this subroutine only returns the results of
! the last datapoint. The full results are saved in fullHBres.
use usefulbits, only : np, Hneut, Hplus, run_HB_classic
implicit none
integer HBresult, chan, ncombined
double precision obsratio
integer hbres(0:np(Hneut)+np(Hplus)), hbchan(0:np(Hneut)+np(Hplus)), hbcomb(0:np(Hneut)+np(Hplus))
double precision hbobs(0:np(Hneut)+np(Hplus))
! Check if we are using the old 'classic' method
if (run_HB_classic.EQV..True.) then
call run_HiggsBounds_classic(HBresult,chan,obsratio,ncombined)
return
endif
! Call the new ('full') method
call run_HiggsBounds_full(hbres, hbchan, hbobs, hbcomb)
! Combined results are contained in the zero elements of result arrays
HBresult = hbres(0)
chan = hbchan(0)
obsratio = hbobs(0)
ncombined = hbcomb(0)
end subroutine run_HiggsBounds
!************************************************************
subroutine run_HiggsBounds_single(h, HBresult, chan, obsratio, ncombined)
! This subroutine can be used to get the exclusion results
! for a single Higgs boson (specified by the index h).
!
! To obtain individual results from more than one Higgs boson, it
! is more efficient to use run_HiggsBounds_full rather than this method.
use usefulbits, only : np, Hneut, Hplus
implicit none
integer, intent(in) :: h
integer, intent(out) :: HBresult, chan, ncombined
double precision, intent(out) :: obsratio
integer hbres(0:np(Hneut)+np(Hplus)), hbchan(0:np(Hneut)+np(Hplus)), hbcomb(0:np(Hneut)+np(Hplus))
double precision hbobs(0:np(Hneut)+np(Hplus))
IF (h.LT.0) stop "Illegal number of Higgs boson: h < 0"
if (h.GT.np(Hneut)+np(Hplus)) stop "Illegal number of Higgs boson"
call run_HiggsBounds_full(hbres, hbchan, hbobs, hbcomb)
HBresult = hbres(h)
chan = hbchan(h)
obsratio = hbobs(h)
ncombined = hbcomb(h)
end subroutine run_HiggsBounds_single
!************************************************************
subroutine run_HiggsBounds_full( HBresult,chan, &
& obsratio, ncombined )
! This subroutine can be called by the user after HiggsBounds_initialize has been called.
! The input routines, where required, should be called before calling run_HiggsBounds.
! It takes theoretical predictions for a particular parameter point
! in the model and calls subroutines which compare these predictions
! to the experimental limits.
!
! The results are given as (n+1)-component arrays (starting from 0),
! where n is the total number of Higgs bosons in the model (neutral+charged).
! The zeroth component gives the combined results (equivalent to run_HiggsBounds).
!
! Arguments (output):
! * HBresult = 1 if point is unexcluded, 0 if excluded, -1 if parameter point is invalid
! * chan = number of channel predicted to have the highest statistical sensitivity, as defined in Key.dat
! * obsratio = ratio of the theoretical rate to the observed limit for this channel
! * ncombined = number of Higgs combined in order to calculate this obsratio
! (see manual for more precise definitions))
use usefulbits, only : theo,res,just_after_run,ndmh,debug,numres, &
& np,Hneut,Hplus,dmhsteps,ndat,fullHBres,small_mh,&
HBresult_all,ncombined_all,chan_all,obsratio_all,predratio_all
use channels, only : check_channels
!use input, only : test_input
use theo_manip, only : HB5_complete_theo, HB5_recalculate_theo_for_datapoint
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
implicit none
!----------------------------------------output
integer,intent(out):: HBresult(0:np(Hneut)+np(Hplus))
integer,intent(out):: chan(0:np(Hneut)+np(Hplus))
integer,intent(out):: ncombined(0:np(Hneut)+np(Hplus))
double precision,intent(out) :: obsratio(0:np(Hneut)+np(Hplus))
double precision :: Mhneut(np(Hneut))
double precision :: Mhch(np(Hplus))
!-------------------------------------internal
integer :: n,i,j,ind,part,k
!---------------------------------------------
! print *, "Running HiggsBounds in Normal Mode (most sensitive limit considered for each Higgs boson)"
if (lbound(HBresult,dim=1).NE.0) stop "run_HiggsBounds_full: Array HBresult must begin with element 0"
if (ubound(HBresult,dim=1).NE.(np(Hneut)+np(Hplus))) then
stop "run_HiggsBounds_full: Upper limit of array HBresult must be equal to number of Higgses"
endif
if (lbound(chan,dim=1).NE.0) stop "run_HiggsBounds_full: Array chan must begin with element 0"
if (ubound(chan,dim=1).NE.(np(Hneut)+np(Hplus))) then
stop "run_HiggsBounds_full: Upper limit of array chan must be equal to number of Higgses"
endif
if (lbound(obsratio,dim=1).NE.0) stop "run_HiggsBounds_full: Array obsratio must begin with element 0"
if (ubound(obsratio,dim=1).NE.(np(Hneut)+np(Hplus))) then
stop "run_HiggsBounds_full: Upper limit of array obsratio must be equal to number of Higgses"
endif
if (lbound(ncombined,dim=1).NE.0) stop "run_HiggsBounds_full: Array ncombined must begin with element 0"
if (ubound(ncombined,dim=1).NE.(np(Hneut)+np(Hplus))) then
stop "run_HiggsBounds_full: Upper limit of array ncombined must be equal to number of Higgses"
endif
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(.not.allocated(HBresult_all)) allocate(HBresult_all(0:np(Hneut)+np(Hplus),numres))
if(.not.allocated(chan_all)) allocate(chan_all(0:np(Hneut)+np(Hplus),numres))
if(.not.allocated(ncombined_all)) allocate(ncombined_all(0:np(Hneut)+np(Hplus),numres))
if(.not.allocated(obsratio_all)) allocate(obsratio_all(0:np(Hneut)+np(Hplus),numres))
if(.not.allocated(predratio_all)) allocate(predratio_all(0:np(Hneut)+np(Hplus),numres))
! do i=1,ubound(inputsub,dim=1)
! if( inputsub(i)%req .ne. inputsub(i)%stat )then
! write(*,*)'subroutine '//trim(adjustl(inputsub(i)%desc))
! write(*,*)'should be called once and only once before each call to'
! write(*,*)'subroutine run_HiggsBounds.'
! stop 'error in subroutine run_HiggsBounds'
! endif
! inputsub(i)%stat=0!now we have used this input, set back to zero
! enddo
call HB5_complete_theo
do n=1,ndat
! if(debug) then
! write(*,*) "DEBUG BRs: ", theo(n)%BR_hjWW, theo(n)%BR_hjZZ, theo(n)%BR_hjgaga
! endif
theo(n)%particle(Hneut)%Mc = theo(n)%particle(Hneut)%M
theo(n)%particle(Hplus)%Mc = theo(n)%particle(Hplus)%M
call get_mass_variation_param(n)
do i=0,ubound(Hbresult,dim=1)
obsratio_all(i,:) = -999d0
predratio_all(i,:) = -999d0
HBresult_all(i,:) = 1
chan_all(i,:) = -999
ncombined_all(i,:) = -999
enddo
! Do we have mass uncertainties to take care off
IF (ndmh.GT.0) THEN
! print *, "Running HiggsBounds with Higgs mass uncertainties"
! write(*,*) theo(n)%particle(Hplus)%dM
if(np(Hneut).ne.0) Mhneut = theo(n)%particle(Hneut)%M
if(np(Hplus).ne.0) Mhch = theo(n)%particle(Hplus)%M
! Loop over all Higgses
do i=1,np(Hneut)+np(Hplus)
obsratio_all(i,:) = 1.D23
IF (i.LE.np(Hneut)) THEN
ind = i
part = Hneut
ELSE
ind = i-np(Hneut)
part = Hplus
ENDIF
! Check for mass steps for this particular Higgs boson
IF(theo(n)%particle(part)%dMh(ind).GT.small_mh) THEN
! theo(n)%particle(part)%M(ind)=theo(n)%particle(part)%M(ind) &
! & -(dmhsteps-1)/2*theo(n)%particle(part)%dMh(ind)
theo(n)%particle(part)%M(ind)=theo(n)%particle(part)%M(ind) &
& -theo(n)%particle(part)%dMh(ind)
do j=1,dmhsteps
! print *, theo(n)%particle(Hneut)%M, theo(n)%particle(Hplus)%M
call HB5_recalculate_theo_for_datapoint(n)
call check_channels(theo(n),res(n),i)
do k=1,size(res(n)%obsratio)
! write(*,*) "i,k,res(n)%obsratio(k),res(n)%chan(k) = ",i,k,res(n)%obsratio(k),res(n)%chan(k)
IF (res(n)%obsratio(k).LT.obsratio_all(i,k)) THEN
! write(*,*) "i,k,res(n)%obsratio(k),res(n)%chan(k) = ",i,k,res(n)%obsratio(k),res(n)%chan(k)
HBresult_all(i,k) = res(n)%allowed95(k)
chan_all(i,k) = res(n)%chan(k)
obsratio_all(i,k) = res(n)%obsratio(k)
predratio_all(i,k) = res(n)%predratio(k)
ncombined_all(i,k) = res(n)%ncombined(k)
ENDIF
enddo
! print *, i,theo(n)%particle(part)%M(ind),HBresult(i),chan(i),obsratio(i),ncombined(i)
theo(n)%particle(part)%M(ind)= theo(n)%particle(part)%M(ind) &
& +theo(n)%particle(part)%dMh(ind)/(dmhsteps-1)*2
enddo
else
call HB5_recalculate_theo_for_datapoint(n)
call check_channels(theo(n),res(n),i)
do k=1,size(res(n)%obsratio)
! write(*,*) "i,k,res(n)%obsratio(k),res(n)%chan(k) = ",i,k,res(n)%obsratio(k),res(n)%chan(k)
HBresult_all(i,k) = res(n)%allowed95(k)
chan_all(i,k) = res(n)%chan(k)
obsratio_all(i,k) = res(n)%obsratio(k)
predratio_all(i,k) = res(n)%predratio(k)
ncombined_all(i,k) = res(n)%ncombined(k)
enddo
! HBresult(i) = res(n)%allowed95(1)
! chan(i) = res(n)%chan(1)
! obsratio(i) = res(n)%obsratio(1)
! ncombined(i) = res(n)%ncombined(1)
endif
HBresult(i) = HBresult_all(i,1)
chan(i) = chan_all(i,1)
obsratio(i) = obsratio_all(i,1)
ncombined(i) = ncombined_all(i,1)
! Logical OR between exclusions (one Higgs excluded = combined exclusion)
HBresult(0) = HBresult(0) * HBresult(i)
! Save the data for the Higgs that has the highest ratio of theory/obs
IF (obsratio(i).GT.obsratio(0)) THEN
chan(0) = chan(i)
obsratio(0) = obsratio(i)
ncombined(0) = ncombined(i)
ENDIF
theo(n)%particle(Hneut)%M = Mhneut
theo(n)%particle(Hplus)%M = Mhch
enddo
! return
ELSE
! print *, "Running HiggsBounds without Higgs mass uncertainties"
call HB5_recalculate_theo_for_datapoint(n)
! write(*,*) "Higgses = " , np(Hneut)+np(Hplus)
do i=1,np(Hneut)+np(Hplus)
call check_channels(theo(n),res(n),i)
! do k=1,size(res(n)%obsratio)
! write(*,*) "i,k,res(n)%obsratio(k),res(n)%chan(k) = ",i,k,res(n)%obsratio(k),res(n)%chan(k)
! enddo
do k=1,size(res(n)%obsratio)
! write(*,*) "i,k,res(n)%obsratio(k),res(n)%chan(k) = ",i,k,res(n)%obsratio(k),res(n)%chan(k)
HBresult_all(i,k) = res(n)%allowed95(k)
chan_all(i,k) = res(n)%chan(k)
obsratio_all(i,k) = res(n)%obsratio(k)
predratio_all(i,k) = res(n)%predratio(k)
ncombined_all(i,k) = res(n)%ncombined(k)
enddo
HBresult(i) = HBresult_all(i,1)
chan(i) = chan_all(i,1)
obsratio(i) = obsratio_all(i,1)
ncombined(i) = ncombined_all(i,1)
! HBresult(i) = res(n)%allowed95(1)
! chan(i) = res(n)%chan(1)
! obsratio(i) = res(n)%obsratio(1)
! ncombined(i) = res(n)%ncombined(1)
!
! write(*,*) "hello: i=",i," HBres, chan, obsratio = ", HBresult(i), chan(i), obsratio(i)
HBresult(0) = HBresult(0) * res(n)%allowed95(1)
IF (obsratio(i).GT.obsratio(0)) THEN
! write(*,*) "hello: ", n, i
chan(0) = res(n)%chan(1)
obsratio(0) = res(n)%obsratio(1)
ncombined(0) = res(n)%ncombined(1)
ENDIF
! IF (i.LE.np(Hneut)) THEN
! print *, i,theo(n)%particle(Hneut)%M(i),HBresult(i),chan(i),obsratio(i),ncombined(i),HBresult(0), obsratio(0)
! ELSE
! print *, i,theo(n)%particle(Hplus)%M(i-np(Hneut)),HBresult(i),chan(i),obsratio(i),ncombined(i),HBresult(0), obsratio(0)
! endif
enddo
ENDIF
fullHBres(n)%allowed95=HBresult(0)
fullHBres(n)%chan=chan(0)
fullHBres(n)%obsratio=obsratio(0)
fullHBres(n)%ncombined=ncombined(0)
enddo
just_after_run=.True.
! print *, "HB: run done"
end subroutine run_HiggsBounds_full
!************************************************************
subroutine HiggsBounds_get_most_sensitive_channels_per_Higgs(nH,pos,HBresult,chan,obsratio,predratio,ncombined)
!************************************************************
use usefulbits, only : HBresult_all,obsratio_all,chan_all,ncombined_all,predratio_all,&
& just_after_run,np,Hneut,Hplus,numres
integer, intent(in) :: nH, pos
integer, intent(out) :: HBresult, chan, ncombined
double precision, intent(out) :: obsratio, predratio
HBresult = 0
chan = 0
obsratio = 0
predratio = 0
ncombined = 0
if(just_after_run.and.allocated(HBresult_all)) then
if(nH.le.np(Hneut)+np(Hplus)) then
if(pos.le.numres) then
HBresult = HBresult_all(nH,pos)
chan = chan_all(nH,pos)
obsratio = obsratio_all(nH,pos)
predratio = predratio_all(nH,pos)
ncombined = ncombined_all(nH,pos)
else
write(*,*) 'WARNING: request exceeds the number of stored most sensitive channels (',numres,')'
endif
else
write(*,*) 'WARNING: requested Higgs boson is invalid (choose between 1 and ',np(Hneut)+np(Hplus),'!)'
endif
else
write(*,*) 'WARNING: Please call run_HiggsBounds or run_HiggsBounds_full before calling',&
& ' HiggsBounds_get_most_sensitive_channels!'
endif
end subroutine HiggsBounds_get_most_sensitive_channels_per_Higgs
!************************************************************
subroutine HiggsBounds_get_most_sensitive_channels(pos,HBresult,chan,obsratio,predratio,ncombined)
!************************************************************
use usefulbits, only : HBresult_all,obsratio_all,predratio_all,chan_all,ncombined_all,&
& just_after_run,np,Hneut,Hplus,numres
integer, intent(in) :: pos
integer, intent(out) :: HBresult, chan, ncombined
double precision, intent(out) :: obsratio,predratio
integer :: i,j,count
integer,allocatable :: nH_rank(:),pos_rank(:), posflat(:)
double precision, allocatable :: predratio_tmp(:)
allocate(nH_rank(numres),pos_rank(numres),posflat(numres),predratio_tmp(numres*(np(Hneut)+np(Hplus))))
HBresult = 0
chan = 0
obsratio = 0
ncombined = 0
predratio_tmp = 0
count=0
if(just_after_run.and.allocated(HBresult_all)) then
if(pos.le.numres) then
do j=1,np(Hneut)+np(Hplus)
do i=1,numres
count=count+1
predratio_tmp(count)=predratio_all(j,i)
enddo
enddo
do i=1,numres
posflat(i) = maxloc(predratio_tmp,1)
predratio_tmp(posflat(i)) = -1.0D0
enddo
count=0
do j=1,np(Hneut)+np(Hplus)
do i=1,numres
count=count+1
do k=1,numres
if(count.eq.posflat(k)) then
nH_rank(k) = j
pos_rank(k) = i
endif
enddo
enddo
enddo
HBresult = HBresult_all(nH_rank(pos),pos_rank(pos))
chan = chan_all(nH_rank(pos),pos_rank(pos))
obsratio = obsratio_all(nH_rank(pos),pos_rank(pos))
predratio = predratio_all(nH_rank(pos),pos_rank(pos))
ncombined = ncombined_all(nH_rank(pos),pos_rank(pos))
else
write(*,*) 'WARNING: request exceeds the number of stored most sensitive channels (',numres,')'
endif
else
write(*,*) 'WARNING: Please call run_HiggsBounds or run_HiggsBounds_full before calling',&
& ' HiggsBounds_get_most_sensitive_channels!'
endif
deallocate(nH_rank,pos_rank,posflat,predratio_tmp)
end subroutine HiggsBounds_get_most_sensitive_channels
!************************************************************
subroutine run_HiggsBounds_classic( HBresult,chan,obsratio,ncombined)
! This subroutine can be called by the user after HiggsBounds_initialize has been called.
! The input routines, where required, should be called before calling run_HiggsBounds.
! It takes theoretical predictions for a particular parameter point
! in the model and calls subroutines which compare these predictions
! to the experimental limits
! Arguments (output):
! * HBresult = 1 if point is unexcluded, 0 if excluded, -1 if parameter point is invalid
! * chan = number of channel predicted to have the highest statistical sensitivity, as defined in Key.dat
! * obsratio = ratio of the theoretical rate to the observed limit for this channel
! * ncombined = number of Higgs combined in order to calculate this obsratio
! (see manual for more precise definitions))
use usefulbits, only : theo,res,debug,just_after_run,ndmh,diffmhneut,diffmhch, &
np,Hneut,Hplus,full_dmth_variation,dmhsteps, ndat,fullHBres!,inputsub
use channels, only : check_channels
!use input, only : test_input
use theo_manip, only : HB5_complete_theo, HB5_recalculate_theo_for_datapoint
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
implicit none
!----------------------------------------output
integer,intent(out):: HBresult,chan,ncombined
double precision,intent(out) :: obsratio
double precision :: Mhneut(np(Hneut))
double precision :: Mhch(np(Hplus))
!-------------------------------------internal
integer :: n,i
integer :: HBresult_tmp,chan_tmp,ncombined_tmp
double precision :: obsratio_tmp
!---------------------------------------------
! n=1
! print *, "Running HiggsBounds in Classic Mode (globally most sensitive limit only)"
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
! do i=1,ubound(inputsub,dim=1)
! if( inputsub(i)%req .ne. inputsub(i)%stat )then
! write(*,*)'subroutine '//trim(adjustl(inputsub(i)%desc))
! write(*,*)'should be called once and only once before each call to'
! write(*,*)'subroutine run_HiggsBounds.'
! stop 'error in subroutine run_HiggsBounds'
! endif
! inputsub(i)%stat=0!now we have used this input, set back to zero
! enddo
call HB5_complete_theo
do n=1,ndat
theo(n)%particle(Hneut)%Mc = theo(n)%particle(Hneut)%M
call get_mass_variation_param(n)
IF (ndmh.GT.0) THEN
if(np(Hneut).ne.0) Mhneut = theo(n)%particle(Hneut)%M
if(np(Hplus).ne.0) Mhch = theo(n)%particle(Hplus)%M
obsratio_tmp = 10.0E6 ! Set to very large initial value
do i=1,dmhsteps**ndmh
theo(n)%particle(Hneut)%M = diffMhneut(i,:)
theo(n)%particle(Hplus)%M = diffMhch(i,:)
if(debug)write(*,*)'manipulating input...' ; call flush(6)
call HB5_recalculate_theo_for_datapoint(n)
if(debug)write(*,*)'compare each data point to the experimental bounds...' ; call flush(6)
call check_channels(theo(n),res(n),0)
HBresult = res(n)%allowed95(1)
chan = res(n)%chan(1)
obsratio = res(n)%obsratio(1)
ncombined = res(n)%ncombined(1)
! print *, HBresult, chan, obsratio, ncombined
IF (.NOT.full_dmth_variation) THEN
IF (HBresult.EQ.1) THEN
! theo(n)%particle(Hneut)%M = Mhneut
! theo(n)%particle(Hplus)%M = Mhch
just_after_run=.True.
exit
ENDIF
ELSE
IF (obsratio.lt.obsratio_tmp) THEN
HBresult_tmp = HBresult
chan_tmp = chan
obsratio_tmp = obsratio
ncombined_tmp = ncombined
ENDIF
ENDIF
enddo
IF (full_dmth_variation) THEN
HBresult = HBresult_tmp
chan = chan_tmp
obsratio = obsratio_tmp
ncombined = ncombined
! theo(n)%particle(Hneut)%M = Mhneut
! theo(n)%particle(Hplus)%M = Mhch
just_after_run=.True.
! return
ENDIF
theo(n)%particle(Hneut)%M = Mhneut
theo(n)%particle(Hplus)%M = Mhch
call HB5_recalculate_theo_for_datapoint(n)
call check_channels(theo(n),res(n),0)
ELSE
if(debug)write(*,*)'manipulating input...' ; call flush(6)
call HB5_recalculate_theo_for_datapoint(n)
if(debug)write(*,*)'compare each data point to the experimental bounds...' ; call flush(6)
call check_channels(theo(n),res(n),0)
HBresult = res(n)%allowed95(1)
chan = res(n)%chan(1)
obsratio = res(n)%obsratio(1)
ncombined = res(n)%ncombined(1)
just_after_run=.True.
ENDIF
fullHBres(n)%allowed95=HBresult
fullHBres(n)%chan=chan
fullHBres(n)%obsratio=obsratio
fullHBres(n)%ncombined=ncombined
enddo
just_after_run=.True.
end subroutine run_HiggsBounds_classic
!************************************************************
subroutine HiggsBounds_get_likelihood(analysisID, Hindex, nc, cbin, M, llh, obspred)
!************************************************************
use usefulbits, only : theo,np,Hneut,Hplus
use theo_manip, only : HB5_complete_theo
use likelihoods, only : get_likelihood, calcpredratio_llh
implicit none
integer, intent(in) :: analysisID
integer, intent(out) :: Hindex, nc, cbin
double precision, intent(out) :: llh, M
character(LEN=*), intent(in) :: obspred
integer :: c,i
double precision, allocatable :: expllh(:)
! double precision :: fact
double precision, allocatable :: mass(:) ! predratio(:)
integer, allocatable :: nclist(:)
! call complete_theo
! allocate(predratio(np(Hneut)))
! predratio = 0.0D0
! write(*,*) "Calling HiggsBounds_get_likelihood..."
allocate(expllh(np(Hneut)),mass(np(Hneut)),nclist(np(Hneut)))
expllh = 0.0D0
select case(analysisID)
case(3316,14029)
c=1
case default
stop 'Unknown analysisID in subroutine HiggsBounds_get_likelihood!'
end select
call HB5_complete_theo
! Determine most sensitive combination
do i=1,np(Hneut)
call get_likelihood(analysisID, i, theo(1), expllh(i), mass(i), nclist(i), cbin, 'pred')
enddo
Hindex = maxloc(expllh,dim=1)
call get_likelihood(analysisID, Hindex, theo(1), llh, M, nc, cbin, obspred)
deallocate(mass,nclist,expllh) !predratio
end subroutine HiggsBounds_get_likelihood
!************************************************************
subroutine HiggsBounds_get_combined_likelihood(analysisID, llh, obspred)
!************************************************************
use usefulbits, only : theo,np,Hneut,Hplus, vsmall
integer, intent(in) :: analysisID
character(LEN=*), intent(in), optional :: obspred
double precision, intent(out) :: llh
double precision :: M, llh_tmp
integer :: i, j, nc, cbin, Hindex, cbin_end, cbin_in
write(*,*) 'WARNING: The subroutine HiggsBounds_get_combined_likelihood is NOT '
write(*,*) ' officially validated and approved. Use it on your own risk!'
cbin_end = 0
do i= 1,np(Hneut)
cbin_end = cbin_end + 2**(i-1)
enddo
llh = -1.0D0
cbin_in = 0
llh_tmp = 0.0D0
do while(cbin_in.lt.cbin_end)
if(present(obspred)) then
call HiggsBounds_get_likelihood_for_comb(analysisID, cbin_in, Hindex, nc, cbin, M, llh, obspred)
else
call HiggsBounds_get_likelihood_for_comb(analysisID, cbin_in, Hindex, nc, cbin, M, llh, 'obs')
endif
if(llh.ge.0.0D0) then
llh_tmp = llh_tmp + llh
else
exit
endif
cbin_in = cbin_in + cbin
enddo
if(llh_tmp.gt.0.0D0) then
llh = llh_tmp
endif
end subroutine HiggsBounds_get_combined_likelihood
!************************************************************
subroutine HiggsBounds_get_likelihood_for_Higgs(analysisID, cbin_in, Hindex, nc, cbin, M, llh, obspred)
!************************************************************
use usefulbits, only : theo,np,Hneut,Hplus
use theo_manip, only : HB5_complete_theo
use likelihoods, only : get_likelihood, calcpredratio_llh
implicit none
integer, intent(in) :: analysisID,Hindex
integer, intent(out) :: nc, cbin
double precision, intent(out) :: llh, M
integer, intent(in) :: cbin_in
character(LEN=*), intent(in) :: obspred
integer :: c,i
select case(analysisID)
case(3316,14029)
c=1
case default
stop 'Unknown analysisID in subroutine HiggsBounds_get_likelihood_for_Higgs!'
end select
call HB5_complete_theo
call get_likelihood(analysisID, Hindex, theo(1), llh, M, nc, cbin, obspred, cbin_in)
end subroutine HiggsBounds_get_likelihood_for_Higgs
!************************************************************
subroutine HiggsBounds_get_likelihood_for_comb(analysisID, cbin_in, Hindex, nc, cbin, M, llh, obspred)
!************************************************************
use usefulbits, only : theo,np,Hneut,Hplus
use theo_manip, only : HB5_complete_theo
use likelihoods, only : get_likelihood, calcpredratio_llh
implicit none
integer, intent(in) :: analysisID, cbin_in
integer, intent(out) :: Hindex, nc, cbin
double precision, intent(out) :: llh, M
character(LEN=*), intent(in) :: obspred
integer :: c,i
double precision, allocatable :: obsllh(:)
double precision, allocatable :: mass(:)
integer, allocatable :: nclist(:), cbinlist(:)
allocate(obsllh(np(Hneut)),mass(np(Hneut)),nclist(np(Hneut)),cbinlist(np(Hneut)))
obsllh = 0.0D0
select case(analysisID)
case(3316,14029)
c=1
case default
stop 'Unknown analysisID in subroutine HiggsBounds_get_likelihood_for_comb!'
end select
call HB5_complete_theo
! Determine most sensitive combination
do i=1,np(Hneut)
call get_likelihood(analysisID, i, theo(1), obsllh(i), mass(i), nclist(i),cbinlist(i),obspred, cbin_in)
enddo
Hindex = maxloc(obsllh,dim=1)
llh = obsllh(Hindex)
M = mass(Hindex)
nc = nclist(Hindex)
cbin = cbinlist(Hindex)
deallocate(mass,nclist,obsllh,cbinlist)
end subroutine HiggsBounds_get_likelihood_for_comb
!************************************************************
subroutine HiggsBounds_SLHA_output
!**** ********************************************************
use usefulbits, only : whichinput,just_after_run
use output, only : do_output
if(.not.just_after_run)then
stop 'subroutine run_HiggsBounds should be called before subroutine HiggsBounds_SLHA_output'
endif
select case(whichinput)
case('SLHA')
call do_output
case default
stop 'The subroutine HiggsBounds_SLHA_output should only be used when whichinput=SLHA'
end select
end subroutine HiggsBounds_SLHA_output
#ifdef enableCHISQ
!************************************************************
subroutine initialize_HiggsBounds_chisqtables
! use S95tables, only : S95_t2
use S95tables_type3
use usefulbits, only : allocate_if_stats_required,theo
implicit none
if(allocated(theo))then
stop 'subroutine initialize_HiggsBounds_chisqtables should be called before subroutine HiggsBounds_initialize'
elseif(allocated(clsb_t3))then
stop 'subroutine initialize_HiggsBounds_chisqtables has already been called once'
endif
allocate(clsb_t3(ntable3))
call initializetables_type3_blank(clsb_t3)
call initializetables3(clsb_t3)
call readclsbfiles_binary
if(allocated(allocate_if_stats_required))then
stop 'error in subroutine initialize_HiggsBounds_chisqtables'
else
allocate(allocate_if_stats_required(1))
endif
end subroutine initialize_HiggsBounds_chisqtables
!************************************************************
subroutine finish_HiggsBounds_chisqtables
!************************************************************
use S95tables_type3
use usefulbits, only : allocate_if_stats_required
implicit none
integer :: x
if(.not.allocated(clsb_t3))then
stop 'initialize_HiggsBounds_chisqtables should be called first'
endif
do x=lbound(clsb_t3,dim=1),ubound(clsb_t3,dim=1)
deallocate(clsb_t3(x)%dat)
enddo
deallocate(filename)
deallocate(clsb_t3)
deallocate(allocate_if_stats_required)
end subroutine finish_HiggsBounds_chisqtables
!************************************************************
subroutine HB_calc_stats(theory_uncertainty_1s,chisq_withouttheory,chisq_withtheory,chan2)
!************************************************************
! this is in the middle of development! DO NOT USE!
use usefulbits, only : res,theo,pr,just_after_run,vsmall
use interpolate
use S95tables_type1
use S95tables_type3
use S95tables
use extra_bits_for_chisquared
implicit none
integer,intent(out)::chan2
integer :: x,c,z,y
integer :: id
double precision, intent(in) :: theory_uncertainty_1s
double precision :: chisq_withouttheory,chisq_withtheory
double precision :: low_chisq,sigma
x=1
low_chisq=1.0D-2
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
elseif(.not.allocated(clsb_t3))then
stop 'subroutine initialize_HiggsBounds_chisqtables must be called first'
elseif(.not.just_after_run)then
stop 'subroutine run_HiggsBounds must be called first'
endif
sigma=theory_uncertainty_1s
if(sigma.lt.vsmall)then
write(*,*)'Warning: will not calculate chi^2 with theory uncertainty'
endif
chisq_withtheory = -2.0D0
chisq_withouttheory = -2.0D0
z=2;
c= res(x)%chan(z)
chan2=c
if(res(x)%allowed95(z).eq.-1)then! labels an unphysical parameter point
chisq_withtheory =-1.0D0
chisq_withouttheory =-1.0D0
elseif( c.gt.0 )then ! labels a physical parameter point and a real channel
id=S95_t1_or_S95_t2_idfromelementnumber(pr(c)%ttype,pr(c)%tlist)
y=clsb_t3elementnumber_from_S95table(pr(c)%ttype,id)
if(y.gt.0)then
!------------------------------
call get_chisq(sigma,res(x)%axis_i(z),res(x)%axis_j(z),res(x)%sfactor(z), &
& y,chisq_withouttheory,chisq_withtheory)
!-------------------------------
else
write(*,*)'hello y=',y
stop 'problem here with y'
endif
else
chisq_withtheory =0.0D0
chisq_withouttheory =0.0D0
endif
end subroutine HB_calc_stats
#endif
!************************************************************
subroutine finish_HiggsBounds
! This subroutine needs to be called right at the end, to close files
! and deallocate arrays
!************************************************************
use usefulbits, only : deallocate_usefulbits,debug,theo,debug, &
& file_id_debug1,file_id_debug2!,inputsub
use S95tables, only : deallocate_S95tables
use theory_BRfunctions, only : deallocate_BRSM
#if defined(NAGf90Fortran)
use F90_UNIX_IO, only : flush
#endif
if(debug)then
close(file_id_debug2)
close(file_id_debug1)
endif
if(.not.allocated(theo))then
stop 'HiggsBounds_initialize should be called first'
endif
if(debug)write(*,*)'finishing off...' ; call flush(6)
call deallocate_BRSM
call deallocate_S95tables
call deallocate_usefulbits
if(debug)write(*,*)'finished' ; call flush(6)
! if(allocated(inputsub)) deallocate(inputsub)
end subroutine finish_HiggsBounds
!
! HB-5 additions
! Do we need control functions to guarantee all theory input is up-to-date and reset?
!subroutine HB5_reset_input
!end subroutine HB5_reset_input
-!************************************************************
-!
-! HB5 GENERAL INPUT ROUTINES
-!
-!************************************************************
-subroutine HB5_neutral_input_properties(Mh,GammaTotal_hj,CP_value)
-!************************************************************
- use usefulbits, only : theo,np,Hneut,just_after_run!,inputsub
-
-#if defined(NAGf90Fortran)
- use F90_UNIX_IO, only : flush
-#endif
-
- implicit none
- !----------------------------------------input
- double precision,intent(in) :: Mh(np(Hneut)),GammaTotal_hj(np(Hneut)),CP_value(np(Hneut))
- !--------------------------------------internal
- integer :: n
-! integer :: subtype
- !----------------------------------------------
-! subtype=1
- n=1
-! inputsub(subtype)%stat=inputsub(subtype)%stat+1
-
- if(.not.allocated(theo))then
- stop 'subroutine HiggsBounds_initialize must be called first'
- endif
-
- if(np(Hneut).eq.0)then
- write(*,*)'subroutine HiggsBounds_neutral_input_mass_width should'
- write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HiggsBounds_neutral_input_mass_width'
- endif
-
- theo(n)%particle(Hneut)%M = Mh
- theo(n)%particle(Hneut)%Mc = Mh
- theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
- theo(n)%CP_value = CP_value
-
- just_after_run=.False.
-
-end subroutine HB5_neutral_input_properties
-!************************************************************
-subroutine HB5_neutral_input_effC( &
- & ghjss_s,ghjss_p,ghjcc_s,ghjcc_p, &
- & ghjbb_s,ghjbb_p,ghjtt_s,ghjtt_p, &
- & ghjmumu_s,ghjmumu_p, &
- & ghjtautau_s,ghjtautau_p, &
- & ghjWW,ghjZZ,ghjZga, &
- & ghjgaga,ghjgg,ghjhiZ)!, &
-! & BR_hjinvisible,BR_hjhihi_nHbynH)
-! New neutral Higgs effective coupling input routine.
-! BR's are set separately.
-!************************************************************
- use usefulbits, only : theo,np,Hneut,effC,whichinput,just_after_run!,inputsub
-
-#if defined(NAGf90Fortran)
- use F90_UNIX_IO, only : flush
-#endif
-
- implicit none
-
- !----------------------------------------input
- double precision,intent(in) :: &!Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) ),&
- & ghjss_s( np(Hneut) ),ghjss_p( np(Hneut) ), &
- & ghjcc_s( np(Hneut) ),ghjcc_p( np(Hneut) ), &
- & ghjbb_s( np(Hneut) ),ghjbb_p( np(Hneut) ), &
- & ghjtt_s( np(Hneut) ),ghjtt_p( np(Hneut) ), &
- & ghjmumu_s( np(Hneut) ),ghjmumu_p( np(Hneut) ), &
- & ghjtautau_s( np(Hneut) ),ghjtautau_p( np(Hneut) ), &
- & ghjWW( np(Hneut) ),ghjZZ( np(Hneut) ),ghjZga( np(Hneut) ), &
- & ghjgaga( np(Hneut) ),ghjgg( np(Hneut) ), &
- & ghjhiZ(np(Hneut),np(Hneut))
-! & BR_hjinvisible( np(Hneut) ),BR_hjhihi_nHbynH(np(Hneut),np(Hneut))
- !--------------------------------------internal
- integer :: n
-! integer :: subtype
- !----------------------------------------------
-
- whichinput='effC'
-! subtype=1
- n=1
-! inputsub(subtype)%stat=inputsub(subtype)%stat+1
-
- if(.not.allocated(theo))then
- stop 'subroutine HiggsBounds_initialize must be called first'
- endif
-
- if(np(Hneut).eq.0)then
- write(*,*)'subroutine HiggsBounds_neutral_input_effC should'
- write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HiggsBounds_neutral_input_effC'
- endif
-
-! theo(n)%particle(Hneut)%M = Mh
-! theo(n)%particle(Hneut)%Mc = Mh
-! theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
-
- effC(n)%hjss_s = ghjss_s
- effC(n)%hjss_p = ghjss_p
- effC(n)%hjcc_s = ghjcc_s
- effC(n)%hjcc_p = ghjcc_p
- effC(n)%hjbb_s = ghjbb_s
- effC(n)%hjbb_p = ghjbb_p
- effC(n)%hjtt_s = ghjtt_s
- effC(n)%hjtt_p = ghjtt_p
- effC(n)%hjmumu_s = ghjmumu_s
- effC(n)%hjmumu_p = ghjmumu_p
- effC(n)%hjtautau_s = ghjtautau_s
- effC(n)%hjtautau_p = ghjtautau_p
-
- effC(n)%hjWW = ghjWW
- effC(n)%hjZZ = ghjZZ
- effC(n)%hjZga = ghjZga
- effC(n)%hjgaga = ghjgaga
- effC(n)%hjgg = ghjgg
-! g2(n)%hjggZ = g2hjggZ
-
- effC(n)%hjhiZ = ghjhiZ
-
-! theo(n)%BR_hjinvisible = BR_hjinvisible
-! theo(n)%BR_hjhihi = BR_hjhihi_nHbynH
-
- just_after_run=.False.
-
-end subroutine HB5_neutral_input_effC
-!************************************************************
-subroutine HB5_neutral_input_SMBR(BR_hjss,BR_hjcc,BR_hjbb, &
- & BR_hjtt,BR_hjmumu, &
- & BR_hjtautau,BR_hjWW, &
- & BR_hjZZ,BR_hjZga,BR_hjgaga, &
- & BR_hjgg)
-! Input for the SM branching ratios
-!************************************************************
- use usefulbits, only : theo,np,Hneut,whichinput,just_after_run,BRdirectinput
-
-#if defined(NAGf90Fortran)
- use F90_UNIX_IO, only : flush
-#endif
-
- implicit none
- !----------------------------------------input
- double precision,intent(in) :: BR_hjss( np(Hneut) ),BR_hjcc( np(Hneut) ), &
- & BR_hjbb( np(Hneut) ),BR_hjtt( np(Hneut) ), &
- & BR_hjmumu( np(Hneut) ),BR_hjtautau( np(Hneut) ), &
- & BR_hjWW( np(Hneut) ),BR_hjZZ( np(Hneut) ), &
- & BR_hjZga( np(Hneut) ),BR_hjgaga( np(Hneut) ), &
- & BR_hjgg( np(Hneut) )
- !-------------------------------------internal
- integer :: n
- !---------------------------------------------
-
- n=1
-
- if(.not.allocated(theo))then
- stop 'subroutine HiggsBounds_initialize must be called first'
- endif
-
- if(np(Hneut).eq.0)then
- write(*,*)'subroutine HiggsBounds_neutral_input_SMBR should'
- write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HiggsBounds_neutral_input_SMBR'
- endif
-!
- theo(n)%BR_hjss = BR_hjss
- theo(n)%BR_hjcc = BR_hjcc
- theo(n)%BR_hjbb = BR_hjbb
- theo(n)%BR_hjtt = BR_hjtt
- theo(n)%BR_hjmumu = BR_hjmumu
- theo(n)%BR_hjtautau = BR_hjtautau
- theo(n)%BR_hjWW = BR_hjWW
- theo(n)%BR_hjZZ = BR_hjZZ
- theo(n)%BR_hjZga = BR_hjZga
- theo(n)%BR_hjgaga = BR_hjgaga
- theo(n)%BR_hjgg = BR_hjgg
-
- just_after_run=.False.
- BRdirectinput=.True.
-
-end subroutine HB5_neutral_input_SMBR
-!************************************************************
-subroutine HB5_neutral_input_nonSMBR(BR_hjinvisible,BR_hkhjhi,BR_hjhiZ,&
-& BR_hjemu,BR_hjetau,BR_hjmutau)
-! Input for the non-SM branching ratios
-!************************************************************
- use usefulbits, only : theo,np,Hneut,whichinput,just_after_run!,inputsub
-
-#if defined(NAGf90Fortran)
- use F90_UNIX_IO, only : flush
-#endif
-
- implicit none
-
- !----------------------------------------input
- double precision,intent(in) :: BR_hjinvisible( np(Hneut) ), &
- & BR_hkhjhi(np(Hneut),np(Hneut),np(Hneut)), &
- & BR_hjhiZ(np(Hneut),np(Hneut)), &
- & BR_hjemu(np(Hneut)),&
- & BR_hjetau(np(Hneut)),&
- & BR_hjmutau(np(Hneut))
- !--------------------------------------internal
- integer :: n
-! integer :: k,j
-! integer :: subtype
- !----------------------------------------------
-! subtype=1
- n=1
-! inputsub(subtype)%stat=inputsub(subtype)%stat+1
-
- if(.not.allocated(theo))then
- stop 'subroutine HiggsBounds_initialize must be called first'
- endif
-
- if(np(Hneut).eq.0)then
- write(*,*)'subroutine HiggsBounds_neutral_input_nonSMBR should'
- write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HiggsBounds_neutral_input_nonSMBR'
- endif
-
-! write(*,*) "# ----- debugging HB5_neutral_input_non_SMBR ----- #"
-! do k=1,np(Hneut)
-! do j=1,np(Hneut)
-! write(*,*) "BR(hk->hjh:)",k,j,BR_hkhjhi(k,j,:)
-! enddo
-! enddo
-! write(*,*) "# ----- end debugging ----- #"
-
- theo(n)%BR_hjinvisible = BR_hjinvisible
- theo(n)%BR_hkhjhi = BR_hkhjhi
- theo(n)%BR_hjhiZ = BR_hjhiZ
- theo(n)%BR_hjemu = BR_hjemu
- theo(n)%BR_hjetau = BR_hjetau
- theo(n)%BR_hjmutau = BR_hjmutau
-
- just_after_run=.False.
-
-end subroutine HB5_neutral_input_nonSMBR
-!************************************************************
-subroutine HB5_neutral_input_hadr(collider,CS_hj_ratio, &
- & CS_gg_hj_ratio,CS_bb_hj_ratio, &
- & CS_hjW_ratio,CS_hjZ_ratio, &
- & CS_vbf_ratio,CS_tthj_ratio, &
- & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
- & CS_hjhi)
-!************************************************************
- use usefulbits, only : theo,np,Hneut,whichinput,just_after_run,hadroncolliderdataset
-
-#if defined(NAGf90Fortran)
- use F90_UNIX_IO, only : flush
-#endif
-
- implicit none
- double precision,intent(in) :: CS_hj_ratio( np(Hneut) ), &
- & CS_gg_hj_ratio( np(Hneut) ),CS_bb_hj_ratio( np(Hneut) ), &
- & CS_hjW_ratio( np(Hneut) ) ,CS_hjZ_ratio( np(Hneut) ), &
- & CS_vbf_ratio( np(Hneut) ) ,CS_tthj_ratio( np(Hneut) ), &
- & CS_thj_tchan_ratio( np(Hneut) ),CS_thj_schan_ratio( np(Hneut) ), &
- & CS_hjhi( np(Hneut), np(Hneut) )
- integer, intent(in) :: collider
- !-------------------------------------internal
- integer :: n
-! type(hadroncolliderdataset) :: dataset
- !---------------------------------------------
- whichinput='hadr'
- n=1
-
- if(.not.allocated(theo))then
- stop 'subroutine HiggsBounds_initialize must be called first'
- endif
-
- if(np(Hneut).eq.0)then
- write(*,*)'subroutine HiggsBounds_neutral_input_hadr should'
- write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HiggsBounds_neutral_input_hadr'
- endif
-
- select case(collider)
- case(2)
- call set_input(theo(n)%tev,CS_hj_ratio, &
- & CS_gg_hj_ratio,CS_bb_hj_ratio, &
- & CS_hjW_ratio,CS_hjZ_ratio, &
- & CS_vbf_ratio,CS_tthj_ratio, &
- & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
- & CS_hjhi)
- case(7)
- call set_input(theo(n)%lhc7,CS_hj_ratio, &
- & CS_gg_hj_ratio,CS_bb_hj_ratio, &
- & CS_hjW_ratio,CS_hjZ_ratio, &
- & CS_vbf_ratio,CS_tthj_ratio, &
- & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
- & CS_hjhi)
- case(8)
- call set_input(theo(n)%lhc8,CS_hj_ratio, &
- & CS_gg_hj_ratio,CS_bb_hj_ratio, &
- & CS_hjW_ratio,CS_hjZ_ratio, &
- & CS_vbf_ratio,CS_tthj_ratio, &
- & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
- & CS_hjhi)
- case(13)
- call set_input(theo(n)%lhc13,CS_hj_ratio, &
- & CS_gg_hj_ratio,CS_bb_hj_ratio, &
- & CS_hjW_ratio,CS_hjZ_ratio, &
- & CS_vbf_ratio,CS_tthj_ratio, &
- & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
- & CS_hjhi)
- case default
- stop 'wrong input for collider to subroutine HB5_neutral_input_hadr'
- end select
-
- just_after_run=.False.
-
- contains
-
- subroutine set_input(dataset,CS_hj_ratio, &
- & CS_gg_hj_ratio,CS_bb_hj_ratio, &
- & CS_hjW_ratio,CS_hjZ_ratio, &
- & CS_vbf_ratio,CS_tthj_ratio, &
- & CS_thj_tchan_ratio,CS_thj_schan_ratio, &
- & CS_hjhi)
-
- implicit none
- double precision,intent(in) :: CS_hj_ratio( np(Hneut) ), &
- & CS_gg_hj_ratio( np(Hneut) ),CS_bb_hj_ratio( np(Hneut) ), &
- & CS_hjW_ratio( np(Hneut) ) ,CS_hjZ_ratio( np(Hneut) ), &
- & CS_vbf_ratio( np(Hneut) ) ,CS_tthj_ratio( np(Hneut) ), &
- & CS_thj_tchan_ratio( np(Hneut) ),CS_thj_schan_ratio( np(Hneut) ), &
- & CS_hjhi( np(Hneut), np(Hneut) )
- type(hadroncolliderdataset) :: dataset
-
- dataset%XS_hj_ratio = CS_hj_ratio
- dataset%XS_gg_hj_ratio = CS_gg_hj_ratio
- dataset%XS_bb_hj_ratio = CS_bb_hj_ratio
- dataset%XS_hjW_ratio = CS_hjW_ratio
- dataset%XS_hjZ_ratio = CS_hjZ_ratio
- dataset%XS_vbf_ratio = CS_vbf_ratio
- dataset%XS_tthj_ratio = CS_tthj_ratio
- dataset%XS_thj_tchan_ratio = CS_thj_tchan_ratio
- dataset%XS_thj_schan_ratio = CS_thj_schan_ratio
- dataset%XS_hjhi = CS_hjhi
-
- end subroutine set_input
-
-end subroutine HB5_neutral_input_hadr
-!************************************************************
-subroutine HB5_charged_input_hadr(collider, CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
-! This subroutine can be called by the user after subroutine initialize_HiggsBounds
-! has been called.
-! Arguments (input): theoretical predictions (see manual for definitions)
-!************************************************************
- use usefulbits, only : theo,np,Hplus,Hneut,just_after_run,hadroncolliderdataset!,inputsub
-
-#if defined(NAGf90Fortran)
- use F90_UNIX_IO, only : flush
-#endif
-
- implicit none
-
- !----------------------------------------input
- double precision,intent(in) :: CS_Hpjtb( np(Hplus) ), CS_Hpjbjet( np(Hplus) ),&
-& CS_HpjW( np(Hplus) ), CS_HpjZ( np(Hplus) ),&
-& CS_vbf_Hpj( np(Hplus) ), CS_HpjHmj( np(Hplus) )
- integer, intent(in) :: collider
- double precision,optional,intent(in) :: CS_Hpjhi( np(Hplus),np(Hneut) )
- !--------------------------------------internal
- integer :: n
-! integer :: subtype
- !----------------------------------------------
- n=1
-! subtype=2
-! inputsub(subtype)%stat=inputsub(subtype)%stat+1
-
- if(.not.allocated(theo))then
- stop 'subroutine HiggsBounds_initialize must be called first'
- endif
-
- if(np(Hplus).eq.0)then
- write(*,*)'subroutine HiggsBounds_charged_input should'
- write(*,*)'only be called if np(Hplus)>0'
- stop 'error in subroutine HiggsBounds_charged_input'
- endif
-
- select case(collider)
- case(2)
- if(present(CS_Hpjhi)) then
- call set_input(theo(n)%tev,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
- else
- call set_input(theo(n)%tev,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj)
- endif
- case(7)
- if(present(CS_Hpjhi)) then
- call set_input(theo(n)%lhc7,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
- else
- call set_input(theo(n)%lhc7,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj)
- endif
- case(8)
- if(present(CS_Hpjhi)) then
- call set_input(theo(n)%lhc8,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
- else
- call set_input(theo(n)%lhc8,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj)
- endif
- case(13)
- if(present(CS_Hpjhi)) then
- call set_input(theo(n)%lhc13,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
- else
- call set_input(theo(n)%lhc13,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj)
- endif
- case default
- stop 'wrong input for collider to subroutine HB5_charged_input_hadr'
- end select
-
- just_after_run=.False.
-
- contains
-
- subroutine set_input(dataset,CS_Hpjtb, CS_Hpjbjet, CS_HpjW, &
-& CS_HpjZ, CS_vbf_Hpj, CS_HpjHmj, CS_Hpjhi)
-
- double precision,intent(in) :: CS_Hpjtb( np(Hplus) ), CS_Hpjbjet( np(Hplus) ),&
-& CS_HpjW( np(Hplus) ), CS_HpjZ( np(Hplus) ),&
-& CS_vbf_Hpj( np(Hplus) ), CS_HpjHmj( np(Hplus) )
- double precision,optional,intent(in) :: CS_Hpjhi( np(Hplus),np(Hneut) )
- type(hadroncolliderdataset) :: dataset
-
- dataset%XS_Hpjtb = CS_Hpjtb
- dataset%XS_Hpjbjet = CS_Hpjbjet
- dataset%XS_vbf_Hpj = CS_vbf_Hpj
- dataset%XS_HpjW = CS_HpjW
- dataset%XS_HpjZ = CS_HpjZ
- dataset%XS_HpjHmj = CS_HpjHmj
- if(present(CS_Hpjhi)) then
- dataset%XS_Hpjhi = CS_Hpjhi
- endif
-
- end subroutine set_input
-end subroutine HB5_charged_input_hadr
-!************************************************************
!************************************************************
!
! SIMPLIFIED EFFC INPUT ROUTINES
!
!************************************************************
-subroutine HB5_neutral_input_effC_single(quantity,val)
+subroutine HiggsBounds_neutral_input_effC_single(quantity,val)
!************************************************************
use usefulbits, only : theo,np,Hneut,effC,whichinput,just_after_run!,inputsub
implicit none
!---------------------------------------------
character(LEN=*), intent(in) :: quantity
double precision, intent(in) :: val(np(Hneut))
!-------------------------------------internal
integer :: n
! integer :: subtype
!---------------------------------------------
whichinput='effC'
! subtype=1
n=1
! inputsub(subtype)%stat=inputsub(subtype)%stat+1 ! WHAT IS THIS DOING?
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hneut).eq.0)then
- write(*,*)'subroutine HB5_neutral_input_effC_single should'
+ write(*,*)'subroutine HiggsBounds_neutral_input_effC_single should'
write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HB5_neutral_input_effC_single'
+ stop 'error in subroutine HiggsBounds_neutral_input_effC_single'
endif
select case(trim(adjustl(quantity)))
case("ghjcc_s")
effC(n)%hjcc_s=val
case("ghjcc_p")
effC(n)%hjcc_p=val
case("ghjss_s")
effC(n)%hjss_s=val
case("ghjss_p")
effC(n)%hjss_p=val
case("ghjbb_s")
effC(n)%hjbb_s=val
case("ghjbb_p")
effC(n)%hjbb_p=val
case("ghjtt_s")
effC(n)%hjtt_s=val
case("ghjtt_p")
effC(n)%hjtt_p=val
case("ghjmumu_s")
effC(n)%hjmumu_s=val
case("ghjmumu_p")
effC(n)%hjmumu_p=val
case("ghjtautau_s")
effC(n)%hjtautau_s=val
case("ghjtautau_p")
effC(n)%hjtautau_p=val
case("ghjWW")
effC(n)%hjWW=val
case("ghjZZ")
effC(n)%hjZZ=val
case("ghjZga")
effC(n)%hjZga=val
case("ghjgaga")
effC(n)%hjgaga=val
case("ghjgg")
effC(n)%hjgg=val
case default
- stop 'wrong input for quantity to subroutine HB5_neutral_input_effC_single'
+ stop 'wrong input for quantity to subroutine HiggsBounds_neutral_input_effC_single'
end select
just_after_run=.False.
-end subroutine HB5_neutral_input_effC_single
+end subroutine HiggsBounds_neutral_input_effC_single
!************************************************************
-subroutine HB5_neutral_input_effC_double(quantity,val)
+subroutine HiggsBounds_neutral_input_effC_double(quantity,val)
!************************************************************
use usefulbits, only : theo,np,Hneut,effC,whichinput,just_after_run!,inputsub
implicit none
!---------------------------------------------
character(LEN=*), intent(in) :: quantity
double precision, intent(in) :: val(np(Hneut),np(Hneut))
!-------------------------------------internal
integer :: n
! integer :: subtype
!---------------------------------------------
whichinput='effC'
! subtype=1
n=1
! inputsub(subtype)%stat=inputsub(subtype)%stat+1 ! WHAT IS THIS DOING?
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hneut).eq.0)then
- write(*,*)'subroutine HB5_neutral_input_effC_double should'
+ write(*,*)'subroutine HiggsBounds_neutral_input_effC_double should'
write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HB5_neutral_input_effC_double'
+ stop 'error in subroutine HiggsBounds_neutral_input_effC_double'
endif
select case(trim(adjustl(quantity)))
case("ghjhiZ")
effC(n)%hjhiZ = val
case default
- stop 'wrong input for quantity to subroutine HB5_neutral_input_effC_double'
+ stop 'wrong input for quantity to subroutine HiggsBounds_neutral_input_effC_double'
end select
just_after_run=.False.
-end subroutine HB5_neutral_input_effC_double
+end subroutine HiggsBounds_neutral_input_effC_double
!************************************************************
!
! SIMPLIFIED LEP/HADRONIC XS INPUT ROUTINES
!
!************************************************************
-subroutine HB5_neutral_input_LEP_single(quantity,val)
+subroutine HiggsBounds_neutral_input_LEP_single(quantity,val)
!************************************************************
use usefulbits, only : theo,np,Hneut,whichinput,just_after_run!,inputsub
implicit none
!---------------------------------------------
character(LEN=*), intent(in) :: quantity
double precision, intent(in) :: val(np(Hneut))
!-------------------------------------internal
integer :: n
! integer :: subtype
!---------------------------------------------
whichinput='hadr'
! subtype=1
n=1
! inputsub(subtype)%stat=inputsub(subtype)%stat+1 ! WHAT IS THIS DOING?
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hneut).eq.0)then
- write(*,*)'subroutine HB5_neutral_input_LEP_single should'
+ write(*,*)'subroutine HiggsBounds_neutral_input_LEP_single should'
write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HB5_neutral_input_LEP_single'
+ stop 'error in subroutine HiggsBounds_neutral_input_LEP_single'
endif
select case(trim(adjustl(quantity)))
case("XS_hjZ_ratio")
theo(n)%lep%XS_hjZ_ratio = val
case("XS_bbhj_ratio")
theo(n)%lep%XS_bbhj_ratio = val
case("XS_tautauhj_ratio")
theo(n)%lep%XS_tautauhj_ratio = val
case default
- stop 'wrong input for quantity to subroutine HB5_neutral_input_LEP_single'
+ stop 'wrong input for quantity to subroutine HiggsBounds_neutral_input_LEP_single'
end select
just_after_run=.False.
-end subroutine HB5_neutral_input_LEP_single
+end subroutine HiggsBounds_neutral_input_LEP_single
!************************************************************
-subroutine HB5_neutral_input_LEP_double(quantity,val)
+subroutine HiggsBounds_neutral_input_LEP_double(quantity,val)
!************************************************************
use usefulbits, only : theo,np,Hneut,whichinput,just_after_run!,inputsub
implicit none
!---------------------------------------------
character(LEN=*), intent(in) :: quantity
double precision, intent(in) :: val(np(Hneut),np(Hneut))
!-------------------------------------internal
integer :: n
! integer :: subtype
!---------------------------------------------
whichinput='hadr'
! subtype=1
n=1
! inputsub(subtype)%stat=inputsub(subtype)%stat+1 ! WHAT IS THIS DOING?
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hneut).eq.0)then
- write(*,*)'subroutine HB5_neutral_input_LEP_double should'
+ write(*,*)'subroutine HiggsBounds_neutral_input_LEP_double should'
write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HB5_neutral_input_LEP_double'
+ stop 'error in subroutine HiggsBounds_neutral_input_LEP_double'
endif
select case(trim(adjustl(quantity)))
case("XS_hjhi_ratio")
theo(n)%lep%XS_hjhi_ratio = val
case default
- stop 'wrong input for quantity to subroutine HB5_neutral_input_LEP_double'
+ stop 'wrong input for quantity to subroutine HiggsBounds_neutral_input_LEP_double'
end select
just_after_run=.False.
-end subroutine HB5_neutral_input_LEP_double
+end subroutine HiggsBounds_neutral_input_LEP_double
!************************************************************
-subroutine HB5_neutral_input_hadr_single(collider,quantity,val)
+subroutine HiggsBounds_neutral_input_hadr_single(collider,quantity,val)
!************************************************************
use usefulbits, only : theo,np,Hneut,whichinput,just_after_run, &
& hadroncolliderdataset !,inputsub
implicit none
!---------------------------------------------
integer, intent(in) :: collider
character(LEN=*), intent(in) :: quantity
double precision, intent(in) :: val(np(Hneut))
!-------------------------------------internal
integer :: n
! integer :: subtype
! type(hadroncolliderdataset) :: dataset
!---------------------------------------------
whichinput='hadr'
! subtype=1
n=1
! inputsub(subtype)%stat=inputsub(subtype)%stat+1 ! WHAT IS THIS DOING?
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hneut).eq.0)then
- write(*,*)'subroutine HB5_neutral_input_hadr_single should'
+ write(*,*)'subroutine HiggsBounds_neutral_input_hadr_single should'
write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HB5_neutral_input_hadr_single'
+ stop 'error in subroutine HiggsBounds_neutral_input_hadr_single'
endif
select case(collider)
case(2)
call set_input(theo(n)%tev,quantity,val)
case(7)
call set_input(theo(n)%lhc7,quantity,val)
case(8)
call set_input(theo(n)%lhc8,quantity,val)
case(13)
call set_input(theo(n)%lhc13,quantity,val)
case default
- stop 'wrong input for collider to subroutine HB5_neutral_input_hadr_single'
+ stop 'wrong input for collider to subroutine HiggsBounds_neutral_input_hadr_single'
end select
just_after_run=.False.
contains
subroutine set_input(dataset,quantity,val)
character(LEN=*), intent(in) :: quantity
double precision, intent(in) :: val(np(Hneut))
type(hadroncolliderdataset) :: dataset
select case(trim(adjustl(quantity)))
case("XS_gg_hj_ratio")
dataset%XS_gg_hj_ratio=val
case("XS_bb_hj_ratio")
dataset%XS_bb_hj_ratio=val
dataset%XS_hjb_ratio=val
case("XS_vbf_ratio")
dataset%XS_vbf_ratio=val
case("XS_hjZ_ratio")
dataset%XS_hjZ_ratio=val
case("XS_hjW_ratio")
dataset%XS_hjW_ratio=val
case("XS_tthj_ratio")
dataset%XS_tthj_ratio=val
case("XS_thj_tchan_ratio")
dataset%XS_thj_tchan_ratio=val
case("XS_thj_schan_ratio")
dataset%XS_thj_schan_ratio=val
case default
- stop 'wrong input for quantity to subroutine HB5_neutral_input_hadr_single'
+ stop 'wrong input for quantity to subroutine HiggsBounds_neutral_input_hadr_single'
end select
end subroutine set_input
-end subroutine HB5_neutral_input_hadr_single
+end subroutine HiggsBounds_neutral_input_hadr_single
!************************************************************
-subroutine HB5_neutral_input_hadr_double(collider,quantity,val)
+subroutine HiggsBounds_neutral_input_hadr_double(collider,quantity,val)
!************************************************************
use usefulbits, only : theo,np,Hneut,whichinput,just_after_run, &
& hadroncolliderdataset! ,inputsub
implicit none
!---------------------------------------------
integer, intent(in) :: collider
character(LEN=*), intent(in) :: quantity
double precision, intent(in) :: val(np(Hneut),np(Hneut))
!-------------------------------------internal
integer :: n
!---------------------------------------------
whichinput='hadr'
n=1
if(.not.allocated(theo))then
stop 'subroutine HiggsBounds_initialize must be called first'
endif
if(np(Hneut).eq.0)then
- write(*,*)'subroutine HB5_neutral_input_hadr_double should'
+ write(*,*)'subroutine HiggsBounds_neutral_input_hadr_double should'
write(*,*)'only be called if np(Hneut)>0'
- stop 'error in subroutine HB5_neutral_input_hadr_double'
+ stop 'error in subroutine HiggsBounds_neutral_input_hadr_double'
endif
select case(trim(adjustl(quantity)))
case("XS_hjhi")
select case(collider)
case(2)
theo(n)%tev%XS_hjhi=val
case(7)
theo(n)%lhc7%XS_hjhi=val
case(8)
theo(n)%lhc8%XS_hjhi=val
case(13)
theo(n)%lhc13%XS_hjhi=val
case default
- stop 'wrong input for collider to subroutine HB5_neutral_input_hadr_double'
+ stop 'wrong input for collider to subroutine HiggsBounds_neutral_input_hadr_double'
end select
case default
- stop 'wrong input for quantity to subroutine HB5_neutral_input_hadr_double'
+ stop 'wrong input for quantity to subroutine HiggsBounds_neutral_input_hadr_double'
end select
just_after_run=.False.
-end subroutine HB5_neutral_input_hadr_double
-!************************************************************
\ No newline at end of file
+end subroutine HiggsBounds_neutral_input_hadr_double
+!************************************************************
+! HB-4 legacy routines
+!************************************************************
+! subroutine HiggsBounds_neutral_input_effC(Mh,GammaTotal_hj, &
+! & g2hjss_s,g2hjss_p,g2hjcc_s,g2hjcc_p, &
+! & g2hjbb_s,g2hjbb_p,g2hjtoptop_s,g2hjtoptop_p, &
+! & g2hjmumu_s,g2hjmumu_p, &
+! & g2hjtautau_s,g2hjtautau_p, &
+! & g2hjWW,g2hjZZ,g2hjZga, &
+! & g2hjgaga,g2hjgg,g2hjggZ,g2hjhiZ_nHbynH, &
+! & BR_hjinvisible,BR_hjhihi_nHbynH )
+! ! This subroutine can be called by the user after subroutine initialize_HiggsBounds
+! ! has been called.
+! ! Arguments (input): theoretical predictions (see manual for definitions)
+! !************************************************************
+! use usefulbits, only : theo,np,Hneut,g2,whichinput,just_after_run!,inputsub
+!
+! #if defined(NAGf90Fortran)
+! use F90_UNIX_IO, only : flush
+! #endif
+!
+! implicit none
+!
+! !----------------------------------------input
+! double precision,intent(in) :: Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) ), &
+! & g2hjss_s( np(Hneut) ),g2hjss_p( np(Hneut) ),g2hjcc_s( np(Hneut) ),g2hjcc_p( np(Hneut) ), &
+! & g2hjbb_s( np(Hneut) ),g2hjbb_p( np(Hneut) ),g2hjtoptop_s( np(Hneut) ),g2hjtoptop_p( np(Hneut) ),&
+! & g2hjmumu_s( np(Hneut) ),g2hjmumu_p( np(Hneut) ), &
+! & g2hjtautau_s( np(Hneut) ),g2hjtautau_p( np(Hneut) ), &
+! & g2hjWW( np(Hneut) ),g2hjZZ( np(Hneut) ),g2hjZga( np(Hneut) ), &
+! & g2hjgaga( np(Hneut) ),g2hjgg( np(Hneut) ),g2hjggZ( np(Hneut) ),g2hjhiZ_nHbynH(np(Hneut),np(Hneut)),&
+! & BR_hjinvisible( np(Hneut) ),BR_hjhihi_nHbynH(np(Hneut),np(Hneut))
+! !--------------------------------------internal
+! integer :: n
+! ! integer :: subtype
+! !----------------------------------------------
+!
+! whichinput='effC'
+! ! subtype=1
+! n=1
+! ! inputsub(subtype)%stat=inputsub(subtype)%stat+1
+!
+! if(.not.allocated(theo))then
+! stop 'subroutine HiggsBounds_initialize must be called first'
+! endif
+!
+! if(np(Hneut).eq.0)then
+! write(*,*)'subroutine HiggsBounds_neutral_input_effC should'
+! write(*,*)'only be called if np(Hneut)>0'
+! stop 'error in subroutine HiggsBounds_neutral_input_effC'
+! endif
+!
+! theo(n)%particle(Hneut)%M = Mh
+! theo(n)%particle(Hneut)%Mc = Mh
+! theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
+!
+! g2(n)%hjss_s = g2hjss_s
+! g2(n)%hjss_p = g2hjss_p
+! g2(n)%hjcc_s = g2hjcc_s
+! g2(n)%hjcc_p = g2hjcc_p
+! g2(n)%hjbb_s = g2hjbb_s
+! g2(n)%hjbb_p = g2hjbb_p
+! g2(n)%hjtoptop_s = g2hjtoptop_s
+! g2(n)%hjtoptop_p = g2hjtoptop_p
+! g2(n)%hjmumu_s = g2hjmumu_s
+! g2(n)%hjmumu_p = g2hjmumu_p
+! g2(n)%hjtautau_s = g2hjtautau_s
+! g2(n)%hjtautau_p = g2hjtautau_p
+!
+! g2(n)%hjWW = g2hjWW
+! g2(n)%hjZZ = g2hjZZ
+! g2(n)%hjZga = g2hjZga
+! g2(n)%hjgaga = g2hjgaga
+! g2(n)%hjgg = g2hjgg
+! g2(n)%hjggZ = g2hjggZ
+!
+! g2(n)%hjhiZ = g2hjhiZ_nHbynH
+!
+! theo(n)%BR_hjinvisible = BR_hjinvisible
+! theo(n)%BR_hjhihi = BR_hjhihi_nHbynH
+!
+! just_after_run=.False.
+!
+! end subroutine HiggsBounds_neutral_input_effC
+! !************************************************************
+! subroutine HiggsBounds_neutral_input_part(Mh,GammaTotal_hj,CP_value, &
+! & CS_lep_hjZ_ratio, &
+! & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio, &
+! & CS_lep_hjhi_ratio_nHbynH, &
+! & CS_gg_hj_ratio,CS_bb_hj_ratio, &
+! & CS_bg_hjb_ratio, &
+! & CS_ud_hjWp_ratio,CS_cs_hjWp_ratio, &
+! & CS_ud_hjWm_ratio,CS_cs_hjWm_ratio, &
+! & CS_gg_hjZ_ratio, &
+! & CS_dd_hjZ_ratio,CS_uu_hjZ_ratio, &
+! & CS_ss_hjZ_ratio,CS_cc_hjZ_ratio, &
+! & CS_bb_hjZ_ratio, &
+! & CS_tev_vbf_ratio,CS_tev_tthj_ratio, &
+! & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio, &
+! & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio, &
+! & BR_hjss,BR_hjcc, &
+! & BR_hjbb,BR_hjmumu,BR_hjtautau, &
+! & BR_hjWW,BR_hjZZ,BR_hjZga, BR_hjgaga,BR_hjgg, &
+! & BR_hjinvisible,BR_hjhihi_nHbynH )
+! ! This subroutine can be called by the user after subroutine initialize_HiggsBounds
+! ! has been called.
+! ! (see manual for full description)
+! !************************************************************
+! use usefulbits, only : theo,np,Hneut,partR,whichinput,just_after_run!,inputsub
+!
+! #if defined(NAGf90Fortran)
+! use F90_UNIX_IO, only : flush
+! #endif
+!
+! implicit none
+! !----------------------------------------input
+! double precision,intent(in) :: Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) )
+! integer,intent(in) ::CP_value( np(Hneut) )
+! double precision,intent(in) :: CS_lep_hjZ_ratio( np(Hneut) ), &
+! & CS_lep_bbhj_ratio( np(Hneut) ),CS_lep_tautauhj_ratio( np(Hneut) ), &
+! & CS_lep_hjhi_ratio_nHbynH(np(Hneut),np(Hneut)), &
+! & CS_gg_hj_ratio( np(Hneut) ),CS_bb_hj_ratio( np(Hneut) ), &
+! & CS_bg_hjb_ratio( np(Hneut) ), &
+! & CS_ud_hjWp_ratio( np(Hneut) ),CS_cs_hjWp_ratio( np(Hneut) ), &
+! & CS_ud_hjWm_ratio( np(Hneut) ),CS_cs_hjWm_ratio( np(Hneut) ), &
+! & CS_gg_hjZ_ratio( np(Hneut) ), &
+! & CS_dd_hjZ_ratio( np(Hneut) ),CS_uu_hjZ_ratio( np(Hneut) ), &
+! & CS_ss_hjZ_ratio( np(Hneut) ),CS_cc_hjZ_ratio( np(Hneut) ), &
+! & CS_bb_hjZ_ratio( np(Hneut) ), &
+! & CS_tev_vbf_ratio( np(Hneut) ),CS_tev_tthj_ratio( np(Hneut) ), &
+! & CS_lhc7_vbf_ratio( np(Hneut) ),CS_lhc7_tthj_ratio( np(Hneut) ), &
+! & CS_lhc8_vbf_ratio( np(Hneut) ),CS_lhc8_tthj_ratio( np(Hneut) ), &
+! & BR_hjss( np(Hneut) ),BR_hjcc( np(Hneut) ), &
+! & BR_hjbb( np(Hneut) ),BR_hjmumu( np(Hneut) ),BR_hjtautau( np(Hneut) ), &
+! & BR_hjWW( np(Hneut) ),BR_hjZZ( np(Hneut) ),BR_hjZga( np(Hneut) ), &
+! & BR_hjgaga( np(Hneut) ),BR_hjgg( np(Hneut) ), &
+! & BR_hjinvisible( np(Hneut) ),BR_hjhihi_nHbynH(np(Hneut),np(Hneut))
+! !---------------------------------------internal
+! integer :: n
+! ! integer :: subtype
+! !-----------------------------------------------
+!
+! whichinput='part'
+! ! subtype=1
+! n=1
+! ! inputsub(subtype)%stat=inputsub(subtype)%stat+1
+!
+! if(.not.allocated(theo))then
+! stop 'subroutine HiggsBounds_initialize must be called first'
+! endif
+!
+! if(np(Hneut).eq.0)then
+! write(*,*)'subroutine HiggsBounds_neutral_input_part should'
+! write(*,*)'only be called if np(Hneut)>0'
+! stop 'error in subroutine HiggsBounds_neutral_input_part'
+! endif
+!
+! theo(n)%particle(Hneut)%M = Mh
+! theo(n)%particle(Hneut)%Mc = Mh
+! theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
+! theo(n)%CP_value = CP_value
+! theo(n)%lep%XS_hjZ_ratio = CS_lep_hjZ_ratio
+! theo(n)%lep%XS_bbhj_ratio = CS_lep_bbhj_ratio
+! theo(n)%lep%XS_tautauhj_ratio = CS_lep_tautauhj_ratio
+! theo(n)%lep%XS_hjhi_ratio = CS_lep_hjhi_ratio_nHbynH
+! partR(n)%gg_hj = CS_gg_hj_ratio
+! partR(n)%qq_hj(5,:) = CS_bb_hj_ratio
+! partR(n)%bg_hjb = CS_bg_hjb_ratio
+! partR(n)%qq_hjWp(1,:) = CS_ud_hjWp_ratio
+! partR(n)%qq_hjWp(2,:) = CS_cs_hjWp_ratio
+! partR(n)%qq_hjWm(1,:) = CS_ud_hjWm_ratio
+! partR(n)%qq_hjWm(2,:) = CS_cs_hjWm_ratio
+! partR(n)%gg_hjZ(:) = CS_gg_hjZ_ratio
+! partR(n)%qq_hjZ(1,:) = CS_dd_hjZ_ratio
+! partR(n)%qq_hjZ(2,:) = CS_uu_hjZ_ratio
+! partR(n)%qq_hjZ(3,:) = CS_ss_hjZ_ratio
+! partR(n)%qq_hjZ(4,:) = CS_cc_hjZ_ratio
+! partR(n)%qq_hjZ(5,:) = CS_bb_hjZ_ratio
+! theo(n)%tev%XS_vbf_ratio = CS_tev_vbf_ratio
+! theo(n)%tev%XS_tthj_ratio = CS_tev_tthj_ratio
+! theo(n)%lhc7%XS_vbf_ratio = CS_lhc7_vbf_ratio
+! theo(n)%lhc7%XS_tthj_ratio= CS_lhc7_tthj_ratio
+! theo(n)%lhc8%XS_vbf_ratio = CS_lhc8_vbf_ratio
+! theo(n)%lhc8%XS_tthj_ratio= CS_lhc8_tthj_ratio
+! theo(n)%BR_hjss = BR_hjss
+! theo(n)%BR_hjcc = BR_hjcc
+! theo(n)%BR_hjbb = BR_hjbb
+! theo(n)%BR_hjmumu = BR_hjmumu
+! theo(n)%BR_hjtautau = BR_hjtautau
+! theo(n)%BR_hjWW = BR_hjWW
+! theo(n)%BR_hjZZ = BR_hjZZ
+! theo(n)%BR_hjZga = BR_hjZga
+! theo(n)%BR_hjgaga = BR_hjgaga
+! theo(n)%BR_hjgg = BR_hjgg
+! theo(n)%BR_hjinvisible = BR_hjinvisible
+! theo(n)%BR_hjhihi = BR_hjhihi_nHbynH
+!
+! just_after_run=.False.
+!
+! end subroutine HiggsBounds_neutral_input_part
+! !************************************************************
+! subroutine HiggsBounds_neutral_input_hadr(Mh,GammaTotal_hj,CP_value, &
+! & CS_lep_hjZ_ratio, &
+! & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio, &
+! & CS_lep_hjhi_ratio_nHbynH, &
+! & CS_tev_hj_ratio ,CS_tev_hjb_ratio, &
+! & CS_tev_hjW_ratio,CS_tev_hjZ_ratio, &
+! & CS_tev_vbf_ratio,CS_tev_tthj_ratio, &
+! & CS_lhc7_hj_ratio ,CS_lhc7_hjb_ratio, &
+! & CS_lhc7_hjW_ratio,CS_lhc7_hjZ_ratio, &
+! & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio, &
+! & CS_lhc8_hj_ratio ,CS_lhc8_hjb_ratio, &
+! & CS_lhc8_hjW_ratio,CS_lhc8_hjZ_ratio, &
+! & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio, &
+! & BR_hjss,BR_hjcc, &
+! & BR_hjbb, &
+! & BR_hjmumu, &
+! & BR_hjtautau, &
+! & BR_hjWW,BR_hjZZ,BR_hjZga,BR_hjgaga, &
+! & BR_hjgg, BR_hjinvisible, &
+! & BR_hjhihi_nHbynH )
+! ! This subroutine can be called by the user after subroutine initialize_HiggsBounds
+! ! has been called.
+! ! (see manual for full description)
+! !************************************************************
+! use usefulbits, only : theo,np,Hneut,whichinput,just_after_run!,inputsub
+!
+! #if defined(NAGf90Fortran)
+! use F90_UNIX_IO, only : flush
+! #endif
+!
+! implicit none
+! !----------------------------------------input
+! double precision,intent(in) :: Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) )
+! integer,intent(in) :: CP_value( np(Hneut) )
+! double precision,intent(in) :: CS_lep_hjZ_ratio( np(Hneut) ), &
+! & CS_lep_bbhj_ratio( np(Hneut) ),CS_lep_tautauhj_ratio( np(Hneut) ), &
+! & CS_lep_hjhi_ratio_nHbynH(np(Hneut),np(Hneut)), &
+! & CS_tev_hj_ratio( np(Hneut) ) ,CS_tev_hjb_ratio( np(Hneut) ), &
+! & CS_tev_hjW_ratio( np(Hneut) ) ,CS_tev_hjZ_ratio( np(Hneut) ), &
+! & CS_tev_vbf_ratio( np(Hneut) ) ,CS_tev_tthj_ratio( np(Hneut)), &
+! & CS_lhc7_hj_ratio( np(Hneut) ),CS_lhc7_hjb_ratio( np(Hneut) ), &
+! & CS_lhc7_hjW_ratio( np(Hneut) ),CS_lhc7_hjZ_ratio( np(Hneut) ), &
+! & CS_lhc7_vbf_ratio( np(Hneut) ),CS_lhc7_tthj_ratio( np(Hneut)), &
+! & CS_lhc8_hj_ratio( np(Hneut) ),CS_lhc8_hjb_ratio( np(Hneut) ), &
+! & CS_lhc8_hjW_ratio( np(Hneut) ),CS_lhc8_hjZ_ratio( np(Hneut) ), &
+! & CS_lhc8_vbf_ratio( np(Hneut) ),CS_lhc8_tthj_ratio( np(Hneut)), &
+! & BR_hjss( np(Hneut) ),BR_hjcc( np(Hneut) ), &
+! & BR_hjbb( np(Hneut) ), &
+! & BR_hjmumu( np(Hneut) ),BR_hjtautau( np(Hneut) ), &
+! & BR_hjWW( np(Hneut) ),BR_hjZZ( np(Hneut) ), &
+! & BR_hjZga( np(Hneut) ),BR_hjgaga( np(Hneut) ), &
+! & BR_hjgg( np(Hneut) ), BR_hjinvisible( np(Hneut) ), &
+! & BR_hjhihi_nHbynH(np(Hneut),np(Hneut))
+! !-------------------------------------internal
+! integer :: n
+! ! integer :: subtype
+! !---------------------------------------------
+!
+! whichinput='hadr'
+! ! subtype=1
+! n=1
+! ! inputsub(subtype)%stat=inputsub(subtype)%stat+1
+!
+! if(.not.allocated(theo))then
+! stop 'subroutine HiggsBounds_initialize must be called first'
+! endif
+!
+! if(np(Hneut).eq.0)then
+! write(*,*)'subroutine HiggsBounds_neutral_input_hadr should'
+! write(*,*)'only be called if np(Hneut)>0'
+! stop 'error in subroutine HiggsBounds_neutral_input_hadr'
+! endif
+!
+! ! write(*,*) "DEBUG HB: before hadronic input. Mass is ",theo(n)%particle(Hneut)%M
+!
+!
+! theo(n)%particle(Hneut)%M = Mh
+! theo(n)%particle(Hneut)%Mc = Mh
+! theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj
+! theo(n)%CP_value = CP_value
+! theo(n)%lep%XS_hjZ_ratio = CS_lep_hjZ_ratio
+! theo(n)%lep%XS_bbhj_ratio = CS_lep_bbhj_ratio
+! theo(n)%lep%XS_tautauhj_ratio = CS_lep_tautauhj_ratio
+! theo(n)%lep%XS_hjhi_ratio = CS_lep_hjhi_ratio_nHbynH
+! theo(n)%tev%XS_hj_ratio = CS_tev_hj_ratio
+! theo(n)%tev%XS_hjb_ratio = CS_tev_hjb_ratio
+! theo(n)%tev%XS_hjW_ratio = CS_tev_hjW_ratio
+! theo(n)%tev%XS_hjZ_ratio = CS_tev_hjZ_ratio
+! theo(n)%tev%XS_vbf_ratio = CS_tev_vbf_ratio
+! theo(n)%tev%XS_tthj_ratio = CS_tev_tthj_ratio
+! theo(n)%lhc7%XS_hj_ratio = CS_lhc7_hj_ratio
+! theo(n)%lhc7%XS_hjb_ratio = CS_lhc7_hjb_ratio
+! theo(n)%lhc7%XS_hjW_ratio = CS_lhc7_hjW_ratio
+! theo(n)%lhc7%XS_hjZ_ratio = CS_lhc7_hjZ_ratio
+! theo(n)%lhc7%XS_vbf_ratio = CS_lhc7_vbf_ratio
+! theo(n)%lhc7%XS_tthj_ratio = CS_lhc7_tthj_ratio
+! theo(n)%lhc8%XS_hj_ratio = CS_lhc8_hj_ratio
+! theo(n)%lhc8%XS_hjb_ratio = CS_lhc8_hjb_ratio
+! theo(n)%lhc8%XS_hjW_ratio = CS_lhc8_hjW_ratio
+! theo(n)%lhc8%XS_hjZ_ratio = CS_lhc8_hjZ_ratio
+! theo(n)%lhc8%XS_vbf_ratio = CS_lhc8_vbf_ratio
+! theo(n)%lhc8%XS_tthj_ratio = CS_lhc8_tthj_ratio
+! theo(n)%BR_hjss = BR_hjss
+! theo(n)%BR_hjcc = BR_hjcc
+! theo(n)%BR_hjbb = BR_hjbb
+! theo(n)%BR_hjmumu = BR_hjmumu
+! theo(n)%BR_hjtautau = BR_hjtautau
+! theo(n)%BR_hjWW = BR_hjWW
+! theo(n)%BR_hjZZ = BR_hjZZ
+! theo(n)%BR_hjZga = BR_hjZga
+! theo(n)%BR_hjgaga = BR_hjgaga
+! theo(n)%BR_hjgg = BR_hjgg
+! theo(n)%BR_hjinvisible = BR_hjinvisible
+! theo(n)%BR_hjhihi = BR_hjhihi_nHbynH
+!
+! just_after_run=.False.
+!
+! ! write(*,*) "DEBUG HB: filled hadronic input. Mass is ",theo(n)%particle(Hneut)%M
+!
+! end subroutine HiggsBounds_neutral_input_hadr
+!************************************************************
\ No newline at end of file
Index: trunk/HiggsBounds-5/extra_bits_for_SLHA.f90
===================================================================
--- trunk/HiggsBounds-5/extra_bits_for_SLHA.f90 (revision 532)
+++ trunk/HiggsBounds-5/extra_bits_for_SLHA.f90 (revision 533)
@@ -1,660 +1,697 @@
! This file is part of HiggsBounds
! -KW
!******************************************************************
module extra_bits_for_SLHA
!******************************************************************
use PDGnumbering
implicit none
integer,parameter :: h(5)=(/h0,HH,A0,h03,A02/)
!h(1)=h0 !lightest CP even Higgs in real MSSM
!h(2)=HH !heaviest CP even Higgs in real MSSM
!h(3)=A0 !CP odd Higgs in real MSSM
!h(4)=h03 !NMSSM only
!h(5)=A02 !NMSSM only
integer,parameter :: neutralino(5)=(/neut1,neut2,neut3,neut4,neut5/)
!neutrlino(5) is in NMSSM only
integer,parameter :: chargino(2)=(/char1p,char2p/)
contains
!************************************************************
subroutine getSLHAdata(d,effC,infile)
! looks at theory predictions needed for Higgs searches only
!************************************************************
use usefulbits, only : dataset,hadroncolliderextras,Hneut,Hplus,Chineut,Chiplus,&
& np,file_id_common,couplratio,vvsmall!,sqcouplratio
use SLHA_manip
implicit none
!--------------------------------------input
type(dataset) :: d
! type(sqcouplratio) :: gsq
type(couplratio) :: effC
character(len=300),intent(in) :: infile
!-----------------------------------internal
integer :: i,j,k,x,ios,n
integer :: particlecontent,Rparityviolation,CPviolation
!double precision,allocatable ::g2hjcc(:,:),g2hjss(:,:)
double precision,allocatable ::ghjbb(:,:)
double precision,allocatable ::ghjtoptop(:,:),ghjtautau(:,:)
double precision :: mass
integer :: visible_lspcandidate_PDG(21),invisible_lspcandidate_PDG(7)
logical :: is_valid_point
type lightestsusyparticle
integer :: pdg
double precision :: mass
end type
type(lightestsusyparticle) :: lsp
logical :: invisible_lsp
double precision :: cofmenergy
!-------------------------------------------
if((np(Hneut).lt.0).or.(np(Hneut).gt.5))then
stop 'can not use subroutine getSLHAdata if number of neutral Higgs is not in range 0:5'
endif
if((np(Hplus).lt.0).or.(np(Hplus).gt.1))then
stop 'can not use subroutine getSLHAdata if number of charged Higgs is not in range 0:1'
endif
if((np(Chineut).lt.0).or.(np(Chineut).gt.5))then
stop 'can not use subroutine getSLHAdata if number of neutralinos is not in range 0:5'
endif
if((np(Chiplus).lt.0).or.(np(Chiplus).gt.2))then
stop 'can not use subroutine getSLHAdata if number of charginos is not in range 0:2'
endif
open(file_id_common,file=trim(infile),status='old',action='read',iostat=ios)
if(ios.ne.0)then
write(*,*)'problem opening the SLHA file: $'//trim(adjustl(infile))//'$'
!stop 'problem opening SLHA input file'
else
call readSLHAfile(file_id_common)
call check_validity(is_valid_point)
if(is_valid_point)then
particlecontent =get_modsel(3)
Rparityviolation =get_modsel(4)
CPviolation =get_modsel(5)
if(Rparityviolation.ne.0)stop 'HB can not yet use SLHA files with R parity violation'
select case(particlecontent)
case(0)
if((np(Hneut).ne.0).and.(np(Hneut).ne.3))then
write(*,*)'warning: modsel(3)=0 (MSSM) in SLHA file'
write(*,*)' but number of neutral Higgs that HB was told to expect=',np(Hneut)
endif
if((np(Chineut).ne.0).and.(np(Chineut).ne.4))then
write(*,*)'warning: modsel(3)=0 (MSSM) in SLHA file'
write(*,*)' but number of neutralinos that HB was told to expect=',np(Chineut)
endif
case(1)
if((np(Hneut).ne.0).and.(np(Hneut).ne.5))then
write(*,*)'warning: modsel(3)=1 (NMSSM) in SLHA file'
write(*,*)' but number of neutral Higgs that HB was told to expect=',np(Hneut)
endif
if((np(Chineut).ne.0).and.(np(Chineut).ne.5))then
write(*,*)'warning: modsel(3)=1 (NMSSM) in SLHA file'
write(*,*)' but number of neutralinos that HB was told to expect=',np(Chineut)
endif
end select
!------------------------------------------------
!------------ work out what the lsp is -----------
invisible_lsp=.False.
call fill_visible_lspcandidate_PDG
call fill_invisible_lspcandidate_PDG
lsp%mass=1.0D12 !set to a very big value
!find the invisible LSP candidate with the lowest mass
!and use it for BR_hjinvisible
do x=1,ubound(invisible_lspcandidate_PDG,dim=1)
n=invisible_lspcandidate_PDG(x)
mass=get_mass( n )
if(mass.gt.0.0D0.and.(mass.lt.lsp%mass))then !mass<0 means that this particle mass couldn't be found
lsp%mass=mass
lsp%pdg =n
invisible_lsp=.True.
endif
enddo
!however, if there's a charged SUSY particle or gluino with
!lower mass than the invisible LSP candidate,
!this candidate is not the LSP, so set BR_hjinvisible=0
do x=1,ubound(visible_lspcandidate_PDG,dim=1)
n=visible_lspcandidate_PDG(x)
mass=get_mass( n )
if(mass.gt.0.0D0.and.(mass.lt.lsp%mass))then !mass<0 means that this particle mass couldn't be found
lsp%mass=mass
lsp%pdg =n
invisible_lsp=.False.
endif
enddo
!------------------------------------------------
if(np(Hneut).gt.0)then
!allocate(g2hjcc( np(Hneut),2))
!allocate(g2hjss( np(Hneut),2))
allocate(ghjbb( np(Hneut),2))
allocate(ghjtoptop(np(Hneut),2))
allocate(ghjtautau(np(Hneut),2))
do i=1,np(Hneut)
d%particle(Hneut)%M(i) = get_mass(h(i))
d%particle(Hneut)%Mc(i) = get_mass(h(i))
d%particle(Hneut)%dMh(i) = get_mass_uncertainty(h(i))
if(d%particle(Hneut)%dMh(i).lt.0.1D0) d%particle(Hneut)%dMh(i)=0.0D0
d%particle(Hneut)%dM(i) = d%particle(Hneut)%dMh(i)
d%particle(Hneut)%GammaTot(i) = get_totaldecaywidth( h(i))
d%BR_hjss(i) = get_twobodybranchingratio( h(i),squark,sbar)
d%BR_hjcc(i) = get_twobodybranchingratio( h(i),cquark,cbar)
d%BR_hjbb(i) = get_twobodybranchingratio( h(i),bquark,bbar)
d%BR_hjtt(i) = get_twobodybranchingratio( h(i),tquark,tbar)
d%BR_hjmumu(i) = get_twobodybranchingratio( h(i),mup,mum)
d%BR_hjtautau(i) = get_twobodybranchingratio( h(i),taup,taum)
d%BR_hjemu(i) = get_twobodybranchingratio( h(i),ep,mum)
if(d%BR_hjemu(i).lt.vvsmall) then
d%BR_hjemu(i) = get_twobodybranchingratio( h(i),em,mup)
endif
d%BR_hjetau(i) = get_twobodybranchingratio( h(i),ep,taum)
if(d%BR_hjetau(i).lt.vvsmall) then
d%BR_hjetau(i) = get_twobodybranchingratio( h(i),em,taup)
endif
d%BR_hjmutau(i) = get_twobodybranchingratio( h(i),mup,taum)
if(d%BR_hjmutau(i).lt.vvsmall) then
d%BR_hjmutau(i) = get_twobodybranchingratio( h(i),mum,taup)
endif
d%BR_hjWW(i) = get_twobodybranchingratio( h(i),Wp ,Wm)
d%BR_hjZZ(i) = get_twobodybranchingratio( h(i),Z0 ,Z0)
d%BR_hjZga(i) = get_twobodybranchingratio( h(i),Z0 ,photon)
d%BR_hjgaga(i) = get_twobodybranchingratio( h(i),photon,photon)
d%BR_hjgg(i) = get_twobodybranchingratio( h(i),gluon ,gluon)
-
+ if(np(Hplus)>0) then
+ d%BR_hjHpiW(i,1) = get_twobodybranchingratio( h(i),Hp ,Wm)
+ if(d%BR_hjHpiW(i,1).lt.vvsmall) then
+ d%BR_hjHpiW(i,1) = get_twobodybranchingratio( h(i),Hm ,Wp)
+ endif
+ endif
if(invisible_lsp)then
if(lsp%pdg.eq.neut1) then
d%BR_hjinvisible(i) = get_twobodybranchingratio( h(i), lsp%pdg, lsp%pdg )
else
d%BR_hjinvisible(i) = get_twobodybranchingratio( h(i), lsp%pdg,-lsp%pdg )
endif
else
d%BR_hjinvisible(i) = 0.0D0
endif
!g2hjcc(i,:) = HB5_get_HiggsCouplingsFermions( h(i), cquark, cquark )
!g2hjss(i,:) = HB5_get_HiggsCouplingsFermions( h(i), squark, squark )
ghjbb(i,:) = HB5_get_HiggsCouplingsFermions( h(i), bquark, bquark )
ghjtoptop(i,:) = HB5_get_HiggsCouplingsFermions( h(i), tquark, tquark )
ghjtautau(i,:) = HB5_get_HiggsCouplingsFermions( h(i), taum, taum )
effC%hjWW(i) = HB5_get_HiggsCouplingsBosons( h(i), Wp, Wp )
effC%hjZZ(i) = HB5_get_HiggsCouplingsBosons( h(i), Z0, Z0 )
effC%hjgg(i) = HB5_get_HiggsCouplingsBosons( h(i), gluon, gluon )
! effC%hjggZ(i) = HB5_get_HiggsCouplingsBosons( h(i), gluon, gluon, Z0 )
enddo
do j=1,np(Hneut)
do i=1,np(Hneut)
effC%hjhiZ(j,i) = HB5_get_HiggsCouplingsBosons( h(j), h(i), Z0 )
do k=1,np(Hneut)
d%BR_hkhjhi(j,i,k) = get_twobodybranchingratio( h(j), h(i), h(k) )
enddo
d%BR_hjhiZ(j,i) = get_twobodybranchingratio( h(j), h(i), Z0 )
enddo
enddo
effC%hjZga = 0.0D0 !these are not needed
effC%hjgaga = 0.0D0
effC%hjmumu_s = 0.0D0
effC%hjmumu_p = 0.0D0
effC%hjcc_s = 0.0D0
effC%hjcc_p = 0.0D0
effC%hjss_s = 0.0D0
effC%hjss_p = 0.0D0
!effC%hjcc_s(:) = g2hjcc(:,1)
!effC%hjcc_p(:) = g2hjcc(:,2)
!effC%hjss_s(:) = g2hjss(:,1)
!effC%hjss_p(:) = g2hjss(:,2)
effC%hjbb_s(:) = ghjbb(:,1)
effC%hjbb_p(:) = ghjbb(:,2)
effC%hjtt_s(:) = ghjtoptop(:,1)
effC%hjtt_p(:) = ghjtoptop(:,2)
effC%hjtautau_s(:) = ghjtautau(:,1)
effC%hjtautau_p(:) = ghjtautau(:,2)
!deallocate(g2hjcc)
!deallocate(g2hjss)
deallocate(ghjbb)
deallocate(ghjtoptop)
deallocate(ghjtautau)
endif
if(np(Hplus).gt.0)then
i=1
d%particle(Hplus)%M(i) = get_mass( Hp )
d%particle(Hplus)%GammaTot(i) = get_totaldecaywidth( Hp )
d%particle(Hplus)%dMh(i) = get_mass_uncertainty( Hp )
!For now, set the LEP cross section ratio to one. Later, read it in from a block.
d%lep%XS_HpjHmj_ratio(i)=1.0
d%BR_tWpb = get_twobodybranchingratio( tquark, Wp, bquark )
d%BR_tHpjb(i) = get_twobodybranchingratio( tquark, Hp, bquark )
d%BR_Hpjcs(i) = get_twobodybranchingratio( Hp, cquark, sbar )
d%BR_Hpjcb(i) = get_twobodybranchingratio( Hp, cquark, bbar )
d%BR_Hpjtaunu(i) = get_twobodybranchingratio( Hp, taup, nutau )
d%BR_HpjWZ(i) = get_twobodybranchingratio( Hp, Wp, Z0 )
d%BR_Hpjtb(i) = get_twobodybranchingratio( Hp, tquark, bbar )
if(np(Hneut).gt.0) then
do j=1,np(Hneut)
d%BR_HpjhiW(i,j) = get_twobodybranchingratio( Hp, h(j), Wp )
enddo
endif
- d%lhc8%XS_Hpjtb(i) = get_crosssection_threeparticles("ChargedHiggsLHC8",5,6,37)
- d%lhc13%XS_Hpjtb(i) = get_crosssection_threeparticles("ChargedHiggsLHC13",5,6,37)
+ d%lhc8%XS_Hpjtb(i) = get_crosssection_threeparticles("ChargedHiggsLHC8",bquark,tquark,Hp)
+ d%lhc8%XS_Hpjcb(i) = get_crosssection_threeparticles("ChargedHiggsLHC8",cquark,bquark,Hp)
+ d%lhc8%XS_Hpjbjet(i) = get_crosssection_threeparticles("ChargedHiggsLHC8",uquark,bquark,Hp)
+ d%lhc8%XS_Hpjcjet(i) = get_crosssection_threeparticles("ChargedHiggsLHC8",dquark,cquark,Hp)
+ d%lhc8%XS_Hpjcjet(i) = d%lhc8%XS_Hpjcjet(i) + &
+ & get_crosssection_threeparticles("ChargedHiggsLHC8",squark,cquark,Hp)
+ d%lhc8%XS_Hpjjetjet(i) = get_crosssection_threeparticles("ChargedHiggsLHC8",dquark,uquark,Hp)
+ d%lhc8%XS_Hpjjetjet(i) = d%lhc8%XS_Hpjjetjet(i) + &
+ & get_crosssection_threeparticles("ChargedHiggsLHC8",uquark,squark,Hp)
+ d%lhc8%XS_HpjW(i) = get_crosssection_threeparticles("ChargedHiggsLHC8",0,Wm,Hp)
+ d%lhc8%XS_vbf_Hpj(i) = get_crosssection_threeparticles("ChargedHiggsLHC8",1,1,Hp)
+ d%lhc8%XS_HpjHmj(i) = get_crosssection_threeparticles("ChargedHiggsLHC8",0,Hm,Hp)
+ if(np(Hneut).gt.0) then
+ do j=1,np(Hneut)
+ d%lhc8%XS_Hpjhi(i,j) = get_crosssection_threeparticles("ChargedHiggsLHC8",0,h(j),Hp)
+ enddo
+ endif
+ d%lhc13%XS_Hpjtb(i) = get_crosssection_threeparticles("ChargedHiggsLHC13",bquark,tquark,Hp)
+ d%lhc13%XS_Hpjcb(i) = get_crosssection_threeparticles("ChargedHiggsLHC13",cquark,bquark,Hp)
+ d%lhc13%XS_Hpjbjet(i) = get_crosssection_threeparticles("ChargedHiggsLHC13",uquark,bquark,Hp)
+ d%lhc13%XS_Hpjcjet(i) = get_crosssection_threeparticles("ChargedHiggsLHC13",dquark,cquark,Hp)
+ d%lhc13%XS_Hpjcjet(i) = d%lhc13%XS_Hpjcjet(i) + &
+ & get_crosssection_threeparticles("ChargedHiggsLHC13",squark,cquark,Hp)
+ d%lhc13%XS_Hpjjetjet(i) = get_crosssection_threeparticles("ChargedHiggsLHC13",dquark,uquark,Hp)
+ d%lhc13%XS_Hpjjetjet(i) = d%lhc13%XS_Hpjjetjet(i) + &
+ & get_crosssection_threeparticles("ChargedHiggsLHC13",uquark,squark,Hp)
+ d%lhc13%XS_HpjW(i) = get_crosssection_threeparticles("ChargedHiggsLHC13",0,Wm,Hp)
+ d%lhc13%XS_vbf_Hpj(i) = get_crosssection_threeparticles("ChargedHiggsLHC13",1,1,Hp)
+ d%lhc13%XS_HpjHmj(i) = get_crosssection_threeparticles("ChargedHiggsLHC13",0,Hm,Hp)
+ if(np(Hneut).gt.0) then
+ do j=1,np(Hneut)
+ d%lhc13%XS_Hpjhi(i,j) = get_crosssection_threeparticles("ChargedHiggsLHC13",0,h(j),Hp)
+ enddo
+ endif
! write(*,*) "# ------- Charged Higgs SLHA input debugging ------ #"
! write(*,*) "d%BR_HpjhiW(i,:) = ", d%BR_HpjhiW(i,:)
! write(*,*) "d%BR_HpjWZ(i) = ",d%BR_HpjWZ(i)
! write(*,*) "d%BR_Hpjtb(i) = ",d%BR_Hpjtb(i)
! write(*,*) "d%lhc8%XS_Hpjtb(i) = ",d%lhc8%XS_Hpjtb(i)
! write(*,*) "d%lhc13%XS_Hpjtb(i) = ",d%lhc13%XS_Hpjtb(i)
! write(*,*) "# ------- end debugging ------ #"
endif
if(lsp%pdg.eq.neut1)then ! all these chargino and neutralino searches rely on the neutralino1
! being the lsp
if(np(Chineut).gt.0)then
cofmenergy=get_SPhenocrosssectionCMenergy(ep,em,0.0D0,0.0D0,1)
if(abs(cofmenergy-207.0D0).gt.1.0D-3)then
write(*,*)'Wrong centre of mass energy for chargino and neutralino LEP production XS.'
else
do i=1,np(Chineut)
d%particle(Chineut)%M(i) = abs(get_mass(neutralino(i))) ! 'abs' because
!SLHA files can have negative neutralino masses (if mixing matrix is defined to
!be real). Note that this means that the neutralino masses should never
!be set to -1 to indicate they should be ignored (which we can do for the Higgs).
d%particle(Chineut)%GammaTot(i) = get_totaldecaywidth(neutralino(i))
enddo
d%lep%XS_NjNi=0.0D0
do j=1,np(Chineut) !we're only interested when one of the particles is neutralino1
d%lep%XS_NjNi(j,1)=get_SPhenocrosssection(neutralino(j),neut1)
d%lep%XS_NjNi(1,j)=d%lep%XS_NjNi(j,1) !should be symmetric
enddo
d%BR_NjqqNi = 0.0D0 !ignoring for the moment
d%BR_NjZNi = 0.0D0
d%BR_NjqqNi = 0.0D0
do j=2,np(Chineut)!we're only interested when one of the daughter particles is neutralino1
!and parent is not neutralino1
d%BR_NjZNi(j,1) = get_twobodybranchingratio(neutralino(j),neut1,Z0)
d%BR_NjqqNi(j,1) = get_threebodybranchingratio(neutralino(j),neut1,uquark,ubar) &
& + get_threebodybranchingratio(neutralino(j),neut1,dquark,dbar) &
& + get_threebodybranchingratio(neutralino(j),neut1,cquark,cbar) &
& + get_threebodybranchingratio(neutralino(j),neut1,squark,sbar) &
& + get_threebodybranchingratio(neutralino(j),neut1,tquark,tbar) &
& + get_threebodybranchingratio(neutralino(j),neut1,bquark,ubar)
enddo
if(np(Chiplus).gt.0)then
do i=1,np(Chiplus)
d%particle(Chiplus)%M(i) = abs(get_mass(chargino(i)))
d%particle(Chiplus)%GammaTot(i) = get_totaldecaywidth(chargino(i))
enddo
do j=1,np(Chiplus)
d%lep%XS_CpjCmj(j)=get_SPhenocrosssection(chargino(j),-chargino(j))
enddo
d%BR_CjWNi = 0.0D0
d%BR_CjqqNi = 0.0D0
d%BR_CjlnuNi = 0.0D0
do j=1,np(Chiplus)
d%BR_CjWNi(j,1) = get_twobodybranchingratio(chargino(j),neut1,Wp)
d%BR_CjqqNi(j,1) = get_threebodybranchingratio(chargino(j),neut1,dbar,uquark) &
& + get_threebodybranchingratio(chargino(j),neut1,sbar,cquark)
d%BR_CjlnuNi(j,1) = get_threebodybranchingratio(chargino(j),neut1,ep, nue) &
& + get_threebodybranchingratio(chargino(j),neut1,mup, numu) &
& + get_threebodybranchingratio(chargino(j),neut1,taup,nutau)
enddo
endif
endif
endif
endif
endif
close(file_id_common)
call finishwithSLHA
endif
contains
subroutine fill_invisible_lspcandidate_PDG
invisible_lspcandidate_PDG(1) = neut1
invisible_lspcandidate_PDG(2) = s_nueL
invisible_lspcandidate_PDG(3) = s_numuL
invisible_lspcandidate_PDG(4) = s_nutauL
invisible_lspcandidate_PDG(5) = s_nutau1A
invisible_lspcandidate_PDG(6) = s_nutau2A
invisible_lspcandidate_PDG(7) = s_nutau3A
end subroutine fill_invisible_lspcandidate_PDG
subroutine fill_visible_lspcandidate_PDG
visible_lspcandidate_PDG(1) = char1p
visible_lspcandidate_PDG(2) = char2p
visible_lspcandidate_PDG(3) = s_t1
visible_lspcandidate_PDG(4) = s_b1
visible_lspcandidate_PDG(5) = s_cL
visible_lspcandidate_PDG(6) = s_sL
visible_lspcandidate_PDG(7) = s_uL
visible_lspcandidate_PDG(8) = s_dL
visible_lspcandidate_PDG(9) = s_t2
visible_lspcandidate_PDG(10) = s_b2
visible_lspcandidate_PDG(11) = s_cR
visible_lspcandidate_PDG(12) = s_sR
visible_lspcandidate_PDG(13) = s_uR
visible_lspcandidate_PDG(14) = s_dR
visible_lspcandidate_PDG(15) = s_emL
visible_lspcandidate_PDG(16) = s_mumL
visible_lspcandidate_PDG(17) = s_taumL
visible_lspcandidate_PDG(18) = s_emR
visible_lspcandidate_PDG(19) = s_mumR
visible_lspcandidate_PDG(20) = s_taumR
visible_lspcandidate_PDG(21) = gluino
end subroutine fill_visible_lspcandidate_PDG
end subroutine getSLHAdata
!************************************************************
subroutine outputSLHAdata(infile)
!************************************************************
use usefulbits, only : whichanalyses,pr,vers,file_id_common,fullHBres,infile1,&
& HBresult_all, numres
use SLHA_manip
use S95tables
implicit none
!--------------------------------------input
character(len=300),intent(in) :: infile
!-----------------------------------internal
double precision :: obsratio,predratio
integer :: x,y,ios,rank,HBresult,chan,ncombined
integer :: k_out
character(LEN=200):: descrip
logical :: newfile = .False.
logical :: exist
!-------------------------------------------
if(infile.eq.infile1) then
open(file_id_common,file=trim(infile),status='old',iostat=ios)
else
inquire(file=trim(infile),exist=exist)
if(exist) then
open(file_id_common,file=trim(infile),status='replace',iostat=ios)
else
open(file_id_common,file=trim(infile),status='new',iostat=ios)
endif
newfile=.True.
endif
if(ios.ne.0)then
write(*,*)'problem opening the SLHA file: $'//trim(adjustl(infile))//'$'
else
k_out=file_id_common
if(.not.newfile) then
call readSLHAfile(file_id_common)
rewind(file_id_common)
call writeSLHAfile_except(k_out,'HiggsBoundsResults')
endif
!write(k_out,'(a)')'#'
write(k_out,'(a)')'Block HiggsBoundsResults # results from HiggsBounds http://projects.hepforge.org/higgsbounds'
write(k_out,'(a)')'# HBresult : scenario allowed flag (1: allowed, 0: excluded, -1: unphysical)'
write(k_out,'(a)')'# chan id number: most sensitive channel (see below). chan=0 if no channel applies'
write(k_out,'(a)')'# obsratio : ratio [sig x BR]_model/[sig x BR]_limit (<1: allowed, >1: excluded)'
write(k_out,'(a)')'# ncomb : number of Higgs bosons combined in most sensitive channel'
write(k_out,'(a)')'# Note that the HB channel id number varies depending on the HB version and setting "whichanalyses"'
write(k_out,'(a)')'#'
write(k_out,*)' 0 '//trim(adjustl(vers))//' ||'//whichanalyses// &
& '|| # version of HB used to produce these results,the HB setting "whichanalyses"'
write(k_out,'(a)')'#'
if(allocated(HBresult_all)) then
do rank=1,numres
y=1
call HiggsBounds_get_most_sensitive_channels(rank,HBresult,chan,obsratio,predratio,ncombined)
! x=fullHBres(y)%chan
call outputproc(pr(chan),0,descrip,1)
write(k_out,'(a)')'#CHANNEL info: ranked from highest statistical sensitivity'
write(k_out,*)' ',rank,1 , chan, ' # channel id number'
write(k_out,*)' ',rank,2 , HBresult,' # HBresult '
write(k_out,*)' ',rank,3 , obsratio, ' # obsratio '
write(k_out,*)' ',rank,4 , ncombined,' # ncombined'
write(k_out,*)' ',rank,5 ,'||'//trim(adjustl(descrip))//'|| # text description of channel'
write(k_out,'(a)')'#'
enddo
else
y=1
x=fullHBres(y)%chan
call outputproc(pr(x),0,descrip,1)
write(k_out,'(a)')'#CHANNEL info: channel with the highest statistical sensitivity'
write(k_out,*)' 1',1 , fullHBres(y)%chan, ' # channel id number'
write(k_out,*)' 1',2 , fullHBres(y)%allowed95,' # HBresult '
write(k_out,*)' 1',3 , fullHBres(y)%obsratio, ' # obsratio '
write(k_out,*)' 1',4 , fullHBres(y)%ncombined,' # ncombined'
write(k_out,*)' 1',5 ,'||'//trim(adjustl(descrip))//'|| # text description of channel'
write(k_out,'(a)')'#'
endif
close(file_id_common)
if(k_out.ne.file_id_common)close(k_out)
call finishwithSLHA
endif
end subroutine outputSLHAdata
!************************************************************
! subroutine addcouplingsblocktoSLHAfile(infile,gsq)
! !************************************************************
! use usefulbits, only : file_id_common,sqcouplratio,np,Hneut
! use SLHA_manip
!
! implicit none
! !--------------------------------------input
! type(sqcouplratio) :: gsq
! character(len=300),intent(in) :: infile
! !-----------------------------------internal
! integer :: i,ios,j
! integer :: k_out
! !-------------------------------------------
!
! open(file_id_common,file=trim(infile),status='old',iostat=ios)
! if(ios.ne.0)then
! write(*,*)'problem opening the SLHA file: $'//trim(adjustl(infile))//'$'
! else
!
! call readSLHAfile(file_id_common)
!
! rewind(file_id_common)
! k_out=file_id_common
!
! call writeSLHAfile_except(k_out, &
! & 'HiggsBoundsInputHiggsCouplingsBosons', &
! & 'HiggsBoundsInputHiggsCouplingsFermions')
!
! write(k_out,'(a)')'#'
! write(k_out,'(a)')'Block HiggsBoundsInputHiggsCouplingsBosons'
! write(k_out,'(a)')'# For exact definitions of NormEffCoupSq see HiggsBounds manual'
!
! do i=1,np(Hneut)
! write(k_out,'(G16.6,4I6,a)')gsq%hjWW(i), 3,h(i),Wp,Wp, &
! & ' # higgs-W-W effective coupling^2, normalised to SM'
! enddo
! do i=1,np(Hneut)
! write(k_out,'(G16.6,4I6,a)')gsq%hjZZ(i), 3,h(i),Z0,Z0, &
! & ' # higgs-Z-Z effective coupling^2, normalised to SM'
! enddo
! do i=1,np(Hneut)
! write(k_out,'(G16.6,4I6,a)')gsq%hjgg(i), 3,h(i),gluon,gluon, &
! & ' # higgs-gluon-gluon effective coupling^2, normalised to SM'
! enddo
! do j=1,np(Hneut)
! do i=1,j
! write(k_out,'(G16.6,4I6,a)')gsq%hjhiZ(j,i),3,h(j),h(i),Z0, &
! & ' # higgs-higgs-Z effective coupling^2, normalised'
! enddo
! enddo
! do i=1,np(Hneut)
! write(k_out,'(G16.6,5I6,a)')gsq%hjggZ(i), 4,h(i),gluon,gluon,Z0, &
! & ' # higgs-gluon-gluon-Z effective coupling^2, normalised to SM'
! enddo
!
! write(k_out,'(a)')'#'
! write(k_out,'(a)')'Block HiggsBoundsInputHiggsCouplingsFermions'
! write(k_out,'(a)')'# For exact definitions of NormEffCoupSq see HiggsBounds manual'
! write(k_out,'(a)')'# ScalarNormEffCoupSq PseudoSNormEffCoupSq NP IP1 IP2 IP3' // &
! & ' # Scalar, Pseudoscalar Normalised Effective Coupling Squared'
! do i=1,np(Hneut)
! write(k_out,*)gsq%hjbb_s(i),gsq%hjbb_p(i), 3,h(i),bquark,bquark, &
! & '# higgs-b-b eff. coupling^2, normalised to SM'
! enddo
! do i=1,np(Hneut)
! write(k_out,*)gsq%hjtoptop_s(i),gsq%hjtoptop_p(i),3,h(i),tquark,tquark, &
! & '# higgs-top-top eff. coupling^2, normalised to SM'
! enddo
! do i=1,np(Hneut)
! write(k_out,*)gsq%hjtautau_s(i),gsq%hjtautau_p(i),3,h(i),taum,taum, &
! & '# higgs-tau-tau eff. coupling^2, normalised to SM'
! enddo
!
! close(file_id_common)
! if(k_out.ne.file_id_common)close(k_out)
!
! call finishwithSLHA
!
! endif
! end subroutine addcouplingsblocktoSLHAfile
!************************************************************
subroutine addcouplingsblocktoSLHAfile(infile,effC)
!************************************************************
use usefulbits, only : file_id_common,couplratio,np,Hneut!,sqcouplratio
use SLHA_manip
implicit none
!--------------------------------------input
! type(sqcouplratio) :: gsq
type(couplratio) :: effC
character(len=300),intent(in) :: infile
!-----------------------------------internal
integer :: i,ios,j
integer :: k_out
!-------------------------------------------
open(file_id_common,file=trim(infile),status='old',iostat=ios)
if(ios.ne.0)then
write(*,*)'problem opening the SLHA file: $'//trim(adjustl(infile))//'$'
else
call readSLHAfile(file_id_common)
rewind(file_id_common)
k_out=file_id_common
call writeSLHAfile_except(k_out, &
& 'HiggsCouplingsBosons', &
& 'HiggsCouplingsFermions')
write(k_out,'(a)')'#'
write(k_out,'(a)')'Block HiggsCouplingsBosons'
write(k_out,'(a)')'# For exact definitions of NormEffCoup see HiggsBounds manual'
do i=1,np(Hneut)
write(k_out,'(G16.6,4I6,a)')effC%hjWW(i), 3,h(i),Wp,Wp, &
& ' # higgs-W-W effective coupling, normalised to SM'
enddo
do i=1,np(Hneut)
write(k_out,'(G16.6,4I6,a)')effC%hjZZ(i), 3,h(i),Z0,Z0, &
& ' # higgs-Z-Z effective coupling, normalised to SM'
enddo
do i=1,np(Hneut)
write(k_out,'(G16.6,4I6,a)')effC%hjgg(i), 3,h(i),gluon,gluon, &
& ' # higgs-gluon-gluon effective coupling, normalised to SM'
enddo
do j=1,np(Hneut)
do i=1,j
write(k_out,'(G16.6,4I6,a)')effC%hjhiZ(j,i),3,h(j),h(i),Z0, &
& ' # higgs-higgs-Z effective coupling, normalised'
enddo
enddo
! do i=1,np(Hneut)
! write(k_out,'(G16.6,5I6,a)')effC%hjggZ(i), 4,h(i),gluon,gluon,Z0, &
! & ' # higgs-gluon-gluon-Z effective coupling, normalised to SM'
! enddo
write(k_out,'(a)')'#'
write(k_out,'(a)')'Block HiggsCouplingsFermions'
write(k_out,'(a)')'# For exact definitions of NormEffCoup see HiggsBounds manual'
write(k_out,'(a)')'# ScalarNormEffCoup PseudoSNormEffCoup NP IP1 IP2 IP3' // &
& ' # Scalar, Pseudoscalar Normalised Effective Coupling'
do i=1,np(Hneut)
write(k_out,*)effC%hjbb_s(i),effC%hjbb_p(i), 3,h(i),bquark,bquark, &
& '# higgs-b-b eff. coupling, normalised to SM'
enddo
do i=1,np(Hneut)
write(k_out,*)effC%hjtt_s(i),effC%hjtt_p(i),3,h(i),tquark,tquark, &
& '# higgs-top-top eff. coupling, normalised to SM'
enddo
do i=1,np(Hneut)
write(k_out,*)effC%hjtautau_s(i),effC%hjtautau_p(i),3,h(i),taum,taum, &
& '# higgs-tau-tau eff. coupling, normalised to SM'
enddo
close(file_id_common)
if(k_out.ne.file_id_common)close(k_out)
call finishwithSLHA
endif
end subroutine addcouplingsblocktoSLHAfile
!************************************************************
end module extra_bits_for_SLHA
!******************************************************************
Index: trunk/HiggsBounds-5/input.F90
===================================================================
--- trunk/HiggsBounds-5/input.F90 (revision 532)
+++ trunk/HiggsBounds-5/input.F90 (revision 533)
@@ -1,1544 +1,1600 @@
! This file is part of HiggsBounds
! -KW
!******************************************************************
module input
!******************************************************************
#ifdef NAGf90Fortran
use F90_UNIX_ENV, only : iargc,getarg
use F90_UNIX_IO, only : flush
#endif
use usefulbits, only : Hneut,Hplus,Chineut,Chiplus
implicit none
integer,parameter :: nHmax=99
!nHneut>9 not allowed in this version
!(if you really need nHneut>9,
!change nHmax in subroutine setup_input,
!and adapt subroutine outputproc_t1/t2
!and do_output, by changing the size of
!the character variables nHchar,i,j
!since LEN=1 will no longer be sufficient)
integer :: f_orig=15 ! file id
! n.b. debug_predratio.txt is 14, debug_channels.txt is 12
! (see HiggsBounds.f90 and HiggsBounds_subroutines.F90)
character(LEN=50),allocatable :: stem_array(:)
logical,allocatable :: required(:)
logical,allocatable :: isoptional(:)
integer :: nargs_datfile
logical,parameter :: official=.True.!do not change this without contacting us first!
!logical,parameter :: official=.False.
contains
!************************************************************
subroutine setup_input
!************************************************************
! * if inputmethod='datfile' or 'website', finds whichanalyses,whichinput,np
! * if inputmethod='datfile', finds infile1 (prefix for input/output filenames)
! * sets ndat (number of parameter points considered)
! * sets n_additional (number of additional data values for each parameter point)
! * allocates theo, g2, partR
!************************************************************
use usefulbits, only : np,ndat,n_additional,theo,effC,g2,partR, &
& inputmethod,whichinput, &
& debug,infile1,infile2, &
& allocate_hadroncolliderextras_parts,allocate_dataset_parts, &
& allocate_sqcouplratio_parts,allocate_couplratio_parts,fill_pdesc
use theory_BRfunctions
implicit none
!-----------------------------------internal
integer :: f,ios,cc,g
character(LEN=50) :: stem
!-------------------------------------------
call fill_pdesc
select case(inputmethod)
case('datfile')
call getbasiccommandline!get whichanalyses,whichinput,numbers of particles
call getshortcommandline(infile1,infile2)! get infile1
case('website')
call getbasiccommandline!get whichanalyses,whichinput,numbers of particles
!don't need infile1
case('subrout')
!np(Hneut),np(Hplus) are already set
call check_number_of_particles
call check_whichanalyses
!haven't yet set whichanalyses,whichinput
infile1=''
case default
stop 'incorrect value for inputmethod'
end select
!getting ndat and n_additional...
select case(inputmethod)
case('datfile')
f=f_orig
n_additional=0
select case(whichinput)
case('part','effC','hadr')
call fill_stem_array
g=1
stem=stem_array(g)
f=f_orig+g
open(f,file=trim(infile1)//trim(stem)//'.dat',status='old',action='read',iostat=ios)
if(ios.ne.0)then
call file_name_msg(f)
write(*,*)'Check that <prefix> was specified correctly'
write(*,*)'and that file exists.'
call flush(6)
stop 'Problem opening file: see standard output for more info'
endif
ndat=getfilelength(f) ! number of data sets (i.e. lines) in input
if((ndat.le.0))stop 'error getting ndat'
close(f)
g=ubound(stem_array,dim=1)
stem=stem_array(g)
f=f_orig+g
!the last element in stem_array should be 'additional'
if(trim(stem_array(g)).ne.'additional')stop 'Error in subroutine setup_input (a)'
required(g)=.False.
open(f,file=trim(infile1)//trim(stem)//'.dat',status='old',action='read',iostat=ios)
if(ios.eq.0)then
cc=count_columns(f)
if(cc.gt.1)then
if(getfilelength(f).eq.ndat)then
n_additional=cc-1
required(g)=.True.
endif
endif
endif
close(f)
case('SLHA')
ndat=1 ; n_additional=0
case default
stop 'error in subroutine do_input (1a)'
end select
case('website','subrout')
ndat=1 ; n_additional=0
case default
stop 'error in subroutine do_input (1b)'
end select
!...finished getting ndat and n_additional
if(debug)then
write(*,*)'np(Hneut)=',np(Hneut)
write(*,*)'ndat=',ndat
write(*,*)'n_additional=',n_additional
endif
allocate(theo(ndat))
call allocate_dataset_parts(theo,n_additional)
! - Outdated:
allocate(g2(ndat))
call allocate_sqcouplratio_parts(g2)
! -
-
allocate(effC(ndat))
call allocate_couplratio_parts(effC)
allocate(partR(ndat))
call allocate_hadroncolliderextras_parts(partR)
end subroutine setup_input
!************************************************************
subroutine do_input
! determines what input is needed and calls the appropriate
! subroutines to get this input
!************************************************************
use usefulbits, only : ndat,inputmethod,whichinput, &
& theo,effC,partR,infile1,g2
use extra_bits_for_web, only : getlongcommandline2web
use extra_bits_for_SLHA, only : getSLHAdata
use theory_BRfunctions
implicit none
!-----------------------------------internal
integer :: n
logical :: webdebugmode
!-------------------------------------------
select case(inputmethod)
case('datfile')
select case(whichinput)
case('part','effC','hadr')
do n=1,ubound(stem_array,dim=1)
call readthefile(n)
enddo
deallocate(stem_array)
deallocate(required)
deallocate(isoptional)
case('SLHA')
n=1
if(ndat.ne.1)then
stop 'error in subroutine do_input (4): need to specify infile1 for each SLHA file somehow'
endif
! call getSLHAdata(theo(n),g2(n),infile1)
call getSLHAdata(theo(n),effC(n),infile1)
!call test_input(n)
case default
stop 'error in subroutine do_input (1)'
end select
case('website')
n=1
call getlongcommandline2web(theo(n),g2(n),partR(n),webdebugmode)
if(webdebugmode) call test_input(n)
case default
stop 'error in subroutine do_input (3)'
end select
end subroutine do_input
!************************************************************
subroutine fill_stem_array
! lists all possible files
! note that stem_array(ubound(stem_array,dim=1)) should be 'additional'
!************************************************************
use usefulbits, only : np,whichinput,whichanalyses
implicit none
integer :: n,nt
n=1
nt=28
allocate(stem_array(nt))
allocate(required(nt))
allocate(isoptional(nt))
! the following table sets input filenames and says which input files are relevant to each option
! | | | np
! | whichinput | whichanalyses |Hneu Hcha Chineut Chiplus
! stem |part hadr effC |LandH onlyL onlyH onlyP | ==0 ==0 ==0 ==0
! call fill('MH_GammaTot' , 1, 1, 1, 1, 1, 1, 1, 0, 1, 1, 1)
! call fill('MHall_uncertainties' , -1, -1, -1, 1, 1, 1, 1, 1, 1, 1, 1)
! call fill('MHplus_GammaTot' , 1, 1, 1, 1, 1, 1, 1, 1, 0, 1, 1)
! call fill('MC_GammaTot' , 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0)
! call fill('MN_GammaTot' , 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 1)
! call fill('effC' , 0, 0, 1, 1, 1, 1, 1, 0, 1, 1, 1)
!
! call fill('BR_H_OP' , 1, 1, 0, 1, 1, 1, 1, 0, 1, 1, 1)
! call fill('BR_H_NP' , 1, 1, 1, 1, 1, 1, 1, 0, 1, 1, 1)
! call fill('BR_t' , 1, 1, 1, 1, 0, 1, 1, 1, 0, 1, 1)
! call fill('BR_Hplus' , 1, 1, 1, 1, 1, 1, 1, 1, 0, 1, 1)
! call fill('BR_C' , 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0)
! call fill('BR_N' , 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 1)
!
! call fill('LEP_HZ_CS_ratios' , 1, 1, 0, 1, 1, 0, 1, 0, 1, 1, 1)
! call fill('LEP_H_ff_CS_ratios' , 1, 1, 0, 1, 1, 0, 1, 0, 1, 1, 1)
! call fill('LEP_2H_CS_ratios' , 1, 1, 0, 1, 1, 0, 1, 0, 1, 1, 1)
! call fill('LEP_HpHm_CS_ratios' , 1, 1, 1, 1, 1, 0, 1, 1, 0, 1, 1)
! call fill('LEP_CpCm_CS' , 1, 1, 1, 1, 1, 0, 1, 1, 1, 0, 0)
! call fill('LEP_2N_CS' , 1, 1, 1, 1, 1, 0, 1, 1, 1, 0, 1)
!
! call fill('TEVLHC_H_0jet_partCS_ratios', 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
! call fill('TEVLHC_H_1jet_partCS_ratios', 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
! call fill('TEVLHC_HW_partCS_ratios' , 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
! call fill('TEVLHC_HZ_partCS_ratios' , 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
!
! call fill('TEV_H_vbf_hadCS_ratios' , 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
! call fill('TEV_H_tt_hadCS_ratios' , 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
! call fill('TEV_1H_hadCS_ratios' , 0, 1, 0, 1, 0, 1, 1, 0, 1, 1, 1)
!
! call fill('LHC7_H_vbf_hadCS_ratios' , 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
! call fill('LHC7_H_tt_hadCS_ratios' , 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
! call fill('LHC7_1H_hadCS_ratios' , 0, 1, 0, 1, 0, 1, 1, 0, 1, 1, 1)
!
! call fill('LHC8_H_vbf_hadCS_ratios' , 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
! call fill('LHC8_H_tt_hadCS_ratios' , 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1)
! call fill('LHC8_1H_hadCS_ratios' , 0, 1, 0, 1, 0, 1, 1, 0, 1, 1, 1)
!
! call fill('CP_values' , 1, 1, 0, 1, 1, 1, 1, 0, 1, 1, 1)
! call fill('additional' , 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1)
call fill('MH_GammaTot' , 1, 1, 1, 1, 1, 1, 0, 1, 1, 1)
call fill('MHall_uncertainties' , -1, -1, 1, 1, 1, 1, 1, 1, 1, 1)
call fill('MHplus_GammaTot' , 1, 1, 1, 1, 1, 1, 1, 0, 1, 1)
call fill('MC_GammaTot' , 1, 1, 1, 1, 1, 1, 1, 1, 0, 0)
call fill('MN_GammaTot' , 1, 1, 1, 1, 1, 1, 1, 1, 0, 1)
call fill('effC' , 0, 1, 1, 1, 1, 1, 0, 1, 1, 1)
call fill('BR_H_OP' , 1, -1, 1, 1, 1, 1, 0, 1, 1, 1)
call fill('BR_H_NP' , 1, 1, 1, 1, 1, 1, 0, 1, 1, 1)
call fill('BR_t' , 1, 1, 1, 0, 1, 1, 1, 0, 1, 1)
call fill('BR_Hplus' , 1, 1, 1, 1, 1, 1, 1, 0, 1, 1)
call fill('BR_C' , 1, 1, 1, 1, 1, 1, 1, 1, 0, 0)
call fill('BR_N' , 1, 1, 1, 1, 1, 1, 1, 1, 0, 1)
call fill('LEP_HZ_CS_ratios' , 1, 0, 1, 1, 0, 1, 0, 1, 1, 1)
call fill('LEP_H_ff_CS_ratios' , 1, 0, 1, 1, 0, 1, 0, 1, 1, 1)
call fill('LEP_2H_CS_ratios' , 1, 0, 1, 1, 0, 1, 0, 1, 1, 1)
call fill('LEP_HpHm_CS_ratios' , 1, 1, 1, 1, 0, 1, 1, 0, 1, 1)
call fill('LEP_CpCm_CS' , 1, 1, 1, 1, 0, 1, 1, 1, 0, 0)
call fill('LEP_2N_CS' , 1, 1, 1, 1, 0, 1, 1, 1, 0, 1)
call fill('TEV_1H_hadCS_ratios' , 1, 0, 1, 0, 1, 1, 0, 1, 1, 1)
call fill('LHC7_1H_hadCS_ratios' , 1, 0, 1, 0, 1, 1, 0, 1, 1, 1)
call fill('LHC8_1H_hadCS_ratios' , 1, 0, 1, 0, 1, 1, 0, 1, 1, 1)
call fill('LHC13_1H_hadCS_ratios' , 1, 0, 1, 0, 1, 1, 0, 1, 1, 1)
call fill('TEV_Hplus_hadCS' , 1, 1, 1, 0, 1, 1, 1, 0, 1, 1)
call fill('LHC7_Hplus_hadCS' , 1, 1, 1, 0, 1, 1, 1, 0, 1, 1)
call fill('LHC8_Hplus_hadCS' , 1, 1, 1, 0, 1, 1, 1, 0, 1, 1)
call fill('LHC13_Hplus_hadCS' , 1, 1, 1, 0, 1, 1, 1, 0, 1, 1)
!--n.B.: Extend this by 2H hadronic input in case needed! (No searches yet)
call fill('CP_values' , 1, 0, 1, 1, 1, 1, 0, 1, 1, 1)
call fill('additional' , 1, 1, 1, 1, 1, 1, 1, 1, 1, 1)
if(n.ne.nt+1)stop 'Error in subroutine fill_stem_array A'
!write(*,*)'hello whichinput',whichinput
!write(*,*)'hello whichanalyses',whichanalyses
!write(*,*)'hello np(Hneut)',np(Hneut)
!write(*,*)'hello np(Hplus)',np(Hplus)
!do n=1,nt
! write(*,*)'hello ',stem_array(n),required(n)
!enddo
!stop 'hello ending here for now'
contains
! | | | np
! | whichinput | whichanalyses |Hneu Hcha Chineut Chiplus
! stem |part hadr effC |LandH onlyL onlyH onlyP | ==0 ==0 ==0 ==0
! subroutine fill(stem ,part,hadr,effC, LandH,onlyL,onlyH,onlyP, Hneu,Hcha, Chneu, Chcha)
! !nb required(i) for 'additional' is not set until later
! implicit none
!
! character(LEN=*), intent(in):: stem
! integer, intent(in) :: part,hadr,effC,LandH,onlyL,onlyH,onlyP,Hneu,Hcha,Chneu,Chcha
! integer :: req
!
! stem_array(n)=stem
!
! req=1
! select case(whichinput)
! case('part')
! req= part * req
! case('hadr')
! req= hadr * req
! case('effC')
! req= effC * req
! case default
! stop 'error in subroutine fill(whichinput)'
! end select
!
! select case(whichanalyses)
! case('LandH')
! req= LandH * req
! case('onlyL')
! req= onlyL * req
! case('onlyH')
! req= onlyH * req
! case('onlyP')
! req= onlyP * req
! case default
! stop 'error in subroutine fill(whichanalyses)'
! end select
!
! if(np(Hneut)==0) req= Hneu * req
! if(np(Hplus)==0) req= Hcha * req
! if(np(Chineut)==0)req= Chneu * req
! if(np(Chiplus)==0)req= Chcha * req
!
! select case(req)
! case(0)
! required(n)=.False.
! isoptional(n)=.False.
! case(1)
! required(n)=.True.
! isoptional(n)=.False.
! case(-1)
! required(n)=.False.
! isoptional(n)=.True.
! case default
! stop 'error in subroutine fill(req)'
! end select
!
! n=n+1
!
! end subroutine fill
subroutine fill(stem ,hadr,effC, LandH,onlyL,onlyH,onlyP, Hneu,Hcha, Chneu, Chcha)
!nb required(i) for 'additional' is not set until later
implicit none
character(LEN=*), intent(in):: stem
integer, intent(in) :: hadr,effC,LandH,onlyL,onlyH,onlyP,Hneu,Hcha,Chneu,Chcha
integer :: req
stem_array(n)=stem
req=1
select case(whichinput)
! case('part')
! req= part * req
case('hadr')
req= hadr * req
case('effC')
req= effC * req
case default
stop 'error in subroutine fill(whichinput)'
end select
select case(whichanalyses)
case('LandH')
req= LandH * req
case('onlyL')
req= onlyL * req
case('onlyH')
req= onlyH * req
case('onlyP')
req= onlyP * req
case default
stop 'error in subroutine fill(whichanalyses)'
end select
if(np(Hneut)==0) req= Hneu * req
if(np(Hplus)==0) req= Hcha * req
if(np(Chineut)==0)req= Chneu * req
if(np(Chiplus)==0)req= Chcha * req
select case(req)
case(0)
required(n)=.False.
isoptional(n)=.False.
case(1)
required(n)=.True.
isoptional(n)=.False.
case(-1)
required(n)=.False.
isoptional(n)=.True.
case default
stop 'error in subroutine fill(req)'
end select
n=n+1
end subroutine fill
end subroutine fill_stem_array
!************************************************************
subroutine readthefile(n_stem)
!************************************************************
! Opens and reads the input data from files
! checks the number of lines and columns in the file first
! First column is always line number. Last line is checked to make
! sure line number is correct
!************************************************************
use usefulbits, only : np,theo,ndat,infile1,g2,effC,partR, &
& n_additional,BRdirectinput
implicit none
!--------------------------------------input
integer,intent(in) :: n_stem
!-----------------------------------internal
character(LEN=50) :: stem
integer :: jj,i,j,f,k,q,ios,x,y,count
double precision :: nc
logical :: needed, opt
- double precision, allocatable :: BR_NjqqNi_in(:),BR_NjZNi_in(:),&
+ double precision, allocatable :: BR_NjqqNi_in(:),BR_NjZNi_in(:),BR_hjHpiW_in(:), &
& BR_hkhjhi_in(:),BR_hjhiZ_in(:),BR_HpjhiW_in(:) !BR_hjhihi_in(:)
character(LEN=500) :: line
integer :: numskip
double precision, allocatable :: numbersfromline(:)
logical :: readHneut, readHplus
!-------------------------------------------
stem=stem_array(n_stem)
needed=required(n_stem)
opt=isoptional(n_stem)
if(needed.or.opt)then
f=f_orig+n_stem
open(f,file=trim(infile1)//trim(stem)//'.dat',status='old',action='read',iostat=ios)
if(ios.ne.0)then
call file_name_msg(f)
! stop 'problem opening file: see standard output for more info'
if(needed) then
write(*,*) 'WARNING: Required file not found. Corresponding values are set to zero!'
else
write(*,*) 'Optional datafile '//trim(infile1)//trim(stem)//'.dat'//' not found.'//&
& ' Using default values.'
return
endif
endif
if(getfilelength(f).eq.0) return
if((ndat.ne.getfilelength(f)))then
write(*,*)'wrong no. lines in input file'
write(*,*)'It had',getfilelength(f),'lines'
write(*,*)'but should have been',ndat
call file_name_msg(f)
stop 'error in input file length (see standard output for filename).'
endif
!--NEW TO ALLOW DIFFERENT FILE READINGS OF DMHALL_UNCERTAINTIES.dat
numskip=0
readHneut=.True.
readHplus=.True.
if(isoptional(n_stem)) then
if(get_ncol(stem).ne.count_columns(f))then
if(get_ncol(stem).eq.np(Hneut)+1) then
readHneut=.True.
readHplus=.False.
numskip=0
else if(get_ncol(stem).eq.np(Hplus)+1) then
readHneut=.False.
readHplus=.True.
numskip=count_columns(f)-1-np(Hplus)
else
readHneut=.False.
readHplus=.False.
numskip=0
endif
endif
else
if(get_ncol(stem).ne.count_columns(f))then
write(*,*)'wrong no. columns in input file'
write(*,*)'It had',count_columns(f),'columns'
write(*,*)'but should have been',get_ncol(stem)
write(*,*)'including line ID number'
call file_name_msg(f)
stop 'error in input file format (see standard output for filename).'
endif
endif
select case(trim(stem))
case('MH_GammaTot')
x=Hneut
do jj=1,ndat
read(f,*) nc, (theo(jj)%particle(x)%M(i) ,i=1,np(x)), &
& (theo(jj)%particle(x)%GammaTot(i),i=1,np(x))
enddo
case('MHall_uncertainties')
x=Hneut
y=Hplus
do jj=1,ndat
read(f,'(A)') line
!! write(*,*) "Line: ", line
call extractnumbersfromline(line, nc, numbersfromline)
!------Copy the HB mass uncertainties to the HS mass uncertainties for datfiles input.
if(readHneut) then
do i=1,np(x)
! theo(jj)%particle(x)%dM(i) = theo(jj)%particle(x)%dMh(i)
theo(jj)%particle(x)%dM(i) = numbersfromline(i)
theo(jj)%particle(x)%dMh(i) = numbersfromline(i)
enddo
numskip=np(x)
endif
if(readHplus) then
do i=1,np(y)
! theo(jj)%particle(y)%dM(i) = theo(jj)%particle(y)%dMh(i)
theo(jj)%particle(y)%dM(i) = numbersfromline(numskip+i)
theo(jj)%particle(y)%dMh(i) = numbersfromline(numskip+i)
enddo
endif
deallocate(numbersfromline)
!! write(*,*) nc, theo(jj)%particle(Hneut)%dM, theo(jj)%particle(Hplus)%dM
enddo
case('MHplus_GammaTot')
x=Hplus
do jj=1,ndat
read(f,*) nc, (theo(jj)%particle(x)%M(i) ,i=1,np(x)), &
& (theo(jj)%particle(x)%GammaTot(i),i=1,np(x))
enddo
case('MC_GammaTot')
x=Chiplus
do jj=1,ndat
read(f,*) nc, (theo(jj)%particle(x)%M(i) ,i=1,np(x)), &
& (theo(jj)%particle(x)%GammaTot(i),i=1,np(x))
enddo
case('MN_GammaTot')
x=Chineut
do jj=1,ndat
read(f,*) nc, (theo(jj)%particle(x)%M(i) ,i=1,np(x)), &
& (theo(jj)%particle(x)%GammaTot(i),i=1,np(x))
enddo
case('effC')
do jj=1,ndat
read(f,*) nc, (effC(jj)%hjss_s(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjss_p(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjcc_s(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjcc_p(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjbb_s(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjbb_p(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjtt_s(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjtt_p(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjmumu_s(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjmumu_p(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjtautau_s(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjtautau_p(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjWW(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjZZ(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjZga(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjgaga(i) ,i=1,np(Hneut)), &
& (effC(jj)%hjgg(i) ,i=1,np(Hneut)), &
& ((effC(jj)%hjhiZ(j,i) ,i=1,j),j=1,np(Hneut))
! read(f,*) nc, (g2(jj)%hjss_s(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjss_p(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjcc_s(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjcc_p(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjbb_s(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjbb_p(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjtoptop_s(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjtoptop_p(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjmumu_s(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjmumu_p(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjtautau_s(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjtautau_p(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjWW(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjZZ(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjZga(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjgaga(i) ,i=1,np(Hneut)), &
! & (g2(jj)%hjgg(i) ,i=1,np(Hneut)), &
! ! & (g2(jj)%hjggZ(i) ,i=1,np(Hneut)), &
! & ((g2(jj)%hjhiZ(j,i) ,i=1,j),j=1,np(Hneut))
enddo
case('LEP_HZ_CS_ratios')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lep%XS_hjZ_ratio(i) ,i=1,np(Hneut))
enddo
case('LEP_H_ff_CS_ratios')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lep%XS_bbhj_ratio(i) ,i=1,np(Hneut)), &
& (theo(jj)%lep%XS_tautauhj_ratio(i) ,i=1,np(Hneut))
enddo
case('LEP_2H_CS_ratios')
do jj=1,ndat
read(f,*) nc, ((theo(jj)%lep%XS_hjhi_ratio(j,i),i=1,j),j=1,np(Hneut))
enddo
case('LEP_HpHm_CS_ratios')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lep%XS_HpjHmj_ratio(i) ,i=1,np(Hplus))
enddo
case('LEP_CpCm_CS')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lep%XS_CpjCmj(i) ,i=1,np(Chiplus))
enddo
case('LEP_2N_CS')
do jj=1,ndat
read(f,*) nc, ((theo(jj)%lep%XS_NjNi(j,i),i=1,j),j=1,np(Chineut))
enddo
! case('TEVLHC_H_0jet_partCS_ratios')
! do jj=1,ndat
! read(f,*) nc, (partR(jj)%gg_hj(i) ,i=1,np(Hneut)), &
! & (partR(jj)%qq_hj(5,i) ,i=1,np(Hneut))
! enddo
! case('TEVLHC_H_1jet_partCS_ratios')
! do jj=1,ndat
! read(f,*) nc, (partR(jj)%bg_hjb(i),i=1,np(Hneut))
! enddo
! case('TEVLHC_HW_partCS_ratios')
! do jj=1,ndat
! read(f,*) nc, ((partR(jj)%qq_hjWp(q,i) ,i=1,np(Hneut)), q=1,partR(jj)%nq_hjWp), &
! & ((partR(jj)%qq_hjWm(q,i) ,i=1,np(Hneut)), q=1,partR(jj)%nq_hjWm)
! enddo
! case('TEVLHC_HZ_partCS_ratios')
! do jj=1,ndat
! read(f,*) nc,(partR(jj)%gg_hjZ(i) ,i=1,np(Hneut)), &
! & (( partR(jj)%qq_hjZ(q,i) ,i=1,np(Hneut)), q=1,partR(jj)%nq_hjZ )
! enddo
! case('TEV_H_vbf_hadCS_ratios')
! do jj=1,ndat
! read(f,*) nc, (theo(jj)%tev%XS_vbf_ratio(i),i=1,np(Hneut))
! enddo
! case('TEV_H_tt_hadCS_ratios')
! do jj=1,ndat
! read(f,*) nc, (theo(jj)%tev%XS_tthj_ratio(i),i=1,np(Hneut))
! enddo
case('TEV_1H_hadCS_ratios')
do jj=1,ndat
read(f,*) nc, (theo(jj)%tev%XS_hj_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%tev%XS_gg_hj_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%tev%XS_bb_hj_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%tev%XS_hjW_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%tev%XS_hjZ_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%tev%XS_vbf_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%tev%XS_tthj_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%tev%XS_thj_tchan_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%tev%XS_thj_schan_ratio(i),i=1,np(Hneut))
enddo
! case('LHC7_H_vbf_hadCS_ratios')
! do jj=1,ndat
! read(f,*) nc, (theo(jj)%lhc7%XS_vbf_ratio(i),i=1,np(Hneut))
! enddo
! case('LHC7_H_tt_hadCS_ratios')
! do jj=1,ndat
! read(f,*) nc, (theo(jj)%lhc7%XS_tthj_ratio(i),i=1,np(Hneut))
! enddo
case('LHC7_1H_hadCS_ratios')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lhc7%XS_hj_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc7%XS_gg_hj_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%lhc7%XS_bb_hj_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%lhc7%XS_hjW_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc7%XS_hjZ_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc7%XS_vbf_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc7%XS_tthj_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc7%XS_thj_tchan_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%lhc7%XS_thj_schan_ratio(i),i=1,np(Hneut))
enddo
! case('LHC8_H_vbf_hadCS_ratios')
! do jj=1,ndat
! read(f,*) nc, (theo(jj)%lhc8%XS_vbf_ratio(i),i=1,np(Hneut))
! enddo
! case('LHC8_H_tt_hadCS_ratios')
! do jj=1,ndat
! read(f,*) nc, (theo(jj)%lhc8%XS_tthj_ratio(i),i=1,np(Hneut))
! enddo
case('LHC8_1H_hadCS_ratios')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lhc8%XS_hj_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc8%XS_gg_hj_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%lhc8%XS_bb_hj_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%lhc8%XS_hjW_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc8%XS_hjZ_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc8%XS_vbf_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc8%XS_tthj_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc8%XS_thj_tchan_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%lhc8%XS_thj_schan_ratio(i),i=1,np(Hneut))
enddo
case('LHC13_1H_hadCS_ratios')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lhc13%XS_hj_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc13%XS_gg_hj_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%lhc13%XS_bb_hj_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%lhc13%XS_hjW_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc13%XS_hjZ_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc13%XS_vbf_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc13%XS_tthj_ratio(i) ,i=1,np(Hneut)) , &
& (theo(jj)%lhc13%XS_thj_tchan_ratio(i),i=1,np(Hneut)) , &
& (theo(jj)%lhc13%XS_thj_schan_ratio(i),i=1,np(Hneut))
enddo
case('BR_H_OP')
do jj=1,ndat
read(f,*) nc, (theo(jj)%BR_hjss(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjcc(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjbb(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjtt(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjmumu(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjtautau(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjWW(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjZZ(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjZga(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjgaga(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjgg(i) ,i=1,np(Hneut))
enddo
BRdirectinput=.True.
case('TEV_Hplus_hadCS')
do jj=1,ndat
read(f,*) nc, (theo(jj)%tev%XS_Hpjtb(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%tev%XS_Hpjcb(i) ,i=1,np(Hplus)) , &
& (theo(jj)%tev%XS_Hpjbjet(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%tev%XS_Hpjcjet(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%tev%XS_Hpjjetjet(i) ,i=1,np(Hplus)) , &
& (theo(jj)%tev%XS_HpjW(i) ,i=1,np(Hplus)) , &
& (theo(jj)%tev%XS_HpjZ(i) ,i=1,np(Hplus)) , &
& (theo(jj)%tev%XS_vbf_Hpj(i) ,i=1,np(Hplus)) , &
& (theo(jj)%tev%XS_HpjHmj(i) ,i=1,np(Hplus)) , &
& ((theo(jj)%tev%XS_Hpjhi(j,i) ,i=1,np(Hneut)),j=1,np(Hplus))
enddo
case('LHC7_Hplus_hadCS')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lhc7%XS_Hpjtb(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%lhc7%XS_Hpjcb(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc7%XS_Hpjbjet(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%lhc7%XS_Hpjcjet(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%lhc7%XS_Hpjjetjet(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc7%XS_HpjW(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc7%XS_HpjZ(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc7%XS_vbf_Hpj(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc7%XS_HpjHmj(i) ,i=1,np(Hplus)) , &
& ((theo(jj)%lhc7%XS_Hpjhi(j,i) ,i=1,np(Hneut)),j=1,np(Hplus))
enddo
case('LHC8_Hplus_hadCS')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lhc8%XS_Hpjtb(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%lhc8%XS_Hpjcb(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc8%XS_Hpjbjet(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%lhc8%XS_Hpjcjet(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%lhc8%XS_Hpjjetjet(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc8%XS_HpjW(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc8%XS_HpjZ(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc8%XS_vbf_Hpj(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc8%XS_HpjHmj(i) ,i=1,np(Hplus)) , &
& ((theo(jj)%lhc8%XS_Hpjhi(j,i) ,i=1,np(Hneut)),j=1,np(Hplus))
enddo
case('LHC13_Hplus_hadCS')
do jj=1,ndat
read(f,*) nc, (theo(jj)%lhc13%XS_Hpjtb(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%lhc13%XS_Hpjcb(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc13%XS_Hpjbjet(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%lhc13%XS_Hpjcjet(i) ,i=1,np(Hplus)) , &
+ & (theo(jj)%lhc13%XS_Hpjjetjet(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc13%XS_HpjW(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc13%XS_HpjZ(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc13%XS_vbf_Hpj(i) ,i=1,np(Hplus)) , &
& (theo(jj)%lhc13%XS_HpjHmj(i) ,i=1,np(Hplus)) , &
& ((theo(jj)%lhc13%XS_Hpjhi(j,i) ,i=1,np(Hneut)),j=1,np(Hplus))
enddo
case('BR_H_NP')
+
+ if(np(Hplus)>0) then
+ allocate(BR_hjHpiW_in(np(Hneut)*np(Hplus)))
+ BR_hjHpiW_in =0.0D0
+ endif
+
if(np(Hneut)>1)then !because if np(Hneut)=1, then matrix BR_hjhihi has no off diagonal entries
! allocate(BR_hjhihi_in(np(Hneut)**2-np(Hneut)))
! BR_hjhihi_in =0.0D0
allocate(BR_hkhjhi_in(np(Hneut)**2*(np(Hneut)-1)/2))
BR_hkhjhi_in =0.0D0
allocate(BR_hjhiZ_in(np(Hneut)**2-np(Hneut)))
BR_hjhiZ_in =0.0D0
- do jj=1,ndat
+ do jj=1,ndat
+ if(np(Hplus)>0)then
+ read(f,*) nc, (theo(jj)%BR_hjinvisible(i) ,i=1,np(Hneut)), &
+& (BR_hkhjhi_in(i) ,i=1,int(np(Hneut)**2*(np(Hneut)-1)/2)),&
+& (BR_hjhiZ_in(i) ,i=1,int(np(Hneut)**2-np(Hneut))),&
+& (theo(jj)%BR_hjemu(i) ,i=1,np(Hneut)), &
+& (theo(jj)%BR_hjetau(i) ,i=1,np(Hneut)), &
+& (theo(jj)%BR_hjmutau(i) ,i=1,np(Hneut)),&
+& (BR_hjHpiW_in(i) ,i=1,int(np(Hneut)*np(Hplus)))
+ else
read(f,*) nc, (theo(jj)%BR_hjinvisible(i) ,i=1,np(Hneut)), &
& (BR_hkhjhi_in(i) ,i=1,int(np(Hneut)**2*(np(Hneut)-1)/2)),&
& (BR_hjhiZ_in(i) ,i=1,int(np(Hneut)**2-np(Hneut))),&
& (theo(jj)%BR_hjemu(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjetau(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjmutau(i) ,i=1,np(Hneut))
+ endif
! & ( BR_hjhihi_in(i) ,i=1,int(np(Hneut)**2-np(Hneut)))
theo(jj)%BR_hkhjhi=0.0D0
count=0
do k=1,np(Hneut)
do j=1,np(Hneut)
do i=1,np(Hneut)
if(i.ne.k.and.j.ne.k) then
if(j.le.i) then
count=count+1
theo(jj)%BR_hkhjhi(k,j,i)=BR_hkhjhi_in(count)
else
theo(jj)%BR_hkhjhi(k,j,i)=theo(jj)%BR_hkhjhi(k,i,j)
endif
! write(*,*) "Reading BR_hkhjhi(",k,j,i,") element = ", theo(jj)%BR_hkhjhi(k,j,i)
endif
enddo
enddo
enddo
theo(jj)%BR_hjhiZ = 0.0D0
count=0
do j=1,np(Hneut)
do i=1,np(Hneut)
if(i.ne.j)then
count=count+1
theo(jj)%BR_hjhiZ(j,i) = BR_hjhiZ_in(count)
endif
! write(*,*) "Reading BR_hjhiZ(",j,i,") element = ", theo(jj)%BR_hjhiZ(j,i)
enddo
enddo
+ if(np(Hplus)>0)then
+ theo(jj)%BR_hjHpiW = 0.0D0
+ count=0
+ do j=1,np(Hneut)
+ do i=1,np(Hplus)
+ count=count+1
+ theo(jj)%BR_hjHpiW(j,i) = BR_hjHpiW_in(count)
+ enddo
+ enddo
+ endif
! k=0
! do j=1,np(Hneut)
! do i=1,np(Hneut)
! if(i.ne.j)then
! k=k+1
! theo(jj)%BR_hjhihi(j,i) = BR_hjhihi_in(k)
! endif
! enddo
! enddo
enddo
! deallocate(BR_hjhihi_in)
deallocate(BR_hkhjhi_in)
deallocate(BR_hjhiZ_in)
else
- do jj=1,ndat
+ do jj=1,ndat
+ if(np(Hplus)>0)then
read(f,*) nc, (theo(jj)%BR_hjinvisible(i) ,i=1,np(Hneut)),&
& (theo(jj)%BR_hjemu(i) ,i=1,np(Hneut)), &
& (theo(jj)%BR_hjetau(i) ,i=1,np(Hneut)), &
-& (theo(jj)%BR_hjmutau(i) ,i=1,np(Hneut))
+& (theo(jj)%BR_hjmutau(i) ,i=1,np(Hneut)), &
+& (BR_hjHpiW_in(i) ,i=1,int(np(Hneut)*np(Hplus)))
+
+ theo(jj)%BR_hjHpiW = 0.0D0
+ count=0
+ do j=1,np(Hneut)
+ do i=1,np(Hplus)
+ count=count+1
+ theo(jj)%BR_hjHpiW(j,i) = BR_hjHpiW_in(count)
+ enddo
+ enddo
+ else
+ read(f,*) nc, (theo(jj)%BR_hjinvisible(i) ,i=1,np(Hneut)),&
+& (theo(jj)%BR_hjemu(i) ,i=1,np(Hneut)), &
+& (theo(jj)%BR_hjetau(i) ,i=1,np(Hneut)), &
+& (theo(jj)%BR_hjmutau(i) ,i=1,np(Hneut))
+ endif
+
enddo
endif
case('BR_t')
do jj=1,ndat
read(f,*) nc, theo(jj)%BR_tWpb, &
& (theo(jj)%BR_tHpjb(i) ,i=1,np(Hplus))
enddo
case('BR_Hplus')
if(np(Hneut).ge.1) then
allocate(BR_HpjhiW_in(int(np(Hplus)*np(Hneut))))
BR_HpjhiW_in =0.0D0
do jj=1,ndat
read(f,*) nc, (theo(jj)%BR_Hpjcs(i) ,i=1,np(Hplus)), &
& (theo(jj)%BR_Hpjcb(i) ,i=1,np(Hplus)), &
& (theo(jj)%BR_Hpjtaunu(i) ,i=1,np(Hplus)), &
& (theo(jj)%BR_Hpjtb(i) ,i=1,np(Hplus)), &
& (theo(jj)%BR_HpjWZ(i) ,i=1,np(Hplus)), &
& (BR_HpjhiW_in(i) ,i=1,int(np(Hplus)*np(Hneut)))
count=0
do j=1,np(Hplus)
do i=1,np(Hneut)
count=count+1
theo(jj)%BR_HpjhiW(j,i) = BR_HpjhiW_in(count)
enddo
enddo
enddo
else
do jj=1,ndat
read(f,*) nc, (theo(jj)%BR_Hpjcs(i) ,i=1,np(Hplus)), &
& (theo(jj)%BR_Hpjcb(i) ,i=1,np(Hplus)), &
& (theo(jj)%BR_Hpjtaunu(i) ,i=1,np(Hplus)), &
& (theo(jj)%BR_Hpjtb(i) ,i=1,np(Hplus)), &
& (theo(jj)%BR_HpjWZ(i) ,i=1,np(Hplus))
enddo
endif
case('BR_C')
do jj=1,ndat
read(f,*) nc, ((theo(jj)%BR_CjqqNi(j,i) ,i=1,np(Chineut)),j=1,np(Chiplus)), &
& ((theo(jj)%BR_CjlnuNi(j,i) ,i=1,np(Chineut)),j=1,np(Chiplus)), &
& ((theo(jj)%BR_CjWNi(j,i) ,i=1,np(Chineut)),j=1,np(Chiplus))
enddo
case('BR_N')
if(np(Chineut)>1)then !because if np(Chineut)=1, then BR matrix has no off diagonal entries
allocate( BR_NjqqNi_in( np(Chineut)**2-np(Chineut) ) )
allocate( BR_NjZNi_in( np(Chineut)**2-np(Chineut) ) )
BR_NjqqNi_in =0.0D0
BR_NjZNi_in =0.0D0
do jj=1,ndat
read(f,*) nc, (BR_NjqqNi_in(i) ,i=1,int(np(Chineut)**2-np(Chineut))) , &
& (BR_NjZNi_in(i) ,i=1,int(np(Chineut)**2-np(Chineut)))
k=0
do j=1,np(Chineut)
do i=1,np(Chineut)
if(i.ne.j)then
k=k+1
theo(jj)%BR_NjqqNi(j,i) = BR_NjqqNi_in(k)
theo(jj)%BR_NjZNi(j,i) = BR_NjZNi_in(k)
endif
enddo
enddo
enddo
deallocate(BR_NjqqNi_in)
deallocate(BR_NjZNi_in)
endif
case('CP_values')
do jj=1,ndat
read(f,*) nc, (theo(jj)%CP_value(i) ,i=1,np(Hneut))
enddo
case('additional')
do jj=1,ndat
read(f,*) nc, (theo(jj)%additional(i),i=1,n_additional)
enddo
case default
stop 'problem in subroutine readthefile (2)'
end select
close(f)
if(ndat.ne.nint(nc))then
write(*,*)'last line read in was not labled ndat'
call file_name_msg(f)
stop 'error in input file (see standard output for filename and more details).'
endif
endif
end subroutine readthefile
!************************************************************
subroutine extractnumbersfromline(line, nc, numbers)
! Scans a line and extracts numbers separated by whitespaces
!************************************************************
implicit none
character(LEN=500), intent(in) :: line
double precision, allocatable, intent(out) :: numbers(:)
double precision, intent(out) :: nc
! integer, intent(out) :: ii
integer :: i, indx, prev, beginning, N
double precision :: dbltmp
prev = 0
beginning = 1
N = 0
do i=1,len(line)
indx = index('0123456789.EeDd-+', line(i:i))
if (indx.eq.0 .and. prev.gt.0) then
read(line(beginning:i-1), *) dbltmp
N=N+1
else if (indx.gt.0 .and. prev.eq.0) then
beginning = i
end if
prev = indx
end do
allocate(numbers(N-1))
N=0
do i=1,len(line)
indx = index('0123456789.EeDd-+', line(i:i))
if (indx.eq.0 .and. prev.gt.0) then
N=N+1
if(N.eq.1) then
read(line(beginning:i-1), *) nc
else
read(line(beginning:i-1), *) numbers(N-1)
endif
else if (indx.gt.0 .and. prev.eq.0) then
beginning = i
end if
prev = indx
end do
end subroutine extractnumbersfromline
!************************************************************
subroutine getbasiccommandline
!************************************************************
! finds whichanalyses,whichinput,np from command line
!************************************************************
!nb iargc and getarg are non-standard
use usefulbits, only : np,pdesc,whichanalyses,whichinput,inputmethod
implicit none
!-----------------------------------internal
#ifndef NAGf90Fortran
integer :: iargc
#endif
character(LEN=100) :: temp
character(LEN=5) :: nHtemp
integer :: i,x,xmax
integer :: number_args
logical :: wrong_args
logical :: additionalSLHAoutput = .False.
!-------------------------------------------
number_args = IARGC()
if(inputmethod .eq. 'datfile')then
if(official)then !whichanalyses, whichinput, np(Hneut), np(Hplus) , prefix
nargs_datfile = 2+ 2 +1
np(Chineut)=0
np(Chiplus)=0
else !whichanalyses, whichinput, all elements of np, prefix
nargs_datfile = 2+ ubound(np,dim=1) +1
endif
wrong_args= (number_args .ne. nargs_datfile)
additionalSLHAoutput = (number_args.eq.(nargs_datfile+1))
elseif(inputmethod .eq. 'website')then
wrong_args= (number_args .lt. (2+ ubound(np,dim=1)))
else
write(*,*)'inputmethod=',inputmethod
stop 'error in getbasiccommandline'
endif
if(wrong_args.and.(.not.additionalSLHAoutput))then
write(*,*) "Incorrect number of parameters given on command line"
call command_line_how2
stop "Error: command line entered incorrectly (see standard output for more info)"
endif
! Read arguments into text strings.
i=1
temp=""
call GETARG(i,temp)
whichanalyses = ""
whichanalyses = trim(temp)
i=i+1
temp=""
call GETARG(i,temp)
whichinput = ""
whichinput = trim(temp)
i=i+1
if(whichinput.ne.'SLHA'.and.wrong_args.and.additionalSLHAoutput)then
write(*,*) "Incorrect number of parameters given on command line"
call command_line_how2
stop "Error: command line entered incorrectly (see standard output for more info)"
endif
if((inputmethod .eq. 'website').or.(.not.official))then
xmax=ubound(np,dim=1)
else !datfile, official
xmax=2 !nHneut,nHplus
endif
do x=1,xmax
temp=""
call GETARG(i,temp)
nHtemp = ""
nHtemp = trim(temp)
i=i+1
if(verify(nHtemp," 1234567890").gt.0)then ! checks that the string nHtemp just contains the characters " 1234567890"
! the function verify is standard in fortran 95
write(*,*)'Incorrect n'//trim(adjustl(pdesc(x)%short))//': not a number.'
write(*,*)'(you entered n'//trim(adjustl(pdesc(x)%short))//'="'//trim(adjustl(nHtemp))//'")'
write(*,*)'n'//trim(adjustl(pdesc(x)%short))//' is the number of '//trim(adjustl(pdesc(x)%long))//'s'
call command_line_how2
stop "Error: command line entered incorrectly (see standard output for more info)"
endif
read(nHtemp,*) np(x)
enddo
call check_number_of_particles
call check_whichinput
call check_whichanalyses
end subroutine getbasiccommandline
!************************************************************
subroutine command_line_how2
!************************************************************
use usefulbits, only : np,inputmethod
write(*,*)'The correct syntax for the command line is:'
if(inputmethod.eq.'website')then
if(ubound(np,dim=1).eq.4)then
write(*,*)' ./HiggsBounds whichanalyses whichinput nHneut nHplus nNeutralino nChargino debug ...'
write(*,*)'e.g.'
write(*,*)' ./HiggsBounds LandH part 3 1 4 2 T ...'
else
stop 'error in subroutine command_line_how2'
endif
elseif(.not.official)then
if(ubound(np,dim=1).eq.4)then
write(*,*)' ./HiggsBounds whichanalyses whichinput nHneut nHplus nNeutralino nChargino prefix'
write(*,*)'e.g.'
write(*,*)' ./HiggsBounds LandH part 3 1 4 2 mhmax'
else
stop 'error in subroutine command_line_how2'
endif
else !official, datfile
write(*,*)' ./HiggsBounds whichanalyses whichinput nHneut nHplus prefix'
write(*,*)'e.g.'
write(*,*)' ./HiggsBounds LandH part 3 1 mhmax'
endif
write(*,*)'See HiggsBounds manual for more details.'
call flush(6)
end subroutine command_line_how2
!************************************************************
subroutine check_whichinput
!************************************************************
use usefulbits, only : whichinput
select case(whichinput)
case('part','effC','hadr','SLHA')
case default
call command_line_how2
write(*,*)'Error: This value of "whichinput" is not allowed.'
write(*,*)'(you entered whichinput="'//trim(adjustl(whichinput))//'")'
write(*,*)'Allowed values for "whichinput" are (see manual):'
write(*,*)'part masses, branching ratios, decay widths, LEP cross sections,'
write(*,*)' Tevatron and LHC partonic cross sections'
write(*,*)'effC effective coupling approx'
write(*,*)'hadr masses, branching ratios, decay widths, LEP cross sections,'
write(*,*)' Tevatron and LHC hadronic cross sections'
write(*,*)'SLHA SUSY Les Houches Accord files'
call flush(6)
stop 'error: input type selected incorrectly (see standard output for more info)'
end select
end subroutine check_whichinput
!************************************************************
subroutine check_number_of_particles
!************************************************************
use usefulbits, only : np,pdesc,inputmethod,whichinput
integer :: x
do x=1,ubound(np,dim=1)
if(np(x).lt.0)then
write(*,*) 'number of '//trim(adjustl(pdesc(x)%long))//'s must be greater than zero'
if(inputmethod.eq.'datfile')call command_line_how2
stop 'error in subroutine check_number_of_particles (a) (see standard output for more info)'
elseif(np(x)>nHmax)then
write(*,*) 'number of '//trim(adjustl(pdesc(x)%long))//'s must be less than',nHmax
write(*,*) ' (if you need more than this, please contact us)'
if(inputmethod.eq.'datfile')call command_line_how2
stop 'error in subroutine check_number_of_particles (b) (see standard output for more info)'
endif
enddo
if(sum(np).eq.0)then
stop 'There should be a non-zero number of particles'
endif
if((inputmethod.eq.'datfile').and.(official))then
do x=3,ubound(np,dim=1) !i.e. particles other than Hneut,Hplus
if(np(x).gt.0)then
write(*,*)'In this version of HiggsBounds, the number of ' &
&//trim(adjustl(pdesc(x)%long))//'s must be zero'
write(*,*)'and you have entered the number',np(x)
write(*,*)'Please contact us if you would like more information.'
stop 'error in subroutine check_number_of_particles (c) (see standard output for more info)'
endif
enddo
endif
if(whichinput.eq.'SLHA')then
if((np(Hneut).lt.0).or.(np(Hneut).gt.5))then
write(*,*)'If a SLHA file is used as input,'
write(*,*)'number of neutral Higgs must be in the range 0:5'
stop 'error in subroutine check_number_of_particles (d) (see standard output for more info)'
endif
if((np(Hplus).lt.0).or.(np(Hplus).gt.1))then
write(*,*)'If a SLHA file is used as input,'
write(*,*)'number of charged Higgs must be in the range 0:1'
stop 'error in subroutine check_number_of_particles (e) (see standard output for more info)'
endif
endif
end subroutine check_number_of_particles
!************************************************************
subroutine check_whichanalyses
!************************************************************
use usefulbits, only : whichanalyses,inputmethod
select case(whichanalyses)
case('onlyL','onlyH','LandH','onlyP','list')
case default
if(inputmethod.eq.'datfile')call command_line_how2
write(*,*)'Error: This value of "whichanalyses" is not allowed'
write(*,*)'(you entered whichanalyses="'//trim(adjustl(whichanalyses))//'")'
write(*,*)'Allowed values for "whichanalyses" are:'
write(*,*)'onlyL only LEP results used'
write(*,*)'onlyH only hadronic colliders i.e. only Tevatron and LHC results used'
write(*,*)'LandH LEP, Tevatron and LHC results used'
write(*,*)'onlyP use all analyses with an arXiv number'
call flush(6)
stop 'error: experiment selected incorrectly (see standard output for more info)'
end select
end subroutine check_whichanalyses
!************************************************************
subroutine getshortcommandline(inf1,inf2)
!************************************************************
! used if inputmethod='datfile'
! finds infile1 from command line
!************************************************************
!nb iargc and getarg are non-standard
implicit none
!--------------------------------------input
character(LEN=*) :: inf1
character(LEN=*),optional :: inf2
!-----------------------------------internal
#ifndef NAGf90Fortran
integer :: iargc
#endif
character(LEN=100) :: temp
integer :: i
integer :: number_args
!-------------------------------------------
number_args = IARGC()
if(number_args.ne.nargs_datfile)then
if(number_args.eq.(nargs_datfile+1)) then
i=nargs_datfile
temp=""
call GETARG(i,temp)
inf1 = ""
inf1 = trim(temp)
i=i+1
temp=""
call GETARG(i,temp)
if(present(inf2)) then
inf2 = ""
inf2 = trim(temp)
endif
else
stop "Incorrect number of parameters given (getshortcommandline)"
endif
else
! Read last argument into text string.
i=nargs_datfile
temp=""
call GETARG(i,temp)
inf1 = ""
inf1 = trim(temp)
i=i+1
if(present(inf2)) then
inf2=inf1
endif
endif
write(*,*)"------"
write(*,*)"From command line:"
write(*,*)"prefix:",trim(inf1)
write(*,*)"------"
call flush(6)
end subroutine getshortcommandline
!****************************************************
function getfilelength(fileid)
!****************************************************
! calculates file length and checks for errors
! nb. files must end in a 'newline' character
!****************************************************
implicit none
!--------------------------------------input
integer fileid
!-----------------------------------function
integer :: getfilelength
!-----------------------------------internal
integer :: n,ios,m
character(LEN=5) :: filechar
character(LEN=20) :: sample
!-------------------------------------------
write(filechar,'(I5)')fileid
!this will count the number of lines in the file, including the last one,
! even if it doesn't end in a newline character
n = 0
do
read(fileid,'(a)',iostat=ios) sample
if(ios.lt.0)then
exit
elseif(ios.gt.0) then
call file_name_msg(fileid)
stop 'error in input file: see standard output'
elseif(trim(adjustl(sample)).eq.'')then
write(*,*)'No blank lines allowed in input file.'
call file_name_msg(fileid)
stop 'no blank lines allowed in input file: see standard output'
endif
n = n + 1
enddo
getfilelength=n
if(n.eq.0) return !stop 'File is empty'
rewind(fileid)
m = 0 ;
do !this will count the number of lines which end in a newline character
read(fileid,*,iostat=ios)
if(ios.lt.0) exit
m = m + 1
enddo
rewind(fileid)
if(m.ne.n)then !checking that every line end in a newline character
call file_name_msg(fileid)
stop 'Error: file needs to end with a newline character (see standard output for filename)'
endif
end function getfilelength
!****************************************************
subroutine file_name_msg(fileid)
!****************************************************
use usefulbits,only : infile1
implicit none
integer, intent(in) :: fileid
write(*,*)'The problematic input file is called:'
write(*,*)' '//trim(adjustl(infile1))//trim(adjustl(stem_array(fileid-f_orig)))//'.dat'
call flush(6)
end subroutine file_name_msg
!****************************************************
function count_columns(fileid)
!****************************************************
! calculateshow many columns of numbers there are in file
! with the id 'fileid'
! max line length= 1000 characters
! assumes objects in columns are separated by spaces
! and that first line has the same
! number of columns as the rest of the file
!****************************************************
implicit none
!--------------------------------------input
integer, intent(in) :: fileid
!-----------------------------------function
integer :: count_columns
!-----------------------------------internal
integer :: n,x,a
character(LEN=5000) :: teststr
!-------------------------------------------
n=0
read(fileid,'(a)')teststr ! reads first line into a string 'teststr'
teststr=adjustl(teststr) ! shifts characters left so that first char is not a space
a=1
do while (a.gt.0) !replace all tab characters with spaces
a=INDEX(teststr,' ')
teststr=teststr(:a-1)//' '//teststr(a+1:)
enddo
teststr=adjustl(teststr) ! shifts characters left so that first char is not a space
do while (trim(adjustl(teststr)).ne.'') !while teststr is not made of spaces
n=n+1
x=INDEX(teststr,' ') !finds position of first space from left
teststr=adjustl(teststr(x:)) !chops of everything left of the first space, then adjustl
enddo
count_columns=n
rewind(fileid)
end function count_columns
!********************************************************
subroutine test_input(n)
! prints out input (useful for testing)
!********************************************************
use usefulbits, only : np, theo, g2, partR
implicit none
!--------------------------------------input
integer :: n
!-----------------------------------internal
integer :: j, i
!-------------------------------------------
write(*,*)'**************INPUT**************'
#include "write_out_input.txt"
write(*,*)'*********************************'
end subroutine test_input
!*****************************************************
function get_ncol(stem)
! calculates how many columns HiggsBounds should expect
! to find in file stem//'.dat'
use usefulbits, only : np,n_additional
implicit none
!--------------------------------------input
character(LEN=50), intent(in) :: stem
!-----------------------------------function
integer :: get_ncol
!-----------------------------------internal
integer :: x
!-------------------------------------------
select case(trim(stem))
case('MH_GammaTot')
x=2*np(Hneut)
case('MHall_uncertainties')
x=np(Hneut)+np(Hplus)
case('MHplus_GammaTot')
x=2*np(Hplus)
case('MC_GammaTot')
x=2*np(Chiplus)
case('MN_GammaTot')
x=2*np(Chineut)
case('BR_H_NP')
!n.b.: extended by hk->hjhi (n^2(n-1)/2), hj->hiZ (n(n-1)), hj->emu, hj->etau, hj->mutau
+! and hj->HpjW
! x=1*np(Hneut)+np(Hneut)*(np(Hneut)-1)
- x=4*np(Hneut) + np(Hneut)*(np(Hneut)-1) + np(Hneut)**2*(np(Hneut)-1)/2
+ x=4*np(Hneut) + np(Hneut)*(np(Hneut)-1) + np(Hneut)**2*(np(Hneut)-1)/2 + np(Hneut)*np(Hplus)
case('BR_H_OP')
!n.b.: added BR(Hj->tt).
! x=10*np(Hneut)
x=11*np(Hneut)
case('LEP_HZ_CS_ratios')
x=1*np(Hneut)
case('LEP_H_ff_CS_ratios')
x=2*np(Hneut)
case('LEP_2H_CS_ratios')
x= (np(Hneut)*(np(Hneut)+1))/2
case('LEP_HpHm_CS_ratios')
x=1*np(Hplus)
case('LEP_CpCm_CS')
x=1*np(Chiplus)
case('LEP_2N_CS')
x=1*(np(Chineut)*(np(Chineut)+1))/2
case('effC')
!n.b.: removed g2hjggZ
! x=18*np(Hneut) + (np(Hneut)*(np(Hneut)+1))/2
x=17*np(Hneut) + (np(Hneut)*(np(Hneut)+1))/2
! case('TEVLHC_H_0jet_partCS_ratios')
! x=2*np(Hneut)
! case('TEVLHC_H_1jet_partCS_ratios')
! x=1*np(Hneut)
! case('TEVLHC_HW_partCS_ratios')
! x=4*np(Hneut)
! case('TEVLHC_HZ_partCS_ratios')
! x=6*np(Hneut)
! case('TEV_H_vbf_hadCS_ratios')
! x=1*np(Hneut)
! case('TEV_H_tt_hadCS_ratios')
! x=1*np(Hneut)
case('TEV_1H_hadCS_ratios')
!n.b.: extended by gg->hj,hjbb,thj(t-channel),thj(s-channel)
! x=6*np(Hneut)
x=9*np(Hneut)
! case('LHC7_H_vbf_hadCS_ratios')
! x=1*np(Hneut)
! case('LHC7_H_tt_hadCS_ratios')
! x=1*np(Hneut)
case('LHC7_1H_hadCS_ratios')
x=9*np(Hneut)
! case('LHC8_H_vbf_hadCS_ratios')
! x=1*np(Hneut)
! case('LHC8_H_tt_hadCS_ratios')
! x=1*np(Hneut)
case('LHC8_1H_hadCS_ratios')
x=9*np(Hneut)
case('LHC13_1H_hadCS_ratios')
x=9*np(Hneut)
case('TEV_Hplus_hadCS')
- x=6*np(Hplus)+np(Hplus)*np(Hneut)
+ x=9*np(Hplus)+np(Hplus)*np(Hneut)
case('LHC7_Hplus_hadCS')
- x=6*np(Hplus)+np(Hplus)*np(Hneut)
+ x=9*np(Hplus)+np(Hplus)*np(Hneut)
case('LHC8_Hplus_hadCS')
- x=6*np(Hplus)+np(Hplus)*np(Hneut)
+ x=9*np(Hplus)+np(Hplus)*np(Hneut)
case('LHC13_Hplus_hadCS')
- x=6*np(Hplus)+np(Hplus)*np(Hneut)
+ x=9*np(Hplus)+np(Hplus)*np(Hneut)
case('BR_t')
x=1+np(Hplus)
case('BR_Hplus')
!n.b.: extended by Hpj->tb, Hpj->WZ, Hpj->hiW
! x=3*np(Hplus)
x=5*np(Hplus) + np(Hplus)*np(Hneut)
case('BR_C')
x=3*np(Chiplus)*np(Chineut)
case('BR_N')
x=2*np(Chineut)*(np(Chineut)-1)
case('CP_values')
x=1*np(Hneut)
case('additional')
x=n_additional
case default
write(*,*)'stem=',stem
call flush(6)
stop 'error in function get_ncol'
end select
! each file has the line number as the first column
get_ncol= x + 1
end function get_ncol
!************************************************************
end module input
!****************************************************
Index: trunk/HiggsBounds-5/AllAnalyses
===================================================================
Cannot display: file marked as a binary type.
svn:mime-type = application/octet-stream

File Metadata

Mime Type
text/x-diff
Expires
Tue, Nov 19, 2:30 PM (1 d, 8 h)
Storage Engine
blob
Storage Format
Raw Data
Storage Handle
3804742
Default Alt Text
(512 KB)

Event Timeline