Index: trunk/HiggsBounds-5/AllAnalyses =================================================================== Cannot display: file marked as a binary type. svn:mime-type = application/octet-stream Index: trunk/HiggsBounds-5/S95tables.f90 =================================================================== --- trunk/HiggsBounds-5/S95tables.f90 (revision 600) +++ trunk/HiggsBounds-5/S95tables.f90 (revision 601) @@ -1,5295 +1,5329 @@ ! This file is part of HiggsBounds ! -KW !****************************************************************** module S95tables !****************************************************************** use S95tables_type1 use S95tables_type2 use usefulbits, only: Hneut,Hplus implicit none private public :: & & S95_t1,S95_t2, & & setup_S95tables,deallocate_S95tables, & & calcfact,outputproc, & & check_against_bound, & & convolve_chisq_with_gaussian, & & S95_t1_or_S95_t2_idfromelementnumber, & & f_from_t2,f_from_t3,f_from_slices_t2, & & WhichColliderString,get_collider_element_number, & & inrange, deallocate_Exptranges integer :: ntable1,ntable2 !----------------------------------------------------------------------------------- ! delta_M*_* determine how close in mass particles should be before their masses are combined ! nb. delta*_* is only used for tables of type 1 at the moment ! for some analyses, S95_t1(x)%deltax has already been set in S95tables_type1.f90 ! for analyses where S95_t1(x)%deltax is *not* has already set: ! we set ! LEP neutral Higgs tables to have deltax=delta_Mh_LEP ! Tevatron neutral Higgs tables to have deltax=delta_Mh_TEV ! LHC neutral Higgs tables to have deltax=delta_Mh_LHC ! LEP charged Higgs tables to have deltax=delta_Mhplus_LEP ! Tevatron charged Higgs tables to have deltax=delta_Mhplus_TEV ! LHC charged Higgs tables to have deltax=delta_Mhplus_LHC ! other LEP tables to have deltax=delta_M_LEP_default ! other Tevatron tables to have deltax=delta_M_TEV_default ! other LHC tables to have deltax=delta_M_LHC_default ! setting delta_M*_LHC and/or delta_M*_TEV and/or delta_M*_LEP to zero turns this feature off ! DO NOT CHANGE THESE VALUES BEFORE READING THE MANUAL ! even when it is appropriate to add the cross sections, we would recommend using ! delta_Mh_LEP<=2.0D0, delta_Mh_TEV<=10.0, delta_Mh_LHC<=10.0 double precision, parameter :: delta_Mh_LEP=0.0D0 double precision, parameter :: delta_Mh_TEV=10.0D0 double precision, parameter :: delta_Mh_LHC=10.0D0 double precision, parameter :: delta_Mhplus_LEP=0.0D0 double precision, parameter :: delta_Mhplus_TEV=0.0D0 double precision, parameter :: delta_Mhplus_LHC=0.0D0 double precision, parameter :: delta_M_LEP_default=0.0D0 !where delta_M_LEP/TEV/LHC is not specified double precision, parameter :: delta_M_TEV_default=0.0D0 !these values will be used double precision, parameter :: delta_M_LHC_default=0.0D0 ! !double precision, parameter :: delta_Mh_LEP=15.0D0 !crazy values - for debugging only !double precision, parameter :: delta_Mh_TEV=15.0D0 !crazy(ish) values - for debugging only !double precision, parameter :: delta_Mh_LHC=15.0D0 !crazy(ish) values - for debugging only !----------------------------------------------------------------------------------- ! Use the SM expected channel contributions to weight the channels in the likeness test logical :: use_weight = .True. ! eps determines how strict the Standard Model test is double precision, parameter :: eps=2.0D-2 !double precision, parameter :: eps=1.0D3 !crazy value - for debugging only !----------------------------------------------------------------------------------- !table type 1----------------------------- type(table1),allocatable :: S95_t1(:) !------------------------------------------ !table type 2------------------------------ type(table2),allocatable :: S95_t2(:) !------------------------------------------ character(LEN=5),parameter :: colliders(5) = (/'LEP ','TEV ','LHC7 ','LHC8 ','LHC13'/) !------------------------------------------- double precision, allocatable :: Exptrange_Mhmin_forSMdecays(:), Exptrange_Mhmax_forSMdecays(:) double precision, allocatable :: Exptrange_Mhmin_forSMXS(:), Exptrange_Mhmax_forSMXS(:) contains !********************************************************** subroutine setup_S95tables ! Allocates and calls subroutines to fill S95_t1, S95_t2 ! (which store the experimental data) ! Sets delta_M_TEV,delta_M_LEP,delta_M_LHC which govern how close Higgs ! need to be in mass before HiggsBounds combines their cross sections !********************************************************** use usefulbits, only : debug,np,not_a_particle use theory_BRfunctions, only : BRSMt1Mhmax,BRSMt1Mhmin use theory_XS_SM_functions, only : tevXS_SM_functions_xmin, tevXS_SM_functions_xmax, & & lhc7XS_SM_functions_xmin,lhc7XS_SM_functions_xmax, & & lhc8XS_SM_functions_xmin,lhc8XS_SM_functions_xmax, & & lhc13XS_SM_functions_xmin,lhc13XS_SM_functions_xmax implicit none !-----------------------------------internal integer :: i,c double precision, allocatable :: max_expt_delta_Mh(:) double precision, allocatable :: Expttables_Mhmin_forSMXS(:),Expttables_Mhmax_forSMXS(:) double precision, allocatable :: Expttables_Mhmin_forSMdecays(:),Expttables_Mhmax_forSMdecays(:) double precision, allocatable :: delta_x_default(:,:) ! these numbers have to be changed appropriately every time a table is added ! or taken away: - ntable1=204 + ntable1=206 ntable2=39 ! table type 2 involves 2 variables allocate(S95_t1(ntable1)) allocate(S95_t2(ntable2)) call initializetables_type1_blank(S95_t1) call initializetables_type2_blank(S95_t2) call initializetables1(S95_t1) call initializetables2(S95_t2) allocate( Expttables_Mhmin_forSMXS( size(colliders,dim=1) ) ) allocate( Expttables_Mhmax_forSMXS( size(colliders,dim=1) ) ) allocate( Exptrange_Mhmin_forSMXS( size(colliders,dim=1) ) ) allocate( Exptrange_Mhmax_forSMXS( size(colliders,dim=1) ) ) allocate( Expttables_Mhmin_forSMdecays( size(colliders,dim=1) ) ) allocate( Expttables_Mhmax_forSMdecays( size(colliders,dim=1) ) ) allocate( Exptrange_Mhmin_forSMdecays( size(colliders,dim=1) ) ) allocate( Exptrange_Mhmax_forSMdecays( size(colliders,dim=1) ) ) allocate( max_expt_delta_Mh( size(colliders,dim=1) ) ) ! will pick up on any typos in S95_t1%expt do i=lbound(S95_t1,dim=1),ubound(S95_t1,dim=1) if(WhichColliderElement(S95_t1(i)%expt, S95_t1(i)%energy).eq.0)then write(*,*)'~'//trim(adjustl(S95_t1(i)%expt))//'~ is not a valid experiment name' stop 'error in setup_S95tables (a)' endif enddo ! will pick up on any typos in S95_t2%expt do i=lbound(S95_t2,dim=1),ubound(S95_t2,dim=1) if(WhichColliderElement(S95_t2(i)%expt, S95_t2(i)%energy).eq.0)then write(*,*)'~'//trim(adjustl(S95_t2(i)%expt))//'~ is not a valid experiment name' stop 'error in setup_S95tables (b)' endif enddo ! checks that none of the id's are repeated in S95_t1 do i=lbound(S95_t1,dim=1),ubound(S95_t1,dim=1) if( count(S95_t1%id.eq.S95_t1(i)%id) & +count(S95_t2%id.eq.S95_t1(i)%id).ne.1)then write(*,*)'the id',S95_t1(i)%id,'is repeated' stop 'error in setup_S95tables (c1)' endif enddo ! checks that none of the id's are repeated in S95_t2 do i=lbound(S95_t2,dim=1),ubound(S95_t2,dim=1) if( count(S95_t1%id.eq.S95_t2(i)%id)& +count(S95_t2%id.eq.S95_t2(i)%id).ne.1)then write(*,*)'the id',S95_t2(i)%id,'is repeated' stop 'error in setup_S95tables (c2)' endif enddo !check to make sure that S95_t1(i)%particle_x are all particles do i=lbound(S95_t1,dim=1),ubound(S95_t1,dim=1) if(S95_t1(i)%particle_x.eq.not_a_particle)then write(*,*)S95_t1(i)%id,'particle_x=not_a_particle.' stop 'error in setup_S95tables (d1)' endif enddo !check to make sure that S95_t2(i)%particle_x2 are all particles do i=lbound(S95_t2,dim=1),ubound(S95_t2,dim=1) if(S95_t2(i)%particle_x2.eq.not_a_particle)then write(*,*)S95_t2(i)%id,'particle_x2=not_a_particle.' stop 'error in setup_S95tables (d2)' endif enddo ! looks for the min and max values of Mh (neutral Higgs) in each type of tables ! will be used in input.f90 to work out which SM para need to be calculated ! initial (impossible) values Expttables_Mhmin_forSMXS=1.0D6 Expttables_Mhmax_forSMXS=0.0D0 do i=lbound(S95_t1,dim=1),ubound(S95_t1,dim=1) if(S95_t1(i)%particle_x.eq.Hneut)then do c=1,ubound(colliders,dim=1) if(WhichColliderElement(S95_t1(i)%expt, S95_t1(i)%energy).eq.c)then if(S95_t1(i)%xmax.gt.Expttables_Mhmax_forSMXS(c))Expttables_Mhmax_forSMXS(c)=S95_t1(i)%xmax if(S95_t1(i)%xmin.lt.Expttables_Mhmin_forSMXS(c))Expttables_Mhmin_forSMXS(c)=S95_t1(i)%xmin endif enddo endif enddo do i=lbound(S95_t2,dim=1),ubound(S95_t2,dim=1) if(S95_t2(i)%particle_x2.eq.Hneut)then do c=1,ubound(colliders,dim=1) if(WhichColliderElement(S95_t2(i)%expt, S95_t2(i)%energy).eq.c)then if(S95_t2(i)%xmax2.gt.Expttables_Mhmax_forSMdecays(c))Expttables_Mhmax_forSMdecays(c)=S95_t2(i)%xmax2 if(S95_t2(i)%xmin2.lt.Expttables_Mhmin_forSMdecays(c))Expttables_Mhmin_forSMdecays(c)=S95_t2(i)%xmin2 endif enddo endif enddo Expttables_Mhmin_forSMdecays=Expttables_Mhmin_forSMXS Expttables_Mhmax_forSMdecays=Expttables_Mhmax_forSMXS do i=lbound(S95_t2,dim=1),ubound(S95_t2,dim=1) if(S95_t2(i)%particle_x1.eq.Hneut)then do c=1,ubound(colliders,dim=1) if(WhichColliderElement(S95_t2(i)%expt, S95_t2(i)%energy).eq.c)then if(S95_t2(i)%xmax1.gt.Expttables_Mhmax_forSMdecays(c))Expttables_Mhmax_forSMdecays(c)=S95_t2(i)%xmax1 if(S95_t2(i)%xmin1.lt.Expttables_Mhmin_forSMdecays(c))Expttables_Mhmin_forSMdecays(c)=S95_t2(i)%xmin1 ! Needs_M2_gt_2M1 is true only for processes involving hj->hihi. ! Therefore, SM production cross sections will not be needed for hi. if(.not.S95_t2(i)%needs_M2_gt_2M1)then if(S95_t2(i)%xmax1.gt.Expttables_Mhmax_forSMXS(c))Expttables_Mhmax_forSMXS(c)=S95_t2(i)%xmax1 if(S95_t2(i)%xmin1.lt.Expttables_Mhmin_forSMXS(c))Expttables_Mhmin_forSMXS(c)=S95_t2(i)%xmin1 else if(S95_t2(i)%xmax2.gt.Expttables_Mhmax_forSMXS(c))Expttables_Mhmax_forSMXS(c)=S95_t2(i)%xmax2 if(S95_t2(i)%xmin2.lt.Expttables_Mhmin_forSMXS(c))Expttables_Mhmin_forSMXS(c)=S95_t2(i)%xmin2 endif endif enddo endif enddo ! now we set delta_x if(delta_M_LEP_default.gt.2.1d0) write(*,*)'WARNING: delta_M_LEP_default.gt.2.1d0' if(delta_M_TEV_default.gt.10.1d0)write(*,*)'WARNING: delta_M_TEV_default.gt.10.1d0' if(delta_M_LHC_default.gt.10.1d0)write(*,*)'WARNING: delta_M_LHC_default.gt.10.1d0' if(delta_Mh_LEP .gt.2.1d0) write(*,*)'WARNING: delta_Mh_LEP.gt.2.1d0' if(delta_Mh_TEV .gt.10.1d0)write(*,*)'WARNING: delta_Mh_TEV.gt.10.1d0' if(delta_Mh_LHC .gt.10.1d0)write(*,*)'WARNING: delta_Mh_LHC.gt.10.1d0' if(delta_Mhplus_LEP .gt.2.1d0) write(*,*)'WARNING: delta_Mhplus_LEP.gt.2.1d0' if(delta_Mhplus_TEV .gt.10.1d0)write(*,*)'WARNING: delta_Mhplus_TEV.gt.10.1d0' if(delta_Mhplus_LHC .gt.10.1d0)write(*,*)'WARNING: delta_Mhplus_LHC.gt.10.1d0' allocate( delta_x_default(size(np,dim=1),size(colliders,dim=1)) ) ! fill delta_x_default do c=1,ubound(colliders,dim=1) if(c.eq.get_collider_element_number('LEP '))then ! for some reason, gfortran didn't like having a case statement here delta_x_default(:,c) =delta_M_LEP_default delta_x_default(Hneut,c)=delta_Mh_LEP delta_x_default(Hplus,c)=delta_Mhplus_LEP elseif(c.eq.get_collider_element_number('TEV '))then delta_x_default(:,c) =delta_M_TEV_default delta_x_default(Hneut,c)=delta_Mh_TEV delta_x_default(Hplus,c)=delta_Mhplus_TEV elseif(c.eq.get_collider_element_number('LHC7 '))then delta_x_default(:,c) =delta_M_LHC_default delta_x_default(Hneut,c)=delta_Mh_LHC delta_x_default(Hplus,c)=delta_Mhplus_LHC elseif(c.eq.get_collider_element_number('LHC8 '))then delta_x_default(:,c) =delta_M_LHC_default delta_x_default(Hneut,c)=delta_Mh_LHC delta_x_default(Hplus,c)=delta_Mhplus_LHC elseif(c.eq.get_collider_element_number('LHC13'))then delta_x_default(:,c) =delta_M_LHC_default delta_x_default(Hneut,c)=delta_Mh_LHC delta_x_default(Hplus,c)=delta_Mhplus_LHC else stop 'error in subroutine setup_S95tables' endif enddo do i=lbound(S95_t1,dim=1),ubound(S95_t1,dim=1) if(S95_t1(i)%deltax.lt.-0.5D0)then !i.e. deltax has not been set yet S95_t1(i)%deltax = delta_x_default(S95_t1(i)%particle_x,WhichColliderElement(S95_t1(i)%expt, S95_t1(i)%energy)) endif enddo do i=lbound(S95_t2,dim=1),ubound(S95_t2,dim=1) if(S95_t2(i)%deltax.lt.-0.5D0)then !i.e. deltax has not been set yet S95_t2(i)%deltax = delta_x_default(S95_t2(i)%particle_x2,WhichColliderElement(S95_t2(i)%expt, S95_t2(i)%energy)) endif enddo ! finds the maximum delta_Mh for the each set of tables ! will be used in theo_SM.f90 to work out which SM para need to be calculated max_expt_delta_Mh= -1.0D0 do i=lbound(S95_t1,dim=1),ubound(S95_t1,dim=1) do c=1,ubound(colliders,dim=1) if(WhichColliderElement(S95_t1(i)%expt, S95_t1(i)%energy).eq.c)then if( S95_t1(i)%particle_x.eq.Hneut)then if(S95_t1(i)%deltax .gt.max_expt_delta_Mh(c))then max_expt_delta_Mh(c)=S95_t1(i)%deltax endif endif endif enddo enddo do i=lbound(S95_t2,dim=1),ubound(S95_t2,dim=1) do c=1,ubound(colliders,dim=1) if(WhichColliderElement(S95_t2(i)%expt, S95_t2(i)%energy).eq.c)then if( S95_t2(i)%particle_x2.eq.Hneut)then !note, this means only cross sections for different particle_x2 will be combined if(S95_t2(i)%deltax .gt.max_expt_delta_Mh(c))then max_expt_delta_Mh(c)=S95_t2(i)%deltax endif endif endif enddo enddo if(debug)write(*,*)'max_expt_delta_Mh',max_expt_delta_Mh ! Exptrange_Mhmin_forSMXS = max(Expttables_Mhmin_forSMXS - max_expt_delta_Mh,0.0D0) ! Exptrange_Mhmax_forSMXS = Expttables_Mhmax_forSMXS + max_expt_delta_Mh ! ! Exptrange_Mhmin_forSMdecays = max(Expttables_Mhmin_forSMdecays - max_expt_delta_Mh,0.0D0) ! Exptrange_Mhmax_forSMdecays = Expttables_Mhmax_forSMdecays + max_expt_delta_Mh Exptrange_Mhmin_forSMXS = max(Expttables_Mhmin_forSMXS,0.0D0) Exptrange_Mhmax_forSMXS = Expttables_Mhmax_forSMXS Exptrange_Mhmin_forSMdecays = max(Expttables_Mhmin_forSMdecays,0.0D0) Exptrange_Mhmax_forSMdecays = Expttables_Mhmax_forSMdecays !we need tevXS_SM_functions to have a big enough range to cover the tables if(Exptrange_Mhmax_forSMXS(get_collider_element_number('TEV ')).gt.tevXS_SM_functions_xmax)then stop 'need to extend upper range of tevXS_SM_functions or reduce delta_M_TEV' endif if(Exptrange_Mhmin_forSMXS(get_collider_element_number('TEV ')).lt.tevXS_SM_functions_xmin)then write(*,*)Exptrange_Mhmin_forSMXS(get_collider_element_number('TEV ')),tevXS_SM_functions_xmin ! TS 24/03/2017: Commented out the following (because some new analyses for low mass Higgses ! do not need these functions (decay from heavier Higgs) ! stop 'need to extend lower range of tevXS_SM_functions' endif !we need lhc7XS_SM_functions to have a big enough range to cover the tables if(Exptrange_Mhmax_forSMXS(get_collider_element_number('LHC7 ')).gt.lhc7XS_SM_functions_xmax)then stop 'need to extend upper range of lhc7XS_SM_functions or reduce delta_M_LHC' endif if(Exptrange_Mhmin_forSMXS(get_collider_element_number('LHC7 ')).lt.lhc7XS_SM_functions_xmin)then ! TS 24/03/2017: Commented out the following (because some new analyses for low mass Higgses ! do not need these functions (decay from heavier Higgs) ! stop 'need to extend lower range of lhc7XS_SM_functions' endif !we need lhc8XS_SM_functions to have a big enough range to cover the tables if(Exptrange_Mhmax_forSMXS(get_collider_element_number('LHC8 ')).gt.lhc8XS_SM_functions_xmax)then stop 'need to extend upper range of lhc8XS_SM_functions or reduce delta_M_LHC' endif if(Exptrange_Mhmin_forSMXS(get_collider_element_number('LHC8 ')).lt.lhc8XS_SM_functions_xmin)then ! write(*,*) Exptrange_Mhmin_forSMXS(get_collider_element_number('LHC8 ')) ! TS 24/03/2017: Commented out the following (because some new analyses for low mass Higgses ! do not need these functions (decay from heavier Higgs) ! stop 'need to extend lower range of lhc8XS_SM_functions' endif !we need lhc8XS_SM_functions to have a big enough range to cover the tables if(Exptrange_Mhmax_forSMXS(get_collider_element_number('LHC13')).gt.lhc13XS_SM_functions_xmax)then stop 'need to extend upper range of lhc13XS_SM_functions or reduce delta_M_LHC' endif if(Exptrange_Mhmin_forSMXS(get_collider_element_number('LHC13')).lt.lhc13XS_SM_functions_xmin)then write(*,*) Exptrange_Mhmin_forSMXS(get_collider_element_number('LHC13')) ! TS 24/03/2017: Commented out the following (because some new analyses for low mass Higgses ! do not need these functions (decay from heavier Higgs) ! stop 'need to extend lower range of lhc13XS_SM_functions' endif ! we need the branching ratios for all the colliders if( maxval(Exptrange_Mhmax_forSMdecays).gt.BRSMt1Mhmax)then ! write(*,*) "hello : ", BRSMt1Mhmax, maxval(Exptrange_Mhmax_forSMdecays) stop 'need to extend upper range of BRfunctions or reduce delta_M_(LEP/TEV)' elseif(minval(Exptrange_Mhmin_forSMdecays).lt.BRSMt1Mhmin)then write(*,*)'hello',minval(Exptrange_Mhmin_forSMdecays),BRSMt1Mhmin stop 'need to extend lower range of BRfunctions' endif deallocate(Expttables_Mhmin_forSMXS) deallocate(Expttables_Mhmax_forSMXS) deallocate(Expttables_Mhmin_forSMdecays) deallocate(Expttables_Mhmax_forSMdecays) deallocate(max_expt_delta_Mh) deallocate(delta_x_default) end subroutine setup_S95tables !********************************************************** function inrange(mass,str) ! mass is the neutral Higgs mass to be checked ! str indicates which range it should be checked against: ! str should be either 'SMBR' or one of the elements of the array 'colliders' ! ! The function returns .True. if the mass is in the appropriate range. ! If str='SMBR', this range is ! minval(Exptrange_Mhmin_forSMdecays) to maxval(Exptrange_Mhmax_forSMdecays) ! otherwise this range is ! Exptrange_Mhmin_forSMXS(x) to Exptrange_Mhmax_forSMXS(x) ! where x is the element of the array 'colliders' character(len=*),intent(in) :: str double precision,intent(in) :: mass logical :: inrange integer :: x, i !-TS(05/07/2012) Added a check whether the ranges are allocated (which happens in !-subroutine setup_S95tables. If not, they are allocated and given default values. !-This is needed for HiggsSignals. if(.not.allocated(Exptrange_Mhmin_forSMXS)) then allocate(Exptrange_Mhmin_forSMXS(size(colliders,dim=1))) allocate(Exptrange_Mhmax_forSMXS(size(colliders,dim=1))) do i=1, size(colliders) if(i.eq.get_collider_element_number('LEP ')) then Exptrange_Mhmin_forSMXS(i)=1.0D0 Exptrange_Mhmax_forSMXS(i)=180.0D0 else if(i.eq.get_collider_element_number('TEV ')) then Exptrange_Mhmin_forSMXS(i)=80.0D0 Exptrange_Mhmax_forSMXS(i)=350.0D0 else if(i.eq.get_collider_element_number('LHC7 ')) then Exptrange_Mhmin_forSMXS(i)=90.0D0 Exptrange_Mhmax_forSMXS(i)=1000.0D0 else if(i.eq.get_collider_element_number('LHC8 ')) then Exptrange_Mhmin_forSMXS(i)=90.0D0 Exptrange_Mhmax_forSMXS(i)=1000.0D0 else if(i.eq.get_collider_element_number('LHC13')) then Exptrange_Mhmin_forSMXS(i)=90.0D0 Exptrange_Mhmax_forSMXS(i)=3000.0D0 else stop 'Error in subroutine inrange. str for XS unknown.' endif enddo endif if(.not.allocated(Exptrange_Mhmin_forSMdecays)) then allocate( Exptrange_Mhmin_forSMdecays(size(colliders,dim=1))) allocate( Exptrange_Mhmax_forSMdecays(size(colliders,dim=1))) do i=1, size(colliders) if(i.eq.get_collider_element_number('LEP ')) then Exptrange_Mhmin_forSMdecays(i)=1.0D0 Exptrange_Mhmax_forSMdecays(i)=180.0D0 else if(i.eq.get_collider_element_number('TEV ')) then Exptrange_Mhmin_forSMdecays(i)=0.2D0 Exptrange_Mhmax_forSMdecays(i)=350.0D0 else if(i.eq.get_collider_element_number('LHC7 ')) then Exptrange_Mhmin_forSMdecays(i)=90.0D0 Exptrange_Mhmax_forSMdecays(i)=1000.0D0 else if(i.eq.get_collider_element_number('LHC8 ')) then Exptrange_Mhmin_forSMdecays(i)=90.0D0 Exptrange_Mhmax_forSMdecays(i)=1000.0D0 else if(i.eq.get_collider_element_number('LHC13')) then Exptrange_Mhmin_forSMdecays(i)=90.0D0 Exptrange_Mhmax_forSMdecays(i)=1000.0D0 else stop 'Error in subroutine inrange. str for decay unknown.' endif enddo endif if(str.eq.'SMBR')then if( (mass.gt.minval(Exptrange_Mhmin_forSMdecays)) & .and.(mass.lt.maxval(Exptrange_Mhmax_forSMdecays)) )then inrange=.True. else inrange=.False. endif else x=get_collider_element_number(str) ! write(*,*) 'debugging inrange:' ! write(*,*) x, mass, Exptrange_Mhmin_forSMXS(x), Exptrange_Mhmax_forSMXS(x) if( (mass.gt.Exptrange_Mhmin_forSMXS(x)) & .and.(mass.lt.Exptrange_Mhmax_forSMXS(x)) )then inrange=.True. else inrange=.False. endif endif end function inrange !********************************************************** function get_collider_element_number(collidername) ! this will return the position of the element with the value 'collidername' in the array 'colliders' !********************************************************** character(len=*),intent(in) :: collidername integer :: x,y integer :: get_collider_element_number y=0 ! print *, collidername do x=lbound(colliders,dim=1),ubound(colliders,dim=1) if(index(colliders(x),collidername).gt.0)then get_collider_element_number=x y=y+1 endif enddo if(y.ne.1)stop 'problem in function get_collider_element_number' end function get_collider_element_number !****************************************************************** function WhichColliderElement(expt,energy) ! this will return the position of the element corresponding to 'expt' in the array 'colliders' !****************************************************************** use usefulbits, only : small character(LEN=3),intent(in) :: expt integer :: WhichColliderElement double precision :: energy if( expt.eq.'LEP' )then WhichColliderElement=get_collider_element_number('LEP ') elseif( (expt.eq.'CDF').or.(expt.eq.' D0').or.(expt.eq.'TCB') )then WhichColliderElement=get_collider_element_number('TEV ') elseif( (expt.eq.'ATL').or.(expt.eq.'CMS') )then if(energy-7.0D0.le.small) then WhichColliderElement=get_collider_element_number('LHC7 ') else if(energy-8.0D0.le.small) then WhichColliderElement=get_collider_element_number('LHC8 ') else if(energy-13.0D0.le.small) then WhichColliderElement=get_collider_element_number('LHC13') else stop 'WhichColliderElement: Collider Energy not correctly specified.' endif else WhichColliderElement=0 endif end function WhichColliderElement !****************************************************************** function WhichColliderString(expt, energy) ! this will return the contents of the element corresponding to 'expt' in the array 'colliders' !****************************************************************** character(LEN=3),intent(in) :: expt character(LEN=5) :: WhichColliderString double precision :: energy ! write(*,*) 'WhichColliderString = ',colliders(WhichColliderElement(expt, energy)) WhichColliderString=colliders(WhichColliderElement(expt, energy)) end function WhichColliderString !****************************************************************** subroutine calcfact(proc,t,cfact,axis_i,axis_j,nc) !****************************************************************** !for table type1, calls calcfact_t1 !for table type2, calls calcfact_t2 !****************************************************************** use usefulbits, only : dataset,listprocesses !internal implicit none !--------------------------------------input type(dataset) :: t type(listprocesses) :: proc !-----------------------------------output double precision :: cfact,axis_j,axis_i integer :: nc !------------------------------------------- select case(proc%ttype) case(1) call calcfact_t1(proc%tlist,proc%findj,t,cfact,axis_i,nc) axis_j=axis_i case(2) call calcfact_t2(proc%tlist,proc%findj,proc%findi,t,cfact,axis_i,axis_j,nc) case default ! ### OS ### cfact = -1D0 return stop 'wrong input to function calcfact in module channels' end select end subroutine calcfact !****************************************************************** subroutine outputproc(proc,k,descrip,specific) !****************************************************************** !for table type1, calls outputproc_t1 !for table type2, calls outputproc_t2 !if neither table applies, writes message !k is where output goes !specific=1 if the specific process should be printed !e.g. ee->h1Z->bbZ !whereas specific==0 if the generic process should be printed !e.g. ee->hiZ->bbZ !****************************************************************** use usefulbits, only : listprocesses !input use likelihoods, only : outputproc_llh implicit none !--------------------------------------input integer,intent(in) :: k,specific integer :: i,j type(listprocesses),intent(in) :: proc character(LEN=200):: descrip !------------------------------------------- select case(specific) case(0) i=0 j=0 case(1) i=proc%findi j=proc%findj case default end select select case(proc%ttype) case(0) descrip='none of the processes apply' case(1) call outputproc_t1(proc%tlist,i,k,descrip) case(2) call outputproc_t2(proc%tlist,i,j,k,descrip) case(9) call outputproc_llh(proc,k,descrip) case default stop 'wrong input to subroutine outputproc in module channels' end select end subroutine outputproc !****************************************************************** subroutine check_against_bound(proc,fact,axis_i,axis_j,ratio,predobs) !****************************************************************** !for table type1, calls interpolate_tabletype1 !for table type2, calls interpolate_tabletype2 !****************************************************************** use usefulbits, only : dataset,listprocesses !internal use interpolate implicit none !--------------------------------------input integer :: predobs double precision :: fact,axis_i,axis_j type(listprocesses) :: proc !-------------------------------------output double precision :: ratio !-----------------------------------internal double precision :: Mi,Mj,interpol !------------------------------------------- interpol=-1.0D0 Mi=axis_i Mj=axis_j if(fact.gt.0.0D0)then select case(proc%ttype) case(1) call interpolate_tabletype1(Mi,S95_t1(proc%tlist),predobs,interpol) case(2) call interpolate_tabletype2(Mi,Mj,S95_t2(proc%tlist),predobs,interpol) case default ! ### OS ### ratio = -1d0 return write(*,*)'wrong input to subroutine check_against_bound in module channels' stop end select endif !--TESTING! ! if(predobs.eq.1) write(*,*) 'Interpolated value = ', interpol if(interpol.ge.0)then ratio=fact/interpol else ratio= -1.0D0 endif end subroutine check_against_bound !********************************************************** subroutine calcfact_t1(c,jj,t,cfact_t1,M_av,nc) !********************************************************** ! calculates fact for table type 1 ! Takes in to account how Standard Model-like parameter point is ! and whether there are any Higgs with slightly higher masses which ! can be combined with his result ! note: numerator and denominator are worked out separately !********************************************************** use usefulbits, only : dataset, np, div, vvsmall, vsmall use theory_BRfunctions use theory_XS_SM_functions implicit none !--------------------------------------input type(dataset) :: t integer :: c,jj !-----------------------------------output double precision :: cfact_t1,M_av integer :: nc !------------------------------------------- integer :: f,j,ii,iii double precision :: M_tot double precision :: BR_Hbb_SM_av,BR_HWW_SM_av,BR_Htautau_SM_av double precision :: tev_XS_HW_SM_av,tev_XS_HZ_SM_av double precision :: tev_XS_H_SM_av double precision :: tev_XS_Hb_SM_av double precision :: tev_XS_ttH_SM_av double precision :: lhc7_XS_H_SM_av double precision :: lhc7_XS_VBF_SM_av double precision :: BR_Zll,BR_Znunu,BR_Wlnu,BR_Ztautau double precision :: BR_Whad,BR_Zhad double precision :: fact_tmp double precision,allocatable :: mass(:),fact(:) integer,allocatable :: model_like(:) integer :: npart !number of particles !source: PDG (Yao et al. J Phys G 33 (2006)) BR_Zll=3.363D-2+3.366D-2 !BR_Zll = sum(l=e,mu), BR(Z ->l+ l-) BR_Znunu=20D-2 !BR_Znunu = BR(Z ->nu_l nu_l-bar) ('invisible') BR_Wlnu=10.75D-2+10.57D-2 !BR_Wlnu = sum(l=e,mu), !BR(W+ ->l+ nu_l) = BR(W- ->l- + nu_l-bar) BR_Whad=67.6D-2 BR_Zhad=69.91D-2 BR_Ztautau=3.370D-2 npart=np( S95_t1(c)%particle_x ) allocate(mass(npart),fact(npart),model_like(npart)) mass(:)=t%particle( S95_t1(c)%particle_x )%M(:) fact= 0.0D0 cfact_t1=0.0D0 model_like=0 !now calculate numerator of 'fact' do j=1,npart if( (abs(mass(jj)-mass(j)).le.S95_t1(c)%deltax) & & .and.( mass(jj).le.mass(j) ) )then select case(S95_t1(c)%id) !these can be compacted, but not doing it yet... doing it at the !same time as revamping the model_likeness test case(142) fact(j)=t%lep%XS_hjZ_ratio(j) *t%BR_hjbb(j) !notice that this is not absolute XS case(143) fact(j)=t%lep%XS_hjZ_ratio(j) *t%BR_hjtautau(j) !notice that this is not absolute XS case(300) fact(j)=t%lep%XS_hjZ_ratio(j) !notice that this is not absolute XS case(400,401,402,403) fact(j)=t%lep%XS_hjZ_ratio(j) *t%BR_hjinvisible(j) !notice that this is not absolute XS case(500) fact(j)=t%lep%XS_hjZ_ratio(j) *t%BR_hjgaga(j) !notice that this is not absolute XS case(600,601) fact(j)=t%lep%XS_hjZ_ratio(j) &!notice that this is not absolute XS & *(t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)) case(711,713) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(721,723,741,743) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(731,733) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(801,811,821) fact(j)=t%lep%XS_HpjHmj_ratio(j)*(t%BR_Hpjcs(j)+t%BR_Hpjcb(j))**2.0D0 !notice that this is not absolute XS case(802) fact(j)=t%lep%XS_HpjHmj_ratio(j)*(t%BR_Hpjcs(j)+t%BR_Hpjcb(j))*2.0D0*t%BR_Hpjtaunu(j) !notice that this is not absolute XS case(803,813) fact(j)=t%lep%XS_HpjHmj_ratio(j)*t%BR_Hpjtaunu(j)**2.0D0 !notice that this is not absolute XS case(8742,4493,9475,5482,5570,5876,1024,9889,3534,6089,10235,3047,10799,3564,6166,6296) fact(j)=t%tev%XS_hjZ_ratio(j) *t%tev%XS_HZ_SM(j) *t%BR_hjbb(j) case(8958,5489,5624,9236,3930,6039,3216,10433,6221,10600) fact(j)=t%tev%XS_hj_ratio(j)*t%tev%XS_H_SM(j) *t%BR_hjWW(j) case(3331) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) fact(j)=fact(j)*t%tev%XS_H_SM(j)*t%BR_HWW_SM(j)!to get the normalisation right case(5757) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(8957,5472,9219,9463,9596,5828,1970,3493,5972,3155,5613,9868,10068,6092,10217,10239,10796,0874,6220) fact(j)=t%tev%XS_hjW_ratio(j) *t%tev%XS_HW_SM(j) *t%BR_hjbb(j) case(5485,7307,5873) fact(j)=t%tev%XS_hjW_ratio(j) *t%tev%XS_HW_SM(j) *t%BR_hjWW(j) case(9071,2491,5740,5980,1014,3363,4555) fact(j)=t%tev%XS_hj_ratio(j) *t%tev%XS_H_SM(j) *t%BR_hjtautau(j) case(8961,0598) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(9284,5503,5726,10105) fact(j)=t%tev%XS_hjb_ratio(j) *t%tev%XS_Hb_SM(j) *t%BR_hjbb(j)/0.9D0/2.0D0 case(6083) fact(j)=t%tev%XS_hjb_ratio(j) *t%tev%XS_Hb_SM(j) *t%BR_hjtautau(j)/0.1D0/2.0D0 case(1514,5601,5737) fact(j)=( t%tev%XS_hjZ_ratio(j) * t%tev%XS_HZ_SM(j) & & + t%tev%XS_hjW_ratio(j) * t%tev%XS_HW_SM(j) & & + t%tev%XS_hj_ratio(j) * t%tev%XS_H_SM(j) & & + t%tev%XS_vbf_ratio(j) * t%tev%XS_vbf_SM(j) & & ) & & * t%BR_hjgaga(j) case(5858,6177,6295,1887,10065,10485,4960) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(7081,9166,9483,5586,9642,1266,0432,9891,5285,3935,6087,6170,10212,6223,6299,10583,10798,10596) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2012015) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(10010,10607,6436) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(9248,10133,10439) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(4800) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(5845) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(6171) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(9290) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(5984,9714,6006,4481,6095,10432,6179,6302,10599) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(3556,1931) fact(j)=t%tev%XS_hjb_ratio(j) *t%tev%XS_Hb_c2_SM(j) *t%BR_hjbb(j) case(4782) fact(j)=t%tev%XS_hjb_ratio(j) *t%tev%XS_Hb_c1_SM(j) *t%BR_hjbb(j) case(9465,5871,9022,0710,9887,4162,10102,4468) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) !case(9023) ! call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(9674) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(9897,9999) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(0024,5985,0968,5974,4885) fact(j)=t%tev%XS_hjb_ratio(j) *t%tev%XS_Hb_c3_SM(j) *t%BR_hjtautau(j) case(5739,10574) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) fact(j)=fact(j)*t%tev%XS_ttH_SM(j)*t%BR_Hbb_SM(j)!to get the normalisation right case(2012135,12025) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(0611) fact(j)=t%tev%XS_hj_ratio(j)*t%tev%XS_H_SM(j) *t%BR_hjZga(j) case(1269,1270,2011094,13035,160311) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(1811) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(1812,2011138,2011151,2760,2013090,2014050,14020,8353,7712,11002,11008,79152) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(6008,9998) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(6082,6182,6219,6276,10573) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(6096,10606,10806,10884) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(6183,3233) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(6229) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(6286,6301,6304,6305,6309) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(6091,1268) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2011048,11004,11015,11013,11028,11006,11017,110271,110272,14161,14162,5064,2012017,2011150,2011131) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2011162,1415,2012092,20130131) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(059301) fact(j)=t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j)*t%BR_hjZZ(j) case(059302) fact(j)=t%lhc8%XS_vbf_ratio(j)*t%lhc8%XS_vbf_SM(j)*t%BR_hjZZ(j) case(20130132) fact(j)=1000.d0*t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j)*t%BR_hjZZ(j)*BR_Zll**2 case(20130133) fact(j)=1000.d0*(t%lhc8%XS_hjZ_ratio(j) * t%lhc8%XS_HZ_SM(j) & & + t%lhc8%XS_hjW_ratio(j) * t%lhc8%XS_HW_SM(j) & & + t%lhc8%XS_vbf_ratio(j) * t%lhc8%XS_vbf_SM(j)) & & * t%BR_hjZZ(j)*BR_Zll**2 case(11025,1997,12041,130021,130022,009361) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) ! write(*,*) "Analysis(130021) fact(",j,")=",fact(j) case(2011026,11005,11016,11026,3478,3357,2011148,2012016) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(110212) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(17013,2011025,2011085,2011161,5895,1414,2012091,2012168,1487,12001,12015,13001,11010,11030,11021) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(13006, 13075515,2013009,3051) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(11031,12044,13012) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(13011) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(11034,12039,13009,2012078,12006,12051) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2011005,3615,2012018,12046) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2748, 1408, 2012019) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(7214) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(10500) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(11003,11014,2577,11024,1489,12042,13003,13027) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2011020,2011021) fact(j)=t%lhc7%XS_hj_ratio(j)*t%lhc7%XS_H_SM(j) *t%BR_hjmumu(j) case(5429,2011052,2011111,2011134) fact(j)=t%lhc7%XS_hj_ratio(j)*t%lhc7%XS_H_SM(j) *t%BR_hjWW(j) case(2012012,2012158,2013030) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(10002,5003,2011132,2012094,110201,110292) fact(j)=t%lhc7%XS_hj_ratio(j)*t%lhc7%XS_H_SM(j) *t%BR_hjtautau(j) case(20140492) ! fact(j)=t%lhc8%XS_gg_hj_ratio(j)*t%lhc8%XS_gg_H_SM(j)*t%BR_hjtautau(j) fact(j)=t%lhc8%channelrates(j,6,4)*t%lhc8%XS_gg_H_SM(j) case(2014049) ! fact(j)=t%lhc8%XS_bb_hj_ratio(j)*t%lhc8%XS_bb_H_SM(j)*t%BR_hjtautau(j) fact(j)=t%lhc8%channelrates(j,7,4)*t%lhc8%XS_bb_H_SM(j) case(20160851,160371,20170501) ! fact(j)=t%lhc13%XS_gg_hj_ratio(j)*t%lhc13%XS_gg_H_SM(j)*t%BR_hjtautau(j) ! write(*,*) "debug: ",j,t%lhc13%channelrates(j,6,4) fact(j)=t%lhc13%channelrates(j,6,4)*t%lhc13%XS_gg_H_SM(j) case(20160852,160372,20170502) ! write(*,*) "debug: ",j,t%lhc13%channelrates(j,7,4) ! fact(j)=t%lhc13%XS_bb_hj_ratio(j)*t%lhc13%XS_bb_H_SM(j)*t%BR_hjtautau(j) fact(j)=t%lhc13%channelrates(j,7,4)*t%lhc13%XS_bb_H_SM(j) case(12050,13021) fact(j)=t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) *t%BR_hjtautau(j) case(11009,11020,2011133,2012014,2012160) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(110291,12043) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2013010,7663) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(11011,2011163,11022,11032,1488,12008,12045,2011157) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2011103,2012161,11012) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(13022) fact(j)=t%lhc8%XS_vbf_ratio(j)*div(t%BR_hjWW(j),t%BR_HWW_SM(j) ,0.0D0,1.0D0) case(13013,13441) fact(j)=t%lhc8%XS_vbf_ratio(j)*t%BR_hjinvisible(j) case(6682) fact(j)=t%lhc13%XS_vbf_ratio(j)*t%lhc13%XS_vbf_SM(j)*t%BR_hjinvisible(j) case(13018,13442) fact(j)=t%lhc8%XS_hjZ_ratio(j)*t%BR_hjinvisible(j) case(13443) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2013011,3244) ! Limit is on sigma(HZ)*BR(H->inv)*(BR(Z->ll)+BR(Z->tautau) ! Data given in fb - (multiply by 1000) fact(j)=1000.D0*t%lhc8%XS_hjZ_ratio(j)*t%lhc8%XS_HZ_SM(j) & & *t%BR_hjinvisible(j) !*(BR_Zll+BR_Ztautau) ! print *, 1000.D0*t%lhc8%XS_hjZ_ratio(j)*t%lhc8%XS_HZ_SM(j)*(BR_Zll+BR_Ztautau), fact(j) case(1508329,2015080) fact(j) = t%lhc8%XS_bb_hj_ratio(j)*t%lhc8%XS_bb_H_SM(j)*t%BR_hjbb(j) case(6583) ! Data given in fb - (multiply by 1000) ! (TS 2016/10/13: Added conservatively estimated signal efficiency factor of ~0.56) fact(j)=0.56D0*1000.0D0*( & t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) + & t%lhc8%XS_vbf_ratio(j)*t%lhc8%XS_vbf_SM(j) + & t%lhc8%XS_hjZ_ratio(j)*t%lhc8%XS_HZ_SM(j) + & t%lhc8%XS_hjW_ratio(j)*t%lhc8%XS_HW_SM(j) + & t%lhc8%XS_tthj_ratio(j)*t%lhc8%XS_ttH_SM(j) ) * t%BR_hjgaga(j) case(14011) do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0) then fact(j)=fact(j)+1000.0D0 * t%lhc8%XS_hj_ratio(j) * t%lhc8%XS_H_SM(j) & & * t%BR_hjhiZ(j,ii) * BR_Zll * t%BR_hjbb(ii) endif enddo case(17006) ! Data given in fb - (multiply by 1000). ! Limit on leptonic (e,mu,tau) decays of VV -> lnulnu ! BR(W->lnu) = 0.3257 ! BR(Z->ll) = 0.10099 ! BR(Z->nunu) = 0.2000 do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0) then fact(j)=fact(j)+ 1000.0D0 * t%lhc13%XS_gg_hj_ratio(j) * t%lhc13%XS_gg_H_SM(j) & & * t%BR_hkhjhi(j,ii,ii) * t%BR_hjbb(ii) * & & (t%BR_hjWW(ii) * 0.3257D0**2 + t%BR_hjZZ(ii) * 0.10099D0 * 0.2D0 *2.0D0) endif enddo case(1506534) do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0) then fact(j)=fact(j)+ t%lhc8%XS_gg_hj_ratio(ii) * t%lhc8%XS_gg_H_SM(ii) & & * t%BR_hkhjhi(ii,j,j) * t%BR_hjtautau(j)**2.0D0 endif enddo case(5051) do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.2.5D0) then fact(j)=fact(j)+ t%lhc8%XS_gg_hj_ratio(ii) * t%BR_hkhjhi(ii,j,j)*t%BR_hjgaga(j)**2.0D0 endif enddo case(7355) do ii=1,npart fact_tmp = 0.0D0 if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.(10.0D0+t%particle(Hneut)%dMh(ii))) then fact_tmp = t%lhc13%XS_hjZ_ratio(j) * t%lhc13%XS_HZ_SM(j) + t%lhc13%XS_hjW_ratio(j) * t%lhc13%XS_HW_SM(j) fact(j) = fact(j) + fact_tmp * t%BR_hkhjhi(ii,j,j) * t%BR_hjbb(j) * t%BR_hjbb(j) endif enddo case(17020321) do ii=1,npart fact_tmp = 0.0D0 if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.(25.0D0+t%particle(Hneut)%dMh(ii))) then call model_likeness(ii,S95_t1(c)%id,t,model_like(ii),fact_tmp) fact(j) = fact(j) + fact_tmp * t%BR_hkhjhi(ii,j,j) * t%BR_hjtautau(j)**2.0D0 endif enddo case(17020322,539) do ii=1,npart ! Multiply by 2.0 because limit is set on BR(H->hh->mumubb) fact_tmp = 0.0D0 if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.(25.0D0+t%particle(Hneut)%dMh(ii))) then call model_likeness(ii,S95_t1(c)%id,t,model_like(ii),fact_tmp) fact(j) = fact(j) + fact_tmp * t%BR_hkhjhi(ii,j,j) * 2.0D0 * t%BR_hjmumu(j) * t%BR_hjbb(j) endif enddo case(17020323) do ii=1,npart ! Multiply by 2.0 because limit is set on BR(H->hh->mumutautau) fact_tmp = 0.0D0 if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.(25.0D0+t%particle(Hneut)%dMh(ii))) then call model_likeness(ii,S95_t1(c)%id,t,model_like(ii),fact_tmp) fact(j) = fact(j) + fact_tmp * t%BR_hkhjhi(ii,j,j) * 2.0D0 * t%BR_hjmumu(j) * t%BR_hjtautau(j) endif enddo case(011812) ! Limit given in fb, multiply by 1000. do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0) then fact(j)=fact(j)+1000.0D0 * t%lhc8%XS_hj_ratio(j) * t%lhc8%XS_H_SM(j) & & * t%BR_hjhiZ(j,ii) * BR_Zll * t%BR_hjtautau(ii) endif enddo case(011811) ! Limit given in pb do ii=1,npart do iii=1,npart ! No symmetry factor (1/2) because limit is set on BR(H->hh->bbtautau) if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0.and.abs(t%particle(Hneut)%M(iii)-125.0D0).lt.10.0D0) then fact(j)=fact(j)+ t%lhc8%XS_hj_ratio(j) * t%lhc8%XS_H_SM(j) & & * t%BR_hkhjhi(j,ii,iii) * ( t%BR_hjtautau(ii) * t%BR_hjbb(iii) + & & t%BR_hjtautau(iii) * t%BR_hjbb(ii) ) endif enddo enddo case(16029) ! Limit given in pb do ii=1,npart do iii=1,npart ! No symmetry factor (1/2) because limit is set on BR(H->hh->bbtautau) if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0.and.abs(t%particle(Hneut)%M(iii)-125.0D0).lt.10.0D0) then fact(j)=fact(j)+ t%lhc13%XS_hj_ratio(j) * t%lhc13%XS_H_SM(j) & & * t%BR_hkhjhi(j,ii,iii) * ( t%BR_hjtautau(ii) * t%BR_hjbb(iii) + & & t%BR_hjtautau(iii) * t%BR_hjbb(ii) ) endif enddo enddo case(17002) ! Limit given in fb do ii=1,npart do iii=1,npart ! No symmetry factor (1/2) because limit is set on BR(H->hh->bbtautau) if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0.and.abs(t%particle(Hneut)%M(iii)-125.0D0).lt.10.0D0) then fact(j)=fact(j)+ 1000.0D0 * t%lhc13%XS_hj_ratio(j) * t%lhc13%XS_H_SM(j) & & * t%BR_hkhjhi(j,ii,iii) * ( t%BR_hjtautau(ii) * t%BR_hjbb(iii) + & & t%BR_hjtautau(iii) * t%BR_hjbb(ii) ) endif enddo enddo case(2016071) ! Limit given in pb do ii=1,npart do iii=1,npart ! No symmetry factor (1/2) because limit is set on BR(H->hh->WWgaga) if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.2.5D0.and.abs(t%particle(Hneut)%M(iii)-125.0D0).lt.2.5D0) then fact(j)=fact(j)+ t%lhc13%XS_hj_ratio(j) * t%lhc13%XS_H_SM(j) & & * t%BR_hkhjhi(j,ii,iii) * ( t%BR_hjWW(ii) * t%BR_hjgaga(iii) + & & t%BR_hjWW(iii) * t%BR_hjgaga(ii) ) endif enddo enddo case(16002,2016049) ! Limit given in fb, multiply by 1000. do ii=1,npart do iii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0.and.abs(t%particle(Hneut)%M(iii)-125.0D0).lt.10.0D0) then fact(j)=fact(j)+ 1000.0D0 * t%lhc13%XS_hj_ratio(j) * t%lhc13%XS_H_SM(j) & & * t%BR_hkhjhi(j,ii,iii) * t%BR_hjbb(iii) * t%BR_hjbb(ii) endif enddo enddo case(14013) ! Limit given in fb, multiply by 1000. do ii=1,npart do iii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0.and.abs(t%particle(Hneut)%M(iii)-125.0D0).lt.10.0D0) then fact(j)=fact(j)+ 1000.0D0 * t%lhc8%XS_hj_ratio(j) * t%lhc8%XS_H_SM(j) & & * t%BR_hkhjhi(j,ii,iii) * t%BR_hjbb(iii) * t%BR_hjbb(ii) endif enddo enddo case(044781) ! Limit given in pb (Z->ll unfolded) do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0) then fact(j)=fact(j) + t%lhc8%XS_gg_hj_ratio(j) * t%lhc8%XS_gg_H_SM(j) & & * t%BR_hjhiZ(j,ii) * t%BR_hjtautau(ii) endif enddo case(044782) ! Limit given in pb (Z->ll unfolded) do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0) then fact(j)=fact(j) + t%lhc8%XS_gg_hj_ratio(j) * t%lhc8%XS_gg_H_SM(j) & & * t%BR_hjhiZ(j,ii) * t%BR_hjbb(ii) endif enddo case(20160151,180051) ! Limit given in pb (Z->ll unfolded) do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0) then fact(j)=fact(j) + t%lhc13%XS_gg_hj_ratio(j) * t%lhc13%XS_gg_H_SM(j) & & * t%BR_hjhiZ(j,ii) * t%BR_hjbb(ii) endif enddo case(20160152,180052) ! Limit given in pb (Z->ll unfolded) do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0) then fact(j)=fact(j) + t%lhc13%XS_bb_hj_ratio(j) * t%lhc13%XS_bb_H_SM(j) & & * t%BR_hjhiZ(j,ii) * t%BR_hjbb(ii) endif enddo case(14006,14037) ! Data given in pb fact(j)= ( & t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) + & t%lhc8%XS_vbf_ratio(j)*t%lhc8%XS_vbf_SM(j) + & t%lhc8%XS_hjZ_ratio(j)*t%lhc8%XS_HZ_SM(j) + & t%lhc8%XS_hjW_ratio(j)*t%lhc8%XS_HW_SM(j) + & t%lhc8%XS_tthj_ratio(j)*t%lhc8%XS_ttH_SM(j) ) * t%BR_hjgaga(j) case(2018025) ! Data given in fb (fiducial cross section, multiply here with acceptance functions) fact(j)= 1000.0D0 * ( & (0.574D0 - 2.051 * exp(-0.0311*mass(j))) * t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) + & (0.663D0 - 1.054 * exp(-0.0182*mass(j))) * t%lhc13%XS_vbf_ratio(j)*t%lhc13%XS_vbf_SM(j) + & (0.547D0 - 1.223 * exp(-0.0222*mass(j))) * t%lhc13%XS_hjZ_ratio(j)*t%lhc13%XS_HZ_SM(j) + & (0.547D0 - 1.223 * exp(-0.0222*mass(j))) * t%lhc13%XS_hjW_ratio(j)*t%lhc13%XS_HW_SM(j) + & (0.663D0 - 1.054 * exp(-0.0182*mass(j))) * t%lhc13%XS_tthj_ratio(j)*t%lhc13%XS_ttH_SM(j) ) * & t%BR_hjgaga(j) case(14031) fact(j)=1000.0D0* t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) * & t%BR_hjZga(j)*BR_Zll case(20160821,20160822,063861) fact(j)=t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j)*t%BR_hjZZ(j) case(20160823) fact(j)=t%lhc13%XS_vbf_ratio(j)*t%lhc13%XS_vbf_SM(j)*t%BR_hjZZ(j) case(20160792) ! Data given in fb fact(j)=1000.0D0*t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j)*t%BR_hjZZ(j)*BR_Zll**2 case(20160793) ! Data given in fb fact(j)=1000.0D0*t%lhc13%XS_vbf_ratio(j)*t%lhc13%XS_vbf_SM(j)*t%BR_hjZZ(j)*BR_Zll**2 case(20160741,2016062) fact(j)=t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j)*t%BR_hjWW(j) case(20160742) fact(j)=t%lhc13%XS_vbf_ratio(j)*t%lhc13%XS_vbf_SM(j)*t%BR_hjWW(j) + case(23801) + call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) + if(model_like(j).eq.1) then + ! Limit is given in fb. + fact(j)=1000.0D0* t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j)*( t%BR_hjWW(j) + t%BR_hjZZ(j) ) + endif + case(23802) + call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) + if(model_like(j).eq.1) then + ! Limit is given in fb. + fact(j)=1000.0D0* t%lhc13%XS_vbf_ratio(j)*t%lhc13%XS_vbf_SM(j)*( t%BR_hjWW(j) + t%BR_hjZZ(j) ) + endif case(2011112) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(2011135) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(6224,6225,6226) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(04670,046701,046702,17030,4873,8567,336) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(0038911,0038912,0038913,0038914) call model_likeness(j,S95_t1(c)%id,t,model_like(j),fact(j)) case(160312,2016088,79151,18014) ! Data given in pb fact(j)= t%lhc13%XS_Hpmjtb(j) * t%BR_Hpjtaunu(j) case(1504233) ! Data given in fb fact(j)= 1000.0D0*t%lhc8%XS_vbf_Hpmj(j) * t%BR_HpjWZ(j) case(2016089,3599) ! Data given in pb fact(j)= t%lhc13%XS_Hpmjtb(j) * t%BR_Hpjtb(j) ! Daniel's attempts case(2016025) fact(j) = t%lhc13%XS_hj_ratio(j) * t%lhc13%XS_H_SM(j) * t%BR_hjbb(j) case(2016044) fact(j) = 1000.0D0*t%lhc13%XS_hj_ratio(j) * t%lhc13%XS_H_SM(j) * t%BR_hjZga(j) case(201608391) do ii=1,npart if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0) then fact(j)=fact(j) + t%lhc13%XS_hjW_ratio(ii) *t%lhc13%XS_HW_SM(ii) * t%BR_hkhjhi(ii,j,j) & & * t%BR_hjbb(j) * t%BR_hjbb(j) endif enddo case(16030) fact(j) = t%BR_tHpjb(j) * t%BR_Hpjcs(j) case(2016004) ! Limit given in pb do ii=1,npart do iii=1,npart ! Multiply fact by symmetry factor, 1/2. if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.2.5D0.and.abs(t%particle(Hneut)%M(iii)-125.0D0).lt.2.5D0) then fact(j)=fact(j)+ 0.5D0 * t%lhc13%XS_gg_hj_ratio(j)*t%lhc13%XS_gg_H_SM(j) & & * t%BR_hkhjhi(j,ii,iii) * & & ( t%BR_hjbb(ii)/t%BR_Hbb_SM(ii) * t%BR_hjgaga(iii)/t%BR_Hgaga_SM(iii) + & & t%BR_hjbb(iii)/t%BR_Hbb_SM(iii) * t%BR_hjgaga(ii)/t%BR_Hgaga_SM(ii) ) endif enddo enddo ! case(2016004) ! do ii=1,npart ! if(abs(t%particle(Hneut)%M(ii)-125.0D0).lt.10.0D0.and.t%BR_Hbb_SM(ii).gt.0D0.and.t%BR_Hgaga_SM(ii).gt.0D0) then ! fact(j) + t%lhc13%XS_gg_hj_ratio(j)*t%lhc13%XS_gg_H_SM(j) * t%BR_hkhjhi(j,ii,ii) & ! & * t%BR_hjbb(ii)/t%BR_Hbb_SM(ii) * t%BR_hjgaga(ii)/t%BR_Hgaga_SM(ii) ! endif ! enddo case(1604833) if(abs(t%BR_hjWW(j)/t%BR_hjZZ(j) / (t%BR_HWW_SM(j)/t%BR_HZZ_SM(j))-1.0D0).lt.0.05) then fact(j) = t%lhc13%XS_gg_hj_ratio(j)*t%lhc13%XS_gg_H_SM(j) * (t%BR_hjWW(j) + t%BR_hjZZ(j)) else fact(j) = 0.0D0 endif case(16034) fact(j) = (t%lhc13%XS_hj_ratio(j) * t%lhc13%XS_H_SM(j) + & & t%lhc13%XS_vbf_ratio(j) * t%lhc13%XS_vbf_SM(j) ) * t%BR_hjZZ(j) case(2016056) fact(j) = 1000.0D0*t%lhc13%XS_gg_hj_ratio(j) * t%lhc13%XS_gg_H_SM(j) * t%BR_hjZZ(j) case(15009) fact(j)= 1000.*t%lhc8%XS_bb_hj_ratio(j)*t%lhc8%XS_bb_H_SM(j)*t%BR_hjmumu(j) case(20160551) fact(j) = 1000.0D0*t%lhc13%XS_hj_ratio(j) * t%lhc13%XS_H_SM(j) * t%BR_hjZZ(j) case(20160552) fact(j) = 1000.0D0*t%lhc13%XS_hj_ratio(j) * t%lhc13%XS_H_SM(j) * t%BR_hjWW(j) case default stop 'wrong input to function calcfact_t1 in module S95tables' end select endif enddo if(fact(jj).le.vvsmall)then!A !Higgs jj doesn't contribute - wait until another call of this subroutine before !looking at nearby masses M_av = mass(jj) nc=0 cfact_t1=0.0D0 else!A !find M_av (only using higgs which have non-zero fact): f=0 M_tot=0.0D0 do j=1,npart if( fact(j).gt.vvsmall )then f=f+1 M_tot=M_tot+mass(j) endif enddo nc=f !f will always be > 0 because we've already made sure that fact(jj)>0.0D0 M_av = M_tot/dble(nc) if((WhichColliderString(S95_t1(c)%expt,S95_t1(c)%energy).eq.'LEP'))then!B cfact_t1=sum(fact) elseif(S95_t1(c)%particle_x .ne. Hneut)then!B cfact_t1=sum(fact) else!B ! HB-5 new ---> if(cfact_t1.gt.vvsmall.and.M_av.gt.S95_t1(c)%xmax) then M_av = S95_t1(c)%xmax write(*,*) "WARNING: Evaluating limit of ",trim(adjustl(S95_t1(c)%label))," at upper mass range." else if(cfact_t1.gt.vvsmall.and.M_av.lt.S95_t1(c)%xmin) then M_av = S95_t1(c)%xmin write(*,*) "WARNING: Evaluating limit of ",trim(adjustl(S95_t1(c)%label))," at lower mass range." endif ! <--- if(f.eq.1)then !have already calculated these in theo_manip to save time BR_Hbb_SM_av = t%BR_Hbb_SM(jj) BR_HWW_SM_av = t%BR_HWW_SM(jj) BR_Htautau_SM_av = t%BR_Htautau_SM(jj) tev_XS_HW_SM_av = t%tev%XS_HW_SM(jj) tev_XS_HZ_SM_av = t%tev%XS_HZ_SM(jj) tev_XS_H_SM_av = t%tev%XS_H_SM(jj) tev_XS_Hb_SM_av = t%tev%XS_Hb_SM(jj) tev_XS_ttH_SM_av = t%tev%XS_ttH_SM(jj) lhc7_XS_H_SM_av = t%lhc7%XS_H_SM(jj) lhc7_XS_VBF_SM_av= t%lhc7%XS_vbf_SM(jj) else BR_Hbb_SM_av = BRSM_Hbb(M_av) BR_HWW_SM_av = BRSM_HWW(M_av) BR_Htautau_SM_av = BRSM_Htautau(M_av) tev_XS_HW_SM_av = XS_tev_HW_SM(M_av) tev_XS_HZ_SM_av = XS_tev_HZ_SM(M_av) tev_XS_H_SM_av = XS_tev_gg_H_SM(M_av)+XS_tev_bb_H_SM(M_av) tev_XS_Hb_SM_av = XS_tev_bg_Hb_SM(M_av) tev_XS_ttH_SM_av = XS_tev_ttH_SM(M_av) lhc7_XS_H_SM_av = XS_lhc7_gg_H_SM(M_av)+XS_lhc7_bb_H_SM(M_av) lhc7_XS_VBF_SM_av= XS_lhc7_vbf_SM(M_av) endif ! now include denominator of 'fact' select case(S95_t1(c)%id) case(8742,5482,5570,4493,9475,5876,1024,9889,3534,6089,10235,3047,10799,3564,6166,6296) do j=1,npart fact(j)= div( fact(j) , tev_XS_HZ_SM_av * BR_Hbb_SM_av ,0.0D0,0.0D0) enddo case(8958,5489,5624,9236,3930) do j=1,npart fact(j)= div( fact(j) , tev_XS_H_SM_av * BR_HWW_SM_av ,0.0D0,0.0D0) enddo case(8957,5472,9219,9463,9596,5828,1970,3493,5972,3155,5613,9868,10068,6092,10217,10239,10796,0874,6220) do j=1,npart fact(j)= div( fact(j) , tev_XS_HW_SM_av * BR_Hbb_SM_av ,0.0D0,0.0D0) enddo case(5503,9284,5726,10105) do j=1,npart fact(j)= div( fact(j) , tev_XS_Hb_SM_av ,0.0D0,0.0D0) enddo case(6083) do j=1,npart fact(j)= div( fact(j) , tev_XS_Hb_SM_av ,0.0D0,0.0D0) enddo case(7307,5873) do j=1,npart fact(j)= div( fact(j) , tev_XS_HW_SM_av * BR_HWW_SM_av ,0.0D0,0.0D0) enddo case(8961,0598,10010,9290,9674,9897,9999,10607,6436) case(7081,9166,9483,5586,9642,1266,0432,9891,5285,3935,6087,6170,10212,6223,6299,10583,10798,10596) case(2012015) case(9248,5845,4800,5858,6177,6295,1887,10065,10485,10133,10439,4960) case(9465,5871,9022,9023,0710,9887) case(6171) case(6183,3233) case(6229) case(6304) case(5984,9714,4162,10102,6006,4481,4468,5757,6095,10432,6179,6302,10599) case(5739,10574) do j=1,npart fact(j)= div( fact(j) , tev_XS_ttH_SM_av * BR_Hbb_SM_av ,0.0D0,0.0D0) enddo case(2012135,12025) case(6008,9998) case(6082,6182,6219,6276,10573) case(6096,10606,10806,10884) case(6091,1268) case(5485,9071,2491,5601,1514,3556,5740,4555,0024,5980,1014,5985, & & 0611,3363,6039,3216,0968,5974,1931,4885,6221) case(3331) case(6286,6301,6305,6309) case(10600) case(10433) do j=1,npart fact(j)=div(fact(j) , tev_XS_H_SM_av * BR_HWW_SM_av ,0.0D0,0.0D0) enddo case(2011048,11004,11015,11013,11028,11006,11017,110271,110272,14161,14162,5064,2012017,2011150,2011131) case(2011162,1415,2012092,20130131) case(11025,1997,12041,130021,130022,009361,16034) case(2011026,11005,11016,11026,3478,3357,2011148,2012016) case(110212) case(17013,2011025,2011085,2011161,5895,1414,2012091,2012168,1487,12001,12015,13001,11010,11030,11021) case(13006, 13075515,2013009,3051) case(11031,12044,13012) case(13011) case(11034,12039,13009,2012078,12006,12051) case(2011005,3615,2012018,12046) case(2748, 1408, 2012019) case(7214) case(4782) case(5429,2011052,2011111,2011134) do j=1,npart fact(j)= div( fact(j) , lhc7_XS_H_SM_av * BR_HWW_SM_av ,0.0D0,0.0D0) enddo case(2012012,2012158,2013030) case(10002,5003,2011132,2012094,2014049,20140492,110201,110292,12050,13021) case(059301,059302) case(20130132,20130133) case(11009,11020,2011133,2012014,2012160) case(110291,12043) case(2013010,7663) case(11002,11008) case(11003,11014,2577,11024,1489,12042,13003,13027) case(2011020,2011021) case(10500) case(11011,2011163,11022,11032,1488,12008,12045,2011157) case(2011103,2012161,11012) case(13022) case(13013) case(13441,13442,13443,6682) case(13018) case(2013011,3244) case(2011112) case(6583,14006,14037,14031,2018025) case(2011135) case(1508329,2015080) case(17020321,17020322,17020323,539,7355) case(6224,6225,6226) case(04670,046701,046702,17030,4873,8567,336) case(0038911,0038912,0038913,0038914) case(160312,18014,2016088,2016089,3599,14011,011811,16029,17002,14013,2016071) case(16002,011812,20160851,20160852,20170501,20170502,79151) case(1504233,1506534,5051) case(160371,160372,044781,044782,20160151,180051,180052,20160152,17006) case(20160741,20160742,2016062,20160821,20160822,20160823,20160792,20160793,2016049,063861) case(2016025,2016044,201608391,2016004,1604833,2016056,20160551,20160552,15009) - case(16030) + case(16030,23801,23802) case default stop 'error calculating denom. in calcfact_t1' end select cfact_t1=sum(fact) endif!B endif!A deallocate(mass) deallocate(fact) deallocate(model_like) end subroutine calcfact_t1 !********************************************************** subroutine calcfact_t2(c,jj,ii,t,cfact_t2,axis_i,axis_j,nc) !********************************************************** !calculates fact for table type 2 !********************************************************** use usefulbits, only : dataset,np,vsmall,not_a_particle,extrapolatewidth implicit none !--------------------------------------input type(dataset) :: t integer :: c,jj,ii !-----------------------------------output double precision :: cfact_t2,axis_i,axis_j integer :: nc !------------------------------------------- integer :: f,i,j,npart2,npart1 double precision :: fact,eps2,crosssection,Mi_av,Mj_av,masstot,BR_Zll,acceptance double precision,allocatable :: massj(:),massi(:) BR_Zll=3.363D-2+3.366D-2 !BR_Zll = sum(l=e,mu), BR(Z ->l+ l-) eps2=0.02D0 npart2=np( S95_t2(c)%particle_x2 ) allocate(massj(npart2)) massj(:)=t%particle( S95_t2(c)%particle_x2 )%M(:) if(S95_t2(c)%particle_x1.eq.not_a_particle)then npart1=1 allocate(massi(npart1)) massi(:)=-1.0D0 else npart1=np( S95_t2(c)%particle_x1 ) allocate(massi(npart1)) massi(:)=t%particle( S95_t2(c)%particle_x1 )%M(:) endif Mj_av=massj(jj) Mi_av=massi(ii) fact= 0.0D0 cfact_t2=0.0D0 masstot=0.0D0 j=jj i=ii f=1 select case(S95_t2(c)%id) case(150) fact=test_appl(t%lep%XS_hjZ_ratio(j)*t%BR_hjhihi(j,i)*t%BR_hjbb(i)**2.0D0)!table 15 hep-ex/0602042 XS ratio case(160) fact=test_appl(t%lep%XS_hjZ_ratio(j)*t%BR_hjhihi(j,i)*t%BR_hjtautau(i)**2.0D0)!table 16 hep-ex/0602042 XS ratio case(180) fact=test_appl(t%lep%XS_hjhi_ratio(j,i)*t%BR_hjbb(j)*t%BR_hjbb(i))!table 18 hep-ex/0602042 XS ratio case(190) fact=test_appl(t%lep%XS_hjhi_ratio(j,i)*t%BR_hjtautau(j)*t%BR_hjtautau(i))!table 19 hep-ex/0602042 XS ratio case(200) fact=test_appl(t%lep%XS_hjhi_ratio(j,i)*t%BR_hjhihi(j,i)*t%BR_hjbb(i)**3.0D0)!table 20 hep-ex/0602042 XS ratio case(210) fact=test_appl(t%lep%XS_hjhi_ratio(j,i)*t%BR_hjhihi(j,i)*t%BR_hjtautau(i)**3.0D0)!table 21 hep-ex/0602042 XS ratio case(220) fact=test_appl(t%lep%XS_hjZ_ratio(j)*t%BR_hjhihi(j,i)*t%BR_hjbb(i)*t%BR_hjtautau(i))!table 22 hep-ex/0602042 XS ratio case(230) fact=test_appl(t%lep%XS_hjhi_ratio(j,i)*t%BR_hjbb(j)*t%BR_hjtautau(i))!table 23 hep-ex/0602042 XS ratio case(240) fact=test_appl(t%lep%XS_hjhi_ratio(j,i)*t%BR_hjtautau(j)*t%BR_hjbb(i))!table 24 hep-ex/0602042 XS ratio case(905) fact=test_appl(t%lep%XS_CpjCmj(j)*t%BR_CjqqNi(j,i)**2.0D0)!fig 5 hep-ex/0401026 absolute XS in fb case(906) fact=test_appl(t%lep%XS_CpjCmj(j)*t%BR_CjqqNi(j,i)*t%BR_CjlnuNi(j,i))!fig 6 hep-ex/0401026 absolute XS in fb case(907) fact=test_appl( t%lep%XS_CpjCmj(j)*t%BR_CjlnuNi(j,i)**2.0D0)!fig 7 hep-ex/0401026 absolute XS in fb case(908) fact=test_appl(t%lep%XS_CpjCmj(j)) !fig 8 hep-ex/0401026 absolute XS in fb case(909) fact=test_appl( t%lep%XS_NjNi(j,i)*t%BR_NjqqNi(j,i)) !fig 9 hep-ex/0401026 absolute XS in fb case(910) fact=test_appl(t%lep%XS_NjNi(j,i))!fig 10 hep-ex/0401026 absolute XS in fb case(6065) fact=test_appl(t%lep%XS_HpjHmj_ratio(j)*(t%BR_Hpjcs(j)+t%BR_Hpjcb(j)+t%BR_Hpjtaunu(j))) case(02671) fact=test_appl(t%lep%XS_HpjHmj_ratio(j)*(t%BR_HpjhiW(j,i)*t%BR_hjbb(i))**2.0D0) case(02672) fact=test_appl( 4.0D0 * t%lep%XS_HpjHmj_ratio(j)*t%BR_HpjhiW(j,i) * & & t%BR_Hpjtaunu(j)*t%BR_hjbb(i)**2.0D0) !Multiplied by 4 (see LEP paper) case(3381) fact=test_appl(t%tev%XS_hj_ratio(j) * t%tev%XS_H_SM(j) * t%BR_hjhihi(j,i) * & & t%BR_hjmumu(i)**2.0D0 )! arXiv:0905.3381 table I, absolute XS in fb case(3382) fact=test_appl(t%tev%XS_hj_ratio(j) * t%tev%XS_H_SM(j) * t%BR_hjhihi(j,i) * & & 2.0D0 * t%BR_hjtautau(i) * t%BR_hjmumu(i) )! arXiv:0905.3381 table II (also using fig 3b), absolute XS in fb case(5053) fact=test_appl(t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) * t%BR_hjhihi(j,i)) case(13032) ! Limit given in fb, multiply by 1000. fact=test_appl(1000.0D0*t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j)*t%BR_hjhihi(j,i) ) ! case(011811) ! ! Limit given in pb ! fact=test_appl(t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j)*t%BR_hjhihi(j,i) * & ! & t%BR_hjtautau(i) * t%BR_hjbb(i) ) ! case(011812) ! ! Limit given in fb, multiply by 1000. ! fact=test_appl(1000.0D0*t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j)*t%BR_hjhiZ(j,i) * & ! & t%BR_hjtautau(i) * BR_Zll ) ! case(044781) ! ! Limit given in pb (Z->ll unfolded) ! fact=test_appl(t%lhc8%XS_gg_hj_ratio(j)*t%lhc8%XS_gg_H_SM(j)*t%BR_hjhiZ(j,i) * & ! & t%BR_hjtautau(i)) ! case(044782) ! ! Limit given in pb (Z->ll unfolded) ! fact=test_appl(t%lhc8%XS_gg_hj_ratio(j)*t%lhc8%XS_gg_H_SM(j)*t%BR_hjhiZ(j,i) * & ! & t%BR_hjbb(i) ) ! case(20160151) ! ! Limit given in pb (Z->ll unfolded) ! fact=test_appl(t%lhc13%XS_gg_hj_ratio(j)*t%lhc13%XS_gg_H_SM(j)*t%BR_hjhiZ(j,i) * & ! & t%BR_hjbb(i) ) ! case(20160152) ! ! Limit given in pb (Z->ll unfolded) ! fact=test_appl(t%lhc13%XS_bb_hj_ratio(j)*t%lhc13%XS_bb_H_SM(j)*t%BR_hjhiZ(j,i) * & ! & t%BR_hjbb(i) ) case(06896) ! Limit given in fb, multiply by 1000. fact=test_appl(1000.0D0*t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j)*t%BR_hjhihi(j,i) * & & t%BR_hjgaga(i) * t%BR_hjbb(i) ) case(16032) ! Limit given in fb, multiply by 1000. fact=test_appl(1000.0D0*t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j)*t%BR_hjhihi(j,i) * & & t%BR_hjgaga(i) * t%BR_hjbb(i) ) ! case(14013) ! ! Limit given in fb, multiply by 1000. ! fact=test_appl(1000.0D0*t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j)*t%BR_hjhihi(j,i) * & ! & t%BR_hjbb(i) * t%BR_hjbb(i) ) case(16002) ! Limit given in fb, multiply by 1000. fact=test_appl(1000.0D0*t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j)*t%BR_hjhihi(j,i) * & & t%BR_hjbb(i) * t%BR_hjbb(i) ) case(150011) ! Limit given in fb, multiply by 1000. fact=test_appl(1000.0D0*t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j)*t%BR_hjhiZ(j,i) * & & t%BR_hjtautau(i) * BR_Zll ) case(150012) ! Limit given in fb, multiply by 1000. fact=test_appl(1000.0D0*t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j)*t%BR_hjhiZ(j,i) * & & t%BR_hjbb(i) * BR_Zll ) case(16010) ! Limit given in fb, multiply by 1000. fact=test_appl(1000.0D0*t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j)*t%BR_hjhiZ(j,i) * & & t%BR_hjbb(i) * BR_Zll ) case(14022) fact=test_appl( t%BR_hjhihi(j,i) * t%BR_hjtautau(i) * t%BR_hjtautau(i) ) case(150600424) fact=test_appl(1000.0D0*t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) * & & t%BR_hkhjhi(j,i,i)*t%BR_hjmumu(i)**2.0D0 ) case(16035) fact=test_appl(1000.0D0*t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) * & & t%BR_hkhjhi(j,i,i)*t%BR_hjmumu(i)**2.0D0 ) case(6227) f=0 do j=1,npart2 if( (abs(massj(jj)-massj(j)).le.S95_t2(c)%deltax) & & .and.( massj(jj).le.massj(j) ) )then crosssection=test_appl( t%tev%XS_hjb_ratio(j)*t%tev%XS_Hb_c4_SM(j) ) if(crosssection.gt.vsmall)then f=f+1 fact=fact+crosssection masstot=massj(j)+masstot endif endif enddo if(f.ne.0)then Mj_av=masstot/dble(f) endif case(02301) fact = ( & t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) + & t%lhc8%XS_vbf_ratio(j)*t%lhc8%XS_vbf_SM(j) + & t%lhc8%XS_hjZ_ratio(j)*t%lhc8%XS_HZ_SM(j) + & t%lhc8%XS_hjW_ratio(j)*t%lhc8%XS_HW_SM(j) + & t%lhc8%XS_tthj_ratio(j)*t%lhc8%XS_ttH_SM(j) ) * t%BR_hjgaga(j) ! DD, Nov 8 case(20160341) fact=test_appl(t%lhc13%XS_bb_hj_ratio(j)*t%lhc13%XS_bb_H_SM(j) & & * t%BR_hjhiZ(j,i) * t%BR_hjbb(i)) case(20160342) fact=test_appl(t%lhc13%XS_gg_hj_ratio(j) * t%lhc13%XS_gg_H_SM(j) & & * t%BR_hjhiZ(j,i) * t%BR_hjbb(i)) case(2016059) ! Data given in fb - (multiply by 1000) ! ( Acceptance factor linearly increasing between 200 and 700 GeV, then constant) acceptance = 0.61D0 if(Mj_av.le.700.0D0) then acceptance = ((Mj_av-200.0D0)*0.61D0+(700.0D0-Mj_av)*0.54D0)/500.0D0 endif fact =acceptance*1000.0D0*( & t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) + & t%lhc13%XS_vbf_ratio(j)*t%lhc13%XS_vbf_SM(j) + & t%lhc13%XS_hjZ_ratio(j)*t%lhc13%XS_HZ_SM(j) + & t%lhc13%XS_hjW_ratio(j)*t%lhc13%XS_HW_SM(j) + & t%lhc13%XS_tthj_ratio(j)*t%lhc13%XS_ttH_SM(j) ) * t%BR_hjgaga(j) case(4147) ! Data given in fb - (multiply by 1000) ! ( Acceptance factor linearly increasing between 200 and 800 GeV, then constant) acceptance = 0.63D0 if(Mj_av.le.800.0D0) then acceptance = ((Mj_av-200.0D0)*0.63D0+(800.0D0-Mj_av)*0.54D0)/600.0D0 endif fact =acceptance*1000.0D0*( & t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) + & t%lhc13%XS_vbf_ratio(j)*t%lhc13%XS_vbf_SM(j) + & t%lhc13%XS_hjZ_ratio(j)*t%lhc13%XS_HZ_SM(j) + & t%lhc13%XS_hjW_ratio(j)*t%lhc13%XS_HW_SM(j) + & t%lhc13%XS_tthj_ratio(j)*t%lhc13%XS_ttH_SM(j) ) * t%BR_hjgaga(j) case(003892) fact = ( & t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) + & t%lhc8%XS_vbf_ratio(j)*t%lhc8%XS_vbf_SM(j)) * t%BR_hjWW(j) case(20160791,160331) fact = 1000.0D0 * t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) * t%BR_hjZZ(j) * BR_Zll**2.0D0 case(160332) fact = 1000.0D0 * t%lhc13%XS_vbf_ratio(j)*t%lhc13%XS_VBF_SM(j) * t%BR_hjZZ(j) * BR_Zll**2.0D0 case(01123) ! Limit given in pb fact = t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) * t%BR_hjWW(j) case(170121,06386) ! Limit given in pb fact = t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) * t%BR_hjZZ(j) case default stop 'wrong input to function calcfact_t2 in module S95tables' end select if(S95_t2(c)%particle_x1.eq.not_a_particle)then select case(S95_t2(c)%id) case(6227) axis_i=t%BR_hjtautau(jj) case(02301,2016059,4147,20160791,06386) axis_i=t%particle( S95_t2(c)%particle_x2 )%GammaTot(j) / & & t%particle( S95_t2(c)%particle_x2 )%M(j) case(01123) ! in percent axis_i=t%particle( S95_t2(c)%particle_x2 )%GammaTot(j) / & & t%particle( S95_t2(c)%particle_x2 )%M(j) * 100.0D0 case(003892) axis_i=t%particle( S95_t2(c)%particle_x2 )%GammaTot(j) / & & t%GammaTot_SM(j) case(160331,160332,170121) axis_i=t%particle( S95_t2(c)%particle_x2 )%GammaTot(j) case(6065) axis_i=t%BR_Hpjtaunu(j) case default stop 'Problem in subroutine calcfact_t2 (y1)' end select select case(S95_t2(c)%id) case(02301,2016059,4147,20160791,06386,01123,003892,160331,160332,170121) if(extrapolatewidth) then if(axis_i.gt.S95_t2(c)%xmax1) then axis_i = S95_t2(c)%xmax1 endif endif case default continue end select else axis_i=Mi_av endif if(S95_t2(c)%particle_x2.eq.not_a_particle)then select case(S95_t2(c)%id) case default stop 'Problem in subroutine calcfact_t2 (y2)' end select else axis_j=Mj_av endif cfact_t2=cfact_t2+fact nc=f deallocate(massi) deallocate(massj) contains !******************************************************** function test_appl(x) !******************************************************** use usefulbits, only : div implicit none !--------------------------------------input double precision :: x !-----------------------------------function double precision :: test_appl !------------------------------------------- double precision, allocatable :: XS_ratio(:), ds(:) double precision :: s integer :: k select case(S95_t2(c)%id) case(150,160,180,190,200,210,220,230,240,3381,3382,13032,06896,14013,& & 16002,150011,150012,16032,16029,011811,011812,044781,044782,20160151,& & 20160152,16010,17002,150600424,16035,20160341,20160342) if(S95_t2(c)%needs_M2_gt_2M1.and.(massj(j).lt.2.0D0*massi(i)))then test_appl=0.0D0 elseif(massj(j).lt.massi(i))then test_appl=0.0D0 else test_appl=x endif case(02671,02672) if(massj(j).lt.massi(i)+3.0D0) then test_appl=0.0D0 else test_appl=x endif case(6065) if( (t%BR_Hpjtaunu(j) + t%BR_Hpjcs(j) + t%BR_Hpjcb(j)).gt.1.0D0 ) then test_appl=0.0D0 write(*,*) 'WARNING: Sum of charged Higgs branching ratios (cs,cb,taunu) > 1.' else test_appl=x endif case(14022) ! SM likeness test of the heavier Higgs boson allocate(XS_ratio(4),ds(4)) XS_ratio=(/ div( t%lhc8%XS_hj_ratio(j),t%lhc8%XS_H_SM(j),0.0D0,1.0D9), & div( t%lhc8%XS_vbf_ratio(j),t%lhc8%XS_vbf_SM(j),0.0D0,1.0D9), & div( t%lhc8%XS_hjW_ratio(j),t%lhc8%XS_HW_SM(j),0.0D0,1.0D9), & div( t%lhc8%XS_hjZ_ratio(j),t%lhc8%XS_HZ_SM(j),0.0D0,1.0D9) /) s=sum(XS_ratio)/4. do k=1,4 ds(k)= div((XS_ratio(k)-s), s, 0.0D0, 1.0D9) enddo if(S95_t2(c)%needs_M2_gt_2M1.and.(massj(j).lt.2.0D0*massi(i)))then test_appl=0.0D0 elseif(massj(j).lt.massi(i))then test_appl=0.0D0 elseif(maxval(ds).gt.0.1D0) then ! SM likeness test of the heavier Higgs boson test_appl=0.0D0 else test_appl=s*x endif case(5053) if(S95_t2(c)%needs_M2_gt_2M1.and.(massj(j).lt.2.0D0*massi(i)))then test_appl=0.0D0 !----Check for sufficiently SM-like BRs to gaga and bb of lighter Higgs elseif(abs(t%BR_hjgaga(i)-t%BR_Hgaga_SM(i)).gt.0.05*t%BR_Hgaga_SM(i)) then test_appl=0.0D0 elseif(abs(t%BR_hjbb(i)-t%BR_Hbb_SM(i)).gt.0.05*t%BR_Hbb_SM(i)) then test_appl=0.0D0 else test_appl=x endif case(905,906,907,909) if(abs(minval(massi)-massi(i)).gt.vsmall)then !checking that lightest neutralino in process is lightest neutralino in model test_appl=0.0D0 elseif(massj(j).lt.massi(i))then test_appl=0.0D0 else test_appl=x endif case(908) if( abs(t%BR_CjWNi(j,i)-1.0D0) .gt. eps2 )then test_appl=0.0D0 elseif(abs(minval(massi)-massi(i)).gt.vsmall)then !checking that lightest neutralino in process is lightest neutralino in model test_appl=0.0D0 elseif(massj(j).lt.massi(i))then test_appl=0.0D0 else test_appl=x endif case(910) if( abs(t%BR_NjZNi(j,i)-1.0D0) .gt. eps2 )then test_appl=0.0D0 elseif(abs(minval(massi)-massi(i)).gt.vsmall)then !checking that lightest neutralino in process is lightest neutralino in model test_appl=0.0D0 elseif(massj(j).lt.massi(i))then test_appl=0.0D0 else test_appl=x endif case(6227) if( ( t%BR_hjtautau(j)+t%BR_hjbb(j) ).le.0.98D0)then test_appl=0.0D0 else test_appl=x endif case default stop 'error in function test_appl' end select end function test_appl end subroutine calcfact_t2 !******************************************************** subroutine outputproc_t1(tlistn,jj,k,descrip) !******************************************************** ! uses information about the process to output a description ! for processes using table type 1 ! note: at the moment, np(x) (and so ii and jj) needs to be 1 digit long i.e. nH<10 !******************************************************** implicit none !--------------------------------------input integer :: tlistn integer :: jj,k !-----------------------------------internal character(LEN=2) :: j character(LEN=45) :: label character(LEN=200):: descrip !------------------------------------------- if(jj.ne.0)then write(j,'(I2)')jj j=adjustl(j) else j='j' endif if(k.eq.21)then label='' !no need to lable each line in Key.dat else label='('//trim(S95_t1(tlistn)%label)//')' endif descrip='' select case(S95_t1(tlistn)%id) case(142) descrip=' (e e)->(h'//j//')Z->(b b-bar)Z ' //label case(143) descrip=' (e e)->(h'//j//')Z->(tau tau)Z ' //label case(300) descrip=' (e e)->(h'//j//')Z->(...)Z ' //label case(400,401,402,403) descrip=' (e e)->(h'//j//')Z->(invisible)Z ' //label case(500) descrip=' (e e)->(h'//j//')Z->(gamma gamma)Z ' //label case(600,601) descrip=' (e e)->(h'//j//')Z->(2 jets)Z ' //label case(711) descrip=' (e e)->b b-bar(h'//j//')->b b-bar(b b-bar) where h'//j//' is CP even ' //label case(713) descrip=' (e e)->b b-bar(h'//j//')->b b-bar(b b-bar) where h'//j//' is CP odd ' //label case(721,741) descrip=' (e e)->b b-bar(h'//j//')->b b-bar(tau tau) where h'//j//' is CP even ' //label case(723,743) descrip=' (e e)->b b-bar(h'//j//')->b b-bar(tau tau) where h'//j//' is CP odd ' //label case(731) descrip=' (e e)->tau tau(h'//j//')->tau tau(tau tau) where h'//j//' is CP even ' //label case(733) descrip=' (e e)->tau tau(h'//j//')->tau tau(tau tau) where h'//j//' is CP odd ' //label case(801,811,821) descrip=' (e e)->(H'//j//'+)(H'//j//'-)->4 quarks ' //label case(802) descrip=' (e e)->(H'//j//'+)(H'//j//'-)->(2 quarks) tau nu ' //label case(803,813) descrip=' (e e)->(H'//j//'+)(H'//j//'-)->tau nu tau nu' //label case(5482,5570,8742,4493,9475,5876,1024,9889,3534,6089,10235,3047,10799,3564,6166,6296) descrip=' (p p-bar)->Z(h'//j//')->l l (b b-bar) ' //label case(9236,3930,8958,6039,3216,10433,6221,10600) descrip=' (p p-bar)->h'//j//'->W W ' //label case(9219,9463,5472,8957,9596,5828,1970,3493,5972,3155,5613,9868,10068,6092,10217,10239,10796,0874,6220,6309) descrip=' (p p-bar)->W(h'//j//')->l nu (b b-bar) ' //label case(5489) descrip=' (p p-bar)->h'//j//'->W W->e mu ' //label case(5624) descrip=' (p p-bar)->h'//j//'->W W->l l ' //label case(3331) descrip=' (p p-bar)->h'//j//'->V V ' //label case(5757) descrip=' (p p-bar)->h'//j//'/VBF->W W->l l where h'//j//' is SM-like ' //label case(5485,5873) descrip=' (p p-bar)->W(h'//j//')->W W W->l l nu nu ' //label case(9071,2491,5740,5980,1014,3363,4555) descrip=' (p p-bar)->h'//j//'->tau tau ' //label case(8961,9465,9290,9713,9674,0598,9897,9998,9999,6008,6096,6183,3233,6229,6304,10606,10806,10884) descrip=' (p p-bar)->h'//j//'+... where h'//j//' is SM-like ' //label case(9284,5503,5726,3556,10105,1931,4782) descrip=' (p p-bar)->h'//j//'(b/b-bar)->(b b-bar) (b/b-bar) ' //label case(6224,6225,6226) descrip=' (p p-bar)->h'//j//'(b/b-bar)->(b b-bar) (b/b-bar) or (tau tau) (b/b-bar) ' //label case(7307) descrip=' (p p-bar)->W(h'//j//')->W W W ' //label case(6301) descrip=' (p p-bar)->V h'//j//'->V W W ' //label case(5601,5737,1514) descrip=' (p p-bar)->h'//j//'+...->gamma gamma+... ' //label case(5858,6177,6295,1887,10065,10485,4960) descrip=' (p p-bar)->h'//j//'+...->gamma gamma+... where h'//j//' is SM-like ' //label case(7081,9166,9483,5586,9642,1266,0432,9891,5285,3935,6087,6170,10212,6223,6299,10583,10798) descrip=' (p p-bar)->V h'//j//'-> (b b-bar) +missing Et where h'//j//' is SM-like ' //label case(10596) descrip=' (p p-bar)->V h'//j//'-> (b b-bar) l nu where h'//j//' is SM-like ' //label case(6091,1268) descrip=' (p p-bar)->V h'//j//'-> ll + X where h'//j//' is SM-like ' //label case(10010) descrip=' (p p-bar)->V (h'//j//')/VBF-> (b b-bar) q q where h'//j//' is SM-like ' //label case(10607) descrip=' (p p-bar)->V (h'//j//')/VBF-> (b b-bar)+... where h'//j//' is SM-like ' //label case(6436) descrip=' (p p-bar)->V (h'//j//')-> (b b-bar)+...' //label case(9248,10133,10439,6305,6286) descrip=' (p p-bar)->h'//j//'+...->tau tau +... where h'//j//' is SM-like ' //label case(4800,5845,6171) descrip=' (p p-bar)->h'//j//'+...->tau tau (2 jets) where h'//j//' is SM-like ' //label case(5871) descrip=' (p p-bar)->h'//j//'+...->W W +... ->l l nu nu +... where h'//j//' is SM-like ' //label case(6082) descrip=' (p p-bar)->h'//j//'+...->V V +... ->e mu missing Et +... where h'//j//' is SM-like ' //label case(6182,6219) descrip=' (p p-bar)->h'//j//'+...->V V +... ->l l missing Et +... where h'//j//' is SM-like ' //label case(6276) descrip=' (p p-bar)->h'//j//'+...->V V +... ->l l l missing Et +... where h'//j//' is SM-like ' //label case(10573) descrip=' (p p-bar)->h'//j//'+...->V V +... ->l l l l +... where h'//j//' is SM-like ' //label case(5984,9714,6006,9022,9023,0710,9887,4162,10102,4481,4468,6095,10432,6179,6302,10599) descrip=' (p p-bar)->h'//j//'+...->W W +... where h'//j//' is SM-like ' //label case(0024,5985,0968,5974,6083,4885) descrip=' (p p-bar)->h'//j//'(b/b-bar)->(tau tau) (b/b-bar) ' //label case(5739,10574) descrip=' (p p-bar)->t t-bar h'//j//'->t t-bar b b-bar ' //label case(2012135,12025) descrip=' (p p)->t t-bar h'//j//'->t t-bar b b-bar ' //label case(0611) descrip=' (p p-bar)->h'//j//'->Z gamma ' //label case(10500) descrip=' (p p-bar)->V h'//j//'-> V tau tau ' //label case(1811) descrip=' t->(H'//j//'+)b->(2 quarks) b ' //label case(1812,2011138,2011151,2760,2013090,2014050,14020,8353,7712,11002,11008,160311,79152) descrip=' t->(H'//j//'+)b->tau nu b ' //label case(1269,1270,2011094,13035) descrip=' t->(H'//j//'+)b->(c s) b' //label case(16030) descrip=' t->(H'//j//'+)b->(c b) b' //label case(11006,11017,110271,110272,14161,14162,5064,2012017,2011150) descrip=' (p p)->h'//j//'/VBF->Z Z-> l l q q where h'//j//' is SM-like ' //label case(2011048,11004,11015,2011131) descrip=' (p p)->h'//j//'/VBF->Z Z-> l l l l where h'//j//' is SM-like ' //label case(2011162,1415,2012092) descrip=' (p p)->h'//j//'/VBF/V h'//j//'->Z Z-> l l l l where h'//j//' is SM-like ' //label case(11025,1997,12041) descrip=' (p p)->h'//j//'/VBF/V/tt h'//j//'->Z Z-> l l l l where h'//j//' is SM-like ' //label case(20130131) descrip=' (p p)->h'//j//'->Z Z-> l l l l where h'//j//' is SM-like ' //label + case(23801) + descrip=' (p p)->h'//j//'->V V (combination) ' //label + case(23802) + descrip=' (p p)->h'//j//'(VBF)->V V (combination) ' //label case(20130132) descrip=' (p p)->h'//j//'/ggF h->Z Z-> l l l l ' //label case(20130133) descrip=' (p p)->h'//j//'/VBF/V h->Z Z-> l l l l ' //label case(04670) descrip=' (p p)->h'//j//'->h(SM,125)h(SM,125)-> bb/tautau/WW/gaga (combination) ' //label case(046701,8567) descrip=' (p p)->h'//j//'->h(SM,125)h(SM,125)-> gaga WW ' //label case(4873) descrip=' (p p)->h'//j//'->h(SM,125)h(SM,125)-> gaga bb ' //label case(046702,336) descrip=' (p p)->h'//j//'->h(SM,125)h(SM,125)-> bb tautau ' //label case(17030) descrip=' (p p)->h'//j//'->h(SM,125)h(SM,125)-> bb/tautau/WW/ZZ/gaga (combination) ' //label case(059301) descrip=' (p p)->h'//j//'->Z Z ' //label case(059302) descrip=' (p p)->h'//j//'(VBF)->Z Z ' //label case(130021) descrip=' (p p)->h'//j//'->Z Z-> l l l l (low mass) where h'//j//' is SM-like ' //label case(130022) descrip=' (p p)->h'//j//'->Z Z-> l l l l (high mass) where h'//j//' is SM-like ' //label case(16034) descrip=' (p p)->h'//j//'/VBF->Z Z-> l l q q, with single-Higgs/VBF ratio profiled ' //label case(009361) descrip=' (p p)->h'//j//'->V V where h'//j//' is SM-like ' //label case(11005,11016,11026,3478) descrip=' (p p)->h'//j//'/VBF->V V-> l l nu nu where h'//j//' is SM-like ' //label case(3357,2011148,2012016) descrip=' (p p)->h'//j//'->V V-> l l nu nu where h'//j//' is SM-like ' //label case(11013,11028) descrip=' (p p)->h'//j//'/VBF->V V-> l l tau tau where h'//j//' is SM-like ' //label case(2011026) descrip=' (p p)->h'//j//'/VBF->V V where h'//j//' is SM-like ' //label case(5429,2011052,2011111,2011134) descrip=' (p p)->h'//j//'->W W ' //label case(063861) descrip=' (g g)->h'//j//' -> Z Z -> 4l+2l2nu (employs NWA)' //label case(20160821) descrip=' (g g)->h'//j//' -> Z Z -> llnunu (employs NWA)' //label case(20160822) descrip=' (g g)->h'//j//' -> Z Z -> llqq (employs NWA)' //label case(20160792) descrip=' (g g)->h'//j//' -> Z Z -> 4l (low-mass range, employs NWA)' //label case(20160823) descrip=' (p p)->h'//j//'(VBF) -> Z Z -> llqq (employs NWA)' //label case(2016062) descrip=' (p p)->h'//j//' -> W W -> lnuqq (employs NWA)' //label case(20160741) descrip=' (p p)->h'//j//' -> W W -> lnulnu (employs NWA)' //label case(20160742) descrip=' (p p)->h'//j//'(VBF) -> W W -> lnulnu (employs NWA)' //label case(20160793) descrip=' (p p)->h'//j//'(VBF) -> Z Z -> 4l (employs NWA)' //label case(0038911) descrip=' (p p)->h'//j//'->W W (employs NWA)' //label case(0038912) descrip=' (p p)->VBF, h'//j//'->W W (employs NWA)' //label case(0038913) descrip=' (p p)->h'//j//'->W W (assumes SM Higgs width, employs CPS)' //label case(0038914) descrip=' (p p)->VBF, h'//j//'->W W (assumes SM Higgs width, employs CPS)' //label case(11034,12039,13009,2012078) descrip=' (p p)->W(h'//j//')->W W W where h'//j//' is SM-like ' //label case(12006) descrip=' (p p)->W(h'//j//')->W tau tau ' //label case(12051) descrip=' (p p)->V(h'//j//')->V tau tau ' //label case(2012012,2012158,2013030) descrip=' (p p)->h'//j//'->W W where h'//j//' is SM-like ' //label case(110212) descrip=' (p p)->V h'//j//'/VBF->gamma gamma ' //label case(17013,2011025,2011085,2011161,5895,1414,2012091,2012168,1487,12001,12015,13001,11010,11030,11021) descrip=' (p p)->h'//j//'+...->gamma gamma+... where h'//j//' is SM-like ' //label case(6583,14006,14037,2018025) descrip=' (p p)->h'//j//'/VBF/Wh'//j//'/Zh'//j//'/tth'//j//'->gamma gamma ' //label case(14031) descrip=' (p p)->h'//j//'->Z gamma -> l l gamma ' //label case(13006, 13075515,2013009,3051) descrip=' (p p)->h'//j//'+...->gamma Z+... where h'//j//' is SM-like ' //label case(11031,12044,13012) descrip=' (p p)->V h'//j//'->b b where h'//j//' is SM-like ' //label case(13011) descrip=' (p p)->h'//j//'/VBF->bb+... where h'//j//' is SM-like ' //label case(2011020,2011021) descrip=' (p p)->h'//j//'->mu mu (lower mass range) ' //label case(2011005,3615,2012018) descrip=' (p p)->h'//j//'/VBF->W W where h'//j//' is SM-like ' //label case(12046) descrip=' (p p)->h'//j//'->W W-> l nu q q where h'//j//' is SM-like ' //label case(11003,11014,2577,11024,1489,12042,13003,13027) descrip=' (p p)->h'//j//'+...->W W +... where h'//j//' is SM-like ' //label case(2748,1408,11011,2011163,11022,11032,1488,12008,12045,2011157,2011112,2011135,2012019) descrip=' (p p)->h'//j//'+... where h'//j//' is SM-like ' //label case(7214) descrip=' (p p)->h'//j//'+... where h'//j//' is SM-like ' //label case(10002,5003,2011132,2012094,110201,110292,12050,13021) descrip=' (p p)->h'//j//'->tau tau ' //label case(2014049,20160852,160372,20170502) descrip=' (p p)->bbh'//j//'->tau tau ' //label case(20140492,20160851,160371,20170501) descrip=' (p p)->ggh'//j//'->tau tau ' //label case(11009,11020,2011133,2012014) descrip=' (p p)->h'//j//'/VBF->tau tau +... where h'//j//' is SM-like ' //label case(2012160,12043) descrip=' (p p)->h'//j//'->tau tau +... where h'//j//' is SM-like ' //label case(2013010,7663) descrip=' (p p)->h'//j//'->mu mu +... where h'//j//' is SM-like ' //label case(2012015) descrip=' (p p)->V h'//j//'-> (b b-bar) + X where h'//j//' is SM-like ' //label case(110291) descrip=' (p p)->h'//j//'/VBF/V h'//j//'/tt h'//j//'->tau tau +... where h'//j//' is SM-like ' //label case(2011103,2012161,11012) descrip=' (p p)->V(h'//j//')->V (b b-bar) ' //label case(13022) descrip=' (p p)->h'//j//'(VBF)->WW ' //label case(13013,13441,6682) descrip=' (p p)->h'//j//'(VBF)->V (invisible) ' //label case(13018,13442) descrip=' (p p)->Zh'//j//'->Z (invisible) ' //label case(13443) descrip=' (p p)->h'//j//'(VBF)/Zh'//j//', h'//j//'->(invisible) ' //label case(2013011,3244) descrip=' (p p)->Vh'//j//'->V (invisible) ' //label case(160312,2016088,79151,18014) descrip=' (p p) -> (H'//j//'+) t b -> (tau nu) t b '//label case(1504233) descrip=' (p p) -> (H'//j//'+) (VBF) -> W Z '//label case(2016089,3599) descrip=' (p p) -> (H'//j//'+) t b -> (t b) t b '//label case(2016071) descrip=' (p p) -> h'//j//' -> h h -> W W gamma gamma, where h lies around 125 (+- 2.5 GeV) '//label case(14013,16002,2016049) descrip=' (p p) -> h'//j//' -> h h -> b b b b, where h lies around 125 (+- 10 GeV) '//label case(011811,16029,17002) descrip=' (p p) -> h'//j//' -> h h -> b b tau tau, where h lies around 125 (+- 10 GeV) '//label case(14011,044782) descrip=' (p p) -> h'//j//' -> Z h -> l l b b, where h lies around 125 (+- 10 GeV) '//label case(011812,044781) descrip=' (p p) -> h'//j//' -> Z h -> l l tau tau, where h lies around 125 (+- 10 GeV) '//label case(20160151,180051) descrip=' (g g) -> h'//j//' -> Z h -> l l b b, where h lies around 125 (+- 10 GeV) '//label case(20160152,180052) descrip=' (b b) -> h'//j//' -> Z h -> l l b b, where h lies around 125 (+- 10 GeV) '//label case(1508329,2015080) descrip=' (p p)->bbh'//j//'->b b ' //label case(2016025) descrip=' (p p)->h'//j//'->b b ' //label case(2016044) descrip=' (p p)->h'//j//'->Z gamma ' //label case(201608391) descrip=' (p p) -> W h -> W a a -> W b b b b, where h lies around 125 (+- 10 GeV) '//label case(15009) descrip=' (p p)->b b h'//j//'->b b mu mu ' //label case(2016004) descrip=' (p p)->h'//j//'->h h -> b b gamma gamma, where h lies around 125 (+- 2.5 GeV) ' //label case(17006) descrip=' (p p)->h'//j//'->h h -> b b l l nu nu, where h lies around 125 (+- 10 GeV) ' //label case(1604833) descrip=' (p p)->h'//j//'->V V (V=W,Z) ' //label case(2016056) descrip=' (p p)->h'//j//'->Z Z-> l l nu nu ' //label case(20160551) descrip=' (p p)->h'//j//'->Z Z-> q q q q (boosted jets, using RS graviton limit) ' //label case(20160552) descrip=' (p p)->h'//j//'->W W-> q q q q (boosted jets, using RS graviton limit) ' //label case(7355) descrip=' (p p)-> V H (H near 125 GeV) -> h'//j//'h'//j//' -> b b b b ' //label case(17020321,1506534) descrip=' (p p)-> H_{SM-like} near 125 GeV -> h'//j//'h'//j//' -> tau tau tau tau ' //label case(5051) descrip=' (p p)-> H_{SM-like} near 125 GeV -> h'//j//'h'//j//' -> gamma gamma gamma gamma ' //label case(17020322,539) descrip=' (p p)-> H_{SM-like} near 125 GeV -> h'//j//'h'//j//' -> mu mu b b ' //label case(17020323) descrip=' (p p)-> H_{SM-like} near 125 GeV -> h'//j//'h'//j//' -> mu mu tau tau ' //label case default stop 'wrong input to function outputproc_t1 in module S95tables (1)' end select ! New description string based on data file input ! Added by OS 2012-03-12 if(S95_t1(tlistn)%desc.NE.'') then descrip = trim(S95_t1(tlistn)%desc) // ', h='//j if (S95_t1(tlistn)%SMlike.EQ.1) then descrip = trim(descrip)//' where h is SM-like' endif descrip = trim(descrip)//' '//label endif end subroutine outputproc_t1 !******************************************************** subroutine outputproc_t2(tlistn,ii,jj,k,descrip) !******************************************************** ! uses information about the process to output a description ! for processes using table type 1 ! note: at the moment, np(x) (and so ii and jj) needs to be 1 digit long i.e. np(x)<10 !******************************************************** implicit none !--------------------------------------input integer :: tlistn integer :: ii,jj,k !-----------------------------------internal character(LEN=2) :: j,i character(LEN=45) :: label character(LEN=200):: descrip !------------------------------------------- if((ii.ne.0).and.(jj.ne.0))then write(i,'(I2)')ii i=adjustl(i) write(j,'(I2)')jj j=adjustl(j) else i='i' j='j' endif if(k.eq.21)then label='' !no need to lable each line in Key.dat else label='('//trim(S95_t2(tlistn)%label)//')' endif select case(S95_t2(tlistn)%id) case(150) descrip=' (ee)->(h'//j//'->h'//i//' h'//i//')Z->(b b b b)Z ' //label case(160) descrip=' (ee)->(h'//j//'->h'//i//' h'//i//')Z->(tau tau tau tau)Z ' //label case(180) descrip=' (ee)->(h'//j//' h'//i//')->(b b b b) ' //label case(190) descrip=' (ee)->(h'//j//' h'//i//')->(tau tau tau tau) ' //label case(200) descrip=' (ee)->(h'//j//'->h'//i//' h'//i//')h'//i//'->(b b b b)b b '//label case(210) descrip=' (ee)->(h'//j//'->h'//i//' h'//i//')h'//i//'->(tau tau tau tau)tau tau '//label case(220) descrip=' (ee)->(h'//j//'->h'//i//' h'//i//')Z->(b b)(tau tau)Z ' //label case(230) descrip=' (ee)->(h'//j//'->b b)(h'//i//'->tau tau) ' //label case(240) descrip=' (ee)->(h'//j//'->tau tau)(h'//i//'->b b) ' //label case(905) descrip=' (ee)->(C'//j//'+)(C'//j//'-)-> (q q N'//i//') (q q N'//i//') ' //label case(906) descrip=' (ee)->(C'//j//'+)(C'//j//'-)-> q q l nu N'//i//' N'//i//' ' //label case(907) descrip=' (ee)->(C'//j//'+)(C'//j//'-)-> (l nu N'//i//') (l nu N'//i//') ' //label case(908) descrip=' (ee)->(C'//j//'+)(C'//j//'-) with all C'//j//' decaying to W + N'//i//' ' //label case(909) descrip=' (ee)->(N'//j//') N'//i//'-> (q q N'//i//') N'//i//' ' //label case(910) descrip=' (ee)->N'//j//' N'//i//' with all N'//j//' decaying to Z + N'//i//' ' //label case(6065) descrip=' (ee)->(H'//j//'+)(H'//j//'-), with H^(+/-) -> 2 quarks or tau nu (combination)' //label case(02671) descrip=' (ee)->(H'//j//'+)(H'//j//'-)-> (h'//i//'W)(h'//i//'W), with h'//i//'-> bb' //label case(02672) descrip=' (ee)->(H'//j//'+)(H'//j//'-)-> (h'//i//'W)(tau nu), with h'//i//'-> bb' //label case(3381) descrip=' (p p-bar)->h'//j//'->h'//i//' h'//i//'->mu mu mu mu ' //label case(3382) descrip=' (p p-bar)->h'//j//'->h'//i//' h'//i//'->tau tau mu mu ' //label case(5053) descrip=' (p p)->h'//j//'->h'//i//' h'//i//'->gamma gamma b b, where h'//i//' is SM-like around 125 GeV '//label case(13032,06896,16032) descrip=' (p p)->h'//j//'->h'//i//' h'//i//'->gamma gamma b b, where h'//i//' lies around 125 GeV '//label case(011811) descrip=' (p p)->h'//j//'->h'//i//' h'//i//'->b b tau tau, where h'//i//' lies around 125 GeV '//label case(14013,16002) descrip=' (p p)->h'//j//'->h'//i//' h'//i//'->b b b b, where h'//i//' lies around 125 GeV '//label case(14022) descrip=' (p p)->h'//j//'->h'//i//' h'//i//'->tau tau tau tau, where h'//j//' lies around 125 GeV and is SM-like '//label case(011812,150011) descrip=' (p p)->h'//j//' -> h'//i//'Z -> (tau tau)(l l) '//label case(20160342) descrip=' (p p)->h'//j//' -> h'//i//'Z -> (b b-bar)(l l), gluon fusion '//label case(20160341) descrip=' (p p)->h'//j//' -> h'//i//'Z -> (b b-bar)(l l), b-associated '//label case(150012,16010) descrip=' (p p)->h'//j//' -> h'//i//'Z -> (b b-bar)(l l) '//label case(044781) descrip=' (g g)->h'//j//' -> h'//i//'Z -> (tau tau)(l l) '//label case(044782,20160151) descrip=' (g g)->h'//j//' -> h'//i//'Z -> (b b-bar)(l l) '//label case(20160152) descrip=' (b b)->h'//j//' -> h'//i//'Z -> (b b-bar)(l l) '//label case(6227) descrip=' (p p-bar)->h'//j//'(b/b-bar)->(b b-bar) (b/b-bar) or (tau tau) (b/b-bar) ' //label case(02301,2016059,4147) descrip=' (p p)->h'//j//'/VBF/Wh'//j//'/Zh'//j//'/tth'//j//'->gamma gamma (including widths effects) ' //label case(003892) descrip=' (p p)->h'//j//'/VBF->W W (including widths effects) ' //label case(01123) descrip=' (p p)->h'//j//'->W W (including widths effects) ' //label case(20160791,160331) descrip=' (g g)->h'//j//'->Z Z -> 4l (including widths effects) ' //label case(170121) descrip=' (p p)->h'//j//'->Z Z -> 4l,2l2q,2l2nu (including widths effects) ' //label case(06386) descrip=' (p p)->h'//j//'->Z Z -> 4l,2l2nu (including widths effects) ' //label case(160332) descrip=' (p p)->h'//j//' (VBF)->Z Z -> 4l (including widths effects) ' //label case(150600424,16035) descrip=' (p p)->h'//j//'->h'//i//'h'//i//'->mu mu mu mu ' //label case default stop 'wrong input to function outputproc_t2 in module S95tables (2)' end select end subroutine outputproc_t2 !****************************************************************** subroutine model_likeness(j,id,t,model_like,sigmaXbr) !***************************************************************** ! Tests how Standard Model-like a parameter point is ! 0 means Mi.ge.MSingleLim (treat as single channel) ! 1 passes the SM-like test and Mi.lt.MSingleLim ! -1 fails the SM-like test and Mi.lt.MSingleLim use usefulbits, only : dataset,div, vsmall, iselementofarray, np, Hneut use theory_BRfunctions use theory_XS_SM_functions implicit none !--------------------------------------input type(dataset) :: t integer :: id,j !-----------------------------------internal integer :: ns,nb,n,jj !--TS 14/03/2011: For revamped model-likeness test method double precision,allocatable :: channel_rat(:,:), channel_SM(:,:) double precision,allocatable :: XS_SM_temp(:), BR_SM_temp(:) double precision :: SMrate, weight, c, dcbyc_dble integer :: ic,nc,nc_rel !---- double precision,allocatable :: XS_rat(:), BR_rat(:) integer :: model_like,testSMratios double precision :: sigmaXbr integer :: is,ib double precision :: s,b double precision,allocatable :: dsbys(:),dbbyb(:),dcbyc(:) logical :: correct_properties double precision,parameter :: unset=-9.9999D6 correct_properties=.True. ns=-1 nb=-1 nc=-1 n=t1elementnumberfromid(S95_t1,id) select case(id) case(711,713,721,723,731,733,741,743,5739,10574,6224,6225,6226,6276,6301,6309,& - & 04670,046701,046702,336,0038911,0038912,0038913,0038914,17030,4873,8567) + & 04670,046701,046702,336,0038911,0038912,0038913,0038914,17030,4873,8567,23801,23802) !these have a very simple model-likeness test, so we can have a non-zero deltax case default if(S95_t1(n)%deltax.gt.0.0D0)then write(*,*)'hello id=',id,'deltax=',S95_t1(n)%deltax stop 'error in subroutine model_likeness (1)' endif end select select case(id) case(8961,0598) ! ns = 3; nb = 2; call initialise_XS_rat_BR_rat nc = 6; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! BR_rat(1) = div(t%BR_hjbb(j) , t%BR_Hbb_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div(t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) case(10010,10607) ! ns = 4; nb = 2; call initialise_XS_rat_BR_rat nc = 8; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_vbf_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_tthj_ratio(j) ! BR_rat(1) = div(t%BR_hjbb(j) , t%BR_Hbb_SM(j),0.0D0,1.0D0) ! BR_rat(2) = div(( t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j) ) & ! & , t%BR_Hjets_SM(j),0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) case(13443) nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hjZ_ratio(j) , div(t%BR_hjinvisible(j),1.0D0,0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j) , div(t%BR_hjinvisible(j),1.0D0,0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_HZ_SM(j) , 1.0D0 /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j) , 1.0D0 /) case(6436) nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) case(9290) ! ns = 4; nb = 4; call initialise_XS_rat_BR_rat nc = 16; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div( t%BR_hjbb(j) , t%BR_Hbb_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j),0.0D0,1.0D0) ! BR_rat(4) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(13,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(14,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(15,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(16,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hgaga_SM(j) /) case(9674,9897,9999) ! ns = 4; nb = 3; call initialise_XS_rat_BR_rat nc = 12; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div( t%BR_hjbb(j) , t%BR_Hbb_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) case(7081,9166,9483,5586,9642,1266,0432,9891,5285,3935,6087,6170,10212,6223,6299,10583,10798,10596) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hjZ_ratio(j) ! BR_rat(1) = div(t%BR_hjbb(j) , t%BR_Hbb_SM(j),0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) case(10500) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hjZ_ratio(j) ! BR_rat(1) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) case(9248,10133,10439) ! ns = 4; nb = 1; call initialise_XS_rat_BR_rat nc = 4; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j),0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) case(4800) ! ns = 4; nb = 3; call initialise_XS_rat_BR_rat nc = 12; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div(t%BR_hjbb(j) , t%BR_Hbb_SM(j),0.0D0,1.0D0) ! BR_rat(3) = div(( t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j) ) & ! & , t%BR_Hjets_SM(j),0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) case(5845) ! ns = 4; nb = 2; call initialise_XS_rat_BR_rat nc = 8; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div(( t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j) ) & ! & , t%BR_Hjets_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hjets_SM(j) /) case(5858,6177,6295,1887,10065,10485,4960) ! ns = 4; nb = 1; call initialise_XS_rat_BR_rat nc = 4; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div(t%BR_hjgaga(j) , t%BR_Hgaga_SM(j),0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hgaga_SM(j) /) case(9465,5871,9022,9023,0710,9887,5984,9714,4162,10102,6006,4481,4468,6095,10432,6179,6302,10599) ! ns = 4; nb = 1; call initialise_XS_rat_BR_rat nc = 4; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) case(6082,6182,6219,10573,6276) ! ns = 4; nb = 2; call initialise_XS_rat_BR_rat nc = 8; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div(t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div(t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HZZ_SM(j) /) case(3331) ! ns = 1; nb = 2; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hj_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_H_SM(j) , t%BR_HZZ_SM(j) /) case(6301) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hjZ_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) case(6309) ! ns = 4; nb = 2; call initialise_XS_rat_BR_rat nc = 5; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) case(1268,6091) ! ns = 2; nb = 2; call initialise_XS_rat_BR_rat nc = 4; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hjZ_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HZZ_SM(j) /) case(6008,9998) ! ns = 5; nb = 5; call initialise_XS_rat_BR_rat nc = 25; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! XS_rat(5) = t%tev%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjbb(j) , t%BR_Hbb_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) ! BR_rat(4) = div(t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) ! BR_rat(5) = div(( t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j) ) & ! & , t%BR_Hjets_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_tthj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_tthj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hj_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_vbf_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%tev%XS_hjW_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%tev%XS_hjZ_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%tev%XS_tthj_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(17,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(18,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(19,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(20,:) = (/ t%tev%XS_tthj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(21,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(22,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(23,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(24,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(25,:) = (/ t%tev%XS_tthj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(13,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(14,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(15,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(16,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(17,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(18,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(19,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(20,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(21,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(22,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(23,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(24,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(25,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_Hbb_SM(j) /) case(6183,3233) ! ns = 4; nb = 4; call initialise_XS_rat_BR_rat nc = 16; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div(t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) ! BR_rat(4) = div(t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(13,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(14,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(15,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(16,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hgaga_SM(j) /) case(6286) ! ns = 4; nb = 4; call initialise_XS_rat_BR_rat nc = 9; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjmumu(j),t%BR_Hmumu_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hmumu_SM(j) /) case(6305) ! ns = 4; nb = 3; call initialise_XS_rat_BR_rat nc = 12; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div(t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HZZ_SM(j) /) case(6096,10606,10806,10884) nc = 30; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_tthj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_tthj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hj_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_vbf_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%tev%XS_hjW_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%tev%XS_hjZ_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%tev%XS_tthj_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(17,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(18,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(19,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(20,:) = (/ t%tev%XS_tthj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(21,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(22,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(23,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(24,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(25,:) = (/ t%tev%XS_tthj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(26,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(27,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(28,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(29,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(30,:) = (/ t%tev%XS_tthj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(13,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(14,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(15,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(16,:) = (/ t%tev%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(17,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(18,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(19,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(20,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(21,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(22,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(23,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(24,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(25,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(26,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(27,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(28,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(29,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(30,:) = (/ t%tev%XS_ttH_SM(j) , t%BR_Hbb_SM(j) /) case(6229) ! ns = 4; nb = 6; call initialise_XS_rat_BR_rat nc = 24; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div( t%BR_hjbb(j) , t%BR_Hbb_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) ! BR_rat(4) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) ! BR_rat(5) = div(( t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j) ) & ! & , t%BR_Hjets_SM(j) ,0.0D0,1.0D0) ! BR_rat(6) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hj_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_vbf_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hjW_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_hjZ_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(17,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(18,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(19,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(20,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(21,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(22,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(23,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(24,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(13,:) = (/ t%tev%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(14,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(15,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(16,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(17,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(18,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(19,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(20,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(21,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(22,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(23,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(24,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) case(6304) ! ns = 4; nb = 5; call initialise_XS_rat_BR_rat nc = 20; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(17,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(18,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(19,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(20,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(13,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(14,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(15,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(16,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(17,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(18,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(19,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(20,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) case(6171) ! ns = 4; nb = 3; call initialise_XS_rat_BR_rat nc = 12; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hj_ratio(j) ! XS_rat(3) = t%tev%XS_hjZ_ratio(j) ! XS_rat(4) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j),0.0D0,1.0D0) ! BR_rat(3) = div(( t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j) ) & ! & , t%BR_Hjets_SM(j),0.0D0,1.0D0) channel_rat(1,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%tev%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%tev%XS_vbf_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%tev%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%tev%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%tev%XS_hj_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%tev%XS_vbf_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%tev%XS_hjW_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%tev%XS_hjZ_ratio(j) , & & div((t%BR_hjss(j)+t%BR_hjcc(j)+t%BR_hjbb(j)+t%BR_hjgg(j)),t%BR_Hjets_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%tev%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%tev%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%tev%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(6,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(7,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(8,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(9,:) = (/ t%tev%XS_H_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(10,:) = (/ t%tev%XS_vbf_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(11,:) = (/ t%tev%XS_HW_SM(j) , t%BR_Hjets_SM(j) /) channel_SM(12,:) = (/ t%tev%XS_HZ_SM(j) , t%BR_Hjets_SM(j) /) !---------------------- LHC 7/8 TeV searches -------------------- case(5757,2011005,3615,2012018) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hj_ratio(j) ! XS_rat(2) = t%tev%XS_vbf_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HWW_SM(j) /) case(12046) nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HWW_SM(j) /) case(2011048,11004,11015,11013,11028,11006,11017,110271,110272,14161,14162,5064,2012017,2011150,2011131) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! BR_rat(1) = div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j) , t%BR_HZZ_SM(j) /) case(11034,12039,13009,12006,2012078) ! ns = 1; nb = 2; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc7%XS_hjW_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_HW_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) case(12051) nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc7%XS_hjW_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_hjZ_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_HW_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_HZ_SM(j) , t%BR_Htautau_SM(j) /) case(2012015) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM ! XS_rat(1) = t%tev%XS_hjW_ratio(j) ! XS_rat(2) = t%tev%XS_hjZ_ratio(j) ! BR_rat(1) = div(t%BR_hjbb(j) , t%BR_Hbb_SM(j),0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hjW_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_hjZ_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_HW_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_HZ_SM(j) , t%BR_Hbb_SM(j) /) case(2011162,1415) ! ns = 4; nb = 1; call initialise_XS_rat_BR_rat nc = 4; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_hjW_ratio(j) ! BR_rat(1) = div(t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HZZ_SM(j) /) case(2012092,20130131) nc = 4; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HZZ_SM(j) /) case(11025,1997) ! ns = 5; nb = 1; call initialise_XS_rat_BR_rat nc = 5; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div(t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(5,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) case(12041,130021,130022) nc = 5; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(5,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) case(2011026,11005,11016,11026,3478,3357,2011148,2012016) ! ns = 2; nb = 2; call initialise_XS_rat_BR_rat nc = 4; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div(t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) case(11003,11014,2577,11024,1489) ! ns = 5; nb = 2; call initialise_XS_rat_BR_rat nc = 10; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(8,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(9,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) case(12042,13003,13027) nc = 4; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HWW_SM(j) /) case(2012014) ! ns = 5; nb = 1; call initialise_XS_rat_BR_rat nc = 5; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Htautau_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Htautau_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Htautau_SM(j) /) channel_SM(5,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Htautau_SM(j) /) case(2012160) ! ns = 5; nb = 1; call initialise_XS_rat_BR_rat nc = 4; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Htautau_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Htautau_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Htautau_SM(j) /) case(11009,11020,2011133) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! BR_rat(1) = div( t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Htautau_SM(j) /) case(110291) ! ns = 5; nb = 1; call initialise_XS_rat_BR_rat nc = 5; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Htautau_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Htautau_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Htautau_SM(j) /) channel_SM(5,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Htautau_SM(j) /) case(12043) nc = 4; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_Htautau_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Htautau_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Htautau_SM(j) /) case(2013010,7663) nc = 4; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjmumu(j),t%BR_Hmumu_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjmumu(j),t%BR_Hmumu_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjmumu(j),t%BR_Hmumu_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjmumu(j),t%BR_Hmumu_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_Hmumu_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_Hmumu_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Hmumu_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Hmumu_SM(j) /) case(11031,2011103,11012) nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hbb_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hbb_SM(j) /) case(12044,13012) nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Hbb_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Hbb_SM(j) /) case(13011) nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_Hbb_SM(j) /) case(2012161) nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Hbb_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Hbb_SM(j) /) case(11021) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! BR_rat(1) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) case(110212) ! ns = 3; nb = 1; call initialise_XS_rat_BR_rat nc = 3; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(2) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjW_ratio(j) ! BR_rat(1) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) case(2011025,2011085,2011161,5895,1414,1487,12001,11010,11030) ! ns = 5; nb = 1; call initialise_XS_rat_BR_rat nc = 5; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(5,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) case(17013) nc = 5; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc13%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc13%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc13%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc13%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc13%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc13%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(2,:) = (/ t%lhc13%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(3,:) = (/ t%lhc13%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(4,:) = (/ t%lhc13%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(5,:) = (/ t%lhc13%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) +case(23801) +nc = 2; call initialise_channel_rat_SM + +channel_rat(1,:) = (/ t%lhc13%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) +channel_rat(2,:) = (/ t%lhc13%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) + +channel_SM(1,:) = (/ t%lhc13%XS_H_SM(j) , t%BR_HWW_SM(j) /) +channel_SM(2,:) = (/ t%lhc13%XS_H_SM(j) , t%BR_HZZ_SM(j) /) + +case(23802) +nc = 2; call initialise_channel_rat_SM + +channel_rat(1,:) = (/ t%lhc13%XS_vbf_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) +channel_rat(2,:) = (/ t%lhc13%XS_vbf_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) + +channel_SM(1,:) = (/ t%lhc13%XS_vbf_SM(j) , t%BR_HWW_SM(j) /) +channel_SM(2,:) = (/ t%lhc13%XS_vbf_SM(j) , t%BR_HZZ_SM(j) /) + case(2012091,2012168) ! ns = 5; nb = 1; call initialise_XS_rat_BR_rat nc = 5; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(5,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) case(12015,13001) nc = 5; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(5,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) case(13006,13075515,2013009,3051) nc = 5; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjZga(j),t%BR_HZga_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjZga(j),t%BR_HZga_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjZga(j),t%BR_HZga_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjZga(j),t%BR_HZga_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjZga(j),t%BR_HZga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HZga_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HZga_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HZga_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HZga_SM(j) /) channel_SM(5,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_HZga_SM(j) /) case(2748, 1408) ! ns = 5; nb = 3; call initialise_XS_rat_BR_rat nc = 15; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(2) = t%lhc7%XS_hj_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(8,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(9,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) channel_SM(11,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(12,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(13,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(14,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(15,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) case(11011,2011163) ! ns = 5; nb = 4; call initialise_XS_rat_BR_rat nc = 20; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(2) = t%lhc7%XS_hj_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) ! BR_rat(4) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(17,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(18,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(19,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(20,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(8,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(9,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) channel_SM(11,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(12,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(13,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(14,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(15,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(16,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(17,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Htautau_SM(j) /) channel_SM(18,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Htautau_SM(j) /) channel_SM(19,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Htautau_SM(j) /) channel_SM(20,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Htautau_SM(j) /) case(2012012) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 2; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HWW_SM(j) /) case(2012158,2013030) ! ns = 2; nb = 1; call initialise_XS_rat_BR_rat nc = 4; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HWW_SM(j) /) case(2012135,12025) nc = 1; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Hbb_SM(j) /) case(2011112) ! ns = 5; nb = 4; call initialise_XS_rat_BR_rat nc = 20; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(2) = t%lhc7%XS_hj_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(4) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) ! BR_rat(4) = div( t%BR_hjbb(j) , t%BR_Hbb_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(17,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(18,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(19,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(20,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(8,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(9,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) channel_SM(11,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(12,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(13,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(14,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(15,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(16,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(17,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hbb_SM(j) /) channel_SM(18,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hbb_SM(j) /) channel_SM(19,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hbb_SM(j) /) channel_SM(20,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Hbb_SM(j) /) case(11022,11032,1488,12008,2011157,2012019,2011135) ! ns = 5; nb = 5; call initialise_XS_rat_BR_rat nc = 25; call initialise_channel_rat_SM ! XS_rat(1) = t%lhc7%XS_hj_ratio(j) ! XS_rat(2) = t%lhc7%XS_vbf_ratio(j) ! XS_rat(1) = t%lhc7%XS_hjW_ratio(j) ! XS_rat(3) = t%lhc7%XS_hjZ_ratio(j) ! XS_rat(5) = t%lhc7%XS_tthj_ratio(j) ! BR_rat(1) = div( t%BR_hjZZ(j) , t%BR_HZZ_SM(j) ,0.0D0,1.0D0) ! BR_rat(2) = div( t%BR_hjWW(j) , t%BR_HWW_SM(j) ,0.0D0,1.0D0) ! BR_rat(3) = div( t%BR_hjgaga(j) , t%BR_Hgaga_SM(j) ,0.0D0,1.0D0) ! BR_rat(4) = div(t%BR_hjtautau(j) , t%BR_Htautau_SM(j) ,0.0D0,1.0D0) ! BR_rat(5) = div( t%BR_hjbb(j) , t%BR_Hbb_SM(j) ,0.0D0,1.0D0) channel_rat(1,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(17,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(18,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(19,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(20,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(21,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(22,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(23,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(24,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(25,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(8,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(9,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) channel_SM(11,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(12,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(13,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(14,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(15,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(16,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(17,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Htautau_SM(j) /) channel_SM(18,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Htautau_SM(j) /) channel_SM(19,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Htautau_SM(j) /) channel_SM(20,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Htautau_SM(j) /) channel_SM(21,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(22,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hbb_SM(j) /) channel_SM(23,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hbb_SM(j) /) channel_SM(24,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hbb_SM(j) /) channel_SM(25,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Hbb_SM(j) /) case(12045) nc = 25; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(17,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(18,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(19,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(20,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(21,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(22,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(23,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(24,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(25,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(8,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(9,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) channel_SM(11,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(12,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(13,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(14,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(15,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(16,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(17,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_Htautau_SM(j) /) channel_SM(18,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Htautau_SM(j) /) channel_SM(19,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Htautau_SM(j) /) channel_SM(20,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_Htautau_SM(j) /) channel_SM(21,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(22,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_Hbb_SM(j) /) channel_SM(23,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Hbb_SM(j) /) channel_SM(24,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Hbb_SM(j) /) channel_SM(25,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_Hbb_SM(j) /) case(009361) nc = 10; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(8,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(9,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) case(17020321,17020322,17020323) ! This only checks the relative proportions of the four main production modes nc = 4; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , 1.0D0 /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), 1.0D0 /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), 1.0D0 /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), 1.0D0 /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , 1.0D0 /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), 1.0D0 /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), 1.0D0 /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), 1.0D0 /) case(539) ! This only checks the relative proportions of the four main production modes nc = 4; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc13%XS_hj_ratio(j) , 1.0D0 /) channel_rat(2,:) = (/ t%lhc13%XS_vbf_ratio(j), 1.0D0 /) channel_rat(3,:) = (/ t%lhc13%XS_hjZ_ratio(j), 1.0D0 /) channel_rat(4,:) = (/ t%lhc13%XS_hjW_ratio(j), 1.0D0 /) channel_SM(1,:) = (/ t%lhc13%XS_H_SM(j) , 1.0D0 /) channel_SM(2,:) = (/ t%lhc13%XS_vbf_SM(j), 1.0D0 /) channel_SM(3,:) = (/ t%lhc13%XS_HZ_SM(j), 1.0D0 /) channel_SM(4,:) = (/ t%lhc13%XS_HW_SM(j), 1.0D0 /) case(7214) nc = 25; call initialise_channel_rat_SM channel_rat(1,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(2,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(3,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(4,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(5,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) /) channel_rat(6,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(7,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(8,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(9,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(10,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) /) channel_rat(11,:) = (/ t%lhc8%XS_hj_ratio(j) , div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(12,:) = (/ t%lhc8%XS_vbf_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(13,:) = (/ t%lhc8%XS_hjZ_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(14,:) = (/ t%lhc8%XS_hjW_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(15,:) = (/ t%lhc8%XS_tthj_ratio(j), div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) /) channel_rat(16,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(17,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(18,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(19,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(20,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) /) channel_rat(21,:) = (/ t%lhc7%XS_hj_ratio(j) , div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(22,:) = (/ t%lhc7%XS_vbf_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(23,:) = (/ t%lhc7%XS_hjZ_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(24,:) = (/ t%lhc7%XS_hjW_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_rat(25,:) = (/ t%lhc7%XS_tthj_ratio(j), div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) /) channel_SM(1,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HWW_SM(j) /) channel_SM(2,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HWW_SM(j) /) channel_SM(3,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HWW_SM(j) /) channel_SM(4,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HWW_SM(j) /) channel_SM(5,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_HWW_SM(j) /) channel_SM(6,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_HZZ_SM(j) /) channel_SM(7,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_HZZ_SM(j) /) channel_SM(8,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_HZZ_SM(j) /) channel_SM(9,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_HZZ_SM(j) /) channel_SM(10,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_HZZ_SM(j) /) channel_SM(11,:) = (/ t%lhc8%XS_H_SM(j) , t%BR_Hgaga_SM(j) /) channel_SM(12,:) = (/ t%lhc8%XS_vbf_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(13,:) = (/ t%lhc8%XS_HZ_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(14,:) = (/ t%lhc8%XS_HW_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(15,:) = (/ t%lhc8%XS_ttH_SM(j), t%BR_Hgaga_SM(j) /) channel_SM(16,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Htautau_SM(j) /) channel_SM(17,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Htautau_SM(j) /) channel_SM(18,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Htautau_SM(j) /) channel_SM(19,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Htautau_SM(j) /) channel_SM(20,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Htautau_SM(j) /) channel_SM(21,:) = (/ t%lhc7%XS_H_SM(j) , t%BR_Hbb_SM(j) /) channel_SM(22,:) = (/ t%lhc7%XS_vbf_SM(j), t%BR_Hbb_SM(j) /) channel_SM(23,:) = (/ t%lhc7%XS_HZ_SM(j), t%BR_Hbb_SM(j) /) channel_SM(24,:) = (/ t%lhc7%XS_HW_SM(j), t%BR_Hbb_SM(j) /) channel_SM(25,:) = (/ t%lhc7%XS_ttH_SM(j), t%BR_Hbb_SM(j) /) case(5739,10574) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%tev%XS_tthj_ratio(j) BR_rat(1) = div(t%BR_hjbb(j) , t%BR_Hbb_SM(j) ,0.0D0,1.0D0) if(t%CP_value(j).eq.1)then ! analysis only applies if higgs is CP even else correct_properties=.False. endif case(711) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lep%XS_bbhj_ratio(j) BR_rat(1) = t%BR_hjbb(j) !note *not* normalised to SM if(t%CP_value(j).eq.1)then ! analysis only applies if higgs is CP even else correct_properties=.False. endif case(713) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lep%XS_bbhj_ratio(j) BR_rat(1) = t%BR_hjbb(j)!note *not* normalised to SM if(t%CP_value(j).eq.-1)then ! analysis only applies if higgs is CP odd else correct_properties=.False. endif case(721) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lep%XS_bbhj_ratio(j) BR_rat(1) = t%BR_hjtautau(j)!note *not* normalised to SM if(t%CP_value(j).eq.1)then ! analysis only applies if higgs is CP even else correct_properties=.False. endif case(723) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lep%XS_bbhj_ratio(j) BR_rat(1) = t%BR_hjtautau(j)!note *not* normalised to SM if(t%CP_value(j).eq.-1)then ! analysis only applies if higgs is CP odd else correct_properties=.False. endif case(731) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lep%XS_tautauhj_ratio(j) BR_rat(1) = t%BR_hjtautau(j)!note *not* normalised to SM if(t%CP_value(j).eq.1)then ! analysis only applies if higgs is CP even else correct_properties=.False. endif case(733) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lep%XS_tautauhj_ratio(j) BR_rat(1) = t%BR_hjtautau(j)!note *not* normalised to SM if(t%CP_value(j).eq.-1)then ! analysis only applies if higgs is CP odd else correct_properties=.False. endif case(741) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lep%XS_bbhj_ratio(j) BR_rat(1) = t%BR_hjtautau(j)!note *not* normalised to SM if(t%CP_value(j).eq.1)then ! analysis only applies if higgs is CP even else correct_properties=.False. endif case(743) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lep%XS_bbhj_ratio(j) BR_rat(1) = t%BR_hjtautau(j)!note *not* normalised to SM if(t%CP_value(j).eq.-1)then ! analysis only applies if higgs is CP odd else correct_properties=.False. endif case(1811,2011094,13035) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%BR_tHpjb(j) BR_rat(1) = t%BR_Hpjcs(j) if( (t%BR_tHpjb(j)+t%BR_tWpb ).le.0.98D0)then correct_properties=.False. elseif((t%BR_Hpjcs(j)+t%BR_Hpjtaunu(j)).le.0.98D0)then correct_properties=.False. endif case(1812,7712,8353,11002,11008,160311) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%BR_tHpjb(j) BR_rat(1) = t%BR_Hpjtaunu(j) if( (t%BR_tHpjb(j)+t%BR_tWpb).le.0.98D0)then correct_properties=.False. elseif((t%BR_Hpjcs(j)+t%BR_Hpjtaunu(j)).le.0.98D0)then correct_properties=.False. endif case(2011138,2011151,2760,2013090,2014050,14020,79152) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%BR_tHpjb(j) BR_rat(1) = t%BR_Hpjtaunu(j) if( (t%BR_tHpjb(j)+t%BR_tWpb).le.0.98D0)then correct_properties=.False. endif case(1269,1270) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%BR_tHpjb(j) BR_rat(1) = t%BR_Hpjcs(j) if( (t%BR_tHpjb(j)+t%BR_tWpb ).le.0.98D0)then correct_properties=.False. elseif( t%BR_Hpjcs(j) .le.0.98D0)then correct_properties=.False. endif case(6224) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%tev%XS_hjb_ratio(j)*t%tev%XS_Hb_c4_SM(j) BR_rat(1) = 1.0D0 if( ( t%BR_hjtautau(j)+t%BR_hjbb(j) ).le.0.98D0)then correct_properties=.False. elseif( t%BR_hjtautau(j) .le.0.06D0)then correct_properties=.False. endif case(6225) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%tev%XS_hjb_ratio(j)*t%tev%XS_Hb_c4_SM(j) BR_rat(1) = 1.0D0 if( ( t%BR_hjtautau(j)+t%BR_hjbb(j) ).le.0.98D0)then correct_properties=.False. elseif( t%BR_hjtautau(j) .le.0.1D0)then correct_properties=.False. endif case(6226) ns = 1; nb = 1; call initialise_XS_rat_BR_rat XS_rat(1) = t%tev%XS_hjb_ratio(j)*t%tev%XS_Hb_c4_SM(j) BR_rat(1) = 1.0D0 if( ( t%BR_hjtautau(j)+t%BR_hjbb(j) ).le.0.98D0)then correct_properties=.False. elseif( t%BR_hjtautau(j) .le.0.14D0)then correct_properties=.False. endif case(04670) ! This is a H->h(SM)h(SM) search! ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) BR_rat(1) = 0.0D0 correct_properties=.False. do jj=1,np(Hneut) if(abs(t%particle(Hneut)%M(jj)-125.4).lt.(5.0D0+t%particle(Hneut)%dMh(jj))) then dcbyc_dble=maxval((/ div(abs(t%BR_hjgaga(jj)-t%BR_Hgaga_SM(jj)),t%BR_Hgaga_SM(jj),0.0D0,1.0D0),& & div(abs(t%BR_hjWW(jj)-t%BR_HWW_SM(jj)),t%BR_HWW_SM(jj),0.0D0,1.0D0), & & div(abs(t%BR_hjbb(jj)-t%BR_Hbb_SM(jj)),t%BR_Hbb_SM(jj),0.0D0,1.0D0), & & div(abs(t%BR_hjtautau(jj)-t%BR_Htautau_SM(jj)),t%BR_Htautau_SM(jj),0.0D0,1.0D0) /)) if(dcbyc_dble.lt.0.1D0) then correct_properties=.True. BR_rat(1) = BR_rat(1)+t%BR_hjhihi(j,jj) endif endif enddo case(17030) ! This is a H->h(SM)h(SM) search! ! n.b.: In principle, should also check for SM strength of h production modes, as this ! is part of the assumed background! ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = 1000.0D0 * t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) ! convert to fb BR_rat(1) = 0.0D0 correct_properties=.False. do jj=1,np(Hneut) if(abs(t%particle(Hneut)%M(jj)-125.0D0).lt.(5.0D0+t%particle(Hneut)%dMh(jj))) then dcbyc_dble=maxval((/ div(abs(t%BR_hjgaga(jj)-t%BR_Hgaga_SM(jj)),t%BR_Hgaga_SM(jj),0.0D0,1.0D0),& & div(abs(t%BR_hjWW(jj)-t%BR_HWW_SM(jj)),t%BR_HWW_SM(jj),0.0D0,1.0D0), & & div(abs(t%BR_hjZZ(jj)-t%BR_HZZ_SM(jj)),t%BR_HZZ_SM(jj),0.0D0,1.0D0), & & div(abs(t%BR_hjbb(jj)-t%BR_Hbb_SM(jj)),t%BR_Hbb_SM(jj),0.0D0,1.0D0), & & div(abs(t%BR_hjtautau(jj)-t%BR_Htautau_SM(jj)),t%BR_Htautau_SM(jj),0.0D0,1.0D0) /)) if(dcbyc_dble.lt.0.1D0) then correct_properties=.True. BR_rat(1) = BR_rat(1)+t%BR_hjhihi(j,jj) endif endif enddo case(046701) ! This is a H->h(SM)h(SM) search! ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) BR_rat(1) = 0.0D0 correct_properties=.False. do jj=1,np(Hneut) if(abs(t%particle(Hneut)%M(jj)-125.4).lt.(5.0D0+t%particle(Hneut)%dMh(jj))) then dcbyc_dble=maxval((/ div(abs(t%BR_hjgaga(jj)-t%BR_Hgaga_SM(jj)),t%BR_Hgaga_SM(jj),0.0D0,1.0D0),& & div(abs(t%BR_hjWW(jj)-t%BR_HWW_SM(jj)),t%BR_HWW_SM(jj),0.0D0,1.0D0) /)) if(dcbyc_dble.lt.0.1D0) then correct_properties=.True. BR_rat(1) = BR_rat(1)+t%BR_hjhihi(j,jj) endif endif enddo case(8567) ! This is a H->h(SM)h(SM) search! ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) BR_rat(1) = 0.0D0 correct_properties=.False. do jj=1,np(Hneut) if(abs(t%particle(Hneut)%M(jj)-125.0).lt.(5.0D0+t%particle(Hneut)%dMh(jj))) then dcbyc_dble=maxval((/ div(abs(t%BR_hjgaga(jj)-t%BR_Hgaga_SM(jj)),t%BR_Hgaga_SM(jj),0.0D0,1.0D0),& & div(abs(t%BR_hjWW(jj)-t%BR_HWW_SM(jj)),t%BR_HWW_SM(jj),0.0D0,1.0D0) /)) if(dcbyc_dble.lt.0.1D0) then correct_properties=.True. BR_rat(1) = BR_rat(1)+t%BR_hjhihi(j,jj) * t%BR_hjgaga(jj) * t%BR_hjWW(jj) * 2.0D0 ! symmetry factor of 2 endif endif enddo case(4873) ! This is a H->h(SM)h(SM) search! ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) BR_rat(1) = 0.0D0 correct_properties=.False. do jj=1,np(Hneut) if(abs(t%particle(Hneut)%M(jj)-125.0).lt.(5.0D0+t%particle(Hneut)%dMh(jj))) then dcbyc_dble=maxval((/ div(abs(t%BR_hjgaga(jj)-t%BR_Hgaga_SM(jj)),t%BR_Hgaga_SM(jj),0.0D0,1.0D0),& & div(abs(t%BR_hjbb(jj)-t%BR_Hbb_SM(jj)),t%BR_Hbb_SM(jj),0.0D0,1.0D0) /)) if(dcbyc_dble.lt.0.1D0) then correct_properties=.True. BR_rat(1) = BR_rat(1)+t%BR_hjhihi(j,jj) endif endif enddo case(046702) ! This is a H->h(SM)h(SM) search! ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) BR_rat(1) = 0.0D0 correct_properties=.False. do jj=1,np(Hneut) if(abs(t%particle(Hneut)%M(jj)-125.4).lt.(10.0D0+t%particle(Hneut)%dMh(jj))) then dcbyc_dble=maxval((/ div(abs(t%BR_hjbb(jj)-t%BR_Hbb_SM(jj)),t%BR_Hbb_SM(jj),0.0D0,1.0D0), & & div(abs(t%BR_hjtautau(jj)-t%BR_Htautau_SM(jj)),t%BR_Htautau_SM(jj),0.0D0,1.0D0) /)) if(dcbyc_dble.lt.0.1D0) then correct_properties=.True. BR_rat(1) = BR_rat(1)+t%BR_hjhihi(j,jj) endif endif enddo case(336) ! This is a H->h(SM)h(SM) search! ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc13%XS_hj_ratio(j)*t%lhc13%XS_H_SM(j) BR_rat(1) = 0.0D0 correct_properties=.False. do jj=1,np(Hneut) if(abs(t%particle(Hneut)%M(jj)-125.0).lt.(10.0D0+t%particle(Hneut)%dMh(jj))) then dcbyc_dble=maxval((/ div(abs(t%BR_hjbb(jj)-t%BR_Hbb_SM(jj)),t%BR_Hbb_SM(jj),0.0D0,1.0D0), & & div(abs(t%BR_hjtautau(jj)-t%BR_Htautau_SM(jj)),t%BR_Htautau_SM(jj),0.0D0,1.0D0) /)) if(dcbyc_dble.lt.0.1D0) then correct_properties=.True. BR_rat(1) = BR_rat(1)+t%BR_hjhihi(j,jj) * t%BR_hjbb(jj) * t%BR_hjtautau(jj) * 2.0D0 endif endif enddo case(0038911) ! H-WW search with width-assumptions ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) BR_rat(1) = t%BR_hjWW(j) if(t%particle(Hneut)%GammaTot(j)<0.2D0*t%GammaTot_SM(j)) then ! NWA requirement correct_properties=.True. else correct_properties=.False. endif case(0038912) ! H-WW search with width-assumptions ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc8%XS_vbf_ratio(j)*t%lhc8%XS_vbf_SM(j) BR_rat(1) = t%BR_hjWW(j) if(t%particle(Hneut)%GammaTot(j)<0.2D0*t%GammaTot_SM(j)) then ! NWA requirement correct_properties=.True. else correct_properties=.False. endif case(0038913) ! H-WW search with width-assumptions ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc8%XS_hj_ratio(j)*t%lhc8%XS_H_SM(j) BR_rat(1) = t%BR_hjWW(j) if(t%particle(Hneut)%GammaTot(j)>0.8D0*t%GammaTot_SM(j)) then ! NWA requirement correct_properties=.True. else correct_properties=.False. endif case(0038914) ! H-WW search with width-assumptions ns = 1; nb =1; call initialise_XS_rat_BR_rat XS_rat(1) = t%lhc8%XS_vbf_ratio(j)*t%lhc8%XS_vbf_SM(j) BR_rat(1) = t%BR_hjWW(j) if(t%particle(Hneut)%GammaTot(j)>0.8D0*t%GammaTot_SM(j)) then ! NWA requirement correct_properties=.True. else correct_properties=.False. endif !case(801,802,803,811,813,821) !ns = 1; nb = 1; call initialise_XS_rat_BR_rat ! XS_rat(1) = !BR_rat(1) = !if((t%BR_Hpjcb(j)+t%BR_Hpjcs(j)+t%BR_Hpjtaunu(j)).gt.0.98D0)then !else ! correct_properties=.False. !endif case default write(*,*)'hello id=',id stop 'error in subroutine model_likeness (2)' end select !---------------------------------------------------------- !--New model likeness check (TS 23/03/2012) !---------------------------------------------------------- if(allocated(channel_rat)) then if(nc.ne.ubound(channel_rat,dim=1))stop 'error in subroutine model_likeness (3a)' if(nc.ne.ubound(channel_SM,dim=1))stop 'error in subroutine model_likeness (3a)' ! Check if the channels have been filled correctly do ic=1,nc if(abs(channel_rat(ic,1)-unset).lt.1.0D-3)stop 'error in subroutine model_likeness (4a)' if(abs(channel_rat(ic,2)-unset).lt.1.0D-3)stop 'error in subroutine model_likeness (4a)' if(abs(channel_SM(ic,1)-unset).lt.1.0D-3)stop 'error in subroutine model_likeness (4a)' if(abs(channel_SM(ic,2)-unset).lt.1.0D-3)stop 'error in subroutine model_likeness (4a)' enddo !---Eliminate irrelevant channels (=channels with very small SM prediction). !---Construct mean value of the ratio for the relevant channels nc_rel=0 do ic=1,nc if(channel_SM(ic,1).gt.vsmall.and.channel_SM(ic,2).gt.vsmall) then nc_rel=nc_rel+1 channel_SM(nc_rel,:)=channel_SM(ic,:) channel_rat(nc_rel,:)=channel_rat(ic,:) endif enddo if(nc_rel.gt.0) then nc=nc_rel call reallocate_channel_rat_SM endif !--Evaluate the total SM rate expected for the (relevant) channels SMrate=0. do ic=1,nc SMrate=SMrate+channel_SM(ic,1)*channel_SM(ic,2) enddo !--Evaluate the predicted signal strength modifier c of the model c=0. do ic=1,nc !----use a weighted average of the channel rate ratios if(use_weight) then weight = div(channel_SM(ic,1)*channel_SM(ic,2),SMrate,0.0D0,1.0D9) else weight = 1.0D0/nc endif c=c+weight*channel_rat(ic,1)*channel_rat(ic,2) enddo !--Evaluate the deviation of each channel rate ratio to the signal !--strength modifier c allocate(dcbyc(nc)) do ic=1,nc dcbyc(ic)= div((channel_rat(ic,1)*channel_rat(ic,2)-c),c,0.0D0,1.0D9) enddo !--Do the model likeness test testSMratios= 1 !passes the SM-like ratios test do ic=1,nc !----Again, evaluate the weight of the channel if(use_weight) then weight = div(channel_SM(ic,1)*channel_SM(ic,2),SMrate,0.0D0,1.0D9) else weight = 1.0D0 endif !----Check if the channel fulfills the model likeness criteria ! print *, ic, channel_rat(ic,1), channel_rat(ic,2), abs(dcbyc(ic)*weight), dcbyc(ic), weight, c if(abs(dcbyc(ic)*weight).gt.eps)then testSMratios= -1 !fails the SM-like ratios test ! write(*,*) "Analysis application ", id, "fail the SM likeness test!" endif enddo !--Write total ratio into s and b to return later. s=c b=1. deallocate(channel_rat) deallocate(channel_SM) deallocate(dcbyc) !-If channel_rat is not allocated, use old method: else if(ns.ne.ubound(XS_rat,dim=1))stop 'error in subroutine model_likeness (3a)' if(nb.ne.ubound(BR_rat,dim=1))stop 'error in subroutine model_likeness (3b)' do is=1,ns if(abs(XS_rat(is)-unset).lt.1.0D-3)stop 'error in subroutine model_likeness (4a)' enddo do ib=1,nb if(abs(BR_rat(ib)-unset).lt.1.0D-3)stop 'error in subroutine model_likeness (4b)' enddo s=sum(XS_rat)/ns b=sum(BR_rat)/nb allocate(dsbys(ns)) do is=1,ns dsbys(is)= div((XS_rat(is) -s),s, 0.0D0,1.0D9) enddo allocate(dbbyb(nb)) do ib=1,nb dbbyb(ib)= div((BR_rat(ib) -b),b, 0.0D0,1.0D9) enddo testSMratios= 1 !passes the SM-like ratios test do is=1,ns do ib=1,nb if(abs( dsbys(is)+dbbyb(ib)+dsbys(is)*dbbyb(ib) ).gt.eps )then testSMratios= -1 !fails the SM-like ratios test endif enddo enddo deallocate(dsbys) deallocate(dbbyb) deallocate(XS_rat) deallocate(BR_rat) endif if(testSMratios.lt.0)correct_properties=.False. if(correct_properties)then model_like= 1 !passes the model-likeness test sigmaXbr=s*b else model_like= -1 !fails the model-likeness test sigmaXbr=0.0D0 endif contains !---------------------------------------- subroutine initialise_XS_rat_BR_rat allocate(XS_rat(ns)) allocate(BR_rat(nb)) XS_rat=unset BR_rat=unset allocate(XS_SM_temp(ns)) allocate(BR_SM_temp(nb)) XS_SM_temp=unset BR_SM_temp=unset end subroutine initialise_XS_rat_BR_rat !---------------------------------------- subroutine initialise_channel_rat_SM allocate(channel_rat(nc,2)) allocate(channel_SM(nc,2)) channel_rat=unset channel_SM=unset end subroutine initialise_channel_rat_SM !---------------------------------------- subroutine reallocate_channel_rat_SM double precision, allocatable :: reallocate_array(:,:) allocate(reallocate_array(nc,2)) reallocate_array(1:nc,:) = channel_rat(1:nc,:) deallocate(channel_rat) allocate(channel_rat(nc,2)) channel_rat = reallocate_array reallocate_array(1:nc,:) = channel_SM(1:nc,:) deallocate(channel_SM) allocate(channel_SM(nc,2)) channel_SM = reallocate_array deallocate(reallocate_array) end subroutine reallocate_channel_rat_SM !---------------------------------------- end subroutine model_likeness !*********************************************************** subroutine fill_blank_ft1_dat(ft1,ft1_sep,vmasslower,vmasshigher,vmass_xmin,vmass_xmax,vmass_sep,valueoutsidetable) ! don't forget to deallocate f_t1%dat use usefulbits, only : small implicit none integer :: ilower,ihigher double precision, intent(in) :: ft1_sep,vmasslower,vmasshigher,vmass_xmin,vmass_xmax,vmass_sep,valueoutsidetable type(table1) :: ft1 if(abs(vmass_xmin-vmass_xmax).lt.small)stop 'problem in f_from_t3 (4)' ft1%sep=ft1_sep ! we want f_t1%xmin to be lower than x1lower if((vmasslower -vmass_xmin).ge.0.0D0)then ilower = int((vmasslower -vmass_xmin)/vmass_sep)+1 else !off lower edge of table ilower = int((vmasslower -vmass_xmin)/vmass_sep)+1-1 !-1 since int rounds up for negative numbers endif ihigher = int((vmasshigher-vmass_xmin)/vmass_sep)+2 ! we want f_t1%xmax to be higher than x1higher ft1%xmin = dble(ilower - 1)*vmass_sep + vmass_xmin ft1%xmax = dble(ihigher - 1)*vmass_sep + vmass_xmin ft1%nx=nint((ft1%xmax-ft1%xmin)/ft1%sep)+1 allocate(ft1%dat(ft1%nx,1)) ft1%dat(:,1)=valueoutsidetable end subroutine fill_blank_ft1_dat !*********************************************************** subroutine f_from_t1(t1,vmasslower,vmasshigher,sepmultfactor,datcomp, & & f_t1,valueoutsidetable) ! Fills the f_t1 array with the information from a t1 array ! ! Do not forget to deallocate f_t1%dat later on !*********************************************************** use interpolate use usefulbits, only : small implicit none !--------------------------------------input type(table1), intent(in) :: t1 double precision, intent(in) :: vmasslower,vmasshigher,valueoutsidetable double precision, intent(in) :: sepmultfactor integer, intent(in) :: datcomp !-----------------------------------output type(table1), intent(out) :: f_t1 !-----------------------------------internal integer :: i double precision :: interpol double precision :: vmass,vmass_xmin,vmass_xmax,vmass_sep !------------------------------------------- if(vmasslower.gt.vmasshigher)then stop 'problem in f_from_t1 (1)' endif f_t1%id = t1%id f_t1%deltax = t1%deltax vmass_xmin = t1%xmin vmass_xmax = t1%xmax vmass_sep = t1%sep f_t1%sep = t1%sep*sepmultfactor call fill_blank_ft1_dat(f_t1,f_t1%sep,vmasslower,vmasshigher,vmass_xmin,vmass_xmax,vmass_sep,valueoutsidetable) do i=1,ubound(f_t1%dat,dim=1) vmass = dble(i-1)*f_t1%sep + f_t1%xmin if( vmass.lt.vmass_xmin-small )then f_t1%dat(i,1)=valueoutsidetable elseif( vmass.gt.vmass_xmax+small )then f_t1%dat(i,1)=valueoutsidetable else call interpolate_tabletype1(vmass,t1,datcomp,interpol) f_t1%dat(i,1)=interpol endif enddo end subroutine f_from_t1 !*********************************************************** subroutine f_from_t2(t2,m1_at_ref_point_1,m2_at_ref_point_1,m1_at_ref_point_2,m2_at_ref_point_2, & & vmassm1orm2,vmasslower,vmasshigher,sepmultfactor,datcomp, & & f_t1,valueoutsidetable) ! Fills the f_t1 array with the information from a t2 array along a line ! m2 = line_grad*m1 + line_const ! ! Do not forget to deallocate f_t1%dat later on !*********************************************************** use interpolate use usefulbits, only : small implicit none !--------------------------------------input type(table2), intent(in) :: t2 double precision, intent(in) :: m1_at_ref_point_1,m2_at_ref_point_1,m1_at_ref_point_2,m2_at_ref_point_2 double precision, intent(in) :: vmasslower,vmasshigher,valueoutsidetable double precision, intent(in) :: sepmultfactor integer, intent(in) :: datcomp,vmassm1orm2 !-----------------------------------output type(table1), intent(out) :: f_t1 !-----------------------------------internal type(table1) :: t1 double precision :: line_grad,line_const integer :: i logical :: const_m1,const_m2 integer :: const_m1_i,const_m2_j logical :: on_m1_gridline,on_m2_gridline double precision :: interpol,mass1,mass2 double precision :: m1bit,m2bit double precision :: vmass,vmass_xmin,vmass_xmax,vmass_sep integer :: ftype_selection(1) !------------------------------------------- if(vmasslower.gt.vmasshigher)then stop 'problem in f_from_t2 (1)' endif if(abs(m1_at_ref_point_1-m1_at_ref_point_2).lt.small)then const_m1=.True. !line_grad is not needed !line_const is not needed else const_m1=.False. line_grad =(m2_at_ref_point_1-m2_at_ref_point_2)/(m1_at_ref_point_1-m1_at_ref_point_2) line_const=(m1_at_ref_point_1*m2_at_ref_point_2-m1_at_ref_point_2*m2_at_ref_point_1) & & /(m1_at_ref_point_1-m1_at_ref_point_2) endif if(abs(m2_at_ref_point_1-m2_at_ref_point_2).lt.small)then const_m2=.True. else const_m2=.False. endif f_t1%id = t2%id f_t1%deltax = t2%deltax select case(vmassm1orm2) case(1) if(const_m1)stop 'problem in f_from_t2 (3a)' vmass_xmin = t2%xmin1 vmass_xmax = t2%xmax1 vmass_sep = t2%sep1 f_t1%sep = t2%sep1*sepmultfactor case(2) if(const_m2)stop 'problem in f_from_t2 (3b)' vmass_xmin = t2%xmin2 vmass_xmax = t2%xmax2 vmass_sep = t2%sep2 f_t1%sep = t2%sep2*sepmultfactor case default stop 'problem in f_from_t2 (3)' end select call fill_blank_ft1_dat(f_t1,f_t1%sep,vmasslower,vmasshigher,vmass_xmin,vmass_xmax,vmass_sep,valueoutsidetable) on_m1_gridline=.False. if(const_m1)then const_m1_i=nint( (m1_at_ref_point_1-t2%xmin1) /t2%sep1)+1 m1bit= m1_at_ref_point_1 -(dble(const_m1_i-1)*t2%sep1+t2%xmin1)/t2%sep1 if(m1bit.lt.small)on_m1_gridline=.True. endif on_m2_gridline=.False. if(const_m2)then const_m2_j=nint( (m2_at_ref_point_1-t2%xmin2) /t2%sep2)+1 m2bit= m2_at_ref_point_1 -(dble(const_m2_j-1)*t2%sep2+t2%xmin2)/t2%sep2 if(m2bit.lt.small)on_m2_gridline=.True. endif ftype_selection(1)=datcomp if( on_m1_gridline )then call fill_t1_from_t2(t2,2,const_m1_i,ftype_selection,t1) call f_from_t1(t1,vmasslower,vmasshigher,sepmultfactor,datcomp, & & f_t1,valueoutsidetable) deallocate(t1%dat) elseif(on_m2_gridline )then call fill_t1_from_t2(t2,1,const_m2_j,ftype_selection,t1) call f_from_t1(t1,vmasslower,vmasshigher,sepmultfactor,datcomp, & & f_t1,valueoutsidetable) deallocate(t1%dat) else do i=1,ubound(f_t1%dat,dim=1) vmass = dble(i-1)*f_t1%sep + f_t1%xmin if(t2%nx2.eq.1)then mass1 = vmass mass2 = t2%xmin2 elseif(vmassm1orm2.eq.1)then mass1 = vmass mass2 = mass1*line_grad+line_const else mass2 = vmass if(const_m1)then mass1 = m1_at_ref_point_1 else mass1 = (mass2 - line_const)/line_grad endif endif if( vmass.lt.vmass_xmin-small )then f_t1%dat(i,1)=valueoutsidetable elseif( vmass.gt.vmass_xmax+small )then f_t1%dat(i,1)=valueoutsidetable elseif(( t2%needs_M2_gt_2M1 ).and.(2.0D0*mass1>mass2+small))then f_t1%dat(i,1)=valueoutsidetable elseif((.not.(t2%needs_M2_gt_2M1)).and.(mass1>mass2+small).and.(t2%nx2.gt.1))then f_t1%dat(i,1)=valueoutsidetable else call interpolate_tabletype2(mass1,mass2,t2,datcomp,interpol) f_t1%dat(i,1)=interpol endif enddo endif end subroutine f_from_t2 !****************************************************************** subroutine f_from_slices_t2(slices_t2,m1_at_ref_point_1,m2_at_ref_point_1,m1_at_ref_point_2,m2_at_ref_point_2,z, & & vmassm1orm2,vmasslower,vmasshigher,sepmultfactor,datcomp, & & f_t1,valueoutsidetable) !****************************************************************** ! fill the f_t1 array with the information from a t3 array at constant sf along a line ! m2 = line_grad*m1 + line_const ! do not forget to deallocate dat use S95tables_type3 use interpolate use usefulbits, only : small implicit none type(table2), intent(in) :: slices_t2(2) type(table1) :: f_t1 double precision, intent(in) :: m1_at_ref_point_1,m2_at_ref_point_1,m1_at_ref_point_2,m2_at_ref_point_2 double precision, intent(in) :: z,vmasslower,vmasshigher,valueoutsidetable double precision, intent(in) :: sepmultfactor double precision :: line_grad,line_const integer, intent(in) :: datcomp,vmassm1orm2 integer :: i logical :: const_m1,const_m2 double precision :: interpol,mass1,mass2 double precision :: vmass,vmass_xmin,vmass_xmax,vmass_sep double precision :: z_below,z_above if(vmasslower.gt.vmasshigher)then stop 'problem in f_from_slices_t2 (1)' endif if(abs(m1_at_ref_point_1-m1_at_ref_point_2).lt.small)then const_m1=.True. else const_m1=.False. endif if(abs(m2_at_ref_point_1-m2_at_ref_point_2).lt.small)then const_m2=.True. else const_m2=.False. endif ! check if mass is within z range of table: if( .not. ( (z .ge. slices_t2(1)%z-small).and.(z .le. slices_t2(2)%z+small) ) )then !#1! written in convoluted way to get the NaNs f_t1%id = slices_t2(1)%id f_t1%deltax = slices_t2(1)%deltax if((slices_t2(1)%nx2.eq.1).or.(vmassm1orm2.eq.1))then if(const_m1)stop 'problem in f_from_slices_t2 (1a)' vmass_xmin = slices_t2(1)%xmin1 vmass_sep = slices_t2(1)%sep1 f_t1%sep = slices_t2(1)%sep1*sepmultfactor else if(const_m2)stop 'problem in f_from_slices_t2 (1b)' vmass_xmin = slices_t2(1)%xmin2 vmass_sep = slices_t2(1)%sep2 f_t1%sep = slices_t2(1)%sep2*sepmultfactor endif call fill_blank_ft1_dat(f_t1,f_t1%sep,vmasslower,vmasshigher,vmass_xmin,vmass_xmax,vmass_sep,valueoutsidetable) else !#1 z_below=slices_t2(1)%z z_above=slices_t2(2)%z if(abs(z_below-z).lt.small)then !z is the same as z_below !#2 call f_from_t2(slices_t2(1),m1_at_ref_point_1,m2_at_ref_point_1,m1_at_ref_point_2,m2_at_ref_point_2, & & vmassm1orm2,vmasslower,vmasshigher,sepmultfactor,1, & & f_t1,valueoutsidetable) elseif(abs(z_above-z).lt.small)then !z is the same as z_above !#2 call f_from_t2(slices_t2(2),m1_at_ref_point_1,m2_at_ref_point_1,m1_at_ref_point_2,m2_at_ref_point_2, & & vmassm1orm2,vmasslower,vmasshigher,sepmultfactor,1, & & f_t1,valueoutsidetable) else!#2 if(const_m1)then !line_grad is not needed !line_const is not needed else line_grad =(m2_at_ref_point_1-m2_at_ref_point_2)/(m1_at_ref_point_1-m1_at_ref_point_2) line_const=(m1_at_ref_point_1*m2_at_ref_point_2-m1_at_ref_point_2*m2_at_ref_point_1) & & /(m1_at_ref_point_1-m1_at_ref_point_2) endif f_t1%id = slices_t2(1)%id f_t1%deltax = slices_t2(1)%deltax if((slices_t2(1)%nx2.eq.1).or.(vmassm1orm2.eq.1))then vmass_xmin = slices_t2(1)%xmin1 vmass_xmax = slices_t2(1)%xmax1 vmass_sep = slices_t2(1)%sep1 f_t1%sep = slices_t2(1)%sep1*sepmultfactor else if(const_m2)stop 'problem in f_from_slices_t2 (3b)' vmass_xmin = slices_t2(1)%xmin2 vmass_xmax = slices_t2(1)%xmax2 vmass_sep = slices_t2(1)%sep2 f_t1%sep = slices_t2(1)%sep2*sepmultfactor endif call fill_blank_ft1_dat(f_t1,f_t1%sep,vmasslower,vmasshigher,vmass_xmin,vmass_xmax,vmass_sep,valueoutsidetable) do i=1,ubound(f_t1%dat,dim=1) vmass = dble(i-1)*f_t1%sep + f_t1%xmin if(slices_t2(1)%nx2.eq.1)then mass1 = vmass mass2 = slices_t2(1)%xmin2 else select case(vmassm1orm2) case(1) mass1 = vmass mass2 = mass1*line_grad+line_const case(2) mass2 = vmass if(const_m1)then mass1 = m1_at_ref_point_1 else mass1 = (mass2 - line_const)/line_grad endif case default stop 'problem in f_from_slices_t2 (4b)' end select endif if( vmass.lt.vmass_xmin-small )then f_t1%dat(i,1)=valueoutsidetable elseif( vmass.gt.vmass_xmax+small )then f_t1%dat(i,1)=valueoutsidetable elseif((slices_t2(1)%nx2.gt.1).and.( slices_t2(1)%needs_M2_gt_2M1 ).and.(2.0D0*mass1>mass2+small))then f_t1%dat(i,1)=valueoutsidetable elseif((slices_t2(1)%nx2.gt.1).and.(.not.(slices_t2(1)%needs_M2_gt_2M1)).and.(mass1>mass2+small))then f_t1%dat(i,1)=valueoutsidetable else call interpolate_slices_t2(mass1,mass2,z,slices_t2,datcomp,interpol) f_t1%dat(i,1)=interpol endif enddo endif !#2 endif !#1 end subroutine f_from_slices_t2 !****************************************************************** subroutine f_from_t3(t3,m1_at_ref_point_1,m2_at_ref_point_1,m1_at_ref_point_2,m2_at_ref_point_2,z, & & vmassm1orm2,vmasslower,vmasshigher,sepmultfactor,datcomp, & & f_t1,valueoutsidetable) !****************************************************************** ! fill the f_t1 array with the information from a t3 array at constant sf along a line ! m2 = line_grad*m1 + line_const ! do not forget to deallocate dat use S95tables_type3 use interpolate use usefulbits, only : small implicit none type(table3), intent(in) :: t3 type(table2) :: slices_t2(2) type(table1) :: f_t1 double precision, intent(in) :: m1_at_ref_point_1,m2_at_ref_point_1,m1_at_ref_point_2,m2_at_ref_point_2 double precision, intent(in) :: z,vmasslower,vmasshigher,valueoutsidetable double precision, intent(in) :: sepmultfactor integer, intent(in) :: datcomp,vmassm1orm2 integer :: a logical :: const_m1,const_m2 double precision :: vmass_xmin,vmass_xmax,vmass_sep integer :: ilow,c_zi(2),ftype_selection(1) double precision :: z_below,z_above if(vmasslower.gt.vmasshigher)then stop 'problem in f_from_t3 (1)' endif if(abs(m1_at_ref_point_1-m1_at_ref_point_2).lt.small)then const_m1=.True. else const_m1=.False. endif if(abs(m2_at_ref_point_1-m2_at_ref_point_2).lt.small)then const_m2=.True. else const_m2=.False. endif ! check if mass is within z range of table: if( .not. ( (z .ge. t3%zmin-small).and.(z .le. t3%zmax+small) ) )then !#1! written in convoluted way to get the NaNs f_t1%id = t3%id f_t1%deltax = t3%deltax if((t3%nx2.eq.1).or.(vmassm1orm2.eq.1))then if(const_m1)stop 'problem in f_from_t3 (1a)' vmass_xmin = t3%xmin1 vmass_sep = t3%sep1 f_t1%sep = t3%sep1*sepmultfactor else if(const_m2)stop 'problem in f_from_t3 (1b)' vmass_xmin = t3%xmin2 vmass_sep = t3%sep2 f_t1%sep = t3%sep2*sepmultfactor endif call fill_blank_ft1_dat(f_t1,f_t1%sep,vmasslower,vmasshigher,vmass_xmin,vmass_xmax,vmass_sep,valueoutsidetable) else !#1 ilow=int((z-t3%zmin)/t3%zsep)+1 z_below=dble(ilow-1)*t3%zsep+t3%zmin z_above=z_below+t3%zsep if(abs(z_below-z).lt.small)then !z is the same as z_below !#2 c_zi= ilow elseif(abs(z_above-z).lt.small)then !z is the same as z_above !#2 c_zi= ilow+1 else !#2 c_zi(1)= ilow c_zi(2)= ilow+1 endif !#2 ftype_selection(1)=datcomp call fill_slices_t2_from_slices_of_t3(t3,c_zi,ftype_selection,slices_t2) call f_from_slices_t2(slices_t2,m1_at_ref_point_1,m2_at_ref_point_1,m1_at_ref_point_2,m2_at_ref_point_2,z, & & vmassm1orm2,vmasslower,vmasshigher,sepmultfactor,datcomp, & & f_t1,valueoutsidetable) do a=1,2 deallocate(slices_t2(a)%dat) enddo endif !#1 end subroutine f_from_t3 !************************************************************ subroutine convolve_chisq_with_gaussian(t1,datcomp,sigma,mass,result) !************************************************************ ! intergrate exp(-t1%dat(xi,1)/2)*exp(-(massx-mass)^2/(2*sigma^2))/sqrt(2*pi*sigma^2) w.r.t. x ! between xlower and xhigher ! then do -2.0D0*log to get result ! negative data points are invalid. They are set to zero. use usefulbits, only : vsmall,vvsmall,pi !internal use interpolate use S95tables_type1 implicit none type(table1),intent(in) :: t1 integer,intent(in) :: datcomp double precision,intent(in) :: sigma,mass double precision,intent(out) :: result !-----------------------------------internal integer :: i,ilow,ihigh,j,divisions,n,ntot double precision :: runningtotal,massx,datvalue,newsep double precision,allocatable :: newdat(:) double precision :: big_number_instead_of_infinity double precision :: dati,datiplus1 !------------------------------------------- if((datcomp.lt.lbound(t1%dat,dim=2)).or.(datcomp.gt.ubound(t1%dat,dim=2)))then stop 'wrong datcomp inputted to subroutine convolve_with_gaussian' elseif(t1%nx.le.1)then stop 'wrong t1%nx inputted to subroutine convolve_with_gaussian (2)' elseif(sigma.le.vsmall)then stop 'wrong sigma inputted to subroutine convolve_with_gaussian' elseif(abs(t1%sep).le.vsmall)then stop 'wrong t1%sep inputted to subroutine convolve_with_gaussian' endif big_number_instead_of_infinity=1.0D5 divisions=5 !do i=1,t1%nx ! if(t1%dat(i,datcomp).ge.big_number_instead_of_infinity)t1%dat(i,datcomp)=1.0D20 !enddo n=0 if(minval(t1%dat(:,datcomp)).lt.1.0D4)then ilow = lbound(t1%dat,dim=1) ihigh = ubound(t1%dat,dim=1) if(ilow.eq.ihigh)stop 'problem in subroutine convolve_with_gaussian' newsep=t1%sep/dble(divisions) ntot=divisions*(ihigh-ilow)+1 allocate(newdat(ntot)) newdat=0.0D0 do i=ilow,ihigh dati=t1%dat(i,datcomp) if(dati.ge.0.0D0)then n=n+1 massx=dble(i-1)*t1%sep+t1%xmin datvalue=dati newdat(n)=exp(-datvalue/2.0D0) & & *exp(-(massx-mass)**2.0D0/(2.0D0*sigma**2.0D0))/sqrt(2.0D0*pi*sigma**2.0D0) if(i.lt.ihigh)then datiplus1=t1%dat(i+1,datcomp) if(datiplus1.ge.0.0D0)then do j=2,divisions-1 n=n+1 massx=dble(i-1)*t1%sep+t1%xmin + dble(j-1)*newsep !do a=1,ihigh ! write(*,*)a,dble(a-1)*t1%sep+t1%xmin ,t1%dat(a,datcomp) !enddo datvalue=dati +((datiplus1-dati)/t1%sep)*dble(j-1)*newsep if(datvalue.lt.0.0D0)then !these are invalid point or places outside range of table datvalue=0.0D0 endif newdat(n)=exp(-datvalue/2.0D0) & & *exp(-(massx-mass)**2.0D0/(2.0D0*sigma**2.0D0))/sqrt(2.0D0*pi*sigma**2.0D0) enddo else do j=2,divisions-1 n=n+1 enddo endif else !negative data points are invalid do j=2,divisions-1 n=n+1 enddo endif !massx=dble(i-1)*t1%sep+t1%xmin !newdat(i)=exp(-t1%dat(i,datcomp)/2.0D0) & ! & *exp(-(massx-mass)**2.0D0/(2.0D0*sigma**2.0D0))/sqrt(2.0D0*pi*sigma**2.0D0) else do j=1,divisions-1 n=n+1 enddo endif enddo !intergrate with trapezium rule runningtotal=0.5D0*(newdat(1)+newdat(ntot)) if((ntot).gt.1)then do n=2,ntot-1 runningtotal=runningtotal+newdat(n) enddo endif deallocate(newdat) if(abs(runningtotal).le.vvsmall)then result= big_number_instead_of_infinity else result= -2.0D0*log(runningtotal*newsep) endif if(result.gt.22.4D0)then !corresponds to clsb=1.0D-6, which is the lowest clsb that ppchi2 can take as input result= big_number_instead_of_infinity endif else result= big_number_instead_of_infinity endif end subroutine convolve_chisq_with_gaussian !************************************************************ function S95_t1_or_S95_t2_idfromelementnumber(ttype,tlist) !************************************************************ implicit none integer :: S95_t1_or_S95_t2_idfromelementnumber integer,intent(in) ::tlist integer,intent(in) ::ttype select case(ttype) case(1) S95_t1_or_S95_t2_idfromelementnumber=S95_t1(tlist)%id case(2) S95_t1_or_S95_t2_idfromelementnumber=S95_t2(tlist)%id case(9) S95_t1_or_S95_t2_idfromelementnumber=3316 case default stop 'wrong input to function S95_t1_or_S95_t2_idfromelementnumber' end select end function S95_t1_or_S95_t2_idfromelementnumber !************************************************************ function S95_t1_or_S95_t2_elementnumberfromid(ttype,id) !************************************************************ use S95tables_type1, only :t1elementnumberfromid use S95tables_type2, only :t2elementnumberfromid implicit none integer,intent(in) ::id integer,intent(in) ::ttype integer :: S95_t1_or_S95_t2_elementnumberfromid select case(ttype) case(1) S95_t1_or_S95_t2_elementnumberfromid= t1elementnumberfromid(S95_t1,id) case(2) S95_t1_or_S95_t2_elementnumberfromid= t2elementnumberfromid(S95_t2,id) case default stop 'problem with function S95_t1_or_S95_t2_elementnumberfromid' end select end function S95_t1_or_S95_t2_elementnumberfromid !************************************************************ subroutine deallocate_S95tables !************************************************************ implicit none !-----------------------------------internal integer x !------------------------------------------- do x=lbound(S95_t1,dim=1),ubound(S95_t1,dim=1) deallocate(S95_t1(x)%dat) enddo do x=lbound(S95_t2,dim=1),ubound(S95_t2,dim=1) deallocate(S95_t2(x)%dat) enddo deallocate(S95_t1) deallocate(S95_t2) call deallocate_Exptranges end subroutine deallocate_S95tables !*********************************************************** subroutine deallocate_Exptranges !*********************************************************** implicit none if(allocated(Exptrange_Mhmin_forSMXS)) deallocate(Exptrange_Mhmin_forSMXS) if(allocated(Exptrange_Mhmax_forSMXS)) deallocate(Exptrange_Mhmax_forSMXS) if(allocated(Exptrange_Mhmin_forSMdecays)) deallocate(Exptrange_Mhmin_forSMdecays) if(allocated(Exptrange_Mhmax_forSMdecays)) deallocate(Exptrange_Mhmax_forSMdecays) end subroutine deallocate_Exptranges !*********************************************************** end module S95tables !************************************************************ Index: trunk/HiggsBounds-5/theory_XS_SM_functions.F90 =================================================================== --- trunk/HiggsBounds-5/theory_XS_SM_functions.F90 (revision 600) +++ trunk/HiggsBounds-5/theory_XS_SM_functions.F90 (revision 601) @@ -1,3057 +1,3057 @@ ! This file is part of HiggsBounds ! ! ! XS_HW_SM,XS_HZ_SM,XS_gg_H_SM,XS_bb_H_SM,XS_vbf:_H_SM ! in units of fb ! functions are fitted to data ! downloaded from http://maltoni.home.cern.ch/maltoni/TeV4LHC/bbh-tev_ed.dat ! on Thursday 10th April 2008 ! data has range 100 to 300 GeV ! ! functions XS_tev_bg_Hb_SM,XS_tev_bg_Hb_c1_SM,XS_tev_bg_Hb_c2_SM were generated by Oliver Brein ! ! on Tuesday 22nd March 2011 ! functions XS_lhc7_gg_H_SM,XS_lhc7_HW_SM,XS_lhc7_HZ_SM,XS_lhc7_vbf_SM,XS_lhc7_ttH_SM were generated by Tim Stefaniak ! ! Summer 2012 ! Functions for 8 TeV added by OS ! !****************************************************** module theory_XS_SM_functions use interpolate use S95tables_type1 use usefulbits, only : div implicit none type(table1),allocatable :: XSSM(:) ! For the WH and ZH approximation from effective couplings: type(table1),allocatable :: VHcoeff(:) ! For the full ZH approximation: type(table1),allocatable :: ZHcoeff(:) ! index: Tev, LHC7, LHC8, LHC13 integer :: Ncollider = 4 ! this must be narrower than range of ! XS_bg_Hb_SM,XS_bg_Hb_c1_SM,XS_bg_Hb_c2_SM ([10:400]) ! XS_tev_gg_H_SM (currently [50:350]) ! theory_tevSfunctions (currently [50:400]) !have temporarily set tevXS_SM_functions_xmax to 361, even though this is !outside the range of XS_tev_gg_H_SM, because the very high Mh are only used for !tev%XS_Hb_c1_SM at the moment, but we need to be careful (we should calculate XS_tev_gg_H_SM for a bigger range !as soon as possible) ! double precision :: tevXS_SM_functions_xmin=60.0D0 ! double precision :: tevXS_SM_functions_xmax=361.0D0 ! ! double precision :: lhc7XS_SM_functions_xmin=79.0D0 ! double precision :: lhc7XS_SM_functions_xmax=1001.0D0 ! ! double precision :: lhc8XS_SM_functions_xmin=45.0D0 ! double precision :: lhc8XS_SM_functions_xmax=1120.0D0 ! NEW BOUNDARIES: double precision :: tevXS_SM_functions_xmin=60.0D0 double precision :: tevXS_SM_functions_xmax=361.0D0 double precision :: lhc7XS_SM_functions_xmin=10.0D0 double precision :: lhc7XS_SM_functions_xmax=3000.0D0 double precision :: lhc8XS_SM_functions_xmin=10.0D0 double precision :: lhc8XS_SM_functions_xmax=3000.0D0 double precision :: lhc13XS_SM_functions_xmin=10.0D0 double precision :: lhc13XS_SM_functions_xmax=3000.0D0 contains !files from OB (his calculations) !only change I made: ! end->end function #include "cs-ratios_sigma-bg-Hb/Tevatron.sigma_bg_Hb.h" #include "cs-ratios_sigma-bg-Hb/Tevatron.sigma_bg_Hb.ptmin15.etamax2.h" #include "cs-ratios_sigma-bg-Hb/Tevatron.sigma_bg_Hb.ptmin20.etamax2.5.h" #include "cs-ratios_sigma-bg-Hb/Tevatron.sigma_bg_Hb.ptmin15.etamax2.5.h" #include "cs-ratios_sigma-bg-Hb/Tevatron.sigma_bg_Hb.ptmin12.etamax5.h" ! NEW ROUTINES FOR HB-5 ! !****************************************************** subroutine setup_XSSM ! reads in the Standard Model Cross Sections from files, ! currently using the YR4 predictions !****************************************************** use store_pathname use usefulbits, only: file_id_common2 implicit none !------------------------------------internal integer :: x,xbeg,xend character(len=100),allocatable :: filename(:) character(LEN=pathname_length+150) :: fullfilename integer :: col,ios !-------------------------------------------- allocate(XSSM(12)) xbeg=lbound(XSSM,dim=1) xend=ubound(XSSM,dim=1) allocate(filename(xbeg:xend)) x=xbeg-1 ! NOTE: The %id placeholder is abused to specify the number of columns in the file x=x+1 XSSM(x)%xmin=10.0D0 XSSM(x)%xmax=3000.0D0 XSSM(x)%sep=5.0D0 XSSM(x)%id=4 filename(x)='YR4/BSM_XS_7_ggHVBFbbH.dat' x=x+1 XSSM(x)%xmin=10.0D0 XSSM(x)%xmax=2000.0D0 XSSM(x)%sep=5.0D0 XSSM(x)%id=3 filename(x)='YR4/BSM_XS_7_WHZH.dat' x=x+1 XSSM(x)%xmin=120.0D0 XSSM(x)%xmax=130.0D0 XSSM(x)%sep=0.1D0 XSSM(x)%id=9 ! filename(x)='YR4/SM_XS_7_all.dat' filename(x)='YR4/SM_XS_7_all_YR4update.dat' x=x+1 XSSM(x)%xmin=10.0D0 XSSM(x)%xmax=3000.0D0 XSSM(x)%sep=5.0D0 XSSM(x)%id=4 filename(x)='YR4/BSM_XS_8_ggHVBFbbH.dat' x=x+1 XSSM(x)%xmin=10.0D0 XSSM(x)%xmax=2000.0D0 XSSM(x)%sep=5.0D0 XSSM(x)%id=3 filename(x)='YR4/BSM_XS_8_WHZH.dat' x=x+1 XSSM(x)%xmin=10.0D0 XSSM(x)%xmax=3000.0D0 XSSM(x)%sep=5.0D0 XSSM(x)%id=2 filename(x)='YR4/BSM_XS_8_ttH.dat' x=x+1 XSSM(x)%xmin=120.0D0 XSSM(x)%xmax=130.0D0 XSSM(x)%sep=0.1D0 XSSM(x)%id=9 ! filename(x)='YR4/SM_XS_8_all.dat' filename(x)='YR4/SM_XS_8_all_YR4update.dat' x=x+1 XSSM(x)%xmin=10.0D0 XSSM(x)%xmax=3000.0D0 XSSM(x)%sep=5.0D0 XSSM(x)%id=4 -! filename(x)='YR4/BSM_XS_13_ggHVBFbbH.dat' - filename(x)='YR4/BSM_XS_13_ggHVBFbbH_YR4update.dat' + filename(x)='YR4/BSM_XS_13_ggHVBFbbH.dat' +! filename(x)='YR4/BSM_XS_13_ggHVBFbbH_YR4update.dat' x=x+1 XSSM(x)%xmin=10.0D0 XSSM(x)%xmax=2000.0D0 XSSM(x)%sep=5.0D0 XSSM(x)%id=3 filename(x)='YR4/BSM_XS_13_WHZH.dat' x=x+1 XSSM(x)%xmin=10.0D0 XSSM(x)%xmax=3000.0D0 XSSM(x)%sep=5.0D0 XSSM(x)%id=2 filename(x)='YR4/BSM_XS_13_ttH.dat' x=x+1 XSSM(x)%xmin=10.0D0 XSSM(x)%xmax=3000.0D0 XSSM(x)%sep=5.0D0 XSSM(x)%id=3 filename(x)='YR4/BSM_XS_13_tH.dat' x=x+1 XSSM(x)%xmin=120.0D0 XSSM(x)%xmax=130.0D0 XSSM(x)%sep=0.1D0 XSSM(x)%id=9 ! filename(x)='YR4/SM_XS_13_all.dat' filename(x)='YR4/SM_XS_13_all_YR4update.dat' ! checks we've filled the whole array if(x.ne.xend)then stop 'error in setup_XSSM (a)' endif ! do loop to read in S95 tables do x=xbeg,xend XSSM(x)%nx=nint((XSSM(x)%xmax-XSSM(x)%xmin)/XSSM(x)%sep)+1 allocate(XSSM(x)%dat(XSSM(x)%nx,XSSM(x)%id-1)) enddo open(file_id_common2,file = trim(adjustl(pathname))//'Theory_tables/' // & & 'XSSM.binary',form='unformatted') read(file_id_common2,iostat=ios)XSSM(xbeg)%dat if(ios.eq.0)then do x=xbeg+1,xend read(file_id_common2)XSSM(x)%dat enddo else rewind(file_id_common2) do x=xbeg,xend fullfilename=trim(adjustl(pathname))//'Theory_tables/' & & //trim(filename(x)) call read_tabletype1(XSSM(x),0,XSSM(x)%id,fullfilename) #ifndef WEBVERSION write(file_id_common2)XSSM(x)%dat #endif enddo endif close(file_id_common2) deallocate(filename) !**************************************************** ! Read in the WH/ZH coefficients for the effective coupling approximation !**************************************************** allocate(VHcoeff(20)) xbeg=lbound(VHcoeff,dim=1) xend=ubound(VHcoeff,dim=1) allocate(filename(xbeg:xend)) x=xbeg-1 ! NOTE: The %id placeholder is abused to specify the number of columns in the file ! Tevatron x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=1850.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/Teva__coefficients_WH_NOEW.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=1850.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/Teva__coefficients_WH.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=1850.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/Teva__coefficients_ZH_NOEW.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=1850.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/Teva__coefficients_ZH.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=1850.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/Teva__coefficients_ZH_CPodd.dat' ! LHC7 x=x+1 VHcoeff(x)%xmin=2.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC7__coefficients_WH_NOEW.dat' x=x+1 VHcoeff(x)%xmin=2.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC7__coefficients_WH.dat' x=x+1 VHcoeff(x)%xmin=2.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC7__coefficients_ZH_NOEW.dat' x=x+1 VHcoeff(x)%xmin=2.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC7__coefficients_ZH.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=1850.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC7__coefficients_ZH_CPodd.dat' ! LHC8 x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC8__coefficients_WH_NOEW.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC8__coefficients_WH.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC8__coefficients_ZH_NOEW.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC8__coefficients_ZH.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=1850.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC8__coefficients_ZH_CPodd.dat' ! LHC13 x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC13__coefficients_WH_NOEW.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC13__coefficients_WH.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC13__coefficients_ZH_NOEW.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=2950.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC13__coefficients_ZH.dat' x=x+1 VHcoeff(x)%xmin=1.0D0 VHcoeff(x)%xmax=1850.0D0 VHcoeff(x)%sep=1.0D0 VHcoeff(x)%id=8 filename(x)='VH_coefficients/LHC8__coefficients_ZH_CPodd.dat' ! checks we've filled the whole array if(x.ne.xend)then stop 'error in setup_XSSM (b)' endif ! do loop to read in S95 tables do x=xbeg,xend VHcoeff(x)%nx=nint((VHcoeff(x)%xmax-VHcoeff(x)%xmin)/VHcoeff(x)%sep)+1 allocate(VHcoeff(x)%dat(VHcoeff(x)%nx,VHcoeff(x)%id-1)) enddo open(file_id_common2,file = trim(adjustl(pathname))//'Theory_tables/' // & & 'VHcoeff.binary',form='unformatted') read(file_id_common2,iostat=ios)VHcoeff(xbeg)%dat if(ios.eq.0)then do x=xbeg+1,xend read(file_id_common2)VHcoeff(x)%dat enddo else rewind(file_id_common2) do x=xbeg,xend fullfilename=trim(adjustl(pathname))//'Theory_tables/' & & //trim(filename(x)) ! write(*,*) "Reading in "//fullfilename call read_tabletype1(VHcoeff(x),1,VHcoeff(x)%id,fullfilename) #ifndef WEBVERSION write(file_id_common2)VHcoeff(x)%dat #endif enddo endif close(file_id_common2) deallocate(filename) !**************************************************** ! Read in the full ZH coefficients for the effective coupling approximation ! (TS/DD 2018-08-23) !**************************************************** allocate(ZHcoeff(Ncollider)) xbeg=lbound(ZHcoeff,dim=1) xend=ubound(ZHcoeff,dim=1) allocate(filename(xbeg:xend)) x=xbeg-1 ! NOTE: The %id placeholder is abused to specify the number of columns in the file x=x+1 ZHcoeff(x)%xmin=1.0D0 ZHcoeff(x)%xmax=1000.0D0 ZHcoeff(x)%sep=1.0D0 ZHcoeff(x)%id=133 filename(x)='VH_coefficients/Teva_fulltable.dat' x=x+1 ZHcoeff(x)%xmin=1.0D0 ZHcoeff(x)%xmax=4999.0D0 ZHcoeff(x)%sep=1.0D0 ZHcoeff(x)%id=133 filename(x)='VH_coefficients/LHC7_fulltable.dat' x=x+1 ZHcoeff(x)%xmin=1.0D0 ZHcoeff(x)%xmax=4999.0D0 ZHcoeff(x)%sep=1.0D0 ZHcoeff(x)%id=133 filename(x)='VH_coefficients/LHC8_fulltable.dat' x=x+1 ZHcoeff(x)%xmin=1.0D0 ZHcoeff(x)%xmax=4999.0D0 ZHcoeff(x)%sep=1.0D0 ZHcoeff(x)%id=133 filename(x)='VH_coefficients/LHC13_fulltable.dat' ! checks we've filled the whole array if(x.ne.xend)then stop 'error in setup_XSSM (c)' endif ! do loop to read in S95 tables do x=xbeg,xend ZHcoeff(x)%nx=nint((ZHcoeff(x)%xmax-ZHcoeff(x)%xmin)/ZHcoeff(x)%sep)+1 allocate(ZHcoeff(x)%dat(ZHcoeff(x)%nx,ZHcoeff(x)%id-1)) enddo open(file_id_common2,file = trim(adjustl(pathname))//'Theory_tables/' // & & 'ZHcoeff.binary',form='unformatted') read(file_id_common2,iostat=ios) ZHcoeff(xbeg)%dat if(ios.eq.0)then do x=xbeg+1,xend read(file_id_common2) ZHcoeff(x)%dat enddo else rewind(file_id_common2) do x=xbeg,xend fullfilename=trim(adjustl(pathname))//'Theory_tables/' & & //trim(filename(x)) ! write(*,*) "Reading in "//fullfilename call read_tabletype1(ZHcoeff(x),1,ZHcoeff(x)%id,fullfilename) #ifndef WEBVERSION write(file_id_common2)ZHcoeff(x)%dat #endif enddo endif close(file_id_common2) deallocate(filename) ! ----------------------- end subroutine setup_XSSM !************************************************************ subroutine deallocate_XSSM !************************************************************ implicit none !-----------------------------------internal integer x !------------------------------------------- do x=lbound(XSSM,dim=1),ubound(XSSM,dim=1) deallocate(XSSM(x)%dat) enddo deallocate(XSSM) do x=lbound(VHcoeff,dim=1),ubound(VHcoeff,dim=1) deallocate(VHcoeff(x)%dat) enddo deallocate(VHcoeff) do x=lbound(ZHcoeff,dim=1),ubound(ZHcoeff,dim=1) deallocate(ZHcoeff(x)%dat) enddo deallocate(ZHcoeff) end subroutine deallocate_XSSM !************************************************************ !****************************************************** ! New coefficient functions for HB-5 for effective coupling ! approximation of WH, ZH production. !****************************************************** function XS_WHcoeff(x,collider,coeff_i,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x integer, intent(in) :: coeff_i character(LEN=5), intent(in) :: collider double precision :: interpol double precision :: XS_WHcoeff logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue integer :: iwEW, iwoEW call testXSSM(x) select case(trim(adjustl(collider))) case("TEV") iwoEW = 1 iwEW = 2 case("LHC7") iwoEW = 6 iwEW = 7 case("LHC8") iwoEW = 11 iwEW = 12 case("LHC13") iwoEW = 16 iwEW = 17 case default stop 'wrong input for collider to subroutine XS_WHcoeff' end select call interpolate_tabletype1(x,VHcoeff(iwoEW),coeff_i,interpol,.True.) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,VHcoeff(iwEW),coeff_i,interpol,.True.) endif endif ! else ! interpol=badvalue ! endif XS_WHcoeff=interpol end function XS_WHcoeff function WH_nnlo(x,collider,ghw,ght,ghb,strict,EWcorr) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghw,ght,ghb character(LEN=5), intent(in) :: collider logical,optional :: strict logical,optional :: EWcorr double precision :: WH_nnlo WH_nnlo = XS_WHcoeff(x,collider,1,strict, EWcorr) * ght**2.0D0 + & & XS_WHcoeff(x,collider,2,strict, EWcorr) * ghb**2.0D0 + & & XS_WHcoeff(x,collider,3,strict, EWcorr) * ghw**2.0D0 + & & XS_WHcoeff(x,collider,4,strict, EWcorr) * ght * ghw + & & XS_WHcoeff(x,collider,5,strict, EWcorr) * ghb * ghw + & & XS_WHcoeff(x,collider,6,strict, EWcorr) * ght * ghb end function WH_nnlo function WH_nnlo_SM(x,collider,strict,EWcorr) implicit none double precision, intent(in) :: x character(LEN=5), intent(in) :: collider logical,optional :: strict logical,optional :: EWcorr double precision :: WH_nnlo_SM WH_nnlo_SM = XS_WHcoeff(x,collider,7,strict,EWcorr) end function WH_nnlo_SM !****************************************************** function XS_ZHcoeff(x,collider,coeff_i,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x integer, intent(in) :: coeff_i character(LEN=5), intent(in) :: collider double precision :: interpol double precision :: XS_ZHcoeff logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue integer :: iwEW, iwoEW call testXSSM(x) select case(trim(adjustl(collider))) case("TEV") iwoEW = 3 iwEW = 4 case("LHC7") iwoEW = 8 iwEW = 9 case("LHC8") iwoEW = 13 iwEW = 14 case("LHC13") iwoEW = 18 iwEW = 19 case default stop 'wrong input for collider to subroutine XS_ZHcoeff' end select call interpolate_tabletype1(x,VHcoeff(iwoEW),coeff_i,interpol,.True.) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,VHcoeff(iwEW),coeff_i,interpol,.True.) endif endif XS_ZHcoeff=interpol end function XS_ZHcoeff !****************************************************** function XS_ZHcoeff_CPodd(x,collider,coeff_i,strict) !****************************************************** implicit none double precision, intent(in) :: x integer, intent(in) :: coeff_i character(LEN=5), intent(in) :: collider double precision :: interpol double precision :: XS_ZHcoeff_CPodd logical,optional :: strict logical :: rangeok double precision :: func,badvalue integer :: i call testXSSM(x) select case(trim(adjustl(collider))) case("TEV") i = 5 case("LHC7") i = 10 case("LHC8") i = 15 case("LHC13") i = 20 case default stop 'wrong input for collider to subroutine XS_ZHcoeff_CPodd' end select call interpolate_tabletype1(x,VHcoeff(i),coeff_i,interpol,.True.) XS_ZHcoeff_CPodd=interpol end function XS_ZHcoeff_CPodd !****************************************************** function ZHcoeff_func(x,collider,coeff_i,strict)!,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x integer, intent(in) :: coeff_i character(LEN=5), intent(in) :: collider double precision :: interpol double precision :: ZHcoeff_func logical,optional :: strict ! logical,optional :: EWcorr ! logical :: rangeok ! double precision :: func,badvalue integer :: i! wEW, iwoEW call testXSSM(x) select case(trim(adjustl(collider))) case("TEV") i=1 case("LHC7") i=2 case("LHC8") i=3 case("LHC13") i=4 case default stop 'wrong input for collider to subroutine XS_ZHcoeff_full' end select ! as long as only LHC13 is implemented: ! i = 1 call interpolate_tabletype1(x,ZHcoeff(i),coeff_i,interpol,.True.) ! if(present(EWcorr))then ! if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then ! call interpolate_tabletype1(x,VHcoeff(iwEW),coeff_i,interpol,.True.) ! endif ! endif ZHcoeff_func=interpol end function ZHcoeff_func !****************************************************** ! Internal functions to obtain the ZH cross section !****************************************************** !***********************<<<>>>>**************** function ZH_cp0_nlo(x,collider,ghz,ght,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nlo ZH_cp0_nlo= ghz**2.0D0 * ZHcoeff_func(x,collider,7,strict) + & & ght**2.0D0 * ZHcoeff_func(x,collider,1,strict) + & & ght*ghz * ZHcoeff_func(x,collider,9,strict) + & & ght*ghb * ZHcoeff_func(x,collider,5,strict) + & & ghb**2.0D0 * ZHcoeff_func(x,collider,3,strict) + & & ghb*ghz * ZHcoeff_func(x,collider,11,strict) ZH_cp0_nlo = ZH_cp0_nlo/1000.0D0 ! convert from fb to pb end function ZH_cp0_nlo function ZH_cp0_nlo_gg(x,collider,ghz,ght,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nlo_gg ZH_cp0_nlo_gg= ghz**2.0D0 * ZHcoeff_func(x,collider,37,strict) + & & ght**2.0D0 * ZHcoeff_func(x,collider,31,strict) + & & ght*ghz * ZHcoeff_func(x,collider,39,strict) + & & ght*ghb * ZHcoeff_func(x,collider,35,strict) + & & ghb**2.0D0 * ZHcoeff_func(x,collider,33,strict) + & & ghb*ghz * ZHcoeff_func(x,collider,41,strict) ZH_cp0_nlo_gg = ZH_cp0_nlo_gg/1000.0D0 ! convert from fb to pb end function ZH_cp0_nlo_gg function ZH_cp0_nlo_qq(x,collider,ghz,ght,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nlo_qq ZH_cp0_nlo_qq= ghz**2.0D0 * ZHcoeff_func(x,collider,67,strict) + & & ght**2.0D0 * ZHcoeff_func(x,collider,61,strict) + & & ght*ghz * ZHcoeff_func(x,collider,69,strict) + & & ght*ghb * ZHcoeff_func(x,collider,65,strict) + & & ghb**2.0D0 * ZHcoeff_func(x,collider,63,strict) + & & ghb*ghz * ZHcoeff_func(x,collider,71,strict) ZH_cp0_nlo_qq = ZH_cp0_nlo_qq/1000.0D0 ! convert from fb to pb end function ZH_cp0_nlo_qq function ZH_cp0_nlo_bb(x,collider,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nlo_bb ZH_cp0_nlo_bb= ghb**2.0D0 * ZHcoeff_func(x,collider,91,strict) ZH_cp0_nlo_bb = ZH_cp0_nlo_bb/1000.0D0 ! convert from fb to pb end function ZH_cp0_nlo_bb function ZH_cp0_nlo_ggqqbb(x,collider,ghz,ght,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nlo_ggqqbb ZH_cp0_nlo_ggqqbb = ZH_cp0_nlo_gg(x,collider,ghz,ght,ghb,strict) + & & ZH_cp0_nlo_qq(x,collider,ghz,ght,ghb,strict) + & & ZH_cp0_nlo_bb(x,collider,ghb,strict) end function ZH_cp0_nlo_ggqqbb function ZH_cp0_nnlo(x,collider,ghz,ght,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nnlo ZH_cp0_nnlo= ghz**2.0D0 * ZHcoeff_func(x,collider,99,strict) + & & ght**2.0D0 * ZHcoeff_func(x,collider,95,strict) + & & ght*ghz * ZHcoeff_func(x,collider,101,strict) + & & ght*ghb * ZHcoeff_func(x,collider,105,strict) + & & ghb**2.0D0 * ZHcoeff_func(x,collider,97,strict) + & & ghb*ghz * ZHcoeff_func(x,collider,103,strict) ZH_cp0_nnlo = ZH_cp0_nnlo/1000.0D0 ! convert from fb to pb end function ZH_cp0_nnlo function ZH_cp0_nnlo_gg(x,collider,ghz,ght,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nnlo_gg ZH_cp0_nnlo_gg= ghz**2.0D0 * ZHcoeff_func(x,collider,111,strict) + & & ght**2.0D0 * ZHcoeff_func(x,collider,107,strict) + & & ght*ghz * ZHcoeff_func(x,collider,113,strict) + & & ght*ghb * ZHcoeff_func(x,collider,117,strict) + & & ghb**2.0D0 * ZHcoeff_func(x,collider,109,strict) + & & ghb*ghz * ZHcoeff_func(x,collider,115,strict) ZH_cp0_nnlo_gg = ZH_cp0_nnlo_gg/1000.0D0 ! convert from fb to pb end function ZH_cp0_nnlo_gg function ZH_cp0_nnlo_qq(x,collider,ghz,ght,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nnlo_qq ZH_cp0_nnlo_qq= ghz**2.0D0 * ZHcoeff_func(x,collider,123,strict) + & & ght**2.0D0 * ZHcoeff_func(x,collider,119,strict) + & & ght*ghz * ZHcoeff_func(x,collider,125,strict) + & & ght*ghb * ZHcoeff_func(x,collider,129,strict) + & & ghb**2.0D0 * ZHcoeff_func(x,collider,121,strict) + & & ghb*ghz * ZHcoeff_func(x,collider,127,strict) ZH_cp0_nnlo_qq = ZH_cp0_nnlo_qq/1000.0D0 ! convert from fb to pb end function ZH_cp0_nnlo_qq function ZH_cp0_nnlo_bb(x,collider,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nnlo_bb ZH_cp0_nnlo_bb= ghb**2.0D0 * ZHcoeff_func(x,collider,131,strict) ZH_cp0_nnlo_bb = ZH_cp0_nnlo_bb/1000.0D0 ! convert from fb to pb end function ZH_cp0_nnlo_bb function ZH_cp0_nnlo_ggqqbb(x,collider,ghz,ght,ghb,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cp0_nnlo_ggqqbb ZH_cp0_nnlo_ggqqbb = ZH_cp0_nnlo_gg(x,collider,ghz,ght,ghb,strict) + & & ZH_cp0_nnlo_qq(x,collider,ghz,ght,ghb,strict) + & & ZH_cp0_nnlo_bb(x,collider,ghb,strict) end function ZH_cp0_nnlo_ggqqbb function ZH_cpmix_nlo(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nlo ZH_cpmix_nlo= ghz**2.0D0 * ZHcoeff_func(x,collider,7,strict) + & & ghz*ght * ZHcoeff_func(x,collider,9,strict) + & & ghz*ghb * ZHcoeff_func(x,collider,11,strict) + & & gat**2.0D0 * ZHcoeff_func(x,collider,13,strict) + & & gat*ghz * ZHcoeff_func(x,collider,19,strict) + & & gat*ght * ZHcoeff_func(x,collider,15,strict) + & & gat*ghb * ZHcoeff_func(x,collider,17,strict) + & & ght**2.0D0 * ZHcoeff_func(x,collider,1,strict) + & & ght*ghb * ZHcoeff_func(x,collider,5,strict) + & & gab**2.0D0 * ZHcoeff_func(x,collider,21,strict) + & & gab*ghz * ZHcoeff_func(x,collider,27,strict) + & & gab*gat * ZHcoeff_func(x,collider,29,strict) + & & gab*ght * ZHcoeff_func(x,collider,23,strict) + & & gab*ghb * ZHcoeff_func(x,collider,25,strict) + & & ghb**2.0D0 * ZHcoeff_func(x,collider,3,strict) ZH_cpmix_nlo = ZH_cpmix_nlo/1000.0D0 ! convert from fb to pb end function ZH_cpmix_nlo function ZH_cpmix_nlo_gg(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nlo_gg ZH_cpmix_nlo_gg= ghz**2.0D0 * ZHcoeff_func(x,collider,37,strict) + & & ghz*ght * ZHcoeff_func(x,collider,39,strict) + & & ghz*ghb * ZHcoeff_func(x,collider,41,strict) + & & gat**2.0D0 * ZHcoeff_func(x,collider,43,strict) + & & gat*ghz * ZHcoeff_func(x,collider,49,strict) + & & gat*ght * ZHcoeff_func(x,collider,45,strict) + & & gat*ghb * ZHcoeff_func(x,collider,47,strict) + & & ght**2.0D0 * ZHcoeff_func(x,collider,31,strict) + & & ght*ghb * ZHcoeff_func(x,collider,35,strict) + & & gab**2.0D0 * ZHcoeff_func(x,collider,51,strict) + & & gab*ghz * ZHcoeff_func(x,collider,57,strict) + & & gab*gat * ZHcoeff_func(x,collider,59,strict) + & & gab*ght * ZHcoeff_func(x,collider,53,strict) + & & gab*ghb * ZHcoeff_func(x,collider,55,strict) + & & ghb**2.0D0 * ZHcoeff_func(x,collider,33,strict) ZH_cpmix_nlo_gg = ZH_cpmix_nlo_gg/1000.0D0 ! convert from fb to pb end function ZH_cpmix_nlo_gg function ZH_cpmix_nlo_qq(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nlo_qq ZH_cpmix_nlo_qq= ghz**2.0D0 * ZHcoeff_func(x,collider,67,strict) + & & ghz*ght * ZHcoeff_func(x,collider,69,strict) + & & ghz*ghb * ZHcoeff_func(x,collider,71,strict) + & & gat**2.0D0 * ZHcoeff_func(x,collider,73,strict) + & & gat*ghz * ZHcoeff_func(x,collider,79,strict) + & & gat*ght * ZHcoeff_func(x,collider,75,strict) + & & gat*ghb * ZHcoeff_func(x,collider,77,strict) + & & ght**2.0D0 * ZHcoeff_func(x,collider,61,strict) + & & ght*ghb * ZHcoeff_func(x,collider,65,strict) + & & gab**2.0D0 * ZHcoeff_func(x,collider,81,strict) + & & gab*ghz * ZHcoeff_func(x,collider,87,strict) + & & gab*gat * ZHcoeff_func(x,collider,89,strict) + & & gab*ght * ZHcoeff_func(x,collider,83,strict) + & & gab*ghb * ZHcoeff_func(x,collider,85,strict) + & & ghb**2.0D0 * ZHcoeff_func(x,collider,63,strict) ZH_cpmix_nlo_qq = ZH_cpmix_nlo_qq/1000.0D0 ! convert from fb to pb end function ZH_cpmix_nlo_qq function ZH_cpmix_nlo_bb(x,collider,ghb,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghb,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nlo_bb ZH_cpmix_nlo_bb= (ghb**2.0D0+gab**2.0D0) * ZHcoeff_func(x,collider,91,strict) ZH_cpmix_nlo_bb = ZH_cpmix_nlo_bb/1000.0D0 ! convert from fb to pb end function ZH_cpmix_nlo_bb function ZH_cpmix_nlo_ggqqbb(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nlo_ggqqbb ZH_cpmix_nlo_ggqqbb = ZH_cpmix_nlo_gg(x,collider,ghz,ght,ghb,gat,gab,strict) + & & ZH_cpmix_nlo_qq(x,collider,ghz,ght,ghb,gat,gab,strict) + & & ZH_cpmix_nlo_bb(x,collider,ghb,gab,strict) end function ZH_cpmix_nlo_ggqqbb function ZH_cpmix_nnlo_qq(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nnlo_qq if((ghz.eq.0.0D0).and.(ght.eq.0.0D0).and.(ghb.eq.0.0D0))then ZH_cpmix_nnlo_qq = ZH_cpmix_nlo_qq(x,collider,ghz,ght,ghb,gat,gab,strict) * & div(ZH_cp0_nnlo_qq(x,collider,1.0D0,1.0D0,1.0D0,strict), & ZH_cp0_nlo_qq(x,collider,1.0D0,1.0D0,1.0D0,strict),1.0D0, 0.0D0) else ZH_cpmix_nnlo_qq = ZH_cpmix_nlo_qq(x,collider,ghz,ght,ghb,gat,gab,strict) * & div(ZH_cp0_nnlo_qq(x,collider,ghz,ght,ghb,strict), & ZH_cp0_nlo_qq(x,collider,ghz,ght,ghb,strict),1.0D0, 0.0D0) endif end function ZH_cpmix_nnlo_qq function ZH_cpmix_nnlo_bb(x,collider,ghb,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghb,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nnlo_bb if((ghb.eq.0.0D0))then ZH_cpmix_nnlo_bb = ZH_cpmix_nlo_bb(x,collider,ghb,gab,strict) * & div(ZH_cp0_nnlo_bb(x,collider,1.0D0,strict), & ZH_cp0_nlo_bb(x,collider,1.0D0,strict),1.0D0, 0.0D0) else ZH_cpmix_nnlo_bb = ZH_cpmix_nlo_bb(x,collider,ghb,gab,strict) * & div(ZH_cp0_nnlo_bb(x,collider,ghb,strict), & ZH_cp0_nlo_bb(x,collider,ghb,strict),1.0D0, 0.0D0) endif end function ZH_cpmix_nnlo_bb function ZH_cpmix_nnlo_gg(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nnlo_gg if((ghz.eq.0.0D0).and.(ght.eq.0.0D0).and.(ghb.eq.0.0D0))then ZH_cpmix_nnlo_gg = ZH_cpmix_nlo_gg(x,collider,ghz,ght,ghb,gat,gab,strict) * & div(ZH_cp0_nnlo_gg(x,collider,1.0D0,1.0D0,1.0D0,strict), & ZH_cp0_nlo_gg(x,collider,1.0D0,1.0D0,1.0D0,strict),1.0D0, 0.0D0) else ZH_cpmix_nnlo_gg = ZH_cpmix_nlo_gg(x,collider,ghz,ght,ghb,gat,gab,strict) * & div(ZH_cp0_nnlo_gg(x,collider,ghz,ght,ghb,strict), & ZH_cp0_nlo_gg(x,collider,ghz,ght,ghb,strict),1.0D0, 0.0D0) endif end function ZH_cpmix_nnlo_gg function ZH_cpmix_nnlo(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nnlo if((ghz.eq.0.0D0).and.(ght.eq.0.0D0).and.(ghb.eq.0.0D0))then ZH_cpmix_nnlo = ZH_cpmix_nlo(x,collider,ghz,ght,ghb,gat,gab,strict) * & div(ZH_cp0_nnlo(x,collider,1.0D0,1.0D0,1.0D0,strict), & ZH_cp0_nlo(x,collider,1.0D0,1.0D0,1.0D0,strict),1.0D0, 0.0D0) else ZH_cpmix_nnlo = ZH_cpmix_nlo(x,collider,ghz,ght,ghb,gat,gab,strict) * & div(ZH_cp0_nnlo(x,collider,ghz,ght,ghb,strict), & ZH_cp0_nlo(x,collider,ghz,ght,ghb,strict),1.0D0, 0.0D0) endif end function ZH_cpmix_nnlo function ZH_cpmix_nnlo_ggqqbb(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nnlo_ggqqbb ZH_cpmix_nnlo_ggqqbb = ZH_cpmix_nnlo_qq(x,collider,ghz,ght,ghb,gat,gab,strict) + & & ZH_cpmix_nnlo_bb(x,collider,ghb,gab,strict) + & & ZH_cpmix_nnlo_gg(x,collider,ghz,ght,ghb,gat,gab,strict) end function ZH_cpmix_nnlo_ggqqbb function ZH_cpmix_nnlo_qqbb(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: ZH_cpmix_nnlo_qqbb ZH_cpmix_nnlo_qqbb = ZH_cpmix_nnlo_qq(x,collider,ghz,ght,ghb,gat,gab,strict) + & & ZH_cpmix_nnlo_bb(x,collider,ghb,gab,strict) end function ZH_cpmix_nnlo_qqbb !***********************<<<>>>>**************** subroutine check_kfactor_ZH(x,collider,ghz,ght,ghb,gat,gab,strict) implicit none double precision, intent(in) :: x double precision, intent(in) :: ghz,ght,ghb,gat,gab character(LEN=5), intent(in) :: collider logical,optional :: strict double precision :: NLOsum, NLOincl NLOsum = ZH_cpmix_nlo_ggqqbb(x,collider,ghz,ght,ghb,gat,gab,strict) NLOincl = ZH_cpmix_nlo(x,collider,ghz,ght,ghb,gat,gab,strict) ! write(*,*) NLOsum, NLOincl if((abs(NLOsum - NLOincl)/NLOincl).gt.1E-04) then !-- usually values of 1E-08 or less! write(*,*) "WARNING for ZH XS approximation: NNLO/NLO k-factor may not be accurate: ",& & abs(NLOsum - NLOincl)/NLOincl endif end subroutine check_kfactor_ZH !****************************************************** !*** *** !*** LHC 7 TeV *** !*** *** !****************************************************** function XS_lhc7_gg_H_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc7_gg_H_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC7 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(1),1,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(3),1,interpol) endif endif else interpol=badvalue endif XS_lhc7_gg_H_SM=interpol end function XS_lhc7_gg_H_SM !****************************************************** function XS_lhc7_bb_H_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc7_bb_H_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC7 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(1),3,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(3),6,interpol) endif endif else interpol=badvalue endif XS_lhc7_bb_H_SM=interpol end function XS_lhc7_bb_H_SM !****************************************************** function XS_lhc7_vbf_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc7_vbf_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC7 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(1),2,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(3),2,interpol) endif endif else interpol=badvalue endif XS_lhc7_vbf_SM=interpol end function XS_lhc7_vbf_SM !****************************************************** function XS_lhc7_HW_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc7_HW_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) badvalue=0.0D0 if(present(strict))then if(strict)then badvalue=-1.0D0 endif endif rangeok=.False. if(x.ge.10.0D0.and.x.le.2000) then rangeok=.True. endif ! call check_range('LHC7 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(2),1,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(3),3,interpol) endif endif else interpol=badvalue endif XS_lhc7_HW_SM=interpol end function XS_lhc7_HW_SM !****************************************************** function XS_lhc7_HZ_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc7_HZ_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) badvalue=0.0D0 if(present(strict))then if(strict)then badvalue=-1.0D0 endif endif rangeok=.False. if(x.ge.10.0D0.and.x.le.2000) then rangeok=.True. endif ! call check_range('LHC7 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(2),2,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(3),4,interpol) endif endif else interpol=badvalue endif XS_lhc7_HZ_SM=interpol end function XS_lhc7_HZ_SM !****************************************************** function XS_lhc7_ttH_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc7_ttH_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC7 ',x,rangeok,badvalue,strict) if(rangeok)then interpol = XS_lhc7_ttH_SM_func(x,strict) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(3),5,interpol) endif endif else interpol=badvalue endif XS_lhc7_ttH_SM=interpol end function XS_lhc7_ttH_SM !****************************************************** function XS_lhc7_tH_tchan_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc7_tH_tchan_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC7 ',x,rangeok,badvalue,strict) if(rangeok)then interpol=badvalue if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(3),7,interpol) endif endif else interpol=badvalue endif XS_lhc7_tH_tchan_SM=interpol end function XS_lhc7_tH_tchan_SM !****************************************************** function XS_lhc7_tH_schan_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc7_tH_schan_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC7 ',x,rangeok,badvalue,strict) if(rangeok)then interpol=badvalue if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(3),8,interpol) endif endif else interpol=badvalue endif XS_lhc7_tH_schan_SM=interpol end function XS_lhc7_tH_schan_SM !****************************************************** !*** *** !*** LHC 8 TeV *** !*** *** !****************************************************** function XS_lhc8_gg_H_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc8_gg_H_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC8 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(4),1,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(7),1,interpol) endif endif else interpol=badvalue endif XS_lhc8_gg_H_SM=interpol end function XS_lhc8_gg_H_SM !****************************************************** function XS_lhc8_bb_H_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc8_bb_H_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC8 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(4),3,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(7),6,interpol) endif endif else interpol=badvalue endif XS_lhc8_bb_H_SM=interpol end function XS_lhc8_bb_H_SM !****************************************************** function XS_lhc8_vbf_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc8_vbf_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC8 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(4),2,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(7),2,interpol) endif endif else interpol=badvalue endif XS_lhc8_vbf_SM=interpol end function XS_lhc8_vbf_SM !****************************************************** function XS_lhc8_HW_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc8_HW_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) badvalue=0.0D0 if(present(strict))then if(strict)then badvalue=-1.0D0 endif endif rangeok=.False. if(x.ge.10.0D0.and.x.le.2000) then rangeok=.True. endif ! call check_range('LHC8 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(5),1,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(7),3,interpol) endif endif else interpol=badvalue endif XS_lhc8_HW_SM=interpol end function XS_lhc8_HW_SM !****************************************************** function XS_lhc8_HZ_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc8_HZ_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) badvalue=0.0D0 if(present(strict))then if(strict)then badvalue=-1.0D0 endif endif rangeok=.False. if(x.ge.10.0D0.and.x.le.2000) then rangeok=.True. endif ! call check_range('LHC8 ',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(5),2,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(7),4,interpol) endif endif else interpol=badvalue endif XS_lhc8_HZ_SM=interpol end function XS_lhc8_HZ_SM !****************************************************** function XS_lhc8_ttH_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc8_ttH_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC8 ',x,rangeok,badvalue,strict) if(rangeok)then ! call interpolate_tabletype1(x,XSSM(6),1,interpol) interpol = XS_lhc8_ttH_SM_func(x,strict) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(3),5,interpol) endif endif else interpol=badvalue endif XS_lhc8_ttH_SM=interpol end function XS_lhc8_ttH_SM !****************************************************** function XS_lhc8_tH_tchan_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc8_tH_tchan_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC8 ',x,rangeok,badvalue,strict) if(rangeok)then interpol=badvalue if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(7),7,interpol) endif endif else interpol=badvalue endif XS_lhc8_tH_tchan_SM=interpol end function XS_lhc8_tH_tchan_SM !****************************************************** function XS_lhc8_tH_schan_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc8_tH_schan_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC8 ',x,rangeok,badvalue,strict) if(rangeok)then interpol=badvalue if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(7),8,interpol) endif endif else interpol=badvalue endif XS_lhc8_tH_schan_SM=interpol end function XS_lhc8_tH_schan_SM !****************************************************** !*** *** !*** LHC 13 TeV *** !*** *** !****************************************************** function XS_lhc13_gg_H_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc13_gg_H_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC13',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(8),1,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(12),1,interpol) endif endif else interpol=badvalue endif XS_lhc13_gg_H_SM=interpol end function XS_lhc13_gg_H_SM !****************************************************** function XS_lhc13_bb_H_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc13_bb_H_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC13',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(8),3,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(12),6,interpol) endif endif else interpol=badvalue endif XS_lhc13_bb_H_SM=interpol end function XS_lhc13_bb_H_SM !****************************************************** function XS_lhc13_vbf_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc13_vbf_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC13',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(8),2,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(12),2,interpol) endif endif else interpol=badvalue endif XS_lhc13_vbf_SM=interpol end function XS_lhc13_vbf_SM !****************************************************** function XS_lhc13_HW_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc13_HW_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) badvalue=0.0D0 if(present(strict))then if(strict)then badvalue=-1.0D0 endif endif rangeok=.False. if(x.ge.10.0D0.and.x.le.2000) then rangeok=.True. endif ! call check_range('lhc13',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(9),1,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(12),3,interpol) endif endif else interpol=badvalue endif XS_lhc13_HW_SM=interpol end function XS_lhc13_HW_SM !****************************************************** function XS_lhc13_HZ_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc13_HZ_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) badvalue=0.0D0 if(present(strict))then if(strict)then badvalue=-1.0D0 endif endif rangeok=.False. if(x.ge.10.0D0.and.x.le.2000) then rangeok=.True. endif ! call check_range('lhc13',x,rangeok,badvalue,strict) if(rangeok)then call interpolate_tabletype1(x,XSSM(9),2,interpol) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(12),4,interpol) endif endif else interpol=badvalue endif XS_lhc13_HZ_SM=interpol end function XS_lhc13_HZ_SM !****************************************************** function XS_lhc13_ttH_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc13_ttH_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC13',x,rangeok,badvalue,strict) if(rangeok)then ! call interpolate_tabletype1(x,XSSM(10),1,interpol) interpol = XS_lhc13_ttH_SM_func(x,strict) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(12),5,interpol) endif endif else interpol=badvalue endif XS_lhc13_ttH_SM=interpol end function XS_lhc13_ttH_SM !****************************************************** function XS_lhc13_tH_tchan_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc13_tH_tchan_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC13',x,rangeok,badvalue,strict) if(rangeok)then ! call interpolate_tabletype1(x,XSSM(11),1,interpol) interpol = XS_lhc13_tH_tchan_SM_func(x,strict) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(12),7,interpol) endif endif else interpol=badvalue endif XS_lhc13_tH_tchan_SM=interpol end function XS_lhc13_tH_tchan_SM !****************************************************** function XS_lhc13_tH_schan_SM(x,strict,EWcorr) !****************************************************** implicit none double precision, intent(in) :: x double precision :: interpol double precision :: XS_lhc13_tH_schan_SM logical,optional :: strict logical,optional :: EWcorr logical :: rangeok double precision :: func,badvalue call testXSSM(x) call check_range('LHC13',x,rangeok,badvalue,strict) if(rangeok)then ! call interpolate_tabletype1(x,XSSM(11),2,interpol) interpol = XS_lhc13_tH_schan_SM_func(x,strict) if(present(EWcorr))then if(EWcorr.and.(abs(x-125.0D0).le.5.0D0)) then call interpolate_tabletype1(x,XSSM(12),8,interpol) endif endif else interpol=badvalue endif XS_lhc13_tH_schan_SM=interpol end function XS_lhc13_tH_schan_SM !****************************************************** subroutine check_range(coll,Mh,rangeok,badvalue,strict) !****************************************************** implicit none character(LEN=5), intent(in) :: coll ! coll should be the same as the elements of ! collider in S95tables.f90 double precision, intent(in) :: Mh logical :: rangeok double precision :: badvalue logical,optional :: strict rangeok=.True. if( .not.(Mh.gt.0.0D0) )then !in case Mh is NaN rangeok=.False. else select case(coll) case('TEV ') if( Mh.lt.tevXS_SM_functions_xmin)then rangeok=.False. elseif(Mh.gt.tevXS_SM_functions_xmax)then rangeok=.False. endif case('LHC7 ') if( Mh.lt.lhc7XS_SM_functions_xmin)then rangeok=.False. elseif(Mh.gt.lhc7XS_SM_functions_xmax)then rangeok=.False. endif case('LHC8 ') if( Mh.lt.lhc8XS_SM_functions_xmin)then rangeok=.False. elseif(Mh.gt.lhc8XS_SM_functions_xmax)then rangeok=.False. endif case('LHC13 ') if( Mh.lt.lhc13XS_SM_functions_xmin)then rangeok=.False. elseif(Mh.gt.lhc13XS_SM_functions_xmax)then rangeok=.False. endif case default stop 'problem in subroutine check_range' end select endif badvalue=0.0D0 if(present(strict))then if(strict)then badvalue=-1.0D0 if(.not.rangeok)then ! write(*,*)'Warning: Higgs mass is outside valid range for the SM cross section functions' endif endif endif end subroutine check_range !****************************************************** function XS_tev_bg_Hb_SM(x,strict) !****************************************************** implicit none double precision :: XS_tev_bg_Hb_SM double precision, intent(in) :: x logical :: rangeok double precision :: func,badvalue logical,optional :: strict call check_range('TEV ',x,rangeok,badvalue,strict) if(rangeok)then func=1.0D3*tev_cs_bg_Hb_SM(x) !convert from pb to fb else func=badvalue endif XS_tev_bg_Hb_SM=func end function XS_tev_bg_Hb_SM !****************************************************** function XS_tev_bg_Hb_c1_SM(x,strict) !****************************************************** implicit none double precision :: XS_tev_bg_Hb_c1_SM double precision, intent(in) :: x logical :: rangeok double precision :: func,badvalue logical,optional :: strict call check_range('TEV ',x,rangeok,badvalue,strict) if(rangeok)then func=1.0D3*tev_cs_bg_Hb_c1_SM(x) !convert from pb to fb else func=badvalue endif XS_tev_bg_Hb_c1_SM=func end function XS_tev_bg_Hb_c1_SM !****************************************************** function XS_tev_bg_Hb_c2_SM(x,strict) !****************************************************** implicit none double precision :: XS_tev_bg_Hb_c2_SM double precision, intent(in) :: x logical :: rangeok double precision :: func,badvalue logical,optional :: strict call check_range('TEV ',x,rangeok,badvalue,strict) if(rangeok)then func=1.0D3*tev_cs_bg_Hb_c2_SM(x) !convert from pb to fb else func=badvalue endif XS_tev_bg_Hb_c2_SM= func end function XS_tev_bg_Hb_c2_SM !****************************************************** function XS_tev_bg_Hb_c3_SM(x,strict) !****************************************************** implicit none double precision :: XS_tev_bg_Hb_c3_SM double precision, intent(in) :: x logical :: rangeok double precision :: func,badvalue logical,optional :: strict call check_range('TEV ',x,rangeok,badvalue,strict) if(rangeok)then func=1.0D3*SMCS_tev_bg_Hb_c3(x) !convert from pb to fb else func=badvalue endif XS_tev_bg_Hb_c3_SM= func end function XS_tev_bg_Hb_c3_SM !****************************************************** function XS_tev_bg_Hb_c4_SM(x,strict) !****************************************************** implicit none double precision :: XS_tev_bg_Hb_c4_SM double precision, intent(in) :: x logical :: rangeok double precision :: func,badvalue logical,optional :: strict call check_range('TEV ',x,rangeok,badvalue,strict) if(rangeok)then func=1.0D3*tev_cs_bg_Hb_c4_SM(x) !convert from pb to fb else func=badvalue endif XS_tev_bg_Hb_c4_SM= func end function XS_tev_bg_Hb_c4_SM !****************************************************** function XS_tev_HW_SM(x,strict) !****************************************************** implicit none double precision :: XS_tev_HW_SM double precision, intent(in) :: x logical :: rangeok double precision :: func,badvalue double precision :: a0,a0p5,a1,a2 logical,optional :: strict a0 = 5.7514105496046D0 a0p5 = -0.375021739545092D0 a1 = 0.0049451487167627D0 a2 = -3.77008582179264D-06 call check_range('TEV ',x,rangeok,badvalue,strict) if(rangeok)then func=10.0D0**(a0+a0p5*x**0.5D0+a1*x+a2*x**2.0D0) else func=badvalue endif XS_tev_HW_SM=func end function XS_tev_HW_SM !****************************************************** function XS_tev_HZ_SM(x,strict) !****************************************************** implicit none double precision :: XS_tev_HZ_SM double precision, intent(in) :: x logical :: rangeok double precision :: func,badvalue double precision :: a0,a0p5,a1,a2 logical,optional :: strict a0 = 5.29935340004443D0 a0p5 = -0.351677660532052D0 a1 = 0.0047848452802514D0 a2 = -3.82425969474559D-06 call check_range('TEV ',x,rangeok,badvalue,strict) if(rangeok)then func=10.0D0**(a0+a0p5*x**0.5D0+a1*x+a2*x**2.0D0) else func=badvalue endif XS_tev_HZ_SM=func end function XS_tev_HZ_SM !****************************************************** !function XS_tev_gg_H_SM(x,strict) !****************************************************** ! implicit none ! double precision :: XS_tev_gg_H_SM ! double precision, intent(in) :: x ! logical :: rangeok ! double precision :: func,badvalue ! double precision :: a0,a0p5,a1,a2 ! logical,optional :: strict ! a0 = 5.59682783597183D0 ! a0p5 = -0.244216706673437D0 ! a1 = 0.000365613425058581D0 ! a2 = 2.66122261164927D-06 ! call check_range('TEV ',x,rangeok,badvalue,strict) ! if(rangeok)then ! func=10.0D0**(a0+a0p5*x**0.5D0+a1*x+a2*x**2.0D0) ! else ! func=badvalue ! endif ! XS_tev_gg_H_SM= func !end function XS_tev_gg_H_SM !****************************************************** function XS_tev_gg_H_SM(x,strict) !****************************************************** !Updated by TS on 31/03/2011, result given in fb implicit none double precision :: XS_tev_gg_H_SM double precision, intent(in) :: x logical :: rangeok double precision :: func,badvalue double precision :: a0,a0p5,a1,a2 logical,optional :: strict a0 = 2.82844783978179 a0p5 = -0.238895314316816 a1 = -0.00244189137753305 a2 = 7.90070235250398e-06 call check_range('TEV ',x,rangeok,badvalue,strict) if(rangeok)then func=10.0D0**3.0D0*10.0D0**(a0+a0p5*x**0.5D0+a1*x+a2*x**2.0D0) else func=badvalue endif XS_tev_gg_H_SM= func end function XS_tev_gg_H_SM !****************************************************** function XS_tev_gg_H_SM_9713(x,strict) !****************************************************** ! from CDF note 9713, D0 Note 5889 ! note: need to check valdity outside 100 l l b b ------------------------- ! x=x+1 ! S95_t1(x)%id=10235 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 10235' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=5.7D0 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='CDF_ZH_llbb_5.7fb_10235' ! ! x=x+1 ! S95_t1(x)%id=3047 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='[hep-ex] arXiv:1009.3047 (CDF)' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=4.1D0 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='CDF_ZH_llbb_4.1fb_3047' x=x+1 S95_t1(x)%id=10799 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10799' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.45D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 filename(x)='CDF_ZH_llbb_9.45fb_10799' ! x=x+1 ! S95_t1(x)%id=6166 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6166' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.6D0 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='D0_ZH_llbb_8.6fb_6166' x=x+1 S95_t1(x)%id=6296 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6296' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.7D0 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 filename(x)='D0_ZH_llbb_9.7fb_6296' !x=x+1 !S95_t1(x)%id=6089 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 6089' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='D0_ZH_llbb_6.2fb_6089' x=x+1 S95_t1(x)%id=3564 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:1008.3564 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=4.2D0 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 filename(x)='D0_ZH_llbb_4.2fb_3564' !x=x+1 !S95_t1(x)%id=10212 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 10212' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_VH_Metbb_5.7fb_10212' ! x=x+1 ! S95_t1(x)%id=6087 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6087' ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_VH_bb_6.4fb_6087' ! x=x+1 ! S95_t1(x)%id=2012015 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2012-015' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.7D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=130.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2012015_Atlas_VH_bb_ll_lnu_nunu_4.7fb-1' !----------------------- V H -> b b Etmiss ------------------------- ! x=x+1 ! S95_t1(x)%id=10583 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 10583' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=7.8D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_VH_Metbb_7.8fb_10583' ! x=x+1 ! S95_t1(x)%id=6223 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6223' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.4D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_VH_bb_8.4fb_6223' ! x=x+1 ! S95_t1(x)%id=3935 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='[hep-ex] arXiv:0911.3935v4 (CDF)' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=2.1D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_VH_Metbb_2.1fb_3935_interpol' ! ! x=x+1 ! S95_t1(x)%id=5285 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='[hep-ex] arXiv:0912.5285 (D0)' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=5.2D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_VH_bb_5.2fb_5285' !x=x+1 !S95_t1(x)%id=6092 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 6092'!this is what the note says, but the website says 6082 !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='D0_WH_lnubb_5.3fb_6092' ! x=x+1 ! S95_t1(x)%id=10596 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 10596' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=7.5D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_VH_lnubb_7.5fb_10596' ! x=x+1 ! S95_t1(x)%id=2011103 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-103' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=1.04D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=130.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2011103_Atlas_VH_Vbb_1.04fb-1' x=x+1 S95_t1(x)%id=10798 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10798' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.45D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_VH_Metbb_9.45fb_10798' x=x+1 S95_t1(x)%id=6299 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6299' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.5D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_VH_bb_9.5fb_6299' x=x+1 S95_t1(x)%id=2012161 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-161' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=17.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=130.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012161_Atlas_VH-Vbb_17.7fb-1' ! x=x+1 ! S95_t1(x)%id=11031 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-031' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.7D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=135.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11031_CMS_VH-bb_BDT_4.7fb-1' ! x=x+1 ! S95_t1(x)%id=12044 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-12-044' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=17.1D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=135.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='12044_CMS_VH_Vbb_17.1fb-1' ! x=x+1 S95_t1(x)%id=13012 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-012' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=24.D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=135.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='13012_CMS_VH_bb_24fb-1' !----------------------- VBF(H), H -> b b ------------------------- x=x+1 S95_t1(x)%id=13011 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-011' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=115.0D0 S95_t1(x)%xmax=135.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='13011_CMS_VBF_bb_19fb-1' !----------------------- W H -> b b ------------------------- ! x=x+1 ! S95_t1(x)%id=6220 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6220' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.5D0 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='D0_WH_lnubb_8.5fb_6220' x=x+1 S95_t1(x)%id=6309 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6309' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.6D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_WH_lnubb_9.7_6309' ! x=x+1 ! S95_t1(x)%id=10239 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 10239' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=5.7D0 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='CDF_WH_lnubb_5.7fb_10239' x=x+1 S95_t1(x)%id=10796 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10796' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.45D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 filename(x)='CDF_WH_lnubb_9.45fb_10796' x=x+1 S95_t1(x)%id=0874 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:1012.0874 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=5.3D0 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 filename(x)='D0_WH_lnubb_5.3fb_0874' x=x+1 S95_t1(x)%id=5613 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='[hep-ex] arXiv:0906.5613 (CDF)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=2.7D0 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 filename(x)='CDF_WH_lnubb_2.7fb_5613' !----------------------- V H, H -> invisible ------------------------- ! x=x+1 ! S95_t1(x)%id=2013011 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2013-011' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=17.7D0 ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2013011_Atlas_H-inv_17.7fb-1' x=x+1 S95_t1(x)%id=3244 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1402.3244 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=24.8D0 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=400.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=0.0D0 filename(x)='3244_Atlas_H-inv_24.8fb-1' ! x=x+1 ! S95_t1(x)%id=13018 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-13-018' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=24.7D0 ! S95_t1(x)%xmin=105.0D0 ! S95_t1(x)%xmax=145.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='13018_CMS_ZH-inv_24.7fb-1' x=x+1 S95_t1(x)%id=13442 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1404.1344 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=24.60 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=105.0D0 S95_t1(x)%xmax=145.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='1344_CMS_ZH-invisible_24.6fb-1' !----------------------- VBF, H -> invisible ------------------------- ! x=x+1 ! S95_t1(x)%id=13013 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-13-013' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=19.6D0 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=400.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='13013_CMS_VBF-inv_19.6fb-1' x=x+1 S95_t1(x)%id=13441 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1404.1344 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.5D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=400.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='1344_CMS_VBF-invisible_19.5fb-1' x=x+1 S95_t1(x)%id=13443 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1404.1344 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%lumi=24.60 S95_t1(x)%xmin=115.0D0 S95_t1(x)%xmax=145.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='1344_CMS_ZH_VBF-invisible_24.6fb-1' x=x+1 S95_t1(x)%id=6682 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1809.06682 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%SMlike=0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%xmin=75.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=5.0D0 filename(x)='6682_Atlas_VBF_h-invisible_13TeV_36.1fb-1' !----------------------- H -> W W ------------------------- x=x+1 S95_t1(x)%id=5757 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 5757' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=3.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=115.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_ppH_WW_ll_3.0fb_5757' x=x+1 S95_t1(x)%id=3930 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='[hep-ex] arXiv:0809.3930 (CDF)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=3.0D0 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=10.0D0 filename(x)='CDF_ggH_WW_3.0fb_3930' ! x=x+1 ! S95_t1(x)%id=3216 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:1005.3216 (TEVNPHWG)' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=5.4D0 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='CDF_D0_combined_gg-H-WW_4.8-5.4fb_3216_bayesian_interpol' !x=x+1 !S95_t1(x)%id=10102 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 10102' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_H-WW_5.3fb_10102' ! x=x+1 ! S95_t1(x)%id=6221 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6219' !this note has two results in it, both can not have the id 6219 ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.1D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='D0_H-WW_8.1fb_6221_interpol' x=x+1 S95_t1(x)%id=6276 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6276' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_H-VV_9.7fb_6276' x=x+1 S95_t1(x)%id=6301 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6301' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=115.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 filename(x)='D0_VH_VWW_9.7fb_6301' x=x+1 S95_t1(x)%id=10600 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10599' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=8.2D0 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=300.0D0 S95_t1(x)%sep=5.0D0 filename(x)='CDF_ggH-WW_8.2fb_10600_interpol' x=x+1 S95_t1(x)%id=10599 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10599' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=8.2D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_H-WW_8.2fb_10599' x=x+1 S95_t1(x)%id=4468 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='[hep-ex] arXiv:1001.4468 (CDF)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=4.8D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_H-WW_4.8fb_4468_interpol' ! x=x+1 ! S95_t1(x)%id=5871 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5871' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=4.2D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_H-WW_llnunu_4.2fb_5871' !x=x+1 !S95_t1(x)%id=6082 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 6082' !S95_t1(x)%xmin=115.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='D0_H-VV_6.7fb_6082' ! x=x+1 ! S95_t1(x)%id=6219 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6219' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.1D0 ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_H-VV_8.1fb_6219' ! x=x+1 ! S95_t1(x)%id=6179 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6179' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=7.3D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_H-WW-mutau_7.3fb_6179' x=x+1 S95_t1(x)%id=6302 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6302' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=115.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_H-WW_9.7fb_6302' x=x+1 S95_t1(x)%id=6183 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6183' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=8.2D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=130.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_SM_combined_6183' x=x+1 S95_t1(x)%id=4481 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:1001.4481 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=5.4D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=115.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_H-WW_5.4fb_4481' ! x=x+1 ! S95_t1(x)%id=4162 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:1001.4162 (TEVNPHWG)' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=5.4D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=130.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_D0_SM_combined_H-WW_4.8-5.4fb_4162' x=x+1 S95_t1(x)%id=3331 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='TCB' S95_t1(x)%label='[hep-ex] arXiv:1108.3331 (TEVNPHWG)'!CDF note 10608, D0 Note 6230 S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=8.2D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=300.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_D0_combined_gg-H-WW_8.2fb_3331_bayesian_interpol' ! x=x+1 ! S95_t1(x)%id=2011134 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-134' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=1.7D0 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=1.0D0 ! filename(x)='2011134_Atlas_H-WW-lnulnu_1.7fb-1_interpol' x=x+1 S95_t1(x)%id=2012012 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-012' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012012_Atlas_H-WW-lnulnu_4.7fb-1' ! x=x+1 ! S95_t1(x)%id=2012158 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2012-158' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=13.0D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2012158_Atlas_H-WW-enumunu_13fb-1' x=x+1 S95_t1(x)%id=2013030 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2013-030' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=25.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2013030_Atlas_H-WW-lnulnu_25fb-1' ! x=x+1 ! S95_t1(x)%id=5429 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='[hep-ex] arXiv: 1102.5429(CMS)' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=0.036D0 ! S95_t1(x)%xmin=130.0D0 ! S95_t1(x)%xmax=400.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='5429_CMS_H-WW_36pb-1_rat_interpol' x=x+1 S95_t1(x)%id=2577 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arxiv:1112.2577' S95_t1(x)%desc='pp->h + X->W W* + X ->l l nu nu' S95_t1(x)%energy=7.D0 S95_t1(x)%lumi=2.05D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=300.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2577_Atlas_H-WW-lnulnu_2.05fb-1' ! x=x+1 ! S95_t1(x)%id=1489 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='[hep-ex] arxiv:1202.1489 (CMS)' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.6D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=5D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11024_CMS_H-WW-lnulnu_4.6fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=12042 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-12-042' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=16.0D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='12042_CMS_H-WW-lnulnu_16.0fb-1' x=x+1 S95_t1(x)%id=13003 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-003' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=25.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=5D0 S95_t1(x)%deltax=0.0D0 filename(x)='13003_CMS_H-WW-lnulnu_25fb-1' x=x+1 S95_t1(x)%id=13027 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-027' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=24.3D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=170.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='13027_CMS_H-WW-lnujj_24.3fb-1' x=x+1 S95_t1(x)%id=13022 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-022' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=25.4D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=5D0 S95_t1(x)%deltax=0.0D0 filename(x)='13022_CMS_VBF-WW_25.4fb-1' x=x+1 S95_t1(x)%id=2016062 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-CONF-2016-062' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.2D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=500.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=50.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='2016062_Atlas_gg-H-WW-lnuqq_13.2fb-1' !--------------- H -> VV -> l nu l nu ---------------- x=x+1 S95_t1(x)%id=3357 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1109.3357 (ATLAS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=1.04D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=20.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='3357_Atlas_H-ZZ-llnunu_1.04fb-1' ! x=x+1 ! S95_t1(x)%id=2011148 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-148' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=2.05D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=200.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=20.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2011148_Atlas_H-ZZ-lnulnu_2.05fb-1' x=x+1 S95_t1(x)%id=2012016 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-016' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012016_Atlas_H-ZZ-llnunu_4.7fb-1' x=x+1 S95_t1(x)%id=3478 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arxiv:1202.3478 (CMS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.6D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=250.0D0 S95_t1(x)%xmax=590.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='11026_CMS_H-ZZ-llnunu_4.6fb-1' !----------------------- H -> W W ----------------------------- ! x=x+1 ! S95_t1(x)%id=2011052 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-052' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=0.035D0 ! S95_t1(x)%xmin=220.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=20.0D0 ! filename(x)='2011052_Atlas_H-WW_35pb-1' ! x=x+1 ! S95_t1(x)%id=3615 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='[hep-ex] arXiv:1109.3615 (ATLAS)' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=0.035D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=240.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=20.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='3615_Atlas_H-WW-lnuqq_1.04fb-1' ! ! x=x+1 ! S95_t1(x)%id=2012018 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2012-018' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.7D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=300.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2012018_Atlas_H-WW-lnuqq_4.7fb-1' x=x+1 S95_t1(x)%id=12046 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-12-046' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=17D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=170.0D0 S95_t1(x)%xmax=580.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='12046_CMS_H-WW-lnuqq_17fb-1' x=x+1 S95_t1(x)%id=20160741 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-074' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.2D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=50.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='2016074_Atlas_gg-H-WW-lnulnu_13.2fb-1' x=x+1 S95_t1(x)%id=20160742 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-074' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.2D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=50.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='2016074_Atlas_vbf-H-WW-lnulnu_13.2fb-1' +! H -> V V combination + +x=x+1 +S95_t1(x)%id=23801 +S95_t1(x)%particle_x=Hneut +S95_t1(x)%expt='ATL' +S95_t1(x)%label='(hep-ex) arXiv:1808.02380 (ATLAS)' +S95_t1(x)%energy=13.0D0 +S95_t1(x)%lumi=36.1D0 +S95_t1(x)%xmin=300.0D0 +S95_t1(x)%xmax=3000.0D0 +S95_t1(x)%sep=100.0D0 +filename(x)='23801_Atlas_gg-phi-VV_36.1fb-1_13TeV' + +x=x+1 +S95_t1(x)%id=23802 +S95_t1(x)%particle_x=Hneut +S95_t1(x)%expt='ATL' +S95_t1(x)%label='(hep-ex) arXiv:1808.02380 (ATLAS)' +S95_t1(x)%energy=13.0D0 +S95_t1(x)%lumi=36.1D0 +S95_t1(x)%xmin=500.0D0 +S95_t1(x)%xmax=3000.0D0 +S95_t1(x)%sep=100.0D0 +filename(x)='23802_Atlas_vbf-phi-VV_36.1fb-1_13TeV' + !------------------------- H -> Z Z -------------------------- x=x+1 S95_t1(x)%id=5064 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1108.5064 (ATLAS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=1.04D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='5064_Atlas_H-ZZ-llqq_1.04fb-1' x=x+1 S95_t1(x)%id=2012017 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-017' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012017_Atlas_H-ZZ-llqq_4.7fb-1' x=x+1 S95_t1(x)%id=14161 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1202.1416 (CMS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.6D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=130.0D0 S95_t1(x)%xmax=164.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='110271_CMS_H-ZZ-llqq_4.6fb-1' x=x+1 S95_t1(x)%id=14162 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1202.1416 (CMS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.6D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='110272_CMS_H-ZZ-llqq_4.6fb-1' x=x+1 S95_t1(x)%id=1415 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1202.1415 (ATLAS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.8D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='1415_Atlas_H-ZZ-4l_4.8fb-1' x=x+1 S95_t1(x)%id=2012092 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-092' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=10.6D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012092_Atlas_H-ZZ-4l_10.6fb-1' x=x+1 S95_t1(x)%id=20130131 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2013-013' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=25.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=180.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2013013-1_Atlas_H-ZZ-4l_incl_25fb-1' x=x+1 S95_t1(x)%id=20130132 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2013-013' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=21.0D0 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=5.0D0 filename(x)='2013013-2_Atlas_H-ZZ-4l_ggF_21fb-1' x=x+1 S95_t1(x)%id=20130133 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2013-013' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=21.0D0 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=5.0D0 filename(x)='2013013-3_Atlas_H-ZZ-4l_VBFVH_21fb-1' x=x+1 S95_t1(x)%id=20160792 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-079' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=14.8D0 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=400.0D0 S95_t1(x)%sep=1.0D0 filename(x)='20160792_gg-H-ZZ-4l_14.8fb-1_lowmass' x=x+1 S95_t1(x)%id=20160793 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-079' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=14.8D0 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=1.0D0 filename(x)='20160793_VBF-H-ZZ-4l_14.8fb-1' x=x+1 S95_t1(x)%id=1997 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arxiv:1202.1997 (CMS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='11025_CMS_H-ZZ-4l_4.7fb-1' ! x=x+1 ! S95_t1(x)%id=12041 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-12-041' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=17.3D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='12041_CMS_H-ZZ-4l_17.3fb-1' x=x+1 S95_t1(x)%id=130021 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-002' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=25.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='13002-1_CMS_H-ZZ-4l_lowm_25fb-1' x=x+1 S95_t1(x)%id=130022 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-002' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=25.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=150.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='13002-2_CMS_H-ZZ-4l_highm_25fb-1' x=x+1 S95_t1(x)%id=009361 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1504.00936 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=24.8D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=145.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='009361_CMS_H-VV_5.1fb-1_19.7fb-1' x=x+1 S95_t1(x)%id=063861 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='arXiv:1712.06386 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=400.0D0 S95_t1(x)%sep=1.0D0 filename(x)='063861_ATLAS_gg-H-ZZ-4l+2l2nu_NWA_36.1fb-1' x=x+1 S95_t1(x)%id=20160821 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-082' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.2D0 S95_t1(x)%xmin=500.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=1.0D0 filename(x)='20160821_Atlas_gg-H-ZZ-llnunu_13.2fb-1' x=x+1 S95_t1(x)%id=20160822 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-082' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.2D0 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=1.0D0 filename(x)='20160822_Atlas_gg-H-ZZ-llqq_13.2fb-1' x=x+1 S95_t1(x)%id=20160823 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-082' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.2D0 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=1.0D0 filename(x)='20160823_Atlas_qq-Hqq-ZZ-llqq_13.2fb-1' x=x+1 S95_t1(x)%id=16034 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-16-034' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=12.9D0 S95_t1(x)%xmin=550.0D0 S95_t1(x)%xmax=2000.0D0 S95_t1(x)%sep=10.0D0 filename(x)='16034_CMS_H-ZZ-llqq_12.9fb-1' !------------------------- SM combined ----------------------- ! x=x+1 ! S95_t1(x)%id=8961 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:0712.2383v1(TEVNPHWG)' !CDF Note 8961, D0 Note 5536 ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=1.9D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_D0_SM_combined_1.0-1.9fb_8961-5536_interpol' x=x+1 S95_t1(x)%id=10439 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10439' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=6.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_H-tautau_6.0fb_10439' !x=x+1 !S95_t1(x)%id=10133 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 10133' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_H-tautau_2.3fb_10133' ! x=x+1 ! S95_t1(x)%id=4800 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='[hep-ex] arXiv:0903.4800 (D0)' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=1.0D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=105.0D0 ! S95_t1(x)%xmax=145.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_SM_tautau_1.0fb_4800' ! x=x+1 S95_t1(x)%id=5845 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 5845' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=4.9D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=105.0D0 S95_t1(x)%xmax=145.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_tautauqq_4.9fb_5845' ! x=x+1 ! S95_t1(x)%id=9290 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:0804.3423(TEVNPHWG)' !CDF Note 9290, D0 Note 5645 ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=2.4D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_D0_SM_combined_1.0-2.4fb_9290-5645_interpol' ! x=x+1 ! S95_t1(x)%id=9465 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:0808.0534(TEVNPHWG)' !CDF Note 9465, D0 Note 5754 ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=3.0D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=155.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! !filename(x)='CDF_D0_SM_combined_3.0fb_9465-5754_CLs' ! filename(x)='CDF_D0_SM_combined_3.0fb_9465-5754_bayesian' ! x=x+1 ! S95_t1(x)%id=0598 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='[hep-ex] arXiv:0712.0598v1 (D0)' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=0.44D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_SM_combined_0598_interpol' x=x+1 S95_t1(x)%id=9999 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 9999' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=4.8D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_SM_combined_2.0-4.8fb_9999_interpol' ! x=x+1 ! S95_t1(x)%id=6008 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6008' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=5.4D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_SM_combined_6008' x=x+1 S95_t1(x)%id=6305 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6305' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=7.3D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=105.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_H-tautau_7.3fb_6305' ! x=x+1 ! S95_t1(x)%id=9998 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:0911.3930 (TEVNPHWG)'!CDF Note 9998, D0 Note 5983 ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=5.4D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_D0_SM_combined_2.1-5.4fb_9998-5983_bayesian' ! x=x+1 ! S95_t1(x)%id=6096 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:1007.4587 (TEVNPHWG)' !CDF Note 10241, D0 Note 6096 ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=6.7D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_D0_SM_combined_2.1-6.7fb_10241-6096_bayesian' x=x+1 S95_t1(x)%id=10010 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10010' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=4D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_hadr_4fb_10010' x=x+1 S95_t1(x)%id=6171 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6171' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=4.3D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=105.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_H-tautaujj-4.3fb_6171' ! x=x+1 ! S95_t1(x)%id=6229 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6229' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.6D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_SM_combined_6229' x=x+1 S95_t1(x)%id=6304 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6304' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_SM_combined_6304' x=x+1 S95_t1(x)%id=10500 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10500' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=6.2D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_VH_tautau_6.2fb_10500' x=x+1 S95_t1(x)%id=10573 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10573' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=8.2D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=120.0D0 S95_t1(x)%xmax=300.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_H-WW_8.2fb_10573' x=x+1 S95_t1(x)%id=6286 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6286' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=7.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_tautaumu_7.0fb_6286' ! x=x+1 ! S95_t1(x)%id=3233 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:1103.3233v2 (TEVNPHWG)' !CDF Note 10432, D0 Note 6183 ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.2D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=130.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! !filename(x)='CDF_D0_SM_combined_4.3-8.2fb_3233_CLs' ! filename(x)='CDF_D0_SM_combined_4.3-8.2fb_3233_bayesian' ! ! x=x+1 ! S95_t1(x)%id=10606 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:1107.5518 (TEVNPHWG)' !CDF Note 10606, D0 Note 6226 ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.6D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_D0_SM_combined_8.6fb_10606' x=x+1 S95_t1(x)%id=10884 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='TCB' S95_t1(x)%label='[hep-ex] arXiv:1207.0449 (TEVNPHWG)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=10.D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='10884_CDF_D0_SM_combined_10fb-1' ! x=x+1 ! S95_t1(x)%id=10607 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='[hep-ex] arXiv:1107.5518 (TEVNPHWG)' !CDF Note 10606, D0 Note 6226 ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.6D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_D0_combined_h-bb_8.6fb_10607' x=x+1 S95_t1(x)%id=6436 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='TCB' S95_t1(x)%label='[hep-ex] arXiv:1207.6436 (TEVNPHWG)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='1207.6436_CDF_D0_combined_h-bb_9.7fb-1' ! x=x+1 ! S95_t1(x)%id=2011112 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-112' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=1.21D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2011112_Atlas_SMcombined_1.04-1.21fb-1_interpol' ! ! x=x+1 ! S95_t1(x)%id=2011135 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-135' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=2.3D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2011135_Atlas_SMcombined_1-2.3fb-1_interpol' ! ! x=x+1 ! S95_t1(x)%id=2011163 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-163' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.9D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=0.5D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2011163_Atlas_SMcombined_4.9fb-1' ! x=x+1 S95_t1(x)%id=1408 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='(hep-ex) arxiv:1202.1408 (ATLAS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.9D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='1408_Atlas_SMcombined_4.9fb-1' x=x+1 S95_t1(x)%id=2012019 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-019' S95_t1(x)%desc='(p p)->h+...' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.9D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012019_Atlas_SMcombined_4.9fb-1' x=x+1 S95_t1(x)%id=7214 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='(hep-ex) arXiv:1207.7214 (ATLAS)' S95_t1(x)%desc='(p p)->h+...' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=10.5D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=0.0D0 filename(x)='7214_Atlas_SMcombined_10.5fb-1' x=x+1 S95_t1(x)%id=2011157 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2011-157, CMS-PAS-HIG-11-023' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=2.3D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2011157_Atlas_CMS_SMcombined_2.7fb-1' ! x=x+1 ! S95_t1(x)%id=11011 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-011' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=1.1D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11011_CMS_SMcomb_1.1fb-1_interpol' x=x+1 S95_t1(x)%id=1488 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arxiv:1202.1488 (CMS)' S95_t1(x)%energy=7.D0 S95_t1(x)%lumi=4.8D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='1488_CMS_SMcombined_4.8fb-1' ! x=x+1 ! S95_t1(x)%id=12008 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-12-008' ! S95_t1(x)%desc='(p p)->h+...' ! S95_t1(x)%energy=7.D0 ! S95_t1(x)%lumi=4.8D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='12008_CMS_SMcombined_4.8fb-1' x=x+1 S95_t1(x)%id=12045 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-12-045' S95_t1(x)%desc='(p p)->h+...' S95_t1(x)%energy=8.D0 S95_t1(x)%lumi=17.3D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='12045_CMS_SMcombined_17.3fb-1' !----------------- b H -> 3 b jets ------------------- ! x=x+1 ! S95_t1(x)%id=10105 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 10105' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=2.2D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=210.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='CDF_bbH_bb_2.2fb_10105' ! x=x+1 ! S95_t1(x)%id=5726 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5726' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=2.6D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=220.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_bbH_bb_2.6fb_5726_sq_interpol' x=x+1 S95_t1(x)%id=1931 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:1011.1931 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=5.2D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=300.0D0 S95_t1(x)%sep=10.0D0 filename(x)='D0_bbH_bb_5.2fb_1931' x=x+1 S95_t1(x)%id=4782 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='arXiv:1106.4782 (CDF)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=2.6D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=350.0D0 S95_t1(x)%sep=10.0D0 filename(x)='CDF_bbH_bb_2.6fb_4782' ! x=x+1 ! S95_t1(x)%id=12033 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-12-033' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.8D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=350.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='12033_CMS_bbH-bbbb_4.8fb-1' x=x+1 S95_t1(x)%id=1508329 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='arXiv:1506.08329 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=900.0D0 S95_t1(x)%sep=10.0D0 filename(x)='1508329_CMS_Hb-bbb_19.7fb-1' x=x+1 S95_t1(x)%id=2015080 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='CERN-THESIS-2015-080 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.5D0 S95_t1(x)%xmin=450.0D0 S95_t1(x)%xmax=800.0D0 S95_t1(x)%sep=50.0D0 filename(x)='2015080_Atlas_hb-bbb_19.5fb-1' !-------------------- H -> tau tau ------------------------- x=x+1 S95_t1(x)%id=4555 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:1106.4555 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=5.4D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=300.0D0 S95_t1(x)%sep=10.0D0 filename(x)='D0_H-tautau_5.4fb_4555_interpol' ! x=x+1 ! S95_t1(x)%id=2491 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='[hep-ex] arXiv:0805.2491 (D0)' ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_ppH_tautau_1fb_2491_interpol' x=x+1 S95_t1(x)%id=1014 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='[hep-ex] arXiv:0906.1014 (CDF)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=1.8D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=250.0D0 S95_t1(x)%sep=10.0D0 filename(x)='CDF_H-tautau_1.8fb_1014_interpol' ! x=x+1 ! S95_t1(x)%id=5740 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5740' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=2.2D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_H-tautau_2.2fb_5740_interpol' x=x+1 S95_t1(x)%id=3363 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='TCB' S95_t1(x)%label='[hep-ex] arXiv:1003.3363 (TEVNPHWG)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=2.2D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=10.0D0 filename(x)='CDF_D0_combinedH-tautau_2.2fb_3363_CLs' ! x=x+1 ! S95_t1(x)%id=2011133 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-133' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=1.06D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=140.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2011133_Atlas_H-tautau-ll4nu_1.06fb-1' ! x=x+1 ! S95_t1(x)%id=2012014 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2012-014' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.7D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2012014_Atlas_H-tautau_4.7fb-1' x=x+1 S95_t1(x)%id=2012160 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-160' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=17.6D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012160_Atlas_H-tautau_17.6fb-1' ! x=x+1 ! S95_t1(x)%id=5003 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='[hep-ex] arXiv:1107.5003 (ATLAS)'!CERN-PH-EP-2011-104 ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=0.036D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='5003_Atlas_ggh_h-tautau_36pb-1' ! x=x+1 ! S95_t1(x)%id=2011132 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-132' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=1.06D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='2011132_Atlas_conserv_h-tautau_1.06fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=2012094 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2012-094' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.7D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=500.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='2012094_Atlas_H-tautau_4.7fb-1' ! Analysis is disabled when using CMS tau tau likelihood x=x+1 S95_t1(x)%id=2014049 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2014-049, arXiv:1409.6064' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%llh=1 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=20.0D0 filename(x)='2014049_Atlas_bbh_h-tautau_20.3fb-1' ! Analysis is disabled when using CMS tau tau likelihood x=x+1 S95_t1(x)%id=20140492 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2014-049, arXiv:1409.6064' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%llh=1 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=20.0D0 filename(x)='20140492_Atlas_ggh_h-tautau_20.3fb-1' ! Analysis is disabled when using CMS tau tau likelihood ! x=x+1 ! S95_t1(x)%id=20160851 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2016-085' ! S95_t1(x)%energy=13.0D0 ! S95_t1(x)%lumi=13.3D0 ! S95_t1(x)%xmin=200.0D0 ! S95_t1(x)%xmax=1200.0D0 ! S95_t1(x)%llh=1 ! S95_t1(x)%sep=20.0D0 ! S95_t1(x)%deltax=20.0D0 ! filename(x)='20160851_Atlas_ggh_h_tautau_13.3fb-1' ! Analysis is disabled when using CMS tau tau likelihood ! x=x+1 ! S95_t1(x)%id=20160852 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2016-085' ! S95_t1(x)%energy=13.0D0 ! S95_t1(x)%lumi=13.3D0 ! S95_t1(x)%xmin=200.0D0 ! S95_t1(x)%xmax=1200.0D0 ! S95_t1(x)%llh=1 ! S95_t1(x)%sep=20.0D0 ! S95_t1(x)%deltax=20.0D0 ! filename(x)='20160852_Atlas_bbh_h_tautau_13.3fb-1' ! Analysis is disabled when using CMS tau tau likelihood ! x=x+1 ! S95_t1(x)%id=160371 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-16-037' ! S95_t1(x)%energy=13.0D0 ! S95_t1(x)%lumi=12.9D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=3000.0D0 ! S95_t1(x)%llh=1 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=20.0D0 ! filename(x)='160371_CMS_ggh_h_tautau_12.9fb-1' ! Analysis is disabled when using CMS tau tau likelihood ! x=x+1 ! S95_t1(x)%id=160372 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-16-037' ! S95_t1(x)%energy=13.0D0 ! S95_t1(x)%lumi=12.9D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=3000.0D0 ! S95_t1(x)%llh=1 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=20.0D0 ! filename(x)='160372_CMS_bbh_h_tautau_12.9fb-1' ! Analysis is disabled when using CMS tau tau likelihood ! x=x+1 ! S95_t1(x)%id=20170501 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2017-050' ! S95_t1(x)%energy=13.0D0 ! S95_t1(x)%lumi=36.1D0 ! S95_t1(x)%xmin=200.0D0 ! S95_t1(x)%xmax=2250.0D0 ! S95_t1(x)%llh=1 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=20.0D0 ! filename(x)='20170501_Atlas_gg-H-tautau_36.1fb-1' ! x=x+1 ! S95_t1(x)%id=20170502 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2017-050' ! S95_t1(x)%energy=13.0D0 ! S95_t1(x)%lumi=36.1D0 ! S95_t1(x)%xmin=200.0D0 ! S95_t1(x)%xmax=2250.0D0 ! S95_t1(x)%llh=1 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=20.0D0 ! filename(x)='20170502_Atlas_bb-H-tautau_36.1fb-1' ! x=x+1 ! S95_t1(x)%id=110291 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-029' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.6D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=145.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11029_CMS_H-tautau_4.6fb-1_SM' x=x+1 S95_t1(x)%id=12043 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-12-043' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=17.D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=145.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='12043_CMS_H_tautau_17fb-1' ! x=x+1 ! S95_t1(x)%id=10002 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='[hep-ex] arXiv: 1104:1619(CMS)'!CMS-PAS-HIG-10-002 ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=0.036D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=500.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='10002_CMS_H-tautau_36pb-1_interpol' ! x=x+1 ! S95_t1(x)%id=110292 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='[hep-ex] arXiv: 1202.4083 (CMS)' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.6D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=500.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='11029_CMS_H-tautau_4.6fb-1_MSSM_interpol' ! ! x=x+1 ! S95_t1(x)%id=12050 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-12-050' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=17.D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=800.0D0 ! S95_t1(x)%sep=1.0D0 ! filename(x)='12050_CMS_H-tautau_17fb-1' ! Still in testing phase! ! x=x+1 ! S95_t1(x)%id=13021 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-13-021' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=25.6D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=1000.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='13021_CMS_H-tautau_25.6fb-1_MSSM_ggH' !-------------------- Higgs to Higgs decays ------------------------- ! ! Requires hi -> hj Z branching ratio in input! ! x=x+1 S95_t1(x)%id=14011 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-14-011, arXiv:1504.04710 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=225.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=10.0D0 filename(x)='14011_CMS_A-Zh-llbb_19.7fb-1' ! x=x+1 S95_t1(x)%id=04670 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1509.04670 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=10.0D0 filename(x)='04670_Atlas_H-hh-combined_20.3fb-1' x=x+1 S95_t1(x)%id=046701 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1509.04670 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=500.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='04670_Atlas_H-hh-gagaWW_20.3fb-1' x=x+1 S95_t1(x)%id=8567 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1807.08567 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=500.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='8567_Atlas_X-HH-WWgaga_13TeV_36.1fb-1' x=x+1 S95_t1(x)%id=4873 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1807.04873 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='4873_Atlas_X-HH-gagabb_13TeV_36.1fb-1' x=x+1 S95_t1(x)%id=2016071 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-071' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=500.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='2016071_Atlas_gg-H-hh-WWgaga_13.3fb-1' x=x+1 S95_t1(x)%id=046702 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1509.04670 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='04670_Atlas_H-hh-bbtautau_20.3fb-1' x=x+1 S95_t1(x)%id=336 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1808.00336 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='336_Atlas_X-HH-bbtautau_13TeV_36.1fb-1' x=x+1 S95_t1(x)%id=2016049 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-049' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=50.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='2016049_Atlas_H-hh-bbbb_13.3fb-1' x=x+1 S95_t1(x)%id=011811 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1510.01181 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=350.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='140341_CMS_H-hh-bbtautau_19.7fb-1' x=x+1 S95_t1(x)%id=17020321 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1701.02032 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=5.0D0 S95_t1(x)%xmax=15.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='170102032_CMS_HSM-aa-tautau_19.7fb-1' x=x+1 S95_t1(x)%id=7355 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1806.07355 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=20.0D0 S95_t1(x)%xmax=60.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='7355_Atlas_VH-aa-bbbb_13TeV_36.1fb-1' x=x+1 S95_t1(x)%id=17020322 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1701.02032 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=25.0D0 S95_t1(x)%xmax=62.5D0 S95_t1(x)%sep=0.5D0 S95_t1(x)%deltax=0.0D0 filename(x)='170102032_CMS_HSM-aa-mumubb_19.7fb-1' x=x+1 S95_t1(x)%id=539 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1807.00539 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=20.0D0 S95_t1(x)%xmax=60.0D0 S95_t1(x)%sep=0.5D0 S95_t1(x)%deltax=0.0D0 filename(x)='539_Atlas_H-aa-bbmumu_13TeV_36.1fb-1' x=x+1 S95_t1(x)%id=17020323 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1701.02032 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=15.0D0 S95_t1(x)%xmax=62.5D0 S95_t1(x)%sep=0.5D0 S95_t1(x)%deltax=0.0D0 filename(x)='170102032_CMS_HSM-aa-mumutautau_19.7fb-1' x=x+1 S95_t1(x)%id=5051 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1509.05051 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=10.0D0 S95_t1(x)%xmax=61.75D0 S95_t1(x)%sep=0.05D0 S95_t1(x)%deltax=0.0D0 filename(x)='5051_Atlas_gg-H-aa-gagagaga_20.3fb-1' x=x+1 S95_t1(x)%id=1506534 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1510.06534 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=4.0D0 S95_t1(x)%xmax=8.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='1506534_CMS_gg-H-hh-tautautautau_19.7fb-1' x=x+1 S95_t1(x)%id=17006 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG 17-006' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.0D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=900.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='17006_CMS_H-hh-bbVV-bblnulnu_36fb-1' x=x+1 S95_t1(x)%id=011812 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1510.01181 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=220.0D0 S95_t1(x)%xmax=350.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='140342_CMS_A-hZ-tautaull_19.7fb-1' x=x+1 S95_t1(x)%id=044781 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='[hep-ex] arXiv:1502.04478 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=220.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='044781_ATLAS_gg-A-hZ-tautaull_20.3fb-1' x=x+1 S95_t1(x)%id=044782 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='[hep-ex] arXiv:1502.04478 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=220.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='044782_ATLAS_gg-A-hZ-bbll_20.3fb-1' x=x+1 S95_t1(x)%id=20160151 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-CONF-2016-015' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=3.2D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=220.0D0 S95_t1(x)%xmax=2000.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='20160151_ATLAS_gg-A-hZ-bbll_3.2fb-1' x=x+1 S95_t1(x)%id=20160152 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-CONF-2016-015' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=3.2D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=220.0D0 S95_t1(x)%xmax=2000.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='20160152_ATLAS_bb-A-hZ-bbll_3.2fb-1' x=x+1 S95_t1(x)%id=180051 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-18-005' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=35.9D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=220.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='180051_CMS_gg-A-Zh-Zbb_13TeV_35.9fb-1' x=x+1 S95_t1(x)%id=180052 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-18-005' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=35.9D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=220.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='180052_CMS_bb-A-Zh-Zbb_13TeV_35.9fb-1' x=x+1 S95_t1(x)%id=16002 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-16-002' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=2.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=260.0D0 S95_t1(x)%xmax=1200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='16002_CMS_H-hh-bbbb_2.3fb-1' ! x=x+1 ! S95_t1(x)%id=16029 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-16-029' ! S95_t1(x)%energy=13.0D0 ! S95_t1(x)%lumi=12.9D0 ! S95_t1(x)%SMlike=0 ! S95_t1(x)%xmin=250.0D0 ! S95_t1(x)%xmax=900.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=10.0D0 ! filename(x)='16029_CMS_H-hh-bbtautau_12.9fb-1' x=x+1 S95_t1(x)%id=17002 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-17-002' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=35.9D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=250.0D0 S95_t1(x)%xmax=900.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='17002_CMS_H-hh-tautaubb_35.9fb-1' x=x+1 S95_t1(x)%id=14013 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-14-013,arXiv:1503.04114 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=17.9D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=270.0D0 S95_t1(x)%xmax=1097.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='14013_H-hh-bbbb_17.9fb-1' x=x+1 S95_t1(x)%id=17030 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-17-030' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=35.9D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=270.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='17030_CMS_pp-X-HH_comb_13TeV_35.9fb-1' !-------------------- H -> mu mu ------------------------- x=x+1 S95_t1(x)%id=2013010 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2013-010' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=21D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2013010_Atlas_H-mumu_21fb-1' x=x+1 S95_t1(x)%id=7663 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1406.7663 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=24.8D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=120.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='7663_Atlas_H-mumu_24.8fb-1' !------------------------ H W -> W W W -------------------------- x=x+1 S95_t1(x)%id=5873 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 5873' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=3.6D0 S95_t1(x)%xmin=120.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=20.0D0 filename(x)='D0_WH_WWW_llnunu_3.6fb_5873' x=x+1 S95_t1(x)%id=7307 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 7307 vs 3' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=2.7D0 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=10.0D0 filename(x)='CDF_WH_WWW_2.7fb_7307vs3.0' !filename(x)='CDF_WH_WWW_1.9fb_7307' x=x+1 S95_t1(x)%id=1268 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:1107.1268 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=5.3D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=115.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_VH_ll_5.3fb_1268' ! x=x+1 ! S95_t1(x)%id=11034 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-034' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.6D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11034_CMS_WH-WWW_4.6fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=12039 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-12-039' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=10.D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='12039_CMS_WH-WWW_10fb-1' x=x+1 S95_t1(x)%id=13009 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-009' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=25.D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='13009_CMS_WH-WWW_25fb-1' x=x+1 S95_t1(x)%id=12006 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-12-006' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=140.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='12006_CMS_WH-Wtautau_4.7fb-1' x=x+1 S95_t1(x)%id=12051 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-12-051' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=17.D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=145.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='12051_CMS_VH_Vtautau_17fb-1' x=x+1 S95_t1(x)%id=2012078 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-078' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=300.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012078_Atlas_WH_WWW_4.7fb-1' !-------------------- H -> gamma gamma -------------------- ! x=x+1 ! S95_t1(x)%id=6177 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6177' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=8.2D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=2.5D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_gaga_8.2fb_6177' x=x+1 S95_t1(x)%id=6295 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6295' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=9.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=2.5D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_gaga_9.7fb_6295' x=x+1 S95_t1(x)%id=1887 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:0901.1887 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=2.7D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_Hgaga_2.7fb_1887' x=x+1 S95_t1(x)%id=10485 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10485' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=7.0D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_SM_Hgaga_7.0fb_10485' x=x+1 S95_t1(x)%id=4960 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='TCB' S95_t1(x)%label='[hep-ex] arXiv:1107.4960 (TEVNPHWG)'!CDF Note 10510, D0 Note 6203 S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=8.2D0 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_D0_combined_SM_Hgaga_8.2fb_4960' x=x+1 S95_t1(x)%id=1414 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1202.1414 (ATLAS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.9D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='1414_Atlas_H-gaga_4.9fb-1' ! x=x+1 ! S95_t1(x)%id=2012091 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2012-091' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=10.8D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=0.5D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2012091_Atlas_H-gaga_10.8fb-1' x=x+1 S95_t1(x)%id=2012168 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-168' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=17.8D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=0.5D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012168_Atlas_H-gaga_17.8fb-1' x=x+1 S95_t1(x)%id=6583 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1407.6583' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=65.0D0 S95_t1(x)%xmax=600.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=0.0D0 filename(x)='6583_Atlas_H-gaga_20.3fb-1' x=x+1 S95_t1(x)%id=059301 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1507.05930 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=140.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='05930_Atlas_gg-H-ZZ-20.3fb-1' x=x+1 S95_t1(x)%id=059302 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1507.05930 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=140.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='05930_Atlas_VBF-H-ZZ-20.3fb-1' x=x+1 S95_t1(x)%id=0038911 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1509.00389 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=100.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='0038911_Atlas_ggH-WW-NWA_20.3fb-1' x=x+1 S95_t1(x)%id=0038912 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1509.00389 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=100.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='0038912_Atlas_VBF-WW-NWA_20.3fb-1' x=x+1 S95_t1(x)%id=0038913 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1509.00389 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=20.0D0 S95_t1(x)%deltax=20.0D0 filename(x)='0038913_Atlas_ggH-WW-CPS_20.3fb-1' x=x+1 S95_t1(x)%id=0038914 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1509.00389 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=20.0D0 S95_t1(x)%deltax=20.0D0 filename(x)='0038914_Atlas_VBF-WW-CPS_20.3fb-1' x=x+1 S95_t1(x)%id=17013 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-17-013' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=35.9D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=110.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=0.0D0 filename(x)='17013_CMS_H-gaga_lowmass_8TeV_20fb-1_and_13TeV_36fb-1' ! x=x+1 ! S95_t1(x)%id=1487 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='[hep-ex] arXiv:1202.1487 (CMS)' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.8D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=0.5D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='1487_CMS_H-gaga_4.8fb-1' ! x=x+1 ! S95_t1(x)%id=12001 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-12-001' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=4.76D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=0.5D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='12001_CMS_H-gaga_BDT_4.8fb-1' ! x=x+1 ! S95_t1(x)%id=12015 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-12-015' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=9.9D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=0.5D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='12015_CMS_H-gaga_9.9fb-1' ! x=x+1 S95_t1(x)%id=13001 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-001' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=25.D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=0.5D0 S95_t1(x)%deltax=0.0D0 filename(x)='13001_CMS_H-gaga_MVA_25fb-1' x=x+1 S95_t1(x)%id=14037 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-14-037' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=110.0D0 S95_t1(x)%sep=0.5D0 S95_t1(x)%deltax=0.0D0 filename(x)='14037_CMS_H-gaga_19.7fb-1' x=x+1 S95_t1(x)%id=14031 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-14-031' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=500.0D0 S95_t1(x)%sep=1.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='14031_CMS_H-Zgamma-19.7fb-1' x=x+1 S95_t1(x)%id=2018025 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2018-025' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=80.0D0 S95_t1(x)%SMlike=0 S95_t1(x)%xmin=65.0D0 S95_t1(x)%xmax=110.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=0.0D0 filename(x)='2018025_Atlas_h-gaga_13TeV_80fb-1' ! x=x+1 ! S95_t1(x)%id=14006 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-14-006' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=19.7D0 ! S95_t1(x)%SMlike=0 ! S95_t1(x)%xmin=150.0D0 ! S95_t1(x)%xmax=847.6D0 ! S95_t1(x)%sep=0.1D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='14006_CMS_H-gaga_19.7fb-1' ! !-------------------- H -> gamma Z -------------------- ! x=x+1 ! S95_t1(x)%id=13006 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-13-006' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=25.D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=120.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=1.D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='13006_CMS_H-gaZ_25fb-1' x=x+1 S95_t1(x)%id=13075515 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='[hep-ex] arXiv:1307.5515 (CMS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=24.6D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=120.0D0 S95_t1(x)%xmax=160.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=0.0D0 filename(x)='13075515_CMS_H-Zgamma_24.6fb-1' ! x=x+1 ! S95_t1(x)%id=2013009 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2013-009' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=25.D0 ! S95_t1(x)%SMlike=1 ! S95_t1(x)%xmin=120.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=1.D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2013009_Atlas_H-gaZ_25fb-1' x=x+1 S95_t1(x)%id=3051 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1402.3051 (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=24.8D0 S95_t1(x)%SMlike=1 S95_t1(x)%xmin=120.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=0.0D0 filename(x)='3051_Atlas_H-Zga_24.8fb-1' !--------------------- b H -> b tau tau --------------------------- x=x+1 S95_t1(x)%id=4885 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:1106.4885 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=7.3D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=320.0D0 S95_t1(x)%sep=10.0D0 filename(x)='D0_Hb_tautaub_7.3fb_4885' ! x=x+1 ! S95_t1(x)%id=5985 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5985' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=2.7D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=320.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_bH_btautau_2.7fb_5985' ! x=x+1 ! S95_t1(x)%id=5974 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5974' ! S95_t1(x)%energy=1.96D0 ! S95_t1(x)%lumi=3.7D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_Hb_tautaub_3.7fb_5974' x=x+1 S95_t1(x)%id=6083 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 6083' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=4.3D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=200.0D0 S95_t1(x)%sep=10.0D0 filename(x)='D0_Hb_tautaub_4.3fb_6083' !-------------------- t t H -> t t b b -------------------- x=x+1 S95_t1(x)%id=5739 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='D0 Note 5739' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=2.1D0 S95_t1(x)%xmin=105.0D0 S95_t1(x)%xmax=155.0D0 S95_t1(x)%sep=10.0D0 filename(x)='D0_ttH_ttbb_2.1fb_5739' x=x+1 S95_t1(x)%id=10574 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 10574' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=7.5D0 S95_t1(x)%xmin=100.0D0 S95_t1(x)%xmax=170.0D0 S95_t1(x)%sep=5.0D0 filename(x)='CDF_ttH_ttbb_7.5fb_10574_interpol' x=x+1 S95_t1(x)%id=2012135 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2012-135' S95_t1(x)%energy=7D0 S95_t1(x)%lumi=4.7D0 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=140.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2012135_Atlas_ttH_Hbb_4.7fb-1' x=x+1 S95_t1(x)%id=12025 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-12-025' S95_t1(x)%energy=7D0 S95_t1(x)%lumi=5.D0 S95_t1(x)%xmin=110.0D0 S95_t1(x)%xmax=140.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='12025_CMS_ttH-ttbb_5fb-1' !-------------------- H -> Z gamma -------------------------- x=x+1 S95_t1(x)%id=0611 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:0806.0611 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=1.1D0 S95_t1(x)%xmin=120.0D0 S95_t1(x)%xmax=320.0D0 S95_t1(x)%sep=20.0D0 filename(x)='D0_H-Zgamma_1.0-1.1fb_0611' !x=x+1 !S95_t1(x)%id=6091 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 6091' !S95_t1(x)%xmin=115.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='D0_VH_ll_5.4fb_6091' !x=x+1 !S95_t1(x)%id=5858 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5858' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=2.5D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='D0_gaga_4.2fb_5858' !x=x+1 !S95_t1(x)%id=10065 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 10065' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=10.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_SM_Hgaga_5.4fb_10065' ! x=x+1 ! S95_t1(x)%id=0968 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='[hep-ex] arXiv:0912.0968 (D0)' ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=320.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_Hb_tautaub_2.7fb_0968' !---------------- Daniel's attempts -------------- x=x+1 S95_t1(x)%id=2016025 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-HIG-16-025' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=2.69D0 S95_t1(x)%xmin=550.0D0 S95_t1(x)%xmax=1200.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='2016025_CMS_H-bb_2.69fb-1' x=x+1 S95_t1(x)%id=201608391 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-1606-08391' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=3.2D0 S95_t1(x)%xmin=20.0D0 S95_t1(x)%xmax=60.0D0 S95_t1(x)%sep=0.5D0 S95_t1(x)%deltax=10.0D0 filename(x)='160608391_Atlas_HW_Waa_Wbbbb_3.2fb-1' x=x+1 S95_t1(x)%id=2016044 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-CONF-2016-044' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.3D0 S95_t1(x)%xmin=250.0D0 S95_t1(x)%xmax=2500.0D0 S95_t1(x)%sep=2D0 S95_t1(x)%deltax=10.0D0 filename(x)='2016044_Atlas_H_ZA_13.3fb-1' x=x+1 S95_t1(x)%id=2016004 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-CONF-2016-004' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=3.2D0 S95_t1(x)%xmin=275.0D0 S95_t1(x)%xmax=400.0D0 S95_t1(x)%sep=1D0 S95_t1(x)%deltax=10.0D0 filename(x)='2016004_Atlas_H-hh-bbgaga_3.2fb-1' x=x+1 S95_t1(x)%id=1604833 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-1606-04833' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=3.2D0 S95_t1(x)%xmin=500.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=10D0 S95_t1(x)%deltax=10.0D0 filename(x)='1604833_Atlas_H-VV_3.2fb-1' x=x+1 S95_t1(x)%id=2016056 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-CONF-2016-056' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=13.3D0 S95_t1(x)%xmin=300.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=5D0 S95_t1(x)%deltax=10.0D0 filename(x)='2016056_Atlas_H-ZZ-llnunu_13.3fb-1' x=x+1 S95_t1(x)%id=20160551 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-CONF-2016-055' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=15.5D0 S95_t1(x)%xmin=1200.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=100D0 S95_t1(x)%deltax=10.0D0 filename(x)='20160551_Atlas_pp-H-ZZ-qqqq_15.5fb-1' x=x+1 S95_t1(x)%id=20160552 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='ATLAS' S95_t1(x)%label='ATLAS-CONF-2016-055' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=15.5D0 S95_t1(x)%xmin=1200.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=100D0 S95_t1(x)%deltax=10.0D0 filename(x)='20160552_Atlas_pp-H-WW-qqqq_15.5fb-1' x=x+1 S95_t1(x)%id=15009 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-2015-009' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%xmin=25.0D0 S95_t1(x)%xmax=60.0D0 S95_t1(x)%sep=0.1D0 S95_t1(x)%deltax=1.0D0 filename(x)='15009_CMS_bbA_mumu_19.7fb-1' !---------------- charged Higgs ------------------ x=x+1 S95_t1(x)%id=1811 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:0908.1811 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=1.0D0 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=155.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_Hp_qq_1.0fb_1811_interpol' x=x+1 S95_t1(x)%id=1269 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='CDF' S95_t1(x)%label='[hep-ex] arXiv:0907.1269 (CDF) lower mass' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=2.2D0 S95_t1(x)%xmin=60.0D0 S95_t1(x)%xmax=70.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_t-Hplusb_1269_lowmass' x=x+1 S95_t1(x)%id=1270 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='CDF' S95_t1(x)%label='[hep-ex] arXiv:0907.1269 (CDF) higher mass' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=2.2D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_t-Hplusb_1269_highmass' x=x+1 S95_t1(x)%id=7712 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 7712' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=0.192D0 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=160.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_t-Hplusb_tauonicHM_192pb_7712' x=x+1 S95_t1(x)%id=8353 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='CDF' S95_t1(x)%label='CDF Note 8353' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=0.335D0 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=120.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='CDF_t-Hplusb_8353' x=x+1 S95_t1(x)%id=1812 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt=' D0' S95_t1(x)%label='[hep-ex] arXiv:0908.1811 (D0)' S95_t1(x)%energy=1.96D0 S95_t1(x)%lumi=1.0D0 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=155.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='D0_Hp_taunu_1.0fb_1811_interpol' x=x+1 S95_t1(x)%id=2011094 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2011-094' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=0.035D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=130.0D0 S95_t1(x)%sep=20.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2011094_Atlas_Hplus-cs_35pb-1' ! x=x+1 ! S95_t1(x)%id=2011138 ! S95_t1(x)%particle_x=Hplus ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-138' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=1.03D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=160.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2011138_Atlas_Hp-taunu_1.03fb-1' ! x=x+1 ! S95_t1(x)%id=2011151 ! S95_t1(x)%particle_x=Hplus ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-151' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=1.03D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=160.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2011151_Atlas_chargedH-taunu_1.03fb-1' x=x+1 S95_t1(x)%id=2760 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1204.2760 (ATLAS)' S95_t1(x)%energy=7.0D0 S95_t1(x)%lumi=4.6D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=160.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2760_Atlas_Hp_taunu_4.6fb-1' ! x=x+1 ! S95_t1(x)%id=2013090 ! S95_t1(x)%particle_x=Hplus ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2013-090' ! S95_t1(x)%energy=8.0D0 ! S95_t1(x)%lumi=19.5D0 ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=160.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2013090_Atlas_Hp_taunu_19.6fb-1' x=x+1 S95_t1(x)%id=2014050 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2014-050' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.5D0 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=160.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2014050_Atlas_Hp_taunu_19.5fb-1' x=x+1 S95_t1(x)%id=79151 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1807.07915 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=2000.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='079151_Atlas_tbHp-taunu_36fb-1' x=x+1 S95_t1(x)%id=79152 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1807.07915 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=160.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='079152_Atlas_t-Hpb-taunu_36fb-1' ! x=x+1 ! S95_t1(x)%id=11008 ! S95_t1(x)%particle_x=Hplus ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-008' ! S95_t1(x)%energy=7.0D0 ! S95_t1(x)%lumi=1.1D0 ! S95_t1(x)%xmin=80.0D0 ! S95_t1(x)%xmax=160.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11008_CMS_Hplus-taunu_1.1fb-1_interpol' x=x+1 S95_t1(x)%id=14020 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-14-020' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=160.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='14020_CMS_Hp_taunu_19.7fb-1' x=x+1 S95_t1(x)%id=13035 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-13-035' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=160.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='13035_CMS_chargedH-cs_19.7fb-1' x=x+1 S95_t1(x)%id=16030 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-16-030' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=19.7D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=150.0D0 S95_t1(x)%sep=10.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='16030_CMS_t_Hplusb_cb_19.7fb-1' ! HB-5 x=x+1 S95_t1(x)%id=1504233 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='ATLAS' S95_t1(x)%label='arXiv:1503.04233 [hep-ex] (ATLAS)' S95_t1(x)%energy=8.0D0 S95_t1(x)%lumi=20.3D0 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=1000.0D0 S95_t1(x)%sep=20.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='1504233_Atlas_Hplus_VBF-WZ_20.3fb-1' ! x=x+1 ! S95_t1(x)%id=160312 ! S95_t1(x)%particle_x=Hplus ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-16-031' ! S95_t1(x)%energy=13.0D0 ! S95_t1(x)%lumi=12.9D0 ! S95_t1(x)%xmin=180.0D0 ! S95_t1(x)%xmax=3000.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='16031_CMS_Hptb_taunu_12.9fb-1' ! Still leave this in, although strictly speaking superseded by 18-014, because different implementation. x=x+1 S95_t1(x)%id=160311 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-16-031' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=12.9D0 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=160.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='160311_CMS_t_Hplusb_taunu_12.9fb-1' x=x+1 S95_t1(x)%id=18014 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='CMS' S95_t1(x)%label='CMS-PAS-HIG-18-014' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=35.9D0 S95_t1(x)%xmin=80.0D0 S95_t1(x)%xmax=3000.0D0 S95_t1(x)%sep=5.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='18014_CMS_pp-tbHpm-taunu_13TeV_35.9fb-1' x=x+1 S95_t1(x)%id=2016088 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='ATL' S95_t1(x)%label='ATLAS-CONF-2016-088' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=14.7D0 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=2000.0D0 S95_t1(x)%sep=25.0D0 S95_t1(x)%deltax=0.0D0 filename(x)='2016088_Atlas_Hptb-taunutb_14.7fb-1' ! x=x+1 ! S95_t1(x)%id=2016089 ! S95_t1(x)%particle_x=Hplus ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2016-089' ! S95_t1(x)%energy=13.0D0 ! S95_t1(x)%lumi=13.2D0 ! S95_t1(x)%xmin=300.0D0 ! S95_t1(x)%xmax=1000.0D0 ! S95_t1(x)%sep=50.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2016089_Atlas_Hptb-tbtb_13.2fb-1' x=x+1 S95_t1(x)%id=3599 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='ATL' S95_t1(x)%label='[hep-ex] arXiv:1808.03599 (ATLAS)' S95_t1(x)%energy=13.0D0 S95_t1(x)%lumi=36.1D0 S95_t1(x)%xmin=200.0D0 S95_t1(x)%xmax=2000.0D0 S95_t1(x)%sep=25.0D0 S95_t1(x)%deltax=10.0D0 filename(x)='3599_Atlas_pp-tbHpm-tbtb_13Tev_36.1fb-1' !---------------------------------------------- !&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&& ! superseded !x=x+1 !superseded by arXiv:1011.1931 !S95_t1(x)%id=3556 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='[hep-ex] arXiv:0805.3556 (D0)' !S95_t1(x)%xmin=90.0D0 !S95_t1(x)%xmax=220.0D0 !S95_t1(x)%sep=10.0D0 !filename(x)='D0_bbH_bb_1.0fb_3556_interpol' !x=x+1 !superseded by arXiv:1009.3047 !S95_t1(x)%id=3534 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='[hep-ex] arXiv:0908.3534 (CDF)' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_ZH_llbb_2.7fb_3534' !x=x+1 !superseded by CDF 10239 !S95_t1(x)%id=10217 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 10217' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_WH_lnubb_5.6fb_10217' !x=x+1 !superseded by CDF Note 10133 !S95_t1(x)%id=9248 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9248' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_SMcomb_tautau_2.0fb_9248_interpol' !x=x+1 !superseded by arXiv:1012.0874 !S95_t1(x)%id=1970 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='[hep-ex] arXiv:0808.1970 (D0)' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='D0_WH_lnubb_1.05fb_1970' !x=x+1 !S95_t1(x)%id=6095 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 6095' !S95_t1(x)%xmin=115.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='D0_H-WW_lljj_5.4fb_6095' !x=x+1 !S95_t1(x)%id=5972 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5972' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='D0_WH_lnubb_5.0fb_5972' !x=x+1 !S95_t1(x)%id=10068 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 10068' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_WH_lnubb_4.8fb_10068' !x=x+1 !S95_t1(x)%id=5586 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5586' !S95_t1(x)%xmin=105.0D0 !S95_t1(x)%xmax=145.0D0 !S95_t1(x)%sep=10.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='D0_ZH_nunubb_2.1fb_5586' !x=x+1 !S95_t1(x)%id=9891 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9891' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_VH_Metbb_3.6fb_9891' !x=x+1 !S95_t1(x)%id=5876 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5876' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='D0_ZH_llbb_4.2fb_5876' !x=x+1 !S95_t1(x)%id=9889 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9889' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_ZH_llbb_4.1fb_9889' !x=x+1 !S95_t1(x)%id=9284 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9284' !S95_t1(x)%xmin=90.0D0 !S95_t1(x)%xmax=210.0D0 !S95_t1(x)%sep=10.0D0 !filename(x)='CDF_bbH_bb_1.9fb_9284' !x=x+1 !S95_t1(x)%id=9868 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9868' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_WH_lnubb_4.3fb_9868' !http://www-cdf.fnal.gov/physics/new/hdg/results/whlnubb_090814/WH4.3fb.html !x=x+1 !S95_t1(x)%id=9887 !superseded by arXiv:1001.4468 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9887' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_H-WW_4.8fb_9887_interpol' !x=x+1 !S95_t1(x)%id=0024 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='[hep-ex] arXiv:0811.0024v1 (D0)' !S95_t1(x)%xmin=90.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=10.0D0 !filename(x)='D0_bH_btautau_328pb_0024' !x=x+1 !S95_t1(x)%id=1266 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='[hep-ex] arXiv:0808.1266 (D0)' !S95_t1(x)%xmin=105.0D0 !S95_t1(x)%xmax=135.0D0 !S95_t1(x)%sep=10.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='D0_VH_bb_0.93fb_1266' !x=x+1 !S95_t1(x)%id=0432 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='[hep-ex] arXiv:0802.0432 (CDF)' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=140.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_VH_Metbb_1fb_0432' !x=x+1 !S95_t1(x)%id=9674 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9674' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_SM_combined_2.0-3.0fb_9674_interpol' !x=x+1 !S95_t1(x)%id=5980 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='TCB' !S95_t1(x)%label='D0 Note 5980, CDF Note 9888' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=10.0D0 !filename(x)='CDF_D0_combinedH-tautau_2.2fb_5980' !x=x+1 !S95_t1(x)%id=9714 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='TCB' !S95_t1(x)%label='arXiv:0903.4001 (TEVNPHWG), MH>=155GeV'!CDF Note 9713, D0 Note 5889 !S95_t1(x)%xmin=155.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_D0_SM_combined_4.2fb_9713-5889_bayesian_highmassonly' !x=x+1 !S95_t1(x)%id=9897 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9897' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_SM_combined_2.0-4.8fb_9897_interpol' !x=x+1 !S95_t1(x)%id=8742 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 8742' ! table from CDF note 8742 !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_ZH_llbb_1fb_8742_interpol' ! x=x+1 ! S95_t1(x)%id=7081 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='arxiv 070810 (CDF)' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_ZH_nunubb_1.7fb_070810_interpol' ! ! x=x+1 ! ! S95_t1(x)%id=8958 ! ! S95_t1(x)%particle_x=Hneut ! ! S95_t1(x)%expt='CDF' ! ! S95_t1(x)%label='CDF Note 8958' ! ! S95_t1(x)%xmin=110.0D0 ! ! S95_t1(x)%xmax=200.0D0 ! ! S95_t1(x)%sep=10.0D0 ! ! filename(x)='CDF_ggH_WW_1.9fb_8958' ! x=x+1 ! S95_t1(x)%id=8957 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 8957' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='CDF_WH_lnubb_1.7fb_8957_interpol' ! x=x+1 ! S95_t1(x)%id=5489 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5489' ! S95_t1(x)%xmin=120.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=20.0D0 ! filename(x)='D0_ppH_WW_emu_0.6fb_5489' !x=x+1 !S95_t1(x)%id=5537 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5537' !S95_t1(x)%xmin=120.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=20.0D0 !filename(x)='D0_ppH_WW_ll_1.7fb_5537' ! x=x+1 ! S95_t1(x)%id=5482 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5482' ! S95_t1(x)%xmin=105.0D0 ! S95_t1(x)%xmax=145.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_ZH_llbb_1.1fb_5482' ! x=x+1 ! S95_t1(x)%id=5624 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5624' ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='D0_ppH_WW_ll_2.3fb_5624' !x=x+1 !S95_t1(x)%id=5472 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5472' !S95_t1(x)%xmin=105.0D0 !S95_t1(x)%xmax=145.0D0 !S95_t1(x)%sep=10.0D0 !!filename(x)='D0_WH_lnubb_1.7fb_5472' !filename(x)='D0_WH_lnubb_1.7fb_5472_Fig.6a' !x=x+1 !S95_t1(x)%id=5502 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5502' !S95_t1(x)%xmin=120.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=20.0D0 !filename(x)='D0_ppH_WW_ee_0.6fb_5502' !x=x+1 !S95_t1(x)%id=5332 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5332' !S95_t1(x)%xmin=120.0D0 !S95_t1(x)%xmax=180.0D0 !S95_t1(x)%sep=20.0D0 !filename(x)='D0_ppH_WW_mutau_1fb_5332' !x=x+1 !S95_t1(x)%id=5485 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5485' !S95_t1(x)%xmin=120.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=20.0D0 !filename(x)='D0_WH_WWW_llnunu_1fb_5485' !x=x+1 !S95_t1(x)%id=9071 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9071' !S95_t1(x)%xmin=90.0D0 !S95_t1(x)%xmax=250.0D0 !S95_t1(x)%sep=10.0D0 !filename(x)='CDF_ppH_tautau_1.8fb_9071_interpol' !x=x+1 !S95_t1(x)%id=5331 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5331' !S95_t1(x)%xmin=90.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=10.0D0 !filename(x)='D0_ppH_tautau_1fb_5331_interpol' ! x=x+1 ! S95_t1(x)%id=5503 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5503' ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=170.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_bbH_bb_0.9fb_5503_interpol' !x=x+1 !S95_t1(x)%id=8954 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 8954' !S95_t1(x)%xmin=90.0D0 !S95_t1(x)%xmax=210.0D0 !S95_t1(x)%sep=10.0D0 !filename(x)='CDF_bbH_bb_1fb_8954' ! x=x+1 ! S95_t1(x)%id=9236 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 9236' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='CDF_ggH_WW_2.4fb_9236' ! x=x+1 ! S95_t1(x)%id=9219 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 9219' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='CDF_WH_lnubb_1.9fb_9219' ! x=x+1 ! S95_t1(x)%id=5601 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5601' ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_Hgaga_2.27fb_5601' !taken out until we sort out a fermiophobic-ness test !x=x+1 !S95_t1(x)%id=1514 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='[hep-ex] arXiv:0803.1514v1 (D0)' !S95_t1(x)%xmin=70.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=10.0D0 !filename(x)='D0_gaga_1.1fb_1514' ! x=x+1 ! S95_t1(x)%id=9166 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 9166' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_VH_Metbb_1.97fb_9166_interpol' !x=x+1 !S95_t1(x)%id=9463 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9463' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_WH_lnubb_2.7fb_9463' !x=x+1 !S95_t1(x)%id=5570 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5570' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='D0_ZH_llbb_2.3fb_5570' !x=x+1 !S95_t1(x)%id=4493 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='[hep-ex] arXiv:0807.4493 (CDF)' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_ZH_llbb_1fb_4493_interpol' !x=x+1 !S95_t1(x)%id=9475 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9475' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_ZH_llbb_2.4fb_9475' !x=x+1 !S95_t1(x)%id=5737 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5737' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='D0_gaga_2.68fb_5737' !x=x+1 !S95_t1(x)%id=9483 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF note 9483' !S95_t1(x)%xmin=105.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_VH_Metbb_2.1fb_9483' !x=x+1 !S95_t1(x)%id=9500 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9500' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_ggH_WW_3.0fb_9500_interpol' !x=x+1 !S95_t1(x)%id=9713 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='TCB' !S95_t1(x)%label='CDF Note 9713, D0 Note 5889' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_D0_SM_combined_4.2fb_9713-5889_bayesian' ! x=x+1 ! S95_t1(x)%id=1024 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note XXXX, zhllbb_081024' ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='CDF_ZH_llbb_2.7fb_1024' !x=x+1 !S95_t1(x)%id=9596 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9596' !S95_t1(x)%xmin=100.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_WH_lnubb_2.7fb_9596' ! x=x+1 ! S95_t1(x)%id=5828 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 5828' ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='D0_WH_lnubb_2.7fb_5828' !x=x+1 !S95_t1(x)%id=9642 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9642' !S95_t1(x)%xmin=105.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_VH_Metbb_2.1fb_9642' ! x=x+1 ! S95_t1(x)%id=9022 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='CDF Note 9764,"old" ggH XS' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_H-WW_3.6fb_9022_interpol' !NEW! not yet in OB's code !x=x+1 !S95_t1(x)%id=9023 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 9764,"new" ggH XS' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_H-WW_3.6fb_9023_interpol' ! x=x+1 ! S95_t1(x)%id=3493 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CDF' ! S95_t1(x)%label='[hep-ex] arXiv:0803.3493v1 (CDF)' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! filename(x)='CDF_WH_lnubb_1fb_3493_interpol' !x=x+1 !S95_t1(x)%id=0710 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note XXXX,hwwmenn_090710' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_H-WW_4.8fb_0710_interpol' !x=x+1 !S95_t1(x)%id=5984 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 5984,high mass' !S95_t1(x)%xmin=155.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='D0_SM_combined_5984_highmassonly' !x=x+1 !S95_t1(x)%id=3155 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='[hep-ex] arXiv:0905.3155 (CDF)' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_WH_lnubb_1.9fb_3155_interpol' ! x=x+1 ! S95_t1(x)%id=9997 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='TCB' ! S95_t1(x)%label='arXiv:0911.3930 (TEVNPHWG), MH>=160GeV'!CDF Note 9998, D0 Note 5983 ! S95_t1(x)%xmin=160.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='CDF_D0_SM_combined_2.1-5.4fb_9998-5983_bayesian_highmassonly' !x=x+1 !S95_t1(x)%id=6039 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='TCB' !S95_t1(x)%label='CDF Note 10101, D0 Note 6039' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=260.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_D0_combined_gg-H-WW_4.8-5.4fb_6039_bayesian_interpol' !x=x+1 !S95_t1(x)%id=6006 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt=' D0' !S95_t1(x)%label='D0 Note 6006' !S95_t1(x)%xmin=115.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='D0_H-WW_ll_5.4fb_6006' !x=x+1 !S95_t1(x)%id=2011026 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-026' !S95_t1(x)%xmin=200.0D0 !S95_t1(x)%xmax=600.0D0 !S95_t1(x)%sep=20.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='2011026_Atlas_H-VV_35pb-1' !x=x+1 !superseded by 2011085 !S95_t1(x)%id=2011025 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-025' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=140.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='2011025_Atlas_H-gaga_37.6pb-1_interpol' !x=x+1 !S95_t1(x)%id=2011005 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-005' !S95_t1(x)%xmin=120.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='2011005_Atlas_H-WW_35pb-1_interpol' !x=x+1 !S95_t1(x)%id=10433 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 10432' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=300.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='CDF_ggH-WW_7.1fb_10433_SMnormalized' !x=x+1 !S95_t1(x)%id=10432 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='CDF' !S95_t1(x)%label='CDF Note 10432' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=200.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='CDF_H-WW_7.1fb_10432' ! x=x+1 ! S95_t1(x)%id=6170 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6170' ! S95_t1(x)%xmin=100.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_ZH_bb_6.2fb_6170' ! x=x+1 ! S95_t1(x)%id=6182 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6182' ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=200.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='D0_H-VV_8.1fb_6182' !x=x+1 superseded by 2011131 !S95_t1(x)%id=2011048 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-048' !S95_t1(x)%xmin=120.0D0 !S95_t1(x)%xmax=600.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='2011048_Atlas_H-ZZ-4l_40pb-1_interpol' !x=x+1 !S95_t1(x)%id=2011085 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-085' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=140.0D0 !S95_t1(x)%sep=1.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='2011085_Atlas_H-gaga_209pb-1' ! x=x+1 ! S95_t1(x)%id=2748 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='[hep-ex] arXiv:1106.2748 (ATLAS)' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2748_Atlas_SMcombined_40pb-1' !x=x+1 !S95_t1(x)%id=11002 !S95_t1(x)%particle_x=Hplus !S95_t1(x)%expt='CMS' !S95_t1(x)%label='CMS-PAS-HIG-11-002' !S95_t1(x)%xmin=80.0D0 !S95_t1(x)%xmax=160.0D0 !S95_t1(x)%sep=5.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='11002_CMS_t-Hplusb_36pb-1' !x=x+1 !S95_t1(x)%id=2011020 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-020, lower masses' !S95_t1(x)%xmin=6.1D0 !S95_t1(x)%xmax=9.0D0 !S95_t1(x)%sep=0.1D0 !filename(x)='2011020_Atlas_H-mumu_lowerMa_35pb-1' !x=x+1 !S95_t1(x)%id=2011021 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-020, higher masses' !S95_t1(x)%xmin=11.0D0 !S95_t1(x)%xmax=11.9D0 !S95_t1(x)%sep=0.1D0 !filename(x)='2011021_Atlas_H-mumu_higherMa_35pb-1' ! x=x+1 ! S95_t1(x)%id=11003 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-003' ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11003_CMS_H-WW_1.1fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=11004 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-004' ! S95_t1(x)%xmin=120.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11004_CMS_H-ZZ-llll_1.13fb-1' ! x=x+1 ! S95_t1(x)%id=11005 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-005' ! S95_t1(x)%xmin=250.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11005_CMS_H-ZZ-llnunu_1.1fb-1' ! x=x+1 ! S95_t1(x)%id=11006 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-006' ! S95_t1(x)%xmin=230.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11006_CMS_H-ZZ-llqq_1fb-1' ! x=x+1 ! S95_t1(x)%id=11009 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-009' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=140.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11009_CMS_SM_H-tautau_1.1fb-1' ! x=x+1 ! S95_t1(x)%id=11010 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-010' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=140.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11010_CMS_H-gammagamma_1.09fb-1' !x=x+1 !S95_t1(x)%id=2011111 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-111' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=240.0D0 !S95_t1(x)%sep=5.0D0 !filename(x)='2011111_Atlas_H-WW_1.04fb-1_interpol' !x=x+1 !S95_t1(x)%id=2011131 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-131' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=600.0D0 !S95_t1(x)%sep=2.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='2011131_Atlas_H-ZZ_1.1fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=11012 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-012' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=135.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11012_CMS_H-bb_1.1fb-1' ! x=x+1 ! S95_t1(x)%id=11013 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-013' ! S95_t1(x)%xmin=180.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=10.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11013_CMS_H-ZZ-lltautau_1.1fb-1' ! x=x+1 ! S95_t1(x)%id=11014 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-014' ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11014_CMS_H-WW_1.55fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=11015 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-015' ! S95_t1(x)%xmin=115.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11015_CMS_H-ZZ-4l_1.66fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=11016 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-016' ! S95_t1(x)%xmin=250.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11016_CMS_H-ZZ-llnunu_1.6fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=11017 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-017' ! S95_t1(x)%xmin=225.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11017_CMS_H-ZZ-llqq_1.6fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=11020 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-020' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=145.0D0 ! S95_t1(x)%sep=5.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11020_CMS_H-tautau_1.6fb-1_SM' ! x=x+1 ! S95_t1(x)%id=11021 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-021' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11021_CMS_SM_H-gaga_1.66fb-1' !n.b.: Need fermiophobic-ness check for this analysis ! x=x+1 ! S95_t1(x)%id=110212 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-021' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='110212_CMS_Fermiophob_H-gaga_1.66fb-1' ! x=x+1 ! S95_t1(x)%id=11022 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-022' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11022_CMS_SMcombined_1.1-1.7fb-1' ! x=x+1 ! S95_t1(x)%id=5895 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='[hep-ex] arXiv:1108.5895 (ATLAS)' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='5895_Atlas_H-gaga_1.08fb-1' ! x=x+1 ! S95_t1(x)%id=110201 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-020' ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=500.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='11020_CMS_H-tautau_1.6fb-1_MSSM_interpol' !x=x+1 !S95_t1(x)%id=2011161 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-161' !S95_t1(x)%xmin=110.0D0 !S95_t1(x)%xmax=150.0D0 !S95_t1(x)%sep=1.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='2011161_Atlas_H-gaga_4.9fb-1' ! x=x+1 ! S95_t1(x)%id=2011162 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='ATL' ! S95_t1(x)%label='ATLAS-CONF-2011-162' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='2011162_Atlas_H-ZZ-4l_4.8fb-1' ! x=x+1 ! S95_t1(x)%id=11024 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-024' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=5D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11024_CMS_H-WW-lnulnu_4.6fb-1_interpol' ! x=x+1 ! S95_t1(x)%id=11025 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-025' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11025_CMS_H-ZZ-4l_4.7fb-1' ! x=x+1 ! S95_t1(x)%id=11026 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-026' ! S95_t1(x)%xmin=250.0D0 ! S95_t1(x)%xmax=590.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11026_CMS_H-ZZ-llnunu_4.6fb-1' ! x=x+1 ! S95_t1(x)%id=110271 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-027' ! S95_t1(x)%xmin=130.0D0 ! S95_t1(x)%xmax=164.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='110271_CMS_H-ZZ-llqq_4.6fb-1' ! x=x+1 ! S95_t1(x)%id=110272 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-027' ! S95_t1(x)%xmin=200.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='110272_CMS_H-ZZ-llqq_4.6fb-1' ! x=x+1 ! S95_t1(x)%id=11028 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-028' ! S95_t1(x)%xmin=190.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11028_CMS_H-ZZ-lltautau_4.7fb-1' ! x=x+1 ! S95_t1(x)%id=11030 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-030' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=150.0D0 ! S95_t1(x)%sep=0.5D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11030_CMS_H-gaga_4.8fb-1' ! x=x+1 ! S95_t1(x)%id=11032 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt='CMS' ! S95_t1(x)%label='CMS-PAS-HIG-11-032' ! S95_t1(x)%xmin=110.0D0 ! S95_t1(x)%xmax=600.0D0 ! S95_t1(x)%sep=1.0D0 ! S95_t1(x)%deltax=0.0D0 ! filename(x)='11032_CMS_SMcombined_4.7fb-1' !x=x+1 !S95_t1(x)%id=2011150 !S95_t1(x)%particle_x=Hneut !S95_t1(x)%expt='ATL' !S95_t1(x)%label='ATLAS-CONF-2011-150' !S95_t1(x)%xmin=200.0D0 !S95_t1(x)%xmax=600.0D0 !S95_t1(x)%sep=20.0D0 !S95_t1(x)%deltax=0.0D0 !filename(x)='2011150_Atlas_H-ZZ-llqq_2.05fb-1' ! x=x+1 ! S95_t1(x)%id=6224 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6227, Br(h->tautau)>6%' ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_h-bb_h-tautau_comb_Br0.06_5.2-7.3fb_6224' ! ! x=x+1 ! S95_t1(x)%id=6225 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6227, Br(h->tautau)>10%' ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_h-bb_h-tautau_comb_Br0.10_5.2-7.3fb_6225' ! ! x=x+1 ! S95_t1(x)%id=6226 ! S95_t1(x)%particle_x=Hneut ! S95_t1(x)%expt=' D0' ! S95_t1(x)%label='D0 Note 6227, Br(h->tautau)>14%' ! S95_t1(x)%xmin=90.0D0 ! S95_t1(x)%xmax=300.0D0 ! S95_t1(x)%sep=10.0D0 ! filename(x)='D0_h-bb_h-tautau_comb_Br0.14_5.2-7.3fb_6226' ! checks we've filled the whole array if(x.ne.xend)then stop 'error in initializetables1 (a)' endif ! do loop to read in S95 tables col=3 do x=xbeg,xend S95_t1(x)%nx=nint((S95_t1(x)%xmax-S95_t1(x)%xmin)/S95_t1(x)%sep)+1 allocate(S95_t1(x)%dat(S95_t1(x)%nx,col-1)) enddo open(file_id_common2,file = trim(adjustl(pathname))//'Expt_tables/' // & & 'S95_t1.binary',form='unformatted') read(file_id_common2,iostat=ios)S95_t1(xbeg)%dat if(ios.eq.0)then do x=xbeg+1,xend read(file_id_common2)S95_t1(x)%dat enddo else rewind(file_id_common2) do x=xbeg,xend fullfilename=trim(adjustl(pathname))//'Expt_tables/' & & //trim(adjustl(S95_t1(x)%expt))//'tables/' & & //trim(filename(x))//'.txt' call read_tabletype1(S95_t1(x),5,col,fullfilename) #ifndef WEBVERSION write(file_id_common2)S95_t1(x)%dat #endif enddo endif close(file_id_common2) deallocate(filename) end subroutine initializetables1 !************************************************************ subroutine read_tabletype1(t1,skip,col,fullfilename) !************************************************************ !fills t1%dat !--------------------------------------input type(table1) :: t1 integer :: skip,col character(LEN=*) :: fullfilename !-----------------------------------internal integer :: i,n double precision :: xdummy,xdummy_store !------------------------------------------- t1%dat=0.0D0 open(file_id_1, file=(trim(fullfilename))) do i=1,skip read(file_id_1,*) !skip lines enddo xdummy_store = t1%xmin-t1%sep do i=1,t1%nx read(file_id_1,*)xdummy,(t1%dat(i,n),n=1,col-1) ! if(minval(t1%dat(i,:)).lt.0) then ! write(*,*) xdummy,minval(t1%dat(i,:)) ! endif ! checks that x are evenly spaced as expected if((abs(xdummy-xdummy_store-t1%sep).gt.1.0D-7) & & .or.(abs(xdummy-(t1%xmin+dble(i-1)*t1%sep)).gt.1.0D-7))then write(*,*)i,t1%id,xdummy,t1%xmin+dble(i-1)*t1%sep stop 'error in read_tabletype1 (a1)' endif xdummy_store=xdummy enddo if(abs(xdummy-t1%xmax).gt.1.0D-7)stop 'error in read_tabletype1 (a2)' close(file_id_1) end subroutine read_tabletype1 !************************************************************ end module S95tables_type1 !************************************************************ Index: trunk/HiggsBounds-5/S95tables_type2.F90 =================================================================== --- trunk/HiggsBounds-5/S95tables_type2.F90 (revision 600) +++ trunk/HiggsBounds-5/S95tables_type2.F90 (revision 601) @@ -1,1098 +1,1098 @@ ! This file is part of HiggsBounds ! -KW !****************************************************************** module S95tables_type2 !****************************************************************** use S95tables_type1 implicit none !#define fast !table type 2------------------------------ type table2 logical :: needs_M2_gt_2M1 integer :: id,nx1,nx2,particle_x1,particle_x2 !see usefulbits.f90 for key to particle codes n.b. they're NOT pdg character(LEN=45) :: label character(LEN=3) :: expt double precision :: lumi, energy double precision :: xmax1,xmin1,xmax2,xmin2,sep1,sep2,deltax double precision, allocatable :: dat(:,:,:) !in dat(a,b,1:2)...obs=1,pred=2. 1st component of dat is y, 2nd is x double precision :: maxdatval double precision :: z !only used in slices_t2 end type integer,parameter :: file_id_2_exp=10 !same as file_id_common in usefulbits.f90 integer,parameter :: file_id_2_obs=11 !------------------------------------------ contains !************************************************************ subroutine initializetables_type2_blank(tablet2) !*********************************************************** ! still leaves dat unallocated integer:: i type(table2) :: tablet2(:) do i=lbound(tablet2,dim=1),ubound(tablet2,dim=1) tablet2(i)%id = -1 tablet2(i)%nx1 = -1 tablet2(i)%nx2 = -1 tablet2(i)%particle_x1 = -1 tablet2(i)%particle_x2 = -1 tablet2(i)%label = '' tablet2(i)%expt = '' tablet2(i)%lumi = -1.0D0 tablet2(i)%energy = -1.0D0 tablet2(i)%xmax1 = -1.0D0 tablet2(i)%xmax2 = -1.0D0 tablet2(i)%xmin1 = -1.0D0 tablet2(i)%xmin2 = -1.0D0 tablet2(i)%sep1 = -1.0D0 tablet2(i)%sep2 = -1.0D0 tablet2(i)%deltax = -1.0D0 tablet2(i)%maxdatval = -1.0D0 tablet2(i)%z = -1.0D9 !only used in slices_t2 tablet2(i)%needs_M2_gt_2M1 = .False. enddo end subroutine initializetables_type2_blank !*********************************************************** subroutine initializetables2(S95_t2) !*********************************************************** ! fills S95_t2 !*********************************************************** use store_pathname use usefulbits, only: Hneut,Hplus,Chineut,Chiplus,small,file_id_common2,not_a_particle implicit none !--------------------------------------input type(table2) :: S95_t2(:) !-----------------------------------internal integer :: i,tno,j,x,xbeg,xend,k,ios character(LEN=2) :: tableno character(len=100),allocatable :: filename(:) double precision :: dummy double precision, allocatable :: testrow(:) integer :: file_id_arr(2) double precision :: maxdatval !------------------------------------------- file_id_arr(1)=file_id_2_exp file_id_arr(2)=file_id_2_obs xbeg=lbound(S95_t2,dim=1) xend=ubound(S95_t2,dim=1) allocate(filename(xbeg:xend)) x=xbeg-1 tno=14 do i=1,8 x=x+1 tno=tno+1 if((x.eq.3).or.(x.eq.7))tno=tno+1 write(tableno,'(I2)')tno S95_t2(x)%id=tno*10 S95_t2(x)%expt='LEP' S95_t2(x)%energy=0.208D0 S95_t2(x)%deltax=0.0D0 S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut select case(S95_t2(x)%id) case(220,230,240) S95_t2(x)%label='hep-ex/0602042 (LEP)' case default S95_t2(x)%label='hep-ex/0602042, table '//tableno//' (LEP)' end select S95_t2(x)%sep1=1.0D0 S95_t2(x)%sep2=1.0D0 S95_t2(x)%maxdatval = 1.0D2 !S95_t2(x)%OBid=x+2 select case(S95_t2(x)%id) case(150,160,220) S95_t2(x)%xmin1=1.0D0 S95_t2(x)%xmax1=60.0D0 S95_t2(x)%xmin2=2.0D0 S95_t2(x)%xmax2=120.0D0 S95_t2(x)%needs_M2_gt_2M1=.True. case(180,190,230,240) S95_t2(x)%xmin1=1.0D0 S95_t2(x)%xmax1=180.0D0 S95_t2(x)%xmin2=1.0D0 S95_t2(x)%xmax2=180.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. case(200,210) S95_t2(x)%xmin1=1.0D0 S95_t2(x)%xmax1=90.0D0 S95_t2(x)%xmin2=2.0D0 S95_t2(x)%xmax2=180.0D0 S95_t2(x)%needs_M2_gt_2M1=.True. case default write(*,*)'error in initializetables2 (a)' stop end select filename(x)='table'//tableno//'full' enddo do i=5,10 x=x+1 tno=i write(tableno,'(I2)')tno S95_t2(x)%id=900+tno S95_t2(x)%expt='LEP' S95_t2(x)%energy=0.208D0 S95_t2(x)%deltax=0.0D0 S95_t2(x)%label='hep-ex/0401026, fig '//trim(adjustl(tableno))//' (OPAL)' S95_t2(x)%sep1=1.0D0 S95_t2(x)%sep2=1.0D0 S95_t2(x)%maxdatval = 1.0D6 !these tables are in fb select case(tno) case(5,6,7,8) S95_t2(x)%xmin1=0.0D0 S95_t2(x)%xmax1=100.0D0 S95_t2(x)%xmin2=75.0D0 S95_t2(x)%xmax2=120.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=Chineut S95_t2(x)%particle_x2=Chiplus case(9,10) S95_t2(x)%xmin1=0.0D0 S95_t2(x)%xmax1=100.0D0 S95_t2(x)%xmin2=50.0D0 S95_t2(x)%xmax2=200.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=Chineut S95_t2(x)%particle_x2=Chineut case default write(*,*)'error in initializetables2 (b)' stop end select filename(x)='1026_fig'//trim(adjustl(tableno)) enddo x=x+1 S95_t2(x)%id=6065 S95_t2(x)%expt='LEP' S95_t2(x)%energy=0.208D0 S95_t2(x)%deltax=0.0D0 S95_t2(x)%label='[hep-ex] arXiv:1301.6065 (LEP)' S95_t2(x)%sep1=0.1D0 S95_t2(x)%sep2=0.5D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.0D0 S95_t2(x)%xmax1=1.0D0 S95_t2(x)%xmin2=43.0D0 S95_t2(x)%xmax2=95.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hplus filename(x)="6065_LEP_HpHm_fig4" x=x+1 S95_t2(x)%id=02671 S95_t2(x)%expt='LEP' S95_t2(x)%energy=0.208D0 S95_t2(x)%deltax=0.0D0 S95_t2(x)%label='[hep-ex] arXiv:0812.0267, Fig.10a (OPAL,LEP)' S95_t2(x)%sep1=0.5D0 S95_t2(x)%sep2=0.5D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=12.0D0 S95_t2(x)%xmax1=90.0D0 S95_t2(x)%xmin2=40.0D0 S95_t2(x)%xmax2=93.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hplus filename(x)="OPAL_H+H-_AWAW_0267" x=x+1 S95_t2(x)%id=02672 S95_t2(x)%expt='LEP' S95_t2(x)%energy=0.208D0 S95_t2(x)%deltax=0.0D0 S95_t2(x)%label='[hep-ex] arXiv:0812.0267, Fig.10b (OPAL,LEP)' S95_t2(x)%sep1=0.5D0 S95_t2(x)%sep2=0.5D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=12.0D0 S95_t2(x)%xmax1=77.0D0 S95_t2(x)%xmin2=40.0D0 S95_t2(x)%xmax2=80.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hplus filename(x)="OPAL_H+H-_AWtaunu_0267" x=x+1 S95_t2(x)%id=3381 S95_t2(x)%expt=' D0' S95_t2(x)%energy=1.96D0 S95_t2(x)%deltax=0.0D0 S95_t2(x)%label='[hep-ex] arXiv:0905.3381, table I (D0)' S95_t2(x)%sep1=0.1D0 S95_t2(x)%sep2=5.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.2D0 S95_t2(x)%xmax1=3.0D0 S95_t2(x)%xmin2=80.0D0 S95_t2(x)%xmax2=200.0D0 S95_t2(x)%needs_M2_gt_2M1=.True. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)="D0_h-aa-mumumumu_3381" x=x+1 S95_t2(x)%id=3382 S95_t2(x)%expt=' D0' S95_t2(x)%energy=1.96D0 S95_t2(x)%deltax=0.0D0 S95_t2(x)%label='[hep-ex] arXiv:0905.3381, table II (D0)' S95_t2(x)%sep1=0.2D0 S95_t2(x)%sep2=5.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=3.6D0 S95_t2(x)%xmax1=19.0D0 S95_t2(x)%xmin2=85.0D0 S95_t2(x)%xmax2=200.0D0 S95_t2(x)%needs_M2_gt_2M1=.True. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)="D0_h-aa-tautaumumu_3381" x=x+1 S95_t2(x)%id=6227 S95_t2(x)%expt=' D0' S95_t2(x)%label='D0 Note 6227' S95_t2(x)%energy=1.96D0 S95_t2(x)%sep1=0.04D0 S95_t2(x)%sep2=10.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.06D0 S95_t2(x)%xmax1=0.18D0 S95_t2(x)%xmin2=90.0D0 S95_t2(x)%xmax2=300.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hneut filename(x)='D0_h-bb_h-tautau_comb_5.2-7.3fb_6227' x=x+1 S95_t2(x)%id=5053 S95_t2(x)%expt='ATL' S95_t2(x)%label='[hep-ex] arXiv:1406.5053 (ATLAS)' S95_t2(x)%energy=8.0D0 S95_t2(x)%sep1=5.0D0 S95_t2(x)%sep2=5.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=120.0D0 S95_t2(x)%xmax1=130.0D0 S95_t2(x)%xmin2=260.0D0 S95_t2(x)%xmax2=500.0D0 S95_t2(x)%needs_M2_gt_2M1=.True. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='5053_H-hh-gagabb_20fb-1' ! x=x+1 ! S95_t2(x)%id=13032 ! S95_t2(x)%expt='CMS' ! S95_t2(x)%label='CMS-PAS-HIG-13-032' ! S95_t2(x)%energy=8.0D0 ! S95_t2(x)%sep1=5.0D0 ! S95_t2(x)%sep2=1.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=120.0D0 ! S95_t2(x)%xmax1=130.0D0 ! S95_t2(x)%xmin2=260.0D0 ! S95_t2(x)%xmax2=1100.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='13032_H-hh-gagabb_19.7fb-1' x=x+1 S95_t2(x)%id=06896 S95_t2(x)%expt='CMS' S95_t2(x)%label='[hep-ex] arXiv:1603.06896 (CMS)' S95_t2(x)%energy=8.0D0 S95_t2(x)%sep1=5.0D0 S95_t2(x)%sep2=1.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=120.0D0 S95_t2(x)%xmax1=130.0D0 S95_t2(x)%xmin2=260.0D0 S95_t2(x)%xmax2=1100.0D0 S95_t2(x)%needs_M2_gt_2M1=.True. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='06896_H-hh-gagabb_19.7fb-1' ! x=x+1 ! S95_t2(x)%id=011811 ! S95_t2(x)%expt='CMS' ! S95_t2(x)%label='[hep-ex] arXiv:1510.01181 (CMS)' ! S95_t2(x)%energy=8.0D0 ! S95_t2(x)%sep1=10.0D0 ! S95_t2(x)%sep2=10.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=115.0D0 ! S95_t2(x)%xmax1=135.0D0 ! S95_t2(x)%xmin2=260.0D0 ! S95_t2(x)%xmax2=350.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='140341_CMS_H-hh-bbtautau_19.7fb-1' ! x=x+1 ! S95_t2(x)%id=044781 ! S95_t2(x)%expt='ATLAS' ! S95_t2(x)%label='[hep-ex] arXiv:1502.04478 (ATLAS)' ! S95_t2(x)%energy=8.0D0 ! S95_t2(x)%sep1=10.0D0 ! S95_t2(x)%sep2=10.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=115.0D0 ! S95_t2(x)%xmax1=135.0D0 ! S95_t2(x)%xmin2=220.0D0 ! S95_t2(x)%xmax2=1000.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='044781_ATLAS_gg-A-hZ-tautaull_20.3fb-1' ! ! x=x+1 ! S95_t2(x)%id=044782 ! S95_t2(x)%expt='ATLAS' ! S95_t2(x)%label='[hep-ex] arXiv:1502.04478 (ATLAS)' ! S95_t2(x)%energy=8.0D0 ! S95_t2(x)%sep1=10.0D0 ! S95_t2(x)%sep2=10.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=115.0D0 ! S95_t2(x)%xmax1=135.0D0 ! S95_t2(x)%xmin2=220.0D0 ! S95_t2(x)%xmax2=1000.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='044782_ATLAS_gg-A-hZ-bbll_20.3fb-1' ! x=x+1 ! S95_t2(x)%id=011812 ! S95_t2(x)%expt='CMS' ! S95_t2(x)%label='[hep-ex] arXiv:1510.01181 (CMS)' ! S95_t2(x)%energy=8.0D0 ! S95_t2(x)%sep1=10.0D0 ! S95_t2(x)%sep2=10.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=115.0D0 ! S95_t2(x)%xmax1=135.0D0 ! S95_t2(x)%xmin2=220.0D0 ! S95_t2(x)%xmax2=350.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='140342_CMS_A-hZ-tautaull_19.7fb-1' ! x=x+1 ! S95_t2(x)%id=20160151 ! S95_t2(x)%expt='ATLAS' ! S95_t2(x)%label='ATLAS-CONF-2016-015' ! S95_t2(x)%energy=13.0D0 ! S95_t2(x)%sep1=10.0D0 ! S95_t2(x)%sep2=10.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=115.0D0 ! S95_t2(x)%xmax1=135.0D0 ! S95_t2(x)%xmin2=220.0D0 ! S95_t2(x)%xmax2=2000.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='20160151_ATLAS_gg-A-hZ-bbll_3.2fb-1' ! ! x=x+1 ! S95_t2(x)%id=20160152 ! S95_t2(x)%expt='ATLAS' ! S95_t2(x)%label='ATLAS-CONF-2016-015' ! S95_t2(x)%energy=13.0D0 ! S95_t2(x)%sep1=10.0D0 ! S95_t2(x)%sep2=10.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=115.0D0 ! S95_t2(x)%xmax1=135.0D0 ! S95_t2(x)%xmin2=220.0D0 ! S95_t2(x)%xmax2=2000.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='20160152_ATLAS_bb-A-hZ-bbll_3.2fb-1' ! ! x=x+1 ! S95_t2(x)%id=16002 ! S95_t2(x)%expt='CMS' ! S95_t2(x)%label='CMS-PAS-HIG-16-002' ! S95_t2(x)%energy=13.0D0 ! S95_t2(x)%sep1=10.0D0 ! S95_t2(x)%sep2=5.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=115.0D0 ! S95_t2(x)%xmax1=135.0D0 ! S95_t2(x)%xmin2=260.0D0 ! S95_t2(x)%xmax2=1200.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='16002_CMS_H-hh-bbbb_2.3fb-1' ! ! x=x+1 ! S95_t2(x)%id=16029 ! S95_t2(x)%expt='CMS' ! S95_t2(x)%label='CMS-PAS-HIG-16-029' ! S95_t2(x)%energy=13.0D0 ! S95_t2(x)%sep1=10.0D0 ! S95_t2(x)%sep2=10.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=115.0D0 ! S95_t2(x)%xmax1=135.0D0 ! S95_t2(x)%xmin2=250.0D0 ! S95_t2(x)%xmax2=900.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='16029_CMS_H-hh-bbtautau_12.9fb-1' ! ! x=x+1 ! S95_t2(x)%id=14013 ! S95_t2(x)%expt='CMS' ! S95_t2(x)%label='CMS-PAS-HIG-14-013,arXiv:1503.04114 (CMS)' ! S95_t2(x)%energy=8.0D0 ! S95_t2(x)%sep1=5.0D0 ! S95_t2(x)%sep2=1.0D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=120.0D0 ! S95_t2(x)%xmax1=130.0D0 ! S95_t2(x)%xmin2=270.0D0 ! S95_t2(x)%xmax2=1097.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.True. ! S95_t2(x)%particle_x1=Hneut ! S95_t2(x)%particle_x2=Hneut ! filename(x)='14013_H-hh-bbbb_17.9fb-1' x=x+1 S95_t2(x)%id=16032 S95_t2(x)%expt='CMS' S95_t2(x)%label='CMS-PAS-HIG-16-032' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=2.5D0 S95_t2(x)%sep2=1.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=122.5D0 S95_t2(x)%xmax1=127.5D0 S95_t2(x)%xmin2=250.0D0 S95_t2(x)%xmax2=900.0D0 S95_t2(x)%needs_M2_gt_2M1=.True. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='16032_CMS_H-hh-gagabb_2.70fb-1' x=x+1 S95_t2(x)%id=14022 S95_t2(x)%expt='CMS' S95_t2(x)%label='CMS-PAS-HIG-14-022' S95_t2(x)%energy=8.0D0 S95_t2(x)%sep1=1.0D0 S95_t2(x)%sep2=2.5D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=5.0D0 S95_t2(x)%xmax1=15.0D0 S95_t2(x)%xmin2=122.5D0 S95_t2(x)%xmax2=127.5D0 S95_t2(x)%needs_M2_gt_2M1=.True. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='14022_H-hh-tautau_19.7fb-1' x=x+1 S95_t2(x)%id=150600424 S95_t2(x)%expt='CMS' S95_t2(x)%label='arXiv:1506.00424 (CMS)' S95_t2(x)%energy=8.0D0 S95_t2(x)%sep1=0.05D0 S95_t2(x)%sep2=1.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.25D0 S95_t2(x)%xmax1=3.55D0 S95_t2(x)%xmin2=86.0D0 S95_t2(x)%xmax2=150.0D0 S95_t2(x)%needs_M2_gt_2M1=.True. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='150600424_CMS_H-aa-mumu' x=x+1 S95_t2(x)%id=16035 S95_t2(x)%expt='CMS' S95_t2(x)%label='CMS-PAS-HIG-16-035' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=0.05D0 S95_t2(x)%sep2=1.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.25D0 S95_t2(x)%xmax1=3.55D0 S95_t2(x)%xmin2=86.0D0 S95_t2(x)%xmax2=150.0D0 S95_t2(x)%needs_M2_gt_2M1=.True. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='16035_CMS_H-aa-mumumu_2.8fb-1' x=x+1 S95_t2(x)%id=02301 S95_t2(x)%expt='CMS' S95_t2(x)%label='[hep-ex] arXiv:1506.02301 (CMS)' S95_t2(x)%energy=8.0D0 S95_t2(x)%sep1=0.01D0 S95_t2(x)%sep2=10.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.00D0 S95_t2(x)%xmax1=0.10D0 S95_t2(x)%xmin2=150.0D0 S95_t2(x)%xmax2=840.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hneut filename(x)='14006_CMS_h-gaga_2D' x=x+1 S95_t2(x)%id=003892 S95_t2(x)%expt='ATL' S95_t2(x)%label='[hep-ex] arXiv:1509.00389 (ATLAS)' S95_t2(x)%energy=8.0D0 S95_t2(x)%sep1=0.05D0 S95_t2(x)%sep2=100.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.20D0 S95_t2(x)%xmax1=0.80D0 S95_t2(x)%xmin2=300.0D0 S95_t2(x)%xmax2=1000.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hneut filename(x)='00389_H-WW_20.3fb-1_2D' x=x+1 S95_t2(x)%id=20160791 S95_t2(x)%expt='ATL' S95_t2(x)%label='ATLAS-CONF-2016-079' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=0.01D0 S95_t2(x)%sep2=1.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.0D0 S95_t2(x)%xmax1=0.10D0 S95_t2(x)%xmin2=400.0D0 S95_t2(x)%xmax2=1000.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hneut filename(x)='20160791_gg-H-ZZ-4l_14.8fb-1' x=x+1 S95_t2(x)%id=01123 S95_t2(x)%expt='ATL' S95_t2(x)%label='arXiv:1710.01123 (ATLAS)' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=5.0D0 S95_t2(x)%sep2=100.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=5.0D0 S95_t2(x)%xmax1=15.0D0 S95_t2(x)%xmin2=200.0D0 S95_t2(x)%xmax2=4000.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hneut filename(x)='01123_ATLAS_gg-H-WW-e_nu_mu_nu_36.1fb-1' ! x=x+1 ! S95_t2(x)%id=160331 ! S95_t2(x)%expt='CMS' ! S95_t2(x)%label='CMS-PAS-HIG 16-033' ! S95_t2(x)%energy=13.0D0 ! S95_t2(x)%sep1=2.0D0 ! S95_t2(x)%sep2=0.1D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=0.0D0 ! S95_t2(x)%xmax1=40.0D0 ! S95_t2(x)%xmin2=130.0D0 ! S95_t2(x)%xmax2=2520.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.False. ! S95_t2(x)%particle_x1=not_a_particle ! S95_t2(x)%particle_x2=Hneut ! filename(x)='160331_CMS_H-ZZ-4l_ggF_12.9fb-1' x=x+1 S95_t2(x)%id=06386 S95_t2(x)%expt='ATLAS' S95_t2(x)%label='arXiv:1712.06386 (ATLAS)' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=0.01D0 S95_t2(x)%sep2=1.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.0D0 S95_t2(x)%xmax1=.10D0 S95_t2(x)%xmin2=400.0D0 S95_t2(x)%xmax2=1000.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hneut filename(x)='06386_ATLAS_gg-H-ZZ-4l+2l2nu_36.1fb-1' x=x+1 S95_t2(x)%id=170121 S95_t2(x)%expt='CMS' S95_t2(x)%label='CMS-PAS-HIG 17-012' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=10.0D0 S95_t2(x)%sep2=10.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.0D0 S95_t2(x)%xmax1=100.0D0 S95_t2(x)%xmin2=130.0D0 S95_t2(x)%xmax2=3000.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hneut filename(x)='17012_CMS_gg-H-ZZ_35.9fb-1' x=x+1 S95_t2(x)%id=160332 S95_t2(x)%expt='CMS' S95_t2(x)%label='CMS-PAS-HIG 16-033' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=2.0D0 S95_t2(x)%sep2=0.1D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.0D0 S95_t2(x)%xmax1=40.0D0 S95_t2(x)%xmin2=130.0D0 S95_t2(x)%xmax2=2520.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hneut filename(x)='160332_CMS_H-ZZ-4l_VBF_12.9fb-1' x=x+1 S95_t2(x)%id=150011 S95_t2(x)%expt='CMS' S95_t2(x)%label='CMS-PAS-HIG-15-001,arXiv:1603.02991 (CMS)' S95_t2(x)%energy=8.0D0 S95_t2(x)%sep1=5.0D0 S95_t2(x)%sep2=5.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=15.0D0 S95_t2(x)%xmax1=1000.0D0 S95_t2(x)%xmin2=15.0D0 S95_t2(x)%xmax2=1000.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='150011_H2-ZH1-lltautau_19.8fb-1' x=x+1 S95_t2(x)%id=150012 S95_t2(x)%expt='CMS' S95_t2(x)%label='CMS-PAS-HIG-15-001,arXiv:1603.02991 (CMS)' S95_t2(x)%energy=8.0D0 S95_t2(x)%sep1=2.4D0 S95_t2(x)%sep2=2.4D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=24.0D0 S95_t2(x)%xmax1=1200.0D0 S95_t2(x)%xmin2=24.0D0 S95_t2(x)%xmax2=1200.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='150012_H2-ZH1-llbb_19.8fb-1' x=x+1 S95_t2(x)%id=16010 S95_t2(x)%expt='CMS' S95_t2(x)%label='CMS-PAS-HIG-16-010' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=5.0D0 S95_t2(x)%sep2=5.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=50.0D0 S95_t2(x)%xmax1=600.0D0 S95_t2(x)%xmin2=300.0D0 S95_t2(x)%xmax2=700.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='16010_H2-ZH1-llbb_2.3fb-1' ! x=x+1 ! S95_t2(x)%id=2016059 ! S95_t2(x)%expt='ATLAS' ! S95_t2(x)%label='ATLAS-CONF-2016-059' ! S95_t2(x)%energy=13.0D0 ! S95_t2(x)%sep1=0.02D0 ! S95_t2(x)%sep2=0.5D0 ! S95_t2(x)%maxdatval=1.0D6 ! S95_t2(x)%xmin1=0.00D0 ! S95_t2(x)%xmax1=0.10D0 ! S95_t2(x)%xmin2=200.0D0 ! S95_t2(x)%xmax2=2400.0D0 ! S95_t2(x)%needs_M2_gt_2M1=.False. ! S95_t2(x)%particle_x1=not_a_particle ! S95_t2(x)%particle_x2=Hneut ! filename(x)='2016059_Atlas_pp-H-gaga_15.4fb-1' x=x+1 S95_t2(x)%id=4147 S95_t2(x)%expt='ATLAS' S95_t2(x)%label='[hep-ex] arXiv:1707.04147 (ATLAS)' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=0.02D0 S95_t2(x)%sep2=0.5D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=0.00D0 S95_t2(x)%xmax1=0.10D0 S95_t2(x)%xmin2=200.0D0 S95_t2(x)%xmax2=2700.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=not_a_particle S95_t2(x)%particle_x2=Hneut filename(x)='4147_Atlas_pp-H-gaga_36.7fb-1' ! By DDD, Nov 8 2018 x=x+1 S95_t2(x)%id=20160341 S95_t2(x)%expt='ATLAS' - S95_t2(x)%label='ATLAS-EXOT-2016-034, bbh' + S95_t2(x)%label='[hep-ex] 1804.01126 (ATLAS), bbh' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=10.0D0 S95_t2(x)%sep2=10.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=130.0D0 S95_t2(x)%xmax1=700.0D0 S95_t2(x)%xmin2=230.0D0 S95_t2(x)%xmax2=800.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='20160341_ATLAS_A_HZ_llbb_36.1fb-1_bbh' ! By DDD, Nov 8 2018 x=x+1 S95_t2(x)%id=20160342 S95_t2(x)%expt='ATLAS' - S95_t2(x)%label='ATLAS-EXOT-2016-034, ggf' + S95_t2(x)%label='[hep-ex] 1804.01126 (ATLAS), ggf' S95_t2(x)%energy=13.0D0 S95_t2(x)%sep1=10.0D0 S95_t2(x)%sep2=10.0D0 S95_t2(x)%maxdatval=1.0D6 S95_t2(x)%xmin1=130.0D0 S95_t2(x)%xmax1=700.0D0 S95_t2(x)%xmin2=230.0D0 S95_t2(x)%xmax2=800.0D0 S95_t2(x)%needs_M2_gt_2M1=.False. S95_t2(x)%particle_x1=Hneut S95_t2(x)%particle_x2=Hneut filename(x)='20160342_ATLAS_A_HZ_llbb_36.1fb-1_ggf' ! checks we've filled the whole array if(x.ne.xend)then write(*,*)'error in initializetables2 (c)',x,xend stop endif ! read in the tables do x=xbeg,xend S95_t2(x)%nx2=nint((S95_t2(x)%xmax2-S95_t2(x)%xmin2)/S95_t2(x)%sep2)+1 S95_t2(x)%nx1=nint((S95_t2(x)%xmax1-S95_t2(x)%xmin1)/S95_t2(x)%sep1)+1 allocate(S95_t2(x)%dat(S95_t2(x)%nx2,S95_t2(x)%nx1,2)) enddo ! read in the tables open(file_id_common2,file = trim(adjustl(pathname))//'Expt_tables/' // & & 'S95_t2.binary',form='unformatted') read(file_id_common2,iostat=ios)S95_t2(xbeg)%dat if(ios.eq.0)then do x=xbeg+1,xend read(file_id_common2)S95_t2(x)%dat enddo else do x=xbeg,xend open(file_id_2_exp,file=trim(adjustl(pathname))//('Expt_tables/' & //trim(adjustl(S95_t2(x)%expt))//'tables/' & //trim(adjustl(S95_t2(x)%expt))//'tables2/' & //trim(adjustl(filename(x)))//'_pred.txt')) open(file_id_2_obs,file=trim(adjustl(pathname))//('Expt_tables/' & //trim(adjustl(S95_t2(x)%expt))//'tables/' & //trim(adjustl(S95_t2(x)%expt))//'tables2/' & //trim(adjustl(filename(x)))//'_obs.txt')) ! fill S95 from file ! row 0 and column 0 in LEP file contain higgs masses ! and (0,0) ie top left set to -100 ! so avoid them allocate(testrow(0:S95_t2(x)%nx1)) do k=lbound(file_id_arr,dim=1),ubound(file_id_arr,dim=1) read(file_id_arr(k),*)( testrow(i), i=0,S95_t2(x)%nx1 ) if((testrow(0)+100.0D0).gt.small)stop 'error in initializetables2 (d)' !top left number should be -100 do i=1,S95_t2(x)%nx1 if( abs(testrow(i)- (S95_t2(x)%xmin1 + dble(i-1)*S95_t2(x)%sep1) ).gt.small*S95_t2(x)%sep1 )then write(*,*)S95_t2(x)%id,testrow(i),(S95_t2(x)%xmin1 + dble(i-1)*S95_t2(x)%sep1) stop 'error in initializetables2 (e)' endif enddo enddo deallocate(testrow) do j=1,S95_t2(x)%nx2 read(file_id_2_exp,*) dummy, ( S95_t2(x)%dat(j,i,2), i=1,S95_t2(x)%nx1 ) if( abs(dummy- (S95_t2(x)%xmin2 + dble(j-1)*S95_t2(x)%sep2) ).gt.small*S95_t2(x)%sep2 ) then ! write(*,*) S95_t2(x)%nx1, dummy, S95_t2(x)%dat(j,:,2) ! write(*,*) j,S95_t2(x)%nx2 ,S95_t2(x)%xmin2 + dble(j-1)*S95_t2(x)%sep2 stop 'error in initializetables2 (f)' endif read(file_id_2_obs,*) dummy, ( S95_t2(x)%dat(j,i,1), i=1,S95_t2(x)%nx1 ) if( abs(dummy- (S95_t2(x)%xmin2 + dble(j-1)*S95_t2(x)%sep2) ).gt.small*S95_t2(x)%sep2 ) then write(*,*) "Problematic analysis: ",S95_t2(x)%id stop 'error in initializetables2 (g)' endif end do maxdatval=S95_t2(x)%maxdatval if( maxdatval .gt. 0.0D0 )then ! set entries .ge. S95_t2(x)%maxdatval to (-4): they will not be relevent where( S95_t2(x)%dat .ge. maxdatval ) S95_t2(x)%dat= - 4.0D0 endif close(file_id_2_exp) close(file_id_2_obs) enddo rewind(file_id_common2) #ifndef WEBVERSION do x=xbeg,xend write(file_id_common2)S95_t2(x)%dat enddo #endif endif close(file_id_common2) deallocate(filename) end subroutine initializetables2 !*********************************************************** function t2elementnumberfromid(t2,id) !--------------------------------------input type(table2), intent(in) :: t2(:) integer, intent(in) :: id !-----------------------------------function integer :: t2elementnumberfromid !-----------------------------------internal integer :: n,x !------------------------------------------- n=0 do x=lbound(t2,dim=1),ubound(t2,dim=1) if(t2(x)%id.eq.id)then n=n+1 t2elementnumberfromid=x endif enddo if(n.ne.1)stop 'problem in function t2elementnumberfromid 1' end function t2elementnumberfromid !*********************************************************** subroutine fill_slices_t1_from_slices_of_t2(t2,v1orv2,xy_selection,ftype_selection,slices_t1) ! if this subroutine is used, ! don't forget to deallocate slices_t1(x)%dat at some point !*********************************************************** implicit none !--------------------------------------input type(table2), intent(in) :: t2 integer, intent(in) :: v1orv2 integer, intent(in) :: xy_selection(:) integer, intent(in) :: ftype_selection(:) !-------------------------------------output type(table1) :: slices_t1(:) !i.e. 2 slices !-----------------------------------internal integer :: i,j,k,n integer :: n_ftype_selection !------------------------------------------- n_ftype_selection=ubound(ftype_selection,dim=1) do n=lbound(ftype_selection,dim=1),n_ftype_selection if(ftype_selection(n).lt.lbound(t2%dat,dim=3))stop 'problem in fill_slices_t1_from_slices_of_t2 3a' if(ftype_selection(n).gt.ubound(t2%dat,dim=3))stop 'problem in fill_slices_t1_from_slices_of_t2 3b' enddo if(lbound(xy_selection,dim=1).ne.lbound(slices_t1,dim=1))then stop 'problem in fill_slices_t1_from_slices_of_t2 1a' endif if(ubound(xy_selection,dim=1).ne.ubound(slices_t1,dim=1))then stop 'problem in fill_slices_t1_from_slices_of_t2 1b' endif select case(v1orv2) case(1) do n=lbound(slices_t1,dim=1),ubound(slices_t1,dim=1) if(xy_selection(n).lt.lbound(t2%dat,dim=1))stop 'problem in fill_slices_t1_from_slices_of_t2 4a' if(xy_selection(n).gt.ubound(t2%dat,dim=1))stop 'problem in fill_slices_t1_from_slices_of_t2 4b' slices_t1(n)%id = t2%id slices_t1(n)%nx = t2%nx1 slices_t1(n)%xmax = t2%xmax1 slices_t1(n)%xmin = t2%xmin1 slices_t1(n)%sep = t2%sep1 slices_t1(n)%deltax = t2%deltax allocate( slices_t1(n)%dat(slices_t1(n)%nx,n_ftype_selection) ) slices_t1(n)%dat = -1.0D0 do i=1,slices_t1(n)%nx do k=1,n_ftype_selection slices_t1(n)%dat(i,k)=t2%dat(xy_selection(n),i,ftype_selection(k)) enddo enddo enddo case(2) do n=lbound(slices_t1,dim=1),ubound(slices_t1,dim=1) if(xy_selection(n).lt.lbound(t2%dat,dim=2))stop 'problem in fill_slices_t1_from_slices_of_t2 4aa' if(xy_selection(n).gt.ubound(t2%dat,dim=2))stop 'problem in fill_slices_t1_from_slices_of_t2 4bb' slices_t1(n)%id = t2%id slices_t1(n)%nx = t2%nx2 slices_t1(n)%xmax = t2%xmax2 slices_t1(n)%xmin = t2%xmin2 slices_t1(n)%sep = t2%sep2 slices_t1(n)%deltax = t2%deltax allocate( slices_t1(n)%dat(slices_t1(n)%nx,n_ftype_selection) ) slices_t1(n)%dat = -1.0D0 do j=1,slices_t1(n)%nx do k=1,n_ftype_selection slices_t1(n)%dat(j,k)=t2%dat(j,xy_selection(n),ftype_selection(k)) enddo enddo enddo case default stop 'problem in fill_slices_t1_from_slices_of_t2 5' end select end subroutine fill_slices_t1_from_slices_of_t2 !*********************************************************** !*********************************************************** subroutine fill_t1_from_t2(t2,v1orv2,xy_selection,ftype_selection,t1) ! if this subroutine is used, ! don't forget to deallocate slices_t1(x)%dat at some point !*********************************************************** implicit none !--------------------------------------input type(table2), intent(in) :: t2 integer, intent(in) :: v1orv2 integer, intent(in) :: xy_selection integer, intent(in) :: ftype_selection(:) !-------------------------------------output type(table1) :: t1 !-----------------------------------internal integer :: i,j,k,n integer :: n_ftype_selection !------------------------------------------- n_ftype_selection=ubound(ftype_selection,dim=1) do n=lbound(ftype_selection,dim=1),n_ftype_selection if(ftype_selection(n).lt.lbound(t2%dat,dim=3))stop 'problem in fill_t1_from_t2 3a' if(ftype_selection(n).gt.ubound(t2%dat,dim=3))stop 'problem in fill_t1_from_t2 3b' enddo t1%id = t2%id t1%deltax = t2%deltax select case(v1orv2) case(1) if(xy_selection.lt.lbound(t2%dat,dim=1))stop 'problem in fill_t1_from_t2 4a' if(xy_selection.gt.ubound(t2%dat,dim=1))stop 'problem in fill_t1_from_t2 4b' t1%nx = t2%nx1 t1%xmax = t2%xmax1 t1%xmin = t2%xmin1 t1%sep = t2%sep1 allocate( t1%dat(t1%nx,n_ftype_selection) ) t1%dat = -1.0D0 do i=1,t1%nx do k=1,n_ftype_selection t1%dat(i,k)=t2%dat(xy_selection,i,ftype_selection(k)) enddo enddo case(2) if(xy_selection.lt.lbound(t2%dat,dim=2))stop 'problem in fill_t1_from_t2 4aa' if(xy_selection.gt.ubound(t2%dat,dim=2))stop 'problem in fill_t1_from_t2 4bb' t1%nx = t2%nx2 t1%xmax = t2%xmax2 t1%xmin = t2%xmin2 t1%sep = t2%sep2 allocate( t1%dat(t1%nx,n_ftype_selection) ) t1%dat = -1.0D0 do j=1,t1%nx do k=1,n_ftype_selection t1%dat(j,k)=t2%dat(j,xy_selection,ftype_selection(k)) enddo enddo case default stop 'problem in fill_t1_from_t2 5' end select end subroutine fill_t1_from_t2 !*********************************************************** end module S95tables_type2 !************************************************************ Index: trunk/HiggsBounds-5/minipaper.pdf =================================================================== Cannot display: file marked as a binary type. svn:mime-type = application/octet-stream Index: trunk/HiggsBounds-5/usefulbits.f90 =================================================================== --- trunk/HiggsBounds-5/usefulbits.f90 (revision 600) +++ trunk/HiggsBounds-5/usefulbits.f90 (revision 601) @@ -1,1466 +1,1466 @@ ! 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. logical :: wantkey = .True. logical :: extrapolatewidth = .True. ! 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.4.0beta' + character(LEN=9),parameter :: vers='5.4.0upub' 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(:) ! HB-5.2: Needed for the channelrates_matrix ! integer, parameter :: Nprod = 7 ! integer, parameter :: Ndecay = 9 integer, parameter :: Nprod = 11 integer, parameter :: Ndecay = 11 !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_gg_hjZ_ratio(:) ! HB-5 (TS 6.4.2018) double precision, allocatable :: XS_qq_hjZ_ratio(:) ! HB-5 (TS 6.4.2018) 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_gg_HZ_SM(:) ! HB-5 (TS 6.4.2018) double precision, allocatable :: XS_qq_HZ_SM(:) ! HB-5 (TS 6.4.2018) 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_Hpmj(:) ! for Hpm_j production in VBF double precision, allocatable :: XS_Hpmjtb(:) ! for Hpm_j + t + b production double precision, allocatable :: XS_Hpmjcb(:) ! for Hpm_j + c + b production double precision, allocatable :: XS_Hpmjbjet(:) ! for Hpm_j + b + jet production double precision, allocatable :: XS_Hpmjcjet(:) ! for Hpm_j + b + jet production double precision, allocatable :: XS_Hpmjjetjet(:) ! for Hpm_j + jet + jet production double precision, allocatable :: XS_HpmjW(:) ! for Hpm_j + W production double precision, allocatable :: XS_HpmjZ(:) ! for Hpm_j + Z production double precision, allocatable :: XS_HpjHmj(:) ! (j,i), for Hp_j Hm_j production double precision, allocatable :: XS_Hpmjhi(:,:) ! (j,i), for Hpm_j h_i production ! HB-5.2 beyond the narrow-width approximation matrix: holds the SM normalized channel rates ! with the dimensions (N_H, N_production-modes, N_decay-modes) = (N_H, 7, 9), where the ! ordering is the following ! 1: singleH, 2: VBF, 3: WH, 4: ZH, 5: ttH, 6: gg->phi, 7: bb->phi ! 1: gaga, 2: WW, 3: ZZ, 4: tautau, 5:bb, 6: Zga, 7: cc, 8: mumu, 9: gg double precision, allocatable :: channelrates(:,:,:) ! We need a temporary copy for the interface (will be copied in complete_theo) double precision, allocatable :: channelrates_tmp(:,:,:) ! This one holds the corresponding SM rates (in pb), assuming the NWA: double precision, allocatable :: channelrates_SM(:,:,:) 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(*,*)"~ Tobias Klingl, 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" write(*,*)" (arXiv:1210.5347,arXiv:1802.04817)" write(*,*)" * TeV4LHC Higgs Working Group report" write(*,*)" (see arXiv:hep-ph/0612172 and refs. therein)" write(*,*)" * LHC Higgs Cross Section Working Group" write(*,*)" (arXiv:1101.0593, arXiv:1201.3084, arXiv:1307.1347," write(*,*)" arXiv:1610.07922 and refs. therein, including the " write(*,*)" gluon fusion N3LO prediction (arXiv:1602.00695).)" 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_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_gg_hjZ_ratio( np_t(Hneut) )) allocate(d(x)%tev%XS_qq_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_Hpmj( np_t(Hplus) )) allocate(d(x)%tev%XS_Hpmjtb( np_t(Hplus) )) allocate(d(x)%tev%XS_Hpmjcb( np_t(Hplus) )) allocate(d(x)%tev%XS_Hpmjbjet( np_t(Hplus) )) allocate(d(x)%tev%XS_Hpmjcjet( np_t(Hplus) )) allocate(d(x)%tev%XS_Hpmjjetjet( np_t(Hplus) )) allocate(d(x)%tev%XS_HpmjW( np_t(Hplus) )) allocate(d(x)%tev%XS_HpmjZ( np_t(Hplus) )) allocate(d(x)%tev%XS_HpjHmj( np_t(Hplus) )) allocate(d(x)%tev%XS_Hpmjhi( np_t(Hplus), np_t(Hneut) )) allocate(d(x)%tev%channelrates(np_t(Hneut),Nprod,Ndecay)) allocate(d(x)%tev%channelrates_tmp(np_t(Hneut),Nprod,Ndecay)) 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_gg_hjZ_ratio( np_t(Hneut) )) allocate(d(x)%lhc7%XS_qq_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_Hpmj( np_t(Hplus) )) allocate(d(x)%lhc7%XS_Hpmjtb( np_t(Hplus) )) allocate(d(x)%lhc7%XS_Hpmjcb( np_t(Hplus) )) allocate(d(x)%lhc7%XS_Hpmjbjet( np_t(Hplus) )) allocate(d(x)%lhc7%XS_Hpmjcjet( np_t(Hplus) )) allocate(d(x)%lhc7%XS_Hpmjjetjet( np_t(Hplus) )) allocate(d(x)%lhc7%XS_HpmjW( np_t(Hplus) )) allocate(d(x)%lhc7%XS_HpmjZ( np_t(Hplus) )) allocate(d(x)%lhc7%XS_HpjHmj( np_t(Hplus) )) allocate(d(x)%lhc7%XS_Hpmjhi( np_t(Hplus), np_t(Hneut) )) allocate(d(x)%lhc7%channelrates(np_t(Hneut),Nprod,Ndecay)) allocate(d(x)%lhc7%channelrates_tmp(np_t(Hneut),Nprod,Ndecay)) 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_gg_hjZ_ratio( np_t(Hneut) )) allocate(d(x)%lhc8%XS_qq_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_Hpmj( np_t(Hplus) )) allocate(d(x)%lhc8%XS_Hpmjtb( np_t(Hplus) )) allocate(d(x)%lhc8%XS_Hpmjcb( np_t(Hplus) )) allocate(d(x)%lhc8%XS_Hpmjbjet( np_t(Hplus) )) allocate(d(x)%lhc8%XS_Hpmjcjet( np_t(Hplus) )) allocate(d(x)%lhc8%XS_Hpmjjetjet( np_t(Hplus) )) allocate(d(x)%lhc8%XS_HpmjW( np_t(Hplus) )) allocate(d(x)%lhc8%XS_HpmjZ( np_t(Hplus) )) allocate(d(x)%lhc8%XS_HpjHmj( np_t(Hplus) )) allocate(d(x)%lhc8%XS_Hpmjhi( np_t(Hplus), np_t(Hneut) )) allocate(d(x)%lhc8%channelrates(np_t(Hneut),Nprod,Ndecay)) allocate(d(x)%lhc8%channelrates_tmp(np_t(Hneut),Nprod,Ndecay)) 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_gg_hjZ_ratio( np_t(Hneut) )) allocate(d(x)%lhc13%XS_qq_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_Hpmj( np_t(Hplus) )) allocate(d(x)%lhc13%XS_Hpmjtb( np_t(Hplus) )) allocate(d(x)%lhc13%XS_Hpmjcb( np_t(Hplus) )) allocate(d(x)%lhc13%XS_Hpmjbjet( np_t(Hplus) )) allocate(d(x)%lhc13%XS_Hpmjcjet( np_t(Hplus) )) allocate(d(x)%lhc13%XS_Hpmjjetjet( np_t(Hplus) )) allocate(d(x)%lhc13%XS_HpmjW( np_t(Hplus) )) allocate(d(x)%lhc13%XS_HpmjZ( np_t(Hplus) )) allocate(d(x)%lhc13%XS_HpjHmj( np_t(Hplus) )) allocate(d(x)%lhc13%XS_Hpmjhi( np_t(Hplus), np_t(Hneut) )) allocate(d(x)%lhc13%channelrates(np_t(Hneut),Nprod,Ndecay)) allocate(d(x)%lhc13%channelrates_tmp(np_t(Hneut),Nprod,Ndecay)) 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_hjhiZ =0.0D0 d(x)%BR_hkhjhi =0.0D0 d(x)%BR_hjHpiW =0.0D0 d(x)%BR_hjemu =0.0D0 d(x)%BR_hjetau =0.0D0 d(x)%BR_hjmutau =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_Hpmj =0.0D0 d(x)%tev%XS_Hpmjtb =0.0D0 d(x)%tev%XS_Hpmjcb =0.0D0 d(x)%tev%XS_Hpmjbjet =0.0D0 d(x)%tev%XS_Hpmjcjet =0.0D0 d(x)%tev%XS_Hpmjjetjet =0.0D0 d(x)%tev%XS_HpmjW =0.0D0 d(x)%tev%XS_HpmjZ =0.0D0 d(x)%tev%XS_HpjHmj =0.0D0 d(x)%tev%XS_Hpmjhi =0.0D0 d(x)%tev%channelrates = 0.0D0 d(x)%tev%channelrates_tmp = -1.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_Hpmj =0.0D0 d(x)%lhc7%XS_Hpmjtb =0.0D0 d(x)%lhc7%XS_Hpmjcb =0.0D0 d(x)%lhc7%XS_Hpmjbjet =0.0D0 d(x)%lhc7%XS_Hpmjcjet =0.0D0 d(x)%lhc7%XS_Hpmjjetjet =0.0D0 d(x)%lhc7%XS_HpmjW =0.0D0 d(x)%lhc7%XS_HpmjZ =0.0D0 d(x)%lhc7%XS_HpjHmj =0.0D0 d(x)%lhc7%XS_Hpmjhi =0.0D0 d(x)%lhc7%channelrates = 0.0D0 d(x)%lhc7%channelrates_tmp = -1.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_Hpmj =0.0D0 d(x)%lhc8%XS_Hpmjtb =0.0D0 d(x)%lhc8%XS_Hpmjcb =0.0D0 d(x)%lhc8%XS_Hpmjbjet =0.0D0 d(x)%lhc8%XS_Hpmjcjet =0.0D0 d(x)%lhc8%XS_Hpmjjetjet =0.0D0 d(x)%lhc8%XS_HpmjW =0.0D0 d(x)%lhc8%XS_HpmjZ =0.0D0 d(x)%lhc8%XS_HpjHmj =0.0D0 d(x)%lhc8%XS_Hpmjhi =0.0D0 d(x)%lhc8%channelrates = 0.0D0 d(x)%lhc8%channelrates_tmp = -1.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_Hpmj =0.0D0 d(x)%lhc13%XS_Hpmjtb =0.0D0 d(x)%lhc13%XS_Hpmjcb =0.0D0 d(x)%lhc13%XS_Hpmjbjet =0.0D0 d(x)%lhc13%XS_Hpmjcjet =0.0D0 d(x)%lhc13%XS_Hpmjjetjet =0.0D0 d(x)%lhc13%XS_HpmjW =0.0D0 d(x)%lhc13%XS_HpmjZ =0.0D0 d(x)%lhc13%XS_HpjHmj =0.0D0 d(x)%lhc13%XS_Hpmjhi =0.0D0 d(x)%lhc13%channelrates = 0.0D0 d(x)%lhc13%channelrates_tmp = -1.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_gg_HZ_SM( np_t(Hneut) )) allocate(d(x)%tev%XS_qq_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%channelrates_SM(np_t(Hneut),Nprod,Ndecay)) 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_gg_HZ_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_qq_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%channelrates_SM(np_t(Hneut),Nprod,Ndecay)) 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_gg_HZ_SM( np_t(Hneut) )) allocate(d(x)%lhc8%XS_qq_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%channelrates_SM(np_t(Hneut),Nprod,Ndecay)) 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_gg_HZ_SM( np_t(Hneut) )) allocate(d(x)%lhc13%XS_qq_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)%lhc13%channelrates_SM(np_t(Hneut),Nprod,Ndecay)) ! 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_Hpmj) deallocate(theo(x)%tev%XS_Hpmjtb) deallocate(theo(x)%tev%XS_Hpmjcb) deallocate(theo(x)%tev%XS_Hpmjbjet) deallocate(theo(x)%tev%XS_Hpmjcjet) deallocate(theo(x)%tev%XS_Hpmjjetjet) deallocate(theo(x)%tev%XS_HpmjW) deallocate(theo(x)%tev%XS_HpmjZ) deallocate(theo(x)%tev%XS_HpjHmj) deallocate(theo(x)%tev%XS_Hpmjhi) deallocate(theo(x)%tev%channelrates) deallocate(theo(x)%tev%channelrates_tmp) 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_qq_hjZ_ratio) deallocate(theo(x)%lhc7%XS_gg_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_Hpmj) deallocate(theo(x)%lhc7%XS_Hpmjtb) deallocate(theo(x)%lhc7%XS_Hpmjcb) deallocate(theo(x)%lhc7%XS_Hpmjbjet) deallocate(theo(x)%lhc7%XS_Hpmjcjet) deallocate(theo(x)%lhc7%XS_Hpmjjetjet) deallocate(theo(x)%lhc7%XS_HpmjW) deallocate(theo(x)%lhc7%XS_HpmjZ) deallocate(theo(x)%lhc7%XS_HpjHmj) deallocate(theo(x)%lhc7%XS_Hpmjhi) deallocate(theo(x)%lhc7%channelrates) deallocate(theo(x)%lhc7%channelrates_tmp) 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_qq_hjZ_ratio) deallocate(theo(x)%lhc8%XS_gg_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_Hpmj) deallocate(theo(x)%lhc8%XS_Hpmjtb) deallocate(theo(x)%lhc8%XS_Hpmjcb) deallocate(theo(x)%lhc8%XS_Hpmjbjet) deallocate(theo(x)%lhc8%XS_Hpmjcjet) deallocate(theo(x)%lhc8%XS_Hpmjjetjet) deallocate(theo(x)%lhc8%XS_HpmjW) deallocate(theo(x)%lhc8%XS_HpmjZ) deallocate(theo(x)%lhc8%XS_HpjHmj) deallocate(theo(x)%lhc8%XS_Hpmjhi) deallocate(theo(x)%lhc8%channelrates) deallocate(theo(x)%lhc8%channelrates_tmp) 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_qq_hjZ_ratio) deallocate(theo(x)%lhc13%XS_gg_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_Hpmj) deallocate(theo(x)%lhc13%XS_Hpmjtb) deallocate(theo(x)%lhc13%XS_Hpmjcb) deallocate(theo(x)%lhc13%XS_Hpmjbjet) deallocate(theo(x)%lhc13%XS_Hpmjcjet) deallocate(theo(x)%lhc13%XS_Hpmjjetjet) deallocate(theo(x)%lhc13%XS_HpmjW) deallocate(theo(x)%lhc13%XS_HpmjZ) deallocate(theo(x)%lhc13%XS_HpjHmj) deallocate(theo(x)%lhc13%XS_Hpmjhi) deallocate(theo(x)%lhc13%channelrates) deallocate(theo(x)%lhc13%channelrates_tmp) !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_gg_HZ_SM) deallocate(theo(x)%tev%XS_qq_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%channelrates_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_gg_HZ_SM) deallocate(theo(x)%lhc7%XS_qq_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%channelrates_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_gg_HZ_SM) deallocate(theo(x)%lhc8%XS_qq_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%channelrates_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_gg_HZ_SM) deallocate(theo(x)%lhc13%XS_qq_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) deallocate(theo(x)%lhc13%channelrates_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/manipulate_input_files/interpolate_TS.f90 =================================================================== --- trunk/manipulate_input_files/interpolate_TS.f90 (revision 600) +++ trunk/manipulate_input_files/interpolate_TS.f90 (revision 601) @@ -1,180 +1,180 @@ !------------------------------------------------------------ program interpolate ! Compile with ! gfortran -C interpolate_TS.f90 -o interpolate_TS.exe ! ! This program turns an input table with different mass separations ! into a table with equal mass separation. It interpolates the columns ! linearly. NOTE: delta_mh must be a divisor of all entries in the first column. !------------------------------------------------------------ implicit none !------------------------------------------------------------ integer :: i,j,k,m,x integer :: skip,ncol integer :: l_in,l_out,f_in,f_out, step character(LEN=100) :: filename double precision :: delta_mh, sep double precision, allocatable :: mh_XS_in(:,:),mh_XS_in_even(:,:),mh_XS_out(:,:) character(LEN=150), allocatable :: description(:) character(LEN=4) :: ending character(LEN=2) :: a character(LEN=300) :: temp integer :: number_args number_args = IARGC() if( number_args .ne. 2)then stop "Incorrect number of arguments given! Please give mass-separaration input_filename (without appendix) as arguments" endif ! Read arguments into text strings. i=1 temp="" call GETARG(i,temp) read(temp,*) delta_mh i=i+1 temp="" call GETARG(i,temp) filename = "" filename = trim(temp) !------------------------------------------------------------ ! filename='../HiggsBounds_KW/Expt_tables/CMStables/11034_CMS_WH-WWW_4.6fb-1' !main part of filename (without file extension) ! filename='sample/interpolate_TS_demo' !main part of filename (without file extension) ! filename='../../docs/HiggsSignals/Expt/12042-CMS-H-WW-lnulnu_HCP2012/mu-central' ! filename='observed' ! filename='../../docs/Expt/2011148_ATLAS_H-ZZ-llnunu/expected' ending='.dat' !file extension i.e. will read interpol_demo.txt skip=0 !number of lines to be skipped before data starts ncol=2 !number of columns of data ! delta_mh=10 !Higgs mass separation for output !------------------------------------------------------------ if((ncol.lt.2).or.(ncol.gt.100))stop 'wrong number of columns' if(skip.lt.0)stop 'need to set skip' write(*,*)'starting '//trim(filename)//'...' ! open input and output files f_in=20 f_out=f_in*10 open(f_in,file=trim(filename)//ending) open(f_out,file=trim(filename)//'_interpol'//ending) x=getfilelength(f_in) ! find length of input file l_in=x-skip write(*,*)'skip=',skip write(*,*)'l_in=',l_in allocate(mh_XS_in(l_in,ncol)) allocate(mh_XS_in_even(l_in,ncol)) ! read in input file if(skip.ne.0)then allocate(description(skip)) do i=1,skip read(f_in,'(a)')description(i) enddo endif do i=1,l_in read(f_in,*)(mh_XS_in(i,j),j=1,ncol) enddo do i=1,l_in do m=1,ncol ! if(mh_XS_in(i,m).lt.0.0D0)stop 'negative input data' if(m.ne.1) then mh_XS_in_even(i,m)=mh_XS_in(i,m) endif enddo if(mod(mh_XS_in(i,1),delta_mh).lt.delta_mh/2.) then mh_XS_in_even(i,1)=int(mh_XS_in(i,1)/delta_mh)*delta_mh else mh_XS_in_even(i,1)=(int(mh_XS_in(i,1)/delta_mh)+1)*delta_mh endif enddo l_out=int((mh_XS_in_even(l_in,1)-mh_XS_in_even(1,1))/delta_mh)+1 allocate(mh_XS_out(l_out,ncol)) k=0 do i=1,l_in-1 sep=mh_XS_in_even(i+1,1)-mh_XS_in_even(i,1) step=int(sep/delta_mh) do j=1,step k=k+1 mh_XS_out(k,1) = mh_XS_in_even(i,1)+(j-1)*delta_mh do m=2,ncol mh_XS_out(k,m) = mh_XS_in_even(i,m)+(j-1)*(mh_XS_in_even(i+1,m)-mh_XS_in_even(i,m))/dble(step) enddo enddo enddo do m=1,ncol mh_XS_out(l_out,m) = mh_XS_in_even(l_in,m) enddo write(a,'(I2)')ncol-1 do i=1,l_out write(f_out,'(1f15.2,'//trim(a)//'g15.7)')(mh_XS_out(i,j),j=1,ncol) enddo !******************************************** deallocate(mh_XS_in) deallocate(mh_XS_in_even) deallocate(mh_XS_out) close(f_in) close(f_out) contains !------------------------------------------------------------- function getfilelength(fileid) !------------------------------------------------------------- implicit none !-------------------------------------output integer fileid !-----------------------------------internal integer :: getfilelength integer :: n,ios,m character(len=100) :: temp !------------------------------------------- n= 0 do !this will count the number of lines which end in a newline character read(fileid,*,iostat=ios) if(ios.lt.0) exit if(ios.gt.0)then write(*,*)'error in input file',fileid ; call flush(6) exit endif n = n + 1 enddo rewind(fileid) m = 0 ; temp="" !this will count the number of lines in the file, including the last one, do ! even if it doesn't end in a newline character read(fileid,'(a)',iostat=ios)temp if(ios.lt.0) exit m = m + 1 enddo rewind(fileid) if(m.ne.n)then write(*,*)'error in input file: file id=',fileid ; call flush(6) - stop'Error: file needs to end with a newline character (see standard output for file id)' + stop 'Error: file needs to end with a newline character (see standard output for file id)' endif getfilelength=n end function getfilelength -end program interpolate \ No newline at end of file +end program interpolate Index: trunk/manipulate_input_files/merge_columns.f90 =================================================================== --- trunk/manipulate_input_files/merge_columns.f90 (revision 600) +++ trunk/manipulate_input_files/merge_columns.f90 (revision 601) @@ -1,119 +1,119 @@ program merge_columns ! This program merges the columns of two data files into one. The first column of each input file should be the same. ! Attention: there are no lines skipped in the beginning. implicit none integer:: i,j,obs,pred double precision :: Mhdummy,S95obs,S95pred ! character(LEN=100) :: path double precision, allocatable :: mh_XS_1(:,:),mh_XS_2(:,:) integer :: x,y,ncol character(LEN=100) :: filename1,filename2 character(LEN=300) :: temp integer :: number_args number_args = IARGC() if( number_args .ne. 2)then stop "Incorrect number of arguments given! Please give input_filename1 (exp) and input_filename2 (obs)" endif ! Read arguments into text strings. i=1 temp="" call GETARG(i,temp) filename1 = "" filename1 = trim(temp) i=i+1 temp="" call GETARG(i,temp) filename2 = "" filename2 = trim(temp) obs= 10 pred=11 ! path="../../docs/Expt/7214_ATLAS_SMcombination_7and8TeV/" ! path="" open(obs,file=trim(filename2)) open(pred,file=trim(filename1)) open(12,file="data.dat") ncol=2 x=getfilelength(obs) y=getfilelength(pred) if(x.ne.y) then write(*,*) 'WARNING: Input files do not have equal lengths!' endif allocate(mh_XS_1(x,ncol)) allocate(mh_XS_2(x,ncol)) do i=1,x read(obs,*)(mh_XS_1(i,j),j=1,ncol) enddo do i=1,y read(pred,*)(mh_XS_2(i,j),j=1,ncol) enddo do i=1,x write(12,'(3G16.4)') (mh_XS_1(i,j),j=1,ncol),(mh_XS_2(i,j),j=2,ncol) enddo contains !------------------------------------------------------------- function getfilelength(fileid) !------------------------------------------------------------- implicit none !-------------------------------------output integer fileid !-----------------------------------internal integer :: getfilelength integer :: n,ios,m character(len=100) :: temp !------------------------------------------- n= 0 do !this will count the number of lines which end in a newline character read(fileid,*,iostat=ios) if(ios.lt.0) exit if(ios.gt.0)then write(*,*)'error in input file',fileid ; call flush(6) exit endif n = n + 1 enddo rewind(fileid) m = 0 ; temp="" !this will count the number of lines in the file, including the last one, do ! even if it doesn't end in a newline character read(fileid,'(a)',iostat=ios)temp if(ios.lt.0) exit m = m + 1 enddo rewind(fileid) if(m.ne.n)then write(*,*)'error in input file: file id=',fileid ; call flush(6) - stop'Error: file needs to end with a newline character (see standard output for file id)' + stop 'Error: file needs to end with a newline character (see standard output for file id)' endif getfilelength=n end function getfilelength end program merge_columns Index: trunk/HiggsSignals-2/STXS.f90 =================================================================== --- trunk/HiggsSignals-2/STXS.f90 (revision 600) +++ trunk/HiggsSignals-2/STXS.f90 (revision 601) @@ -1,991 +1,991 @@ module STXS ! Still to do: ! 1: Read in correlation matrix ! 2: Write chi^2 test ! use numerics ! use combinatorics use usefulbits_hs implicit none ! integer :: i,j,k ! double precision,parameter :: pi=3.14159265358979323846264338328D0 ! integer, allocatable :: peakindices_best(:,:) type STXS_observable integer :: id character(LEN=100) :: label ! Reference character(LEN=100) :: desc ! Description character(LEN=3) :: expt ! Experiment character(LEN=10) :: collider character(LEN=10) :: collaboration double precision :: lumi,dlumi,energy character(LEN=100) :: assignmentgroup integer :: rate_SM_normalized integer :: mhchisq double precision :: massobs, dmassobs ! This one enters the chi^2 for the mass! double precision :: mass, dmass ! This one is the mass position for the measurement and the "experimentally allowed assignment range" double precision :: eff_ref_mass ! This is the mass for which the signal efficiencies are given. double precision, allocatable :: model_rate_per_Higgs(:,:) double precision, allocatable :: inclusive_SM_rate(:) integer :: Nc double precision :: model_total_rate double precision :: rate, rate_up, rate_low, drate_up, drate_low double precision :: SMrate, SMrate_up, SMrate_low, dSMrate_up, dSMrate_low ! SM rate used/quoted by the experiment ! At the moment, interpret STXS observables as "pure" channels (production, or decay rate) character(LEN=5), allocatable :: channel_id_str(:) ! Channels array as string, dim(Nc) ! integer, allocatable :: channel_id(:) integer, allocatable :: channel_p_id(:) ! Production channels array, dim(Nc) integer, allocatable :: channel_d_id(:) ! Decay channels array, dim(Nc) double precision, allocatable :: channel_efficiency(:) ! SM signal efficiency of inclusive rates (analysis-specific) - double precision, allocatable :: relative_efficiency(:,:) ! Model signal efficiency relative to SM per Higgs + double precision, allocatable :: modification_factor(:,:) ! Model signal efficiency relative to SM per Higgs double precision :: chisq ! character(LEN=10),allocatable :: channel_description(:,:) ! TODO: How do we deal with ratio of BRs? end type type(STXS_observable), allocatable :: STXSlist(:) type(correlation_info), allocatable :: STXScorrlist(:) contains !------------------------------------------------------------------------------------ subroutine load_STXS(dataset) !------------------------------------------------------------------------------------ use store_pathname_HS use usefulbits, only: file_id_common2, file_id_common3, np, Hneut use datatables, only : read_in_mass_resolution_and_assignment_group ! implicit none character(LEN=*), intent(in) :: dataset character(LEN=100) :: datafile(500) character(LEN=pathname_length+150) :: fullfilename integer, allocatable :: skip(:) integer :: i, n, n_datafiles,n_correlations, n_correlations_tmp, ios, k, m, int1, int2 double precision :: db1 character(LEN=200) :: comment character(LEN=1) :: firstchar character(LEN=100) :: line integer :: id, posperiod ! call system('basename -a `ls -1 -p '//trim(adjustl(pathname_HS))// & ! & 'Expt_tables/'//trim(adjustl(dataset))//'/*.stxs 2>/dev/null` > STXS_analyses.txt 2>/dev/null') call system('ls -1 -p '//trim(adjustl(pathname_HS))// & & 'Expt_tables/'//trim(adjustl(dataset))//'/*.stxs | xargs -L 1 basename > STXS_analyses.txt') open(file_id_common3, file="STXS_analyses.txt",form='formatted') print *, "Reading in STXS measurements from analysis-set "//& trim(adjustl(dataset))//":" n = 0 n_datafiles = 0 do n = n+1 read(file_id_common3,'(A)', iostat=ios) datafile(n) if(ios.ne.0) exit write(*,'(I4,2X,A)') n, datafile(n) enddo n_datafiles = n - 1 close(file_id_common3) allocate(STXSlist(n_datafiles),skip(n_datafiles)) do n=1,n_datafiles skip(n)=11 open(file_id_common3, file=trim(adjustl(pathname_HS)) //'Expt_tables/'// & & trim(adjustl(dataset))//'/' // datafile(n)) do read(file_id_common3,'(A)') comment comment = trim(adjustl(comment)) write(firstchar,'(A1)') comment if(firstchar.ne.'#') then exit else skip(n)=skip(n)+1 endif enddo backspace(file_id_common3) read(file_id_common3,*) STXSlist(n)%id read(file_id_common3,'(A)') STXSlist(n)%label read(file_id_common3,*) STXSlist(n)%collider,STXSlist(n)%collaboration, & & STXSlist(n)%expt read(file_id_common3,'(A)') STXSlist(n)%desc read(file_id_common3,*) STXSlist(n)%energy, STXSlist(n)%lumi, STXSlist(n)%dlumi read(file_id_common3,*) STXSlist(n)%mhchisq, STXSlist(n)%rate_SM_normalized if(STXSlist(n)%mhchisq == 1) then read(file_id_common3,*) STXSlist(n)%massobs, STXSlist(n)%dmassobs else read(file_id_common3,*) STXSlist(n)%massobs = 0.0D0 STXSlist(n)%dmassobs = 0.0D0 endif !--CHECK FOR ASSIGNMENT GROUP AS SECOND COLUMN: read(file_id_common3,*) STXSlist(n)%mass read(file_id_common3,'(A)') line call read_in_mass_resolution_and_assignment_group(line, STXSlist(n)%dmass,& & STXSlist(n)%assignmentgroup) read(file_id_common3,*) STXSlist(n)%Nc, STXSlist(n)%eff_ref_mass allocate(STXSlist(n)%channel_id_str(STXSlist(n)%Nc)) allocate(STXSlist(n)%channel_p_id(STXSlist(n)%Nc)) allocate(STXSlist(n)%channel_d_id(STXSlist(n)%Nc)) read(file_id_common3,*) (STXSlist(n)%channel_id_str(i),i=1,STXSlist(n)%Nc) do i=1,STXSlist(n)%Nc posperiod = index(STXSlist(n)%channel_id_str(i),'.') if(posperiod.eq.0) then if(len(trim(adjustl(STXSlist(n)%channel_id_str(i)))).eq.2) then read(STXSlist(n)%channel_id_str(i),*) id STXSlist(n)%channel_p_id(i) = int((id-modulo(id,10))/dble(10)) STXSlist(n)%channel_d_id(i) = modulo(id,10) else write(*,*) " For observable ID = ",STXSlist(n)%id stop " Error: Cannot handle channel IDs!" endif else read(STXSlist(n)%channel_id_str(i)(:posperiod-1),*) STXSlist(n)%channel_p_id(i) read(STXSlist(n)%channel_id_str(i)(posperiod+1:),*) STXSlist(n)%channel_d_id(i) endif enddo ! write(*,*) "Production channels = ",STXSlist(n)%channel_p_id ! write(*,*) "Decay channels = ",STXSlist(n)%channel_d_id ! allocate(STXSlist(n)%channel_id(STXSlist(n)%Nc)) ! read(file_id_common3,*) (STXSlist(n)%channel_id(i),i=1,STXSlist(n)%Nc) allocate(STXSlist(n)%channel_efficiency(STXSlist(n)%Nc)) if(STXSlist(n)%eff_ref_mass.ge.0D0) then read(file_id_common3,*) (STXSlist(n)%channel_efficiency(i),i=1,STXSlist(n)%Nc) else do i=1,STXSlist(n)%Nc STXSlist(n)%channel_efficiency(i)=1.0D0 enddo read(file_id_common3,*) endif ! read(file_id_common3,*) STXSlist(n)%channel_id ! read(file_id_common3,*) STXSlist(n)%relative_efficiency read(file_id_common3,*) STXSlist(n)%rate_low, STXSlist(n)%rate, STXSlist(n)%rate_up if(STXSlist(n)%rate_SM_normalized.eq.1) then read(file_id_common3,*) comment STXSlist(n)%SMrate_low = 0.0D0 STXSlist(n)%SMrate = 0.0D0 STXSlist(n)%SMrate_up = 0.0D0 else read(file_id_common3,*) STXSlist(n)%SMrate_low, STXSlist(n)%SMrate, STXSlist(n)%SMrate_up endif STXSlist(n)%drate_low = STXSlist(n)%rate - STXSlist(n)%rate_low STXSlist(n)%drate_up = STXSlist(n)%rate_up - STXSlist(n)%rate STXSlist(n)%dSMrate_low = STXSlist(n)%SMrate - STXSlist(n)%SMrate_low STXSlist(n)%dSMrate_up = STXSlist(n)%SMrate_up - STXSlist(n)%SMrate close(file_id_common3) - allocate(STXSlist(n)%relative_efficiency(np(Hneut),STXSlist(n)%Nc)) + allocate(STXSlist(n)%modification_factor(np(Hneut),STXSlist(n)%Nc)) do k=1, np(Hneut) - STXSlist(n)%relative_efficiency(k,:)=1.0D0 + STXSlist(n)%modification_factor(k,:)=1.0D0 enddo enddo close(file_id_common3) !NEW: call system('ls -1 -p '//trim(adjustl(pathname_HS))// & & 'Expt_tables/'//trim(adjustl(dataset))//'/*.stxscorr | xargs -L 1 basename > STXS_correlations.txt') ! call system('basename -a `ls -1 -p '//trim(adjustl(pathname_HS))// & ! & 'Expt_tables/'//trim(adjustl(dataset))//'/*.stxscorr 2>/dev/null` > STXS_correlations.txt 2>/dev/null') call system('rm -rf STXS_ncorrelations.txt') open(file_id_common3, file="STXS_correlations.txt",form='formatted') print *, "Reading in correlations from the following datafiles in analysis-set "// & trim(adjustl(Exptdir))//":" n = 0 n_datafiles = 0 n_correlations = 0 do n = n+1 read(file_id_common3,'(A)', iostat=ios) datafile(n) if(ios.ne.0) exit fullfilename=trim(adjustl(pathname_HS))//'Expt_tables/'//trim(adjustl(dataset))//'/'& & //trim(datafile(n)) call system('cat '//trim(adjustl(fullfilename))//' | wc -l > STXS_ncorrelations.txt') open(file_id_common2,file="STXS_ncorrelations.txt",form='formatted') read(file_id_common2,'(I10)') n_correlations_tmp close(file_id_common2) write(*,'(2I4,2X,A)') n, n_correlations_tmp, datafile(n) n_correlations = n_correlations + n_correlations_tmp enddo n_datafiles = n - 1 close(file_id_common3) allocate(STXScorrlist(n_correlations)) m=0 do n=1,n_datafiles fullfilename=trim(adjustl(pathname_HS))//'Expt_tables/'//trim(adjustl(dataset))//'/'& & //trim(datafile(n)) open(file_id_common3,file=fullfilename) do m= m+1 read(file_id_common3,*,iostat=ios) int1, int2, db1 ! write(*,*) m, int1, int2, db1, ios if(ios.ne.0) exit STXScorrlist(m)%obsID1 = int1 STXScorrlist(m)%obsID2 = int2 STXScorrlist(m)%corr = db1 enddo m=m-1 close(file_id_common3) enddo end subroutine load_STXS !------------------------------------------------------------------------------------ -subroutine assign_modelefficiencies_to_STXS(obsID, Nc, relative_efficiency) +subroutine assign_modification_factor_to_STXS(obsID, Nc, modification_factor) !------------------------------------------------------------------------------------ use usefulbits, only : np, Hneut implicit none integer, intent(in) :: obsID integer, intent(in) :: Nc - double precision, dimension(np(Hneut),Nc), intent(in) :: relative_efficiency + double precision, dimension(np(Hneut),Nc), intent(in) :: modification_factor integer :: i logical :: foundid = .False. do i=lbound(STXSlist, dim=1),ubound(STXSlist, dim=1) if(STXSlist(i)%id.eq.obsID) then if(Nc.ne.STXSlist(i)%Nc) then stop 'Error: Number of channels does not match!' else - STXSlist(i)%relative_efficiency = relative_efficiency + STXSlist(i)%modification_factor = modification_factor foundid = .True. endif endif enddo - if(.not.foundid) write(*,*) "WARNING in assign_modelefficiencies_to_STXS: ",& + if(.not.foundid) write(*,*) "WARNING in assign_modification_factor_to_STXS: ",& & "observable ID ",obsID," not known!" -end subroutine assign_modelefficiencies_to_STXS +end subroutine assign_modification_factor_to_STXS !------------------------------------------------------------------------------------ subroutine get_chisq_from_STXS(chisq_tot, pval) !------------------------------------------------------------------------------------ use usefulbits, only : vsmall use usefulbits_hs, only : Nparam use numerics, only : invmatrix, matmult, gammp implicit none double precision, intent(out) :: chisq_tot, pval integer :: i,j,m,N double precision :: cov logical :: correlationfound, somecorrelationsmissing double precision, allocatable :: covmat(:,:),vmat(:,:),invcovmat(:,:) double precision, allocatable :: v(:), v2(:) N=size(STXSlist) allocate(covmat(N,N),invcovmat(N,N)) allocate(v(N),v2(N)) allocate(vmat(N,1)) somecorrelationsmissing = .False. do i=1,N do j=1,N correlationfound=.False. do m=lbound(STXScorrlist,dim=1), ubound(STXScorrlist,dim=1) if((STXScorrlist(m)%obsID1.eq.STXSlist(i)%id.and.STXScorrlist(m)%obsID2.eq.STXSlist(j)%id)& &.or.(STXScorrlist(m)%obsID2.eq.STXSlist(i)%id.and.STXScorrlist(m)%obsID1.eq.STXSlist(j)%id)) then covmat(i,j) = STXScorrlist(m)%corr*get_drate(i)*get_drate(j) correlationfound=.True. endif enddo if(.not.correlationfound) then ! Use a unit-matrix for the correlations here. ! if(.not.somecorrelationsmissing) then ! write(*,*) "Warning: Correlation matrix element not found for observable ids: ",STXSlist(i)%id, STXSlist(j)%id ! write(*,*) " Suppressing future warnings about missing correlation matrix elements..." ! endif covmat(i,j) = 0.0D0 somecorrelationsmissing = .True. if(STXSlist(i)%id.eq.STXSlist(j)%id) then covmat(i,j) = get_drate(i)*get_drate(j) endif endif enddo v(i) = STXSlist(i)%rate - STXSlist(i)%model_total_rate vmat(i,1) = v(i) enddo ! if(somecorrelationsmissing) then ! write(*,*) "Warning: Some correlation matrix elements were not found." ! endif call invmatrix(covmat,invcovmat) call matmult(invcovmat,vmat,v2,N,1) chisq_tot= 0.0D0 do i=1,N STXSlist(i)%chisq = v(i)*v2(i) chisq_tot = chisq_tot + STXSlist(i)%chisq enddo pval = 1.0D0 if(chisq_tot.gt.vsmall.and.(N-Nparam).gt.0) then pval = 1 - gammp(dble(N-Nparam)/2,chisq_tot/2) endif deallocate(covmat,invcovmat,v,v2,vmat) end subroutine get_chisq_from_STXS !------------------------------------------------------------------------------------ subroutine get_number_of_STXS_observables(Nobs_rates, Nobs_mh) integer, intent(out) :: Nobs_rates, Nobs_mh Nobs_rates=size(STXSlist) Nobs_mh = 0 end subroutine get_number_of_STXS_observables !------------------------------------------------------------------------------------ function get_drate(i) !------------------------------------------------------------------------------------ implicit none integer :: i double precision get_drate if(STXSlist(i)%model_total_rate.le.STXSlist(i)%rate) then get_drate = STXSlist(i)%drate_low else get_drate = STXSlist(i)%drate_up endif end function get_drate !------------------------------------------------------------------------------------ subroutine calculate_model_predictions_for_STXS() !------------------------------------------------------------------------------------ use usefulbits, only : theo use theo_manip, only : HB5_complete_theo integer :: i call HB5_complete_theo do i=lbound(STXSlist,dim=1), ubound(STXSlist,dim=1) call evaluate_model_for_STXS(STXSlist(i),theo(1)) enddo end subroutine calculate_model_predictions_for_STXS !------------------------------------------------------------------------------------ subroutine evaluate_model_for_STXS(STXSobs, t) !------------------------------------------------------------------------------------ use usefulbits, only : theo, div, small, np, Hneut, dataset, vsmall use usefulbits_HS, only : normalize_rates_to_reference_position, & & normalize_rates_to_reference_position_outside_dmtheo, & & assignmentrange_STXS ! use_SMrate_at_reference_position_for_STXS, use theory_XS_SM_functions use theory_BRfunctions use theo_manip, only : HB5_complete_theo implicit none type(STXS_observable), intent(inout) :: STXSobs type(dataset), intent(in) :: t double precision :: norm_rate, SMrate, SMrate_refmass, refmass, BR_SMref integer :: i, j, id, p, d STXSobs%model_total_rate = 0.0D0 if(.not.allocated(theo))then stop 'subroutine HiggsSignals_initialize must be called first' endif if(.not.allocated(STXSobs%model_rate_per_Higgs)) then allocate(STXSobs%model_rate_per_Higgs(np(Hneut),STXSobs%Nc)) endif if(.not.allocated(STXSobs%inclusive_SM_rate)) then ! allocate(STXSobs%inclusive_SM_rate(np(Hneut),STXSobs%Nc)) allocate(STXSobs%inclusive_SM_rate(STXSobs%Nc)) endif ! write(*,*) 'DEBUG HS: id = ', STXSobs%id ! write(*,*) 'DEBUG HS, channel = ',STXSobs%channel_id refmass = STXSobs%mass do i=1,STXSobs%Nc ! id = STXSobs%channel_id(i) ! p = int((id-modulo(id,10))/dble(10)) ! d = modulo(id,10) p = STXSobs%channel_p_id(i) d = STXSobs%channel_d_id(i) do j=1, np(Hneut) ! write(*,*) 'DEBUG HS, m = ', t%particle(Hneut)%M(j) !--Do the production rate for the relevant experiment and cms-energy if(STXSobs%collider.eq.'LHC') then if(abs(STXSobs%energy-7.0D0).le.small) then if(p.eq.1) then norm_rate=t%lhc7%XS_hj_ratio(j) SMrate=t%lhc7%XS_H_SM(j) SMrate_refmass=XS_lhc7_gg_H_SM(refmass)+XS_lhc7_bb_H_SM(refmass) ! STXSobs%channel_description(i,1)='singleH' else if(p.eq.2) then norm_rate=t%lhc7%XS_vbf_ratio(j) SMrate=t%lhc7%XS_vbf_SM(j) SMrate_refmass=XS_lhc7_vbf_SM(refmass) ! STXSobs%channel_description(i,1)='VBF' else if(p.eq.3) then norm_rate=t%lhc7%XS_hjW_ratio(j) SMrate=t%lhc7%XS_HW_SM(j) SMrate_refmass=XS_lhc7_HW_SM(refmass) ! STXSobs%channel_description(i,1)='HW' else if(p.eq.4) then norm_rate=t%lhc7%XS_hjZ_ratio(j) SMrate=t%lhc7%XS_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_ggqqbb(refmass,'LHC7 ',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) ! STXSobs%channel_description(i,1)='HZ' else if(p.eq.5) then norm_rate=t%lhc7%XS_tthj_ratio(j) SMrate=t%lhc7%XS_ttH_SM(j) SMrate_refmass=XS_lhc7_ttH_SM(refmass) ! STXSobs%channel_description(i,1)='ttH' else if(p.eq.6) then norm_rate=t%lhc7%XS_gg_hj_ratio(j) SMrate=t%lhc7%XS_gg_H_SM(j) SMrate_refmass=XS_lhc7_gg_H_SM(refmass) ! mutab%channel_description(i,1)='ggH' else if(p.eq.7) then norm_rate=t%lhc7%XS_bb_hj_ratio(j) SMrate=t%lhc7%XS_bb_H_SM(j) SMrate_refmass=XS_lhc7_bb_H_SM(refmass) ! mutab%channel_description(i,1)='bbH' else if(p.eq.8) then norm_rate=t%lhc7%XS_thj_tchan_ratio(j) SMrate=t%lhc7%XS_tH_tchan_SM(j) SMrate_refmass=XS_lhc7_tH_tchan_SM(refmass) ! mutab%channel_description(i,1)='tH (t-channel)' else if(p.eq.9) then norm_rate=t%lhc7%XS_thj_schan_ratio(j) SMrate=t%lhc7%XS_tH_schan_SM(j) SMrate_refmass=XS_lhc7_tH_schan_SM(refmass) ! mutab%channel_description(i,1)='tH (s-channel)' else if(p.eq.10) then norm_rate=t%lhc7%XS_qq_hjZ_ratio(j) SMrate=t%lhc7%XS_qq_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_qqbb(refmass,'LHC7 ',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) ! mutab%channel_description(i,1)='qq-HZ' else if(p.eq.11) then norm_rate=t%lhc7%XS_gg_hjZ_ratio(j) SMrate=t%lhc7%XS_gg_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_gg(refmass,'LHC7 ',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) ! mutab%channel_description(i,1)='gg-HZ' else if(p.eq.0) then norm_rate=1.0D0 SMrate=1.0D0 SMrate_refmass=1.0D0 ! STXSobs%channel_description(i,1)='none' else write(*,*) "WARNING: Unknown production mode id p=",p," for STXS observable id = ",STXSobs%id endif else if(abs(STXSobs%energy-8.0D0).le.small) then if(p.eq.1) then norm_rate=t%lhc8%XS_hj_ratio(j) SMrate=t%lhc8%XS_H_SM(j) SMrate_refmass=XS_lhc8_gg_H_SM(refmass)+XS_lhc8_bb_H_SM(refmass) ! STXSobs%channel_description(i,1)='singleH' else if(p.eq.2) then norm_rate=t%lhc8%XS_vbf_ratio(j) SMrate=t%lhc8%XS_vbf_SM(j) SMrate_refmass=XS_lhc8_vbf_SM(refmass) ! STXSobs%channel_description(i,1)='VBF' else if(p.eq.3) then norm_rate=t%lhc8%XS_hjW_ratio(j) SMrate=t%lhc8%XS_HW_SM(j) SMrate_refmass=XS_lhc8_HW_SM(refmass) ! STXSobs%channel_description(i,1)='HW' else if(p.eq.4) then norm_rate=t%lhc8%XS_hjZ_ratio(j) SMrate=t%lhc8%XS_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_ggqqbb(refmass,'LHC8 ',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) ! STXSobs%channel_description(i,1)='HZ' else if(p.eq.5) then norm_rate=t%lhc8%XS_tthj_ratio(j) SMrate=t%lhc8%XS_ttH_SM(j) SMrate_refmass=XS_lhc8_ttH_SM(refmass) ! STXSobs%channel_description(i,1)='ttH' else if(p.eq.6) then norm_rate=t%lhc8%XS_gg_hj_ratio(j) SMrate=t%lhc8%XS_gg_H_SM(j) SMrate_refmass=XS_lhc8_gg_H_SM(refmass) ! mutab%channel_description(i,1)='ggH' else if(p.eq.7) then norm_rate=t%lhc8%XS_bb_hj_ratio(j) SMrate=t%lhc8%XS_bb_H_SM(j) SMrate_refmass=XS_lhc8_bb_H_SM(refmass) ! mutab%channel_description(i,1)='bbH' else if(p.eq.8) then norm_rate=t%lhc8%XS_thj_tchan_ratio(j) SMrate=t%lhc8%XS_tH_tchan_SM(j) SMrate_refmass=XS_lhc8_tH_tchan_SM(refmass) ! mutab%channel_description(i,1)='tH (t-channel)' else if(p.eq.9) then norm_rate=t%lhc8%XS_thj_schan_ratio(j) SMrate=t%lhc8%XS_tH_schan_SM(j) SMrate_refmass=XS_lhc8_tH_schan_SM(refmass) ! mutab%channel_description(i,1)='tH (s-channel)' else if(p.eq.10) then norm_rate=t%lhc8%XS_qq_hjZ_ratio(j) SMrate=t%lhc8%XS_qq_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_qqbb(refmass,'LHC8 ',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) ! mutab%channel_description(i,1)='qq-HZ' else if(p.eq.11) then norm_rate=t%lhc8%XS_gg_hjZ_ratio(j) SMrate=t%lhc8%XS_gg_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_gg(refmass,'LHC8 ',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) else if(p.eq.0) then norm_rate=1.0D0 SMrate=1.0D0 SMrate_refmass=1.0D0 ! STXSobs%channel_description(i,1)='none' else write(*,*) "WARNING: Unknown production mode id p=",p," for STXS observable id = ",STXSobs%id endif else if(abs(STXSobs%energy-13.0D0).le.small) then if(p.eq.1) then norm_rate=t%lhc13%XS_hj_ratio(j) SMrate=t%lhc13%XS_H_SM(j) SMrate_refmass=XS_lhc13_gg_H_SM(refmass)+XS_lhc13_bb_H_SM(refmass) ! STXSobs%channel_description(i,1)='singleH' else if(p.eq.2) then norm_rate=t%lhc13%XS_vbf_ratio(j) SMrate=t%lhc13%XS_vbf_SM(j) SMrate_refmass=XS_lhc13_vbf_SM(refmass) ! STXSobs%channel_description(i,1)='VBF' else if(p.eq.3) then norm_rate=t%lhc13%XS_hjW_ratio(j) SMrate=t%lhc13%XS_HW_SM(j) SMrate_refmass=XS_lhc13_HW_SM(refmass) ! STXSobs%channel_description(i,1)='HW' else if(p.eq.4) then norm_rate=t%lhc13%XS_hjZ_ratio(j) SMrate=t%lhc13%XS_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_ggqqbb(refmass,'LHC13',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) ! STXSobs%channel_description(i,1)='HZ' else if(p.eq.5) then norm_rate=t%lhc13%XS_tthj_ratio(j) SMrate=t%lhc13%XS_ttH_SM(j) SMrate_refmass=XS_lhc13_ttH_SM(refmass) ! STXSobs%channel_description(i,1)='ttH' else if(p.eq.6) then norm_rate=t%lhc13%XS_gg_hj_ratio(j) SMrate=t%lhc13%XS_gg_H_SM(j) SMrate_refmass=XS_lhc13_gg_H_SM(refmass) ! mutab%channel_description(i,1)='ggH' else if(p.eq.7) then norm_rate=t%lhc13%XS_bb_hj_ratio(j) SMrate=t%lhc13%XS_bb_H_SM(j) SMrate_refmass=XS_lhc13_bb_H_SM(refmass) ! mutab%channel_description(i,1)='bbH' else if(p.eq.8) then norm_rate=t%lhc13%XS_thj_tchan_ratio(j) SMrate=t%lhc13%XS_tH_tchan_SM(j) SMrate_refmass=XS_lhc13_tH_tchan_SM(refmass) ! mutab%channel_description(i,1)='tH (t-channel)' else if(p.eq.9) then norm_rate=t%lhc13%XS_thj_schan_ratio(j) SMrate=t%lhc13%XS_tH_schan_SM(j) SMrate_refmass=XS_lhc13_tH_schan_SM(refmass) ! mutab%channel_description(i,1)='tH (s-channel)' else if(p.eq.10) then norm_rate=t%lhc13%XS_qq_hjZ_ratio(j) SMrate=t%lhc13%XS_qq_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_qqbb(refmass,'LHC13',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) ! mutab%channel_description(i,1)='qq-HZ' else if(p.eq.11) then norm_rate=t%lhc13%XS_gg_hjZ_ratio(j) SMrate=t%lhc13%XS_gg_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_gg(refmass,'LHC13',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) else if(p.eq.0) then norm_rate=1.0D0 SMrate=1.0D0 SMrate_refmass=1.0D0 ! STXSobs%channel_description(i,1)='none' else write(*,*) "WARNING: Unknown production mode id p=",p," for STXS observable id = ",STXSobs%id endif endif else if(STXSobs%collider.eq.'TEV') then if(p.eq.1) then norm_rate=t%tev%XS_hj_ratio(j) SMrate=t%tev%XS_H_SM(j) SMrate_refmass=XS_tev_gg_H_SM(refmass)+XS_tev_bb_H_SM(refmass) ! STXSobs%channel_description(i,1)='singleH' else if(p.eq.2) then norm_rate=t%tev%XS_vbf_ratio(j) SMrate=t%tev%XS_vbf_SM(j) SMrate_refmass=XS_tev_vbf_SM(refmass) ! STXSobs%channel_description(i,1)='VBF' else if(p.eq.3) then norm_rate=t%tev%XS_hjW_ratio(j) SMrate=t%tev%XS_HW_SM(j) SMrate_refmass=XS_tev_HW_SM(refmass) ! STXSobs%channel_description(i,1)='HW' else if(p.eq.4) then norm_rate=t%tev%XS_hjZ_ratio(j) SMrate=t%tev%XS_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_ggqqbb(refmass,'TEV ',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) ! STXSobs%channel_description(i,1)='HZ' else if(p.eq.5) then norm_rate=t%tev%XS_tthj_ratio(j) SMrate=t%tev%XS_ttH_SM(j) SMrate_refmass=XS_tev_ttH_SM(refmass) ! STXSobs%channel_description(i,1)='ttH' else if(p.eq.10) then norm_rate=t%tev%XS_qq_hjZ_ratio(j) SMrate=t%tev%XS_qq_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_qqbb(refmass,'TEV ',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) ! mutab%channel_description(i,1)='qq-HZ' else if(p.eq.11) then norm_rate=t%tev%XS_gg_hjZ_ratio(j) SMrate=t%tev%XS_gg_HZ_SM(j) SMrate_refmass=ZH_cpmix_nnlo_gg(refmass,'TEV ',1.0D0,1.0D0,1.0D0,0.0D0,0.0D0,.True.) else if(p.eq.0) then norm_rate=1.0D0 SMrate=1.0D0 SMrate_refmass=1.0D0 ! STXSobs%channel_description(i,1)='none' else write(*,*) "WARNING: Unknown production mode id p=",p," for STXS observable id = ",STXSobs%id endif else if(STXSobs%collider.eq.'ILC') then !--n.B.: As a first attempt, we use the LHC8 normalized cross sections for ZH, VBF, ttH. ! In order to do this properly, a separate input for the ILC cross sections ! has to be provided! It works only for single production mode observables (no ! correct weighting of channels included!)Then, at least in the effective coupling ! approximation, there is no difference to a full implementation. ! The theoretical uncertainty of the ILC production modes will are defined in ! usefulbits_HS.f90. if(p.eq.1.or.p.eq.2) then write(*,*) 'Warning: Unknown ILC production mode (',p,') in table ',STXSobs%id norm_rate=0.0D0 SMrate=1.0D0 SMrate_refmass=1.0D0 ! STXSobs%channel_description(i,1)='unknown' else if(p.eq.3) then norm_rate=t%lhc8%XS_hjW_ratio(j) SMrate=t%lhc8%XS_HW_SM(j) SMrate_refmass=XS_lhc8_HW_SM(refmass) ! STXSobs%channel_description(i,1)='WBF' else if(p.eq.4) then norm_rate=t%lhc8%XS_hjZ_ratio(j) SMrate=t%lhc8%XS_HZ_SM(j) SMrate_refmass=XS_lhc8_HZ_SM(refmass) ! STXSobs%channel_description(i,1)='HZ' else if(p.eq.5) then norm_rate=t%lhc8%XS_tthj_ratio(j) SMrate=t%lhc8%XS_ttH_SM(j) SMrate_refmass=XS_lhc8_ttH_SM(refmass) ! STXSobs%channel_description(i,1)='ttH' else if(p.eq.0) then norm_rate=1.0D0 SMrate=1.0D0 SMrate_refmass=1.0D0 ! STXSobs%channel_description(i,1)='none' else write(*,*) "WARNING: Unknown production mode id p=",p," for STXS observable id = ",STXSobs%id endif endif !--Multiply now by the decay rate if(d.eq.1) then norm_rate=norm_rate*div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hgaga_SM(j) SMrate_refmass = SMrate_refmass*BRSM_Hgaga(refmass) ! STXSobs%channel_description(i,2)='gammagamma' else if(d.eq.2) then norm_rate=norm_rate*div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_HWW_SM(j) SMrate_refmass = SMrate_refmass*BRSM_HWW(refmass) ! STXSobs%channel_description(i,2)='WW' else if(d.eq.3) then norm_rate=norm_rate*div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_HZZ_SM(j) SMrate_refmass = SMrate_refmass*BRSM_HZZ(refmass) ! STXSobs%channel_description(i,2)='ZZ' else if(d.eq.4) then norm_rate=norm_rate*div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Htautau_SM(j) SMrate_refmass = SMrate_refmass*BRSM_Htautau(refmass) ! STXSobs%channel_description(i,2)='tautau' else if(d.eq.5) then norm_rate=norm_rate*div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hbb_SM(j) SMrate_refmass = SMrate_refmass*BRSM_Hbb(refmass) ! STXSobs%channel_description(i,2)='bb' else if(d.eq.6) then norm_rate=norm_rate*div(t%BR_hjZga(j),t%BR_HZga_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_HZga_SM(j) SMrate_refmass = SMrate_refmass*BRSM_HZga(refmass) ! STXSobs%channel_description(i,2)='Zgamma' else if(d.eq.7) then norm_rate=norm_rate*div(t%BR_hjcc(j),t%BR_Hcc_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hcc_SM(j) SMrate_refmass = SMrate_refmass*BRSM_Hcc(refmass) ! STXSobs%channel_description(i,2)='cc' else if(d.eq.8) then norm_rate=norm_rate*div(t%BR_hjmumu(j),t%BR_Hmumu_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hmumu_SM(j) SMrate_refmass = SMrate_refmass*BRSM_Hmumu(refmass) ! STXSobs%channel_description(i,2)='mumu' else if(d.eq.9) then norm_rate=norm_rate*div(t%BR_hjgg(j),t%BR_Hgg_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hgg_SM(j) SMrate_refmass = SMrate_refmass*BRSM_Hgg(refmass) ! STXSobs%channel_description(i,2)='gg' else if(d.eq.10) then norm_rate=norm_rate*div(t%BR_hjss(j),t%BR_Hss_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hss_SM(j) SMrate_refmass = SMrate_refmass*BRSM_Hss(refmass) ! mutab%channel_description(i,2)='ss' else if(d.eq.11) then norm_rate=norm_rate*div(t%BR_hjtt(j),t%BR_Htt_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Htt_SM(j) SMrate_refmass = SMrate_refmass*BRSM_Htoptop(refmass) ! mutab%channel_description(i,2)='tt' else if(d.eq.0) then norm_rate=norm_rate*1.0D0 SMrate=SMrate*1.0D0 SMrate_refmass = SMrate_refmass*1.0D0 ! STXSobs%channel_description(i,2)='none' endif !------------------------- ! NEW FEATURE (since HB-5.2): Enable to set channelrates directly. if(p.ne.0.and.d.ne.0) then select case(d) case(1) BR_SMref = t%BR_Hgaga_SM(j) ! BR_SMref_mpeak = BRSM_Hgaga(refmass) case(2) BR_SMref = t%BR_HWW_SM(j) ! BR_SMref_mpeak = BRSM_HWW(refmass) case(3) BR_SMref = t%BR_HZZ_SM(j) ! BR_SMref_mpeak = BRSM_HZZ(refmass) case(4) BR_SMref = t%BR_Htautau_SM(j) ! BR_SMref_mpeak = BRSM_Htautau(refmass) case(5) BR_SMref = t%BR_Hbb_SM(j) ! BR_SMref_mpeak = BRSM_Hbb(refmass) case(6) BR_SMref = t%BR_HZga_SM(j) ! BR_SMref_mpeak = BRSM_HZga(refmass) case(7) BR_SMref = t%BR_Hcc_SM(j) ! BR_SMref_mpeak = BRSM_Hcc(refmass) case(8) BR_SMref = t%BR_Hmumu_SM(j) ! BR_SMref_mpeak = BRSM_Hmumu(refmass) case(9) BR_SMref = t%BR_Hgg_SM(j) ! BR_SMref_mpeak = BRSM_Hgg(refmass) case(10) BR_SMref = t%BR_Hss_SM(j) ! BR_SMref_mpeak = BRSM_Hgg(refmass) case(11) BR_SMref = t%BR_Htt_SM(j) ! BR_SMref_mpeak = BRSM_Htoptop(refmass) end select if(STXSobs%collider.eq.'LHC') then if(abs(STXSobs%energy-7.0D0).le.small) then if(t%lhc7%channelrates(j,p,d).ge.0.0d0) then norm_rate=div(t%lhc7%channelrates(j,p,d),BR_SMref,0.0D0,1.0D0) endif else if(abs(STXSobs%energy-8.0D0).le.small) then if(t%lhc8%channelrates(j,p,d).ge.0.0d0) then norm_rate=div(t%lhc8%channelrates(j,p,d),BR_SMref,0.0D0,1.0D0) endif else if(abs(STXSobs%energy-13.0D0).le.small) then if(t%lhc13%channelrates(j,p,d).ge.0.0d0) then norm_rate=div(t%lhc13%channelrates(j,p,d),BR_SMref,0.0D0,1.0D0) endif endif else if(STXSobs%collider.eq.'TEV') then if(t%tev%channelrates(j,p,d).ge.0.0d0) then norm_rate=div(t%tev%channelrates(j,p,d),BR_SMref,0.0D0,1.0D0) endif endif endif !------------------------- if(abs(t%particle(Hneut)%M(j) - STXSobs%mass).le.(assignmentrange_STXS * & sqrt(t%particle(Hneut)%dM(j)**2.0D0+STXSobs%dmass**2.0D0))) then ! if(STXSobs%rate_SM_normalized.eq.1) then if(normalize_rates_to_reference_position) then STXSobs%model_rate_per_Higgs(j,i)=norm_rate*SMrate/(SMrate_refmass) else STXSobs%model_rate_per_Higgs(j,i)=norm_rate !! OLD WAY endif if(normalize_rates_to_reference_position_outside_dmtheo) then if(abs(STXSobs%mass-t%particle(Hneut)%M(j)).ge.t%particle(Hneut)%dM(j)) then STXSobs%model_rate_per_Higgs(j,i)=norm_rate*SMrate/(SMrate_refmass) endif endif ! else ! if(use_SMrate_at_reference_position_for_STXS) then !--- ! n.B.: Need to use officially quoted SM prediction here, because HB/HS do not contain ! SM predictions for exclusive STXS bins (but only inclusive SM rates). !--- ! STXSobs%model_rate_per_Higgs(j,i)=norm_rate*STXSobs%SMrate ! else ! STXSobs%model_rate=norm_rate*SMrate ! endif ! endif else STXSobs%model_rate_per_Higgs(j,i) = 0.0D0 ! STXSobs%inclusive_SM_rate(j,i) = 0.0D0 endif ! Inclusive SM rate must always be evaluated at the mass position of the measurement! STXSobs%inclusive_SM_rate(i) = SMrate_refmass * STXSobs%channel_efficiency(i) ! write(*,*) "j, i, STXSobs%model_rate_per_Higgs(j,i) = ",j,i, STXSobs%model_rate_per_Higgs(j,i) ! Turn normalized rate into absolute rate (per Higgs per channel) STXSobs%model_rate_per_Higgs(j,i) = STXSobs%model_rate_per_Higgs(j,i) * & - & STXSobs%relative_efficiency(j,i) * & + & STXSobs%modification_factor(j,i) * & & STXSobs%inclusive_SM_rate(i) !& SMrate * STXSobs%channel_efficiency(i) ! write(*,*) "j, i, absolute STXSobs%model_rate_per_Higgs(j,i), STXSobs%inclusive_SM_rate(i) = ",& ! & j, i, STXSobs%model_rate_per_Higgs(j,i), STXSobs%inclusive_SM_rate(j,i) !--- ! Take into account model-dependent signal efficiency (relative to SM). ! These have to be given by the user for each observable using the subroutine ! assign_modelefficiencies_to_STXS: !--- enddo enddo ! write(*,*) "STXSobs%id = " , STXSobs%id ! write(*,*) " model_rate_per_Higgs = ",STXSobs%model_rate_per_Higgs ! write(*,*) " inclusive SM rate = ",STXSobs%inclusive_SM_rate if(sum(STXSobs%inclusive_SM_rate).ge.vsmall) then STXSobs%model_total_rate = sum(STXSobs%model_rate_per_Higgs)/sum(STXSobs%inclusive_SM_rate) ! Mistake: Don't divide by the sum over SM!! else STXSobs%model_total_rate = 0.0D0 endif ! write(*,*) "STXSobs%model_total_rate (SM norm)= ", STXSobs%model_total_rate if(STXSobs%rate_SM_normalized.eq.0) then STXSobs%model_total_rate = STXSobs%model_total_rate * STXSobs%SMrate ! write(*,*) "STXSobs%model_total_rate (absolute)= ", STXSobs%model_total_rate endif ! write(*,*) "#--------------- ", STXSobs%id, " ---------------#" ! do i=1,STXSobs%Nc ! write(*,*) "channel id = ", STXSobs%channel_id(i), " rate = ", & ! & sum(STXSobs%model_rate_per_Higgs(:,i))/sum(STXSobs%inclusive_SM_rate)*STXSobs%SMrate ! enddo -! STXSobs%model_total_rate + STXSobs%relative_efficiency(j) * STXSobs%model_rate_per_Higgs(j) +! STXSobs%model_total_rate + STXSobs%modification_factor(j) * STXSobs%model_rate_per_Higgs(j) ! write(*,*) "Total rate: ", STXSobs%model_total_rate end subroutine evaluate_model_for_STXS !------------------------------------------------------------------------------------ subroutine print_STXS() !------------------------------------------------------------------------------------ implicit none integer :: i character(LEN=100) :: formatter do i=lbound(STXSlist,dim=1), ubound(STXSlist,dim=1) write(*,*) "#--------------------------------------------------#" write(*,*) "#- STXS observable ",i," -#" write(*,*) "#--------------------------------------------------#" write(*,'(A,I10)') " ID = ", STXSlist(i)%id write(*,'(A,A)') " Label = ", STXSlist(i)%label write(*,'(A,A)') " Description = ", STXSlist(i)%desc write(*,'(A,A)') " Experiment = ", STXSlist(i)%expt write(*,'(A,2F6.2)') " Energy, Luminosity = ", STXSlist(i)%energy, STXSlist(i)%lumi write(*,'(A,F10.5,A,F10.5,A,F10.5)') " Obs Signal rate [pb] = ",& & STXSlist(i)%rate, " + ", STXSlist(i)%drate_up, " - ", STXSlist(i)%drate_low write(*,'(A,F10.5,A,F10.5,A,F10.5)') " SM Signal rate [pb] = ",& & STXSlist(i)%SMrate, " + ", STXSlist(i)%dSMrate_up, " - ", STXSlist(i)%dSMrate_low write(*,'(A,F10.5)') " Pred. Signal rate [pb] = ", STXSlist(i)%model_total_rate write(formatter,*) "(A,",STXSlist(i)%Nc,"I10)" formatter = trim(adjustl(formatter)) write(*,'(A)') " Channels = ", STXSlist(i)%channel_id_str write(formatter,*) "(A,",STXSlist(i)%Nc,"F10.5)" formatter = trim(adjustl(formatter)) write(*,formatter) " Channel efficiency = ", STXSlist(i)%channel_efficiency enddo write(*,*) "#--------------------------------------------------#" end subroutine print_STXS !------------------------------------------------------------------------------------ subroutine print_STXS_to_file !------------------------------------------------------------------------------------ use usefulbits, only : file_id_common3 use usefulbits_hs, only : StrCompress implicit none character(LEN=100) :: formatspec integer :: i formatspec='(I3,7X,I10,1X,F6.2,1X,6F10.6,1X,A3,1X,F6.2,1X,F6.2,1X,A,5X,A)' open(file_id_common3,file="STXS_information.txt") write(file_id_common3,*) "#HiggsSignals-"//trim(adjustl(HSvers))// & & " with experimental dataset '"//trim(adjustl(Exptdir))//"'" write(file_id_common3,*) "#Number STXS-ID mass-pos rate_obs drate_low drate_high ", & & "rate_SM dSMrate_low dSMrate_high collaboration energy luminosity description reference" write(file_id_common3,*) "#" do i=lbound(STXSlist,dim=1),ubound(STXSlist,dim=1) write(file_id_common3,formatspec) i ,STXSlist(i)%id,STXSlist(i)%mass, & & STXSlist(i)%rate, STXSlist(i)%drate_low,STXSlist(i)%drate_up, & & STXSlist(i)%SMrate, STXSlist(i)%dSMrate_low,STXSlist(i)%dSMrate_up, & & STXSlist(i)%collaboration, STXSlist(i)%energy, & & STXSlist(i)%lumi, trim(strcompress(STXSlist(i)%desc)), STXSlist(i)%label enddo close(file_id_common3) end subroutine print_STXS_to_file !------------------------------------------------------------------------------------ subroutine clear_STXS() !------------------------------------------------------------------------------------ implicit none integer :: i do i=lbound(STXSlist,dim=1), ubound(STXSlist,dim=1) deallocate(STXSlist(i)%model_rate_per_Higgs) deallocate(STXSlist(i)%inclusive_SM_rate) deallocate(STXSlist(i)%channel_id_str) deallocate(STXSlist(i)%channel_p_id) deallocate(STXSlist(i)%channel_d_id) deallocate(STXSlist(i)%channel_efficiency) - deallocate(STXSlist(i)%relative_efficiency) + deallocate(STXSlist(i)%modification_factor) enddo deallocate(STXSlist) if(allocated(STXScorrlist)) deallocate(STXScorrlist) end subroutine clear_STXS !------------------------------------------------------------------------------------ end module STXS !------------------------------------------------------------------------------------ \ No newline at end of file Index: trunk/webversion/minipaper.bib =================================================================== --- trunk/webversion/minipaper.bib (revision 600) +++ trunk/webversion/minipaper.bib (revision 601) @@ -1,1808 +1,1717 @@ @misc{CDFnotes, collaboration = "CDF", - note = "CDF Notes 10500 10799 10573 8353 9999 10796 7307 10574 10485 7712 10010 10439 10599 10798", + note = "CDF Notes 9999 10574 7307 7712 10485 10010 10798 10799 10573 10439 10500 8353 10599 10796", year = "" } @misc{D0notes, collaboration = "D0", title = "", - note = "D0 Notes 6304 6305 6296 5873 6302 5739 6299 6227 6083 6295 6276 5845 6301 6183 6171 6286 6309 5757", + note = "D0 Notes 5845 6304 6276 6286 6305 6083 5873 5739 6227 6296 6299 6183 6301 6295 6309 6171 5757 6302", year = "" } @misc{CMSnotes, collaboration = "CMS", title = "", note = "CMS Physics Analysis Summaries", year = "" } @misc{ATLASnotes, collaboration = "ATLAS", title = "", - note = "ATLAS CONF Notes 2012-160 2016-062 2016-089 2016-049 2012-135 2013-013 2012-161 2016-004 2016-059 2014-049 2016-074 2014-050 2012-092 2012-078 2016-088 2012-016 2012-019 2016-044 2016-071 2012-168 2011-094 2013-010 2016-055 2011-157 2016-056 2012-012 2013-030 2016-015 2016-079 2012-017 2016-082", + note = "ATLAS CONF Notes 2016-079 2012-135 2012-017 2013-030 2016-044 2011-094 2016-049 2016-056 2013-010 2016-074 2012-078 2014-049 2014-050 2012-012 2013-013 2016-004 2016-055 2016-015 2012-161 2016-071 2016-088 2011-157 2012-160 2012-019 2012-016 2018-025 2016-082 2012-092 2012-168 2016-062", year = "" } @misc{LHWGnotes, collaboration = "LHWG", title = "", note = "LHWG Notes 2002-02", year = "" } -% Save this file and include it in your paper as the bibliography -% or cut and paste directly into your LaTeX - @Article{arXiv:0811.4169, author = "Bechtle, Philip and Brein, Oliver and Heinemeyer, Sven and Weiglein, Georg and Williams, Karina E.", title = "{HiggsBounds: Confronting Arbitrary Higgs Sectors with Exclusion Bounds from LEP and the Tevatron}", journal = "Comput. Phys. Commun.", volume = "181", year = "2010", pages = "138-167", eprint = "0811.4169", archivePrefix = "arXiv", primaryClass = "hep-ph", doi = "10.1016/j.cpc.2009.09.003", SLACcitation = "%%CITATION = 0811.4169;%%" } @Article{arXiv:1102.1898, author = "Bechtle, Philip and Brein, Oliver and Heinemeyer, Sven and Weiglein, Georg and Williams, Karina E.", title = "{HiggsBounds 2.0.0: Confronting Neutral and Charged Higgs Sector Predictions with Exclusion Bounds from LEP and the Tevatron}", journal = "Comput. Phys. Commun.", volume = "182", year = "2011", pages = "2605-2631", eprint = "1102.1898", archivePrefix = "arXiv", primaryClass = "hep-ph", doi = "10.1016/j.cpc.2011.07.015", SLACcitation = "%%CITATION = 1102.1898;%%" } @Article{arXiv:1301.2345, author = "Bechtle, Philip and others", title = "{Recent Developments in HiggsBounds and a Preview of HiggsSignals}", journal = "PoS", volume = "CHARGED2012", year = "2012", pages = "024", eprint = "1301.2345", archivePrefix = "arXiv", primaryClass = "hep-ph", SLACcitation = "%%CITATION = 1301.2345;%%" } @Article{arXiv:1311.0055, author = "Bechtle, Philip and others", title = "{HiggsBounds-4: Improved Tests of Extended Higgs Sectors against Exclusion Bounds from LEP, the Tevatron and the LHC}", journal = "Eur. Phys. J.", volume = "C74", year = "2014", pages = "2693", eprint = "1311.0055", archivePrefix = "arXiv", primaryClass = "hep-ph", SLACcitation = "%%CITATION = 1311.0055;%%" } @Article{arXiv:1507.06706, author = "Bechtle, Philip and Heinemeyer, Sven and Stal, Oscar and Stefaniak, Tim and Weiglein, Georg", title = "{Applying Exclusion Likelihoods from LHC Searches to Extended Higgs Sectors}", year = "2015", eprint = "1507.06706", archivePrefix = "arXiv", primaryClass = "hep-ph", SLACcitation = "%%CITATION = 1507.06706;%%" } -@Article{arXiv:1112.2577, - author = "Aad, Georges", +@Article{arXiv:1406.7663, + author = ",", collaboration = "ATLAS", - title = "{Search for the Higgs boson in the H->WW(*)->lvlv decay - channel in pp collisions at sqrt{s} = 7 TeV with the ATLAS - detector}", - journal = "Phys. Rev. Lett.", - volume = "108", - year = "2012", - pages = "111802", - eprint = "1112.2577", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.108.111802", - SLACcitation = "%%CITATION = 1112.2577;%%" -} - -@Article{arXiv:0806.0611, - author = "Abazov, V. M. and others", -collaboration = "D0", - title = "{Search for a scalar or vector particle decaying into - Zgamma in p anti-p collisions at s**(1/2) = 1.96-TeV}", - journal = "Phys. Lett.", - volume = "B671", - year = "2009", - pages = "349-355", - eprint = "0806.0611", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1016/j.physletb.2008.12.009", - SLACcitation = "%%CITATION = 0806.0611;%%" -} - -@Article{arXiv:1207.0449, - author = "Group, CDF and D0 Collaborations and the Tevatron New Physics an - ", -collaboration = "Tevatron New Physics Higgs Working Group", - title = "{Updated Combination of CDF and D0 Searches for Standard - Model Higgs Boson Production with up to 10.0 fb$^{-1}$ of - Data}", - year = "2012", - eprint = "1207.0449", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1207.0449;%%" -} - -@Article{arXiv:0809.3930, - author = "Aaltonen, T. and others", -collaboration = "CDF", - title = "{Search for a Higgs Boson Decaying to Two W Bosons at - CDF}", - journal = "Phys. Rev. Lett.", - volume = "102", - year = "2009", - pages = "021802", - eprint = "0809.3930", + title = "{Search for the Standard Model Higgs boson decay to + $\mu^{+}\mu^{-}$ with the ATLAS detector}", + journal = "Physics Letters", + volume = "B738", + year = "2014", + pages = "68-86", + eprint = "1406.7663", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.102.021802", - SLACcitation = "%%CITATION = 0809.3930;%%" + SLACcitation = "%%CITATION = 1406.7663;%%" } -@Article{arXiv:0901.1887, - author = "Abazov, V. M. and others", +@Article{arXiv:1106.4885, + author = "Abazov, Victor Mukhamedovich and others", collaboration = "D0", - title = "{Search for Resonant Diphoton Production with the D0 - Detector}", + title = "{Search for neutral Higgs bosons decaying to tau pairs + produced in association with b quarks in ppbar collisions + at sqrt(s)=1.96 TeV}", journal = "Phys. Rev. Lett.", - volume = "102", - year = "2009", - pages = "231801", - eprint = "0901.1887", + volume = "107", + year = "2011", + pages = "121801", + eprint = "1106.4885", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.102.231801", - SLACcitation = "%%CITATION = 0901.1887;%%" + doi = "10.1103/PhysRevLett.107.121801", + SLACcitation = "%%CITATION = 1106.4885;%%" } -@Article{arXiv:1603.06896, +@Article{arXiv:1603.02991, author = ",", collaboration = "CMS", - title = "{Search for two Higgs bosons in final states containing two - photons and two bottom quarks}", + title = "{Search for neutral resonances decaying into a Z boson and + a pair of b jets or tau leptons}", + journal = "Phys. Lett.", + volume = "B759", year = "2016", - eprint = "1603.06896", + pages = "369", + eprint = "1603.02991", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1603.06896;%%" + SLACcitation = "%%CITATION = 1603.02991;%%" } -@Article{arXiv:1108.3331, - author = "Benjamin, Doug and others", -collaboration = "CDF", - title = "{Combined CDF and D0 upper limits on gg->H W+W- and - constraints on the Higgs boson mass in fourth-generation - fermion models with up to 8.2 fb-1 of data}", +@Article{arXiv:1107.1268, + author = "Abazov, V. M. and others", +collaboration = "D0", + title = "{Search for associated Higgs boson production using like + charge dilepton events in ppbar collisions at sqrt{s} = + 1.96 TeV}", + journal = "Phys. Rev.", + volume = "D84", year = "2011", - eprint = "1108.3331", + pages = "092002", + eprint = "1107.1268", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1108.3331;%%" + doi = "10.1103/PhysRevD.84.092002", + SLACcitation = "%%CITATION = 1107.1268;%%" } -@Article{arXiv:1109.3357, - author = " and others", -collaboration = "ATLAS", - title = "{Search for a Standard Model Higgs boson in the H->ZZ- -llnunu decay channel with the ATLAS detector}", +% No SPIRES record found for cite request arXiv:1809.06682 + +@Article{arXiv:1001.4468, + author = "Aaltonen, T. and others", +collaboration = "CDF", + title = "{Inclusive Search for Standard Model Higgs Boson Production + in the WW Decay Channel using the CDF II Detector}", journal = "Phys. Rev. Lett.", - volume = "107", - year = "2011", - pages = "221802", - eprint = "1109.3357", + volume = "104", + year = "2010", + pages = "061803", + eprint = "1001.4468", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.107.221802", - SLACcitation = "%%CITATION = 1109.3357;%%" + doi = "10.1103/PhysRevLett.104.061803", + SLACcitation = "%%CITATION = 1001.4468;%%" } -@Article{arXiv:1202.1408, - author = "Aad, Georges", -collaboration = "ATLAS", - title = "{Combined search for the Standard Model Higgs boson using - up to 4.9 fb$^{-1}$ of $pp$ collision data at $\sqrt{s}=7$ - TeV with the ATLAS detector at the LHC}", - journal = "Phys. Lett.", - volume = "B710", - year = "2012", - pages = "49-66", - eprint = "1202.1408", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1016/j.physletb.2012.02.044", - SLACcitation = "%%CITATION = 1202.1408;%%" -} +% No SPIRES record found for cite request arXiv:1807.00539 -% No SPIRES record found for cite request arXiv:1712.06386 +% No SPIRES record found for cite request arXiv:1807.07915 -@Article{arXiv:1003.3363, - author = "Benjamin, Doug and others", -collaboration = "Tevatron New Phenomena and Higgs Working Group", - title = "{Combined CDF and D0 upper limits on MSSM Higgs boson - production in tau-tau final states with up to 2.2 fb-1}", - year = "2010", - eprint = "1003.3363", +@Article{arXiv:1503.04233, + author = ",", +collaboration = "ATLAS", + title = "{Search for a Charged Higgs Boson Produced in the Vector- + boson Fusion Mode with Decay $H^\pm \to W^\pm Z$ using $pp$ + Collisions at $\sqrt{s}=8$ TeV with the ATLAS Experiment}", + journal = "", + volume = "", + year = "2015", + pages = "", + year = "2015", + eprint = "1503.04233", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1003.3363;%%" + SLACcitation = "%%CITATION = 1503.04233;%%" } -@Article{arXiv:1012.0874, - author = "Abazov, Victor Mukhamedovich and others", -collaboration = "D0", - title = "{Search for $WH$ associated production in 5.3 fb$^{-1}$ of - $p\bar{p}$ collisions at the Fermilab Tevatron}", - journal = "Phys. Lett.", - volume = "B698", - year = "2011", - pages = "6-13", - eprint = "1012.0874", +@Article{arXiv:1509.00389, + author = ",", +collaboration = "ATLAS", + title = "{Search for a high-mass Higgs boson decaying to a $W$ boson + pair in $pp$ collisions at $\sqrt{s} = 8$ TeV with the + ATLAS detector}", + journal = "", + volume = "JHEP01", + year = "2016", + pages = "032", + year = "2015", + eprint = "1509.00389", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1016/j.physletb.2011.02.036", - SLACcitation = "%%CITATION = 1012.0874;%%" + SLACcitation = "%%CITATION = 1509.00389;%%" } -@Article{arXiv:1202.3478, - author = "Chatrchyan, Serguei", -collaboration = "CMS", - title = "{Search for the standard model Higgs boson in the H to ZZ - to 2l 2nu channel in pp collisions at sqrt(s) = 7 TeV}", - journal = "JHEP", - volume = "03", - year = "2012", - pages = "040", - eprint = "1202.3478", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1007/JHEP03(2012)040", - SLACcitation = "%%CITATION = 1202.3478;%%" -} +% No SPIRES record found for cite request arXiv:1701.02032 -@Article{arXiv:1504.00936, +@Article{arXiv:1504.04710, author = ",", collaboration = "CMS", - title = "{Search for a Higgs boson in the mass range from 145 to - 1000 GeV decaying to a pair of W or Z bosons}", + title = "{Search for a pseudoscalar boson decaying into a Z boson + and the 125 GeV Higgs boson in llbb final states}", + journal = "Phys. Lett.", + volume = "B748", year = "2015", - eprint = "1504.00936", + pages = "221", + eprint = "1504.04710", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1504.00936;%%" + SLACcitation = "%%CITATION = 1504.04710;%%" } -@Article{arXiv:1502.04478, - author = ",", -collaboration = "ATLAS", - title = "{Search for a CP-odd Higgs boson decaying to $Zh$ in $pp$ - collisions at $\sqrt{s} = 8$ TeV with the ATLAS detector}", - journal = "Physics Letters", - volume = "B744", - year = "2015", - pages = "163-183", - eprint = "1502.04478", +% No SPIRES record found for cite request arXiv:1807.04873 + +@Article{hep-ex/0107031, + author = "", +collaboration = "LEP Higgs Working Group for Higgs boson searches", + title = "{Search for charged Higgs bosons: Preliminary combined + results using LEP data collected at energies up to 209- + GeV}", + year = "2001", + eprint = "hep-ex/0107031", archivePrefix = "arXiv", - primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1502.04478;%%" + SLACcitation = "%%CITATION = HEP-EX/0107031;%%" } -@Article{arXiv:1509.05051, - author = ",", -collaboration = "ATLAS", - title = "{Search for new phenomena in events with at least three - photons collected in $pp$ collisions at $\sqrt{s}$ = 8 TeV - with the ATLAS detector}", - journal = "", - volume = "", - year = "2015", - pages = "", - year = "2015", - eprint = "1509.05051", +@Article{hep-ex/0410017, + author = "Abdallah, J. and others", +collaboration = "DELPHI", + title = "{Searches for neutral Higgs bosons in extended models}", + journal = "Eur. Phys. J.", + volume = "C38", + year = "2004", + pages = "1-28", + eprint = "hep-ex/0410017", archivePrefix = "arXiv", - primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1509.05051;%%" + doi = "10.1140/epjc/s2004-02011-4", + SLACcitation = "%%CITATION = HEP-EX/0410017;%%" } @Article{arXiv:1507.05930, author = ",", collaboration = "ATLAS", title = "{Search for an additional, heavy Higgs boson in the $H\rightarrow ZZ$ decay channel at $\sqrt{s}$ = 8 TeV in $pp$ collision data with the ATLAS detector}", journal = "Eur. Phys. J.", volume = "C76", year = "2016", pages = "45", eprint = "1507.05930", archivePrefix = "arXiv", primaryClass = "hep-ex", SLACcitation = "%%CITATION = 1507.05930;%%" } -@Article{arXiv:1011.1931, - author = "Abazov, Victor Mukhamedovich and others", -collaboration = "D0", - title = "{Search for neutral Higgs bosons in the multi-b-jet - topology in 5.2fb-1 of ppbar collisions at sqrt(s)=1.96 - TeV}", - journal = "Phys. Lett.", - volume = "B698", - year = "2011", - pages = "97-104", - eprint = "1011.1931", +@Article{arXiv:1407.6583, + author = ",", +collaboration = "ATLAS", + title = "{Search for Scalar Diphoton Resonances in the Mass Range + $65-600$ GeV with the ATLAS Detector in $pp$ Collision Data + at $\sqrt{s}$ = 8 $TeV$}", + year = "2014", + eprint = "1407.6583", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1016/j.physletb.2011.02.062", - SLACcitation = "%%CITATION = 1011.1931;%%" + SLACcitation = "%%CITATION = 1407.6583;%%" } -@Article{arXiv:1506.00424, +@Article{arXiv:1504.00936, author = ",", collaboration = "CMS", - title = "{A search for pair production of new light bosons decaying - into muons}", - journal = "Phys. Lett.", - volume = "B752", - year = "2016", - pages = "146", - eprint = "1506.00424", + title = "{Search for a Higgs boson in the mass range from 145 to + 1000 GeV decaying to a pair of W or Z bosons}", + year = "2015", + eprint = "1504.00936", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1506.00424;%%" + SLACcitation = "%%CITATION = 1504.00936;%%" } -@Article{arXiv:1503.04233, +@Article{arXiv:1406.5053, author = ",", collaboration = "ATLAS", - title = "{Search for a Charged Higgs Boson Produced in the Vector- - boson Fusion Mode with Decay $H^\pm \to W^\pm Z$ using $pp$ - Collisions at $\sqrt{s}=8$ TeV with the ATLAS Experiment}", + title = "{Search For Higgs Boson Pair Production in the + $\gamma\gamma b\bar{b}$ Final State using $pp$ Collision + Data at $\sqrt{s}=8$ TeV from the ATLAS Detector}", journal = "", volume = "", - year = "2015", + year = "2014", pages = "", - year = "2015", - eprint = "1503.04233", + year = "2014", + eprint = "1406.5053", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1503.04233;%%" + SLACcitation = "%%CITATION = 1406.5053;%%" } @Article{arXiv:1008.3564, author = "Abazov, Victor Mukhamedovich and others", collaboration = "D0", title = "{Search for $ZH \rightarrow \ell^+\ell^-b\bar{b}$ production in $4.2$~fb$^{-1}$ of $p\bar{p}$ collisions at $\sqrt{s}=1.96$ TeV}", journal = "Phys. Rev. Lett.", volume = "105", year = "2010", pages = "251801", eprint = "1008.3564", archivePrefix = "arXiv", primaryClass = "hep-ex", doi = "10.1103/PhysRevLett.105.251801", SLACcitation = "%%CITATION = 1008.3564;%%" } -@Article{hep-ex/0404012, +@Article{hep-ex/0401022, author = "Abdallah, J. and others", collaboration = "DELPHI", - title = "{Search for charged Higgs bosons at LEP in general two - Higgs doublet models}", + title = "{Searches for invisibly decaying Higgs bosons with the + DELPHI detector at LEP}", journal = "Eur. Phys. J.", - volume = "C34", + volume = "C32", year = "2004", - pages = "399-418", - eprint = "hep-ex/0404012", + pages = "475-492", + eprint = "hep-ex/0401022", archivePrefix = "arXiv", - doi = "10.1140/epjc/s2004-01732-6", - SLACcitation = "%%CITATION = HEP-EX/0404012;%%" + doi = "10.1140/epjc/s2003-01469-8", + SLACcitation = "%%CITATION = HEP-EX/0401022;%%" } -@Article{arXiv:1108.5064, - author = "Aad, Georges", -collaboration = "ATLAS", - title = "{Search for a heavy Standard Model Higgs boson in the - channel H->ZZ->llqq using the ATLAS detector}", +@Article{arXiv:1506.02301, + author = ",", +collaboration = "CMS", + title = "{Search for diphoton resonances in the mass range from 150 + to 850 GeV in pp collisions at sqrt(s) = 8 TeV}", journal = "Phys. Lett.", - volume = "B707", - year = "2012", - pages = "27-45", - eprint = "1108.5064", + volume = "B750", + year = "2015", + pages = "494", + eprint = "1506.02301", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1016/j.physletb.2011.11.056", - SLACcitation = "%%CITATION = 1108.5064;%%" + SLACcitation = "%%CITATION = 1506.02301;%%" } % No SPIRES record found for cite request arXiv:1710.01123 -@Article{arXiv:1509.00389, - author = ",", +@Article{arXiv:1202.1415, + author = "Aad, G. and others", collaboration = "ATLAS", - title = "{Search for a high-mass Higgs boson decaying to a $W$ boson - pair in $pp$ collisions at $\sqrt{s} = 8$ TeV with the - ATLAS detector}", - journal = "", - volume = "JHEP01", - year = "2016", - pages = "032", - year = "2015", - eprint = "1509.00389", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1509.00389;%%" -} - -@Article{arXiv:1202.1416, - author = "Chatrchyan, Serguei", -collaboration = "CMS", - title = "{Search for a Higgs boson in the decay channel H to ZZ(*) - to q qbar l-l+ in pp collisions at sqrt(s) = 7 TeV}", - journal = "JHEP", - volume = "04", - year = "2012", - pages = "036", - eprint = "1202.1416", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1007/JHEP04(2012)036", - SLACcitation = "%%CITATION = 1202.1416;%%" -} - -@Article{hep-ex/0501033, - author = "Achard, P. and others", -collaboration = "L3", - title = "{Search for an invisibly-decaying Higgs boson at LEP}", + title = "{Search for the Standard Model Higgs boson in the decay + channel H->ZZ(*)->4l with 4.8 fb-1 of pp collision data at + sqrt(s) = 7 TeV with ATLAS}", journal = "Phys. Lett.", - volume = "B609", - year = "2005", - pages = "35-48", - eprint = "hep-ex/0501033", - archivePrefix = "arXiv", - doi = "10.1016/j.physletb.2005.01.030", - SLACcitation = "%%CITATION = HEP-EX/0501033;%%" -} - -% No SPIRES record found for cite request arXiv:1701.02032 - -@Article{arXiv:1506.08329, - author = ",", -collaboration = "CMS", - title = "{Search for neutral MSSM Higgs bosons decaying into a pair - of bottom quarks}", - journal = "", - volume = "JHEP11", - year = "2015", - pages = "071", - year = "2015", - eprint = "1506.08329", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1506.08329;%%" -} - -@Article{arXiv:0905.3381, - author = "Abazov, V. M. and others", -collaboration = "D0", - title = "{Search for NMSSM Higgs bosons in the $h \to a a - \to\mu\mu\: \mu\mu, \mu\mu \: \tau\tau$ channels using $p - \bar{p}$ collisions at $\sqrt{s}$=1.96 TeV}", - journal = "Phys. Rev. Lett.", - volume = "103", - year = "2009", - pages = "061801", - eprint = "0905.3381", + volume = "B710", + year = "2012", + pages = "383-402", + eprint = "1202.1415", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.103.061801", - SLACcitation = "%%CITATION = 0905.3381;%%" + doi = "10.1016/j.physletb.2012.03.005", + SLACcitation = "%%CITATION = 1202.1415;%%" } @Article{arXiv:1001.4481, author = "Abazov, V. M. and others", collaboration = "D0", title = "{Search for Higgs boson production in dilepton and missing energy final states with ~5.4 $\bm{\mathrm{fb^{-1}}}$ of $\bm{p\bar{p}}$ collisions at $\bm{\sqrt $s$ =1.96}$ TeV}", journal = "Phys. Rev. Lett.", volume = "104", year = "2010", pages = "061804", eprint = "1001.4481", archivePrefix = "arXiv", primaryClass = "hep-ex", doi = "10.1103/PhysRevLett.104.061804", SLACcitation = "%%CITATION = 1001.4481;%%" } -% No SPIRES record found for cite request arXiv:1709.07242 +@Article{arXiv:1107.4960, + author = " and others", +collaboration = "TEVNPH Working Group", + title = "{Combined CDF and D0 Searches for the Standard Model Higgs + Boson Decaying to Two Photons with up to 8.2 fb^-1}", + year = "2011", + eprint = "1107.4960", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1107.4960;%%" +} @Article{arXiv:1402.3244, author = ",", collaboration = "ATLAS", title = "{Search for Invisible Decays of a Higgs Boson Produced in Association with a Z Boson in ATLAS}", journal = "", volume = "", year = "2014", pages = "", year = "2014", eprint = "1402.3244", archivePrefix = "arXiv", primaryClass = "hep-ex", SLACcitation = "%%CITATION = 1402.3244;%%" } -@Article{arXiv:1409.6064, +@Article{arXiv:1112.2577, + author = "Aad, Georges", +collaboration = "ATLAS", + title = "{Search for the Higgs boson in the H->WW(*)->lvlv decay + channel in pp collisions at sqrt{s} = 7 TeV with the ATLAS + detector}", + journal = "Phys. Rev. Lett.", + volume = "108", + year = "2012", + pages = "111802", + eprint = "1112.2577", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + doi = "10.1103/PhysRevLett.108.111802", + SLACcitation = "%%CITATION = 1112.2577;%%" +} + +@Article{arXiv:1301.6065, + author = "Abbiendi, G. and others", +collaboration = "ALEPH", + title = "{Search for Charged Higgs bosons: Combined Results Using + LEP Data}", + year = "2013", + eprint = "1301.6065", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1301.6065;%%" +} + +% No SPIRES record found for cite request arXiv:1807.08567 + +@Article{arXiv:0906.1014, + author = "Aaltonen, T. and others", +collaboration = "CDF", + title = "{Search for Higgs bosons predicted in two-Higgs-doublet + models via decays to tau lepton pairs in 1.96 TeV proton- + antiproton collisions}", + journal = "Phys. Rev. Lett.", + volume = "103", + year = "2009", + pages = "201801", + eprint = "0906.1014", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + doi = "10.1103/PhysRevLett.103.201801", + SLACcitation = "%%CITATION = 0906.1014;%%" +} + +@Article{arXiv:1503.04114, + author = ",", +collaboration = "CMS", + title = "{Search for resonant pair production of Higgs bosons + decaying to two bottom quark-antiquark pairs in proton- + proton collisions at 8 TeV}", + journal = "Phys. Lett.", + volume = "B749", + year = "2015", + pages = "560", + eprint = "1503.04114", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1503.04114;%%" +} + +@Article{arXiv:1509.05051, author = ",", collaboration = "ATLAS", - title = "{Search for neutral Higgs bosons of the minimal - supersymmetric standard model in pp collisions at - $\sqrt{s}$ = 8 TeV with the ATLAS detector}", + title = "{Search for new phenomena in events with at least three + photons collected in $pp$ collisions at $\sqrt{s}$ = 8 TeV + with the ATLAS detector}", journal = "", volume = "", - year = "2014", + year = "2015", pages = "", - year = "2014", - eprint = "1409.6064", + year = "2015", + eprint = "1509.05051", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1409.6064;%%" + SLACcitation = "%%CITATION = 1509.05051;%%" } +@Article{arXiv:1202.1997, + author = "Chatrchyan, Serguei", +collaboration = "CMS", + title = "{Search for the standard model Higgs boson in the decay + channel H to ZZ to 4 leptons in pp collisions at sqrt(s) = + 7 TeV}", + journal = "Phys. Rev. Lett.", + volume = "108", + year = "2012", + pages = "111804", + eprint = "1202.1997", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + doi = "10.1103/PhysRevLett.108.111804", + SLACcitation = "%%CITATION = 1202.1997;%%" +} + +@Article{hep-ex/0111010, + author = "Abbiendi, G. and others", +collaboration = "OPAL", + title = "{Search for Yukawa production of a light neutral Higgs + boson at LEP}", + journal = "Eur. Phys. J.", + volume = "C23", + year = "2002", + pages = "397-407", + eprint = "hep-ex/0111010", + archivePrefix = "arXiv", + doi = "10.1007/s100520200896", + SLACcitation = "%%CITATION = HEP-EX/0111010;%%" +} + +@Article{hep-ex/0602042, + author = "Schael, S. and others", +collaboration = "ALEPH", + title = "{Search for neutral MSSM Higgs bosons at LEP}", + journal = "Eur. Phys. J.", + volume = "C47", + year = "2006", + pages = "547-587", + eprint = "hep-ex/0602042", + archivePrefix = "arXiv", + doi = "10.1140/epjc/s2006-02569-7", + SLACcitation = "%%CITATION = HEP-EX/0602042;%%" +} + +@Article{arXiv:1011.1931, + author = "Abazov, Victor Mukhamedovich and others", +collaboration = "D0", + title = "{Search for neutral Higgs bosons in the multi-b-jet + topology in 5.2fb-1 of ppbar collisions at sqrt(s)=1.96 + TeV}", + journal = "Phys. Lett.", + volume = "B698", + year = "2011", + pages = "97-104", + eprint = "1011.1931", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + doi = "10.1016/j.physletb.2011.02.062", + SLACcitation = "%%CITATION = 1011.1931;%%" +} + +% No SPIRES record found for cite request arXiv:1707.04147 + @Article{arXiv:1509.04670, author = ",", collaboration = "ATLAS", title = "{Searches for Higgs boson pair production in the $hh\to bb\tau\tau, \gamma\gamma WW*, \gamma\gamma bb, bbbb$ channels with the ATLAS detector}", journal = "", volume = "", year = "2015", pages = "", year = "2015", eprint = "1509.04670", archivePrefix = "arXiv", primaryClass = "hep-ex", SLACcitation = "%%CITATION = 1509.04670;%%" } -@Article{arXiv:0908.1811, - author = "Abazov, V. M. and others", -collaboration = "D0", - title = "{Search for charged Higgs bosons in top quark decays}", - journal = "Phys. Lett.", - volume = "B682", - year = "2009", - pages = "278-286", - eprint = "0908.1811", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1016/j.physletb.2009.11.016", - SLACcitation = "%%CITATION = 0908.1811;%%" -} - -@Article{hep-ex/0410017, - author = "Abdallah, J. and others", -collaboration = "DELPHI", - title = "{Searches for neutral Higgs bosons in extended models}", - journal = "Eur. Phys. J.", - volume = "C38", - year = "2004", - pages = "1-28", - eprint = "hep-ex/0410017", - archivePrefix = "arXiv", - doi = "10.1140/epjc/s2004-02011-4", - SLACcitation = "%%CITATION = HEP-EX/0410017;%%" -} - @Article{arXiv:1202.1414, author = "Aad, Georges", collaboration = "ATLAS", title = "{Search for the Standard Model Higgs boson in the diphoton decay channel with 4.9 fb$^{-1}$ of $pp$ collisions at $\sqrt{s}=7$ TeV with ATLAS}", journal = "Phys. Rev. Lett.", volume = "108", year = "2012", pages = "111803", eprint = "1202.1414", archivePrefix = "arXiv", primaryClass = "hep-ex", doi = "10.1103/PhysRevLett.108.111803", SLACcitation = "%%CITATION = 1202.1414;%%" } -@Article{arXiv:1001.4468, - author = "Aaltonen, T. and others", -collaboration = "CDF", - title = "{Inclusive Search for Standard Model Higgs Boson Production - in the WW Decay Channel using the CDF II Detector}", +% No SPIRES record found for cite request arXiv:1709.07242 + +@Article{arXiv:1109.3357, + author = " and others", +collaboration = "ATLAS", + title = "{Search for a Standard Model Higgs boson in the H->ZZ- +llnunu decay channel with the ATLAS detector}", journal = "Phys. Rev. Lett.", - volume = "104", - year = "2010", - pages = "061803", - eprint = "1001.4468", + volume = "107", + year = "2011", + pages = "221802", + eprint = "1109.3357", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.104.061803", - SLACcitation = "%%CITATION = 1001.4468;%%" + doi = "10.1103/PhysRevLett.107.221802", + SLACcitation = "%%CITATION = 1109.3357;%%" } -@Article{arXiv:1204.2760, - author = "Aad, Georges", -collaboration = "ATLAS", - title = "{Search for charged Higgs bosons decaying via H+ -> tau nu - in top quark pair events using pp collision data at sqrt(s) - = 7 TeV with the ATLAS detector}", - journal = "JHEP", - volume = "06", +% No SPIRES record found for cite request arXiv:1808.03599 + +@Article{arXiv:0812.0267, + author = "Abbiendi, G. and others", +collaboration = "OPAL", + title = "{Search for Charged Higgs Bosons in e+e- Collisions at + sqrts(s) = 189-209 GeV}", + journal = "Eur. Phys. J.", + volume = "C72", year = "2012", - pages = "039", - eprint = "1204.2760", + pages = "2076", + eprint = "0812.0267", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1007/JHEP06(2012)039", - SLACcitation = "%%CITATION = 1204.2760;%%" + doi = "10.1140/epjc/s10052-012-2076-0", + SLACcitation = "%%CITATION = 0812.0267;%%" +} + +@Article{arXiv:0806.0611, + author = "Abazov, V. M. and others", +collaboration = "D0", + title = "{Search for a scalar or vector particle decaying into + Zgamma in p anti-p collisions at s**(1/2) = 1.96-TeV}", + journal = "Phys. Lett.", + volume = "B671", + year = "2009", + pages = "349-355", + eprint = "0806.0611", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + doi = "10.1016/j.physletb.2008.12.009", + SLACcitation = "%%CITATION = 0806.0611;%%" +} + +@Article{arXiv:1510.01181, + author = ",", +collaboration = "CMS", + title = "{Searches for a heavy scalar boson H decaying to a pair of + 125 GeV Higgs bosons hh or for a heavy pseudoscalar boson A + decaying to Zh, in the final states with h to tau tau}", + journal = "Phys. Lett.", + volume = "B755", + year = "2016", + pages = "217", + eprint = "1510.01181", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1510.01181;%%" +} + +@Article{arXiv:1307.5515, + author = ",", +collaboration = "CMS", + title = "{Search for a Higgs boson decaying into a Z and a photon in + pp collisions at sqrt(s) = 7 and 8 TeV}", + journal = "Phys. Lett.", + volume = "B726", + year = "2013", + pages = "587", + eprint = "1307.5515", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1307.5515;%%" +} + +@Article{hep-ex/0206022, + author = "Abbiendi, G. and others", +collaboration = "OPAL", + title = "{Decay-mode independent searches for new scalar bosons with + the OPAL detector at LEP}", + journal = "Eur. Phys. J.", + volume = "C27", + year = "2003", + pages = "311-329", + eprint = "hep-ex/0206022", + archivePrefix = "arXiv", + doi = "10.1140/epjc/s2002-01115-1", + SLACcitation = "%%CITATION = HEP-EX/0206022;%%" +} + +@Article{arXiv:1108.3331, + author = "Benjamin, Doug and others", +collaboration = "CDF", + title = "{Combined CDF and D0 upper limits on gg->H W+W- and + constraints on the Higgs boson mass in fourth-generation + fermion models with up to 8.2 fb-1 of data}", + year = "2011", + eprint = "1108.3331", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1108.3331;%%" +} + +@Article{arXiv:0707.0373, + author = "Abbiendi, G. and others", +collaboration = "OPAL", + title = "{Search for invisibly decaying Higgs bosons in $e^+e^- \to + Z^0 h^0$ production at $\sqrt{s}$=183 - 209 GeV}", + journal = "Phys. Lett.", + volume = "B682", + year = "2010", + pages = "381-390", + eprint = "0707.0373", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + doi = "10.1016/j.physletb.2009.09.010", + SLACcitation = "%%CITATION = 0707.0373;%%" } @Article{arXiv:0906.5613, author = "Aaltonen, T. and others", collaboration = "CDF", title = "{Search for a Higgs Boson in $W H \to \ell \nu b \bar{b}$ in $p\bar{p}$ Collisions at $\sqrt{s} = 1.96$ TeV}", journal = "Phys. Rev. Lett.", volume = "103", year = "2009", pages = "101802", eprint = "0906.5613", archivePrefix = "arXiv", primaryClass = "hep-ex", doi = "10.1103/PhysRevLett.103.101802", SLACcitation = "%%CITATION = 0906.5613;%%" } +@Article{arXiv:1506.00424, + author = ",", +collaboration = "CMS", + title = "{A search for pair production of new light bosons decaying + into muons}", + journal = "Phys. Lett.", + volume = "B752", + year = "2016", + pages = "146", + eprint = "1506.00424", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1506.00424;%%" +} + +@Article{arXiv:1409.6064, + author = ",", +collaboration = "ATLAS", + title = "{Search for neutral Higgs bosons of the minimal + supersymmetric standard model in pp collisions at + $\sqrt{s}$ = 8 TeV with the ATLAS detector}", + journal = "", + volume = "", + year = "2014", + pages = "", + year = "2014", + eprint = "1409.6064", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1409.6064;%%" +} + +@Article{arXiv:1207.0449, + author = "Group, CDF and D0 Collaborations and the Tevatron New Physics an + ", +collaboration = "Tevatron New Physics Higgs Working Group", + title = "{Updated Combination of CDF and D0 Searches for Standard + Model Higgs Boson Production with up to 10.0 fb$^{-1}$ of + Data}", + year = "2012", + eprint = "1207.0449", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1207.0449;%%" +} + @Article{arXiv:1207.7214, author = "", collaboration = "ATLAS", title = "{Observation of a new particle in the search for the Standard Model Higgs boson with the ATLAS detector at the LHC}", journal = "Phys. Lett.", volume = "B716", year = "2012", pages = "1-29", eprint = "1207.7214", archivePrefix = "arXiv", primaryClass = "hep-ex", doi = "10.1016/j.physletb.2012.08.020", SLACcitation = "%%CITATION = 1207.7214;%%" } -@Article{arXiv:0812.0267, - author = "Abbiendi, G. and others", -collaboration = "OPAL", - title = "{Search for Charged Higgs Bosons in e+e- Collisions at - sqrts(s) = 189-209 GeV}", - journal = "Eur. Phys. J.", - volume = "C72", - year = "2012", - pages = "2076", - eprint = "0812.0267", +@Article{hep-ex/0501033, + author = "Achard, P. and others", +collaboration = "L3", + title = "{Search for an invisibly-decaying Higgs boson at LEP}", + journal = "Phys. Lett.", + volume = "B609", + year = "2005", + pages = "35-48", + eprint = "hep-ex/0501033", archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1140/epjc/s10052-012-2076-0", - SLACcitation = "%%CITATION = 0812.0267;%%" + doi = "10.1016/j.physletb.2005.01.030", + SLACcitation = "%%CITATION = HEP-EX/0501033;%%" } -@Article{arXiv:1207.6436, +@Article{arXiv:0907.1269, author = "Aaltonen, T. and others", collaboration = "CDF", - title = "{Evidence for a particle produced in association with weak - bosons and decaying to a bottom-antibottom quark pair in - Higgs boson searches at the Tevatron}", + title = "{Search for charged Higgs bosons in decays of top quarks in + $p-\bar{p}$ collisions at $\sqrt{s} = 1.96$ TeV}", journal = "Phys. Rev. Lett.", - volume = "109", - year = "2012", - pages = "071804", - eprint = "1207.6436", + volume = "103", + year = "2009", + pages = "101803", + eprint = "0907.1269", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.109.071804", - SLACcitation = "%%CITATION = 1207.6436;%%" + doi = "10.1103/PhysRevLett.103.101803", + SLACcitation = "%%CITATION = 0907.1269;%%" } -@Article{arXiv:0707.0373, - author = "Abbiendi, G. and others", -collaboration = "OPAL", - title = "{Search for invisibly decaying Higgs bosons in $e^+e^- \to - Z^0 h^0$ production at $\sqrt{s}$=183 - 209 GeV}", - journal = "Phys. Lett.", - volume = "B682", - year = "2010", - pages = "381-390", - eprint = "0707.0373", +@Article{arXiv:1202.3478, + author = "Chatrchyan, Serguei", +collaboration = "CMS", + title = "{Search for the standard model Higgs boson in the H to ZZ + to 2l 2nu channel in pp collisions at sqrt(s) = 7 TeV}", + journal = "JHEP", + volume = "03", + year = "2012", + pages = "040", + eprint = "1202.3478", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1016/j.physletb.2009.09.010", - SLACcitation = "%%CITATION = 0707.0373;%%" + doi = "10.1007/JHEP03(2012)040", + SLACcitation = "%%CITATION = 1202.3478;%%" } -@Article{arXiv:1603.02991, +@Article{arXiv:1506.08329, author = ",", collaboration = "CMS", - title = "{Search for neutral resonances decaying into a Z boson and - a pair of b jets or tau leptons}", - journal = "Phys. Lett.", - volume = "B759", - year = "2016", - pages = "369", - eprint = "1603.02991", + title = "{Search for neutral MSSM Higgs bosons decaying into a pair + of bottom quarks}", + journal = "", + volume = "JHEP11", + year = "2015", + pages = "071", + year = "2015", + eprint = "1506.08329", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1603.02991;%%" + SLACcitation = "%%CITATION = 1506.08329;%%" +} + +@Article{arXiv:1502.04478, + author = ",", +collaboration = "ATLAS", + title = "{Search for a CP-odd Higgs boson decaying to $Zh$ in $pp$ + collisions at $\sqrt{s} = 8$ TeV with the ATLAS detector}", + journal = "Physics Letters", + volume = "B744", + year = "2015", + pages = "163-183", + eprint = "1502.04478", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1502.04478;%%" } @Article{arXiv:1402.3051, author = ",", collaboration = "ATLAS", title = "{Search for Higgs boson decays to a photon and a Z boson in pp collisions at sqrt(s)=7 and 8 TeV with the ATLAS detector}", journal = "Phys. Lett.", volume = "B732", year = "2014", pages = "8-27", eprint = "1402.3051", archivePrefix = "arXiv", primaryClass = "hep-ex", doi = "10.1016/j.physletb.2014.03.015", SLACcitation = "%%CITATION = 1402.3051;%%" } -@Article{hep-ex/0107032, - author = "", -collaboration = "LEP Higgs Working for Higgs boson searches", - title = "{Searches for Invisible Higgs bosons: Preliminary combined - results using LEP data collected at energies up to 209 - GeV}", - year = "2001", - eprint = "hep-ex/0107032", - archivePrefix = "arXiv", - SLACcitation = "%%CITATION = HEP-EX/0107032;%%" -} - -@Article{hep-ex/0602042, - author = "Schael, S. and others", -collaboration = "ALEPH", - title = "{Search for neutral MSSM Higgs bosons at LEP}", - journal = "Eur. Phys. J.", - volume = "C47", - year = "2006", - pages = "547-587", - eprint = "hep-ex/0602042", - archivePrefix = "arXiv", - doi = "10.1140/epjc/s2006-02569-7", - SLACcitation = "%%CITATION = HEP-EX/0602042;%%" -} - -@Article{hep-ex/0111010, - author = "Abbiendi, G. and others", -collaboration = "OPAL", - title = "{Search for Yukawa production of a light neutral Higgs - boson at LEP}", - journal = "Eur. Phys. J.", - volume = "C23", - year = "2002", - pages = "397-407", - eprint = "hep-ex/0111010", +@Article{arXiv:1603.06896, + author = ",", +collaboration = "CMS", + title = "{Search for two Higgs bosons in final states containing two + photons and two bottom quarks}", + year = "2016", + eprint = "1603.06896", archivePrefix = "arXiv", - doi = "10.1007/s100520200896", - SLACcitation = "%%CITATION = HEP-EX/0111010;%%" + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1603.06896;%%" } @Article{arXiv:1106.4555, author = "Abazov, Victor Mukhamedovich and others", collaboration = "D0", title = "{Search for Higgs bosons decaying to tautau pairs in ppbar collisions at sqrt(s) = 1.96 TeV}", journal = "Phys. Lett.", volume = "B707", year = "2012", pages = "323-329", eprint = "1106.4555", archivePrefix = "arXiv", primaryClass = "hep-ex", doi = "10.1016/j.physletb.2011.12.050", SLACcitation = "%%CITATION = 1106.4555;%%" } -@Article{arXiv:1503.04114, - author = ",", -collaboration = "CMS", - title = "{Search for resonant pair production of Higgs bosons - decaying to two bottom quark-antiquark pairs in proton- - proton collisions at 8 TeV}", - journal = "Phys. Lett.", - volume = "B749", - year = "2015", - pages = "560", - eprint = "1503.04114", +@Article{arXiv:1204.2760, + author = "Aad, Georges", +collaboration = "ATLAS", + title = "{Search for charged Higgs bosons decaying via H+ -> tau nu + in top quark pair events using pp collision data at sqrt(s) + = 7 TeV with the ATLAS detector}", + journal = "JHEP", + volume = "06", + year = "2012", + pages = "039", + eprint = "1204.2760", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1503.04114;%%" + doi = "10.1007/JHEP06(2012)039", + SLACcitation = "%%CITATION = 1204.2760;%%" } -@Article{hep-ex/0107031, +@Article{hep-ex/0107034, author = "", collaboration = "LEP Higgs Working Group for Higgs boson searches", - title = "{Search for charged Higgs bosons: Preliminary combined - results using LEP data collected at energies up to 209- - GeV}", + title = "{Flavor independent search for hadronically decaying + neutral Higgs bosons at LEP}", year = "2001", - eprint = "hep-ex/0107031", + eprint = "hep-ex/0107034", archivePrefix = "arXiv", - SLACcitation = "%%CITATION = HEP-EX/0107031;%%" + SLACcitation = "%%CITATION = HEP-EX/0107034;%%" } -@Article{arXiv:1407.6583, - author = ",", -collaboration = "ATLAS", - title = "{Search for Scalar Diphoton Resonances in the Mass Range - $65-600$ GeV with the ATLAS Detector in $pp$ Collision Data - at $\sqrt{s}$ = 8 $TeV$}", - year = "2014", - eprint = "1407.6583", +@Article{arXiv:1202.1488, + author = "Chatrchyan, Serguei", +collaboration = "CMS", + title = "{Combined results of searches for the standard model Higgs + boson in pp collisions at sqrt(s) = 7 TeV}", + journal = "Phys. Lett.", + volume = "B710", + year = "2012", + pages = "26-48", + eprint = "1202.1488", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1407.6583;%%" + doi = "10.1016/j.physletb.2012.02.064", + SLACcitation = "%%CITATION = 1202.1488;%%" } -@Article{arXiv:1404.1344, - author = ",", -collaboration = "CMS", - title = "{Search for invisible decays of Higgs bosons in the vector - boson fusion and associated ZH production modes}", - journal = "Eur. Phys. J.", - volume = "C74", - year = "2014", - pages = "2980", - eprint = "1404.1344", +@Article{arXiv:0809.3930, + author = "Aaltonen, T. and others", +collaboration = "CDF", + title = "{Search for a Higgs Boson Decaying to Two W Bosons at + CDF}", + journal = "Phys. Rev. Lett.", + volume = "102", + year = "2009", + pages = "021802", + eprint = "0809.3930", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1404.1344;%%" + doi = "10.1103/PhysRevLett.102.021802", + SLACcitation = "%%CITATION = 0809.3930;%%" } -@Article{hep-ex/0401022, +@Article{arXiv:0901.1887, + author = "Abazov, V. M. and others", +collaboration = "D0", + title = "{Search for Resonant Diphoton Production with the D0 + Detector}", + journal = "Phys. Rev. Lett.", + volume = "102", + year = "2009", + pages = "231801", + eprint = "0901.1887", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + doi = "10.1103/PhysRevLett.102.231801", + SLACcitation = "%%CITATION = 0901.1887;%%" +} + +@Article{hep-ex/0404012, author = "Abdallah, J. and others", collaboration = "DELPHI", - title = "{Searches for invisibly decaying Higgs bosons with the - DELPHI detector at LEP}", + title = "{Search for charged Higgs bosons at LEP in general two + Higgs doublet models}", journal = "Eur. Phys. J.", - volume = "C32", + volume = "C34", year = "2004", - pages = "475-492", - eprint = "hep-ex/0401022", + pages = "399-418", + eprint = "hep-ex/0404012", archivePrefix = "arXiv", - doi = "10.1140/epjc/s2003-01469-8", - SLACcitation = "%%CITATION = HEP-EX/0401022;%%" + doi = "10.1140/epjc/s2004-01732-6", + SLACcitation = "%%CITATION = HEP-EX/0404012;%%" } -@Article{arXiv:1510.06534, - author = ",", -collaboration = "CMS", - title = "{Search for a very light NMSSM Higgs boson produced in - decays of the 125 GeV scalar boson and decaying into tau - leptons in pp collisions at sqrt(s) = 8 TeV}", - journal = "", - volume = "JHEP01", - year = "2016", - pages = "079", - year = "2015", - eprint = "1510.06534", +@Article{hep-ex/0107032, + author = "", +collaboration = "LEP Higgs Working for Higgs boson searches", + title = "{Searches for Invisible Higgs bosons: Preliminary combined + results using LEP data collected at energies up to 209 + GeV}", + year = "2001", + eprint = "hep-ex/0107032", archivePrefix = "arXiv", - primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1510.06534;%%" + SLACcitation = "%%CITATION = HEP-EX/0107032;%%" } -@Article{arXiv:1301.6065, - author = "Abbiendi, G. and others", -collaboration = "ALEPH", - title = "{Search for Charged Higgs bosons: Combined Results Using - LEP Data}", - year = "2013", - eprint = "1301.6065", +% No SPIRES record found for cite request arXiv:1712.06386 + +@Article{arXiv:0905.3381, + author = "Abazov, V. M. and others", +collaboration = "D0", + title = "{Search for NMSSM Higgs bosons in the $h \to a a + \to\mu\mu\: \mu\mu, \mu\mu \: \tau\tau$ channels using $p + \bar{p}$ collisions at $\sqrt{s}$=1.96 TeV}", + journal = "Phys. Rev. Lett.", + volume = "103", + year = "2009", + pages = "061801", + eprint = "0905.3381", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1301.6065;%%" + doi = "10.1103/PhysRevLett.103.061801", + SLACcitation = "%%CITATION = 0905.3381;%%" } -@Article{arXiv:1406.7663, - author = ",", +@Article{arXiv:1108.5064, + author = "Aad, Georges", collaboration = "ATLAS", - title = "{Search for the Standard Model Higgs boson decay to - $\mu^{+}\mu^{-}$ with the ATLAS detector}", - journal = "Physics Letters", - volume = "B738", - year = "2014", - pages = "68-86", - eprint = "1406.7663", + title = "{Search for a heavy Standard Model Higgs boson in the + channel H->ZZ->llqq using the ATLAS detector}", + journal = "Phys. Lett.", + volume = "B707", + year = "2012", + pages = "27-45", + eprint = "1108.5064", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1406.7663;%%" + doi = "10.1016/j.physletb.2011.11.056", + SLACcitation = "%%CITATION = 1108.5064;%%" } -% No SPIRES record found for cite request arXiv:1807.07915 - -@Article{arXiv:1106.4885, - author = "Abazov, Victor Mukhamedovich and others", -collaboration = "D0", - title = "{Search for neutral Higgs bosons decaying to tau pairs - produced in association with b quarks in ppbar collisions - at sqrt(s)=1.96 TeV}", +@Article{arXiv:1207.6436, + author = "Aaltonen, T. and others", +collaboration = "CDF", + title = "{Evidence for a particle produced in association with weak + bosons and decaying to a bottom-antibottom quark pair in + Higgs boson searches at the Tevatron}", journal = "Phys. Rev. Lett.", - volume = "107", - year = "2011", - pages = "121801", - eprint = "1106.4885", + volume = "109", + year = "2012", + pages = "071804", + eprint = "1207.6436", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.107.121801", - SLACcitation = "%%CITATION = 1106.4885;%%" + doi = "10.1103/PhysRevLett.109.071804", + SLACcitation = "%%CITATION = 1207.6436;%%" } -@Article{arXiv:1504.04710, +@Article{arXiv:1404.1344, author = ",", collaboration = "CMS", - title = "{Search for a pseudoscalar boson decaying into a Z boson - and the 125 GeV Higgs boson in llbb final states}", + title = "{Search for invisible decays of Higgs bosons in the vector + boson fusion and associated ZH production modes}", + journal = "Eur. Phys. J.", + volume = "C74", + year = "2014", + pages = "2980", + eprint = "1404.1344", + archivePrefix = "arXiv", + primaryClass = "hep-ex", + SLACcitation = "%%CITATION = 1404.1344;%%" +} + +@Article{arXiv:1012.0874, + author = "Abazov, Victor Mukhamedovich and others", +collaboration = "D0", + title = "{Search for $WH$ associated production in 5.3 fb$^{-1}$ of + $p\bar{p}$ collisions at the Fermilab Tevatron}", journal = "Phys. Lett.", - volume = "B748", - year = "2015", - pages = "221", - eprint = "1504.04710", + volume = "B698", + year = "2011", + pages = "6-13", + eprint = "1012.0874", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1504.04710;%%" + doi = "10.1016/j.physletb.2011.02.036", + SLACcitation = "%%CITATION = 1012.0874;%%" } -@Article{arXiv:1202.1415, - author = "Aad, G. and others", +% No SPIRES record found for cite request arXiv:1806.07355 + +@Article{arXiv:1202.1408, + author = "Aad, Georges", collaboration = "ATLAS", - title = "{Search for the Standard Model Higgs boson in the decay - channel H->ZZ(*)->4l with 4.8 fb-1 of pp collision data at - sqrt(s) = 7 TeV with ATLAS}", + title = "{Combined search for the Standard Model Higgs boson using + up to 4.9 fb$^{-1}$ of $pp$ collision data at $\sqrt{s}=7$ + TeV with the ATLAS detector at the LHC}", journal = "Phys. Lett.", volume = "B710", year = "2012", - pages = "383-402", - eprint = "1202.1415", + pages = "49-66", + eprint = "1202.1408", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1016/j.physletb.2012.03.005", - SLACcitation = "%%CITATION = 1202.1415;%%" -} - -@Article{hep-ex/0107034, - author = "", -collaboration = "LEP Higgs Working Group for Higgs boson searches", - title = "{Flavor independent search for hadronically decaying - neutral Higgs bosons at LEP}", - year = "2001", - eprint = "hep-ex/0107034", - archivePrefix = "arXiv", - SLACcitation = "%%CITATION = HEP-EX/0107034;%%" + doi = "10.1016/j.physletb.2012.02.044", + SLACcitation = "%%CITATION = 1202.1408;%%" } -@Article{arXiv:1406.5053, - author = ",", -collaboration = "ATLAS", - title = "{Search For Higgs Boson Pair Production in the - $\gamma\gamma b\bar{b}$ Final State using $pp$ Collision - Data at $\sqrt{s}=8$ TeV from the ATLAS Detector}", - journal = "", - volume = "", - year = "2014", - pages = "", - year = "2014", - eprint = "1406.5053", +@Article{arXiv:1003.3363, + author = "Benjamin, Doug and others", +collaboration = "Tevatron New Phenomena and Higgs Working Group", + title = "{Combined CDF and D0 upper limits on MSSM Higgs boson + production in tau-tau final states with up to 2.2 fb-1}", + year = "2010", + eprint = "1003.3363", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1406.5053;%%" + SLACcitation = "%%CITATION = 1003.3363;%%" } @Article{arXiv:1106.4782, author = "Aaltonen, T. and others", collaboration = "CDF", title = "{Search for Higgs Bosons Produced in Association with b- Quarks}", journal = "Phys. Rev.", volume = "D85", year = "2012", pages = "032005", eprint = "1106.4782", archivePrefix = "arXiv", primaryClass = "hep-ex", doi = "10.1103/PhysRevD.85.032005", SLACcitation = "%%CITATION = 1106.4782;%%" } -@Article{arXiv:1510.01181, +@Article{arXiv:1510.06534, author = ",", collaboration = "CMS", - title = "{Searches for a heavy scalar boson H decaying to a pair of - 125 GeV Higgs bosons hh or for a heavy pseudoscalar boson A - decaying to Zh, in the final states with h to tau tau}", - journal = "Phys. Lett.", - volume = "B755", + title = "{Search for a very light NMSSM Higgs boson produced in + decays of the 125 GeV scalar boson and decaying into tau + leptons in pp collisions at sqrt(s) = 8 TeV}", + journal = "", + volume = "JHEP01", year = "2016", - pages = "217", - eprint = "1510.01181", + pages = "079", + year = "2015", + eprint = "1510.06534", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1510.01181;%%" + SLACcitation = "%%CITATION = 1510.06534;%%" } -@Article{arXiv:1107.1268, +@Article{arXiv:0908.1811, author = "Abazov, V. M. and others", collaboration = "D0", - title = "{Search for associated Higgs boson production using like - charge dilepton events in ppbar collisions at sqrt{s} = - 1.96 TeV}", - journal = "Phys. Rev.", - volume = "D84", - year = "2011", - pages = "092002", - eprint = "1107.1268", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1103/PhysRevD.84.092002", - SLACcitation = "%%CITATION = 1107.1268;%%" -} - -@Article{arXiv:1202.1997, - author = "Chatrchyan, Serguei", -collaboration = "CMS", - title = "{Search for the standard model Higgs boson in the decay - channel H to ZZ to 4 leptons in pp collisions at sqrt(s) = - 7 TeV}", - journal = "Phys. Rev. Lett.", - volume = "108", - year = "2012", - pages = "111804", - eprint = "1202.1997", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.108.111804", - SLACcitation = "%%CITATION = 1202.1997;%%" -} - -@Article{arXiv:1107.4960, - author = " and others", -collaboration = "TEVNPH Working Group", - title = "{Combined CDF and D0 Searches for the Standard Model Higgs - Boson Decaying to Two Photons with up to 8.2 fb^-1}", - year = "2011", - eprint = "1107.4960", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1107.4960;%%" -} - -@Article{arXiv:1307.5515, - author = ",", -collaboration = "CMS", - title = "{Search for a Higgs boson decaying into a Z and a photon in - pp collisions at sqrt(s) = 7 and 8 TeV}", + title = "{Search for charged Higgs bosons in top quark decays}", journal = "Phys. Lett.", - volume = "B726", - year = "2013", - pages = "587", - eprint = "1307.5515", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1307.5515;%%" -} - -@Article{hep-ex/0206022, - author = "Abbiendi, G. and others", -collaboration = "OPAL", - title = "{Decay-mode independent searches for new scalar bosons with - the OPAL detector at LEP}", - journal = "Eur. Phys. J.", - volume = "C27", - year = "2003", - pages = "311-329", - eprint = "hep-ex/0206022", - archivePrefix = "arXiv", - doi = "10.1140/epjc/s2002-01115-1", - SLACcitation = "%%CITATION = HEP-EX/0206022;%%" -} - -@Article{arXiv:0906.1014, - author = "Aaltonen, T. and others", -collaboration = "CDF", - title = "{Search for Higgs bosons predicted in two-Higgs-doublet - models via decays to tau lepton pairs in 1.96 TeV proton- - antiproton collisions}", - journal = "Phys. Rev. Lett.", - volume = "103", + volume = "B682", year = "2009", - pages = "201801", - eprint = "0906.1014", + pages = "278-286", + eprint = "0908.1811", archivePrefix = "arXiv", primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.103.201801", - SLACcitation = "%%CITATION = 0906.1014;%%" + doi = "10.1016/j.physletb.2009.11.016", + SLACcitation = "%%CITATION = 0908.1811;%%" } -@Article{arXiv:0907.1269, - author = "Aaltonen, T. and others", -collaboration = "CDF", - title = "{Search for charged Higgs bosons in decays of top quarks in - $p-\bar{p}$ collisions at $\sqrt{s} = 1.96$ TeV}", - journal = "Phys. Rev. Lett.", - volume = "103", - year = "2009", - pages = "101803", - eprint = "0907.1269", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1103/PhysRevLett.103.101803", - SLACcitation = "%%CITATION = 0907.1269;%%" -} +% No SPIRES record found for cite request arXiv:1808.00336 -@Article{arXiv:1202.1488, +@Article{arXiv:1202.1416, author = "Chatrchyan, Serguei", collaboration = "CMS", - title = "{Combined results of searches for the standard model Higgs - boson in pp collisions at sqrt(s) = 7 TeV}", - journal = "Phys. Lett.", - volume = "B710", + title = "{Search for a Higgs boson in the decay channel H to ZZ(*) + to q qbar l-l+ in pp collisions at sqrt(s) = 7 TeV}", + journal = "JHEP", + volume = "04", year = "2012", - pages = "26-48", - eprint = "1202.1488", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - doi = "10.1016/j.physletb.2012.02.064", - SLACcitation = "%%CITATION = 1202.1488;%%" -} - -@Article{arXiv:1506.02301, - author = ",", -collaboration = "CMS", - title = "{Search for diphoton resonances in the mass range from 150 - to 850 GeV in pp collisions at sqrt(s) = 8 TeV}", - journal = "Phys. Lett.", - volume = "B750", - year = "2015", - pages = "494", - eprint = "1506.02301", + pages = "036", + eprint = "1202.1416", archivePrefix = "arXiv", primaryClass = "hep-ex", - SLACcitation = "%%CITATION = 1506.02301;%%" + doi = "10.1007/JHEP04(2012)036", + SLACcitation = "%%CITATION = 1202.1416;%%" } % No SPIRES record found for cite request CDFnotes,D0notes,CMSnotes % No SPIRES record found for cite request ATLASnotes,LHWGnotes @Article{hep-ph/9704448, author = "Djouadi, A. and Kalinowski, J. and Spira, M.", title = "{HDECAY: A program for Higgs boson decays in the standard model and its supersymmetric extension}", journal = "Comput. Phys. Commun.", volume = "108", year = "1998", pages = "56-74", eprint = "hep-ph/9704448", archivePrefix = "arXiv", doi = "10.1016/S0010-4655(97)00123-9", SLACcitation = "%%CITATION = HEP-PH/9704448;%%" } @Article{hep-ph/0102227, author = "Catani, Stefano and de Florian, Daniel and Grazzini, Massimiliano", title = "{Higgs production in hadron collisions: Soft and virtual QCD corrections at NNLO}", journal = "JHEP", volume = "05", year = "2001", pages = "025", eprint = "hep-ph/0102227", archivePrefix = "arXiv", SLACcitation = "%%CITATION = HEP-PH/0102227;%%" } @Article{hep-ph/0102241, author = "Harlander, Robert V. and Kilgore, William B.", title = "{Soft and virtual corrections to p p --> H + X at NNLO}", journal = "Phys. Rev.", volume = "D64", year = "2001", pages = "013015", eprint = "hep-ph/0102241", archivePrefix = "arXiv", doi = "10.1103/PhysRevD.64.013015", SLACcitation = "%%CITATION = HEP-PH/0102241;%%" } @Article{hep-ph/0201206, author = "Harlander, Robert V. and Kilgore, William B.", title = "{Next-to-next-to-leading order Higgs production at hadron colliders}", journal = "Phys. Rev. Lett.", volume = "88", year = "2002", pages = "201801", eprint = "hep-ph/0201206", archivePrefix = "arXiv", doi = "10.1103/PhysRevLett.88.201801", SLACcitation = "%%CITATION = HEP-PH/0201206;%%" } @Article{hep-ph/0207004, author = "Anastasiou, Charalampos and Melnikov, Kirill", title = "{Higgs boson production at hadron colliders in NNLO QCD}", journal = "Nucl. Phys.", volume = "B646", year = "2002", pages = "220-256", eprint = "hep-ph/0207004", archivePrefix = "arXiv", doi = "10.1016/S0550-3213(02)00837-4", SLACcitation = "%%CITATION = HEP-PH/0207004;%%" } @Article{hep-ph/0302135, author = "Ravindran, V. and Smith, J. and van Neerven, W. L.", title = "{NNLO corrections to the total cross section for Higgs boson production in hadron hadron collisions}", journal = "Nucl. Phys.", volume = "B665", year = "2003", pages = "325-366", eprint = "hep-ph/0302135", archivePrefix = "arXiv", doi = "10.1016/S0550-3213(03)00457-7", SLACcitation = "%%CITATION = HEP-PH/0302135;%%" } @Article{arXiv:0811.3458, author = "Anastasiou, Charalampos and Boughezal, Radja and Petriello, Frank", title = "{Mixed QCD-electroweak corrections to Higgs boson production in gluon fusion}", journal = "JHEP", volume = "04", year = "2009", pages = "003", eprint = "0811.3458", archivePrefix = "arXiv", primaryClass = "hep-ph", doi = "10.1088/1126-6708/2009/04/003", SLACcitation = "%%CITATION = 0811.3458;%%" } @Article{Dawson:1990zj, author = "Dawson, S.", title = "{Radiative corrections to Higgs boson production}", journal = "Nucl. Phys.", volume = "B359", year = "1991", pages = "283-300", doi = "10.1016/0550-3213(91)90061-2", SLACcitation = "%%CITATION = NUPHA,B359,283;%%" } @Article{Djouadi:1991tka, author = "Djouadi, A. and Spira, M. and Zerwas, P. M.", title = "{Production of Higgs bosons in proton colliders: QCD corrections}", journal = "Phys. Lett.", volume = "B264", year = "1991", pages = "440-446", doi = "10.1016/0370-2693(91)90375-Z", SLACcitation = "%%CITATION = PHLTA,B264,440;%%" } @Article{hep-ph/9504378, author = "Spira, M. and Djouadi, A. and Graudenz, D. and Zerwas, P. M.", title = "{Higgs boson production at the LHC}", journal = "Nucl. Phys.", volume = "B453", year = "1995", pages = "17-82", eprint = "hep-ph/9504378", archivePrefix = "arXiv", doi = "10.1016/0550-3213(95)00379-7", SLACcitation = "%%CITATION = HEP-PH/9504378;%%" } @Article{hep-ph/0404071, author = "Aglietti, U. and Bonciani, R. and Degrassi, G. and Vicini, A.", title = "{Two-loop light fermion contribution to Higgs production and decays}", journal = "Phys. Lett.", volume = "B595", year = "2004", pages = "432-441", eprint = "hep-ph/0404071", archivePrefix = "arXiv", doi = "10.1016/j.physletb.2004.06.063", SLACcitation = "%%CITATION = HEP-PH/0404071;%%" } @Article{hep-ph/0407249, author = "Degrassi, Giuseppe and Maltoni, Fabio", title = "{Two-loop electroweak corrections to Higgs production at hadron colliders}", journal = "Phys. Lett.", volume = "B600", year = "2004", pages = "255-260", eprint = "hep-ph/0407249", archivePrefix = "arXiv", doi = "10.1016/j.physletb.2004.09.008", SLACcitation = "%%CITATION = HEP-PH/0407249;%%" } @Article{arXiv:0809.1301, author = "Actis, Stefano and Passarino, Giampiero and Sturm, Christian and Uccirati, Sandro", title = "{NLO Electroweak Corrections to Higgs Boson Production at Hadron Colliders}", journal = "Phys. Lett.", volume = "B670", year = "2008", pages = "12-17", eprint = "0809.1301", archivePrefix = "arXiv", primaryClass = "hep-ph", doi = "10.1016/j.physletb.2008.10.018", SLACcitation = "%%CITATION = 0809.1301;%%" } @Article{arXiv:0809.3667, author = "Actis, Stefano and Passarino, Giampiero and Sturm, Christian and Uccirati, Sandro", title = "{NNLO Computational Techniques: the Cases $H \to \gamma \gamma$ and $H \to g g$}", journal = "Nucl. Phys.", volume = "B811", year = "2009", pages = "182-273", eprint = "0809.3667", archivePrefix = "arXiv", primaryClass = "hep-ph", doi = "10.1016/j.nuclphysb.2008.11.024", SLACcitation = "%%CITATION = 0809.3667;%%" } @Article{hep-ph/0306211, author = "Catani, Stefano and de Florian, Daniel and Grazzini, Massimiliano and Nason, Paolo", title = "{Soft-gluon resummation for Higgs boson production at hadron colliders}", journal = "JHEP", volume = "07", year = "2003", pages = "028", eprint = "hep-ph/0306211", archivePrefix = "arXiv", SLACcitation = "%%CITATION = HEP-PH/0306211;%%" } @Article{arXiv:0901.2427, author = "de Florian, Daniel and Grazzini, Massimiliano", title = "{Higgs production through gluon fusion: updated cross sections at the Tevatron and the LHC}", journal = "Phys. Lett.", volume = "B674", year = "2009", pages = "291-294", eprint = "0901.2427", archivePrefix = "arXiv", primaryClass = "hep-ph", doi = "10.1016/j.physletb.2009.03.033", SLACcitation = "%%CITATION = 0901.2427;%%" } @Article{hep-ph/0307206, author = "Brein, Oliver and Djouadi, Abdelhak and Harlander, Robert", title = "{NNLO QCD corrections to the Higgs-strahlung processes at hadron colliders}", journal = "Phys. Lett.", volume = "B579", year = "2004", pages = "149-156", eprint = "hep-ph/0307206", archivePrefix = "arXiv", doi = "10.1016/j.physletb.2003.10.112", SLACcitation = "%%CITATION = HEP-PH/0307206;%%" } @Article{hep-ph/0306234, author = "Ciccolini, M. L. and Dittmaier, S. and Kramer, M.", title = "{Electroweak radiative corrections to associated W H and Z H production at hadron colliders}", journal = "Phys. Rev.", volume = "D68", year = "2003", pages = "073003", eprint = "hep-ph/0306234", archivePrefix = "arXiv", doi = "10.1103/PhysRevD.68.073003", SLACcitation = "%%CITATION = HEP-PH/0306234;%%" } @Article{hep-ph/0406152, author = "Assamagan, K. A. and others", collaboration = "Higgs Working Group", title = "{The Higgs working group: Summary report 2003}", year = "2004", eprint = "hep-ph/0406152", archivePrefix = "arXiv", SLACcitation = "%%CITATION = HEP-PH/0406152;%%" } @Article{hep-ph/0304035, author = "Harlander, Robert V. and Kilgore, William B.", title = "{Higgs boson production in bottom quark fusion at next-to- next-to-leading order}", journal = "Phys. Rev.", volume = "D68", year = "2003", pages = "013001", eprint = "hep-ph/0304035", archivePrefix = "arXiv", doi = "10.1103/PhysRevD.68.013001", SLACcitation = "%%CITATION = HEP-PH/0304035;%%" } @Article{hep-ph/9206246, author = "Han, Tao and Valencia, G. and Willenbrock, S.", title = "{Structure function approach to vector boson scattering in p p collisions}", journal = "Phys. Rev. Lett.", volume = "69", year = "1992", pages = "3274-3277", eprint = "hep-ph/9206246", archivePrefix = "arXiv", doi = "10.1103/PhysRevLett.69.3274", SLACcitation = "%%CITATION = HEP-PH/9206246;%%" } @Article{hep-ph/9905386, author = "Campbell, John M. and Ellis, R. Keith", title = "{An update on vector boson pair production at hadron colliders}", journal = "Phys. Rev.", volume = "D60", year = "1999", pages = "113006", eprint = "hep-ph/9905386", archivePrefix = "arXiv", doi = "10.1103/PhysRevD.60.113006", SLACcitation = "%%CITATION = HEP-PH/9905386;%%" } @Article{hep-ph/0306109, author = "Figy, T. and Oleari, C. and Zeppenfeld, D.", title = "{Next-to-leading order jet distributions for Higgs boson production via weak-boson fusion}", journal = "Phys. Rev.", volume = "D68", year = "2003", pages = "073005", eprint = "hep-ph/0306109", archivePrefix = "arXiv", doi = "10.1103/PhysRevD.68.073005", SLACcitation = "%%CITATION = HEP-PH/0306109;%%" } @Article{hep-ph/0403194, author = "Berger, Edmond L. and Campbell, John M.", title = "{Higgs boson production in weak boson fusion at next-to- leading order}", journal = "Phys. Rev.", volume = "D70", year = "2004", pages = "073011", eprint = "hep-ph/0403194", archivePrefix = "arXiv", doi = "10.1103/PhysRevD.70.073011", SLACcitation = "%%CITATION = HEP-PH/0403194;%%" } @Article{hep-ph/0612172, author = "Aglietti, U. and others", title = "{Tevatron for LHC report: Higgs}", year = "2006", eprint = "hep-ph/0612172", archivePrefix = "arXiv", SLACcitation = "%%CITATION = HEP-PH/0612172;%%" } @Article{hep-ph/0107081, author = "Beenakker, W. and others", title = "{Higgs radiation off top quarks at the Tevatron and the LHC}", journal = "Phys. Rev. Lett.", volume = "87", year = "2001", pages = "201805", eprint = "hep-ph/0107081", archivePrefix = "arXiv", doi = "10.1103/PhysRevLett.87.201805", SLACcitation = "%%CITATION = HEP-PH/0107081;%%" } @Article{hep-ph/0107101, author = "Reina, L. and Dawson, S.", title = "{Next-to-leading order results for t anti-t h production at the Tevatron}", journal = "Phys. Rev. Lett.", volume = "87", year = "2001", pages = "201804", eprint = "hep-ph/0107101", archivePrefix = "arXiv", doi = "10.1103/PhysRevLett.87.201804", SLACcitation = "%%CITATION = HEP-PH/0107101;%%" } @Article{hep-ph/0211438, author = "Dawson, S. and Orr, L. H. and Reina, L. and Wackeroth, D.", title = "{Associated top quark Higgs boson production at the LHC}", journal = "Phys. Rev.", volume = "D67", year = "2003", pages = "071503", eprint = "hep-ph/0211438", archivePrefix = "arXiv", doi = "10.1103/PhysRevD.67.071503", SLACcitation = "%%CITATION = HEP-PH/0211438;%%" } @Article{hep-ph/0305321, author = "Brein, Oliver and Hollik, Wolfgang", title = "{MSSM Higgs bosons associated with high-p(T) jets at hadron colliders}", journal = "Phys. Rev.", volume = "D68", year = "2003", pages = "095006", eprint = "hep-ph/0305321", archivePrefix = "arXiv", doi = "10.1103/PhysRevD.68.095006", SLACcitation = "%%CITATION = HEP-PH/0305321;%%" } @Article{arXiv:0705.2744, author = "Brein, Oliver and Hollik, Wolfgang", title = "{Distributions for MSSM Higgs boson + jet production at hadron colliders}", journal = "Phys. Rev.", volume = "D76", year = "2007", pages = "035002", eprint = "0705.2744", archivePrefix = "arXiv", primaryClass = "hep-ph", doi = "10.1103/PhysRevD.76.035002", SLACcitation = "%%CITATION = 0705.2744;%%" } @Article{arXiv:0707.0381, author = "Ciccolini, M. and Denner, Ansgar and Dittmaier, S.", title = "{Strong and electroweak corrections to the production of Higgs+2jets via weak interactions at the LHC}", journal = "Phys. Rev. Lett.", volume = "99", year = "2007", pages = "161803", eprint = "0707.0381", archivePrefix = "arXiv", primaryClass = "hep-ph", doi = "10.1103/PhysRevLett.99.161803", SLACcitation = "%%CITATION = 0707.0381;%%" } @Article{arXiv:0710.4749, author = "Ciccolini, Mariano and Denner, Ansgar and Dittmaier, Stefan ", title = "{Electroweak and QCD corrections to Higgs production via vector-boson fusion at the LHC}", journal = "Phys. Rev.", volume = "D77", year = "2008", pages = "013002", eprint = "0710.4749", archivePrefix = "arXiv", primaryClass = "hep-ph", doi = "10.1103/PhysRevD.77.013002", SLACcitation = "%%CITATION = 0710.4749;%%" } @Article{arXiv:1101.0593, author = "Dittmaier, S. and others", collaboration = "LHC Higgs Cross Section Working Group", title = "{Handbook of LHC Higgs Cross Sections: 1. Inclusive Observables}", year = "2011", eprint = "1101.0593", archivePrefix = "arXiv", primaryClass = "hep-ph", SLACcitation = "%%CITATION = 1101.0593;%%" } @Article{arXiv:1201.3084, author = "Dittmaier, S. and others", title = "{Handbook of LHC Higgs Cross Sections: 2. Differential Distributions}", year = "2012", eprint = "1201.3084", archivePrefix = "arXiv", primaryClass = "hep-ph", SLACcitation = "%%CITATION = 1201.3084;%%" } @Article{arXiv:1307.1347, author = "The LHC Higgs Cross Section Working Group, and others", title = "{Handbook of LHC Higgs Cross Sections: 3. Higgs Properties}", year = "2013", eprint = "1307.1347", archivePrefix = "arXiv", primaryClass = "hep-ph", SLACcitation = "%%CITATION = 1307.1347;%%" } -@article{arXiv:1712.06386, - author = "Aaboud, M. and others", - title = "{Search for heavy ZZ resonances in the $\ell ^+\ell - ^-\ell ^+\ell ^-$ and $\ell ^+\ell ^-\nu \bar{\nu }$ final - states using proton–proton collisions at $\sqrt{s}= 13$ - $\text {TeV}$ with the ATLAS detector}", - collaboration = "ATLAS", - journal = "Eur. Phys. J.", - volume = "C78", - year = "2018", - number = "4", - pages = "293", - doi = "10.1140/epjc/s10052-018-5686-3", - eprint = "1712.06386", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - reportNumber = "CERN-EP-2017-251", - SLACcitation = "%%CITATION = ARXIV:1712.06386;%%" -} - -@article{arXiv:1710.01123, - author = "Aaboud, Morad and others", - title = "{Search for heavy resonances decaying into $WW$ in the - $e\nu\mu\nu$ final state in $pp$ collisions at - $\sqrt{s}=13$ TeV with the ATLAS detector}", - collaboration = "ATLAS", - journal = "Eur. Phys. J.", - volume = "C78", - year = "2018", - number = "1", - pages = "24", - doi = "10.1140/epjc/s10052-017-5491-4", - eprint = "1710.01123", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - reportNumber = "CERN-EP-2017-214", - SLACcitation = "%%CITATION = ARXIV:1710.01123;%%" -} - -@article{arXiv:1701.02032, - author = "Khachatryan, V. and others", - title = "{Search for light bosons in decays of the 125 GeV Higgs - boson in proton-proton collisions at $ \sqrt{s}=8 $ TeV}", - collaboration = "CMS", - journal = "JHEP", - volume = "10", - year = "2017", - pages = "076", - doi = "10.1007/JHEP10(2017)076", - eprint = "1701.02032", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - reportNumber = "CMS-HIG-16-015, CERN-EP-2016-292", - SLACcitation = "%%CITATION = ARXIV:1701.02032;%%" -} - -@article{arXiv:1709.07242, - author = "Aaboud, Morad and others", - title = "{Search for additional heavy neutral Higgs and gauge - bosons in the ditau final state produced in 36 fb$^{−1}$ - of pp collisions at $ \sqrt{s}=13 $ TeV with the ATLAS - detector}", - collaboration = "ATLAS", - journal = "JHEP", - volume = "01", - year = "2018", - pages = "055", - doi = "10.1007/JHEP01(2018)055", - eprint = "1709.07242", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - reportNumber = "CERN-EP-2017-199", - SLACcitation = "%%CITATION = ARXIV:1709.07242;%%" -} - -@article{arXiv:1807.07915, - author = "Aaboud, Morad and others", - title = "{Search for charged Higgs bosons decaying via $H^{\pm} - \to \tau^{\pm}\nu_{\tau}$ in the $\tau$+jets and - $\tau$+lepton final states with 36 fb$^{-1}$ of $pp$ - collision data recorded at $\sqrt{s} = 13$ TeV with the - ATLAS experiment}", - collaboration = "ATLAS", - journal = "Submitted to: JHEP", - year = "2018", - eprint = "1807.07915", - archivePrefix = "arXiv", - primaryClass = "hep-ex", - reportNumber = "CERN-EP-2018-148", - SLACcitation = "%%CITATION = ARXIV:1807.07915;%%" -} - -@article{arXiv:1610.07922, - author = "de Florian, D. and others", - title = "{Handbook of LHC Higgs Cross Sections: 4. Deciphering the - Nature of the Higgs Sector}", - collaboration = "LHC Higgs Cross Section Working Group", - doi = "10.23731/CYRM-2017-002", - year = "2016", - eprint = "1610.07922", - archivePrefix = "arXiv", - primaryClass = "hep-ph", - reportNumber = "FERMILAB-FN-1025-T, CERN-2017-002-M", - SLACcitation = "%%CITATION = ARXIV:1610.07922;%%" -} \ No newline at end of file +% No SPIRES record found for cite request arXiv:1610.07922 \ No newline at end of file Index: trunk/webversion/minipaper.bbl =================================================================== --- trunk/webversion/minipaper.bbl (revision 600) +++ trunk/webversion/minipaper.bbl (revision 601) @@ -1,615 +1,585 @@ \begin{thebibliography}{100}\raggedright \bibitem{arXiv:0811.4169} P. Bechtle et~al., \newblock Comput. Phys. Commun. 181 (2010) 138, {{\tt arXiv:0811.4169}}. %%CITATION = 0811.4169;%% \bibitem{arXiv:1102.1898} P. Bechtle et~al., \newblock Comput. Phys. Commun. 182 (2011) 2605, {{\tt arXiv:1102.1898}}. %%CITATION = 1102.1898;%% \bibitem{arXiv:1301.2345} P. Bechtle et~al., \newblock PoS CHARGED2012 (2012) 024, {{\tt arXiv:1301.2345}}. %%CITATION = 1301.2345;%% \bibitem{arXiv:1311.0055} P. Bechtle et~al., \newblock Eur. Phys. J. C74 (2014) 2693, {{\tt arXiv:1311.0055}}. %%CITATION = 1311.0055;%% \bibitem{arXiv:1507.06706} P. Bechtle et~al., \newblock (2015), {{\tt arXiv:1507.06706}}. %%CITATION = 1507.06706;%% -\bibitem{arxiv:1112.2577} -ATLAS, G. Aad, -\newblock Phys. Rev. Lett. 108 (2012) 111802, {{\tt arXiv:1112.2577}}. -%%CITATION = 1112.2577;%% - -\bibitem{arXiv:0806.0611} -D0, V.M. Abazov et~al., -\newblock Phys. Lett. B671 (2009) 349, {{\tt arXiv:0806.0611}}. -%%CITATION = 0806.0611;%% - -\bibitem{arXiv:1207.0449} -Tevatron New Physics Higgs Working Group, C. Group, D. Collaborations and . the - Tevatron New Physics~an, -\newblock (2012), {{\tt arXiv:1207.0449}}. -%%CITATION = 1207.0449;%% - -\bibitem{arXiv:0809.3930} -CDF, T. Aaltonen et~al., -\newblock Phys. Rev. Lett. 102 (2009) 021802, {{\tt arXiv:0809.3930}}. -%%CITATION = 0809.3930;%% +\bibitem{arXiv:1406.7663} +ATLAS, . , +\newblock Physics Letters B738 (2014) 68, {{\tt arXiv:1406.7663}}. +%%CITATION = 1406.7663;%% -\bibitem{arXiv:0901.1887} +\bibitem{arXiv:1106.4885} D0, V.M. Abazov et~al., -\newblock Phys. Rev. Lett. 102 (2009) 231801, {{\tt arXiv:0901.1887}}. -%%CITATION = 0901.1887;%% +\newblock Phys. Rev. Lett. 107 (2011) 121801, {{\tt arXiv:1106.4885}}. +%%CITATION = 1106.4885;%% -\bibitem{arXiv:1603.06896} +\bibitem{arXiv:1603.02991} CMS, . , -\newblock (2016), {{\tt arXiv:1603.06896}}. -%%CITATION = 1603.06896;%% - -\bibitem{arXiv:1108.3331} -CDF, D. Benjamin et~al., -\newblock (2011), {{\tt arXiv:1108.3331}}. -%%CITATION = 1108.3331;%% - -\bibitem{arXiv:1109.3357} -ATLAS, . and others, -\newblock Phys. Rev. Lett. 107 (2011) 221802, {{\tt arXiv:1109.3357}}. -%%CITATION = 1109.3357;%% - -\bibitem{arxiv:1202.1408} -ATLAS, G. Aad, -\newblock Phys. Lett. B710 (2012) 49, {{\tt arXiv:1202.1408}}. -%%CITATION = 1202.1408;%% +\newblock Phys. Lett. B759 (2016) 369, {{\tt arXiv:1603.02991}}. +%%CITATION = 1603.02991;%% -\bibitem{arXiv:1712.06386} -ATLAS, M. Aaboud et~al., -\newblock Eur. Phys. J. C78 (2018) 293, {{\tt arXiv:1712.06386}}. -%%CITATION = ARXIV:1712.06386;%% +\bibitem{arXiv:1107.1268} +D0, V.M. Abazov et~al., +\newblock Phys. Rev. D84 (2011) 092002, {{\tt arXiv:1107.1268}}. +%%CITATION = 1107.1268;%% -\bibitem{arXiv:1003.3363} -Tevatron New Phenomena and Higgs Working Group, D. Benjamin et~al., -\newblock (2010), {{\tt arXiv:1003.3363}}. -%%CITATION = 1003.3363;%% +\bibitem{arXiv:1001.4468} +CDF, T. Aaltonen et~al., +\newblock Phys. Rev. Lett. 104 (2010) 061803, {{\tt arXiv:1001.4468}}. +%%CITATION = 1001.4468;%% -\bibitem{arXiv:1012.0874} -D0, V.M. Abazov et~al., -\newblock Phys. Lett. B698 (2011) 6, {{\tt arXiv:1012.0874}}. -%%CITATION = 1012.0874;%% +\bibitem{arXiv:1503.04233} +ATLAS, . , +\newblock (2015), {{\tt arXiv:1503.04233}}. +%%CITATION = 1503.04233;%% -\bibitem{arxiv:1202.3478} -CMS, S. Chatrchyan, -\newblock JHEP 03 (2012) 040, {{\tt arXiv:1202.3478}}. -%%CITATION = 1202.3478;%% +\bibitem{arXiv:1509.00389} +ATLAS, . , +\newblock JHEP01 (2016) 032, {{\tt arXiv:1509.00389}}. +%%CITATION = 1509.00389;%% -\bibitem{arXiv:1504.00936} +\bibitem{arXiv:1504.04710} CMS, . , -\newblock (2015), {{\tt arXiv:1504.00936}}. -%%CITATION = 1504.00936;%% +\newblock Phys. Lett. B748 (2015) 221, {{\tt arXiv:1504.04710}}. +%%CITATION = 1504.04710;%% -\bibitem{arXiv:1502.04478} -ATLAS, . , -\newblock Physics Letters B744 (2015) 163, {{\tt arXiv:1502.04478}}. -%%CITATION = 1502.04478;%% +\bibitem{hep-ex/0107031} +LEP Higgs Working Group for Higgs boson searches, +\newblock (2001), {{\tt hep-ex/0107031}}. +%%CITATION = HEP-EX/0107031;%% -\bibitem{arXiv:1509.05051} -ATLAS, . , -\newblock (2015), {{\tt arXiv:1509.05051}}. -%%CITATION = 1509.05051;%% +\bibitem{hep-ex/0410017} +DELPHI, J. Abdallah et~al., +\newblock Eur. Phys. J. C38 (2004) 1, {{\tt hep-ex/0410017}}. +%%CITATION = HEP-EX/0410017;%% \bibitem{arXiv:1507.05930} ATLAS, . , \newblock Eur. Phys. J. C76 (2016) 45, {{\tt arXiv:1507.05930}}. %%CITATION = 1507.05930;%% -\bibitem{arXiv:1011.1931} -D0, V.M. Abazov et~al., -\newblock Phys. Lett. B698 (2011) 97, {{\tt arXiv:1011.1931}}. -%%CITATION = 1011.1931;%% +\bibitem{arXiv:1407.6583} +ATLAS, . , +\newblock (2014), {{\tt arXiv:1407.6583}}. +%%CITATION = 1407.6583;%% -\bibitem{arXiv:1506.00424} +\bibitem{arXiv:1504.00936} CMS, . , -\newblock Phys. Lett. B752 (2016) 146, {{\tt arXiv:1506.00424}}. -%%CITATION = 1506.00424;%% +\newblock (2015), {{\tt arXiv:1504.00936}}. +%%CITATION = 1504.00936;%% -\bibitem{arXiv:1503.04233} +\bibitem{arXiv:1406.5053} ATLAS, . , -\newblock (2015), {{\tt arXiv:1503.04233}}. -%%CITATION = 1503.04233;%% +\newblock (2014), {{\tt arXiv:1406.5053}}. +%%CITATION = 1406.5053;%% \bibitem{arXiv:1008.3564} D0, V.M. Abazov et~al., \newblock Phys. Rev. Lett. 105 (2010) 251801, {{\tt arXiv:1008.3564}}. %%CITATION = 1008.3564;%% -\bibitem{hep-ex/0404012} +\bibitem{hep-ex/0401022} DELPHI, J. Abdallah et~al., -\newblock Eur. Phys. J. C34 (2004) 399, {{\tt hep-ex/0404012}}. -%%CITATION = HEP-EX/0404012;%% - -\bibitem{arXiv:1108.5064} -ATLAS, G. Aad, -\newblock Phys. Lett. B707 (2012) 27, {{\tt arXiv:1108.5064}}. -%%CITATION = 1108.5064;%% - -\bibitem{arXiv:1710.01123} -ATLAS, M. Aaboud et~al., -\newblock Eur. Phys. J. C78 (2018) 24, {{\tt arXiv:1710.01123}}. -%%CITATION = ARXIV:1710.01123;%% - -\bibitem{arXiv:1509.00389} -ATLAS, . , -\newblock JHEP01 (2016) 032, {{\tt arXiv:1509.00389}}. -%%CITATION = 1509.00389;%% - -\bibitem{arXiv:1202.1416} -CMS, S. Chatrchyan, -\newblock JHEP 04 (2012) 036, {{\tt arXiv:1202.1416}}. -%%CITATION = 1202.1416;%% - -\bibitem{hep-ex/0501033} -L3, P. Achard et~al., -\newblock Phys. Lett. B609 (2005) 35, {{\tt hep-ex/0501033}}. -%%CITATION = HEP-EX/0501033;%% - -\bibitem{arXiv:1701.02032} -CMS, V. Khachatryan et~al., -\newblock JHEP 10 (2017) 076, {{\tt arXiv:1701.02032}}. -%%CITATION = ARXIV:1701.02032;%% +\newblock Eur. Phys. J. C32 (2004) 475, {{\tt hep-ex/0401022}}. +%%CITATION = HEP-EX/0401022;%% -\bibitem{arXiv:1506.08329} +\bibitem{arXiv:1506.02301} CMS, . , -\newblock JHEP11 (2015) 071, {{\tt arXiv:1506.08329}}. -%%CITATION = 1506.08329;%% +\newblock Phys. Lett. B750 (2015) 494, {{\tt arXiv:1506.02301}}. +%%CITATION = 1506.02301;%% -\bibitem{arXiv:0905.3381} -D0, V.M. Abazov et~al., -\newblock Phys. Rev. Lett. 103 (2009) 061801, {{\tt arXiv:0905.3381}}. -%%CITATION = 0905.3381;%% +\bibitem{arXiv:1202.1415} +ATLAS, G. Aad et~al., +\newblock Phys. Lett. B710 (2012) 383, {{\tt arXiv:1202.1415}}. +%%CITATION = 1202.1415;%% \bibitem{arXiv:1001.4481} D0, V.M. Abazov et~al., \newblock Phys. Rev. Lett. 104 (2010) 061804, {{\tt arXiv:1001.4481}}. %%CITATION = 1001.4481;%% -\bibitem{arXiv:1709.07242} -ATLAS, M. Aaboud et~al., -\newblock JHEP 01 (2018) 055, {{\tt arXiv:1709.07242}}. -%%CITATION = ARXIV:1709.07242;%% +\bibitem{arXiv:1107.4960} +TEVNPH Working Group, . and others, +\newblock (2011), {{\tt arXiv:1107.4960}}. +%%CITATION = 1107.4960;%% \bibitem{arXiv:1402.3244} ATLAS, . , \newblock (2014), {{\tt arXiv:1402.3244}}. %%CITATION = 1402.3244;%% -\bibitem{arXiv:1409.6064} +\bibitem{arxiv:1112.2577} +ATLAS, G. Aad, +\newblock Phys. Rev. Lett. 108 (2012) 111802, {{\tt arXiv:1112.2577}}. +%%CITATION = 1112.2577;%% + +\bibitem{arXiv:1301.6065} +ALEPH, G. Abbiendi et~al., +\newblock (2013), {{\tt arXiv:1301.6065}}. +%%CITATION = 1301.6065;%% + +\bibitem{arXiv:0906.1014} +CDF, T. Aaltonen et~al., +\newblock Phys. Rev. Lett. 103 (2009) 201801, {{\tt arXiv:0906.1014}}. +%%CITATION = 0906.1014;%% + +\bibitem{arXiv:1503.04114} +CMS, . , +\newblock Phys. Lett. B749 (2015) 560, {{\tt arXiv:1503.04114}}. +%%CITATION = 1503.04114;%% + +\bibitem{arXiv:1509.05051} ATLAS, . , -\newblock (2014), {{\tt arXiv:1409.6064}}. -%%CITATION = 1409.6064;%% +\newblock (2015), {{\tt arXiv:1509.05051}}. +%%CITATION = 1509.05051;%% + +\bibitem{arxiv:1202.1997} +CMS, S. Chatrchyan, +\newblock Phys. Rev. Lett. 108 (2012) 111804, {{\tt arXiv:1202.1997}}. +%%CITATION = 1202.1997;%% + +\bibitem{hep-ex/0111010} +OPAL, G. Abbiendi et~al., +\newblock Eur. Phys. J. C23 (2002) 397, {{\tt hep-ex/0111010}}. +%%CITATION = HEP-EX/0111010;%% + +\bibitem{hep-ex/0602042} +ALEPH, S. Schael et~al., +\newblock Eur. Phys. J. C47 (2006) 547, {{\tt hep-ex/0602042}}. +%%CITATION = HEP-EX/0602042;%% + +\bibitem{arXiv:1011.1931} +D0, V.M. Abazov et~al., +\newblock Phys. Lett. B698 (2011) 97, {{\tt arXiv:1011.1931}}. +%%CITATION = 1011.1931;%% \bibitem{arXiv:1509.04670} ATLAS, . , \newblock (2015), {{\tt arXiv:1509.04670}}. %%CITATION = 1509.04670;%% -\bibitem{arXiv:0908.1811} -D0, V.M. Abazov et~al., -\newblock Phys. Lett. B682 (2009) 278, {{\tt arXiv:0908.1811}}. -%%CITATION = 0908.1811;%% - -\bibitem{hep-ex/0410017} -DELPHI, J. Abdallah et~al., -\newblock Eur. Phys. J. C38 (2004) 1, {{\tt hep-ex/0410017}}. -%%CITATION = HEP-EX/0410017;%% - \bibitem{arXiv:1202.1414} ATLAS, G. Aad, \newblock Phys. Rev. Lett. 108 (2012) 111803, {{\tt arXiv:1202.1414}}. %%CITATION = 1202.1414;%% -\bibitem{arXiv:1001.4468} -CDF, T. Aaltonen et~al., -\newblock Phys. Rev. Lett. 104 (2010) 061803, {{\tt arXiv:1001.4468}}. -%%CITATION = 1001.4468;%% +\bibitem{arXiv:1109.3357} +ATLAS, . and others, +\newblock Phys. Rev. Lett. 107 (2011) 221802, {{\tt arXiv:1109.3357}}. +%%CITATION = 1109.3357;%% -\bibitem{arXiv:1204.2760} -ATLAS, G. Aad, -\newblock JHEP 06 (2012) 039, {{\tt arXiv:1204.2760}}. -%%CITATION = 1204.2760;%% +\bibitem{arXiv:0812.0267} +OPAL, G. Abbiendi et~al., +\newblock Eur. Phys. J. C72 (2012) 2076, {{\tt arXiv:0812.0267}}. +%%CITATION = 0812.0267;%% + +\bibitem{arXiv:0806.0611} +D0, V.M. Abazov et~al., +\newblock Phys. Lett. B671 (2009) 349, {{\tt arXiv:0806.0611}}. +%%CITATION = 0806.0611;%% + +\bibitem{arXiv:1510.01181} +CMS, . , +\newblock Phys. Lett. B755 (2016) 217, {{\tt arXiv:1510.01181}}. +%%CITATION = 1510.01181;%% + +\bibitem{arXiv:1307.5515} +CMS, . , +\newblock Phys. Lett. B726 (2013) 587, {{\tt arXiv:1307.5515}}. +%%CITATION = 1307.5515;%% + +\bibitem{hep-ex/0206022} +OPAL, G. Abbiendi et~al., +\newblock Eur. Phys. J. C27 (2003) 311, {{\tt hep-ex/0206022}}. +%%CITATION = HEP-EX/0206022;%% + +\bibitem{arXiv:1108.3331} +CDF, D. Benjamin et~al., +\newblock (2011), {{\tt arXiv:1108.3331}}. +%%CITATION = 1108.3331;%% + +\bibitem{arXiv:0707.0373} +OPAL, G. Abbiendi et~al., +\newblock Phys. Lett. B682 (2010) 381, {{\tt arXiv:0707.0373}}. +%%CITATION = 0707.0373;%% \bibitem{arXiv:0906.5613} CDF, T. Aaltonen et~al., \newblock Phys. Rev. Lett. 103 (2009) 101802, {{\tt arXiv:0906.5613}}. %%CITATION = 0906.5613;%% +\bibitem{arXiv:1506.00424} +CMS, . , +\newblock Phys. Lett. B752 (2016) 146, {{\tt arXiv:1506.00424}}. +%%CITATION = 1506.00424;%% + +\bibitem{arXiv:1409.6064} +ATLAS, . , +\newblock (2014), {{\tt arXiv:1409.6064}}. +%%CITATION = 1409.6064;%% + +\bibitem{arXiv:1207.0449} +Tevatron New Physics Higgs Working Group, C. Group, D. Collaborations and . the + Tevatron New Physics~an, +\newblock (2012), {{\tt arXiv:1207.0449}}. +%%CITATION = 1207.0449;%% + \bibitem{arXiv:1207.7214} ATLAS, \newblock Phys. Lett. B716 (2012) 1, {{\tt arXiv:1207.7214}}. %%CITATION = 1207.7214;%% -\bibitem{arXiv:0812.0267} -OPAL, G. Abbiendi et~al., -\newblock Eur. Phys. J. C72 (2012) 2076, {{\tt arXiv:0812.0267}}. -%%CITATION = 0812.0267;%% +\bibitem{hep-ex/0501033} +L3, P. Achard et~al., +\newblock Phys. Lett. B609 (2005) 35, {{\tt hep-ex/0501033}}. +%%CITATION = HEP-EX/0501033;%% -\bibitem{arXiv:1207.6436} +\bibitem{arXiv:0907.1269} CDF, T. Aaltonen et~al., -\newblock Phys. Rev. Lett. 109 (2012) 071804, {{\tt arXiv:1207.6436}}. -%%CITATION = 1207.6436;%% +\newblock Phys. Rev. Lett. 103 (2009) 101803, {{\tt arXiv:0907.1269}}. +%%CITATION = 0907.1269;%% -\bibitem{arXiv:0707.0373} -OPAL, G. Abbiendi et~al., -\newblock Phys. Lett. B682 (2010) 381, {{\tt arXiv:0707.0373}}. -%%CITATION = 0707.0373;%% +\bibitem{arxiv:1202.3478} +CMS, S. Chatrchyan, +\newblock JHEP 03 (2012) 040, {{\tt arXiv:1202.3478}}. +%%CITATION = 1202.3478;%% -\bibitem{arXiv:1603.02991} +\bibitem{arXiv:1506.08329} CMS, . , -\newblock Phys. Lett. B759 (2016) 369, {{\tt arXiv:1603.02991}}. -%%CITATION = 1603.02991;%% +\newblock JHEP11 (2015) 071, {{\tt arXiv:1506.08329}}. +%%CITATION = 1506.08329;%% + +\bibitem{arXiv:1502.04478} +ATLAS, . , +\newblock Physics Letters B744 (2015) 163, {{\tt arXiv:1502.04478}}. +%%CITATION = 1502.04478;%% \bibitem{arXiv:1402.3051} ATLAS, . , \newblock Phys. Lett. B732 (2014) 8, {{\tt arXiv:1402.3051}}. %%CITATION = 1402.3051;%% -\bibitem{hep-ex/0107032} -LEP Higgs Working for Higgs boson searches, -\newblock (2001), {{\tt hep-ex/0107032}}. -%%CITATION = HEP-EX/0107032;%% - -\bibitem{hep-ex/0602042} -ALEPH, S. Schael et~al., -\newblock Eur. Phys. J. C47 (2006) 547, {{\tt hep-ex/0602042}}. -%%CITATION = HEP-EX/0602042;%% - -\bibitem{hep-ex/0111010} -OPAL, G. Abbiendi et~al., -\newblock Eur. Phys. J. C23 (2002) 397, {{\tt hep-ex/0111010}}. -%%CITATION = HEP-EX/0111010;%% +\bibitem{arXiv:1603.06896} +CMS, . , +\newblock (2016), {{\tt arXiv:1603.06896}}. +%%CITATION = 1603.06896;%% \bibitem{arXiv:1106.4555} D0, V.M. Abazov et~al., \newblock Phys. Lett. B707 (2012) 323, {{\tt arXiv:1106.4555}}. %%CITATION = 1106.4555;%% -\bibitem{arXiv:1503.04114} -CMS, . , -\newblock Phys. Lett. B749 (2015) 560, {{\tt arXiv:1503.04114}}. -%%CITATION = 1503.04114;%% +\bibitem{arXiv:1204.2760} +ATLAS, G. Aad, +\newblock JHEP 06 (2012) 039, {{\tt arXiv:1204.2760}}. +%%CITATION = 1204.2760;%% -\bibitem{hep-ex/0107031} +\bibitem{hep-ex/0107034} LEP Higgs Working Group for Higgs boson searches, -\newblock (2001), {{\tt hep-ex/0107031}}. -%%CITATION = HEP-EX/0107031;%% +\newblock (2001), {{\tt hep-ex/0107034}}. +%%CITATION = HEP-EX/0107034;%% -\bibitem{arXiv:1407.6583} -ATLAS, . , -\newblock (2014), {{\tt arXiv:1407.6583}}. -%%CITATION = 1407.6583;%% +\bibitem{arxiv:1202.1488} +CMS, S. Chatrchyan, +\newblock Phys. Lett. B710 (2012) 26, {{\tt arXiv:1202.1488}}. +%%CITATION = 1202.1488;%% -\bibitem{arXiv:1404.1344} -CMS, . , -\newblock Eur. Phys. J. C74 (2014) 2980, {{\tt arXiv:1404.1344}}. -%%CITATION = 1404.1344;%% +\bibitem{arXiv:0809.3930} +CDF, T. Aaltonen et~al., +\newblock Phys. Rev. Lett. 102 (2009) 021802, {{\tt arXiv:0809.3930}}. +%%CITATION = 0809.3930;%% -\bibitem{hep-ex/0401022} -DELPHI, J. Abdallah et~al., -\newblock Eur. Phys. J. C32 (2004) 475, {{\tt hep-ex/0401022}}. -%%CITATION = HEP-EX/0401022;%% +\bibitem{arXiv:0901.1887} +D0, V.M. Abazov et~al., +\newblock Phys. Rev. Lett. 102 (2009) 231801, {{\tt arXiv:0901.1887}}. +%%CITATION = 0901.1887;%% -\bibitem{arXiv:1510.06534} -CMS, . , -\newblock JHEP01 (2016) 079, {{\tt arXiv:1510.06534}}. -%%CITATION = 1510.06534;%% +\bibitem{hep-ex/0404012} +DELPHI, J. Abdallah et~al., +\newblock Eur. Phys. J. C34 (2004) 399, {{\tt hep-ex/0404012}}. +%%CITATION = HEP-EX/0404012;%% -\bibitem{arXiv:1301.6065} -ALEPH, G. Abbiendi et~al., -\newblock (2013), {{\tt arXiv:1301.6065}}. -%%CITATION = 1301.6065;%% +\bibitem{hep-ex/0107032} +LEP Higgs Working for Higgs boson searches, +\newblock (2001), {{\tt hep-ex/0107032}}. +%%CITATION = HEP-EX/0107032;%% -\bibitem{arXiv:1406.7663} -ATLAS, . , -\newblock Physics Letters B738 (2014) 68, {{\tt arXiv:1406.7663}}. -%%CITATION = 1406.7663;%% +\bibitem{arXiv:0905.3381} +D0, V.M. Abazov et~al., +\newblock Phys. Rev. Lett. 103 (2009) 061801, {{\tt arXiv:0905.3381}}. +%%CITATION = 0905.3381;%% -\bibitem{arXiv:1807.07915} -ATLAS, M. Aaboud et~al., -\newblock Submitted to: JHEP (2018), {{\tt arXiv:1807.07915}}. -%%CITATION = ARXIV:1807.07915;%% +\bibitem{arXiv:1108.5064} +ATLAS, G. Aad, +\newblock Phys. Lett. B707 (2012) 27, {{\tt arXiv:1108.5064}}. +%%CITATION = 1108.5064;%% -\bibitem{arXiv:1106.4885} -D0, V.M. Abazov et~al., -\newblock Phys. Rev. Lett. 107 (2011) 121801, {{\tt arXiv:1106.4885}}. -%%CITATION = 1106.4885;%% +\bibitem{arXiv:1207.6436} +CDF, T. Aaltonen et~al., +\newblock Phys. Rev. Lett. 109 (2012) 071804, {{\tt arXiv:1207.6436}}. +%%CITATION = 1207.6436;%% -\bibitem{arXiv:1504.04710} +\bibitem{arXiv:1404.1344} CMS, . , -\newblock Phys. Lett. B748 (2015) 221, {{\tt arXiv:1504.04710}}. -%%CITATION = 1504.04710;%% +\newblock Eur. Phys. J. C74 (2014) 2980, {{\tt arXiv:1404.1344}}. +%%CITATION = 1404.1344;%% -\bibitem{arXiv:1202.1415} -ATLAS, G. Aad et~al., -\newblock Phys. Lett. B710 (2012) 383, {{\tt arXiv:1202.1415}}. -%%CITATION = 1202.1415;%% +\bibitem{arXiv:1012.0874} +D0, V.M. Abazov et~al., +\newblock Phys. Lett. B698 (2011) 6, {{\tt arXiv:1012.0874}}. +%%CITATION = 1012.0874;%% -\bibitem{hep-ex/0107034} -LEP Higgs Working Group for Higgs boson searches, -\newblock (2001), {{\tt hep-ex/0107034}}. -%%CITATION = HEP-EX/0107034;%% +\bibitem{arxiv:1202.1408} +ATLAS, G. Aad, +\newblock Phys. Lett. B710 (2012) 49, {{\tt arXiv:1202.1408}}. +%%CITATION = 1202.1408;%% -\bibitem{arXiv:1406.5053} -ATLAS, . , -\newblock (2014), {{\tt arXiv:1406.5053}}. -%%CITATION = 1406.5053;%% +\bibitem{arXiv:1003.3363} +Tevatron New Phenomena and Higgs Working Group, D. Benjamin et~al., +\newblock (2010), {{\tt arXiv:1003.3363}}. +%%CITATION = 1003.3363;%% \bibitem{arXiv:1106.4782} CDF, T. Aaltonen et~al., \newblock Phys. Rev. D85 (2012) 032005, {{\tt arXiv:1106.4782}}. %%CITATION = 1106.4782;%% -\bibitem{arXiv:1510.01181} +\bibitem{arXiv:1510.06534} CMS, . , -\newblock Phys. Lett. B755 (2016) 217, {{\tt arXiv:1510.01181}}. -%%CITATION = 1510.01181;%% +\newblock JHEP01 (2016) 079, {{\tt arXiv:1510.06534}}. +%%CITATION = 1510.06534;%% -\bibitem{arXiv:1107.1268} +\bibitem{arXiv:0908.1811} D0, V.M. Abazov et~al., -\newblock Phys. Rev. D84 (2011) 092002, {{\tt arXiv:1107.1268}}. -%%CITATION = 1107.1268;%% - -\bibitem{arxiv:1202.1997} -CMS, S. Chatrchyan, -\newblock Phys. Rev. Lett. 108 (2012) 111804, {{\tt arXiv:1202.1997}}. -%%CITATION = 1202.1997;%% - -\bibitem{arXiv:1107.4960} -TEVNPH Working Group, . and others, -\newblock (2011), {{\tt arXiv:1107.4960}}. -%%CITATION = 1107.4960;%% - -\bibitem{arXiv:1307.5515} -CMS, . , -\newblock Phys. Lett. B726 (2013) 587, {{\tt arXiv:1307.5515}}. -%%CITATION = 1307.5515;%% - -\bibitem{hep-ex/0206022} -OPAL, G. Abbiendi et~al., -\newblock Eur. Phys. J. C27 (2003) 311, {{\tt hep-ex/0206022}}. -%%CITATION = HEP-EX/0206022;%% - -\bibitem{arXiv:0906.1014} -CDF, T. Aaltonen et~al., -\newblock Phys. Rev. Lett. 103 (2009) 201801, {{\tt arXiv:0906.1014}}. -%%CITATION = 0906.1014;%% - -\bibitem{arXiv:0907.1269} -CDF, T. Aaltonen et~al., -\newblock Phys. Rev. Lett. 103 (2009) 101803, {{\tt arXiv:0907.1269}}. -%%CITATION = 0907.1269;%% +\newblock Phys. Lett. B682 (2009) 278, {{\tt arXiv:0908.1811}}. +%%CITATION = 0908.1811;%% -\bibitem{arxiv:1202.1488} +\bibitem{arXiv:1202.1416} CMS, S. Chatrchyan, -\newblock Phys. Lett. B710 (2012) 26, {{\tt arXiv:1202.1488}}. -%%CITATION = 1202.1488;%% - -\bibitem{arXiv:1506.02301} -CMS, . , -\newblock Phys. Lett. B750 (2015) 494, {{\tt arXiv:1506.02301}}. -%%CITATION = 1506.02301;%% +\newblock JHEP 04 (2012) 036, {{\tt arXiv:1202.1416}}. +%%CITATION = 1202.1416;%% \bibitem{CDFnotes} CDF, -\newblock CDF Notes 10500 10799 10573 8353 9999 10796 7307 10574 10485 7712 - 10010 10439 10599 10798. +\newblock CDF Notes 9999 10574 7307 7712 10485 10010 10798 10799 10573 10439 + 10500 8353 10599 10796. \bibitem{D0notes} D0, -\newblock D0 Notes 6304 6305 6296 5873 6302 5739 6299 6227 6083 6295 6276 5845 - 6301 6183 6171 6286 6309 5757. +\newblock D0 Notes 5845 6304 6276 6286 6305 6083 5873 5739 6227 6296 6299 6183 + 6301 6295 6309 6171 5757 6302. \bibitem{CMSnotes} CMS, \newblock CMS Physics Analysis Summaries. \bibitem{ATLASnotes} ATLAS, -\newblock ATLAS CONF Notes 2012-160 2016-062 2016-089 2016-049 2012-135 - 2013-013 2012-161 2016-004 2016-059 2014-049 2016-074 2014-050 2012-092 - 2012-078 2016-088 2012-016 2012-019 2016-044 2016-071 2012-168 2011-094 - 2013-010 2016-055 2011-157 2016-056 2012-012 2013-030 2016-015 2016-079 - 2012-017 2016-082. +\newblock ATLAS CONF Notes 2016-079 2012-135 2012-017 2013-030 2016-044 + 2011-094 2016-049 2016-056 2013-010 2016-074 2012-078 2014-049 2014-050 + 2012-012 2013-013 2016-004 2016-055 2016-015 2012-161 2016-071 2016-088 + 2011-157 2012-160 2012-019 2012-016 2018-025 2016-082 2012-092 2012-168 + 2016-062. \bibitem{LHWGnotes} LHWG, \newblock LHWG Notes 2002-02. \bibitem{hep-ph/9704448} A. Djouadi, J. Kalinowski and M. Spira, \newblock Comput. Phys. Commun. 108 (1998) 56, {{\tt hep-ph/9704448}}. %%CITATION = HEP-PH/9704448;%% \bibitem{hep-ph/0102227} S. Catani, D. de~Florian and M. Grazzini, \newblock JHEP 05 (2001) 025, {{\tt hep-ph/0102227}}. %%CITATION = HEP-PH/0102227;%% \bibitem{hep-ph/0102241} R.V. Harlander and W.B. Kilgore, \newblock Phys. Rev. D64 (2001) 013015, {{\tt hep-ph/0102241}}. %%CITATION = HEP-PH/0102241;%% \bibitem{hep-ph/0201206} R.V. Harlander and W.B. Kilgore, \newblock Phys. Rev. Lett. 88 (2002) 201801, {{\tt hep-ph/0201206}}. %%CITATION = HEP-PH/0201206;%% \bibitem{hep-ph/0207004} C. Anastasiou and K. Melnikov, \newblock Nucl. Phys. B646 (2002) 220, {{\tt hep-ph/0207004}}. %%CITATION = HEP-PH/0207004;%% \bibitem{hep-ph/0302135} V. Ravindran, J. Smith and W.L. van Neerven, \newblock Nucl. Phys. B665 (2003) 325, {{\tt hep-ph/0302135}}. %%CITATION = HEP-PH/0302135;%% \bibitem{arXiv:0811.3458} C. Anastasiou, R. Boughezal and F. Petriello, \newblock JHEP 04 (2009) 003, {{\tt arXiv:0811.3458}}. %%CITATION = 0811.3458;%% \bibitem{Dawson:1990zj} S. Dawson, \newblock Nucl. Phys. B359 (1991) 283. %%CITATION = NUPHA,B359,283;%% \bibitem{Djouadi:1991tka} A. Djouadi, M. Spira and P.M. Zerwas, \newblock Phys. Lett. B264 (1991) 440. %%CITATION = PHLTA,B264,440;%% \bibitem{hep-ph/9504378} M. Spira et~al., \newblock Nucl. Phys. B453 (1995) 17, {{\tt hep-ph/9504378}}. %%CITATION = HEP-PH/9504378;%% \bibitem{hep-ph/0404071} U. Aglietti et~al., \newblock Phys. Lett. B595 (2004) 432, {{\tt hep-ph/0404071}}. %%CITATION = HEP-PH/0404071;%% \bibitem{hep-ph/0407249} G. Degrassi and F. Maltoni, \newblock Phys. Lett. B600 (2004) 255, {{\tt hep-ph/0407249}}. %%CITATION = HEP-PH/0407249;%% \bibitem{arXiv:0809.1301} S. Actis et~al., \newblock Phys. Lett. B670 (2008) 12, {{\tt arXiv:0809.1301}}. %%CITATION = 0809.1301;%% \bibitem{arXiv:0809.3667} S. Actis et~al., \newblock Nucl. Phys. B811 (2009) 182, {{\tt arXiv:0809.3667}}. %%CITATION = 0809.3667;%% \bibitem{hep-ph/0306211} S. Catani et~al., \newblock JHEP 07 (2003) 028, {{\tt hep-ph/0306211}}. %%CITATION = HEP-PH/0306211;%% \bibitem{arXiv:0901.2427} D. de~Florian and M. Grazzini, \newblock Phys. Lett. B674 (2009) 291, {{\tt arXiv:0901.2427}}. %%CITATION = 0901.2427;%% \bibitem{hep-ph/0307206} O. Brein, A. Djouadi and R. Harlander, \newblock Phys. Lett. B579 (2004) 149, {{\tt hep-ph/0307206}}. %%CITATION = HEP-PH/0307206;%% \bibitem{hep-ph/0306234} M.L. Ciccolini, S. Dittmaier and M. Kramer, \newblock Phys. Rev. D68 (2003) 073003, {{\tt hep-ph/0306234}}. %%CITATION = HEP-PH/0306234;%% \bibitem{hep-ph/0406152} Higgs Working Group, K.A. Assamagan et~al., \newblock (2004), {{\tt hep-ph/0406152}}. %%CITATION = HEP-PH/0406152;%% \bibitem{hep-ph/0304035} R.V. Harlander and W.B. Kilgore, \newblock Phys. Rev. D68 (2003) 013001, {{\tt hep-ph/0304035}}. %%CITATION = HEP-PH/0304035;%% \bibitem{hep-ph/9206246} T. Han, G. Valencia and S. Willenbrock, \newblock Phys. Rev. Lett. 69 (1992) 3274, {{\tt hep-ph/9206246}}. %%CITATION = HEP-PH/9206246;%% \bibitem{hep-ph/9905386} J.M. Campbell and R.K. Ellis, \newblock Phys. Rev. D60 (1999) 113006, {{\tt hep-ph/9905386}}. %%CITATION = HEP-PH/9905386;%% \bibitem{hep-ph/0306109} T. Figy, C. Oleari and D. Zeppenfeld, \newblock Phys. Rev. D68 (2003) 073005, {{\tt hep-ph/0306109}}. %%CITATION = HEP-PH/0306109;%% \bibitem{hep-ph/0403194} E.L. Berger and J.M. Campbell, \newblock Phys. Rev. D70 (2004) 073011, {{\tt hep-ph/0403194}}. %%CITATION = HEP-PH/0403194;%% \bibitem{hep-ph/0612172} U. Aglietti et~al., \newblock (2006), {{\tt hep-ph/0612172}}. %%CITATION = HEP-PH/0612172;%% \bibitem{hep-ph/0107081} W. Beenakker et~al., \newblock Phys. Rev. Lett. 87 (2001) 201805, {{\tt hep-ph/0107081}}. %%CITATION = HEP-PH/0107081;%% \bibitem{hep-ph/0107101} L. Reina and S. Dawson, \newblock Phys. Rev. Lett. 87 (2001) 201804, {{\tt hep-ph/0107101}}. %%CITATION = HEP-PH/0107101;%% \bibitem{hep-ph/0211438} S. Dawson et~al., \newblock Phys. Rev. D67 (2003) 071503, {{\tt hep-ph/0211438}}. %%CITATION = HEP-PH/0211438;%% \bibitem{hep-ph/0305321} O. Brein and W. Hollik, \newblock Phys. Rev. D68 (2003) 095006, {{\tt hep-ph/0305321}}. %%CITATION = HEP-PH/0305321;%% \bibitem{arXiv:0705.2744} O. Brein and W. Hollik, \newblock Phys. Rev. D76 (2007) 035002, {{\tt arXiv:0705.2744}}. %%CITATION = 0705.2744;%% \bibitem{arXiv:0707.0381} M. Ciccolini, A. Denner and S. Dittmaier, \newblock Phys. Rev. Lett. 99 (2007) 161803, {{\tt arXiv:0707.0381}}. %%CITATION = 0707.0381;%% \bibitem{arXiv:0710.4749} M. Ciccolini, A. Denner and S. Dittmaier, \newblock Phys. Rev. D77 (2008) 013002, {{\tt arXiv:0710.4749}}. %%CITATION = 0710.4749;%% \bibitem{arXiv:1101.0593} LHC Higgs Cross Section Working Group, S. Dittmaier et~al., \newblock (2011), {{\tt arXiv:1101.0593}}. %%CITATION = 1101.0593;%% \bibitem{arXiv:1201.3084} S. Dittmaier et~al., \newblock (2012), {{\tt arXiv:1201.3084}}. %%CITATION = 1201.3084;%% \bibitem{arXiv:1307.1347} T.L.H.C.S.W. Group et~al., \newblock (2013), {{\tt arXiv:1307.1347}}. %%CITATION = 1307.1347;%% -\bibitem{arXiv:1610.07922} -LHC Higgs Cross Section Working Group, D. de~Florian et~al., -\newblock (2016), {{\tt arXiv:1610.07922}}. -%%CITATION = ARXIV:1610.07922;%% - \end{thebibliography} Index: trunk/webversion/minipaper.tex =================================================================== --- trunk/webversion/minipaper.tex (revision 600) +++ trunk/webversion/minipaper.tex (revision 601) @@ -1,17 +1,17 @@ \documentclass{article} \usepackage{cite} \begin{document} -HiggsBounds\cite{arXiv:0811.4169,arXiv:1102.1898,arXiv:1301.2345,arXiv:1311.0055,arXiv:1507.06706} version 5.2.0beta uses the following experimental analyses: \cite{arxiv:1112.2577,arXiv:0806.0611,arXiv:1207.0449,arXiv:0809.3930,arXiv:0901.1887,arXiv:1603.06896,arXiv:1108.3331,arXiv:1109.3357,arxiv:1202.1408,arXiv:1712.06386,arXiv:1003.3363,arXiv:1012.0874,arxiv:1202.3478,arXiv:1504.00936,arXiv:1502.04478,arXiv:1509.05051,arXiv:1507.05930,arXiv:1011.1931,arXiv:1506.00424,arXiv:1503.04233,arXiv:1008.3564,hep-ex/0404012,arXiv:1108.5064,arXiv:1710.01123,arXiv:1509.00389,arXiv:1202.1416,hep-ex/0501033,arXiv:1701.02032,arXiv:1506.08329,arXiv:0905.3381,arXiv:1001.4481,arXiv:1709.07242,arXiv:1402.3244,arXiv:1409.6064,arXiv:1509.04670,arXiv:0908.1811,hep-ex/0410017,arXiv:1202.1414,arXiv:1001.4468,arXiv:1204.2760,arXiv:0906.5613,arXiv:1207.7214,arXiv:0812.0267,arXiv:1207.6436,arXiv:0707.0373,arXiv:1603.02991,arXiv:1402.3051,hep-ex/0107032,hep-ex/0602042,hep-ex/0111010,arXiv:1106.4555,arXiv:1503.04114,hep-ex/0107031,arXiv:1407.6583,arXiv:1404.1344,hep-ex/0401022,arXiv:1510.06534,arXiv:1301.6065,arXiv:1406.7663,arXiv:1807.07915,arXiv:1106.4885,arXiv:1504.04710,arXiv:1202.1415,hep-ex/0107034,arXiv:1406.5053,arXiv:1106.4782,arXiv:1510.01181,arXiv:1107.1268,arxiv:1202.1997,arXiv:1107.4960,arXiv:1307.5515,hep-ex/0206022,arXiv:0906.1014,arXiv:0907.1269,arxiv:1202.1488,arXiv:1506.02301,CDFnotes,D0notes,CMSnotes,ATLASnotes,LHWGnotes} +HiggsBounds\cite{arXiv:0811.4169,arXiv:1102.1898,arXiv:1301.2345,arXiv:1311.0055,arXiv:1507.06706} version 5.3.0beta uses the following experimental analyses: \cite{arXiv:1406.7663,arXiv:1106.4885,arXiv:1603.02991,arXiv:1107.1268,arXiv:1809.06682,arXiv:1001.4468,arXiv:1807.00539,arXiv:1807.07915,arXiv:1503.04233,arXiv:1509.00389,arXiv:1701.02032,arXiv:1504.04710,arXiv:1807.04873,hep-ex/0107031,hep-ex/0410017,arXiv:1507.05930,arXiv:1407.6583,arXiv:1504.00936,arXiv:1406.5053,arXiv:1008.3564,hep-ex/0401022,arXiv:1506.02301,arXiv:1710.01123,arXiv:1202.1415,arXiv:1001.4481,arXiv:1107.4960,arXiv:1402.3244,arxiv:1112.2577,arXiv:1301.6065,arXiv:1807.08567,arXiv:0906.1014,arXiv:1503.04114,arXiv:1509.05051,arxiv:1202.1997,hep-ex/0111010,hep-ex/0602042,arXiv:1011.1931,arXiv:1707.04147,arXiv:1509.04670,arXiv:1202.1414,arXiv:1709.07242,arXiv:1109.3357,arXiv:1808.03599,arXiv:0812.0267,arXiv:0806.0611,arXiv:1510.01181,arXiv:1307.5515,hep-ex/0206022,arXiv:1108.3331,arXiv:0707.0373,arXiv:0906.5613,arXiv:1506.00424,arXiv:1409.6064,arXiv:1207.0449,arXiv:1207.7214,hep-ex/0501033,arXiv:0907.1269,arxiv:1202.3478,arXiv:1506.08329,arXiv:1502.04478,arXiv:1402.3051,arXiv:1603.06896,arXiv:1106.4555,arXiv:1204.2760,hep-ex/0107034,arxiv:1202.1488,arXiv:0809.3930,arXiv:0901.1887,hep-ex/0404012,hep-ex/0107032,arXiv:1712.06386,arXiv:0905.3381,arXiv:1108.5064,arXiv:1207.6436,arXiv:1404.1344,arXiv:1012.0874,arXiv:1806.07355,arxiv:1202.1408,arXiv:1003.3363,arXiv:1106.4782,arXiv:1510.06534,arXiv:0908.1811,arXiv:1808.00336,arXiv:1202.1416,CDFnotes,D0notes,CMSnotes,ATLASnotes,LHWGnotes} . -Internally, {\tt HiggsBounds} uses a number of Standard Model results for the Higgs sector\cite{hep-ph/9704448,hep-ph/0102227,hep-ph/0102241,hep-ph/0201206,hep-ph/0207004,hep-ph/0302135,arXiv:0811.3458,Dawson:1990zj,Djouadi:1991tka,hep-ph/9504378,hep-ph/0404071,hep-ph/0407249,arXiv:0809.1301,arXiv:0809.3667,hep-ph/0306211,arXiv:0901.2427,hep-ph/0307206,hep-ph/0306234,hep-ph/0406152,hep-ph/0304035,hep-ph/9206246,hep-ph/9905386,hep-ph/0306109,hep-ph/0403194,hep-ph/0612172,hep-ph/0107081,hep-ph/0107101,hep-ph/0211438,hep-ph/0305321,arXiv:0705.2744,arXiv:0707.0381,arXiv:0710.4749,arXiv:1101.0593,arXiv:1201.3084,arXiv:1307.1347,arXiv:1610.07922} +Internally, {\tt HiggsBounds} uses a number of Standard Model results for the Higgs sector\cite{hep-ph/9704448,hep-ph/0102227,hep-ph/0102241,hep-ph/0201206,hep-ph/0207004,hep-ph/0302135,arXiv:0811.3458,Dawson:1990zj,Djouadi:1991tka,hep-ph/9504378,hep-ph/0404071,hep-ph/0407249,arXiv:0809.1301,arXiv:0809.3667,hep-ph/0306211,arXiv:0901.2427,hep-ph/0307206,hep-ph/0306234,hep-ph/0406152,hep-ph/0304035,hep-ph/9206246,hep-ph/9905386,hep-ph/0306109,hep-ph/0403194,hep-ph/0612172,hep-ph/0107081,hep-ph/0107101,hep-ph/0211438,hep-ph/0305321,arXiv:0705.2744,arXiv:0707.0381,arXiv:0710.4749,arXiv:1101.0593,arXiv:1201.3084,hep-ph/0304035,arXiv:1307.1347,arXiv:1610.07922} to convert between experimental limits with different normalisations. \bibliographystyle{h-elsevier3-newarxivid-leftjust} \bibliography{minipaper} \end{document} Index: trunk/webversion/minipaper.pdf =================================================================== Cannot display: file marked as a binary type. svn:mime-type = application/octet-stream