Index: trunk/HiggsBounds_KW/S95tables.f90 =================================================================== --- trunk/HiggsBounds_KW/S95tables.f90 (revision 508) +++ trunk/HiggsBounds_KW/S95tables.f90 (revision 509) @@ -1,4408 +1,4408 @@ ! 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=4),parameter :: colliders(4) = (/'LEP ','TEV ','LHC7','LHC8'/) !------------------------------------------- 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 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=137 + ntable1=136 ntable2=21 ! 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 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 !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 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 stop'need to extend lower range of lhc7XS_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('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')) stop'need to extend lower range of lhc8XS_SM_functions' endif ! we need the branching ratios for all the colliders if( maxval(Exptrange_Mhmax_forSMdecays).gt.BRSMt1Mhmax)then 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)=600.0D0 else if(i.eq.get_collider_element_number('LHC8')) then Exptrange_Mhmin_forSMXS(i)=90.0D0 Exptrange_Mhmax_forSMXS(i)=600.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)=600.0D0 else if(i.eq.get_collider_element_number('LHC8')) then Exptrange_Mhmin_forSMdecays(i)=90.0D0 Exptrange_Mhmax_forSMdecays(i)=600.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) 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 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=4) :: WhichColliderString double precision :: 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 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 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,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) 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) 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(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) call model_likeness(j,S95_t1(c)%id,t,model_like(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(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(2014049) ! Insert correct xsection alias here ! fact(j)=t%lhc8%XS_bbhj_ratio(j)*t%lhc8%XS_bbH_SM(j)*t%BR_hjtautau(j) case(20140492) ! Insert correct xsection alias here ! fact(j)=t%lhc8%XS_gghj_ratio(j)*t%lhc8%XS_ggH_SM(j)*t%BR_hjtautau(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(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(6583) ! Data given in fb - (multiply by 1000) fact(j)=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((t%particle(Hneut)%M(ii)-125.0D0).lt.5.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) ! endif ! enddo case(14006) ! 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(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 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 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) case(2011026,11005,11016,11026,3478,3357,2011148,2012016) case(110212) case(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(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) case(13018) case(2013011,3244) case(2011112) case(6583,14006) case(2011135) case(6224,6225,6226) 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 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 double precision,allocatable :: massj(:),massi(:) 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(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) * & & 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(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(140062) 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) 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(140062) axis_i=t%particle( S95_t2(c)%particle_x2 )%GammaTot(i) / & & t%particle( S95_t2(c)%particle_x2 )%M(i) case default stop'Problem in subroutine calcfact_t2 (y1)' 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) !******************************************************** implicit none !--------------------------------------input double precision :: x !-----------------------------------function double precision :: test_appl !------------------------------------------- select case(S95_t2(c)%id) case(150,160,180,190,200,210,220,230,240,3381,3382,13032,14013) 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(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=1) :: j character(LEN=45) :: label character(LEN=200):: descrip !------------------------------------------- if(jj.ne.0)then write(j,'(I1)')jj 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) descrip=' t->(H'//j//'+)b->tau nu b ' //label case(1269,1270,2011094,13035) descrip=' t->(H'//j//'+)b->(c s) 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(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(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(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(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(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) descrip=' (p p)->h'//j//'/VBF/Wh'//j//'/Zh'//j//'/tth'//j//'->gamma 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) descrip=' (p p)->bbh'//j//'->tau tau ' //label case(20140492) 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) 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 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=1) :: j,i character(LEN=45) :: label character(LEN=200):: descrip !------------------------------------------- if((ii.ne.0).and.(jj.ne.0))then write(i,'(I1)')ii write(j,'(I1)')jj 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(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) descrip=' (p p)->h'//j//'->h'//i//' h'//i//'->gamma gamma b b, where h'//i//' lies around 125 GeV '//label case(14013) descrip=' (p p)->h'//j//'->h'//i//' h'//i//'->b b b b, where h'//i//' lies around 125 GeV '//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(140062) descrip=' (p p)->h'//j//'/VBF/Wh'//j//'/Zh'//j//'/tth'//j//'->gamma gamma (including widths effects)' //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 use theory_BRfunctions use theory_XS_SM_functions implicit none !--------------------------------------input type(dataset) :: t integer :: id,j !-----------------------------------internal integer :: ns,nb,n !--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 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) !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(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(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) 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) 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(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 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_KW/makefile.in =================================================================== --- trunk/HiggsBounds_KW/makefile.in (revision 508) +++ trunk/HiggsBounds_KW/makefile.in (revision 509) @@ -1,125 +1,125 @@ CHISQMODS = extra_bits_for_chisquared.MOD MODS = usefulbits.mod store_pathname.mod \ S95tables_type1.MOD S95tables_type2.MOD\ S95tables_type3.MOD \ interpolate.mod \ theory_colliderSfunctions.MOD theory_XS_SM_functions.MOD theory_BRfunctions.MOD \ likelihoods.MOD S95tables.mod \ PDGnumbering.mod string_manip.mod SLHA_manip.mod \ extra_bits_for_SLHA.mod \ extra_bits_for_web.MOD\ $(USECHISQMODS) \ input.MOD channels.MOD output.MOD theo_manip.mod \ tempMODS = $(MODS:.mod=.o) OBJSbasic = $(tempMODS:.MOD=.o) OBJScommandline = $(OBJSbasic) \ HiggsBounds.o OBJSsubroutines = $(OBJSbasic) \ HiggsBounds_subroutines.o access_SM.o .SUFFIXES: .exe .o .mod .f90 .F .F90 .MOD #as advised in http://gcc.gnu.org/wiki/GfortranFAQ %.o : %.mod default: HiggsBounds .f90.mod: $(F90C) $(F90FLAGS) $(ADDITIONALDEFINE) -c $< -o $*.o .f90.o: $(F90C) $(F90FLAGS) $(ADDITIONALDEFINE) -c $< -o $*.o .F90.MOD: $(F90C) $(F90FLAGS) $(ADDITIONALDEFINE) -c $< -o $*.o .F90.o: $(F90C) $(F90FLAGS) $(ADDITIONALDEFINE) -c $< -o $*.o .F.o: $(F77C) -c $< -o $*.o .mod.o: $(F90C) $(F90FLAGS) -c $*.f90 -o $*.o .MOD.o: $(F90C) $(F90FLAGS) -c $*.F90 -o $*.o HiggsBounds: HBwithSLHA libHB.a $(MODS) $(OBJScommandline) $(OBJSsubroutines) $(F90C) $(F90FLAGS) $(OBJScommandline) -o $(EXE) $(HBLIBS) $(F90C) $(F90FLAGS) AllAnalyses.F90 -o AllAnalyses $(HBLIBS) rm -f Expt_tables/S95_t1.binary rm -f Expt_tables/S95_t2.binary rm -f Theory_tables/BRSM.binary touch Expt_tables/S95_t1.binary touch Expt_tables/S95_t2.binary touch Expt_tables/CMS_tautau_llh_1408.3316.binary touch Theory_tables/BRSM.binary libHB: $(MODS) $(OBJSsubroutines) ar -rv libHB.a $(OBJSsubroutines) ranlib libHB.a rm -f Expt_tables/S95_t1.binary rm -f Expt_tables/S95_t2.binary rm -f Theory_tables/BRSM.binary touch Expt_tables/S95_t1.binary touch Expt_tables/S95_t2.binary touch Expt_tables/CMS_tautau_llh_1408.3316.binary touch Theory_tables/BRSM.binary libHB.a: libHB HBwithFH: libHB.a $(F90C) $(F90FLAGS) $(FHINCLUDE) example_programs/HBwithFH.F -o example_programs/HBwithFH $(FHLIBS) $(HBLIBS) $(F90C) $(F90FLAGS) $(FHINCLUDE) example_programs/HBwithFH_dm.F -o example_programs/HBwithFH_dm $(FHLIBS) $(HBLIBS) $(F90C) $(F90FLAGS) $(FHINCLUDE) example_programs/HBSLHAinputblocksfromFH_extras.F example_programs/HBSLHAinputblocksfromFH.F90 -o example_programs/HBSLHAinputblocksfromFH $(FHLIBS) $(HBLIBS) HBwithCPsuperH: libHB.a $(F77C) example_programs/HBwithCPsuperH.f -o example_programs/HBwithCPsuperH $(CPSUPERHLIBS) $(HBLIBS) @echo 'now run ./HBwithCPsuperH < HBwithCPsuperH.input in the folder example_programs' HBweb: libHB.a HiggsBounds @echo 'check that WEBVERSION is defined' $(F90C) $(F90FLAGS) extract_SM_results_for_web.f90 -o extract_SM_results_for_web $(HBLIBS) HBwithSLHA: libHB.a $(F90C) $(F90FLAGS) example_programs/HBwithSLHA.F90 -o example_programs/HBwithSLHA $(HBLIBS) -HBwithLHCchisq: libHB.a - $(F90C) $(F90FLAGS) example_programs/HBwithLHCchisq.F90 -o example_programs/HBwithLHCchisq $(HBLIBS) +HBwithLHClikelihood: libHB.a + $(F90C) $(F90FLAGS) example_programs/HBwithLHClikelihood.F90 -o example_programs/HBwithLHClikelihood $(HBLIBS) HBchisq: libHB.a $(F90C) $(F90FLAGS) example_programs/HBchisq.F90 -o example_programs/HBchisq $(HBLIBS) $(F90C) $(F90FLAGS) example_programs/HBchisqwithSLHA.F90 -o example_programs/HBchisqwithSLHA $(HBLIBS) clean: rm -f *.o *.mod *.MOD *.a rm -f store_pathname.f90 hyperclean: rm -f *.o *.mod *.MOD *.a *~ rm -f example_programs/*~ rm -f store_pathname.f90 rm -f example_programs/HBwithFH rm -f example_programs/HBwithCPsuperH rm -f example_programs/example-SM_vs_4thGen rm -f extract_SM_results_for_web rm -f HiggsBounds # rm -f example_data/*results.dat # rm -f example_data/*Key.dat rm -f cs-ratios_sigma-bg-Hb/Tevatron*~ rm -f example_programs/example-4thGen-results.dat rm -f example_programs/example-SM-results.dat rm -f example_programs/Key.dat rm -f example_programs/HBwithCPsuperH_effC.f rm -f example_programs/HBwithFH_effC.F rm -f example_programs/debug_channels.txt rm -f example_programs/debug_predratio.txt rm -f README_old rm -f Expt_tables/*.binary Index: trunk/HiggsBounds_KW/usefulbits.f90 =================================================================== --- trunk/HiggsBounds_KW/usefulbits.f90 (revision 508) +++ trunk/HiggsBounds_KW/usefulbits.f90 (revision 509) @@ -1,969 +1,969 @@ ! This file is part of HiggsBounds ! -KW !****************************************************************** module usefulbits !****************************************************************** implicit none logical :: debug = .True. logical :: full_dmth_variation = .True. integer :: dmhsteps = 3 ! Mass uncertainties smaller than 0.1 GeV are not considered double precision :: small_mh = 0.1D0 logical :: run_HB_classic = .False. ! For the CMS likelihood extension integer :: using_likelihood = 0 ! For the LEP chisq extension: logical :: chisqcut_at_mumax = .False. character(LEN=5) :: whichanalyses character(LEN=4) :: whichinput character(LEN=7) :: inputmethod = 'subrout' - character(LEN=9),parameter :: vers='4.2.0' + character(LEN=9),parameter :: vers='4.2.1' integer :: n_additional character(len=100) :: 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 :: ms=0.105D0 double precision,parameter :: mc=1.27D0 double precision,parameter :: mbmb=4.20D0 double precision,parameter :: mmu=105.7D-3 double precision,parameter :: mtau=1.777D0 double precision,parameter :: MZ=91.1876D0 !PDG 2009 double precision,parameter :: MW=80.398D0 !PDG 2009 double precision,parameter :: GF=1.16637D-5 double precision,parameter :: pi=3.14159265358979323846264338328D0 double precision,parameter :: alphas=0.118D0 double precision,parameter :: small=1.0D-6 double precision,parameter :: vsmall=1.0D-16 double precision,parameter :: vvsmall=1.0D-100 type particledescriptions character(LEN=10) :: short character(LEN=30) :: long end type ! particle codes: (n.b. these are NOT pdg) integer,parameter :: not_a_particle = 0 integer,parameter :: Hneut = 1 !either Mhi, Mh2 or Mh3 (says nothing about CP properties) integer,parameter :: Hplus = 2 !single charged Higgs integer,parameter :: Chineut = 3 !either neutralino1, neutralino2, neutralino3 or neutralino4 integer,parameter :: Chiplus = 4 !either chargino1 or chargino2 integer :: np(0:4)=1 !e.g np(Hneut) holds number of neutral Higgs considered type(particledescriptions),allocatable :: pdesc(:) !for subroutine version-------------------- 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 used for HiggsSignals double precision, allocatable :: dM(:) ! Mass uncertainties (variation) used in HB 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_hjZ_ratio(:) double precision, allocatable :: XS_hjW_ratio(:) double precision, allocatable :: XS_hjb_ratio(:) double precision, allocatable :: XS_tthj_ratio(:) double precision, allocatable :: XS_vbf_ratio(:) double precision, allocatable :: XS_HZ_SM(:) double precision, allocatable :: XS_HW_SM(:) double precision, allocatable :: XS_H_SM(:) !double precision, allocatable :: XS_H_SM_9713(:),XS_H_SM_9674(:) double precision, allocatable :: XS_ttH_SM(:) 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(:),XS_Hb_c1_SM(:),XS_Hb_c2_SM(:) double precision, allocatable :: XS_Hb_c3_SM(:),XS_Hb_c4_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_hjmumu(:),BR_hjtautau(:) double precision, allocatable :: BR_hjinvisible(:) double precision, allocatable :: BR_hjhihi(:,:) 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_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 ! NEW(24/09/2014, TS): double precision, allocatable :: gg_hj_ratio(:) double precision, allocatable :: bb_hj_ratio(:) double precision, allocatable :: BR_Hbb_SM(:),BR_Hcc_SM(:), BR_Hss_SM(:),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(:) 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(:) 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 :: 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(:) !------------------------------------------- contains subroutine HiggsBounds_info implicit none write(*,*) write(*,*)"~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~" write(*,*)"~ ~" write(*,*)"~ HiggsBounds "//adjustl(vers)//" ~" write(*,*)"~ ~" write(*,*)"~ Philip Bechtle, Oliver Brein, Sven Heinemeyer, ~" write(*,*)"~ Oscar Stål, Tim Stefaniak, Georg Weiglein, ~" write(*,*)"~ Karina E. Williams ~" write(*,*)"~ ~" write(*,*)"~ arXiv:0811.4169, arXiv:1102.1898, ~" write(*,*)"~ arXiv:1301.2345, arXiv:1311.0055 ~" 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(*,*)" * TeV4LHC Higgs Working Group report" write(*,*)" (see arXiv:hep-ph/0612172 and ref. therein)" write(*,*)" * LHC Higgs Cross Section Working Group" write(*,*)" (arXiv:1101.0593, arXiv:1201.3084 and ref. therein)" write(*,*) end subroutine HiggsBounds_info !********************************************************** function div(a,b,divlimit,div0res) !********************************************************** ! be careful about using this - not a mathematical limit double precision :: div !--------------------------------------input double precision :: a,b,divlimit,div0res !-----------------------------------internal double precision :: small1,small2 !------------------------------------------- small1 = 1.0D-28 small2 = 1.0D-20 if(abs(b).gt.small1)then div=a/b elseif(abs(a).lt.small2)then div=divlimit if(div.lt.0)stop 'error type divA (see function div in module usefulbits)' else div=div0res if(div.lt.0)stop 'error type divB (see function div in module usefulbits)' endif end function !--TESTING !********************************************************** subroutine iselementofarray(value, array, output) !********************************************************** implicit none !-------------------------------------input and output double precision, intent(in) :: value double precision, allocatable, dimension(:), intent(in) :: array integer, intent(out) :: output !---------------------------------------------internal integer :: i double precision :: small !----------------------------------------------------- small = 1.0D-20 output = -1 if(allocated(array)) then do i=lbound(array,dim=1),ubound(array,dim=1) if(abs(value-array(i)).le.small) output = 1 enddo else stop'error: Passing an unallocated array to subroutine iselementofarray!' endif end subroutine iselementofarray !---- !********************************************************** subroutine fill_pdesc !********************************************************** integer :: x if(ubound(np,dim=1).ne.4)stop'error: have made a mistake in subroutine fill_pdesc (1)' x=0 allocate( pdesc( ubound(np,dim=1) ) ) x=x+1 pdesc(x)%short='h' pdesc(x)%long ='neutral Higgs boson' x=x+1 pdesc(x)%short='hplus' pdesc(x)%long ='charged Higgs boson' x=x+1 pdesc(x)%short='N' pdesc(x)%long ='neutralino' x=x+1 pdesc(x)%short='C' pdesc(x)%long ='chargino' if(x.ne.ubound(np,dim=1))stop'error: have made a mistake in subroutine fill_pdesc (2)' end subroutine fill_pdesc !********************************************************** subroutine allocate_dataset_parts(d,n_addit) !********************************************************** implicit none !------------------------------------------- type(dataset) :: d(:) !--------------------------------------input integer, intent(in) :: n_addit !-----------------------------------internal integer :: n_add,x,y integer, allocatable :: np_t(:) !------------------------------------------- allocate(np_t(lbound(np,dim=1):ubound(np,dim=1))) np_t=np do x=lbound(np_t,dim=1),ubound(np_t,dim=1) if(np(x)>0)then np_t(x)=np(x) elseif(np(x).eq.0)then np_t(x)=1 else write(*,*)'np=',np stop'error in subroutine allocate_dataset_parts (1)' endif enddo if(n_addit>0)then n_add=n_addit elseif(n_addit.eq.0)then n_add=1 else stop'error in subroutine allocate_dataset_parts (2)' endif do x=lbound(d,dim=1),ubound(d,dim=1) allocate(d(x)%additional(n_add)) allocate(d(x)%particle( ubound(np_t,dim=1) )) do y= 1,ubound(np_t,dim=1) allocate(d(x)%particle(y)%M( np_t(y) )) allocate(d(x)%particle(y)%Mc( np_t(y) )) allocate(d(x)%particle(y)%GammaTot( np_t(y) )) allocate(d(x)%particle(y)%dM( np_t(y) )) allocate(d(x)%particle(y)%dMh( np_t(y) )) enddo allocate(d(x)%lep%XS_hjZ_ratio( np_t(Hneut) )) allocate(d(x)%lep%XS_bbhj_ratio( np_t(Hneut) )) allocate(d(x)%lep%XS_tautauhj_ratio( np_t(Hneut) )) allocate(d(x)%lep%XS_hjhi_ratio( np_t(Hneut),np_t(Hneut) )) allocate(d(x)%lep%XS_HpjHmj_ratio( np_t(Hplus) )) allocate(d(x)%lep%XS_CpjCmj( np_t(Chiplus) )) allocate(d(x)%lep%XS_NjNi( np_t(Chineut),np_t(Chineut) )) allocate(d(x)%BR_hjss( np_t(Hneut) )) allocate(d(x)%BR_hjcc( np_t(Hneut) )) allocate(d(x)%BR_hjbb( np_t(Hneut) )) allocate(d(x)%BR_hjmumu( np_t(Hneut) )) allocate(d(x)%BR_hjtautau( np_t(Hneut) )) allocate(d(x)%BR_hjhihi( np_t(Hneut),np_t(Hneut) )) 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_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_CjqqNi( np_t(Chiplus),np_t(Chineut) )) allocate(d(x)%BR_CjlnuNi( np_t(Chiplus),np_t(Chineut) )) allocate(d(x)%BR_CjWNi( np_t(Chiplus),np_t(Chineut) )) allocate(d(x)%BR_NjqqNi( np_t(Chineut),np_t(Chineut) )) allocate(d(x)%BR_NjZNi( np_t(Chineut),np_t(Chineut) )) allocate(d(x)%tev%XS_hjb_ratio( np_t(Hneut) )) allocate(d(x)%tev%XS_tthj_ratio( np_t(Hneut) )) allocate(d(x)%tev%XS_vbf_ratio( np_t(Hneut) )) allocate(d(x)%tev%XS_hjZ_ratio( np_t(Hneut) )) allocate(d(x)%tev%XS_hjW_ratio( np_t(Hneut) )) allocate(d(x)%tev%XS_hj_ratio( np_t(Hneut) )) allocate(d(x)%lhc7%XS_hjb_ratio( np_t(Hneut) )) allocate(d(x)%lhc7%XS_tthj_ratio( np_t(Hneut) )) allocate(d(x)%lhc7%XS_vbf_ratio( np_t(Hneut) )) allocate(d(x)%lhc7%XS_hjZ_ratio( np_t(Hneut) )) allocate(d(x)%lhc7%XS_hjW_ratio( np_t(Hneut) )) allocate(d(x)%lhc7%XS_hj_ratio( np_t(Hneut) )) allocate(d(x)%lhc8%XS_hjb_ratio( np_t(Hneut) )) allocate(d(x)%lhc8%XS_tthj_ratio( np_t(Hneut) )) allocate(d(x)%lhc8%XS_vbf_ratio( np_t(Hneut) )) allocate(d(x)%lhc8%XS_hjZ_ratio( np_t(Hneut) )) allocate(d(x)%lhc8%XS_hjW_ratio( np_t(Hneut) )) allocate(d(x)%lhc8%XS_hj_ratio( np_t(Hneut) )) allocate(d(x)%gg_hj_ratio( np_t(Hneut) )) allocate(d(x)%bb_hj_ratio( np_t(Hneut) )) allocate(d(x)%CP_value( np_t(Hneut) )) do y= 1,ubound(np_t,dim=1) d(x)%particle(y)%M =-1.0D0 d(x)%particle(y)%Mc =-1.0D0 d(x)%particle(y)%GammaTot =0.0D0 d(x)%particle(y)%dM =0.0D0 d(x)%particle(y)%dMh =0.0D0 enddo d(x)%lep%XS_hjZ_ratio =0.0D0 d(x)%lep%XS_bbhj_ratio =0.0D0 d(x)%lep%XS_tautauhj_ratio =0.0D0 d(x)%lep%XS_hjhi_ratio =0.0D0 d(x)%lep%XS_HpjHmj_ratio =0.0D0 d(x)%lep%XS_CpjCmj =0.0D0 d(x)%lep%XS_NjNi =0.0D0 d(x)%BR_hjss =0.0D0 d(x)%BR_hjcc =0.0D0 d(x)%BR_hjbb =0.0D0 d(x)%BR_hjmumu =0.0D0 d(x)%BR_hjtautau =0.0D0 d(x)%BR_hjhihi =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_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_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)%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)%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)%gg_hj_ratio = -1.0D0 d(x)%bb_hj_ratio = -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_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_Hb_SM( np_t(Hneut) )) allocate(d(x)%tev%XS_Hb_c1_SM( np_t(Hneut) )) allocate(d(x)%tev%XS_Hb_c2_SM( np_t(Hneut) )) allocate(d(x)%tev%XS_Hb_c3_SM( np_t(Hneut) )) allocate(d(x)%tev%XS_Hb_c4_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_HZ_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_HW_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_H_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_ttH_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_vbf_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_Hb_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_Hb_c1_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_Hb_c2_SM( np_t(Hneut) )) allocate(d(x)%lhc7%XS_Hb_c3_SM( np_t(Hneut) )) allocate(d(x)%lhc8%XS_HZ_SM( np_t(Hneut) )) allocate(d(x)%lhc8%XS_HW_SM( np_t(Hneut) )) allocate(d(x)%lhc8%XS_H_SM( np_t(Hneut) )) allocate(d(x)%lhc8%XS_ttH_SM( np_t(Hneut) )) allocate(d(x)%lhc8%XS_vbf_SM( np_t(Hneut) )) allocate(d(x)%lhc8%XS_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)%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_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 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_hjmumu) deallocate(theo(x)%BR_hjtautau) deallocate(theo(x)%BR_hjhihi) 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_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)%lhc7%XS_hjb_ratio) deallocate(theo(x)%lhc7%XS_tthj_ratio) deallocate(theo(x)%lhc7%XS_vbf_ratio) deallocate(theo(x)%lhc7%XS_hjZ_ratio) deallocate(theo(x)%lhc7%XS_hjW_ratio) deallocate(theo(x)%lhc7%XS_hj_ratio) deallocate(theo(x)%lhc8%XS_hjb_ratio) deallocate(theo(x)%lhc8%XS_tthj_ratio) deallocate(theo(x)%lhc8%XS_vbf_ratio) deallocate(theo(x)%lhc8%XS_hjZ_ratio) deallocate(theo(x)%lhc8%XS_hjW_ratio) deallocate(theo(x)%lhc8%XS_hj_ratio) !deallocate(theo(x)%inLEPrange_Hpj) !deallocate(theo(x)%inTEVrange_Hpj) deallocate(theo(x)%CP_value) enddo select case(whichanalyses) case('onlyH','LandH','onlyP','list ') do x=lbound(theo,dim=1),ubound(theo,dim=1) deallocate(theo(x)%BR_Hbb_SM) deallocate(theo(x)%BR_Hss_SM) deallocate(theo(x)%BR_Hcc_SM) deallocate(theo(x)%BR_Hmumu_SM) deallocate(theo(x)%BR_Htautau_SM) deallocate(theo(x)%BR_HWW_SM) deallocate(theo(x)%BR_HZZ_SM) deallocate(theo(x)%BR_HZga_SM) deallocate(theo(x)%BR_Hgaga_SM) deallocate(theo(x)%BR_Hgg_SM) deallocate(theo(x)%BR_Hjets_SM) deallocate(theo(x)%GammaTot_SM) deallocate(theo(x)%tev%XS_HZ_SM) deallocate(theo(x)%tev%XS_HW_SM) deallocate(theo(x)%tev%XS_H_SM) deallocate(theo(x)%tev%XS_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_Hb_SM) deallocate(theo(x)%tev%XS_Hb_c1_SM) deallocate(theo(x)%tev%XS_Hb_c2_SM) deallocate(theo(x)%tev%XS_Hb_c3_SM) deallocate(theo(x)%tev%XS_Hb_c4_SM) deallocate(theo(x)%lhc7%XS_HZ_SM) deallocate(theo(x)%lhc7%XS_HW_SM) deallocate(theo(x)%lhc7%XS_H_SM) deallocate(theo(x)%lhc7%XS_ttH_SM) deallocate(theo(x)%lhc7%XS_vbf_SM) deallocate(theo(x)%lhc7%XS_Hb_SM) deallocate(theo(x)%lhc7%XS_Hb_c1_SM) deallocate(theo(x)%lhc7%XS_Hb_c2_SM) deallocate(theo(x)%lhc7%XS_Hb_c3_SM) deallocate(theo(x)%lhc8%XS_HZ_SM) deallocate(theo(x)%lhc8%XS_HW_SM) deallocate(theo(x)%lhc8%XS_H_SM) deallocate(theo(x)%lhc8%XS_ttH_SM) deallocate(theo(x)%lhc8%XS_vbf_SM) deallocate(theo(x)%lhc8%XS_Hb_SM) deallocate(theo(x)%lhc8%XS_Hb_c1_SM) deallocate(theo(x)%lhc8%XS_Hb_c2_SM) deallocate(theo(x)%lhc8%XS_Hb_c3_SM) 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)%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) !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) end subroutine deallocate_usefulbits !********************************************************** end module usefulbits !****************************************************************** Index: trunk/HiggsBounds_KW/example_data/SLHA_example.in.fh-for-comparison =================================================================== --- trunk/HiggsBounds_KW/example_data/SLHA_example.in.fh-for-comparison (revision 508) +++ trunk/HiggsBounds_KW/example_data/SLHA_example.in.fh-for-comparison (revision 509) @@ -1,617 +1,617 @@ BLOCK SPINFO 1 FeynHiggs 2 2.8.6 2 built on Feb 23, 2012 BLOCK MODSEL 1 1 # Model 3 0 # Content 4 0 # RPV 5 2 # CPV 6 1 # FV BLOCK SMINPUTS 1 1.27901376E+02 # invAlfaMZ 2 1.16639000E-05 # GF 3 1.18900000E-01 # AlfasMZ 4 9.11876000E+01 # MZ 5 4.20000000E+00 # Mb 6 1.70900000E+02 # Mt 7 1.77700000E+00 # Mtau 8 0.00000000E+00 # Mnu3 11 5.10998902E-04 # Me 13 1.05658357E-01 # Mmu 14 0.00000000E+00 # Mnu2 21 4.74979987E-03 # Md 22 2.39989777E-03 # Mu 23 1.03995618E-01 # Ms 24 1.27005988E+00 # Mc BLOCK MINPAR 1 7.00000000E+01 # M0 2 2.50000000E+02 # M12 3 1.00000000E+01 # TB 4 1.00000000E+00 # signMUE 5 -3.00000000E+02 # A BLOCK EXTPAR 1 1.01588682E+02 # M1 2 1.91725499E+02 # M2 3 6.08795158E+02 # M3 23 3.91278023E+02 # MUE 25 1.00000000E+01 # TB 26 4.22260295E+02 # MA0 27 4.29844891E+02 # MHp BLOCK MASS 1000012 5.42432419E+02 # MSf(1,1,1) 2000012 1.00000000+123 # MSf(2,1,1) 1000011 5.27800378E+02 # MSf(1,2,1) 2000011 5.48240664E+02 # MSf(2,2,1) 1000002 4.50898064E+02 # MSf(1,3,1) 2000002 5.27010604E+02 # MSf(2,3,1) 1000001 5.12847420E+02 # MSf(1,4,1) 2000001 5.26644471E+02 # MSf(2,4,1) 1000014 5.42342390E+02 # MSf(1,1,2) 2000014 1.00000000+123 # MSf(2,1,2) 1000013 5.27790571E+02 # MSf(1,2,2) 2000013 5.48158715E+02 # MSf(2,2,2) 1000004 5.27011376E+02 # MSf(1,3,2) 2000004 5.29942182E+02 # MSf(2,3,2) 1000003 5.26652457E+02 # MSf(1,4,2) 2000003 5.43742271E+02 # MSf(2,4,2) 1000016 4.86206932E+02 # MSf(1,1,3) 2000016 1.00000000+123 # MSf(2,1,3) 1000015 4.91187612E+02 # MSf(1,2,3) 2000015 5.24998444E+02 # MSf(2,2,3) 1000006 5.43531521E+02 # MSf(1,3,3) 2000006 5.43553115E+02 # MSf(2,3,3) 1000005 5.49345223E+02 # MSf(1,4,3) 2000005 5.49423459E+02 # MSf(2,4,3) 24 8.03939083E+01 # MW 25 1.03813118E+02 # Mh0 35 4.22805456E+02 # MHH 36 4.22260295E+02 # MA0 37 4.30281710E+02 # MHp 1000022 9.90912459E+01 # MNeu(1) 1000023 1.78719573E+02 # MNeu(2) 1000025 3.97233707E+02 # MNeu(3) 1000035 4.12737069E+02 # MNeu(4) 1000024 1.78326861E+02 # MCha(1) 1000037 4.13500225E+02 # MCha(2) 1000021 6.08795158E+02 # MGl BLOCK DMASS 0 1.70900000E+02 # Q 25 6.43742159E-01 # Delta Mh0 35 1.31037820E-02 # Delta MHH 36 0.00000000E+00 # Delta MA0 37 6.44427318E-02 # Delta MHp BLOCK NMIX 1 1 9.89279920E-01 # ZNeu(1,1) 1 2 -4.98194108E-02 # ZNeu(1,2) 1 3 1.29784175E-01 # ZNeu(1,3) 1 4 -4.47139079E-02 # ZNeu(1,4) 2 1 8.63477380E-02 # ZNeu(2,1) 2 2 9.56521337E-01 # ZNeu(2,2) 2 3 -2.45903773E-01 # ZNeu(2,3) 2 4 1.30928741E-01 # ZNeu(2,4) 3 1 -0.00000000E+00 # ZNeu(3,1) 3 2 0.00000000E+00 # ZNeu(3,2) 3 3 0.00000000E+00 # ZNeu(3,3) 3 4 0.00000000E+00 # ZNeu(3,4) 4 1 -1.04158789E-01 # ZNeu(4,1) 4 2 2.73908229E-01 # ZNeu(4,2) 4 3 6.61143128E-01 # ZNeu(4,3) 4 4 -6.90662720E-01 # ZNeu(4,4) BLOCK IMNMIX 1 1 0.00000000E+00 # ZNeu(1,1) 1 2 0.00000000E+00 # ZNeu(1,2) 1 3 0.00000000E+00 # ZNeu(1,3) 1 4 0.00000000E+00 # ZNeu(1,4) 2 1 0.00000000E+00 # ZNeu(2,1) 2 2 0.00000000E+00 # ZNeu(2,2) 2 3 0.00000000E+00 # ZNeu(2,3) 2 4 0.00000000E+00 # ZNeu(2,4) 3 1 -5.49568398E-02 # ZNeu(3,1) 3 2 8.69438946E-02 # ZNeu(3,2) 3 3 6.96833672E-01 # ZNeu(3,3) 3 4 7.09819230E-01 # ZNeu(3,4) 4 1 0.00000000E+00 # ZNeu(4,1) 4 2 0.00000000E+00 # ZNeu(4,2) 4 3 0.00000000E+00 # ZNeu(4,3) 4 4 0.00000000E+00 # ZNeu(4,4) BLOCK UMIX 1 1 9.34037600E-01 # UCha(1,1) 1 2 -3.57174695E-01 # UCha(1,2) 2 1 3.57174695E-01 # UCha(2,1) 2 2 9.34037600E-01 # UCha(2,2) BLOCK VMIX 1 1 9.81558277E-01 # VCha(1,1) 1 2 -1.91163149E-01 # VCha(1,2) 2 1 1.91163149E-01 # VCha(2,1) 2 2 9.81558277E-01 # VCha(2,2) BLOCK STAUMIX 1 1 9.78374358E-01 # USf(1,1) 1 2 2.06842007E-01 # USf(1,2) 2 1 -2.06842007E-01 # USf(2,1) 2 2 9.78374358E-01 # USf(2,2) BLOCK ALPHA -1.10540416E-01 # Alpha BLOCK DALPHA 1.25922215E-03 # Delta Alpha BLOCK HMIX Q= 0.44521862E+03 1 3.91278023E+02 # MUE 2 9.76777715E+00 # TB 3 2.45089026E+02 # VEV 4 1.85471084E+05 # MA02 BLOCK GAUGE Q= 0.44521862E+03 1 3.60955562E-01 # g1 2 6.46217952E-01 # g2 3 1.10396753E+00 # g3 BLOCK MSOFT Q= 0.44521862E+03 1 1.01588682E+02 # M1 2 1.91725499E+02 # M2 3 5.91258068E+02 # M3 21 2.55016944E+04 # MHd2 22 -1.54814302E+05 # MHu2 BLOCK YE Q= 0.44521862E+03 1 1 2.82142660E-05 # Yf(1,1) 2 2 5.83382097E-03 # Yf(2,2) 3 3 1.00955070E-01 # Yf(3,3) BLOCK YU Q= 0.44521862E+03 1 1 7.38440809E-06 # Yf(1,1) 2 2 3.35197318E-03 # Yf(2,2) 3 3 8.67457356E-01 # Yf(3,3) BLOCK YD Q= 0.44521862E+03 1 1 1.43553034E-04 # Yf(1,1) 2 2 3.14309854E-03 # Yf(2,2) 3 3 1.35721419E-01 # Yf(3,3) BLOCK VCKMIN 1 2.27200000E-01 # lambda 2 8.18000000E-01 # A 3 2.21000000E-01 # rhobar 4 3.40000000E-01 # etabar BLOCK VCKM Q= 0.44521862E+03 1 1 9.73840613E-01 # VCKM(1,1) 1 2 2.27197635E-01 # VCKM(1,2) 1 3 3.96159999E-03 # VCKM(1,3) 2 1 -2.27161568E-01 # VCKM(2,1) 2 2 9.72955494E-01 # VCKM(2,2) 2 3 4.18954417E-02 # VCKM(2,3) 3 1 5.66408479E-03 # VCKM(3,1) 3 2 -4.16994059E-02 # VCKM(3,2) 3 3 9.99114146E-01 # VCKM(3,3) BLOCK UPMNS Q= 0.44521862E+03 1 1 1.00000000E+00 # UPMNS(1,1) 1 2 0.00000000E+00 # UPMNS(1,2) 1 3 0.00000000E+00 # UPMNS(1,3) 2 1 0.00000000E+00 # UPMNS(2,1) 2 2 1.00000000E+00 # UPMNS(2,2) 2 3 0.00000000E+00 # UPMNS(2,3) 3 1 0.00000000E+00 # UPMNS(3,1) 3 2 0.00000000E+00 # UPMNS(3,2) 3 3 1.00000000E+00 # UPMNS(3,3) BLOCK MSL2IN 1 1 2.98308190E+05 # MSL2(1,1) 2 2 2.98210529E+05 # MSL2(2,2) 3 3 2.40472441E+05 # MSL2(3,3) BLOCK MSE2IN 1 1 2.76757614E+05 # MSE2(1,1) 2 2 2.76755052E+05 # MSE2(2,2) 3 3 2.72334619E+05 # MSE2(3,3) BLOCK MSQ2IN 1 1 2.98308190E+05 # MSQ2(1,1) 1 2 1.34493695E+01 # MSQ2(1,2) 1 3 -3.28451218E+02 # MSQ2(1,3) 2 2 2.98210529E+05 # MSQ2(2,2) 2 3 2.41811273E+03 # MSQ2(2,3) 3 3 2.60796536E+05 # MSQ2(3,3) BLOCK MSU2IN 1 1 2.78951407E+05 # MSU2(1,1) 1 2 3.29233375E-09 # MSU2(1,2) 1 3 1.22326998E-05 # MSU2(1,3) 2 2 2.78949122E+05 # MSU2(2,2) 2 3 5.87671765E-02 # MSU2(2,3) 3 3 1.78079216E+05 # MSU2(3,3) BLOCK MSD2IN 1 1 2.76757614E+05 # MSD2(1,1) 1 2 -1.99959161E-06 # MSD2(1,2) 1 3 2.11783889E-03 # MSD2(1,3) 2 2 2.76755052E+05 # MSD2(2,2) 2 3 -3.41384084E-01 # MSD2(2,3) 3 3 2.93965343E+05 # MSD2(3,3) BLOCK MSL2 Q= 0.44521862E+03 1 1 3.31843120E+04 # MSL2(1,1) 1 2 0.00000000E+00 # MSL2(1,2) 1 3 0.00000000E+00 # MSL2(1,3) 2 1 0.00000000E+00 # MSL2(2,1) 2 2 3.31822180E+04 # MSL2(2,2) 2 3 0.00000000E+00 # MSL2(2,3) 3 1 0.00000000E+00 # MSL2(3,1) 3 2 0.00000000E+00 # MSL2(3,2) 3 3 3.25614936E+04 # MSL2(3,3) BLOCK MSE2 Q= 0.44521862E+03 1 1 1.34261802E+04 # MSE2(1,1) 1 2 0.00000000E+00 # MSE2(1,2) 1 3 0.00000000E+00 # MSE2(1,3) 2 1 0.00000000E+00 # MSE2(2,1) 2 2 1.34219369E+04 # MSE2(2,2) 2 3 0.00000000E+00 # MSE2(2,3) 3 1 0.00000000E+00 # MSE2(3,1) 3 2 0.00000000E+00 # MSE2(3,2) 3 3 1.21637447E+04 # MSE2(3,3) BLOCK MSQ2 Q= 0.44521862E+03 1 1 2.98308190E+05 # MSQ2(1,1) 1 2 1.34493695E+01 # MSQ2(1,2) 1 3 -3.15393416E+02 # MSQ2(1,3) 2 1 1.34493695E+01 # MSQ2(2,1) 2 2 2.98210529E+05 # MSQ2(2,2) 2 3 2.32197901E+03 # MSQ2(2,3) 3 1 -3.15393416E+02 # MSQ2(3,1) 3 2 2.32197901E+03 # MSQ2(3,2) 3 3 2.40472441E+05 # MSQ2(3,3) BLOCK MSU2 Q= 0.44521862E+03 1 1 2.78951407E+05 # MSU2(1,1) 1 2 3.29233375E-09 # MSU2(1,2) 1 3 1.17629375E-05 # MSU2(1,3) 2 1 3.29233375E-09 # MSU2(2,1) 2 2 2.78949122E+05 # MSU2(2,2) 2 3 5.65103888E-02 # MSU2(2,3) 3 1 1.17629375E-05 # MSU2(3,1) 3 2 5.65103888E-02 # MSU2(3,2) 3 3 1.64664574E+05 # MSU2(3,3) BLOCK MSD2 Q= 0.44521862E+03 1 1 2.76757614E+05 # MSD2(1,1) 1 2 -1.99959161E-06 # MSD2(1,2) 1 3 2.03843224E-03 # MSD2(1,3) 2 1 -1.99959161E-06 # MSD2(2,1) 2 2 2.76755052E+05 # MSD2(2,2) 2 3 -3.28584165E-01 # MSD2(2,3) 3 1 2.03843224E-03 # MSD2(3,1) 3 2 -3.28584165E-01 # MSD2(3,2) 3 3 2.72334619E+05 # MSD2(3,3) BLOCK TEIN 1 1 0.00000000E+00 # Tf(1,1) 2 2 0.00000000E+00 # Tf(2,2) 3 3 0.00000000E+00 # Tf(3,3) BLOCK TUIN 1 1 0.00000000E+00 # Tf(1,1) 1 2 0.00000000E+00 # Tf(1,2) 1 3 0.00000000E+00 # Tf(1,3) 2 1 0.00000000E+00 # Tf(2,1) 2 2 0.00000000E+00 # Tf(2,2) 2 3 0.00000000E+00 # Tf(2,3) 3 1 0.00000000E+00 # Tf(3,1) 3 2 0.00000000E+00 # Tf(3,2) 3 3 -9.14261235E+01 # Tf(3,3) BLOCK TDIN 1 1 0.00000000E+00 # Tf(1,1) 1 2 0.00000000E+00 # Tf(1,2) 1 3 0.00000000E+00 # Tf(1,3) 2 1 0.00000000E+00 # Tf(2,1) 2 2 0.00000000E+00 # Tf(2,2) 2 3 0.00000000E+00 # Tf(2,3) 3 1 0.00000000E+00 # Tf(3,1) 3 2 0.00000000E+00 # Tf(3,2) 3 3 3.77565710E+01 # Tf(3,3) BLOCK TE Q= 0.44521862E+03 1 1 -1.27342165E-02 # Tf(1,1) 1 2 0.00000000E+00 # Tf(1,2) 1 3 0.00000000E+00 # Tf(1,3) 2 1 0.00000000E+00 # Tf(2,1) 2 2 -2.63296676E+00 # Tf(2,2) 2 3 0.00000000E+00 # Tf(2,3) 3 1 0.00000000E+00 # Tf(3,1) 3 2 0.00000000E+00 # Tf(3,2) 3 3 -4.52134292E+01 # Tf(3,3) BLOCK TU Q= 0.44521862E+03 1 1 -6.13924282E-03 # Tf(1,1) 1 2 4.11510887E-09 # Tf(1,2) 1 3 5.65283279E-08 # Tf(1,3) 2 1 1.86795389E-06 # Tf(2,1) 2 2 -2.78673412E+00 # Tf(2,2) 2 3 2.71568059E-04 # Tf(2,3) 3 1 6.72118042E-03 # Tf(3,1) 3 2 7.11333196E-02 # Tf(3,2) 3 3 -5.15625634E+02 # Tf(3,3) BLOCK TD Q= 0.44521862E+03 1 1 -1.52844609E-01 # Tf(1,1) 1 2 -2.66352898E-06 # Tf(1,2) 1 3 6.29087963E-05 # Tf(1,3) 2 1 -5.83180654E-05 # Tf(2,1) 2 2 -3.34610909E+00 # Tf(2,2) 2 3 -1.01405553E-02 # Tf(2,3) 3 1 5.94923598E-02 # Tf(3,1) 3 2 -4.37991698E-01 # Tf(3,2) 3 3 -1.33211094E+02 # Tf(3,3) BLOCK SNUMIX 1 1 0.00000000E+00 # UASf(1,1) 1 2 0.00000000E+00 # UASf(1,2) 1 3 1.00000000E+00 # UASf(1,3) 2 1 0.00000000E+00 # UASf(2,1) 2 2 1.00000000E+00 # UASf(2,2) 2 3 0.00000000E+00 # UASf(2,3) 3 1 1.00000000E+00 # UASf(3,1) 3 2 0.00000000E+00 # UASf(3,2) 3 3 0.00000000E+00 # UASf(3,3) BLOCK SELMIX 1 1 0.00000000E+00 # UASf(1,1) 1 2 0.00000000E+00 # UASf(1,2) 1 3 3.11386769E-01 # UASf(1,3) 1 4 0.00000000E+00 # UASf(1,4) 1 5 0.00000000E+00 # UASf(1,5) 1 6 9.50283263E-01 # UASf(1,6) 2 1 0.00000000E+00 # UASf(2,1) 2 2 2.17472040E-02 # UASf(2,2) 2 3 0.00000000E+00 # UASf(2,3) 2 4 0.00000000E+00 # UASf(2,4) 2 5 9.99763502E-01 # UASf(2,5) 2 6 0.00000000E+00 # UASf(2,6) 3 1 1.05298774E-04 # UASf(3,1) 3 2 0.00000000E+00 # UASf(3,2) 3 3 0.00000000E+00 # UASf(3,3) 3 4 9.99999994E-01 # UASf(3,4) 3 5 0.00000000E+00 # UASf(3,5) 3 6 0.00000000E+00 # UASf(3,6) 4 1 9.99999994E-01 # UASf(4,1) 4 2 0.00000000E+00 # UASf(4,2) 4 3 0.00000000E+00 # UASf(4,3) 4 4 -1.05298774E-04 # UASf(4,4) 4 5 0.00000000E+00 # UASf(4,5) 4 6 0.00000000E+00 # UASf(4,6) 5 1 0.00000000E+00 # UASf(5,1) 5 2 9.99763502E-01 # UASf(5,2) 5 3 0.00000000E+00 # UASf(5,3) 5 4 0.00000000E+00 # UASf(5,4) 5 5 -2.17472040E-02 # UASf(5,5) 5 6 0.00000000E+00 # UASf(5,6) 6 1 0.00000000E+00 # UASf(6,1) 6 2 0.00000000E+00 # UASf(6,2) 6 3 9.50283263E-01 # UASf(6,3) 6 4 0.00000000E+00 # UASf(6,4) 6 5 0.00000000E+00 # UASf(6,5) 6 6 -3.11386769E-01 # UASf(6,6) BLOCK USQMIX 1 1 -1.66416304E-04 # UASf(1,1) 1 2 -9.47762242E-04 # UASf(1,2) 1 3 1.03586639E-01 # UASf(1,3) 1 4 -3.73412776E-10 # UASf(1,4) 1 5 -1.41808335E-06 # UASf(1,5) 1 6 9.94619959E-01 # UASf(1,6) 2 1 5.97658528E-06 # UASf(2,1) 2 2 2.85203746E-03 # UASf(2,2) 2 3 -7.52899044E-04 # UASf(2,3) 2 4 6.84439988E-07 # UASf(2,4) 2 5 9.99995646E-01 # UASf(2,5) 2 6 8.25573909E-05 # UASf(2,6) 3 1 5.30951920E-06 # UASf(3,1) 3 2 9.35655414E-09 # UASf(3,2) 3 3 -2.48894635E-07 # UASf(3,3) 3 4 1.00000000E+00 # UASf(3,4) 3 5 -6.84691012E-07 # UASf(3,5) 3 6 2.71933601E-08 # UASf(3,6) 4 1 -1.00589499E-02 # UASf(4,1) 4 2 -5.74937638E-02 # UASf(4,2) 4 3 9.92881829E-01 # UASf(4,3) 4 4 3.04512753E-07 # UASf(4,4) 4 5 9.20169728E-04 # UASf(4,5) 4 6 -1.03463304E-01 # UASf(4,6) 5 1 -5.62630635E-01 # UASf(5,1) 5 2 7.91356493E-01 # UASf(5,2) 5 3 3.77436520E-02 # UASf(5,3) 5 4 2.98733066E-06 # UASf(5,4) 5 5 -2.22356343E-03 # UASf(5,5) 5 6 -3.30455562E-03 # UASf(5,6) 6 1 7.92159625E-01 # UASf(6,1) 6 2 5.61288033E-01 # UASf(6,2) 6 3 4.01641054E-02 # UASf(6,3) 6 4 -4.20046271E-06 # UASf(6,4) 6 5 -1.57502755E-03 # UASf(6,5) 6 6 -3.51556809E-03 # UASf(6,6) BLOCK IMUSQMIX 1 1 1.41546330E-04 # UASf(1,1) 1 2 -4.41298604E-08 # UASf(1,2) 1 3 -4.10743574E-12 # UASf(1,3) 1 4 1.78573724E-10 # UASf(1,4) 1 5 -2.94636410E-11 # UASf(1,5) 1 6 -3.94367692E-11 # UASf(1,6) 2 1 -5.80998615E-06 # UASf(2,1) 2 2 -8.02450621E-12 # UASf(2,2) 2 3 6.24807665E-08 # UASf(2,3) 2 4 -6.70500885E-07 # UASf(2,4) 2 5 -2.98123669E-13 # UASf(2,5) 2 6 -6.78491986E-09 # UASf(2,6) 3 1 2.97944115E-12 # UASf(3,1) 3 2 9.09652596E-09 # UASf(3,2) 3 3 -2.12286109E-07 # UASf(3,3) 3 4 -3.38616232E-18 # UASf(3,4) 3 5 -6.70722346E-07 # UASf(3,5) 3 6 2.30518111E-08 # UASf(3,6) 4 1 8.57066127E-03 # UASf(4,1) 4 2 -5.31451869E-06 # UASf(4,2) 4 3 1.61779239E-07 # UASf(4,3) 4 4 -2.59806180E-07 # UASf(4,4) 4 5 8.52382873E-08 # UASf(4,5) 4 6 -1.68581491E-08 # UASf(4,6) 5 1 2.36125411E-01 # UASf(5,1) 5 2 1.86125002E-04 # UASf(5,2) 5 3 -2.43571506E-03 # UASf(5,3) 5 4 -1.25372685E-06 # UASf(5,4) 5 5 -5.22265197E-07 # UASf(5,5) 5 6 2.13253143E-04 # UASf(5,6) 6 1 -4.55324875E-05 # UASf(6,1) 6 2 2.35363644E-01 # UASf(6,2) 6 3 2.02791461E-02 # UASf(6,3) 6 4 2.40211712E-10 # UASf(6,4) 6 5 -6.60453747E-04 # UASf(6,5) 6 6 -1.77503557E-03 # UASf(6,6) BLOCK DSQMIX 1 1 8.33331693E-03 # UASf(1,1) 1 2 -6.13679337E-02 # UASf(1,2) 1 3 9.81034207E-01 # UASf(1,3) 1 4 1.00378906E-05 # UASf(1,4) 1 5 -1.62482433E-03 # UASf(1,5) 1 6 1.83667575E-01 # UASf(1,6) 2 1 2.46079998E-05 # UASf(2,1) 2 2 1.54119320E-02 # UASf(2,2) 2 3 2.45827923E-03 # UASf(2,3) 2 4 5.06510370E-05 # UASf(2,4) 2 5 9.99877833E-01 # UASf(2,5) 2 6 8.63313332E-04 # UASf(2,6) 3 1 7.09687921E-04 # UASf(3,1) 3 2 3.37274109E-07 # UASf(3,2) 3 3 -1.53155444E-05 # UASf(3,3) 3 4 9.99999747E-01 # UASf(3,4) 3 5 -5.06375764E-05 # UASf(3,5) 3 6 -5.38172726E-06 # UASf(3,6) 4 1 -9.76661600E-03 # UASf(4,1) 4 2 7.18149394E-02 # UASf(4,2) 4 3 -1.79117100E-01 # UASf(4,3) 4 4 9.36741587E-06 # UASf(4,4) 4 5 -1.51347496E-03 # UASf(4,5) 4 6 9.81153404E-01 # UASf(4,6) 5 1 9.91994300E-01 # UASf(5,1) 5 2 1.26262719E-01 # UASf(5,2) 5 3 -6.27838601E-04 # UASf(5,3) 5 4 -7.04155709E-04 # UASf(5,4) 5 5 -1.96946971E-03 # UASf(5,5) 5 6 5.15156029E-04 # UASf(5,6) 6 1 -1.25626324E-01 # UASf(6,1) 6 2 9.87368619E-01 # UASf(6,2) 6 3 7.40439895E-02 # UASf(6,3) 6 4 8.88563731E-05 # UASf(6,4) 6 5 -1.53462448E-02 # UASf(6,5) 6 6 -6.00267437E-02 # UASf(6,6) BLOCK CVHMIX 1 1 9.99998999E-01 # UH(1,1) 1 2 1.41462695E-03 # UH(1,2) 1 3 0.00000000E+00 # UH(1,3) 2 1 -1.41462695E-03 # UH(2,1) 2 2 9.99998999E-01 # UH(2,2) 2 3 0.00000000E+00 # UH(2,3) 3 1 0.00000000E+00 # UH(3,1) 3 2 0.00000000E+00 # UH(3,2) 3 3 1.00000000E+00 # UH(3,3) BLOCK PRECOBS 1 1.40644753E-04 # DeltaRho 2 8.03655708E+01 # MWMSSM 3 8.03576496E+01 # MWSM 4 2.31456873E-01 # SW2effMSSM 5 2.31500790E-01 # SW2effSM 11 7.82713616E-10 # gminus2mu 21 1.10645657E-38 # EDMeTh 22 -7.04901199E-31 # EDMn 23 -1.02163967E-32 # EDMHg 31 4.37904276E-04 # bsgammaMSSM 32 3.87978705E-04 # bsgammaSM 33 2.25281697E+01 # DeltaMsMSSM 34 2.19020592E+01 # DeltaMsSM DECAY 25 2.96801469E-03 # Gamma(h0) 1.39287672E-03 2 22 22 # BR(h0 -> photon photon) 1.39774658E-03 2 23 23 # BR(h0 -> Z Z) 1.46762297E-02 2 -24 24 # BR(h0 -> W W) 6.38353019E-02 2 21 21 # BR(h0 -> gluon gluon) 6.93428189E-09 2 -11 11 # BR(h0 -> Electron electron) 3.08431917E-04 2 -13 13 # BR(h0 -> Muon muon) 8.89079625E-02 2 -15 15 # BR(h0 -> Tau tau) 1.49603479E-07 2 -2 2 # BR(h0 -> Up up) 3.12528201E-02 2 -4 4 # BR(h0 -> Charm charm) 7.30783271E-07 2 -1 1 # BR(h0 -> Down down) 3.50974986E-04 2 -3 3 # BR(h0 -> Strange strange) 7.97876768E-01 2 -5 5 # BR(h0 -> Bottom bottom) DECAY 35 8.17659361E-01 # Gamma(HH) 6.43211339E-06 2 22 22 # BR(HH -> photon photon) 1.00971565E-03 2 23 23 # BR(HH -> Z Z) 2.18755271E-03 2 -24 24 # BR(HH -> W W) 6.64452989E-04 2 21 21 # BR(HH -> gluon gluon) 8.09299805E-09 2 -11 11 # BR(HH -> Electron electron) 3.60124030E-04 2 -13 13 # BR(HH -> Muon muon) 1.04192031E-01 2 -15 15 # BR(HH -> Tau tau) 1.75602189E-11 2 -2 2 # BR(HH -> Up up) 3.67161150E-06 2 -4 4 # BR(HH -> Charm charm) 7.04890681E-02 2 -6 6 # BR(HH -> Top top) 5.92884351E-07 2 -1 1 # BR(HH -> Down down) 2.84474967E-04 2 -3 3 # BR(HH -> Strange strange) 6.41613982E-01 2 -5 5 # BR(HH -> Bottom bottom) 7.15094306E-02 2 -1000024 1000024 # BR(HH -> Chargino1 chargino1) 1.52033932E-02 2 1000022 1000022 # BR(HH -> neutralino1 neutralino1) 5.44377566E-02 2 1000022 1000023 # BR(HH -> neutralino1 neutralino2) 2.85239341E-02 2 1000023 1000023 # BR(HH -> neutralino2 neutralino2) 9.51337997E-03 2 25 25 # BR(HH -> h0 h0) DECAY 36 1.19791912E+00 # Gamma(A0) 1.09108715E-05 2 22 22 # BR(A0 -> photon photon) 5.53166394E-04 2 21 21 # BR(A0 -> gluon gluon) 5.49761472E-09 2 -11 11 # BR(A0 -> Electron electron) 2.44634063E-04 2 -13 13 # BR(A0 -> Muon muon) 7.07854102E-02 2 -15 15 # BR(A0 -> Tau tau) 9.18020585E-12 2 -2 2 # BR(A0 -> Up up) 1.91952651E-06 2 -4 4 # BR(A0 -> Charm charm) 1.07023671E-01 2 -6 6 # BR(A0 -> Top top) 4.02906163E-07 2 -1 1 # BR(A0 -> Down down) 1.93320917E-04 2 -3 3 # BR(A0 -> Strange strange) 4.36179463E-01 2 -5 5 # BR(A0 -> Bottom bottom) 2.07718418E-01 2 -1000024 1000024 # BR(A0 -> Chargino1 chargino1) 1.52736662E-02 2 1000022 1000022 # BR(A0 -> neutralino1 neutralino1) 7.55739845E-02 2 1000022 1000023 # BR(A0 -> neutralino1 neutralino2) 8.45842902E-02 2 1000023 1000023 # BR(A0 -> neutralino2 neutralino2) 1.85673749E-03 2 23 25 # BR(A0 -> Z h0) 1.37386624E-27 2 25 25 # BR(A0 -> h0 h0) DECAY 37 7.43430718E-01 # Gamma(Hp) 9.57549338E-09 2 -11 12 # BR(Hp -> Electron nu_e) 4.09382129E-04 2 -13 14 # BR(Hp -> Muon nu_mu) 1.15792723E-01 2 -15 16 # BR(Hp -> Tau nu_tau) 6.16559917E-07 2 -1 2 # BR(Hp -> Down up) 3.00895278E-04 2 -3 4 # BR(Hp -> Strange charm) 7.13088181E-01 2 -5 6 # BR(Hp -> Bottom top) 1.64482067E-01 2 1000022 1000024 # BR(Hp -> neutralino1 chargino1) 9.84904880E-04 2 1000023 1000024 # BR(Hp -> neutralino2 chargino1) 3.33791233E-03 2 -25 24 # BR(Hp -> H0 W) 4.21458828E-08 2 -35 24 # BR(Hp -> HH W) 5.94771110E-08 2 -36 24 # BR(Hp -> A0 W) DECAY 6 1.30853975E+00 # Gamma(top) 1.00000000E+00 2 5 24 # BR(top -> bottom W) # Block HiggsBoundsInputHiggsCouplingsBosons # For exact definitions of NormEffCoupSq see HiggsBounds manual 1.01949 3 25 24 24 # higgs-W-W effective coupling^2, normalised to SM 0.867109E-04 3 35 24 24 # higgs-W-W effective coupling^2, normalised to SM 0.00000 3 36 24 24 # higgs-W-W effective coupling^2, normalised to SM 1.01949 3 25 23 23 # higgs-Z-Z effective coupling^2, normalised to SM 0.867109E-04 3 35 23 23 # higgs-Z-Z effective coupling^2, normalised to SM 0.00000 3 36 23 23 # higgs-Z-Z effective coupling^2, normalised to SM 1.05240 3 25 21 21 # higgs-gluon-gluon effective coupling^2, normalised to SM 0.226638E-01 3 35 21 21 # higgs-gluon-gluon effective coupling^2, normalised to SM 0.319097E-01 3 36 21 21 # higgs-gluon-gluon effective coupling^2, normalised to SM 0.00000 3 25 25 23 # higgs-higgs-Z effective coupling^2, normalised 0.00000 3 35 25 23 # higgs-higgs-Z effective coupling^2, normalised 0.00000 3 35 35 23 # higgs-higgs-Z effective coupling^2, normalised 0.120574E-03 3 36 25 23 # higgs-higgs-Z effective coupling^2, normalised 0.939291 3 36 35 23 # higgs-higgs-Z effective coupling^2, normalised 0.00000 3 36 36 23 # higgs-higgs-Z effective coupling^2, normalised 0.00000 4 25 21 21 23 # higgs-gluon-gluon-Z effective coupling^2, normalised to SM 0.00000 4 35 21 21 23 # higgs-gluon-gluon-Z effective coupling^2, normalised to SM 0.00000 4 36 21 21 23 # higgs-gluon-gluon-Z effective coupling^2, normalised to SM # Block HiggsBoundsInputHiggsCouplingsFermions # For exact definitions of NormEffCoupSq see HiggsBounds manual # ScalarNormEffCoupSq PseudoSNormEffCoupSq NP IP1 IP2 IP3 # Scalar, Pseudoscalar Normalised Effective Coupling Squared 1.2443413561648986 9.57682230477937397E-029 3 25 5 5 # higgs-b-b eff. coupling^2, normalised to SM 87.034668435793236 7.46049313153695784E-025 3 35 5 5 # higgs-b-b eff. coupling^2, normalised to SM 7.41372099785478173E-025 86.660349517852111 3 36 5 5 # higgs-b-b eff. coupling^2, normalised to SM 1.0171928578152249 0.0000000000000000 3 25 6 6 # higgs-top-top eff. coupling^2, normalised to SM 1.20030882191280511E-002 0.0000000000000000 3 35 6 6 # higgs-top-top eff. coupling^2, normalised to SM 0.0000000000000000 1.00000000000000019E-002 3 36 6 6 # higgs-top-top eff. coupling^2, normalised to SM 1.2619205607734942 0.0000000000000000 3 25 15 15 # higgs-tau-tau eff. coupling^2, normalised to SM 100.44567808130832 0.0000000000000000 3 35 15 15 # higgs-tau-tau eff. coupling^2, normalised to SM 0.0000000000000000 100.00000000000000 3 36 15 15 # higgs-tau-tau eff. coupling^2, normalised to SM Block HiggsBoundsResults # results from HiggsBounds http://projects.hepforge.org/higgsbounds # HBresult : scenario allowed flag (1: allowed, 0: excluded, -1: unphysical) # chan id number: most sensitive channel (see below). chan=0 if no channel applies # obsratio : ratio [sig x BR]_model/[sig x BR]_limit (<1: allowed, >1: excluded) # ncomb : number of Higgs bosons combined in most sensitive channel # Note that the HB channel id number varies depending on the HB version and setting "whichanalyses" # - 0 4.2.0 ||LandH|| # version of HB used to produce these results,the HB setting "whichanalyses" + 0 4.2.1 ||LandH|| # version of HB used to produce these results,the HB setting "whichanalyses" # #CHANNELTYPE 1: channel with the highest statistical sensitivity 1 1 1 # channel id number 1 2 0 # HBresult 1 3 3.6556097357515465 # obsratio 1 4 1 # ncombined 1 5 ||(e e)->(h1)Z->(b b-bar)Z (hep-ex/0602042, table 14b (LEP))|| # text description of channel # Index: trunk/HiggsBounds_KW/example_data/HB_randomtest50points_Key.dat-for-comparison =================================================================== --- trunk/HiggsBounds_KW/example_data/HB_randomtest50points_Key.dat-for-comparison (revision 508) +++ trunk/HiggsBounds_KW/example_data/HB_randomtest50points_Key.dat-for-comparison (revision 509) @@ -1,1515 +1,1506 @@ *********** Key to Process Numbers ************* - This key has been generated with HiggsBounds version 4.2.0 + This key has been generated with HiggsBounds version 4.2.1 with the setting whichanalyses=LandH ************************************************************** process 0 no process applies ************************************************************** hep-ex/0602042, table 14b (LEP) process 1 (e e)->(h1)Z->(b b-bar)Z (hep-ex/0602042, table 14b (LEP)) process 2 (e e)->(h2)Z->(b b-bar)Z (hep-ex/0602042, table 14b (LEP)) process 3 (e e)->(h3)Z->(b b-bar)Z (hep-ex/0602042, table 14b (LEP)) ************************************************************** hep-ex/0602042, table 14c (LEP) process 4 (e e)->(h1)Z->(tau tau)Z (hep-ex/0602042, table 14c (LEP)) process 5 (e e)->(h2)Z->(tau tau)Z (hep-ex/0602042, table 14c (LEP)) process 6 (e e)->(h3)Z->(tau tau)Z (hep-ex/0602042, table 14c (LEP)) ************************************************************** hep-ex/0206022 (OPAL) process 7 (e e)->(h1)Z->(...)Z (hep-ex/0206022 (OPAL)) process 8 (e e)->(h2)Z->(...)Z (hep-ex/0206022 (OPAL)) process 9 (e e)->(h3)Z->(...)Z (hep-ex/0206022 (OPAL)) ************************************************************** hep-ex/0107032v1 (LEP) process 10 (e e)->(h1)Z->(invisible)Z (hep-ex/0107032v1 (LEP)) process 11 (e e)->(h2)Z->(invisible)Z (hep-ex/0107032v1 (LEP)) process 12 (e e)->(h3)Z->(invisible)Z (hep-ex/0107032v1 (LEP)) ************************************************************** LHWG Note 2002-02 process 13 (e e)->(h1)Z->(gamma gamma)Z (LHWG Note 2002-02) process 14 (e e)->(h2)Z->(gamma gamma)Z (LHWG Note 2002-02) process 15 (e e)->(h3)Z->(gamma gamma)Z (LHWG Note 2002-02) ************************************************************** LHWG (unpublished) process 16 (e e)->(h1)Z->(2 jets)Z (LHWG (unpublished)) process 17 (e e)->(h2)Z->(2 jets)Z (LHWG (unpublished)) process 18 (e e)->(h3)Z->(2 jets)Z (LHWG (unpublished)) ************************************************************** hep-ex/0107034 (LHWG) process 19 (e e)->(h1)Z->(2 jets)Z (hep-ex/0107034 (LHWG)) process 20 (e e)->(h2)Z->(2 jets)Z (hep-ex/0107034 (LHWG)) process 21 (e e)->(h3)Z->(2 jets)Z (hep-ex/0107034 (LHWG)) ************************************************************** hep-ex/0410017 (DELPHI) process 22 (e e)->b b-bar(h1)->b b-bar(b b-bar) where h1 is CP even (hep-ex/0410017 (DELPHI)) process 23 (e e)->b b-bar(h2)->b b-bar(b b-bar) where h2 is CP even (hep-ex/0410017 (DELPHI)) process 24 (e e)->b b-bar(h3)->b b-bar(b b-bar) where h3 is CP even (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0410017 (DELPHI) process 25 (e e)->b b-bar(h1)->b b-bar(b b-bar) where h1 is CP odd (hep-ex/0410017 (DELPHI)) process 26 (e e)->b b-bar(h2)->b b-bar(b b-bar) where h2 is CP odd (hep-ex/0410017 (DELPHI)) process 27 (e e)->b b-bar(h3)->b b-bar(b b-bar) where h3 is CP odd (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0410017 (DELPHI) process 28 (e e)->b b-bar(h1)->b b-bar(tau tau) where h1 is CP even (hep-ex/0410017 (DELPHI)) process 29 (e e)->b b-bar(h2)->b b-bar(tau tau) where h2 is CP even (hep-ex/0410017 (DELPHI)) process 30 (e e)->b b-bar(h3)->b b-bar(tau tau) where h3 is CP even (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0111010 (OPAL) process 31 (e e)->b b-bar(h1)->b b-bar(tau tau) where h1 is CP even (hep-ex/0111010 (OPAL)) process 32 (e e)->b b-bar(h2)->b b-bar(tau tau) where h2 is CP even (hep-ex/0111010 (OPAL)) process 33 (e e)->b b-bar(h3)->b b-bar(tau tau) where h3 is CP even (hep-ex/0111010 (OPAL)) ************************************************************** hep-ex/0410017 (DELPHI) process 34 (e e)->b b-bar(h1)->b b-bar(tau tau) where h1 is CP odd (hep-ex/0410017 (DELPHI)) process 35 (e e)->b b-bar(h2)->b b-bar(tau tau) where h2 is CP odd (hep-ex/0410017 (DELPHI)) process 36 (e e)->b b-bar(h3)->b b-bar(tau tau) where h3 is CP odd (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0111010 (OPAL) process 37 (e e)->b b-bar(h1)->b b-bar(tau tau) where h1 is CP odd (hep-ex/0111010 (OPAL)) process 38 (e e)->b b-bar(h2)->b b-bar(tau tau) where h2 is CP odd (hep-ex/0111010 (OPAL)) process 39 (e e)->b b-bar(h3)->b b-bar(tau tau) where h3 is CP odd (hep-ex/0111010 (OPAL)) ************************************************************** hep-ex/0410017 (DELPHI) process 40 (e e)->tau tau(h1)->tau tau(tau tau) where h1 is CP even (hep-ex/0410017 (DELPHI)) process 41 (e e)->tau tau(h2)->tau tau(tau tau) where h2 is CP even (hep-ex/0410017 (DELPHI)) process 42 (e e)->tau tau(h3)->tau tau(tau tau) where h3 is CP even (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0410017 (DELPHI) process 43 (e e)->tau tau(h1)->tau tau(tau tau) where h1 is CP odd (hep-ex/0410017 (DELPHI)) process 44 (e e)->tau tau(h2)->tau tau(tau tau) where h2 is CP odd (hep-ex/0410017 (DELPHI)) process 45 (e e)->tau tau(h3)->tau tau(tau tau) where h3 is CP odd (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0401022 (Delphi) process 46 (e e)->(h1)Z->(invisible)Z (hep-ex/0401022 (Delphi)) process 47 (e e)->(h2)Z->(invisible)Z (hep-ex/0401022 (Delphi)) process 48 (e e)->(h3)Z->(invisible)Z (hep-ex/0401022 (Delphi)) ************************************************************** hep-ex/0501033 (L3) process 49 (e e)->(h1)Z->(invisible)Z (hep-ex/0501033 (L3)) process 50 (e e)->(h2)Z->(invisible)Z (hep-ex/0501033 (L3)) process 51 (e e)->(h3)Z->(invisible)Z (hep-ex/0501033 (L3)) ************************************************************** [hep-ex] arXiv:0707.0373 (OPAL) process 52 (e e)->(h1)Z->(invisible)Z ([hep-ex] arXiv:0707.0373 (OPAL)) process 53 (e e)->(h2)Z->(invisible)Z ([hep-ex] arXiv:0707.0373 (OPAL)) process 54 (e e)->(h3)Z->(invisible)Z ([hep-ex] arXiv:0707.0373 (OPAL)) ************************************************************** hep-ex/0107031 (LHWG) process 55 (e e)->(H1+)(H1-)->4 quarks (hep-ex/0107031 (LHWG)) ************************************************************** hep-ex/0404012 (Delphi) process 56 (e e)->(H1+)(H1-)->4 quarks (hep-ex/0404012 (Delphi)) ************************************************************** hep-ex/0404012 (Delphi) process 57 (e e)->(H1+)(H1-)->tau nu tau nu(hep-ex/0404012 (Delphi)) ************************************************************** hep-ex/0602042, table 15 (LEP) process 58 *** process 59 (ee)->(h1->h2 h2)Z->(b b b b)Z (hep-ex/0602042, table 15 (LEP)) process 60 (ee)->(h1->h3 h3)Z->(b b b b)Z (hep-ex/0602042, table 15 (LEP)) ------------------------------------------------------------ process 61 (ee)->(h2->h1 h1)Z->(b b b b)Z (hep-ex/0602042, table 15 (LEP)) process 62 *** process 63 (ee)->(h2->h3 h3)Z->(b b b b)Z (hep-ex/0602042, table 15 (LEP)) ------------------------------------------------------------ process 64 (ee)->(h3->h1 h1)Z->(b b b b)Z (hep-ex/0602042, table 15 (LEP)) process 65 (ee)->(h3->h2 h2)Z->(b b b b)Z (hep-ex/0602042, table 15 (LEP)) process 66 *** ************************************************************** hep-ex/0602042, table 16 (LEP) process 67 *** process 68 (ee)->(h1->h2 h2)Z->(tau tau tau tau)Z (hep-ex/0602042, table 16 (LEP)) process 69 (ee)->(h1->h3 h3)Z->(tau tau tau tau)Z (hep-ex/0602042, table 16 (LEP)) ------------------------------------------------------------ process 70 (ee)->(h2->h1 h1)Z->(tau tau tau tau)Z (hep-ex/0602042, table 16 (LEP)) process 71 *** process 72 (ee)->(h2->h3 h3)Z->(tau tau tau tau)Z (hep-ex/0602042, table 16 (LEP)) ------------------------------------------------------------ process 73 (ee)->(h3->h1 h1)Z->(tau tau tau tau)Z (hep-ex/0602042, table 16 (LEP)) process 74 (ee)->(h3->h2 h2)Z->(tau tau tau tau)Z (hep-ex/0602042, table 16 (LEP)) process 75 *** ************************************************************** hep-ex/0602042, table 18 (LEP) process 76 (ee)->(h1 h1)->(b b b b) (hep-ex/0602042, table 18 (LEP)) process 77 (ee)->(h1 h2)->(b b b b) (hep-ex/0602042, table 18 (LEP)) process 78 (ee)->(h1 h3)->(b b b b) (hep-ex/0602042, table 18 (LEP)) ------------------------------------------------------------ process 79 (ee)->(h2 h1)->(b b b b) (hep-ex/0602042, table 18 (LEP)) process 80 (ee)->(h2 h2)->(b b b b) (hep-ex/0602042, table 18 (LEP)) process 81 (ee)->(h2 h3)->(b b b b) (hep-ex/0602042, table 18 (LEP)) ------------------------------------------------------------ process 82 (ee)->(h3 h1)->(b b b b) (hep-ex/0602042, table 18 (LEP)) process 83 (ee)->(h3 h2)->(b b b b) (hep-ex/0602042, table 18 (LEP)) process 84 (ee)->(h3 h3)->(b b b b) (hep-ex/0602042, table 18 (LEP)) ************************************************************** hep-ex/0602042, table 19 (LEP) process 85 (ee)->(h1 h1)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) process 86 (ee)->(h1 h2)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) process 87 (ee)->(h1 h3)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) ------------------------------------------------------------ process 88 (ee)->(h2 h1)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) process 89 (ee)->(h2 h2)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) process 90 (ee)->(h2 h3)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) ------------------------------------------------------------ process 91 (ee)->(h3 h1)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) process 92 (ee)->(h3 h2)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) process 93 (ee)->(h3 h3)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) ************************************************************** hep-ex/0602042, table 20 (LEP) process 94 *** process 95 (ee)->(h1->h2 h2)h2->(b b b b)b b (hep-ex/0602042, table 20 (LEP)) process 96 (ee)->(h1->h3 h3)h3->(b b b b)b b (hep-ex/0602042, table 20 (LEP)) ------------------------------------------------------------ process 97 (ee)->(h2->h1 h1)h1->(b b b b)b b (hep-ex/0602042, table 20 (LEP)) process 98 *** process 99 (ee)->(h2->h3 h3)h3->(b b b b)b b (hep-ex/0602042, table 20 (LEP)) ------------------------------------------------------------ process 100 (ee)->(h3->h1 h1)h1->(b b b b)b b (hep-ex/0602042, table 20 (LEP)) process 101 (ee)->(h3->h2 h2)h2->(b b b b)b b (hep-ex/0602042, table 20 (LEP)) process 102 *** ************************************************************** hep-ex/0602042, table 21 (LEP) process 103 *** process 104 (ee)->(h1->h2 h2)h2->(tau tau tau tau)tau tau (hep-ex/0602042, table 21 (LEP)) process 105 (ee)->(h1->h3 h3)h3->(tau tau tau tau)tau tau (hep-ex/0602042, table 21 (LEP)) ------------------------------------------------------------ process 106 (ee)->(h2->h1 h1)h1->(tau tau tau tau)tau tau (hep-ex/0602042, table 21 (LEP)) process 107 *** process 108 (ee)->(h2->h3 h3)h3->(tau tau tau tau)tau tau (hep-ex/0602042, table 21 (LEP)) ------------------------------------------------------------ process 109 (ee)->(h3->h1 h1)h1->(tau tau tau tau)tau tau (hep-ex/0602042, table 21 (LEP)) process 110 (ee)->(h3->h2 h2)h2->(tau tau tau tau)tau tau (hep-ex/0602042, table 21 (LEP)) process 111 *** ************************************************************** hep-ex/0602042 (LEP) process 112 (ee)->(h1->b b)(h1->tau tau) (hep-ex/0602042 (LEP)) process 113 (ee)->(h1->b b)(h2->tau tau) (hep-ex/0602042 (LEP)) process 114 (ee)->(h1->b b)(h3->tau tau) (hep-ex/0602042 (LEP)) ------------------------------------------------------------ process 115 (ee)->(h2->b b)(h1->tau tau) (hep-ex/0602042 (LEP)) process 116 (ee)->(h2->b b)(h2->tau tau) (hep-ex/0602042 (LEP)) process 117 (ee)->(h2->b b)(h3->tau tau) (hep-ex/0602042 (LEP)) ------------------------------------------------------------ process 118 (ee)->(h3->b b)(h1->tau tau) (hep-ex/0602042 (LEP)) process 119 (ee)->(h3->b b)(h2->tau tau) (hep-ex/0602042 (LEP)) process 120 (ee)->(h3->b b)(h3->tau tau) (hep-ex/0602042 (LEP)) ************************************************************** hep-ex/0602042 (LEP) process 121 (ee)->(h1->tau tau)(h1->b b) (hep-ex/0602042 (LEP)) process 122 (ee)->(h1->tau tau)(h2->b b) (hep-ex/0602042 (LEP)) process 123 (ee)->(h1->tau tau)(h3->b b) (hep-ex/0602042 (LEP)) ------------------------------------------------------------ process 124 (ee)->(h2->tau tau)(h1->b b) (hep-ex/0602042 (LEP)) process 125 (ee)->(h2->tau tau)(h2->b b) (hep-ex/0602042 (LEP)) process 126 (ee)->(h2->tau tau)(h3->b b) (hep-ex/0602042 (LEP)) ------------------------------------------------------------ process 127 (ee)->(h3->tau tau)(h1->b b) (hep-ex/0602042 (LEP)) process 128 (ee)->(h3->tau tau)(h2->b b) (hep-ex/0602042 (LEP)) process 129 (ee)->(h3->tau tau)(h3->b b) (hep-ex/0602042 (LEP)) ************************************************************** CDF Note 10799 process 130 (p p-bar)->Z(h1)->l l (b b-bar) (CDF Note 10799) process 131 (p p-bar)->Z(h2)->l l (b b-bar) (CDF Note 10799) process 132 (p p-bar)->Z(h3)->l l (b b-bar) (CDF Note 10799) ************************************************************** D0 Note 6296 process 133 (p p-bar)->Z(h1)->l l (b b-bar) (D0 Note 6296) process 134 (p p-bar)->Z(h2)->l l (b b-bar) (D0 Note 6296) process 135 (p p-bar)->Z(h3)->l l (b b-bar) (D0 Note 6296) ************************************************************** [hep-ex] arXiv:1008.3564 (D0) process 136 (p p-bar)->Z(h1)->l l (b b-bar) ([hep-ex] arXiv:1008.3564 (D0)) process 137 (p p-bar)->Z(h2)->l l (b b-bar) ([hep-ex] arXiv:1008.3564 (D0)) process 138 (p p-bar)->Z(h3)->l l (b b-bar) ([hep-ex] arXiv:1008.3564 (D0)) ************************************************************** CDF Note 10798 process 139 (p p-bar)->V h1-> (b b-bar) +missing Et where h1 is SM-like (CDF Note 10798) process 140 (p p-bar)->V h2-> (b b-bar) +missing Et where h2 is SM-like (CDF Note 10798) process 141 (p p-bar)->V h3-> (b b-bar) +missing Et where h3 is SM-like (CDF Note 10798) ************************************************************** D0 Note 6299 process 142 (p p-bar)->V h1-> (b b-bar) +missing Et where h1 is SM-like (D0 Note 6299) process 143 (p p-bar)->V h2-> (b b-bar) +missing Et where h2 is SM-like (D0 Note 6299) process 144 (p p-bar)->V h3-> (b b-bar) +missing Et where h3 is SM-like (D0 Note 6299) ************************************************************** ATLAS-CONF-2012-161 process 145 (p p)->V(h1)->V (b b-bar) (ATLAS-CONF-2012-161) process 146 (p p)->V(h2)->V (b b-bar) (ATLAS-CONF-2012-161) process 147 (p p)->V(h3)->V (b b-bar) (ATLAS-CONF-2012-161) ************************************************************** CMS-PAS-HIG-13-012 process 148 (p p)->V h1->b b where h1 is SM-like (CMS-PAS-HIG-13-012) process 149 (p p)->V h2->b b where h2 is SM-like (CMS-PAS-HIG-13-012) process 150 (p p)->V h3->b b where h3 is SM-like (CMS-PAS-HIG-13-012) ************************************************************** CMS-PAS-HIG-13-011 process 151 (p p)->h1/VBF->bb+... where h1 is SM-like (CMS-PAS-HIG-13-011) process 152 (p p)->h2/VBF->bb+... where h2 is SM-like (CMS-PAS-HIG-13-011) process 153 (p p)->h3/VBF->bb+... where h3 is SM-like (CMS-PAS-HIG-13-011) ************************************************************** D0 Note 6309 process 154 (p p-bar)->W(h1)->l nu (b b-bar) (D0 Note 6309) process 155 (p p-bar)->W(h2)->l nu (b b-bar) (D0 Note 6309) process 156 (p p-bar)->W(h3)->l nu (b b-bar) (D0 Note 6309) ************************************************************** CDF Note 10796 process 157 (p p-bar)->W(h1)->l nu (b b-bar) (CDF Note 10796) process 158 (p p-bar)->W(h2)->l nu (b b-bar) (CDF Note 10796) process 159 (p p-bar)->W(h3)->l nu (b b-bar) (CDF Note 10796) ************************************************************** [hep-ex] arXiv:1012.0874 (D0) process 160 (p p-bar)->W(h1)->l nu (b b-bar) ([hep-ex] arXiv:1012.0874 (D0)) process 161 (p p-bar)->W(h2)->l nu (b b-bar) ([hep-ex] arXiv:1012.0874 (D0)) process 162 (p p-bar)->W(h3)->l nu (b b-bar) ([hep-ex] arXiv:1012.0874 (D0)) ************************************************************** [hep-ex] arXiv:0906.5613 (CDF) process 163 (p p-bar)->W(h1)->l nu (b b-bar) ([hep-ex] arXiv:0906.5613 (CDF)) process 164 (p p-bar)->W(h2)->l nu (b b-bar) ([hep-ex] arXiv:0906.5613 (CDF)) process 165 (p p-bar)->W(h3)->l nu (b b-bar) ([hep-ex] arXiv:0906.5613 (CDF)) ************************************************************** [hep-ex] arXiv:1402.3244 (ATLAS) process 166 (p p)->Vh1->V (invisible) ([hep-ex] arXiv:1402.3244 (ATLAS)) process 167 (p p)->Vh2->V (invisible) ([hep-ex] arXiv:1402.3244 (ATLAS)) process 168 (p p)->Vh3->V (invisible) ([hep-ex] arXiv:1402.3244 (ATLAS)) ************************************************************** [hep-ex] arXiv:1404.1344 (CMS) process 169 (p p)->Zh1->Z (invisible) ([hep-ex] arXiv:1404.1344 (CMS)) process 170 (p p)->Zh2->Z (invisible) ([hep-ex] arXiv:1404.1344 (CMS)) process 171 (p p)->Zh3->Z (invisible) ([hep-ex] arXiv:1404.1344 (CMS)) ************************************************************** [hep-ex] arXiv:1404.1344 (CMS) process 172 (p p)->h1(VBF)->V (invisible) ([hep-ex] arXiv:1404.1344 (CMS)) process 173 (p p)->h2(VBF)->V (invisible) ([hep-ex] arXiv:1404.1344 (CMS)) process 174 (p p)->h3(VBF)->V (invisible) ([hep-ex] arXiv:1404.1344 (CMS)) ************************************************************** [hep-ex] arXiv:1404.1344 (CMS) process 175 (p p)->h1(VBF)/Zh1, h1->(invisible) ([hep-ex] arXiv:1404.1344 (CMS)) process 176 (p p)->h2(VBF)/Zh2, h2->(invisible) ([hep-ex] arXiv:1404.1344 (CMS)) process 177 (p p)->h3(VBF)/Zh3, h3->(invisible) ([hep-ex] arXiv:1404.1344 (CMS)) ************************************************************** D0 Note 5757 process 178 (p p-bar)->h1/VBF->W W->l l where h1 is SM-like (D0 Note 5757) process 179 (p p-bar)->h2/VBF->W W->l l where h2 is SM-like (D0 Note 5757) process 180 (p p-bar)->h3/VBF->W W->l l where h3 is SM-like (D0 Note 5757) ************************************************************** [hep-ex] arXiv:0809.3930 (CDF) process 181 (p p-bar)->h1->W W ([hep-ex] arXiv:0809.3930 (CDF)) process 182 (p p-bar)->h2->W W ([hep-ex] arXiv:0809.3930 (CDF)) process 183 (p p-bar)->h3->W W ([hep-ex] arXiv:0809.3930 (CDF)) ************************************************************** D0 Note 6276 process 184 (p p-bar)->h1+...->V V +... ->l l l missing Et +... where h1 is SM-like (D0 Note 6276) process 185 (p p-bar)->h2+...->V V +... ->l l l missing Et +... where h2 is SM-like (D0 Note 6276) process 186 (p p-bar)->h3+...->V V +... ->l l l missing Et +... where h3 is SM-like (D0 Note 6276) ************************************************************** D0 Note 6301 process 187 (p p-bar)->V h1->V W W (D0 Note 6301) process 188 (p p-bar)->V h2->V W W (D0 Note 6301) process 189 (p p-bar)->V h3->V W W (D0 Note 6301) ************************************************************** CDF Note 10599 process 190 (p p-bar)->h1->W W (CDF Note 10599) process 191 (p p-bar)->h2->W W (CDF Note 10599) process 192 (p p-bar)->h3->W W (CDF Note 10599) ************************************************************** CDF Note 10599 process 193 (p p-bar)->h1+...->W W +... where h1 is SM-like (CDF Note 10599) process 194 (p p-bar)->h2+...->W W +... where h2 is SM-like (CDF Note 10599) process 195 (p p-bar)->h3+...->W W +... where h3 is SM-like (CDF Note 10599) ************************************************************** [hep-ex] arXiv:1001.4468 (CDF) process 196 (p p-bar)->h1+...->W W +... where h1 is SM-like ([hep-ex] arXiv:1001.4468 (CDF)) process 197 (p p-bar)->h2+...->W W +... where h2 is SM-like ([hep-ex] arXiv:1001.4468 (CDF)) process 198 (p p-bar)->h3+...->W W +... where h3 is SM-like ([hep-ex] arXiv:1001.4468 (CDF)) ************************************************************** D0 Note 6302 process 199 (p p-bar)->h1+...->W W +... where h1 is SM-like (D0 Note 6302) process 200 (p p-bar)->h2+...->W W +... where h2 is SM-like (D0 Note 6302) process 201 (p p-bar)->h3+...->W W +... where h3 is SM-like (D0 Note 6302) ************************************************************** D0 Note 6183 process 202 (p p-bar)->h1+... where h1 is SM-like (D0 Note 6183) process 203 (p p-bar)->h2+... where h2 is SM-like (D0 Note 6183) process 204 (p p-bar)->h3+... where h3 is SM-like (D0 Note 6183) ************************************************************** [hep-ex] arXiv:1001.4481 (D0) process 205 (p p-bar)->h1+...->W W +... where h1 is SM-like ([hep-ex] arXiv:1001.4481 (D0)) process 206 (p p-bar)->h2+...->W W +... where h2 is SM-like ([hep-ex] arXiv:1001.4481 (D0)) process 207 (p p-bar)->h3+...->W W +... where h3 is SM-like ([hep-ex] arXiv:1001.4481 (D0)) ************************************************************** [hep-ex] arXiv:1108.3331 (TEVNPHWG) process 208 (p p-bar)->h1->V V ([hep-ex] arXiv:1108.3331 (TEVNPHWG)) process 209 (p p-bar)->h2->V V ([hep-ex] arXiv:1108.3331 (TEVNPHWG)) process 210 (p p-bar)->h3->V V ([hep-ex] arXiv:1108.3331 (TEVNPHWG)) ************************************************************** ATLAS-CONF-2012-012 process 211 (p p)->h1->W W where h1 is SM-like (ATLAS-CONF-2012-012) process 212 (p p)->h2->W W where h2 is SM-like (ATLAS-CONF-2012-012) process 213 (p p)->h3->W W where h3 is SM-like (ATLAS-CONF-2012-012) ************************************************************** ATLAS-CONF-2013-030 process 214 (p p)->h1->W W where h1 is SM-like (ATLAS-CONF-2013-030) process 215 (p p)->h2->W W where h2 is SM-like (ATLAS-CONF-2013-030) process 216 (p p)->h3->W W where h3 is SM-like (ATLAS-CONF-2013-030) ************************************************************** [hep-ex] arxiv:1112.2577 process 217 pp->h + X->W W* + X ->l l nu nu, h=1 where h is SM-like ([hep-ex] arxiv:1112.2577) process 218 pp->h + X->W W* + X ->l l nu nu, h=2 where h is SM-like ([hep-ex] arxiv:1112.2577) process 219 pp->h + X->W W* + X ->l l nu nu, h=3 where h is SM-like ([hep-ex] arxiv:1112.2577) ************************************************************** CMS-PAS-HIG-13-003 process 220 (p p)->h1+...->W W +... where h1 is SM-like (CMS-PAS-HIG-13-003) process 221 (p p)->h2+...->W W +... where h2 is SM-like (CMS-PAS-HIG-13-003) process 222 (p p)->h3+...->W W +... where h3 is SM-like (CMS-PAS-HIG-13-003) ************************************************************** CMS-PAS-HIG-13-027 process 223 (p p)->h1+...->W W +... where h1 is SM-like (CMS-PAS-HIG-13-027) process 224 (p p)->h2+...->W W +... where h2 is SM-like (CMS-PAS-HIG-13-027) process 225 (p p)->h3+...->W W +... where h3 is SM-like (CMS-PAS-HIG-13-027) ************************************************************** CMS-PAS-HIG-13-022 process 226 (p p)->h1(VBF)->WW (CMS-PAS-HIG-13-022) process 227 (p p)->h2(VBF)->WW (CMS-PAS-HIG-13-022) process 228 (p p)->h3(VBF)->WW (CMS-PAS-HIG-13-022) ************************************************************** [hep-ex] arXiv:1109.3357 (ATLAS) process 229 (p p)->h1->V V-> l l nu nu where h1 is SM-like ([hep-ex] arXiv:1109.3357 (ATLAS)) process 230 (p p)->h2->V V-> l l nu nu where h2 is SM-like ([hep-ex] arXiv:1109.3357 (ATLAS)) process 231 (p p)->h3->V V-> l l nu nu where h3 is SM-like ([hep-ex] arXiv:1109.3357 (ATLAS)) ************************************************************** ATLAS-CONF-2012-016 process 232 (p p)->h1->V V-> l l nu nu where h1 is SM-like (ATLAS-CONF-2012-016) process 233 (p p)->h2->V V-> l l nu nu where h2 is SM-like (ATLAS-CONF-2012-016) process 234 (p p)->h3->V V-> l l nu nu where h3 is SM-like (ATLAS-CONF-2012-016) ************************************************************** [hep-ex] arxiv:1202.3478 (CMS) process 235 (p p)->h1/VBF->V V-> l l nu nu where h1 is SM-like ([hep-ex] arxiv:1202.3478 (CMS)) process 236 (p p)->h2/VBF->V V-> l l nu nu where h2 is SM-like ([hep-ex] arxiv:1202.3478 (CMS)) process 237 (p p)->h3/VBF->V V-> l l nu nu where h3 is SM-like ([hep-ex] arxiv:1202.3478 (CMS)) ************************************************************** [hep-ex] arXiv:1109.3615 (ATLAS) process 238 (p p)->h1/VBF->W W where h1 is SM-like ([hep-ex] arXiv:1109.3615 (ATLAS)) process 239 (p p)->h2/VBF->W W where h2 is SM-like ([hep-ex] arXiv:1109.3615 (ATLAS)) process 240 (p p)->h3/VBF->W W where h3 is SM-like ([hep-ex] arXiv:1109.3615 (ATLAS)) ************************************************************** ATLAS-CONF-2012-018 process 241 (p p)->h1/VBF->W W where h1 is SM-like (ATLAS-CONF-2012-018) process 242 (p p)->h2/VBF->W W where h2 is SM-like (ATLAS-CONF-2012-018) process 243 (p p)->h3/VBF->W W where h3 is SM-like (ATLAS-CONF-2012-018) ************************************************************** CMS-PAS-HIG-12-046 process 244 (p p)->h1->W W-> l nu q q where h1 is SM-like (CMS-PAS-HIG-12-046) process 245 (p p)->h2->W W-> l nu q q where h2 is SM-like (CMS-PAS-HIG-12-046) process 246 (p p)->h3->W W-> l nu q q where h3 is SM-like (CMS-PAS-HIG-12-046) ************************************************************** [hep-ex] arXiv:1108.5064 (ATLAS) process 247 (p p)->h1/VBF->Z Z-> l l q q where h1 is SM-like ([hep-ex] arXiv:1108.5064 (ATLAS)) process 248 (p p)->h2/VBF->Z Z-> l l q q where h2 is SM-like ([hep-ex] arXiv:1108.5064 (ATLAS)) process 249 (p p)->h3/VBF->Z Z-> l l q q where h3 is SM-like ([hep-ex] arXiv:1108.5064 (ATLAS)) ************************************************************** ATLAS-CONF-2012-017 process 250 (p p)->h1/VBF->Z Z-> l l q q where h1 is SM-like (ATLAS-CONF-2012-017) process 251 (p p)->h2/VBF->Z Z-> l l q q where h2 is SM-like (ATLAS-CONF-2012-017) process 252 (p p)->h3/VBF->Z Z-> l l q q where h3 is SM-like (ATLAS-CONF-2012-017) ************************************************************** [hep-ex] arXiv:1202.1416 (CMS) process 253 (p p)->h1/VBF->Z Z-> l l q q where h1 is SM-like ([hep-ex] arXiv:1202.1416 (CMS)) process 254 (p p)->h2/VBF->Z Z-> l l q q where h2 is SM-like ([hep-ex] arXiv:1202.1416 (CMS)) process 255 (p p)->h3/VBF->Z Z-> l l q q where h3 is SM-like ([hep-ex] arXiv:1202.1416 (CMS)) ************************************************************** [hep-ex] arXiv:1202.1416 (CMS) process 256 (p p)->h1/VBF->Z Z-> l l q q where h1 is SM-like ([hep-ex] arXiv:1202.1416 (CMS)) process 257 (p p)->h2/VBF->Z Z-> l l q q where h2 is SM-like ([hep-ex] arXiv:1202.1416 (CMS)) process 258 (p p)->h3/VBF->Z Z-> l l q q where h3 is SM-like ([hep-ex] arXiv:1202.1416 (CMS)) ************************************************************** [hep-ex] arXiv:1202.1415 (ATLAS) process 259 (p p)->h1/VBF/V h1->Z Z-> l l l l where h1 is SM-like ([hep-ex] arXiv:1202.1415 (ATLAS)) process 260 (p p)->h2/VBF/V h2->Z Z-> l l l l where h2 is SM-like ([hep-ex] arXiv:1202.1415 (ATLAS)) process 261 (p p)->h3/VBF/V h3->Z Z-> l l l l where h3 is SM-like ([hep-ex] arXiv:1202.1415 (ATLAS)) ************************************************************** ATLAS-CONF-2012-092 process 262 (p p)->h1/VBF/V h1->Z Z-> l l l l where h1 is SM-like (ATLAS-CONF-2012-092) process 263 (p p)->h2/VBF/V h2->Z Z-> l l l l where h2 is SM-like (ATLAS-CONF-2012-092) process 264 (p p)->h3/VBF/V h3->Z Z-> l l l l where h3 is SM-like (ATLAS-CONF-2012-092) ************************************************************** ATLAS-CONF-2013-013 process 265 (p p)->h1->Z Z-> l l l l where h1 is SM-like (ATLAS-CONF-2013-013) process 266 (p p)->h2->Z Z-> l l l l where h2 is SM-like (ATLAS-CONF-2013-013) process 267 (p p)->h3->Z Z-> l l l l where h3 is SM-like (ATLAS-CONF-2013-013) ************************************************************** ATLAS-CONF-2013-013 process 268 (p p)->h1/ggF h->Z Z-> l l l l (ATLAS-CONF-2013-013) process 269 (p p)->h2/ggF h->Z Z-> l l l l (ATLAS-CONF-2013-013) process 270 (p p)->h3/ggF h->Z Z-> l l l l (ATLAS-CONF-2013-013) ************************************************************** ATLAS-CONF-2013-013 process 271 (p p)->h1/VBF/V h->Z Z-> l l l l (ATLAS-CONF-2013-013) process 272 (p p)->h2/VBF/V h->Z Z-> l l l l (ATLAS-CONF-2013-013) process 273 (p p)->h3/VBF/V h->Z Z-> l l l l (ATLAS-CONF-2013-013) ************************************************************** [hep-ex] arxiv:1202.1997 (CMS) process 274 (p p)->h1/VBF/V/tt h1->Z Z-> l l l l where h1 is SM-like ([hep-ex] arxiv:1202.1997 (CMS)) process 275 (p p)->h2/VBF/V/tt h2->Z Z-> l l l l where h2 is SM-like ([hep-ex] arxiv:1202.1997 (CMS)) process 276 (p p)->h3/VBF/V/tt h3->Z Z-> l l l l where h3 is SM-like ([hep-ex] arxiv:1202.1997 (CMS)) ************************************************************** CMS-PAS-HIG-13-002 process 277 (p p)->h1->Z Z-> l l l l (low mass) where h1 is SM-like (CMS-PAS-HIG-13-002) process 278 (p p)->h2->Z Z-> l l l l (low mass) where h2 is SM-like (CMS-PAS-HIG-13-002) process 279 (p p)->h3->Z Z-> l l l l (low mass) where h3 is SM-like (CMS-PAS-HIG-13-002) ************************************************************** CMS-PAS-HIG-13-002 process 280 (p p)->h1->Z Z-> l l l l (high mass) where h1 is SM-like (CMS-PAS-HIG-13-002) process 281 (p p)->h2->Z Z-> l l l l (high mass) where h2 is SM-like (CMS-PAS-HIG-13-002) process 282 (p p)->h3->Z Z-> l l l l (high mass) where h3 is SM-like (CMS-PAS-HIG-13-002) ************************************************************** CDF Note 10439 process 283 (p p-bar)->h1+...->tau tau +... where h1 is SM-like (CDF Note 10439) process 284 (p p-bar)->h2+...->tau tau +... where h2 is SM-like (CDF Note 10439) process 285 (p p-bar)->h3+...->tau tau +... where h3 is SM-like (CDF Note 10439) ************************************************************** D0 Note 5845 process 286 (p p-bar)->h1+...->tau tau (2 jets) where h1 is SM-like (D0 Note 5845) process 287 (p p-bar)->h2+...->tau tau (2 jets) where h2 is SM-like (D0 Note 5845) process 288 (p p-bar)->h3+...->tau tau (2 jets) where h3 is SM-like (D0 Note 5845) ************************************************************** CDF Note 9999 process 289 (p p-bar)->h1+... where h1 is SM-like (CDF Note 9999) process 290 (p p-bar)->h2+... where h2 is SM-like (CDF Note 9999) process 291 (p p-bar)->h3+... where h3 is SM-like (CDF Note 9999) ************************************************************** D0 Note 6305 process 292 (p p-bar)->h1+...->tau tau +... where h1 is SM-like (D0 Note 6305) process 293 (p p-bar)->h2+...->tau tau +... where h2 is SM-like (D0 Note 6305) process 294 (p p-bar)->h3+...->tau tau +... where h3 is SM-like (D0 Note 6305) ************************************************************** CDF Note 10010 process 295 (p p-bar)->V (h1)/VBF-> (b b-bar) q q where h1 is SM-like (CDF Note 10010) process 296 (p p-bar)->V (h2)/VBF-> (b b-bar) q q where h2 is SM-like (CDF Note 10010) process 297 (p p-bar)->V (h3)/VBF-> (b b-bar) q q where h3 is SM-like (CDF Note 10010) ************************************************************** D0 Note 6171 process 298 (p p-bar)->h1+...->tau tau (2 jets) where h1 is SM-like (D0 Note 6171) process 299 (p p-bar)->h2+...->tau tau (2 jets) where h2 is SM-like (D0 Note 6171) process 300 (p p-bar)->h3+...->tau tau (2 jets) where h3 is SM-like (D0 Note 6171) ************************************************************** D0 Note 6304 process 301 (p p-bar)->h1+... where h1 is SM-like (D0 Note 6304) process 302 (p p-bar)->h2+... where h2 is SM-like (D0 Note 6304) process 303 (p p-bar)->h3+... where h3 is SM-like (D0 Note 6304) ************************************************************** CDF Note 10500 process 304 (p p-bar)->V h1-> V tau tau (CDF Note 10500) process 305 (p p-bar)->V h2-> V tau tau (CDF Note 10500) process 306 (p p-bar)->V h3-> V tau tau (CDF Note 10500) ************************************************************** CDF Note 10573 process 307 (p p-bar)->h1+...->V V +... ->l l l l +... where h1 is SM-like (CDF Note 10573) process 308 (p p-bar)->h2+...->V V +... ->l l l l +... where h2 is SM-like (CDF Note 10573) process 309 (p p-bar)->h3+...->V V +... ->l l l l +... where h3 is SM-like (CDF Note 10573) ************************************************************** D0 Note 6286 process 310 (p p-bar)->h1+...->tau tau +... where h1 is SM-like (D0 Note 6286) process 311 (p p-bar)->h2+...->tau tau +... where h2 is SM-like (D0 Note 6286) process 312 (p p-bar)->h3+...->tau tau +... where h3 is SM-like (D0 Note 6286) ************************************************************** [hep-ex] arXiv:1207.0449 (TEVNPHWG) process 313 (p p-bar)->h1+... where h1 is SM-like ([hep-ex] arXiv:1207.0449 (TEVNPHWG)) process 314 (p p-bar)->h2+... where h2 is SM-like ([hep-ex] arXiv:1207.0449 (TEVNPHWG)) process 315 (p p-bar)->h3+... where h3 is SM-like ([hep-ex] arXiv:1207.0449 (TEVNPHWG)) ************************************************************** [hep-ex] arXiv:1207.6436 (TEVNPHWG) process 316 (p p-bar)->V (h1)-> (b b-bar)+...([hep-ex] arXiv:1207.6436 (TEVNPHWG)) process 317 (p p-bar)->V (h2)-> (b b-bar)+...([hep-ex] arXiv:1207.6436 (TEVNPHWG)) process 318 (p p-bar)->V (h3)-> (b b-bar)+...([hep-ex] arXiv:1207.6436 (TEVNPHWG)) ************************************************************** (hep-ex) arxiv:1202.1408 (ATLAS) process 319 (p p)->h1+... where h1 is SM-like ((hep-ex) arxiv:1202.1408 (ATLAS)) process 320 (p p)->h2+... where h2 is SM-like ((hep-ex) arxiv:1202.1408 (ATLAS)) process 321 (p p)->h3+... where h3 is SM-like ((hep-ex) arxiv:1202.1408 (ATLAS)) ************************************************************** ATLAS-CONF-2012-019 process 322 (p p)->h+..., h=1 where h is SM-like (ATLAS-CONF-2012-019) process 323 (p p)->h+..., h=2 where h is SM-like (ATLAS-CONF-2012-019) process 324 (p p)->h+..., h=3 where h is SM-like (ATLAS-CONF-2012-019) ************************************************************** (hep-ex) arXiv:1207.7214 (ATLAS) process 325 (p p)->h+..., h=1 where h is SM-like ((hep-ex) arXiv:1207.7214 (ATLAS)) process 326 (p p)->h+..., h=2 where h is SM-like ((hep-ex) arXiv:1207.7214 (ATLAS)) process 327 (p p)->h+..., h=3 where h is SM-like ((hep-ex) arXiv:1207.7214 (ATLAS)) ************************************************************** ATLAS-CONF-2011-157, CMS-PAS-HIG-11-023 process 328 (p p)->h1+... where h1 is SM-like (ATLAS-CONF-2011-157, CMS-PAS-HIG-11-023) process 329 (p p)->h2+... where h2 is SM-like (ATLAS-CONF-2011-157, CMS-PAS-HIG-11-023) process 330 (p p)->h3+... where h3 is SM-like (ATLAS-CONF-2011-157, CMS-PAS-HIG-11-023) ************************************************************** [hep-ex] arxiv:1202.1488 (CMS) process 331 (p p)->h1+... where h1 is SM-like ([hep-ex] arxiv:1202.1488 (CMS)) process 332 (p p)->h2+... where h2 is SM-like ([hep-ex] arxiv:1202.1488 (CMS)) process 333 (p p)->h3+... where h3 is SM-like ([hep-ex] arxiv:1202.1488 (CMS)) ************************************************************** CMS-PAS-HIG-12-045 process 334 (p p)->h+..., h=1 where h is SM-like (CMS-PAS-HIG-12-045) process 335 (p p)->h+..., h=2 where h is SM-like (CMS-PAS-HIG-12-045) process 336 (p p)->h+..., h=3 where h is SM-like (CMS-PAS-HIG-12-045) ************************************************************** [hep-ex] arXiv:1011.1931 (D0) process 337 (p p-bar)->h1(b/b-bar)->(b b-bar) (b/b-bar) ([hep-ex] arXiv:1011.1931 (D0)) process 338 (p p-bar)->h2(b/b-bar)->(b b-bar) (b/b-bar) ([hep-ex] arXiv:1011.1931 (D0)) process 339 (p p-bar)->h3(b/b-bar)->(b b-bar) (b/b-bar) ([hep-ex] arXiv:1011.1931 (D0)) ************************************************************** arXiv:1106.4782 (CDF) process 340 (p p-bar)->h1(b/b-bar)->(b b-bar) (b/b-bar) (arXiv:1106.4782 (CDF)) process 341 (p p-bar)->h2(b/b-bar)->(b b-bar) (b/b-bar) (arXiv:1106.4782 (CDF)) process 342 (p p-bar)->h3(b/b-bar)->(b b-bar) (b/b-bar) (arXiv:1106.4782 (CDF)) ************************************************************** [hep-ex] arXiv:1106.4555 (D0) process 343 (p p-bar)->h1->tau tau ([hep-ex] arXiv:1106.4555 (D0)) process 344 (p p-bar)->h2->tau tau ([hep-ex] arXiv:1106.4555 (D0)) process 345 (p p-bar)->h3->tau tau ([hep-ex] arXiv:1106.4555 (D0)) ************************************************************** [hep-ex] arXiv:0906.1014 (CDF) process 346 (p p-bar)->h1->tau tau ([hep-ex] arXiv:0906.1014 (CDF)) process 347 (p p-bar)->h2->tau tau ([hep-ex] arXiv:0906.1014 (CDF)) process 348 (p p-bar)->h3->tau tau ([hep-ex] arXiv:0906.1014 (CDF)) ************************************************************** [hep-ex] arXiv:1003.3363 (TEVNPHWG) process 349 (p p-bar)->h1->tau tau ([hep-ex] arXiv:1003.3363 (TEVNPHWG)) process 350 (p p-bar)->h2->tau tau ([hep-ex] arXiv:1003.3363 (TEVNPHWG)) process 351 (p p-bar)->h3->tau tau ([hep-ex] arXiv:1003.3363 (TEVNPHWG)) ************************************************************** ATLAS-CONF-2012-160 process 352 (p p)->h1->tau tau +... where h1 is SM-like (ATLAS-CONF-2012-160) process 353 (p p)->h2->tau tau +... where h2 is SM-like (ATLAS-CONF-2012-160) process 354 (p p)->h3->tau tau +... where h3 is SM-like (ATLAS-CONF-2012-160) ************************************************************** - [hep-ex] arXiv:1107.5003 (ATLAS) + ATLAS-CONF-2014-049,arXiv:1409.6064 process 355 - (p p)->h1->tau tau ([hep-ex] arXiv:1107.5003 (ATLAS)) + (p p)->bbh1->tau tau (ATLAS-CONF-2014-049,arXiv:1409.6064) process 356 - (p p)->h2->tau tau ([hep-ex] arXiv:1107.5003 (ATLAS)) + (p p)->bbh2->tau tau (ATLAS-CONF-2014-049,arXiv:1409.6064) process 357 - (p p)->h3->tau tau ([hep-ex] arXiv:1107.5003 (ATLAS)) + (p p)->bbh3->tau tau (ATLAS-CONF-2014-049,arXiv:1409.6064) ************************************************************** - ATLAS-CONF-2014-049 + ATLAS-CONF-2014-049,,arXiv:1409.6064 process 358 - (p p)->bbh1->tau tau (ATLAS-CONF-2014-049) + (p p)->ggh1->tau tau (ATLAS-CONF-2014-049,,arXiv:1409.6064) process 359 - (p p)->bbh2->tau tau (ATLAS-CONF-2014-049) + (p p)->ggh2->tau tau (ATLAS-CONF-2014-049,,arXiv:1409.6064) process 360 - (p p)->bbh3->tau tau (ATLAS-CONF-2014-049) -************************************************************** - ATLAS-CONF-2014-049 - -process 361 - (p p)->ggh1->tau tau (ATLAS-CONF-2014-049) -process 362 - (p p)->ggh2->tau tau (ATLAS-CONF-2014-049) -process 363 - (p p)->ggh3->tau tau (ATLAS-CONF-2014-049) + (p p)->ggh3->tau tau (ATLAS-CONF-2014-049,,arXiv:1409.6064) ************************************************************** CMS-PAS-HIG-12-043 -process 364 +process 361 (p p)->h1->tau tau +... where h1 is SM-like (CMS-PAS-HIG-12-043) -process 365 +process 362 (p p)->h2->tau tau +... where h2 is SM-like (CMS-PAS-HIG-12-043) -process 366 +process 363 (p p)->h3->tau tau +... where h3 is SM-like (CMS-PAS-HIG-12-043) ************************************************************** ATLAS-CONF-2013-010 -process 367 +process 364 (p p)->h1->mu mu +... where h1 is SM-like (ATLAS-CONF-2013-010) -process 368 +process 365 (p p)->h2->mu mu +... where h2 is SM-like (ATLAS-CONF-2013-010) -process 369 +process 366 (p p)->h3->mu mu +... where h3 is SM-like (ATLAS-CONF-2013-010) ************************************************************** [hep-ex] arXiv:1406.7663 (ATLAS) -process 370 +process 367 (p p)->h1->mu mu +... where h1 is SM-like ([hep-ex] arXiv:1406.7663 (ATLAS)) -process 371 +process 368 (p p)->h2->mu mu +... where h2 is SM-like ([hep-ex] arXiv:1406.7663 (ATLAS)) -process 372 +process 369 (p p)->h3->mu mu +... where h3 is SM-like ([hep-ex] arXiv:1406.7663 (ATLAS)) ************************************************************** D0 Note 5873 -process 373 +process 370 (p p-bar)->W(h1)->W W W->l l nu nu (D0 Note 5873) -process 374 +process 371 (p p-bar)->W(h2)->W W W->l l nu nu (D0 Note 5873) -process 375 +process 372 (p p-bar)->W(h3)->W W W->l l nu nu (D0 Note 5873) ************************************************************** CDF Note 7307 vs 3 -process 376 +process 373 (p p-bar)->W(h1)->W W W (CDF Note 7307 vs 3) -process 377 +process 374 (p p-bar)->W(h2)->W W W (CDF Note 7307 vs 3) -process 378 +process 375 (p p-bar)->W(h3)->W W W (CDF Note 7307 vs 3) ************************************************************** [hep-ex] arXiv:1107.1268 (D0) -process 379 +process 376 (p p-bar)->V h1-> ll + X where h1 is SM-like ([hep-ex] arXiv:1107.1268 (D0)) -process 380 +process 377 (p p-bar)->V h2-> ll + X where h2 is SM-like ([hep-ex] arXiv:1107.1268 (D0)) -process 381 +process 378 (p p-bar)->V h3-> ll + X where h3 is SM-like ([hep-ex] arXiv:1107.1268 (D0)) ************************************************************** CMS-PAS-HIG-13-009 -process 382 +process 379 (p p)->W(h1)->W W W where h1 is SM-like (CMS-PAS-HIG-13-009) -process 383 +process 380 (p p)->W(h2)->W W W where h2 is SM-like (CMS-PAS-HIG-13-009) -process 384 +process 381 (p p)->W(h3)->W W W where h3 is SM-like (CMS-PAS-HIG-13-009) ************************************************************** CMS-PAS-HIG-12-006 -process 385 +process 382 (p p)->W(h1)->W tau tau (CMS-PAS-HIG-12-006) -process 386 +process 383 (p p)->W(h2)->W tau tau (CMS-PAS-HIG-12-006) -process 387 +process 384 (p p)->W(h3)->W tau tau (CMS-PAS-HIG-12-006) ************************************************************** CMS-PAS-HIG-12-051 -process 388 +process 385 (p p)->V(h1)->V tau tau (CMS-PAS-HIG-12-051) -process 389 +process 386 (p p)->V(h2)->V tau tau (CMS-PAS-HIG-12-051) -process 390 +process 387 (p p)->V(h3)->V tau tau (CMS-PAS-HIG-12-051) ************************************************************** ATLAS-CONF-2012-078 -process 391 +process 388 (p p)->W(h1)->W W W where h1 is SM-like (ATLAS-CONF-2012-078) -process 392 +process 389 (p p)->W(h2)->W W W where h2 is SM-like (ATLAS-CONF-2012-078) -process 393 +process 390 (p p)->W(h3)->W W W where h3 is SM-like (ATLAS-CONF-2012-078) ************************************************************** D0 Note 6295 -process 394 +process 391 (p p-bar)->h1+...->gamma gamma+... where h1 is SM-like (D0 Note 6295) -process 395 +process 392 (p p-bar)->h2+...->gamma gamma+... where h2 is SM-like (D0 Note 6295) -process 396 +process 393 (p p-bar)->h3+...->gamma gamma+... where h3 is SM-like (D0 Note 6295) ************************************************************** [hep-ex] arXiv:0901.1887 (D0) -process 397 +process 394 (p p-bar)->h1+...->gamma gamma+... where h1 is SM-like ([hep-ex] arXiv:0901.1887 (D0)) -process 398 +process 395 (p p-bar)->h2+...->gamma gamma+... where h2 is SM-like ([hep-ex] arXiv:0901.1887 (D0)) -process 399 +process 396 (p p-bar)->h3+...->gamma gamma+... where h3 is SM-like ([hep-ex] arXiv:0901.1887 (D0)) ************************************************************** CDF Note 10485 -process 400 +process 397 (p p-bar)->h1+...->gamma gamma+... where h1 is SM-like (CDF Note 10485) -process 401 +process 398 (p p-bar)->h2+...->gamma gamma+... where h2 is SM-like (CDF Note 10485) -process 402 +process 399 (p p-bar)->h3+...->gamma gamma+... where h3 is SM-like (CDF Note 10485) ************************************************************** [hep-ex] arXiv:1107.4960 (TEVNPHWG) -process 403 +process 400 (p p-bar)->h1+...->gamma gamma+... where h1 is SM-like ([hep-ex] arXiv:1107.4960 (TEVNPHWG)) -process 404 +process 401 (p p-bar)->h2+...->gamma gamma+... where h2 is SM-like ([hep-ex] arXiv:1107.4960 (TEVNPHWG)) -process 405 +process 402 (p p-bar)->h3+...->gamma gamma+... where h3 is SM-like ([hep-ex] arXiv:1107.4960 (TEVNPHWG)) ************************************************************** [hep-ex] arXiv:1202.1414 (ATLAS) -process 406 +process 403 (p p)->h1+...->gamma gamma+... where h1 is SM-like ([hep-ex] arXiv:1202.1414 (ATLAS)) -process 407 +process 404 (p p)->h2+...->gamma gamma+... where h2 is SM-like ([hep-ex] arXiv:1202.1414 (ATLAS)) -process 408 +process 405 (p p)->h3+...->gamma gamma+... where h3 is SM-like ([hep-ex] arXiv:1202.1414 (ATLAS)) ************************************************************** ATLAS-CONF-2012-168 -process 409 +process 406 (p p)->h1+...->gamma gamma+... where h1 is SM-like (ATLAS-CONF-2012-168) -process 410 +process 407 (p p)->h2+...->gamma gamma+... where h2 is SM-like (ATLAS-CONF-2012-168) -process 411 +process 408 (p p)->h3+...->gamma gamma+... where h3 is SM-like (ATLAS-CONF-2012-168) ************************************************************** [hep-ex] arXiv:1407.6583 -process 412 +process 409 (p p)->h1/VBF/Wh1/Zh1/tth1->gamma gamma ([hep-ex] arXiv:1407.6583) -process 413 +process 410 (p p)->h2/VBF/Wh2/Zh2/tth2->gamma gamma ([hep-ex] arXiv:1407.6583) -process 414 +process 411 (p p)->h3/VBF/Wh3/Zh3/tth3->gamma gamma ([hep-ex] arXiv:1407.6583) ************************************************************** CMS-PAS-HIG-13-001 -process 415 +process 412 (p p)->h1+...->gamma gamma+... where h1 is SM-like (CMS-PAS-HIG-13-001) -process 416 +process 413 (p p)->h2+...->gamma gamma+... where h2 is SM-like (CMS-PAS-HIG-13-001) -process 417 +process 414 (p p)->h3+...->gamma gamma+... where h3 is SM-like (CMS-PAS-HIG-13-001) ************************************************************** [hep-ex] arXiv:1307.5515 (CMS) -process 418 +process 415 (p p)->h1+...->gamma Z+... where h1 is SM-like ([hep-ex] arXiv:1307.5515 (CMS)) -process 419 +process 416 (p p)->h2+...->gamma Z+... where h2 is SM-like ([hep-ex] arXiv:1307.5515 (CMS)) -process 420 +process 417 (p p)->h3+...->gamma Z+... where h3 is SM-like ([hep-ex] arXiv:1307.5515 (CMS)) ************************************************************** [hep-ex] arXiv:1402.3051 (ATLAS) -process 421 +process 418 (p p)->h1+...->gamma Z+... where h1 is SM-like ([hep-ex] arXiv:1402.3051 (ATLAS)) -process 422 +process 419 (p p)->h2+...->gamma Z+... where h2 is SM-like ([hep-ex] arXiv:1402.3051 (ATLAS)) -process 423 +process 420 (p p)->h3+...->gamma Z+... where h3 is SM-like ([hep-ex] arXiv:1402.3051 (ATLAS)) ************************************************************** [hep-ex] arXiv:1106.4885 (D0) -process 424 +process 421 (p p-bar)->h1(b/b-bar)->(tau tau) (b/b-bar) ([hep-ex] arXiv:1106.4885 (D0)) -process 425 +process 422 (p p-bar)->h2(b/b-bar)->(tau tau) (b/b-bar) ([hep-ex] arXiv:1106.4885 (D0)) -process 426 +process 423 (p p-bar)->h3(b/b-bar)->(tau tau) (b/b-bar) ([hep-ex] arXiv:1106.4885 (D0)) ************************************************************** D0 Note 6083 -process 427 +process 424 (p p-bar)->h1(b/b-bar)->(tau tau) (b/b-bar) (D0 Note 6083) -process 428 +process 425 (p p-bar)->h2(b/b-bar)->(tau tau) (b/b-bar) (D0 Note 6083) -process 429 +process 426 (p p-bar)->h3(b/b-bar)->(tau tau) (b/b-bar) (D0 Note 6083) ************************************************************** D0 Note 5739 -process 430 +process 427 (p p-bar)->t t-bar h1->t t-bar b b-bar (D0 Note 5739) -process 431 +process 428 (p p-bar)->t t-bar h2->t t-bar b b-bar (D0 Note 5739) -process 432 +process 429 (p p-bar)->t t-bar h3->t t-bar b b-bar (D0 Note 5739) ************************************************************** CDF Note 10574 -process 433 +process 430 (p p-bar)->t t-bar h1->t t-bar b b-bar (CDF Note 10574) -process 434 +process 431 (p p-bar)->t t-bar h2->t t-bar b b-bar (CDF Note 10574) -process 435 +process 432 (p p-bar)->t t-bar h3->t t-bar b b-bar (CDF Note 10574) ************************************************************** ATLAS-CONF-2012-135 -process 436 +process 433 (p p)->t t-bar h1->t t-bar b b-bar (ATLAS-CONF-2012-135) -process 437 +process 434 (p p)->t t-bar h2->t t-bar b b-bar (ATLAS-CONF-2012-135) -process 438 +process 435 (p p)->t t-bar h3->t t-bar b b-bar (ATLAS-CONF-2012-135) ************************************************************** CMS-PAS-HIG-12-025 -process 439 +process 436 (p p)->t t-bar h1->t t-bar b b-bar (CMS-PAS-HIG-12-025) -process 440 +process 437 (p p)->t t-bar h2->t t-bar b b-bar (CMS-PAS-HIG-12-025) -process 441 +process 438 (p p)->t t-bar h3->t t-bar b b-bar (CMS-PAS-HIG-12-025) ************************************************************** [hep-ex] arXiv:0806.0611 (D0) -process 442 +process 439 (p p-bar)->h1->Z gamma ([hep-ex] arXiv:0806.0611 (D0)) -process 443 +process 440 (p p-bar)->h2->Z gamma ([hep-ex] arXiv:0806.0611 (D0)) -process 444 +process 441 (p p-bar)->h3->Z gamma ([hep-ex] arXiv:0806.0611 (D0)) ************************************************************** [hep-ex] arXiv:0908.1811 (D0) -process 445 +process 442 t->(H1+)b->(2 quarks) b ([hep-ex] arXiv:0908.1811 (D0)) ************************************************************** [hep-ex] arXiv:0907.1269 (CDF) lower mass -process 446 +process 443 t->(H1+)b->(c s) b([hep-ex] arXiv:0907.1269 (CDF) lower mass) ************************************************************** [hep-ex] arXiv:0907.1269 (CDF) higher mass -process 447 +process 444 t->(H1+)b->(c s) b([hep-ex] arXiv:0907.1269 (CDF) higher mass) ************************************************************** CDF Note 7712 -process 448 +process 445 t->(H1+)b->tau nu b (CDF Note 7712) ************************************************************** CDF Note 8353 -process 449 +process 446 t->(H1+)b->tau nu b (CDF Note 8353) ************************************************************** [hep-ex] arXiv:0908.1811 (D0) -process 450 +process 447 t->(H1+)b->tau nu b ([hep-ex] arXiv:0908.1811 (D0)) ************************************************************** ATLAS-CONF-2011-094 -process 451 +process 448 t->(H1+)b->(c s) b(ATLAS-CONF-2011-094) ************************************************************** [hep-ex] arXiv:1204.2760 (ATLAS) -process 452 +process 449 t->(H1+)b->tau nu b ([hep-ex] arXiv:1204.2760 (ATLAS)) ************************************************************** ATLAS-CONF-2014-050 -process 453 +process 450 t->(H1+)b->tau nu b (ATLAS-CONF-2014-050) ************************************************************** CMS-PAS-HIG-14-020 -process 454 +process 451 t->(H1+)b->tau nu b (CMS-PAS-HIG-14-020) ************************************************************** CMS-PAS-HIG-13-035 -process 455 +process 452 t->(H1+)b->(c s) b(CMS-PAS-HIG-13-035) ************************************************************** [hep-ex] arXiv:0905.3381, table I (D0) -process 456 +process 453 *** -process 457 +process 454 (p p-bar)->h1->h2 h2->mu mu mu mu ([hep-ex] arXiv:0905.3381, table I (D0)) -process 458 +process 455 (p p-bar)->h1->h3 h3->mu mu mu mu ([hep-ex] arXiv:0905.3381, table I (D0)) ------------------------------------------------------------ -process 459 +process 456 (p p-bar)->h2->h1 h1->mu mu mu mu ([hep-ex] arXiv:0905.3381, table I (D0)) -process 460 +process 457 *** -process 461 +process 458 (p p-bar)->h2->h3 h3->mu mu mu mu ([hep-ex] arXiv:0905.3381, table I (D0)) ------------------------------------------------------------ -process 462 +process 459 (p p-bar)->h3->h1 h1->mu mu mu mu ([hep-ex] arXiv:0905.3381, table I (D0)) -process 463 +process 460 (p p-bar)->h3->h2 h2->mu mu mu mu ([hep-ex] arXiv:0905.3381, table I (D0)) -process 464 +process 461 *** ************************************************************** [hep-ex] arXiv:0905.3381, table II (D0) -process 465 +process 462 *** -process 466 +process 463 (p p-bar)->h1->h2 h2->tau tau mu mu ([hep-ex] arXiv:0905.3381, table II (D0)) -process 467 +process 464 (p p-bar)->h1->h3 h3->tau tau mu mu ([hep-ex] arXiv:0905.3381, table II (D0)) ------------------------------------------------------------ -process 468 +process 465 (p p-bar)->h2->h1 h1->tau tau mu mu ([hep-ex] arXiv:0905.3381, table II (D0)) -process 469 +process 466 *** -process 470 +process 467 (p p-bar)->h2->h3 h3->tau tau mu mu ([hep-ex] arXiv:0905.3381, table II (D0)) ------------------------------------------------------------ -process 471 +process 468 (p p-bar)->h3->h1 h1->tau tau mu mu ([hep-ex] arXiv:0905.3381, table II (D0)) -process 472 +process 469 (p p-bar)->h3->h2 h2->tau tau mu mu ([hep-ex] arXiv:0905.3381, table II (D0)) -process 473 +process 470 *** ************************************************************** D0 Note 6227 -process 474 +process 471 (p p-bar)->h1(b/b-bar)->(b b-bar) (b/b-bar) or (tau tau) (b/b-bar) (D0 Note 6227) ------------------------------------------------------------ -process 475 +process 472 (p p-bar)->h2(b/b-bar)->(b b-bar) (b/b-bar) or (tau tau) (b/b-bar) (D0 Note 6227) ------------------------------------------------------------ -process 476 +process 473 (p p-bar)->h3(b/b-bar)->(b b-bar) (b/b-bar) or (tau tau) (b/b-bar) (D0 Note 6227) ************************************************************** [hep-ex] arXiv:1406.5053 (ATLAS) -process 477 +process 474 *** -process 478 +process 475 (p p)->h1->h2 h2->gamma gamma b b, where h2 is SM-like around 125 GeV ([hep-ex] arXiv:1406.5053 (ATLAS)) -process 479 +process 476 (p p)->h1->h3 h3->gamma gamma b b, where h3 is SM-like around 125 GeV ([hep-ex] arXiv:1406.5053 (ATLAS)) ------------------------------------------------------------ -process 480 +process 477 (p p)->h2->h1 h1->gamma gamma b b, where h1 is SM-like around 125 GeV ([hep-ex] arXiv:1406.5053 (ATLAS)) -process 481 +process 478 *** -process 482 +process 479 (p p)->h2->h3 h3->gamma gamma b b, where h3 is SM-like around 125 GeV ([hep-ex] arXiv:1406.5053 (ATLAS)) ------------------------------------------------------------ -process 483 +process 480 (p p)->h3->h1 h1->gamma gamma b b, where h1 is SM-like around 125 GeV ([hep-ex] arXiv:1406.5053 (ATLAS)) -process 484 +process 481 (p p)->h3->h2 h2->gamma gamma b b, where h2 is SM-like around 125 GeV ([hep-ex] arXiv:1406.5053 (ATLAS)) -process 485 +process 482 *** ************************************************************** CMS-PAS-HIG-13-032 -process 486 +process 483 *** -process 487 +process 484 (p p)->h1->h2 h2->gamma gamma b b, where h2 lies around 125 GeV (CMS-PAS-HIG-13-032) -process 488 +process 485 (p p)->h1->h3 h3->gamma gamma b b, where h3 lies around 125 GeV (CMS-PAS-HIG-13-032) ------------------------------------------------------------ -process 489 +process 486 (p p)->h2->h1 h1->gamma gamma b b, where h1 lies around 125 GeV (CMS-PAS-HIG-13-032) -process 490 +process 487 *** -process 491 +process 488 (p p)->h2->h3 h3->gamma gamma b b, where h3 lies around 125 GeV (CMS-PAS-HIG-13-032) ------------------------------------------------------------ -process 492 +process 489 (p p)->h3->h1 h1->gamma gamma b b, where h1 lies around 125 GeV (CMS-PAS-HIG-13-032) -process 493 +process 490 (p p)->h3->h2 h2->gamma gamma b b, where h2 lies around 125 GeV (CMS-PAS-HIG-13-032) -process 494 +process 491 *** ************************************************************** CMS-PAS-HIG-14-013 -process 495 +process 492 *** -process 496 +process 493 (p p)->h1->h2 h2->b b b b, where h2 lies around 125 GeV (CMS-PAS-HIG-14-013) -process 497 +process 494 (p p)->h1->h3 h3->b b b b, where h3 lies around 125 GeV (CMS-PAS-HIG-14-013) ------------------------------------------------------------ -process 498 +process 495 (p p)->h2->h1 h1->b b b b, where h1 lies around 125 GeV (CMS-PAS-HIG-14-013) -process 499 +process 496 *** -process 500 +process 497 (p p)->h2->h3 h3->b b b b, where h3 lies around 125 GeV (CMS-PAS-HIG-14-013) ------------------------------------------------------------ -process 501 +process 498 (p p)->h3->h1 h1->b b b b, where h1 lies around 125 GeV (CMS-PAS-HIG-14-013) -process 502 +process 499 (p p)->h3->h2 h2->b b b b, where h2 lies around 125 GeV (CMS-PAS-HIG-14-013) -process 503 +process 500 *** ************************************************************** CMS-PAS-HIG-14-006 -process 504 +process 501 (p p)->h1/VBF/Wh1/Zh1/tth1->gamma gamma (including widths effects)(CMS-PAS-HIG-14-006) ------------------------------------------------------------ -process 505 +process 502 (p p)->h2/VBF/Wh2/Zh2/tth2->gamma gamma (including widths effects)(CMS-PAS-HIG-14-006) ------------------------------------------------------------ -process 506 +process 503 (p p)->h3/VBF/Wh3/Zh3/tth3->gamma gamma (including widths effects)(CMS-PAS-HIG-14-006) ************************************************************** [hep-ex] arXiv:1408.3316 (CMS) -process 507 +process 504 (pp)->h1->tautau, using -2ln(L) reconstruction ([hep-ex] arXiv:1408.3316 (CMS)) -process 508 +process 505 (pp)->h2->tautau, using -2ln(L) reconstruction ([hep-ex] arXiv:1408.3316 (CMS)) -process 509 +process 506 (pp)->h3->tautau, using -2ln(L) reconstruction ([hep-ex] arXiv:1408.3316 (CMS)) Index: trunk/HiggsBounds_KW/example_data/HB_randomtest50points_HiggsBounds_results.dat-for-comparison =================================================================== --- trunk/HiggsBounds_KW/example_data/HB_randomtest50points_HiggsBounds_results.dat-for-comparison (revision 508) +++ trunk/HiggsBounds_KW/example_data/HB_randomtest50points_HiggsBounds_results.dat-for-comparison (revision 509) @@ -1,90 +1,90 @@ - # generated with HiggsBounds version 4.2.0 on 12.12.2014 at 17:27 + # generated with HiggsBounds version 4.2.1 on 27.05.2015 at 16:22 # settings: LandH, part # # column abbreviations # n : line id of input # Mh(i) : Neutral Higgs boson masses in GeV # Mhplus(i) : Charged Higgs boson masses in GeV # HBresult : scenario allowed flag (1: allowed, 0: excluded, -1: unphysical) # chan : most sensitive channel (see below). chan=0 if no channel applies # obsratio : ratio [sig x BR]_model/[sig x BR]_limit (<1: allowed, >1: excluded) # ncomb : number of Higgs bosons combined in most sensitive channel # additional : optional additional data stored in <prefix>additional.dat (e.g. tan beta) # # channel numbers used in this file # 4 : (e e)->(h1)Z->(tau tau)Z (hep-ex/0602042, table 14c (LEP)) # 7 : (e e)->(h1)Z->(...)Z (hep-ex/0206022 (OPAL)) # 8 : (e e)->(h2)Z->(...)Z (hep-ex/0206022 (OPAL)) # 9 : (e e)->(h3)Z->(...)Z (hep-ex/0206022 (OPAL)) # 15 : (e e)->(h3)Z->(gamma gamma)Z (LHWG Note 2002-02) # 18 : (e e)->(h3)Z->(2 jets)Z (LHWG (unpublished)) # 21 : (e e)->(h3)Z->(2 jets)Z (hep-ex/0107034 (LHWG)) # 85 : (ee)->(h1 h1)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) # 89 : (ee)->(h2 h2)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) # 93 : (ee)->(h3 h3)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) # 131 : (p p-bar)->Z(h2)->l l (b b-bar) (CDF Note 10799) # 172 : (p p)->h1(VBF)->V (invisible) ([hep-ex] arXiv:1404.1344 (CMS)) # 192 : (p p-bar)->h3->W W (CDF Note 10599) # 228 : (p p)->h3(VBF)->WW (CMS-PAS-HIG-13-022) # 268 : (p p)->h1/ggF h->Z Z-> l l l l (ATLAS-CONF-2013-013) # 270 : (p p)->h3/ggF h->Z Z-> l l l l (ATLAS-CONF-2013-013) # 271 : (p p)->h1/VBF/V h->Z Z-> l l l l (ATLAS-CONF-2013-013) # 273 : (p p)->h3/VBF/V h->Z Z-> l l l l (ATLAS-CONF-2013-013) - # 412 : (p p)->h1/VBF/Wh1/Zh1/tth1->gamma gamma ([hep-ex] arXiv:1407.6583) - # 413 : (p p)->h2/VBF/Wh2/Zh2/tth2->gamma gamma ([hep-ex] arXiv:1407.6583) - # 414 : (p p)->h3/VBF/Wh3/Zh3/tth3->gamma gamma ([hep-ex] arXiv:1407.6583) - # 508 :(pp)->h2->tautau, using -2ln(L) reconstruction ([hep-ex] arXiv:1408.3316 (CMS)) + # 409 : (p p)->h1/VBF/Wh1/Zh1/tth1->gamma gamma ([hep-ex] arXiv:1407.6583) + # 410 : (p p)->h2/VBF/Wh2/Zh2/tth2->gamma gamma ([hep-ex] arXiv:1407.6583) + # 411 : (p p)->h3/VBF/Wh3/Zh3/tth3->gamma gamma ([hep-ex] arXiv:1407.6583) + # 505 :(pp)->h2->tautau, using -2ln(L) reconstruction ([hep-ex] arXiv:1408.3316 (CMS)) # (for full list of processes, see Key.dat) # #cols: n Mh(1) Mh(2) Mh(3) Mhplus(1) HBresult chan obsratio ncomb additional(1) additional(2) # - 1 359.121 159.618 337.305 71.6423 0 413 514689. 1 0.00000 0.592460 - 2 83.8032 49.2839 220.782 357.500 0 414 0.165707E+07 1 0.00000 0.00000 - 3 85.8826 249.094 179.329 238.330 0 508 29127.1 1 0.00000 0.00000 + 1 359.121 159.618 337.305 71.6423 0 410 514689. 1 0.00000 0.592460 + 2 83.8032 49.2839 220.782 357.500 0 411 0.165707E+07 1 0.00000 0.00000 + 3 85.8826 249.094 179.329 238.330 0 505 29127.1 1 0.00000 0.00000 4 127.520 164.372 55.4257 322.887 0 15 15141.7 1 0.00000 0.294416E-01 5 70.6587 359.723 130.202 6.50796 0 7 154123. 1 0.00000 0.00000 - 6 169.400 70.6569 323.343 41.3798 0 413 17154.1 1 0.333513 0.802317 + 6 169.400 70.6569 323.343 41.3798 0 410 17154.1 1 0.333513 0.802317 7 38.1288 47.7534 112.361 273.425 0 18 29.4229 1 0.00000 0.670977 - 8 137.482 89.2260 191.735 26.2198 0 414 39689.7 1 0.678461E-01 0.00000 + 8 137.482 89.2260 191.735 26.2198 0 411 39689.7 1 0.678461E-01 0.00000 9 57.2973 277.236 120.915 345.145 0 85 349.785 1 0.419713 0.00000 10 269.812 185.721 161.594 234.695 0 271 148.547 1 0.258086 0.322748 - 11 29.5216 264.171 200.460 337.761 0 414 350544. 1 0.00000 0.528913 + 11 29.5216 264.171 200.460 337.761 0 411 350544. 1 0.00000 0.528913 12 282.543 48.0135 273.487 137.955 0 172 884.031 1 0.00000 0.00000 - 13 321.618 57.8368 108.141 58.0303 0 414 0.495151E+07 1 0.579861 0.210765 - 14 25.3174 86.0196 215.979 50.9341 0 414 23428.0 1 0.490045 0.671123 - 15 182.003 168.197 239.773 353.488 0 414 1664.70 1 0.257430 0.241756 - 16 172.629 170.290 331.271 213.331 0 412 13344.0 1 0.256373 0.134367 - 17 43.1592 7.10876 334.029 136.449 0 414 21791.8 1 0.412981 0.00000 - 18 260.351 241.117 52.8639 236.306 0 412 42705.3 1 0.981251 0.00000 - 19 184.389 201.275 93.1450 17.1938 0 413 248082. 1 0.339361 0.00000 - 20 318.588 182.282 96.7497 163.509 0 412 18750.2 1 0.00000 0.00000 + 13 321.618 57.8368 108.141 58.0303 0 411 0.495151E+07 1 0.579861 0.210765 + 14 25.3174 86.0196 215.979 50.9341 0 411 23428.0 1 0.490045 0.671123 + 15 182.003 168.197 239.773 353.488 0 411 1664.70 1 0.257430 0.241756 + 16 172.629 170.290 331.271 213.331 0 409 13344.0 1 0.256373 0.134367 + 17 43.1592 7.10876 334.029 136.449 0 411 21791.8 1 0.412981 0.00000 + 18 260.351 241.117 52.8639 236.306 0 409 42705.3 1 0.981251 0.00000 + 19 184.389 201.275 93.1450 17.1938 0 410 248082. 1 0.339361 0.00000 + 20 318.588 182.282 96.7497 163.509 0 409 18750.2 1 0.00000 0.00000 21 116.354 76.5644 220.670 2.32286 0 270 18581.5 1 0.996861 0.345883 22 42.4572 17.0286 95.6197 93.7070 0 7 81126.2 1 0.00000 0.508411 23 267.868 323.640 297.323 33.2555 0 273 1652.60 1 0.942210 0.00000 24 195.062 277.485 286.385 173.057 0 270 5887.95 1 0.495710 0.293892 25 63.7171 236.923 179.568 247.528 0 228 677.382 1 0.570381E-02 0.00000 26 201.333 154.946 40.1986 78.0106 0 9 33794.8 1 0.00000 0.183563 - 27 316.921 99.1857 134.244 90.8209 0 412 163.540 1 0.00000 0.00000 + 27 316.921 99.1857 134.244 90.8209 0 409 163.540 1 0.00000 0.00000 28 43.1417 109.812 49.9498 358.450 0 131 124.850 1 0.00000 0.389621 29 32.9300 2.50641 307.458 29.2709 0 7 194769. 1 0.00000 0.00000 - 30 179.403 186.978 174.798 89.4833 0 414 3751.19 1 0.326535 0.00000 - 31 129.581 28.5000 253.953 353.162 0 414 288685. 1 0.665685 0.198533 + 30 179.403 186.978 174.798 89.4833 0 411 3751.19 1 0.326535 0.00000 + 31 129.581 28.5000 253.953 353.162 0 411 288685. 1 0.665685 0.198533 32 209.172 99.8650 35.5228 337.892 0 268 251.501 1 0.443801 0.00000 - 33 28.7356 264.683 166.743 258.544 0 414 6287.95 1 0.00000 0.785404E-01 + 33 28.7356 264.683 166.743 258.544 0 411 6287.95 1 0.00000 0.785404E-01 34 173.633 330.726 107.045 225.501 0 21 1473.65 1 0.324846 0.00000 - 35 54.6512 32.6453 283.236 294.189 0 414 813097. 1 0.00000 0.938392 - 36 146.064 285.733 149.044 71.6345 0 412 44036.5 1 0.897355 0.00000 + 35 54.6512 32.6453 283.236 294.189 0 411 813097. 1 0.00000 0.938392 + 36 146.064 285.733 149.044 71.6345 0 409 44036.5 1 0.897355 0.00000 37 24.7264 115.334 203.394 204.786 0 270 2744.03 1 0.528866E-02 0.356043 38 85.8442 307.707 52.0641 243.525 0 4 91729.3 1 0.00000 0.188661 - 39 259.486 349.551 16.4252 206.723 0 412 129721. 1 0.111999 0.374511 + 39 259.486 349.551 16.4252 206.723 0 409 129721. 1 0.111999 0.374511 40 66.0497 66.4642 133.639 295.482 0 89 6279.38 1 0.00000 0.00000 - 41 207.530 321.571 285.256 100.629 0 413 1669.88 1 0.00000 0.00000 - 42 2.33050 206.329 261.763 340.230 0 414 3984.89 1 0.00000 0.00000 + 41 207.530 321.571 285.256 100.629 0 410 1669.88 1 0.00000 0.00000 + 42 2.33050 206.329 261.763 340.230 0 411 3984.89 1 0.00000 0.00000 43 259.148 77.5749 352.402 203.247 0 8 7689.18 1 0.00000 0.162866 44 0.530648E-01 11.4247 52.8747 166.918 -1 93 0.127099E-08 1 0.00000 0.128263 45 187.493 107.107 173.738 247.540 0 192 379.124 1 0.00000 0.444294 - 46 199.313 231.562 168.755 84.5395 0 413 6860.53 1 0.00000 0.815096 - 47 7.13980 179.589 354.651 182.860 0 414 2518.16 1 0.00000 0.00000 - 48 147.464 316.808 236.643 232.922 0 412 0.121490E+07 1 0.00000 0.145378 - 49 241.435 179.680 156.465 256.995 0 412 62640.9 1 0.00000 0.183243 - 50 280.002 215.162 175.263 178.551 0 413 60262.5 1 0.673905 0.00000 + 46 199.313 231.562 168.755 84.5395 0 410 6860.53 1 0.00000 0.815096 + 47 7.13980 179.589 354.651 182.860 0 411 2518.16 1 0.00000 0.00000 + 48 147.464 316.808 236.643 232.922 0 409 0.121490E+07 1 0.00000 0.145378 + 49 241.435 179.680 156.465 256.995 0 409 62640.9 1 0.00000 0.183243 + 50 280.002 215.162 175.263 178.551 0 410 60262.5 1 0.673905 0.00000 Index: trunk/HiggsBounds_KW/S95tables_type1.F90 =================================================================== --- trunk/HiggsBounds_KW/S95tables_type1.F90 (revision 508) +++ trunk/HiggsBounds_KW/S95tables_type1.F90 (revision 509) @@ -1,4503 +1,4503 @@ ! This file is part of HiggsBounds ! -KW !****************************************************************** module S95tables_type1 !****************************************************************** implicit none !table type 1----------------------------- type table1 integer :: id,nx,particle_x !see usefulbits.f90 for key to particle codes n.b. they're NOT pdg character(LEN=45) :: label character(LEN=100) :: desc character(LEN=3) :: expt double precision :: lumi, energy double precision :: xmax,xmin,sep,deltax integer :: SMlike integer :: llh double precision, allocatable :: dat(:,:) !in dat(a,b), a=row, b=1,2 for obs,pred end type !------------------------------------------ integer,parameter :: file_id_1=10 !same as file_id_common in usefulbits.f90 contains !************************************************************ subroutine initializetables_type1_blank(tablet1) !*********************************************************** ! still leaves dat unallocated integer:: i type(table1) :: tablet1(:) do i=lbound(tablet1,dim=1),ubound(tablet1,dim=1) tablet1(i)%id = -1 tablet1(i)%nx = -1 tablet1(i)%particle_x = -1 tablet1(i)%label = '' tablet1(i)%desc = '' tablet1(i)%expt = '' tablet1(i)%lumi = -1.0D0 tablet1(i)%energy = -1.0D0 tablet1(i)%xmax = -1.0D0 tablet1(i)%xmin = -1.0D0 tablet1(i)%sep = -1.0D0 tablet1(i)%deltax = -1.0D0 tablet1(i)%SMlike = 0 tablet1(i)%llh = 0 enddo end subroutine initializetables_type1_blank !************************************************************ subroutine copy_type1(tablet1_orig,tablet1_copy) !*********************************************************** ! note tablet1_1,tablet1_2 are not arrays ! still leaves dat uncopied type(table1) :: tablet1_orig type(table1) :: tablet1_copy tablet1_copy%id = tablet1_orig%id tablet1_copy%nx = tablet1_orig%nx tablet1_copy%particle_x = tablet1_orig%particle_x tablet1_copy%label = tablet1_orig%label tablet1_copy%expt = tablet1_orig%expt tablet1_copy%xmax = tablet1_orig%xmax tablet1_copy%xmin = tablet1_orig%xmin tablet1_copy%sep = tablet1_orig%sep tablet1_copy%deltax = tablet1_orig%deltax end subroutine copy_type1 !*********************************************************** function t1elementnumberfromid(t1,id) !--------------------------------------input type(table1), intent(in) :: t1(:) integer, intent(in) :: id !-----------------------------------function integer :: t1elementnumberfromid !-----------------------------------internal integer :: n,x !------------------------------------------- n=0 do x=lbound(t1,dim=1),ubound(t1,dim=1) if(t1(x)%id.eq.id)then n=n+1 t1elementnumberfromid=x endif enddo if(n.ne.1)stop'problem in function t3elementnumberfromid 1' end function t1elementnumberfromid !************************************************************ subroutine initializetables1(S95_t1) !*********************************************************** ! fills S95_t1 !*********************************************************** use store_pathname use usefulbits, only: Hneut,Hplus,file_id_common2 implicit none !--------------------------------------input type(table1) :: S95_t1(:) !-----------------------------------internal logical :: newtables integer :: x,xbeg,xend character(len=100),allocatable :: filename(:) character(LEN=pathname_length+150) :: fullfilename integer :: col integer :: ios !------------------------------------------- xbeg=lbound(S95_t1,dim=1) xend=ubound(S95_t1,dim=1) allocate(filename(xbeg:xend)) x=xbeg-1 !instead, could read in the values of xmin,xmax,sep from the !files, but it's kinda nice having them all here to refer to newtables=.True. ! i.e. use the recommended LEP single Higgs tables if(newtables)then x=x+1 S95_t1(x)%id=142 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0602042, table 14b (LEP)' ! table 14b S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=12.0D0 S95_t1(x)%xmax=120.0D0 S95_t1(x)%sep=0.5D0 filename(x)='lep210_hbb' x=x+1 S95_t1(x)%id=143 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0602042, table 14c (LEP)' ! table 14c S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=4.0D0 S95_t1(x)%xmax=120.0D0 S95_t1(x)%sep=0.5D0 filename(x)='lep210_htt_interpol' else write(*,*)'WARNING: using old LEP tables' x=x+1 S95_t1(x)%id=142 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='LEP table 14b' ! table 14b S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=1.0D0 S95_t1(x)%xmax=140.0D0 S95_t1(x)%sep=0.1D0 filename(x)='old-s95_h2z_bbz' x=x+1 S95_t1(x)%id=143 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='LEP table 14c' ! table 14c S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=1.0D0 S95_t1(x)%xmax=140.0D0 S95_t1(x)%sep=0.1D0 filename(x)='old-s95_h2z_ttz' endif x=x+1 S95_t1(x)%id=300 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0206022 (OPAL)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=1.0D0 S95_t1(x)%xmax=100.0D0 S95_t1(x)%sep=1.0D0 filename(x)='lep_decaymodeindep' x=x+1 S95_t1(x)%id=400 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0107032v1 (LEP)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=90.0D0 S95_t1(x)%xmax=118.0D0 S95_t1(x)%sep=1.0D0 filename(x)='LEP_h-invisible' x=x+1 S95_t1(x)%id=500 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='LHWG Note 2002-02' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=20.0D0 S95_t1(x)%xmax=116.0D0 S95_t1(x)%sep=2.0D0 filename(x)='LEP_h-gammagamma' x=x+1 S95_t1(x)%id=600 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='LHWG (unpublished)'!uses hep-ex/0510022,hep-ex/0205055,hep-ex/0312042,hep-ex/0408097 S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=20.0D0 S95_t1(x)%xmax=128.6D0 S95_t1(x)%sep=0.1D0 filename(x)='LEP_h-2jets' x=x+1 S95_t1(x)%id=601 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0107034 (LHWG)'!uses hep-ex/0510022,hep-ex/0205055,hep-ex/0312042,hep-ex/0408097 S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=60.0D0 S95_t1(x)%xmax=114.5D0 S95_t1(x)%sep=0.1D0 filename(x)='LEP_h-2jets_0107034' x=x+1 S95_t1(x)%id=711 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0410017 (DELPHI)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=12.0D0 S95_t1(x)%xmax=50.0D0 S95_t1(x)%sep=1.0D0 filename(x)='Delphi_yuk_h_bbbb' x=x+1 S95_t1(x)%id=713 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0410017 (DELPHI)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=12.0D0 S95_t1(x)%xmax=50.0D0 S95_t1(x)%sep=1.0D0 filename(x)='Delphi_yuk_a_bbbb' x=x+1 S95_t1(x)%id=721 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0410017 (DELPHI)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=4.0D0 S95_t1(x)%xmax=50.0D0 S95_t1(x)%sep=1.0D0 filename(x)='Delphi_yuk_h_bbtautau' x=x+1 S95_t1(x)%id=741 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0111010 (OPAL)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=4.0D0 S95_t1(x)%xmax=12.0D0 S95_t1(x)%sep=1.0D0 filename(x)='OPAL_yuk_h_bbtautau' x=x+1 S95_t1(x)%id=723 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0410017 (DELPHI)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=4.0D0 S95_t1(x)%xmax=50.0D0 S95_t1(x)%sep=1.0D0 filename(x)='Delphi_yuk_a_bbtautau' x=x+1 S95_t1(x)%id=743 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0111010 (OPAL)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=4.0D0 S95_t1(x)%xmax=12.0D0 S95_t1(x)%sep=1.0D0 filename(x)='OPAL_yuk_a_bbtautau' x=x+1 S95_t1(x)%id=731 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0410017 (DELPHI)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=4.0D0 S95_t1(x)%xmax=27.0D0 S95_t1(x)%sep=1.0D0 filename(x)='Delphi_yuk_h_tautautautau' x=x+1 S95_t1(x)%id=733 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0410017 (DELPHI)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=4.0D0 S95_t1(x)%xmax=26.0D0 S95_t1(x)%sep=1.0D0 filename(x)='Delphi_yuk_a_tautautautau' x=x+1 S95_t1(x)%id=402 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0401022 (Delphi)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=40.0D0 S95_t1(x)%xmax=114.0D0 S95_t1(x)%sep=2.0D0 filename(x)='Delphi_h-invisible' x=x+1 S95_t1(x)%id=403 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0501033 (L3)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=50.0D0 S95_t1(x)%xmax=110.0D0 S95_t1(x)%sep=5.0D0 filename(x)='L3_h-invisible' x=x+1 S95_t1(x)%id=401 S95_t1(x)%particle_x=Hneut S95_t1(x)%expt='LEP' S95_t1(x)%label='[hep-ex] arXiv:0707.0373 (OPAL)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=5.0D0 S95_t1(x)%xmax=115.0D0 S95_t1(x)%sep=5.0D0 filename(x)='OPAL_h-invisible' !x=x+1 !S95_t1(x)%id=803 !S95_t1(x)%particle_x=Hplus !S95_t1(x)%expt='LEP' !S95_t1(x)%label='[hep-ex] arxiv:0812.0267 (OPAL)' !S95_t1(x)%xmin=50.0D0 !S95_t1(x)%xmax=93.0D0 !S95_t1(x)%sep=1.0D0 !filename(x)='OPAL_HpHm_taunutaunu' !x=x+1 !S95_t1(x)%id=802 !S95_t1(x)%particle_x=Hplus !S95_t1(x)%expt='LEP' !S95_t1(x)%label='[hep-ex] arxiv:0812.0267 (OPAL)' !S95_t1(x)%xmin=50.0D0 !S95_t1(x)%xmax=93.0D0 !S95_t1(x)%sep=1.0D0 !filename(x)='OPAL_HpHm_qqtaunu' !x=x+1 !S95_t1(x)%id=801 !S95_t1(x)%particle_x=Hplus !S95_t1(x)%expt='LEP' !S95_t1(x)%label='[hep-ex] arxiv:0812.0267 (OPAL)' !S95_t1(x)%xmin=50.0D0 !S95_t1(x)%xmax=93.0D0 !S95_t1(x)%sep=1.0D0 !filename(x)='OPAL_HpHm_qqqq' x=x+1 S95_t1(x)%id=821 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0107031 (LHWG)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=60.0D0 S95_t1(x)%xmax=90.0D0 S95_t1(x)%sep=1.0D0 filename(x)='LEP_HpHm_qqqq' x=x+1 S95_t1(x)%id=811 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0404012 (Delphi)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=52.0D0 S95_t1(x)%xmax=94.0D0 S95_t1(x)%sep=2.0D0 filename(x)='Delphi_HpHm_qqqq' x=x+1 S95_t1(x)%id=813 S95_t1(x)%particle_x=Hplus S95_t1(x)%expt='LEP' S95_t1(x)%label='hep-ex/0404012 (Delphi)' S95_t1(x)%energy=0.208D0 S95_t1(x)%xmin=52.0D0 S95_t1(x)%xmax=94.0D0 S95_t1(x)%sep=2.0D0 filename(x)='Delphi_HpHm_taunutaunu' !----------------------- Z H -> 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' !----------------------- 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' !--------------- 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' !------------------------- 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=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' !------------------------- 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' !-------------------- 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=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' + 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' + 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' ! 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' ! 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' ! !-------------------- 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=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=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' !---------------- 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=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' !---------------------------------------------- !&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&& ! 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) ! 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_KW/minipaper.pdf =================================================================== Cannot display: file marked as a binary type. svn:mime-type = application/octet-stream Index: trunk/HiggsBounds_KW/example_programs/example-SM-results.dat-for-comparison =================================================================== --- trunk/HiggsBounds_KW/example_programs/example-SM-results.dat-for-comparison (revision 508) +++ trunk/HiggsBounds_KW/example_programs/example-SM-results.dat-for-comparison (revision 509) @@ -1,511 +1,511 @@ 90.000000000000000 0 1 5.3302631578947368 91.000000000000000 0 1 4.7556470588235289 92.000000000000000 0 1 4.6098285714285714 93.000000000000000 0 1 4.2145549738219898 94.000000000000000 0 1 3.7534579439252336 95.000000000000000 0 1 3.7985781990521326 96.000000000000000 0 1 3.6320909090909090 97.000000000000000 0 1 3.3755084745762711 98.000000000000000 0 1 3.4084978540772530 99.000000000000000 0 1 3.3127196652719668 100.00000000000000 0 1 3.6541666666666668 101.00000000000000 0 1 3.7235071090047396 102.00000000000000 0 1 3.6204629629629634 103.00000000000000 0 1 3.5380909090909087 104.00000000000000 0 1 3.4129515418502199 105.00000000000000 0 1 3.8748743718592964 106.00000000000000 0 1 3.4330941704035878 107.00000000000000 0 1 3.4865137614678896 108.00000000000000 0 1 3.3239647577092510 109.00000000000000 0 1 3.2566086956521740 110.00000000000000 0 1 3.0471311475409837 111.00000000000000 0 1 2.4514666666666667 112.00000000000000 0 1 2.1206413994169093 - 113.00000000000000 0 121 1.7792839384344921 + 113.00000000000000 0 120 1.7792839384344921 114.00000000000000 0 95 1.1961885842006004 115.00000000000000 0 95 1.2004970279413876 116.00000000000000 0 95 1.1286842469013403 117.00000000000000 0 95 1.1338030595359248 118.00000000000000 0 95 1.2225112179002253 119.00000000000000 0 95 1.3441046503432430 120.00000000000000 0 95 1.2019391029600341 121.00000000000000 1 95 0.98620570369389871 122.00000000000000 1 95 0.82237795890828636 123.00000000000000 1 95 0.77340322449180676 124.00000000000000 1 95 0.76162139668162809 125.00000000000000 1 95 0.78864919043579995 126.00000000000000 1 95 0.83893054992098637 127.00000000000000 1 95 0.91407955508674721 128.00000000000000 0 95 1.0245908260328052 129.00000000000000 0 95 1.2886573194836235 130.00000000000000 0 95 1.5408249089822430 131.00000000000000 0 76 1.2437718176309234 132.00000000000000 0 76 1.5600462535209194 133.00000000000000 0 76 1.8691340823476352 134.00000000000000 0 76 2.2624068970080025 135.00000000000000 0 76 2.9153966328876195 136.00000000000000 0 76 4.1665765794330083 137.00000000000000 0 76 5.4943731125074828 138.00000000000000 0 76 6.4100877122785409 139.00000000000000 0 76 7.1426554527698993 140.00000000000000 0 76 7.8122671808518840 141.00000000000000 0 76 7.9997523083302156 142.00000000000000 0 76 6.8963332748378994 143.00000000000000 0 76 4.6510143972482698 144.00000000000000 0 76 3.9998735221534196 145.00000000000000 0 76 3.9214478533437847 146.00000000000000 0 76 4.1839773018092439 147.00000000000000 0 76 4.6510348934161385 148.00000000000000 0 76 5.2630261959738203 149.00000000000000 0 76 5.6816930893825139 150.00000000000000 0 95 3.5335035117348004 151.00000000000000 0 95 3.4964526880234157 152.00000000000000 0 95 3.4964680385399833 153.00000000000000 0 95 3.6900169908431333 154.00000000000000 0 95 4.0322565941705024 155.00000000000000 0 95 4.6729199655687506 156.00000000000000 0 95 4.8544185903688799 157.00000000000000 0 95 5.0505839049546184 158.00000000000000 0 95 5.2632680292653733 159.00000000000000 0 95 5.1547735382500131 160.00000000000000 0 57 4.7171451425149691 161.00000000000000 0 95 4.9752688944270052 162.00000000000000 0 95 4.9020988733285034 163.00000000000000 0 57 4.7439666857426710 164.00000000000000 0 57 4.7529854748114007 165.00000000000000 0 57 4.7620422656874712 166.00000000000000 0 57 4.7620486547475060 167.00000000000000 0 57 4.7620573010812555 168.00000000000000 0 57 4.7620676424668869 169.00000000000000 0 57 4.7620791921781036 170.00000000000000 0 57 4.7620915309312624 171.00000000000000 0 95 5.0764170299209006 172.00000000000000 0 95 5.0254172922281946 173.00000000000000 0 95 4.9508008831544723 174.00000000000000 0 95 4.8783673778238921 175.00000000000000 0 95 4.8080221104211924 176.00000000000000 0 95 4.7396758401121337 177.00000000000000 0 95 4.6515083457380939 178.00000000000000 0 95 4.5875075868235715 179.00000000000000 0 95 4.3863099374738876 180.00000000000000 0 95 4.1844364841387396 181.00000000000000 0 95 4.2020235728315196 182.00000000000000 0 95 4.2556703665681850 183.00000000000000 0 95 4.3293640656750032 184.00000000000000 0 95 4.4056533238157849 185.00000000000000 0 95 4.4846778470746207 186.00000000000000 0 95 4.5875352082465071 187.00000000000000 0 95 4.5665838495355198 188.00000000000000 0 95 4.5048681828876713 189.00000000000000 0 95 4.4646397824511173 190.00000000000000 0 77 8.3339800292066109 191.00000000000000 0 77 7.9878245271690655 192.00000000000000 0 77 7.6692746281892923 193.00000000000000 0 77 7.3751546069835525 194.00000000000000 0 77 7.1027578834643146 195.00000000000000 0 77 6.8497634754362302 196.00000000000000 0 77 6.4024485103852733 197.00000000000000 0 77 6.0099717563866832 198.00000000000000 0 77 5.6628313526346039 199.00000000000000 0 77 5.3536007912223029 200.00000000000000 0 77 5.0763665399118452 201.00000000000000 0 77 5.4468439016386139 202.00000000000000 0 77 5.8756571006700016 203.00000000000000 0 77 6.3777622622276837 204.00000000000000 0 77 6.9737058038078708 205.00000000000000 0 77 7.6925055853349491 206.00000000000000 0 77 7.9493011334875625 207.00000000000000 0 77 8.2238363452366219 208.00000000000000 0 77 8.5180152832037841 209.00000000000000 0 77 8.8340245857817443 210.00000000000000 0 77 9.1743879079242419 211.00000000000000 0 77 9.1575559143107057 212.00000000000000 0 77 9.1407867365874651 213.00000000000000 0 77 9.1240801531347486 214.00000000000000 0 77 9.1074359360480823 215.00000000000000 0 77 9.0908538509218015 216.00000000000000 0 77 8.9927299367345821 217.00000000000000 0 77 8.8967029504569712 218.00000000000000 0 77 8.8027065175498134 219.00000000000000 0 77 8.7106770301014027 220.00000000000000 0 77 8.6205535035775114 221.00000000000000 0 77 8.6354310556924965 222.00000000000000 0 77 8.6503620873944342 223.00000000000000 0 77 8.6653469088199735 224.00000000000000 0 77 8.6803858231356283 225.00000000000000 0 77 8.6954791264286193 226.00000000000000 0 77 8.6205171720142406 227.00000000000000 0 77 8.5468386627279482 228.00000000000000 0 77 8.4744109551211757 229.00000000000000 0 77 8.4032024940936427 230.00000000000000 0 77 8.3331827675821835 231.00000000000000 0 77 8.3750669504607664 232.00000000000000 0 77 8.4173760633374908 233.00000000000000 0 77 8.4601165194605414 234.00000000000000 0 77 8.5032948543229327 235.00000000000000 0 77 8.5469177289306018 236.00000000000000 0 77 8.9765840307403355 237.00000000000000 0 77 9.4517365246012446 238.00000000000000 0 77 9.9800015209659581 239.00000000000000 0 77 10.570811127827719 240.00000000000000 0 77 11.235971367152922 241.00000000000000 0 77 11.574123784848014 242.00000000000000 0 77 11.933260710628984 243.00000000000000 0 77 12.315397701860309 244.00000000000000 0 77 12.722816996342649 245.00000000000000 0 77 13.158113129366486 246.00000000000000 0 77 13.661472967976577 247.00000000000000 0 77 14.204873121320777 248.00000000000000 0 77 14.793288733080887 249.00000000000000 0 77 15.432554841853676 250.00000000000000 0 77 16.129560552151599 251.00000000000000 0 77 16.026398568494567 252.00000000000000 0 77 15.924357148095124 253.00000000000000 0 77 15.823602014984651 254.00000000000000 0 77 15.724109157878898 255.00000000000000 0 77 15.625855155285008 256.00000000000000 0 77 14.663575146049762 257.00000000000000 0 77 13.812937044643862 258.00000000000000 0 77 13.055576959703803 259.00000000000000 0 77 12.376949228131240 260.00000000000000 0 77 11.765383088475287 261.00000000000000 0 77 10.753305400371621 262.00000000000000 0 77 9.9015547405247677 263.00000000000000 0 77 9.1748298513751418 264.00000000000000 0 77 8.5474845168621378 265.00000000000000 0 77 8.0004379493566482 266.00000000000000 0 77 7.5876603180154314 267.00000000000000 0 77 7.2153849742057226 268.00000000000000 0 77 6.8779294094772760 269.00000000000000 0 77 6.5706266474256845 270.00000000000000 0 77 6.2896080860709311 271.00000000000000 0 77 6.1731226866887727 272.00000000000000 0 77 6.0608724455328788 273.00000000000000 0 77 5.9526305325018258 274.00000000000000 0 77 5.8481860348179548 275.00000000000000 0 77 5.7473425850471154 276.00000000000000 0 77 5.8481598349239325 277.00000000000000 0 77 5.9525773015872989 278.00000000000000 0 77 6.0607914141094872 279.00000000000000 0 77 6.1730131524615492 280.00000000000000 0 77 6.2894694205218302 281.00000000000000 0 77 6.5964585362294184 282.00000000000000 0 77 6.9349554014806323 283.00000000000000 0 77 7.3100731875481060 284.00000000000000 0 77 7.7280946963263908 285.00000000000000 0 77 8.1968270847843456 286.00000000000000 0 77 8.6356681771444102 287.00000000000000 0 77 9.1241594601953366 288.00000000000000 0 77 9.6712323218076399 289.00000000000000 0 77 10.288096946205073 290.00000000000000 0 77 10.989018607788283 291.00000000000000 0 77 11.261243765319429 292.00000000000000 0 77 11.547301350370807 293.00000000000000 0 77 11.848273228331927 294.00000000000000 0 77 12.165357095231405 295.00000000000000 0 77 12.499882405347291 296.00000000000000 0 77 12.048060196445189 297.00000000000000 0 77 11.627762607181387 298.00000000000000 0 77 11.235801986279023 299.00000000000000 0 77 10.869406478524615 300.00000000000000 0 77 10.526154374973563 301.00000000000000 0 77 9.8230233396950215 302.00000000000000 0 77 9.2079473133120242 303.00000000000000 0 77 8.6653601481969407 304.00000000000000 0 77 8.1831606735489011 305.00000000000000 0 77 7.7517992816808023 306.00000000000000 0 77 7.3853928256016479 307.00000000000000 0 77 7.0520626519226441 308.00000000000000 0 77 6.7475235880720694 309.00000000000000 0 77 6.4682000036910763 310.00000000000000 0 77 6.2110847815562185 311.00000000000000 0 77 6.0458607389055503 312.00000000000000 0 77 5.8892006301372080 313.00000000000000 0 77 5.7404554434545503 314.00000000000000 0 77 5.5990401394760143 315.00000000000000 0 77 5.4644259642293909 316.00000000000000 0 77 5.3590111545333183 317.00000000000000 0 77 5.2575875731100048 318.00000000000000 0 77 5.1599327900262679 319.00000000000000 0 77 5.0658406002687357 320.00000000000000 0 77 4.9751195674508590 321.00000000000000 0 77 4.9456046808384810 322.00000000000000 0 77 4.9164386892566005 323.00000000000000 0 77 4.8876154208921179 324.00000000000000 0 77 4.8591288412741509 325.00000000000000 0 77 4.8309730496870813 326.00000000000000 0 77 4.8924374843979832 327.00000000000000 0 77 4.9554861519070244 328.00000000000000 0 77 5.0201810217883835 329.00000000000000 0 77 5.0865873369427366 330.00000000000000 0 77 5.1547738332779369 331.00000000000000 0 77 5.2522542218913433 332.00000000000000 0 77 5.3534919428263175 333.00000000000000 0 77 5.4587084064176326 334.00000000000000 0 77 5.5681427715770306 335.00000000000000 0 77 5.6820537612856121 336.00000000000000 0 77 5.8209803378194422 337.00000000000000 0 77 5.9668693482878687 338.00000000000000 0 77 6.1202575556392667 339.00000000000000 0 77 6.2817383637258706 340.00000000000000 0 77 6.4519694916516874 341.00000000000000 0 77 6.5966797632068044 342.00000000000000 0 77 6.7480266439067611 343.00000000000000 0 77 6.9064824438848422 344.00000000000000 0 77 7.0725596669452582 345.00000000000000 0 77 7.2468213302805209 346.00000000000000 0 77 7.3426052614132828 347.00000000000000 0 77 7.4409551757242545 348.00000000000000 0 77 7.5419752733567185 349.00000000000000 0 77 7.6457754984804600 350.00000000000000 0 77 7.7520635624136682 351.00000000000000 0 77 7.8617569996299519 352.00000000000000 0 77 7.9746006192730050 353.00000000000000 0 77 8.0907319567704015 354.00000000000000 0 77 8.2102966835935458 355.00000000000000 0 77 8.3334492171493935 356.00000000000000 0 77 8.3753247091638716 357.00000000000000 0 77 8.4176239035983595 358.00000000000000 0 77 8.4603531818217252 359.00000000000000 0 77 8.5035190600769397 360.00000000000000 0 77 8.5471281926916625 361.00000000000000 0 77 8.4603571108006275 362.00000000000000 0 77 8.3753305774629094 363.00000000000000 0 77 8.2919964674083868 364.00000000000000 0 77 8.2103047129690125 365.00000000000000 0 77 8.1302072035249822 366.00000000000000 0 77 8.0516576907888293 367.00000000000000 0 77 7.9746116995361946 368.00000000000000 0 77 7.8990264434213522 369.00000000000000 0 77 7.8248607455427859 370.00000000000000 0 77 7.7520749634495285 371.00000000000000 0 77 7.7161893947745508 372.00000000000000 0 77 7.6806346097384903 373.00000000000000 0 77 7.6454060357955447 374.00000000000000 0 77 7.6104991856897879 375.00000000000000 0 77 7.5759096554133514 376.00000000000000 0 77 7.5989403647952294 377.00000000000000 0 77 7.6221114607570168 378.00000000000000 0 77 7.6454242186838384 379.00000000000000 0 77 7.6688799309217286 380.00000000000000 0 77 7.6924799069570708 381.00000000000000 0 77 7.7641523398988488 382.00000000000000 0 77 7.8371727460432838 383.00000000000000 0 77 7.9115795099988775 384.00000000000000 0 77 7.9874124889714713 385.00000000000000 0 77 8.0647130839526913 386.00000000000000 0 77 8.1302828121344852 387.00000000000000 0 77 8.1969273247710781 388.00000000000000 0 77 8.2646732665040297 389.00000000000000 0 77 8.3335481708460986 390.00000000000000 0 77 8.4035804974756783 391.00000000000000 0 77 8.4891881258811317 392.00000000000000 0 77 8.5765576890626019 393.00000000000000 0 77 8.6657441522143763 394.00000000000000 0 77 8.7568047913055995 395.00000000000000 0 77 8.8497993157336179 396.00000000000000 0 77 8.9129012644799648 397.00000000000000 0 77 8.9769093804124722 398.00000000000000 0 77 9.0418433295498346 399.00000000000000 0 77 9.1077233513827860 400.00000000000000 0 77 9.1745702798859661 401.00000000000000 0 77 9.2253439102681778 402.00000000000000 0 77 9.2766925082043663 403.00000000000000 0 77 9.3286157724427596 404.00000000000000 0 77 9.3811234089255553 405.00000000000000 0 77 9.4342253436175074 406.00000000000000 0 77 9.4879317287401026 407.00000000000000 0 77 9.5422529492216341 408.00000000000000 0 77 9.5971996293713957 409.00000000000000 0 77 9.6527826397877465 410.00000000000000 0 77 9.7090131045087542 411.00000000000000 0 77 9.7468655616159037 412.00000000000000 0 77 9.7850142119265886 413.00000000000000 0 77 9.8234625509738862 414.00000000000000 0 77 9.8622141295150918 415.00000000000000 0 77 9.9012725546086955 416.00000000000000 0 77 9.8622143389176262 417.00000000000000 0 77 9.8234629765862955 418.00000000000000 0 77 9.7850148688685064 419.00000000000000 0 77 9.7468664731346024 420.00000000000000 0 77 9.7090143017704875 421.00000000000000 0 77 9.6156580657890185 422.00000000000000 0 77 9.5240799794901054 423.00000000000000 0 77 9.4342297218371147 424.00000000000000 0 77 9.3460588529026278 425.00000000000000 0 77 9.2595207267729567 426.00000000000000 0 77 9.1577671667400136 427.00000000000000 0 77 9.0582255978545589 428.00000000000000 0 77 8.9608246690118687 429.00000000000000 0 77 8.8654960652474291 430.00000000000000 0 77 8.7721743479360210 431.00000000000000 0 77 8.6958938429004995 432.00000000000000 0 77 8.6209284940858115 433.00000000000000 0 77 8.5472445824198946 434.00000000000000 0 77 8.4748095317606751 435.00000000000000 0 77 8.4035918608716340 436.00000000000000 0 77 8.3335611377993164 437.00000000000000 0 77 8.2646879365127432 438.00000000000000 0 77 8.1969437956763400 439.00000000000000 0 77 8.1303011794336424 440.00000000000000 0 77 8.0647334400889878 441.00000000000000 0 77 7.9874348867620197 442.00000000000000 0 77 7.9116040273852262 443.00000000000000 0 77 7.8371994554279460 444.00000000000000 0 77 7.7641813073706709 445.00000000000000 0 77 7.6925111914893964 446.00000000000000 0 77 7.6337889940151689 447.00000000000000 0 77 7.5759565343610351 448.00000000000000 0 77 7.5189937445160844 449.00000000000000 0 77 7.4628811554319316 450.00000000000000 0 77 7.4075998748396934 451.00000000000000 0 77 7.3531126339973527 452.00000000000000 0 77 7.2994396904148502 453.00000000000000 0 77 7.2465446282890023 454.00000000000000 0 77 7.1944106595870716 455.00000000000000 0 77 7.1430214758612625 456.00000000000000 0 77 7.0923612312434772 457.00000000000000 0 77 7.0424145261590363 458.00000000000000 0 77 6.9931663917233502 459.00000000000000 0 77 6.9446022747890490 460.00000000000000 0 77 6.8967080236118070 461.00000000000000 0 77 6.8588655803798257 462.00000000000000 0 77 6.8214361677259019 463.00000000000000 0 77 6.7844130607530460 464.00000000000000 0 77 6.7477896797159111 465.00000000000000 0 77 6.7115595861260564 466.00000000000000 0 77 6.6757164789814505 467.00000000000000 0 77 6.6402541911166271 468.00000000000000 0 77 6.6051666856683147 469.00000000000000 0 77 6.5704480526526901 470.00000000000000 0 77 6.5360925056498198 471.00000000000000 0 77 6.4684483533467843 472.00000000000000 0 77 6.4021900112787158 473.00000000000000 0 77 6.3372753252251197 474.00000000000000 0 77 6.2736638334457098 475.00000000000000 0 77 6.2113166825837780 476.00000000000000 0 77 6.0976948706808978 477.00000000000000 0 77 5.9881552914390017 478.00000000000000 0 77 5.8824818262310989 479.00000000000000 0 77 5.7804733472921637 480.00000000000000 0 77 5.6819424400900713 481.00000000000000 0 77 5.5867142541735024 482.00000000000000 0 77 5.4946254676718977 483.00000000000000 0 77 5.4055233525470525 484.00000000000000 0 77 5.3192649293415801 485.00000000000000 0 77 5.2357162015849692 486.00000000000000 0 77 5.1547514612336496 487.00000000000000 0 77 5.0762526575737192 488.00000000000000 0 77 5.0001088229223081 489.00000000000000 0 77 4.9262155492518724 490.00000000000000 0 77 4.8544745105463738 491.00000000000000 0 77 4.7802186543762835 492.00000000000000 0 77 4.7082002653165986 493.00000000000000 0 77 4.6383197153552977 494.00000000000000 0 77 4.5704832048048090 495.00000000000000 0 77 4.5046023422433787 496.00000000000000 0 77 4.4327203670776312 497.00000000000000 0 77 4.3630964642087546 498.00000000000000 0 77 4.2956258771935198 499.00000000000000 0 77 4.2302102306906839 500.00000000000000 0 77 4.1667570518790145 501.00000000000000 0 77 4.1051793343110772 502.00000000000000 0 77 4.0453951398769554 503.00000000000000 0 77 3.9873272350486317 504.00000000000000 0 77 3.9309027580091573 505.00000000000000 0 77 3.8760529136501454 506.00000000000000 0 77 3.8256374930594790 507.00000000000000 0 77 3.7765167236155541 508.00000000000000 0 77 3.7286413675971959 509.00000000000000 0 77 3.6819646527993779 510.00000000000000 0 77 3.6364421201199026 511.00000000000000 0 77 3.5894528523916271 512.00000000000000 0 77 3.5436624540063391 513.00000000000000 0 77 3.4990256209157895 514.00000000000000 0 77 3.4554993033219952 515.00000000000000 0 77 3.4130425671912645 516.00000000000000 0 77 3.3830224755484997 517.00000000000000 0 77 3.3535258653123403 518.00000000000000 0 77 3.3245391618372477 519.00000000000000 0 77 3.2960492557991343 520.00000000000000 0 77 3.2680434834270580 521.00000000000000 0 77 3.2426111055343898 522.00000000000000 0 77 3.2175714967012508 523.00000000000000 0 77 3.1929156274775683 524.00000000000000 0 77 3.1686347430815078 525.00000000000000 0 77 3.1447203530349257 526.00000000000000 0 77 3.1231137304595760 527.00000000000000 0 77 3.1018019774344636 528.00000000000000 0 77 3.0807790982356789 529.00000000000000 0 77 3.0600392585996579 530.00000000000000 0 77 3.0395767803250813 531.00000000000000 0 77 3.0175639356454158 532.00000000000000 0 77 2.9958676221901310 533.00000000000000 0 77 2.9744810610095778 534.00000000000000 0 77 2.9533976653602956 535.00000000000000 0 77 2.9326110339412943 536.00000000000000 0 77 2.9138119810947756 537.00000000000000 0 77 2.8952523956536611 538.00000000000000 0 77 2.8769277306470231 539.00000000000000 0 77 2.8588335535023903 540.00000000000000 0 77 2.8409655424709044 541.00000000000000 0 77 2.8329171698140065 542.00000000000000 0 77 2.8249142569767431 543.00000000000000 0 77 2.8169564197189381 544.00000000000000 0 77 2.8090432781270280 545.00000000000000 0 77 2.8011744565535315 546.00000000000000 0 77 2.7964741356644214 547.00000000000000 0 77 2.7917895498958938 548.00000000000000 0 77 2.7871206202837859 549.00000000000000 0 77 2.7824672684005951 550.00000000000000 0 77 2.7778294163509694 551.00000000000000 0 77 2.7732069867671791 552.00000000000000 0 77 2.7685999028048993 553.00000000000000 0 77 2.7640080881386626 554.00000000000000 0 77 2.7594314669576523 555.00000000000000 0 77 2.7548699639614087 556.00000000000000 0 77 2.7503235043555252 557.00000000000000 0 77 2.7457920138474607 558.00000000000000 0 77 2.7412754186424046 559.00000000000000 0 77 2.7367736454391052 560.00000000000000 0 77 2.7322866214257839 561.00000000000000 0 77 2.7263269164383575 562.00000000000000 0 77 2.7203931409237394 563.00000000000000 0 77 2.7144851260689369 564.00000000000000 0 77 2.7086027045325376 565.00000000000000 0 77 2.7027457104288053 566.00000000000000 0 77 2.6983694104933664 567.00000000000000 0 77 2.6940072483198381 568.00000000000000 0 77 2.6896591556117722 569.00000000000000 0 77 2.6853250645208893 570.00000000000000 0 77 2.6810049076434077 571.00000000000000 0 77 2.6581993718523913 572.00000000000000 0 77 2.6357785279765364 573.00000000000000 0 77 2.6137327237093140 574.00000000000000 0 77 2.5920526269938420 575.00000000000000 0 77 2.5707292128506247 576.00000000000000 0 77 2.5471559375532160 577.00000000000000 0 77 2.5240110434845793 578.00000000000000 0 77 2.5012829587744094 579.00000000000000 0 77 2.4789605246350126 580.00000000000000 0 77 2.4570329770922088 581.00000000000000 0 77 2.4354899296772734 582.00000000000000 0 77 2.4143213570215103 583.00000000000000 0 77 2.3935175792988410 584.00000000000000 0 77 2.3730692474660291 585.00000000000000 0 77 2.3529673292529489 586.00000000000000 0 77 2.3126985358119376 587.00000000000000 0 77 2.2737848495798554 588.00000000000000 0 77 2.2361590002693110 589.00000000000000 0 77 2.1997580977130848 590.00000000000000 0 77 2.1645232810752066 591.00000000000000 0 77 2.1303994012427823 592.00000000000000 0 77 2.0973347327935699 593.00000000000000 0 77 2.0652807123756780 594.00000000000000 0 77 2.0341917007159420 595.00000000000000 0 77 2.0040247658043517 596.00000000000000 0 77 1.9747394850884390 597.00000000000000 0 77 1.9462977647609307 598.00000000000000 0 77 1.9186636744419994 599.00000000000000 0 77 1.8918032957474227 600.00000000000000 0 77 1.8656845834007121 Index: trunk/HiggsBounds_KW/example_programs/HBwithLHClikelihood.F90 =================================================================== --- trunk/HiggsBounds_KW/example_programs/HBwithLHClikelihood.F90 (revision 0) +++ trunk/HiggsBounds_KW/example_programs/HBwithLHClikelihood.F90 (revision 509) @@ -0,0 +1,243 @@ +!****************************************************** +program HBwithLHClikelihood +! +! In this example we evaluate the likelihood from the CMS Higgs search with tautau +! final states (arXiv:1408.3316) for the mhmax scenario. The input is provided from +! a datafile created with SusHi obtained here: +! https://twiki.cern.ch/twiki/bin/view/LHCPhysics/LHCHXSWGMSSMNeutral +! +! Note, that we deactivate the latest ATLAS and CMS tau tau 95% CL limits (the latter +! is reconstructed from the provided likelihood information internally in HiggsBounds) +! from the standard HiggsBounds procedure, since we want to use the likelihood instead. +! This is optional. +! +! (TS 27/05/2015) +!****************************************************** + use theory_XS_SM_functions + use theory_BRfunctions + use channels, only : HiggsBounds_deactivate_analyses,HiggsBounds_activate_all_analyses + use output, only : createKey + implicit none + + integer :: nHzero,nHplus,ndf, i, j, k, ii, jj, CP_value(3) + double precision :: Mh(3),GammaTotal(3),CS_lep_hjZ_ratio(3), & + & CS_lep_bbhj_ratio(3),CS_lep_tautauhj_ratio(3), & + & CS_lep_hjhi_ratio_nHbynH(3), & + & CS_tev_hj_ratio(3) ,CS_tev_hjb_ratio(3), & + & CS_tev_hjW_ratio(3),CS_tev_hjZ_ratio(3), & + & CS_tev_vbf_ratio(3),CS_tev_tthj_ratio(3), & + & CS_lhc7_hj_ratio(3) ,CS_lhc7_hjb_ratio(3), & + & CS_lhc7_hjW_ratio(3),CS_lhc7_hjZ_ratio(3), & + & CS_lhc7_vbf_ratio(3),CS_lhc7_tthj_ratio(3), & + & CS_lhc8_hj_ratio(3) ,CS_lhc8_hjb_ratio(3), & + & CS_lhc8_hjW_ratio(3),CS_lhc8_hjZ_ratio(3), & + & CS_lhc8_vbf_ratio(3),CS_lhc8_tthj_ratio(3), & + & BR_hjss(3),BR_hjcc(3), & + & BR_hjbb(3), & + & BR_hjmumu(3), & + & BR_hjtautau(3), & + & BR_hjWW(3),BR_hjZZ(3),BR_hjZga(3),BR_hjgaga(3), & + & BR_hjgg(3), BR_hjinvisible(3), & + & BR_hjhihi_nHbynH(3,3) + double precision :: ggH(3), bbH(3), tb, llh_h(3) + character(len=100)::filename_in, filename_out + integer :: HBresult,chan,ncombined,HBresult_all,chan_all,ncombined_all + double precision :: obsratio,obsratio_all + integer :: error, status, n, Hindex2, nc2,cbin + double precision :: M_av, llh, mu, M_av2, llh2, mass, combllh, M_av_exp, llh_exp + integer :: Hindex, nc, Hindex_exp, nc_exp + + nHzero = 3 + nHplus = 0 + + call initialize_HiggsBounds(nHzero, nHplus, 'onlyH') + +! Optionally, deactivate the 95%CL limit extraction for CMS MSSM h/H/A->tautau, since +! we want to use the likelihood information instead, as well as all relevant previous +! results from non-standard Higgs to tau tau searches from ATLAS/CMS: + +! call HiggsBounds_deactivate_analyses((/3316, 2014049, 20140492/)) + +! Note: Deactivation of analyses can be changed before every HiggsBounds run +! (as currently done, see below). If all analyses need to be activated again, just call +! call HiggsBounds_activate_all_analyses + + + filename_in ="../example_data/mhmax_SusHi.dat" + filename_out = "mhmax_HBwithLHClikelihood.dat" + + call system('rm -f mhmax_HBwithLHClikelihood.dat') + + open(432,file=trim(adjustl(filename_in)),action='read',status='old',iostat=status) + open(433,file=trim(adjustl(filename_out)),action='write',status='new') + + if(status.ne.0) then + write(*,*) 'Bad status', status, 'with the following file:' + write(*,*) trim(adjustl(filename_in)) + stop + endif + n = 0 + do +! Read in the relevant cross section / BR predictions from the data grid. + read(432,*, iostat = error) Mh, tb, ggH, bbH, BR_hjtautau + if (error == -1) exit + n = n + 1 +!---- +! QUICK STOP FOR TESTING +! if (n.le.9999) cycle +! if (n.ge.10001) exit +!---- + if(mod(n,100).eq.0) write(*,*) "number of processed points: ",n, " MA,TB = ", Mh(3),tb + + CP_value(1) = 1 + CP_value(2) = 1 + CP_value(3) = -1 + + do i=1,3 + GammaTotal(i)=BRSM_GammaTot(Mh(i)) +! Normalize the cross sections to the SM predictions +! (using HiggsBounds SM cross section routines) + CS_lhc8_hj_ratio(i)=ggH(i)/XS_lhc8_gg_H_SM(Mh(i)) + CS_lhc8_hjb_ratio(i)=bbH(i)/XS_lhc8_bb_H_SM(Mh(i)) + enddo +! Set the other predictions to zero here. + CS_lep_hjZ_ratio=0.0D0 + CS_lep_bbhj_ratio=0.0D0 + CS_lep_tautauhj_ratio=0.0D0 + CS_lep_hjhi_ratio_nHbynH=0.0D0 + CS_tev_hj_ratio=0.0D0 + CS_tev_hjb_ratio=0.0D0 + CS_tev_hjW_ratio=0.0D0 + CS_tev_hjZ_ratio=0.0D0 + CS_tev_vbf_ratio=0.0D0 + CS_tev_tthj_ratio=0.0D0 + CS_lhc7_hj_ratio=0.0D0 + CS_lhc7_hjb_ratio=0.0D0 + CS_lhc7_hjW_ratio=0.0D0 + CS_lhc7_hjZ_ratio=0.0D0 + CS_lhc7_vbf_ratio=0.0D0 + CS_lhc7_tthj_ratio=0.0D0 + CS_lhc8_hjW_ratio=0.0D0 + CS_lhc8_hjZ_ratio=0.0D0 + CS_lhc8_vbf_ratio=0.0D0 + CS_lhc8_tthj_ratio=0.0D0 + BR_hjss=0.0D0 + BR_hjcc=0.0D0 + BR_hjbb=0.0D0 + BR_hjmumu=0.0D0 + BR_hjWW=0.0D0 + BR_hjZZ=0.0D0 + BR_hjZga=0.0D0 + BR_hjgaga=0.0D0 + BR_hjgg=0.0D0 + BR_hjinvisible=0.0D0 + BR_hjhihi_nHbynH=0.0D0 + + + call HiggsBounds_neutral_input_hadr(Mh,GammaTotal,CP_value, & + & CS_lep_hjZ_ratio, & + & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio, & + & CS_lep_hjhi_ratio_nHbynH, & + & CS_tev_hj_ratio ,CS_tev_hjb_ratio, & + & CS_tev_hjW_ratio,CS_tev_hjZ_ratio, & + & CS_tev_vbf_ratio,CS_tev_tthj_ratio, & + & CS_lhc7_hj_ratio ,CS_lhc7_hjb_ratio, & + & CS_lhc7_hjW_ratio,CS_lhc7_hjZ_ratio, & + & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio, & + & CS_lhc8_hj_ratio ,CS_lhc8_hjb_ratio, & + & CS_lhc8_hjW_ratio,CS_lhc8_hjZ_ratio, & + & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio, & + & BR_hjss,BR_hjcc, & + & BR_hjbb, & + & BR_hjmumu, & + & BR_hjtautau, & + & BR_hjWW,BR_hjZZ,BR_hjZga,BR_hjgaga, & + & BR_hjgg, BR_hjinvisible, & + & BR_hjhihi_nHbynH ) + + +! Activate all analyses (in case some of them have been deactivated before) + call HiggsBounds_activate_all_analyses + +! Run the standard HiggsBounds routine considering all analyses + call run_HiggsBounds( HBresult_all,chan_all, obsratio_all, ncombined_all ) + + call HiggsBounds_neutral_input_hadr(Mh,GammaTotal,CP_value, & + & CS_lep_hjZ_ratio, & + & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio, & + & CS_lep_hjhi_ratio_nHbynH, & + & CS_tev_hj_ratio ,CS_tev_hjb_ratio, & + & CS_tev_hjW_ratio,CS_tev_hjZ_ratio, & + & CS_tev_vbf_ratio,CS_tev_tthj_ratio, & + & CS_lhc7_hj_ratio ,CS_lhc7_hjb_ratio, & + & CS_lhc7_hjW_ratio,CS_lhc7_hjZ_ratio, & + & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio, & + & CS_lhc8_hj_ratio ,CS_lhc8_hjb_ratio, & + & CS_lhc8_hjW_ratio,CS_lhc8_hjZ_ratio, & + & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio, & + & BR_hjss,BR_hjcc, & + & BR_hjbb, & + & BR_hjmumu, & + & BR_hjtautau, & + & BR_hjWW,BR_hjZZ,BR_hjZga,BR_hjgaga, & + & BR_hjgg, BR_hjinvisible, & + & BR_hjhihi_nHbynH ) + + +! Deactivate present CMS and ATLAS searches for non-standard Higgs to tautau + call HiggsBounds_deactivate_analyses((/3316, 2014049, 20140492/))! ,) +! Standard HiggsBounds run (gives 95% CL limit): + call run_HiggsBounds( HBresult,chan, obsratio, ncombined ) + +! Obtain exclusion-likelihood from CMS MSSM H->tautau search (ID 3316): +! +! The arguments of the following subroutines mean the following: +! 3316 -> Analysis-ID of the CMS h/H/A->tautau search [int input] +! Hindex -> Index of the Higgs boson that was selected as most sensitive [int output] +! M_av -> mass position where limit is extracted (a signal strength average in case +! of combined Higgs bosons) [dbl output] +! nc -> number of combined Higgs bosons [int output] +! cbin -> binary code of the combined Higgs bosons [int output] +! llh -> -2ln L value [dbl output] +! obspred -> 'obs' or 'pred' to chose whether the observed or expected likelihood should be +! extracted. [char input] +! +! Get expected/predicted likelihood + call HiggsBounds_get_likelihood(3316, Hindex, nc, cbin, M_av, llh_exp, 'pred') +! Get observed likelihood + call HiggsBounds_get_likelihood(3316, Hindex, nc, cbin, M_av, llh, 'obs') + + write(433,*) n, Mh, tb, HBresult, chan, obsratio, ncombined, llh, & + & HBresult_all,chan_all, obsratio_all, ncombined_all, Hindex,& + & M_av, nc, cbin, llh_exp + + enddo + +!-------------------------------------------------------- +! Example for the auxiliary chi^2 functions (run on the last point of the scan) +!-------------------------------------------------------- +! Get observed likelihood for lightest Higgs + + write(*,*) "#------------------------------------------------------------------#" + call HiggsBounds_get_likelihood_for_Higgs(3316, 0, 1, nc, cbin, M_av, llh, 'obs') + write(*,*) "The observed likelihood value for the light Higgs h is ",llh + write(*,*) "The binary code and number of Higgses of the formed combination is ", cbin, nc + write(*,*) "The likelihood has been evaluated at an average mass value of ", M_av + write(*,*) "#------------------------------------------------------------------#" + +! Get observed likelihood for a subset of available Higgs bosons +! (here, e.g., exclude h and H from possible combination) + + call HiggsBounds_get_likelihood_for_comb(3316, 3, Hindex, nc, cbin, M_av, llh, 'obs') + write(*,*) "The observed likelihood value is ",llh + write(*,*) "The binary code, number of Higgses and Higgs index of the formed combination is ", cbin, nc, Hindex + write(*,*) "The likelihood has been evaluated at an average mass value of ", M_av + write(*,*) "#------------------------------------------------------------------#" +!-------------------------------------------------------- + +! Write out the key with the used analyses (indicating possibly deactivated analyses) + call createKey("HB_with_deactivated_analyses_") + close(432) + close(433) + +end program HBwithLHClikelihood \ No newline at end of file Index: trunk/HiggsBounds_KW/example_programs/example-4thGen-results.dat-for-comparison =================================================================== --- trunk/HiggsBounds_KW/example_programs/example-4thGen-results.dat-for-comparison (revision 508) +++ trunk/HiggsBounds_KW/example_programs/example-4thGen-results.dat-for-comparison (revision 509) @@ -1,511 +1,511 @@ 90.000000000000000 0 1 3.5792795849414025 91.000000000000000 0 1 3.1721231715738587 92.000000000000000 0 1 3.0544848737268562 93.000000000000000 0 1 2.7741936373235840 94.000000000000000 0 1 2.4545238974138330 95.000000000000000 0 1 2.4678912415879246 96.000000000000000 0 1 2.3444703056842355 97.000000000000000 0 1 2.1648532576141788 98.000000000000000 0 1 2.1720581157836447 99.000000000000000 0 1 2.0976351422383890 100.00000000000000 0 1 2.2992592033289703 101.00000000000000 0 1 2.3291484278073207 102.00000000000000 0 1 2.2514868876757195 103.00000000000000 0 1 2.1875067447984109 104.00000000000000 0 1 2.0979746185419947 105.00000000000000 0 1 2.3682735012830634 106.00000000000000 0 1 2.0882364711800783 107.00000000000000 0 1 2.1106440217328521 108.00000000000000 0 1 2.0027165642257359 109.00000000000000 0 1 1.9528903465445659 110.00000000000000 0 1 1.8187050252715609 111.00000000000000 0 1 1.4587478855851654 - 112.00000000000000 0 121 1.7399268119674871 - 113.00000000000000 0 121 1.5968406332542633 - 114.00000000000000 0 121 1.6643332211216313 - 115.00000000000000 0 121 1.7023699473043974 - 116.00000000000000 0 121 1.7535877930991823 - 117.00000000000000 0 121 1.8752785925752202 - 118.00000000000000 0 121 2.6995508913419557 - 119.00000000000000 0 121 2.9011885979771255 - 120.00000000000000 0 121 2.5866225451007354 - 121.00000000000000 0 121 2.3158178992110563 + 112.00000000000000 0 120 1.7399268119674871 + 113.00000000000000 0 120 1.5968406332542633 + 114.00000000000000 0 120 1.6643332211216313 + 115.00000000000000 0 120 1.7023699473043974 + 116.00000000000000 0 120 1.7535877930991823 + 117.00000000000000 0 120 1.8752785925752202 + 118.00000000000000 0 120 2.6995508913419557 + 119.00000000000000 0 120 2.9011885979771255 + 120.00000000000000 0 120 2.5866225451007354 + 121.00000000000000 0 120 2.3158178992110563 122.00000000000000 1 53 0.85396219499329951 123.00000000000000 1 53 0.87654366851701004 124.00000000000000 1 53 0.89514529824520805 125.00000000000000 1 53 0.91024168480801071 126.00000000000000 1 53 0.96231230291334213 127.00000000000000 0 53 1.0116834641147532 128.00000000000000 0 53 1.0584839170559655 129.00000000000000 0 53 1.1028362722873926 130.00000000000000 0 53 1.1448573154588864 131.00000000000000 0 53 1.1796494303590759 - 132.00000000000000 0 121 3.4819953529256442 - 133.00000000000000 0 121 2.7128152690737863 - 134.00000000000000 0 121 2.1666579266392070 + 132.00000000000000 0 120 3.4819953529256442 + 133.00000000000000 0 120 2.7128152690737863 + 134.00000000000000 0 120 2.1666579266392070 135.00000000000000 0 53 1.2925273823520778 136.00000000000000 0 53 1.3025084089428005 137.00000000000000 0 53 1.3109258259870624 138.00000000000000 0 53 1.3179661000680951 139.00000000000000 0 53 1.3237947838437802 140.00000000000000 0 53 1.3285592830564275 141.00000000000000 0 53 1.4604224258664702 142.00000000000000 0 53 1.6110696060426508 143.00000000000000 0 53 1.7850316608353225 144.00000000000000 0 53 1.9883978612264437 145.00000000000000 0 53 2.2295494949134897 146.00000000000000 0 53 2.4096498133303696 147.00000000000000 0 53 2.6108312694900011 148.00000000000000 0 53 2.8371692020790484 149.00000000000000 0 53 3.0938348964726776 150.00000000000000 0 53 3.3874904871244258 151.00000000000000 0 53 3.4154733586726591 152.00000000000000 0 53 3.4429825011632476 153.00000000000000 0 53 3.4701538382448489 154.00000000000000 0 53 3.4971196244559808 155.00000000000000 0 53 3.5240091718811044 156.00000000000000 0 53 3.9673334404283596 157.00000000000000 0 53 4.5090418695722336 158.00000000000000 0 53 5.1857457176097848 159.00000000000000 0 53 6.0546617088069610 160.00000000000000 0 53 7.2104728015692743 161.00000000000000 0 53 7.3304795915278680 162.00000000000000 0 53 7.4553692337671320 163.00000000000000 0 53 7.5854473096412107 164.00000000000000 0 53 7.7210428115421594 165.00000000000000 0 53 7.8625105396897244 166.00000000000000 0 53 7.9563289711175429 167.00000000000000 0 53 8.0597967027871000 168.00000000000000 0 53 8.1737627543233682 169.00000000000000 0 53 8.2991953936594047 170.00000000000000 0 53 8.4372030517873444 171.00000000000000 0 53 8.2605906645700067 172.00000000000000 0 53 8.0884558226622651 173.00000000000000 0 53 7.9206680886416416 174.00000000000000 0 53 7.7571013057602158 175.00000000000000 0 53 7.5976334416504416 176.00000000000000 0 53 7.1164646409068411 177.00000000000000 0 53 6.6766456881828988 178.00000000000000 0 53 6.2734913274219419 179.00000000000000 0 53 5.9029833733326171 180.00000000000000 0 53 5.5616566601934059 181.00000000000000 0 53 5.4326756199828798 182.00000000000000 0 53 5.3063698602255256 183.00000000000000 0 53 5.1826474459933998 184.00000000000000 0 53 5.0614182774592154 185.00000000000000 0 53 4.9425939473379232 186.00000000000000 0 53 4.6137050741837760 187.00000000000000 0 53 4.3116923063910182 188.00000000000000 0 53 4.0337509426872096 189.00000000000000 0 53 3.7774407578765685 190.00000000000000 0 53 3.5406291561408700 191.00000000000000 0 53 3.4660500573114512 192.00000000000000 0 53 3.3932283246961368 193.00000000000000 0 53 3.3221157413408391 194.00000000000000 0 53 3.2526655602822214 195.00000000000000 0 53 3.1848324545626845 196.00000000000000 0 53 3.0723438366588822 197.00000000000000 0 53 2.9645649884542640 198.00000000000000 0 53 2.8612628306135535 199.00000000000000 0 53 2.7622178204776557 200.00000000000000 0 73 41.824291437153356 201.00000000000000 0 73 44.933346670112520 202.00000000000000 0 73 48.572541866059872 203.00000000000000 0 73 52.889061748729027 204.00000000000000 0 73 58.090042446435959 205.00000000000000 0 73 64.476562088994044 206.00000000000000 0 73 64.880631635098524 207.00000000000000 0 73 65.298721853588390 208.00000000000000 0 73 65.731375629623443 209.00000000000000 0 73 66.179136871082321 210.00000000000000 0 73 66.642549203388185 211.00000000000000 0 73 55.839155636318047 212.00000000000000 0 73 47.979899907031900 213.00000000000000 0 73 42.008066096539061 214.00000000000000 0 73 37.318565397186774 215.00000000000000 0 73 33.539946359261407 216.00000000000000 0 73 33.362843217661201 217.00000000000000 0 73 33.191086100058676 218.00000000000000 0 73 33.024553861668288 219.00000000000000 0 73 32.863112814396381 220.00000000000000 0 73 32.706616760079946 221.00000000000000 0 73 33.662078422745061 222.00000000000000 0 73 34.692700113636064 223.00000000000000 0 73 35.806776623840427 224.00000000000000 0 73 37.013893887669894 225.00000000000000 0 73 38.325193552293513 226.00000000000000 0 73 37.852401420080824 227.00000000000000 0 73 37.391256429226189 228.00000000000000 0 73 36.941216399970024 229.00000000000000 0 73 36.501746793846856 230.00000000000000 0 73 36.072321649998287 231.00000000000000 0 73 36.970073850332192 232.00000000000000 0 73 37.927886539672031 233.00000000000000 0 73 38.951237693081112 234.00000000000000 0 73 40.046338374302032 235.00000000000000 0 73 41.220261510033886 236.00000000000000 0 73 42.753896847190397 237.00000000000000 0 73 44.426162091011491 238.00000000000000 0 73 46.255965390443052 239.00000000000000 0 73 48.265910866503333 240.00000000000000 0 73 50.483247338041153 241.00000000000000 0 73 51.590966403196106 242.00000000000000 0 73 52.762172193189471 243.00000000000000 0 73 54.001999280677467 244.00000000000000 0 73 55.316225066494965 245.00000000000000 0 73 56.711371248320198 246.00000000000000 0 73 55.466602353160404 247.00000000000000 0 73 54.262020366381364 248.00000000000000 0 73 53.095464084855635 249.00000000000000 0 73 51.964947855867294 250.00000000000000 0 73 50.868649112751747 251.00000000000000 0 73 47.815717293126490 252.00000000000000 0 73 45.077244906899260 253.00000000000000 0 73 42.606937966360533 254.00000000000000 0 73 40.367146493504535 255.00000000000000 0 73 38.326988588610568 256.00000000000000 0 73 37.181892893958270 257.00000000000000 0 73 36.089706856216608 258.00000000000000 0 73 35.046943952946400 259.00000000000000 0 73 34.050453814762037 260.00000000000000 0 73 33.097384237660457 261.00000000000000 0 73 33.573817860796169 262.00000000000000 0 73 34.071178988327141 263.00000000000000 0 73 34.591095986242465 264.00000000000000 0 73 35.135361276229737 265.00000000000000 0 73 35.705947955363136 266.00000000000000 0 73 36.420810124476276 267.00000000000000 0 73 37.177056021929964 268.00000000000000 0 73 37.978554639491975 269.00000000000000 0 73 38.829632973384754 270.00000000000000 0 73 39.735142076478851 271.00000000000000 0 73 39.737159200009728 272.00000000000000 0 73 39.743510311767658 273.00000000000000 0 73 39.754683753405253 274.00000000000000 0 73 39.771176836927729 275.00000000000000 0 73 39.793494134198191 276.00000000000000 0 73 39.899520509592875 277.00000000000000 0 73 40.013899885478310 278.00000000000000 0 73 40.137233311949721 279.00000000000000 0 73 40.270130518326951 280.00000000000000 0 73 40.413209057175578 281.00000000000000 0 73 40.154994779482521 282.00000000000000 0 73 39.905770515367337 283.00000000000000 0 73 39.665813415574412 284.00000000000000 0 73 39.435380433837096 285.00000000000000 0 73 39.214706769044959 286.00000000000000 0 73 39.004003754378743 287.00000000000000 0 73 38.803455886893047 288.00000000000000 0 73 38.613216579535937 289.00000000000000 0 73 38.433402066435718 290.00000000000000 0 73 38.264082688661823 291.00000000000000 0 73 38.267726265667072 292.00000000000000 0 73 38.281628251695160 293.00000000000000 0 73 38.305755489930753 294.00000000000000 0 73 38.339937783838856 295.00000000000000 0 73 38.383818098806309 296.00000000000000 0 73 38.495507339316148 297.00000000000000 0 73 38.616098284282224 298.00000000000000 0 73 38.744222770697462 299.00000000000000 0 73 38.877904015040187 300.00000000000000 0 73 39.014389768361788 301.00000000000000 0 73 39.519931056441848 302.00000000000000 0 73 40.033260116523081 303.00000000000000 0 73 40.548776443929768 304.00000000000000 0 73 41.059750716499742 305.00000000000000 0 73 41.558885177687031 306.00000000000000 0 73 42.752376310577013 307.00000000000000 0 73 43.987405480750617 308.00000000000000 0 73 45.269244841931865 309.00000000000000 0 73 46.610207668424707 310.00000000000000 0 73 48.030860499949370 311.00000000000000 0 73 48.911162971920582 312.00000000000000 0 73 49.854355279789978 313.00000000000000 0 73 50.883240636700251 314.00000000000000 0 73 52.017480815908876 315.00000000000000 0 73 53.272380246643586 316.00000000000000 0 73 53.675826545393249 317.00000000000000 0 73 54.141418245437485 318.00000000000000 0 73 54.665258743627341 319.00000000000000 0 73 55.242406778318134 320.00000000000000 0 73 55.867796697993974 321.00000000000000 0 73 56.350288857811584 322.00000000000000 0 73 56.864440004711781 323.00000000000000 0 73 57.406403142161587 324.00000000000000 0 73 57.973040688753628 325.00000000000000 0 73 58.561837616400076 326.00000000000000 0 73 57.937391482638972 327.00000000000000 0 73 57.334826298887108 328.00000000000000 0 73 56.751743271088891 329.00000000000000 0 73 56.186146104657546 330.00000000000000 0 73 55.636354513299302 331.00000000000000 0 73 53.741845821483452 332.00000000000000 0 73 51.978568698488971 333.00000000000000 0 73 50.332852921913172 334.00000000000000 0 73 48.792856687053394 335.00000000000000 0 73 47.348266805316015 336.00000000000000 0 73 46.000047994773077 337.00000000000000 0 73 44.729150510672653 338.00000000000000 0 73 43.528704940544863 339.00000000000000 0 73 42.392616951876107 340.00000000000000 0 73 41.315460198828447 341.00000000000000 0 73 40.865227366709924 342.00000000000000 0 73 40.422116939683235 343.00000000000000 0 73 39.985701825998227 344.00000000000000 0 73 39.555578716225249 345.00000000000000 0 73 39.131369633237483 346.00000000000000 0 73 38.961060543211218 347.00000000000000 0 73 38.788790435791938 348.00000000000000 0 73 38.614423890034011 349.00000000000000 0 73 38.437834996661543 350.00000000000000 0 73 38.256736413118539 351.00000000000000 0 73 37.844430343881456 352.00000000000000 0 73 37.434522277659390 353.00000000000000 0 73 37.026866913302577 354.00000000000000 0 73 36.621331719686509 355.00000000000000 0 73 36.217796473901807 356.00000000000000 0 73 35.364791220873705 357.00000000000000 0 73 34.541097133989311 358.00000000000000 0 73 33.744984423151244 359.00000000000000 0 73 32.974861122431371 360.00000000000000 0 73 32.229260351843173 361.00000000000000 0 73 31.519176487631491 362.00000000000000 0 73 30.830545523497811 363.00000000000000 0 73 30.162232120428222 364.00000000000000 0 73 29.513185760503085 365.00000000000000 0 73 28.882433503546164 366.00000000000000 0 73 27.924086862261081 367.00000000000000 0 73 27.015651519436073 368.00000000000000 0 73 26.153095614501652 369.00000000000000 0 73 25.332817770954655 370.00000000000000 0 73 24.551591697121758 371.00000000000000 0 73 24.250304291774462 372.00000000000000 0 73 23.950474805441711 373.00000000000000 0 73 23.652108722992264 374.00000000000000 0 73 23.355215836518799 375.00000000000000 0 73 23.059809924148155 376.00000000000000 0 73 23.006920120046587 377.00000000000000 0 73 22.950933542773349 378.00000000000000 0 73 22.891877724205145 379.00000000000000 0 73 22.829784143693374 380.00000000000000 0 73 22.764688090926715 381.00000000000000 0 73 22.913922050798156 382.00000000000000 0 73 23.064279413011114 383.00000000000000 0 73 23.215875110643740 384.00000000000000 0 73 23.368832782336607 385.00000000000000 0 73 23.523285115663437 386.00000000000000 0 73 23.966358283241995 387.00000000000000 0 73 24.430136540275203 388.00000000000000 0 73 24.916378586562526 389.00000000000000 0 73 25.427038882902469 390.00000000000000 0 73 25.964295135284786 391.00000000000000 0 73 26.705010261053811 392.00000000000000 0 73 27.497642171854448 393.00000000000000 0 73 28.348236435375281 394.00000000000000 0 73 29.263797257288548 395.00000000000000 0 73 30.252484832272092 396.00000000000000 0 73 31.317956802733807 397.00000000000000 0 73 32.476416470908369 398.00000000000000 0 73 33.741066385906421 399.00000000000000 0 73 35.127702594003225 400.00000000000000 0 73 36.655384116097459 401.00000000000000 0 73 37.580119119205840 402.00000000000000 0 73 38.565553097692856 403.00000000000000 0 73 39.618261372649748 404.00000000000000 0 73 40.745783303938737 405.00000000000000 0 73 41.956799149849765 406.00000000000000 0 73 42.590450037526558 407.00000000000000 0 73 43.252606149077508 408.00000000000000 0 73 43.945536002692613 409.00000000000000 0 73 44.671732117076708 410.00000000000000 0 73 45.433939523809052 411.00000000000000 0 73 45.551467974987474 412.00000000000000 0 73 45.670434780711965 413.00000000000000 0 73 45.791066297668593 414.00000000000000 0 73 45.913595156447947 415.00000000000000 0 73 46.038260471432864 416.00000000000000 0 73 45.866019212099523 417.00000000000000 0 73 45.691798759624106 418.00000000000000 0 73 45.515734424088215 419.00000000000000 0 73 45.337959655312652 420.00000000000000 0 73 45.158605926195058 421.00000000000000 0 73 44.900321354538761 422.00000000000000 0 73 44.640783177974257 423.00000000000000 0 73 44.380124101929923 424.00000000000000 0 73 44.118473747780605 425.00000000000000 0 73 43.855958592500478 426.00000000000000 0 73 43.475635246207602 427.00000000000000 0 73 43.096029552190224 428.00000000000000 0 73 42.717263705333494 429.00000000000000 0 73 42.339455394573655 430.00000000000000 0 73 41.962717829256533 431.00000000000000 0 73 41.654356134346031 432.00000000000000 0 73 41.346301228297428 433.00000000000000 0 73 41.038654697404382 434.00000000000000 0 73 40.731514459476827 435.00000000000000 0 73 40.424974794581658 436.00000000000000 0 73 40.255818464270114 437.00000000000000 0 73 40.086755353369732 438.00000000000000 0 73 39.917867353434850 439.00000000000000 0 73 39.749233964778320 440.00000000000000 0 73 39.580932318786601 441.00000000000000 0 73 39.571292794829226 442.00000000000000 0 73 39.563631563774734 443.00000000000000 0 73 39.558068051901223 444.00000000000000 0 73 39.554722404508901 445.00000000000000 0 73 39.553715616996143 446.00000000000000 0 73 39.657266351569440 447.00000000000000 0 73 39.765937417128150 448.00000000000000 0 73 39.879969627692716 449.00000000000000 0 73 39.999612490759816 450.00000000000000 0 73 40.125124869808772 451.00000000000000 0 73 40.152617147642353 452.00000000000000 0 73 40.183504400320928 453.00000000000000 0 73 40.217928800000394 454.00000000000000 0 73 40.256035398921355 455.00000000000000 0 73 40.297972388891715 456.00000000000000 0 73 40.327254720083459 457.00000000000000 0 73 40.360286050767584 458.00000000000000 0 73 40.397208019303193 459.00000000000000 0 73 40.438165576453649 460.00000000000000 0 73 40.483307268386895 461.00000000000000 0 73 40.539034869226214 462.00000000000000 0 73 40.599273790145894 463.00000000000000 0 73 40.664187392821496 464.00000000000000 0 73 40.733944047844147 465.00000000000000 0 73 40.808717517703336 466.00000000000000 0 73 40.664332426370393 467.00000000000000 0 73 40.521704078737720 468.00000000000000 0 73 40.380866665196834 469.00000000000000 0 73 40.241853267324956 470.00000000000000 0 73 40.104695913517965 471.00000000000000 0 73 39.972495663344418 472.00000000000000 0 73 39.842191849894313 473.00000000000000 0 73 39.713814122289136 474.00000000000000 0 73 39.587391303130389 475.00000000000000 0 73 39.462951441502817 476.00000000000000 0 73 39.207099552979223 477.00000000000000 0 73 38.953325634099293 478.00000000000000 0 73 38.701634974176756 479.00000000000000 0 73 38.452031704309839 480.00000000000000 0 73 38.204518848242635 481.00000000000000 0 73 37.850339331552433 482.00000000000000 0 73 37.499629907860040 483.00000000000000 0 73 37.152372919992771 484.00000000000000 0 73 36.808549797053971 485.00000000000000 0 73 36.468141110686901 486.00000000000000 0 73 36.148846652100389 487.00000000000000 0 73 35.832615384912494 488.00000000000000 0 73 35.519430104552100 489.00000000000000 0 73 35.209272918395435 490.00000000000000 0 73 34.902125290414418 491.00000000000000 0 73 34.651725654340154 492.00000000000000 0 73 34.403567500014248 493.00000000000000 0 73 34.157640190370422 494.00000000000000 0 73 33.913932551210898 495.00000000000000 0 73 33.672432903614840 496.00000000000000 0 73 33.383328009076024 497.00000000000000 0 73 33.097063645841708 498.00000000000000 0 73 32.813618075381683 499.00000000000000 0 73 32.532969234677886 500.00000000000000 0 73 32.255094765643868 501.00000000000000 0 73 31.934713443418957 502.00000000000000 0 73 31.617917421858778 503.00000000000000 0 73 31.304669704697318 504.00000000000000 0 73 30.994933290298306 505.00000000000000 0 73 30.688671195313844 506.00000000000000 0 73 30.370826286019131 507.00000000000000 0 73 30.056721936546602 508.00000000000000 0 73 29.746314865948733 509.00000000000000 0 73 29.439562004395146 510.00000000000000 0 73 29.136420509801074 511.00000000000000 0 73 28.836838598246214 512.00000000000000 0 73 28.540783302147869 513.00000000000000 0 73 28.248212548482392 514.00000000000000 0 73 27.959084548139426 515.00000000000000 0 73 27.673357807573542 516.00000000000000 0 73 27.431075516865807 517.00000000000000 0 73 27.191295703556221 518.00000000000000 0 73 26.953992216327844 519.00000000000000 0 73 26.719139002367353 520.00000000000000 0 73 26.486710117562357 521.00000000000000 0 73 26.245857119064794 522.00000000000000 0 73 26.007573696871923 523.00000000000000 0 73 25.771831137540346 524.00000000000000 0 73 25.538600918367944 525.00000000000000 0 73 25.307854714328080 526.00000000000000 0 73 25.079564404488060 527.00000000000000 0 73 24.853702077935623 528.00000000000000 0 73 24.630240039238924 529.00000000000000 0 73 24.409150813457266 530.00000000000000 0 73 24.190407150728156 531.00000000000000 0 73 23.962344010648387 532.00000000000000 0 73 23.736802866375864 533.00000000000000 0 73 23.513753205981402 534.00000000000000 0 73 23.293164823349294 535.00000000000000 0 73 23.075007820016221 536.00000000000000 0 73 22.848225470846355 537.00000000000000 0 73 22.624053074125097 538.00000000000000 0 73 22.402457252660927 539.00000000000000 0 73 22.183405021725697 540.00000000000000 0 73 21.966863788139001 541.00000000000000 0 73 21.764037212639721 542.00000000000000 0 73 21.563419337939099 543.00000000000000 0 73 21.364983107819814 544.00000000000000 0 73 21.168701772311138 545.00000000000000 0 73 20.974548887106042 546.00000000000000 0 73 20.772592450878648 547.00000000000000 0 73 20.572921620712137 548.00000000000000 0 73 20.375507045151021 549.00000000000000 0 73 20.180319744050461 550.00000000000000 0 73 19.987331106001829 551.00000000000000 0 73 19.805124629542355 552.00000000000000 0 73 19.624878922106923 553.00000000000000 0 73 19.446569776275943 554.00000000000000 0 73 19.270173281351070 555.00000000000000 0 73 19.095665821372968 556.00000000000000 0 73 18.923024073050261 557.00000000000000 0 73 18.752225003607261 558.00000000000000 0 73 18.583245868556553 559.00000000000000 0 73 18.416064209401714 560.00000000000000 0 73 18.250657851276799 561.00000000000000 0 73 18.079874102083089 562.00000000000000 0 73 17.910971071687641 563.00000000000000 0 73 17.743924738193215 564.00000000000000 0 73 17.578711402326871 565.00000000000000 0 73 17.415307683947518 566.00000000000000 0 73 17.269770379220756 567.00000000000000 0 73 17.125684078945294 568.00000000000000 0 73 16.983031640222642 569.00000000000000 0 73 16.841796132865031 570.00000000000000 0 73 16.701960837453857 571.00000000000000 0 73 16.616958434475738 572.00000000000000 0 73 16.532736235322872 573.00000000000000 0 73 16.449286338280942 574.00000000000000 0 73 16.366600930017249 575.00000000000000 0 73 16.284672285187501 576.00000000000000 0 73 16.203492766015387 577.00000000000000 0 73 16.123054821847685 578.00000000000000 0 73 16.043350988687394 579.00000000000000 0 73 15.964373888704930 580.00000000000000 0 73 15.886116229730037 581.00000000000000 0 73 15.794582556479295 582.00000000000000 0 73 15.703828746388146 583.00000000000000 0 73 15.613846455501905 584.00000000000000 0 73 15.524627435745051 585.00000000000000 0 73 15.436163534125143 586.00000000000000 0 73 15.341021221826649 587.00000000000000 0 73 15.246680698780374 588.00000000000000 0 73 15.153133301762400 589.00000000000000 0 73 15.060370469853773 590.00000000000000 0 73 14.968383743452556 591.00000000000000 0 73 14.868810701926670 592.00000000000000 0 73 14.770086893344413 593.00000000000000 0 73 14.672203064860151 594.00000000000000 0 73 14.575150076339073 595.00000000000000 0 73 14.478918899127855 596.00000000000000 0 73 14.383500614827245 597.00000000000000 0 73 14.288886414066512 598.00000000000000 0 73 14.195067595280806 599.00000000000000 0 73 14.102035563492542 600.00000000000000 0 73 14.009781829096097 Index: trunk/HiggsBounds_KW/example_programs/Key.dat-for-comparison-SM_vs_4thGen =================================================================== --- trunk/HiggsBounds_KW/example_programs/Key.dat-for-comparison-SM_vs_4thGen (revision 508) +++ trunk/HiggsBounds_KW/example_programs/Key.dat-for-comparison-SM_vs_4thGen (revision 509) @@ -1,703 +1,698 @@ *********** Key to Process Numbers ************* - This key has been generated with HiggsBounds version 4.2.0 + This key has been generated with HiggsBounds version 4.2.1 with the setting whichanalyses=LandH ************************************************************** process 0 no process applies ************************************************************** hep-ex/0602042, table 14b (LEP) process 1 (e e)->(h1)Z->(b b-bar)Z (hep-ex/0602042, table 14b (LEP)) ************************************************************** hep-ex/0602042, table 14c (LEP) process 2 (e e)->(h1)Z->(tau tau)Z (hep-ex/0602042, table 14c (LEP)) ************************************************************** hep-ex/0206022 (OPAL) process 3 (e e)->(h1)Z->(...)Z (hep-ex/0206022 (OPAL)) ************************************************************** hep-ex/0107032v1 (LEP) process 4 (e e)->(h1)Z->(invisible)Z (hep-ex/0107032v1 (LEP)) ************************************************************** LHWG Note 2002-02 process 5 (e e)->(h1)Z->(gamma gamma)Z (LHWG Note 2002-02) ************************************************************** LHWG (unpublished) process 6 (e e)->(h1)Z->(2 jets)Z (LHWG (unpublished)) ************************************************************** hep-ex/0107034 (LHWG) process 7 (e e)->(h1)Z->(2 jets)Z (hep-ex/0107034 (LHWG)) ************************************************************** hep-ex/0410017 (DELPHI) process 8 (e e)->b b-bar(h1)->b b-bar(b b-bar) where h1 is CP even (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0410017 (DELPHI) process 9 (e e)->b b-bar(h1)->b b-bar(b b-bar) where h1 is CP odd (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0410017 (DELPHI) process 10 (e e)->b b-bar(h1)->b b-bar(tau tau) where h1 is CP even (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0111010 (OPAL) process 11 (e e)->b b-bar(h1)->b b-bar(tau tau) where h1 is CP even (hep-ex/0111010 (OPAL)) ************************************************************** hep-ex/0410017 (DELPHI) process 12 (e e)->b b-bar(h1)->b b-bar(tau tau) where h1 is CP odd (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0111010 (OPAL) process 13 (e e)->b b-bar(h1)->b b-bar(tau tau) where h1 is CP odd (hep-ex/0111010 (OPAL)) ************************************************************** hep-ex/0410017 (DELPHI) process 14 (e e)->tau tau(h1)->tau tau(tau tau) where h1 is CP even (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0410017 (DELPHI) process 15 (e e)->tau tau(h1)->tau tau(tau tau) where h1 is CP odd (hep-ex/0410017 (DELPHI)) ************************************************************** hep-ex/0401022 (Delphi) process 16 (e e)->(h1)Z->(invisible)Z (hep-ex/0401022 (Delphi)) ************************************************************** hep-ex/0501033 (L3) process 17 (e e)->(h1)Z->(invisible)Z (hep-ex/0501033 (L3)) ************************************************************** [hep-ex] arXiv:0707.0373 (OPAL) process 18 (e e)->(h1)Z->(invisible)Z ([hep-ex] arXiv:0707.0373 (OPAL)) ************************************************************** hep-ex/0602042, table 15 (LEP) process 19 *** ************************************************************** hep-ex/0602042, table 16 (LEP) process 20 *** ************************************************************** hep-ex/0602042, table 18 (LEP) process 21 (ee)->(h1 h1)->(b b b b) (hep-ex/0602042, table 18 (LEP)) ************************************************************** hep-ex/0602042, table 19 (LEP) process 22 (ee)->(h1 h1)->(tau tau tau tau) (hep-ex/0602042, table 19 (LEP)) ************************************************************** hep-ex/0602042, table 20 (LEP) process 23 *** ************************************************************** hep-ex/0602042, table 21 (LEP) process 24 *** ************************************************************** hep-ex/0602042 (LEP) process 25 (ee)->(h1->b b)(h1->tau tau) (hep-ex/0602042 (LEP)) ************************************************************** hep-ex/0602042 (LEP) process 26 (ee)->(h1->tau tau)(h1->b b) (hep-ex/0602042 (LEP)) ************************************************************** CDF Note 10799 process 27 (p p-bar)->Z(h1)->l l (b b-bar) (CDF Note 10799) ************************************************************** D0 Note 6296 process 28 (p p-bar)->Z(h1)->l l (b b-bar) (D0 Note 6296) ************************************************************** [hep-ex] arXiv:1008.3564 (D0) process 29 (p p-bar)->Z(h1)->l l (b b-bar) ([hep-ex] arXiv:1008.3564 (D0)) ************************************************************** CDF Note 10798 process 30 (p p-bar)->V h1-> (b b-bar) +missing Et where h1 is SM-like (CDF Note 10798) ************************************************************** D0 Note 6299 process 31 (p p-bar)->V h1-> (b b-bar) +missing Et where h1 is SM-like (D0 Note 6299) ************************************************************** ATLAS-CONF-2012-161 process 32 (p p)->V(h1)->V (b b-bar) (ATLAS-CONF-2012-161) ************************************************************** CMS-PAS-HIG-13-012 process 33 (p p)->V h1->b b where h1 is SM-like (CMS-PAS-HIG-13-012) ************************************************************** CMS-PAS-HIG-13-011 process 34 (p p)->h1/VBF->bb+... where h1 is SM-like (CMS-PAS-HIG-13-011) ************************************************************** D0 Note 6309 process 35 (p p-bar)->W(h1)->l nu (b b-bar) (D0 Note 6309) ************************************************************** CDF Note 10796 process 36 (p p-bar)->W(h1)->l nu (b b-bar) (CDF Note 10796) ************************************************************** [hep-ex] arXiv:1012.0874 (D0) process 37 (p p-bar)->W(h1)->l nu (b b-bar) ([hep-ex] arXiv:1012.0874 (D0)) ************************************************************** [hep-ex] arXiv:0906.5613 (CDF) process 38 (p p-bar)->W(h1)->l nu (b b-bar) ([hep-ex] arXiv:0906.5613 (CDF)) ************************************************************** [hep-ex] arXiv:1402.3244 (ATLAS) process 39 (p p)->Vh1->V (invisible) ([hep-ex] arXiv:1402.3244 (ATLAS)) ************************************************************** [hep-ex] arXiv:1404.1344 (CMS) process 40 (p p)->Zh1->Z (invisible) ([hep-ex] arXiv:1404.1344 (CMS)) ************************************************************** [hep-ex] arXiv:1404.1344 (CMS) process 41 (p p)->h1(VBF)->V (invisible) ([hep-ex] arXiv:1404.1344 (CMS)) ************************************************************** [hep-ex] arXiv:1404.1344 (CMS) process 42 (p p)->h1(VBF)/Zh1, h1->(invisible) ([hep-ex] arXiv:1404.1344 (CMS)) ************************************************************** D0 Note 5757 process 43 (p p-bar)->h1/VBF->W W->l l where h1 is SM-like (D0 Note 5757) ************************************************************** [hep-ex] arXiv:0809.3930 (CDF) process 44 (p p-bar)->h1->W W ([hep-ex] arXiv:0809.3930 (CDF)) ************************************************************** D0 Note 6276 process 45 (p p-bar)->h1+...->V V +... ->l l l missing Et +... where h1 is SM-like (D0 Note 6276) ************************************************************** D0 Note 6301 process 46 (p p-bar)->V h1->V W W (D0 Note 6301) ************************************************************** CDF Note 10599 process 47 (p p-bar)->h1->W W (CDF Note 10599) ************************************************************** CDF Note 10599 process 48 (p p-bar)->h1+...->W W +... where h1 is SM-like (CDF Note 10599) ************************************************************** [hep-ex] arXiv:1001.4468 (CDF) process 49 (p p-bar)->h1+...->W W +... where h1 is SM-like ([hep-ex] arXiv:1001.4468 (CDF)) ************************************************************** D0 Note 6302 process 50 (p p-bar)->h1+...->W W +... where h1 is SM-like (D0 Note 6302) ************************************************************** D0 Note 6183 process 51 (p p-bar)->h1+... where h1 is SM-like (D0 Note 6183) ************************************************************** [hep-ex] arXiv:1001.4481 (D0) process 52 (p p-bar)->h1+...->W W +... where h1 is SM-like ([hep-ex] arXiv:1001.4481 (D0)) ************************************************************** [hep-ex] arXiv:1108.3331 (TEVNPHWG) process 53 (p p-bar)->h1->V V ([hep-ex] arXiv:1108.3331 (TEVNPHWG)) ************************************************************** ATLAS-CONF-2012-012 process 54 (p p)->h1->W W where h1 is SM-like (ATLAS-CONF-2012-012) ************************************************************** ATLAS-CONF-2013-030 process 55 (p p)->h1->W W where h1 is SM-like (ATLAS-CONF-2013-030) ************************************************************** [hep-ex] arxiv:1112.2577 process 56 pp->h + X->W W* + X ->l l nu nu, h=1 where h is SM-like ([hep-ex] arxiv:1112.2577) ************************************************************** CMS-PAS-HIG-13-003 process 57 (p p)->h1+...->W W +... where h1 is SM-like (CMS-PAS-HIG-13-003) ************************************************************** CMS-PAS-HIG-13-027 process 58 (p p)->h1+...->W W +... where h1 is SM-like (CMS-PAS-HIG-13-027) ************************************************************** CMS-PAS-HIG-13-022 process 59 (p p)->h1(VBF)->WW (CMS-PAS-HIG-13-022) ************************************************************** [hep-ex] arXiv:1109.3357 (ATLAS) process 60 (p p)->h1->V V-> l l nu nu where h1 is SM-like ([hep-ex] arXiv:1109.3357 (ATLAS)) ************************************************************** ATLAS-CONF-2012-016 process 61 (p p)->h1->V V-> l l nu nu where h1 is SM-like (ATLAS-CONF-2012-016) ************************************************************** [hep-ex] arxiv:1202.3478 (CMS) process 62 (p p)->h1/VBF->V V-> l l nu nu where h1 is SM-like ([hep-ex] arxiv:1202.3478 (CMS)) ************************************************************** [hep-ex] arXiv:1109.3615 (ATLAS) process 63 (p p)->h1/VBF->W W where h1 is SM-like ([hep-ex] arXiv:1109.3615 (ATLAS)) ************************************************************** ATLAS-CONF-2012-018 process 64 (p p)->h1/VBF->W W where h1 is SM-like (ATLAS-CONF-2012-018) ************************************************************** CMS-PAS-HIG-12-046 process 65 (p p)->h1->W W-> l nu q q where h1 is SM-like (CMS-PAS-HIG-12-046) ************************************************************** [hep-ex] arXiv:1108.5064 (ATLAS) process 66 (p p)->h1/VBF->Z Z-> l l q q where h1 is SM-like ([hep-ex] arXiv:1108.5064 (ATLAS)) ************************************************************** ATLAS-CONF-2012-017 process 67 (p p)->h1/VBF->Z Z-> l l q q where h1 is SM-like (ATLAS-CONF-2012-017) ************************************************************** [hep-ex] arXiv:1202.1416 (CMS) process 68 (p p)->h1/VBF->Z Z-> l l q q where h1 is SM-like ([hep-ex] arXiv:1202.1416 (CMS)) ************************************************************** [hep-ex] arXiv:1202.1416 (CMS) process 69 (p p)->h1/VBF->Z Z-> l l q q where h1 is SM-like ([hep-ex] arXiv:1202.1416 (CMS)) ************************************************************** [hep-ex] arXiv:1202.1415 (ATLAS) process 70 (p p)->h1/VBF/V h1->Z Z-> l l l l where h1 is SM-like ([hep-ex] arXiv:1202.1415 (ATLAS)) ************************************************************** ATLAS-CONF-2012-092 process 71 (p p)->h1/VBF/V h1->Z Z-> l l l l where h1 is SM-like (ATLAS-CONF-2012-092) ************************************************************** ATLAS-CONF-2013-013 process 72 (p p)->h1->Z Z-> l l l l where h1 is SM-like (ATLAS-CONF-2013-013) ************************************************************** ATLAS-CONF-2013-013 process 73 (p p)->h1/ggF h->Z Z-> l l l l (ATLAS-CONF-2013-013) ************************************************************** ATLAS-CONF-2013-013 process 74 (p p)->h1/VBF/V h->Z Z-> l l l l (ATLAS-CONF-2013-013) ************************************************************** [hep-ex] arxiv:1202.1997 (CMS) process 75 (p p)->h1/VBF/V/tt h1->Z Z-> l l l l where h1 is SM-like ([hep-ex] arxiv:1202.1997 (CMS)) ************************************************************** CMS-PAS-HIG-13-002 process 76 (p p)->h1->Z Z-> l l l l (low mass) where h1 is SM-like (CMS-PAS-HIG-13-002) ************************************************************** CMS-PAS-HIG-13-002 process 77 (p p)->h1->Z Z-> l l l l (high mass) where h1 is SM-like (CMS-PAS-HIG-13-002) ************************************************************** CDF Note 10439 process 78 (p p-bar)->h1+...->tau tau +... where h1 is SM-like (CDF Note 10439) ************************************************************** D0 Note 5845 process 79 (p p-bar)->h1+...->tau tau (2 jets) where h1 is SM-like (D0 Note 5845) ************************************************************** CDF Note 9999 process 80 (p p-bar)->h1+... where h1 is SM-like (CDF Note 9999) ************************************************************** D0 Note 6305 process 81 (p p-bar)->h1+...->tau tau +... where h1 is SM-like (D0 Note 6305) ************************************************************** CDF Note 10010 process 82 (p p-bar)->V (h1)/VBF-> (b b-bar) q q where h1 is SM-like (CDF Note 10010) ************************************************************** D0 Note 6171 process 83 (p p-bar)->h1+...->tau tau (2 jets) where h1 is SM-like (D0 Note 6171) ************************************************************** D0 Note 6304 process 84 (p p-bar)->h1+... where h1 is SM-like (D0 Note 6304) ************************************************************** CDF Note 10500 process 85 (p p-bar)->V h1-> V tau tau (CDF Note 10500) ************************************************************** CDF Note 10573 process 86 (p p-bar)->h1+...->V V +... ->l l l l +... where h1 is SM-like (CDF Note 10573) ************************************************************** D0 Note 6286 process 87 (p p-bar)->h1+...->tau tau +... where h1 is SM-like (D0 Note 6286) ************************************************************** [hep-ex] arXiv:1207.0449 (TEVNPHWG) process 88 (p p-bar)->h1+... where h1 is SM-like ([hep-ex] arXiv:1207.0449 (TEVNPHWG)) ************************************************************** [hep-ex] arXiv:1207.6436 (TEVNPHWG) process 89 (p p-bar)->V (h1)-> (b b-bar)+...([hep-ex] arXiv:1207.6436 (TEVNPHWG)) ************************************************************** (hep-ex) arxiv:1202.1408 (ATLAS) process 90 (p p)->h1+... where h1 is SM-like ((hep-ex) arxiv:1202.1408 (ATLAS)) ************************************************************** ATLAS-CONF-2012-019 process 91 (p p)->h+..., h=1 where h is SM-like (ATLAS-CONF-2012-019) ************************************************************** (hep-ex) arXiv:1207.7214 (ATLAS) process 92 (p p)->h+..., h=1 where h is SM-like ((hep-ex) arXiv:1207.7214 (ATLAS)) ************************************************************** ATLAS-CONF-2011-157, CMS-PAS-HIG-11-023 process 93 (p p)->h1+... where h1 is SM-like (ATLAS-CONF-2011-157, CMS-PAS-HIG-11-023) ************************************************************** [hep-ex] arxiv:1202.1488 (CMS) process 94 (p p)->h1+... where h1 is SM-like ([hep-ex] arxiv:1202.1488 (CMS)) ************************************************************** CMS-PAS-HIG-12-045 process 95 (p p)->h+..., h=1 where h is SM-like (CMS-PAS-HIG-12-045) ************************************************************** [hep-ex] arXiv:1011.1931 (D0) process 96 (p p-bar)->h1(b/b-bar)->(b b-bar) (b/b-bar) ([hep-ex] arXiv:1011.1931 (D0)) ************************************************************** arXiv:1106.4782 (CDF) process 97 (p p-bar)->h1(b/b-bar)->(b b-bar) (b/b-bar) (arXiv:1106.4782 (CDF)) ************************************************************** [hep-ex] arXiv:1106.4555 (D0) process 98 (p p-bar)->h1->tau tau ([hep-ex] arXiv:1106.4555 (D0)) ************************************************************** [hep-ex] arXiv:0906.1014 (CDF) process 99 (p p-bar)->h1->tau tau ([hep-ex] arXiv:0906.1014 (CDF)) ************************************************************** [hep-ex] arXiv:1003.3363 (TEVNPHWG) process 100 (p p-bar)->h1->tau tau ([hep-ex] arXiv:1003.3363 (TEVNPHWG)) ************************************************************** ATLAS-CONF-2012-160 process 101 (p p)->h1->tau tau +... where h1 is SM-like (ATLAS-CONF-2012-160) ************************************************************** - [hep-ex] arXiv:1107.5003 (ATLAS) + ATLAS-CONF-2014-049,arXiv:1409.6064 process 102 - (p p)->h1->tau tau ([hep-ex] arXiv:1107.5003 (ATLAS)) + (p p)->bbh1->tau tau (ATLAS-CONF-2014-049,arXiv:1409.6064) ************************************************************** - ATLAS-CONF-2014-049 + ATLAS-CONF-2014-049,,arXiv:1409.6064 process 103 - (p p)->bbh1->tau tau (ATLAS-CONF-2014-049) -************************************************************** - ATLAS-CONF-2014-049 - -process 104 - (p p)->ggh1->tau tau (ATLAS-CONF-2014-049) + (p p)->ggh1->tau tau (ATLAS-CONF-2014-049,,arXiv:1409.6064) ************************************************************** CMS-PAS-HIG-12-043 -process 105 +process 104 (p p)->h1->tau tau +... where h1 is SM-like (CMS-PAS-HIG-12-043) ************************************************************** ATLAS-CONF-2013-010 -process 106 +process 105 (p p)->h1->mu mu +... where h1 is SM-like (ATLAS-CONF-2013-010) ************************************************************** [hep-ex] arXiv:1406.7663 (ATLAS) -process 107 +process 106 (p p)->h1->mu mu +... where h1 is SM-like ([hep-ex] arXiv:1406.7663 (ATLAS)) ************************************************************** D0 Note 5873 -process 108 +process 107 (p p-bar)->W(h1)->W W W->l l nu nu (D0 Note 5873) ************************************************************** CDF Note 7307 vs 3 -process 109 +process 108 (p p-bar)->W(h1)->W W W (CDF Note 7307 vs 3) ************************************************************** [hep-ex] arXiv:1107.1268 (D0) -process 110 +process 109 (p p-bar)->V h1-> ll + X where h1 is SM-like ([hep-ex] arXiv:1107.1268 (D0)) ************************************************************** CMS-PAS-HIG-13-009 -process 111 +process 110 (p p)->W(h1)->W W W where h1 is SM-like (CMS-PAS-HIG-13-009) ************************************************************** CMS-PAS-HIG-12-006 -process 112 +process 111 (p p)->W(h1)->W tau tau (CMS-PAS-HIG-12-006) ************************************************************** CMS-PAS-HIG-12-051 -process 113 +process 112 (p p)->V(h1)->V tau tau (CMS-PAS-HIG-12-051) ************************************************************** ATLAS-CONF-2012-078 -process 114 +process 113 (p p)->W(h1)->W W W where h1 is SM-like (ATLAS-CONF-2012-078) ************************************************************** D0 Note 6295 -process 115 +process 114 (p p-bar)->h1+...->gamma gamma+... where h1 is SM-like (D0 Note 6295) ************************************************************** [hep-ex] arXiv:0901.1887 (D0) -process 116 +process 115 (p p-bar)->h1+...->gamma gamma+... where h1 is SM-like ([hep-ex] arXiv:0901.1887 (D0)) ************************************************************** CDF Note 10485 -process 117 +process 116 (p p-bar)->h1+...->gamma gamma+... where h1 is SM-like (CDF Note 10485) ************************************************************** [hep-ex] arXiv:1107.4960 (TEVNPHWG) -process 118 +process 117 (p p-bar)->h1+...->gamma gamma+... where h1 is SM-like ([hep-ex] arXiv:1107.4960 (TEVNPHWG)) ************************************************************** [hep-ex] arXiv:1202.1414 (ATLAS) -process 119 +process 118 (p p)->h1+...->gamma gamma+... where h1 is SM-like ([hep-ex] arXiv:1202.1414 (ATLAS)) ************************************************************** ATLAS-CONF-2012-168 -process 120 +process 119 (p p)->h1+...->gamma gamma+... where h1 is SM-like (ATLAS-CONF-2012-168) ************************************************************** [hep-ex] arXiv:1407.6583 -process 121 +process 120 (p p)->h1/VBF/Wh1/Zh1/tth1->gamma gamma ([hep-ex] arXiv:1407.6583) ************************************************************** CMS-PAS-HIG-13-001 -process 122 +process 121 (p p)->h1+...->gamma gamma+... where h1 is SM-like (CMS-PAS-HIG-13-001) ************************************************************** [hep-ex] arXiv:1307.5515 (CMS) -process 123 +process 122 (p p)->h1+...->gamma Z+... where h1 is SM-like ([hep-ex] arXiv:1307.5515 (CMS)) ************************************************************** [hep-ex] arXiv:1402.3051 (ATLAS) -process 124 +process 123 (p p)->h1+...->gamma Z+... where h1 is SM-like ([hep-ex] arXiv:1402.3051 (ATLAS)) ************************************************************** [hep-ex] arXiv:1106.4885 (D0) -process 125 +process 124 (p p-bar)->h1(b/b-bar)->(tau tau) (b/b-bar) ([hep-ex] arXiv:1106.4885 (D0)) ************************************************************** D0 Note 6083 -process 126 +process 125 (p p-bar)->h1(b/b-bar)->(tau tau) (b/b-bar) (D0 Note 6083) ************************************************************** D0 Note 5739 -process 127 +process 126 (p p-bar)->t t-bar h1->t t-bar b b-bar (D0 Note 5739) ************************************************************** CDF Note 10574 -process 128 +process 127 (p p-bar)->t t-bar h1->t t-bar b b-bar (CDF Note 10574) ************************************************************** ATLAS-CONF-2012-135 -process 129 +process 128 (p p)->t t-bar h1->t t-bar b b-bar (ATLAS-CONF-2012-135) ************************************************************** CMS-PAS-HIG-12-025 -process 130 +process 129 (p p)->t t-bar h1->t t-bar b b-bar (CMS-PAS-HIG-12-025) ************************************************************** [hep-ex] arXiv:0806.0611 (D0) -process 131 +process 130 (p p-bar)->h1->Z gamma ([hep-ex] arXiv:0806.0611 (D0)) ************************************************************** [hep-ex] arXiv:0905.3381, table I (D0) -process 132 +process 131 *** ************************************************************** [hep-ex] arXiv:0905.3381, table II (D0) -process 133 +process 132 *** ************************************************************** D0 Note 6227 -process 134 +process 133 (p p-bar)->h1(b/b-bar)->(b b-bar) (b/b-bar) or (tau tau) (b/b-bar) (D0 Note 6227) ************************************************************** [hep-ex] arXiv:1406.5053 (ATLAS) -process 135 +process 134 *** ************************************************************** CMS-PAS-HIG-13-032 -process 136 +process 135 *** ************************************************************** CMS-PAS-HIG-14-013 -process 137 +process 136 *** ************************************************************** CMS-PAS-HIG-14-006 -process 138 +process 137 (p p)->h1/VBF/Wh1/Zh1/tth1->gamma gamma (including widths effects)(CMS-PAS-HIG-14-006) ************************************************************** [hep-ex] arXiv:1408.3316 (CMS) -process 139 +process 138 (pp)->h1->tautau, using -2ln(L) reconstruction ([hep-ex] arXiv:1408.3316 (CMS)) Index: trunk/HiggsBounds_KW/example_programs/plot_mhmax_llh.gnu =================================================================== --- trunk/HiggsBounds_KW/example_programs/plot_mhmax_llh.gnu (revision 0) +++ trunk/HiggsBounds_KW/example_programs/plot_mhmax_llh.gnu (revision 509) @@ -0,0 +1,94 @@ +set term postscript enhanced color eps font ',18' + +set pm3d map corners2color c4 clip1in + +filename ='mhmax_HBwithLHClikelihood.dat' + +set xrange [90.:1000.] +set yrange [1.:60.] +set dgrid3d 60,183,1 + +set zrange [0:*] +set cbrange [0:*] + +# Find minimum +set output 'tmp.eps' +splot filename u ($4):($5):(($10) > -0.00001 ? ($10) : 1/0) notit w pm3d +min_z = GPVAL_DATA_Z_MIN +plot filename u ($4):(($10) > -0.00001 ? (($10) < min_z+0.0000001 ? ($10) : 1/0): 1/0) notit w p +min_pos_x = GPVAL_DATA_X_MIN +plot filename u ($5):(($10) > -0.00001 ? (($10) < min_z+0.0000001 ? ($10) : 1/0): 1/0) notit w p +min_pos_y = GPVAL_DATA_X_MIN + +print min_pos_x, min_pos_y, min_z + +set contour +unset surface +set cntrparam bspline + +set table '2sigmacontour.dat' +set cntrparam levels discrete 5.99 +splot filename u ($4):($5):(($10)) notit w pm3d +unset table + +set table '95CL_all_analyses.dat' +set cntrparam levels discrete 1.0 +splot filename u ($4):($5):($13) notit w pm3d +unset table + +reset + +filename_out ='mhmax_HBwithLHClikelihood.eps' + +set pm3d map corners2color c4 clip1in + +set xrange [90.:1000.] +set yrange [1.:60.] + +set dgrid3d 60,183,1 + + +set size 0.7,1 + +set palette rgbformulae 30,31,32 + +set zrange [0.:20.] +set cbrange [0.:20.] + +set grid + +set xlabel 'M_A [GeV]' +set ylabel 'tan{/Symbol b}' + +set output filename_out + +set multiplot + +splot filename u ($4):($5):(($10)) notit w pm3d + +set size 0.545,0.724 +set origin 0.081,0.156 + +unset xtics +unset ytics +unset xlabel +unset ylabel +unset clabel +unset label 1 +unset label 2 +unset label 3 +unset label 4 +unset surface +set cntrparam bspline +unset colorbox + +set key Left reverse box width -13.4 at 655, 60.0 opaque font ',12' + +set label 1 'q@_{MSSM}^{obs}' at 1020,65 +set label 2 'm_h^{max} scenario' at 120,64 + +plot 'mhmax_CMS_obs_wo_SMHiggs.dat' u ($1):($2) w l lt 2 lw 6 lc rgb '#ADFF2F' title '95% CL excl. (CMS)',\ + '2sigmacontour.dat' u ($1):($2) w l lt 1 lw 6 lc rgb 'orange' title 'q@_{MSSM}^{obs} = 5.99 (reconstr.)' + +# '95CL_all_analyses.dat' u ($1):($2) w l lt 3 lw 4 lc rgb '#888888' title '95% CL excl. (HB)',\ +unset multiplot \ No newline at end of file Index: trunk/HiggsBounds_KW/example_programs/plot_mhmax_llh_comb.gnu =================================================================== --- trunk/HiggsBounds_KW/example_programs/plot_mhmax_llh_comb.gnu (revision 0) +++ trunk/HiggsBounds_KW/example_programs/plot_mhmax_llh_comb.gnu (revision 509) @@ -0,0 +1,62 @@ +set term postscript enhanced color eps font ',20' + +# set pm3d map corners2color c4 clip1in + +filename ='mhmax_HBwithLHClikelihood.dat' +filename_out ='mhmax_HBwithLHClikelihood_comb.eps' + +set xrange [90.:1000.] +set yrange [1.:60.] + +set view map + +# set size 0.7,0.7 +# set size square +set size 0.8,1 +# set size 1.,0.8 + +# set palette rgbformulae 30,31,32 +# set zrange [0.:20.] +# set cbrange [0.:20.] + +set grid front + +set xlabel 'M_A [GeV]' +set ylabel 'tan{/Symbol b}' + +set output filename_out + +# set key Left reverse box width 0 at 1000, 60.0 opaque font ',14' +# set key Left reverse box width 0 right outside opaque font ',14' + +# set size square +set key Left reverse spacing 1.2 box width 0 at 1000, 60.0 opaque font ',18' + + +ptsz = 1.2 + +set multiplot + +plot filename u ($4):((($18)==1) ? ($5) : 1/0) ps ptsz pt 5 lc rgb "orange" t "h", \ + filename u ($4):((($18)==2) ? ($5) : 1/0) ps ptsz pt 5 lc rgb "blue" t "H", \ + filename u ($4):((($18)==4) ? ($5) : 1/0) ps ptsz pt 5 lc rgb "red" t "A", \ + filename u ($4):((($18)==5) ? ($5) : 1/0) ps ptsz pt 5 lc rgb "magenta" t "h+A", \ + filename u ($4):((($18)==6) ? ($5) : 1/0) ps ptsz pt 5 lc rgb "#BBBBBB" t "H+A", \ + filename u ($4):((($18)==7) ? ($5) : 1/0) ps ptsz pt 5 lc rgb "#ADFF2F" t "h+H+A" + +# filename u ($4):((($18)==3) ? ($5) : 1/0) ps ptsz pt 5 lc rgb "yellow" t "h+H", \ + +set object 1 rectangle from screen 0, screen 0 to graph 0, screen 1 behind \ + fillstyle solid noborder +set object 2 rectangle from graph 1, screen 0 to graph 1.02, screen 1 behind\ + fillstyle solid noborder +set object 3 rectangle from screen 0, graph 1 to screen 1, screen 1 behind \ + fillstyle solid noborder +set object 4 rectangle from screen 0, screen 0 to screen 1, graph 0 behind \ + fillstyle solid noborder + +# set size 0.831,1. +# set origin -0.003,0. +unset key +unset grid +plot NaN notit \ No newline at end of file Index: trunk/HiggsBounds_KW/HiggsBounds_subroutines.F90 =================================================================== --- trunk/HiggsBounds_KW/HiggsBounds_subroutines.F90 (revision 508) +++ trunk/HiggsBounds_KW/HiggsBounds_subroutines.F90 (revision 509) @@ -1,1785 +1,1779 @@ ! This file is part of HiggsBounds ! -KW !************************************************************ subroutine initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses_in) ! This the first Higgsbounds subroutine that should be called ! by the user. ! It calls subroutines to read in the tables of Standard Model data, ! read in the tables of LEP, Tevatron and LHC data, ! set up lists of processes which should be checked against ! the experimental results, allocate arrays etc ! Arguments (input): ! * nHiggs= number of neutral Higgs in the model ! (see subroutine check_nH_nHplus in input.f90 for more details) ! * nHiggsplus= number of singly,positively charged Higgs in the model ! (see subroutine check_nH_nHplus in input.f90 for more details) ! * whichanalyses_in= which combination of experimental results to use ! (see subroutine check_whichanalyses in input.f90 for more details) !************************************************************ use usefulbits, only : np,Hneut,Hplus,Chineut,Chiplus,debug,inputmethod, & & inputsub,theo,whichanalyses,HiggsBounds_info,just_after_run,& & file_id_debug1,file_id_debug2,allocate_if_stats_required,run_HB_classic use input, only : setup_input,check_number_of_particles,check_whichanalyses use S95tables, only : setup_S95tables,S95_t2 use likelihoods, only : setup_likelihoods use theory_BRfunctions, only : setup_BRSM use channels, only : setup_channels use output, only : setup_output #ifdef enableCHISQ use S95tables_type3, only : clsb_t3,fillt3needs_M2_gt_2M1 #endif #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif !#define FORFITTINO implicit none !--------------------------------------input integer,intent(in) :: nHiggsneut ! integer,intent(in),optional :: nHiggsplus ! character(LEN=5),intent(in),optional :: whichanalyses_in integer,intent(in) :: nHiggsplus character(LEN=5),intent(in) :: whichanalyses_in !-----------------------------------internal integer :: i logical :: messages !------------------------------------------- ! if((.not.present(nHiggsplus)).or.(.not.present(whichanalyses_in)))then !Actually, this doesn't work as I wanted it to !because if initialize_HiggsBounds is called in the old way, the program !usually just crashes..... but leaving it in for now, in case !some compilers accept it ! call attempting_to_use_an_old_HB_version('init') ! endif #ifdef FORFITTINO write(*,*)'The arguments passed to initialize_HiggsBounds are:' write(*,*)'nHiggsneut=',nHiggsneut write(*,*)'nHiggsplus=',nHiggsplus write(*,*)'whichanalyses_in=','~'//trim(adjustl(whichanalyses_in))//'~' #endif #ifdef DEBUGGING debug=.True. #else debug=.False. #endif messages=debug.or.(inputmethod=='datfile') ! inputmethod='subrout' !('datfile' or 'website' are also possible, but not here) np(Hneut)=nHiggsneut np(Hplus)=nHiggsplus np(Chineut)=0! do not change this without contacting us first! np(Chiplus)=0! do not change this without contacting us first! whichanalyses=whichanalyses_in if(inputmethod=='subrout') then if(allocated(theo))then stop 'subroutine HiggsBounds_initialize has already been called once' endif if(messages)write(*,*)'doing other preliminary tasks...' ; call flush(6) call setup_input allocate(inputsub( 4 )) !(1)np(Hneut)>0 (2)np(Hplus)>0 (3)np(Chineut)>0 (4)np(Chineut)>0 and np(Chiplus)>0 ! | np ! |Hneu Hcha Chineut Chiplus ! | ==0 ==0 ==0 ==0 inputsub(1)%desc='HiggsBounds_neutral_input_*' inputsub(1)%req=req( 0, 1, 1, 1) inputsub(2)%desc='HiggsBounds_charged_input' inputsub(2)%req=req( 1, 0, 1, 1) inputsub(3)%desc='SUSYBounds_neutralinoonly_input' inputsub(3)%req=req( 1, 1, 0, 1) inputsub(4)%desc='SUSYBounds_neutralinochargino_input' inputsub(4)%req=req( 1, 1, 0, 0) do i=1,ubound(inputsub,dim=1) inputsub(i)%stat=0 enddo endif #ifndef WEBVERSION if(inputmethod.ne.'datfile') call HiggsBounds_info if (run_HB_classic.EQV..True.) then PRINT *, "run_HB_classic=True - HiggsBounds is running in classic mode" endif #endif if(messages)write(*,*)'reading in Standard Model tables...' ; call flush(6) call setup_BRSM if(messages)write(*,*)'reading in S95tables...' ; call flush(6) call setup_S95tables if(messages)write(*,*)'reading in likelihoods...' ; call flush(6) call setup_likelihoods !if(debug)write(*,*)'doing other preliminary tasks...' ; call flush(6) !call setup_input if(messages)then open(file_id_debug2,file='debug_predratio.txt') open(file_id_debug1,file='debug_channels.txt') endif if(messages)write(*,*)'sorting out processes to be checked...'; call flush(6) call setup_channels if(messages)write(*,*)'preparing output arrays...' ; call flush(6) call setup_output #ifdef enableCHISQ if(allocated(allocate_if_stats_required))then call fillt3needs_M2_gt_2M1(clsb_t3,S95_t2) endif #endif just_after_run=.False. contains ! | np ! |Hneu Hcha Chineut Chiplus ! | ==0 ==0 ==0 ==0 function req(Hneu,Hcha, Chneu, Chcha) integer, intent(in) ::Hneu,Hcha, Chneu, Chcha integer :: req req=1 if(np(Hneut)==0) req= Hneu * req if(np(Hplus)==0) req= Hcha * req if(np(Chineut)==0)req= Chneu * req if(np(Chiplus)==0)req= Chcha * req end function req end subroutine initialize_HiggsBounds !************************************************************ !************************************************************ ! Version of initialize_HiggsBounds which takes an integer as ! the third argument. More useful for library linking to ! non-Fortran codes. subroutine initialize_HiggsBounds_int(nHn,nHp,flag) implicit none integer nHn,nHp,flag interface subroutine initialize_HiggsBounds(nHiggsneut, nHiggsplus, whichanalyses_in) integer,intent(in) :: nHiggsneut integer,intent(in),optional :: nHiggsplus character(LEN=5),intent(in),optional :: whichanalyses_in end subroutine initialize_HiggsBounds end interface IF (flag.EQ.1) then call initialize_HiggsBounds(nHn,nHp, "onlyL") elseif (flag.EQ.2) then call initialize_HiggsBounds(nHn,nHp, "onlyH") elseif (flag.EQ.3) then call initialize_HiggsBounds(nHn,nHp, "LandH") elseif (flag.EQ.4) then call initialize_HiggsBounds(nHn,nHp, "onlyP") else stop "Illegal value for flag in call to initialize_HB" endif end subroutine !************************************************************ !************************************************************ subroutine attempting_to_use_an_old_HB_version(subroutineid) use usefulbits, only : vers character(len=4),intent(in) :: subroutineid select case(subroutineid) case('init') write(*,*)'The subroutine initialize_HiggsBounds has been called with the' write(*,*)'wrong number of arguments. It should be called as:' write(*,*)'initialize_HiggsBounds(nHiggsneut,nHiggsplus,whichanalyses)' write(*,*) write(*,*)'Note that in early versions of HiggsBounds (HB 1.*.*)' write(*,*)'this subroutine was called as:' write(*,*)'initialize_HiggsBounds(nHiggsneut,whichanalyses)' write(*,*) case('effC','part','hadr') write(*,*)'The subroutine run_HiggsBounds_'//subroutineid//' has been discontinued in this' write(*,*)'version of HiggsBounds.' case default stop'wrong input to subroutine attempting_to_use_an_old_HB_version' end select write(*,*)'If you have code written for use with HB 1.*.*, you have two choices:' write(*,*) write(*,*)' (1) You can edit your code, such that it works with this' write(*,*)' version of HiggsBounds (HB'//trim(adjustl(vers))//').' write(*,*)' This has the advantage that you can test your model against many, many' write(*,*)' more Higgs search limits , including charged Higgs search limits.' write(*,*)' See the updated manual for more information.' write(*,*) write(*,*)' (2) You can download the most recent HB 1.*.* from the HiggsBounds' write(*,*)' website. This contains the LEP Higgs search limits which are' write(*,*)' generally the most useful when constraining new physics models.' write(*,*)' We will continue to support this code.' stop'Incorrect call to a HiggsBounds subroutine.' end subroutine attempting_to_use_an_old_HB_version !************************************************************ subroutine HiggsBounds_input_SLHA(infile) ! This subroutine can be called by the user after subroutine initialize_HiggsBounds ! has been called. ! Arguments (input): SLHA filename !************************************************************ use usefulbits, only : whichinput,inputsub,infile1,theo,g2,just_after_run, & & np,Hneut,Hplus use extra_bits_for_SLHA #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !----------------------------------------input character(len=100),intent(in) :: infile !--------------------------------------internal integer :: n !---------------------------------------------- whichinput='SLHA' if(np(Hneut).gt.0)inputsub(Hneut)%stat=inputsub(Hneut)%stat+1 if(np(Hplus).gt.0)inputsub(Hplus)%stat=inputsub(Hplus)%stat+1 ! note: can't be used for charginos or neutralinos yet n=1 if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' endif infile1=infile call getSLHAdata(theo(n),g2(n),infile1) just_after_run=.False. end subroutine HiggsBounds_input_SLHA !************************************************************ subroutine HiggsBounds_neutral_input_effC(Mh,GammaTotal_hj, & & g2hjss_s,g2hjss_p,g2hjcc_s,g2hjcc_p, & & g2hjbb_s,g2hjbb_p,g2hjtoptop_s,g2hjtoptop_p, & & g2hjmumu_s,g2hjmumu_p, & & g2hjtautau_s,g2hjtautau_p, & & g2hjWW,g2hjZZ,g2hjZga, & & g2hjgaga,g2hjgg,g2hjggZ,g2hjhiZ_nHbynH, & & BR_hjinvisible,BR_hjhihi_nHbynH ) ! This subroutine can be called by the user after subroutine initialize_HiggsBounds ! has been called. ! Arguments (input): theoretical predictions (see manual for definitions) !************************************************************ use usefulbits, only : theo,np,Hneut,g2,whichinput,inputsub,just_after_run #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !----------------------------------------input double precision,intent(in) :: Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) ), & & g2hjss_s( np(Hneut) ),g2hjss_p( np(Hneut) ),g2hjcc_s( np(Hneut) ),g2hjcc_p( np(Hneut) ), & & g2hjbb_s( np(Hneut) ),g2hjbb_p( np(Hneut) ),g2hjtoptop_s( np(Hneut) ),g2hjtoptop_p( np(Hneut) ),& & g2hjmumu_s( np(Hneut) ),g2hjmumu_p( np(Hneut) ), & & g2hjtautau_s( np(Hneut) ),g2hjtautau_p( np(Hneut) ), & & g2hjWW( np(Hneut) ),g2hjZZ( np(Hneut) ),g2hjZga( np(Hneut) ), & & g2hjgaga( np(Hneut) ),g2hjgg( np(Hneut) ),g2hjggZ( np(Hneut) ),g2hjhiZ_nHbynH(np(Hneut),np(Hneut)),& & BR_hjinvisible( np(Hneut) ),BR_hjhihi_nHbynH(np(Hneut),np(Hneut)) !--------------------------------------internal integer :: n integer :: subtype !---------------------------------------------- whichinput='effC' subtype=1 n=1 inputsub(subtype)%stat=inputsub(subtype)%stat+1 if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' endif if(np(Hneut).eq.0)then write(*,*)'subroutine HiggsBounds_neutral_input_effC should' write(*,*)'only be called if np(Hneut)>0' stop 'error in subroutine HiggsBounds_neutral_input_effC' endif theo(n)%particle(Hneut)%M = Mh theo(n)%particle(Hneut)%Mc = Mh theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj g2(n)%hjss_s = g2hjss_s g2(n)%hjss_p = g2hjss_p g2(n)%hjcc_s = g2hjcc_s g2(n)%hjcc_p = g2hjcc_p g2(n)%hjbb_s = g2hjbb_s g2(n)%hjbb_p = g2hjbb_p g2(n)%hjtoptop_s = g2hjtoptop_s g2(n)%hjtoptop_p = g2hjtoptop_p g2(n)%hjmumu_s = g2hjmumu_s g2(n)%hjmumu_p = g2hjmumu_p g2(n)%hjtautau_s = g2hjtautau_s g2(n)%hjtautau_p = g2hjtautau_p g2(n)%hjWW = g2hjWW g2(n)%hjZZ = g2hjZZ g2(n)%hjZga = g2hjZga g2(n)%hjgaga = g2hjgaga g2(n)%hjgg = g2hjgg g2(n)%hjggZ = g2hjggZ g2(n)%hjhiZ = g2hjhiZ_nHbynH theo(n)%BR_hjinvisible = BR_hjinvisible theo(n)%BR_hjhihi = BR_hjhihi_nHbynH just_after_run=.False. end subroutine HiggsBounds_neutral_input_effC !************************************************************ subroutine HiggsBounds_neutral_input_part(Mh,GammaTotal_hj,CP_value, & & CS_lep_hjZ_ratio, & & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio, & & CS_lep_hjhi_ratio_nHbynH, & & CS_gg_hj_ratio,CS_bb_hj_ratio, & & CS_bg_hjb_ratio, & & CS_ud_hjWp_ratio,CS_cs_hjWp_ratio, & & CS_ud_hjWm_ratio,CS_cs_hjWm_ratio, & & CS_gg_hjZ_ratio, & & CS_dd_hjZ_ratio,CS_uu_hjZ_ratio, & & CS_ss_hjZ_ratio,CS_cc_hjZ_ratio, & & CS_bb_hjZ_ratio, & & CS_tev_vbf_ratio,CS_tev_tthj_ratio, & & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio, & & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio, & & BR_hjss,BR_hjcc, & & BR_hjbb,BR_hjmumu,BR_hjtautau, & & BR_hjWW,BR_hjZZ,BR_hjZga, BR_hjgaga,BR_hjgg, & & BR_hjinvisible,BR_hjhihi_nHbynH ) ! This subroutine can be called by the user after subroutine initialize_HiggsBounds ! has been called. ! (see manual for full description) !************************************************************ use usefulbits, only : theo,np,Hneut,partR,whichinput,inputsub,just_after_run #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !----------------------------------------input double precision,intent(in) :: Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) ) integer,intent(in) ::CP_value( np(Hneut) ) double precision,intent(in) :: CS_lep_hjZ_ratio( np(Hneut) ), & & CS_lep_bbhj_ratio( np(Hneut) ),CS_lep_tautauhj_ratio( np(Hneut) ), & & CS_lep_hjhi_ratio_nHbynH(np(Hneut),np(Hneut)), & & CS_gg_hj_ratio( np(Hneut) ),CS_bb_hj_ratio( np(Hneut) ), & & CS_bg_hjb_ratio( np(Hneut) ), & & CS_ud_hjWp_ratio( np(Hneut) ),CS_cs_hjWp_ratio( np(Hneut) ), & & CS_ud_hjWm_ratio( np(Hneut) ),CS_cs_hjWm_ratio( np(Hneut) ), & & CS_gg_hjZ_ratio( np(Hneut) ), & & CS_dd_hjZ_ratio( np(Hneut) ),CS_uu_hjZ_ratio( np(Hneut) ), & & CS_ss_hjZ_ratio( np(Hneut) ),CS_cc_hjZ_ratio( np(Hneut) ), & & CS_bb_hjZ_ratio( np(Hneut) ), & & CS_tev_vbf_ratio( np(Hneut) ),CS_tev_tthj_ratio( np(Hneut) ), & & CS_lhc7_vbf_ratio( np(Hneut) ),CS_lhc7_tthj_ratio( np(Hneut) ), & & CS_lhc8_vbf_ratio( np(Hneut) ),CS_lhc8_tthj_ratio( np(Hneut) ), & & BR_hjss( np(Hneut) ),BR_hjcc( np(Hneut) ), & & BR_hjbb( np(Hneut) ),BR_hjmumu( np(Hneut) ),BR_hjtautau( np(Hneut) ), & & BR_hjWW( np(Hneut) ),BR_hjZZ( np(Hneut) ),BR_hjZga( np(Hneut) ), & & BR_hjgaga( np(Hneut) ),BR_hjgg( np(Hneut) ), & & BR_hjinvisible( np(Hneut) ),BR_hjhihi_nHbynH(np(Hneut),np(Hneut)) !---------------------------------------internal integer :: n integer :: subtype !----------------------------------------------- whichinput='part' subtype=1 n=1 inputsub(subtype)%stat=inputsub(subtype)%stat+1 if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' endif if(np(Hneut).eq.0)then write(*,*)'subroutine HiggsBounds_neutral_input_part should' write(*,*)'only be called if np(Hneut)>0' stop 'error in subroutine HiggsBounds_neutral_input_part' endif theo(n)%particle(Hneut)%M = Mh theo(n)%particle(Hneut)%Mc = Mh theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj theo(n)%CP_value = CP_value theo(n)%lep%XS_hjZ_ratio = CS_lep_hjZ_ratio theo(n)%lep%XS_bbhj_ratio = CS_lep_bbhj_ratio theo(n)%lep%XS_tautauhj_ratio = CS_lep_tautauhj_ratio theo(n)%lep%XS_hjhi_ratio = CS_lep_hjhi_ratio_nHbynH partR(n)%gg_hj = CS_gg_hj_ratio partR(n)%qq_hj(5,:) = CS_bb_hj_ratio partR(n)%bg_hjb = CS_bg_hjb_ratio partR(n)%qq_hjWp(1,:) = CS_ud_hjWp_ratio partR(n)%qq_hjWp(2,:) = CS_cs_hjWp_ratio partR(n)%qq_hjWm(1,:) = CS_ud_hjWm_ratio partR(n)%qq_hjWm(2,:) = CS_cs_hjWm_ratio partR(n)%gg_hjZ(:) = CS_gg_hjZ_ratio partR(n)%qq_hjZ(1,:) = CS_dd_hjZ_ratio partR(n)%qq_hjZ(2,:) = CS_uu_hjZ_ratio partR(n)%qq_hjZ(3,:) = CS_ss_hjZ_ratio partR(n)%qq_hjZ(4,:) = CS_cc_hjZ_ratio partR(n)%qq_hjZ(5,:) = CS_bb_hjZ_ratio theo(n)%tev%XS_vbf_ratio = CS_tev_vbf_ratio theo(n)%tev%XS_tthj_ratio = CS_tev_tthj_ratio theo(n)%lhc7%XS_vbf_ratio = CS_lhc7_vbf_ratio theo(n)%lhc7%XS_tthj_ratio= CS_lhc7_tthj_ratio theo(n)%lhc8%XS_vbf_ratio = CS_lhc8_vbf_ratio theo(n)%lhc8%XS_tthj_ratio= CS_lhc8_tthj_ratio theo(n)%BR_hjss = BR_hjss theo(n)%BR_hjcc = BR_hjcc theo(n)%BR_hjbb = BR_hjbb theo(n)%BR_hjmumu = BR_hjmumu theo(n)%BR_hjtautau = BR_hjtautau theo(n)%BR_hjWW = BR_hjWW theo(n)%BR_hjZZ = BR_hjZZ theo(n)%BR_hjZga = BR_hjZga theo(n)%BR_hjgaga = BR_hjgaga theo(n)%BR_hjgg = BR_hjgg theo(n)%BR_hjinvisible = BR_hjinvisible theo(n)%BR_hjhihi = BR_hjhihi_nHbynH just_after_run=.False. end subroutine HiggsBounds_neutral_input_part !************************************************************ subroutine HiggsBounds_neutral_input_hadr(Mh,GammaTotal_hj,CP_value, & & CS_lep_hjZ_ratio, & & CS_lep_bbhj_ratio,CS_lep_tautauhj_ratio, & & CS_lep_hjhi_ratio_nHbynH, & & CS_tev_hj_ratio ,CS_tev_hjb_ratio, & & CS_tev_hjW_ratio,CS_tev_hjZ_ratio, & & CS_tev_vbf_ratio,CS_tev_tthj_ratio, & & CS_lhc7_hj_ratio ,CS_lhc7_hjb_ratio, & & CS_lhc7_hjW_ratio,CS_lhc7_hjZ_ratio, & & CS_lhc7_vbf_ratio,CS_lhc7_tthj_ratio, & & CS_lhc8_hj_ratio ,CS_lhc8_hjb_ratio, & & CS_lhc8_hjW_ratio,CS_lhc8_hjZ_ratio, & & CS_lhc8_vbf_ratio,CS_lhc8_tthj_ratio, & & BR_hjss,BR_hjcc, & & BR_hjbb, & & BR_hjmumu, & & BR_hjtautau, & & BR_hjWW,BR_hjZZ,BR_hjZga,BR_hjgaga, & & BR_hjgg, BR_hjinvisible, & & BR_hjhihi_nHbynH ) ! This subroutine can be called by the user after subroutine initialize_HiggsBounds ! has been called. ! (see manual for full description) !************************************************************ use usefulbits, only : theo,np,Hneut,whichinput,inputsub,just_after_run #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !----------------------------------------input double precision,intent(in) :: Mh( np(Hneut) ),GammaTotal_hj( np(Hneut) ) integer,intent(in) :: CP_value( np(Hneut) ) double precision,intent(in) :: CS_lep_hjZ_ratio( np(Hneut) ), & & CS_lep_bbhj_ratio( np(Hneut) ),CS_lep_tautauhj_ratio( np(Hneut) ), & & CS_lep_hjhi_ratio_nHbynH(np(Hneut),np(Hneut)), & & CS_tev_hj_ratio( np(Hneut) ) ,CS_tev_hjb_ratio( np(Hneut) ), & & CS_tev_hjW_ratio( np(Hneut) ) ,CS_tev_hjZ_ratio( np(Hneut) ), & & CS_tev_vbf_ratio( np(Hneut) ) ,CS_tev_tthj_ratio( np(Hneut)), & & CS_lhc7_hj_ratio( np(Hneut) ),CS_lhc7_hjb_ratio( np(Hneut) ), & & CS_lhc7_hjW_ratio( np(Hneut) ),CS_lhc7_hjZ_ratio( np(Hneut) ), & & CS_lhc7_vbf_ratio( np(Hneut) ),CS_lhc7_tthj_ratio( np(Hneut)), & & CS_lhc8_hj_ratio( np(Hneut) ),CS_lhc8_hjb_ratio( np(Hneut) ), & & CS_lhc8_hjW_ratio( np(Hneut) ),CS_lhc8_hjZ_ratio( np(Hneut) ), & & CS_lhc8_vbf_ratio( np(Hneut) ),CS_lhc8_tthj_ratio( np(Hneut)), & & BR_hjss( np(Hneut) ),BR_hjcc( np(Hneut) ), & & BR_hjbb( np(Hneut) ), & & BR_hjmumu( np(Hneut) ),BR_hjtautau( np(Hneut) ), & & BR_hjWW( np(Hneut) ),BR_hjZZ( np(Hneut) ), & & BR_hjZga( np(Hneut) ),BR_hjgaga( np(Hneut) ), & & BR_hjgg( np(Hneut) ), BR_hjinvisible( np(Hneut) ), & & BR_hjhihi_nHbynH(np(Hneut),np(Hneut)) !-------------------------------------internal integer :: n integer :: subtype !--------------------------------------------- whichinput='hadr' subtype=1 n=1 inputsub(subtype)%stat=inputsub(subtype)%stat+1 if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' endif if(np(Hneut).eq.0)then write(*,*)'subroutine HiggsBounds_neutral_input_hadr should' write(*,*)'only be called if np(Hneut)>0' stop 'error in subroutine HiggsBounds_neutral_input_hadr' endif ! write(*,*) "DEBUG HB: before hadronic input. Mass is ",theo(n)%particle(Hneut)%M theo(n)%particle(Hneut)%M = Mh theo(n)%particle(Hneut)%Mc = Mh theo(n)%particle(Hneut)%GammaTot= GammaTotal_hj theo(n)%CP_value = CP_value theo(n)%lep%XS_hjZ_ratio = CS_lep_hjZ_ratio theo(n)%lep%XS_bbhj_ratio = CS_lep_bbhj_ratio theo(n)%lep%XS_tautauhj_ratio = CS_lep_tautauhj_ratio theo(n)%lep%XS_hjhi_ratio = CS_lep_hjhi_ratio_nHbynH theo(n)%tev%XS_hj_ratio = CS_tev_hj_ratio theo(n)%tev%XS_hjb_ratio = CS_tev_hjb_ratio theo(n)%tev%XS_hjW_ratio = CS_tev_hjW_ratio theo(n)%tev%XS_hjZ_ratio = CS_tev_hjZ_ratio theo(n)%tev%XS_vbf_ratio = CS_tev_vbf_ratio theo(n)%tev%XS_tthj_ratio = CS_tev_tthj_ratio theo(n)%lhc7%XS_hj_ratio = CS_lhc7_hj_ratio theo(n)%lhc7%XS_hjb_ratio = CS_lhc7_hjb_ratio theo(n)%lhc7%XS_hjW_ratio = CS_lhc7_hjW_ratio theo(n)%lhc7%XS_hjZ_ratio = CS_lhc7_hjZ_ratio theo(n)%lhc7%XS_vbf_ratio = CS_lhc7_vbf_ratio theo(n)%lhc7%XS_tthj_ratio = CS_lhc7_tthj_ratio theo(n)%lhc8%XS_hj_ratio = CS_lhc8_hj_ratio theo(n)%lhc8%XS_hjb_ratio = CS_lhc8_hjb_ratio theo(n)%lhc8%XS_hjW_ratio = CS_lhc8_hjW_ratio theo(n)%lhc8%XS_hjZ_ratio = CS_lhc8_hjZ_ratio theo(n)%lhc8%XS_vbf_ratio = CS_lhc8_vbf_ratio theo(n)%lhc8%XS_tthj_ratio = CS_lhc8_tthj_ratio theo(n)%BR_hjss = BR_hjss theo(n)%BR_hjcc = BR_hjcc theo(n)%BR_hjbb = BR_hjbb theo(n)%BR_hjmumu = BR_hjmumu theo(n)%BR_hjtautau = BR_hjtautau theo(n)%BR_hjWW = BR_hjWW theo(n)%BR_hjZZ = BR_hjZZ theo(n)%BR_hjZga = BR_hjZga theo(n)%BR_hjgaga = BR_hjgaga theo(n)%BR_hjgg = BR_hjgg theo(n)%BR_hjinvisible = BR_hjinvisible theo(n)%BR_hjhihi = BR_hjhihi_nHbynH just_after_run=.False. ! write(*,*) "DEBUG HB: filled hadronic input. Mass is ",theo(n)%particle(Hneut)%M end subroutine HiggsBounds_neutral_input_hadr !************************************************************ subroutine HiggsBounds_charged_input(Mhplus,GammaTotal_Hpj, & & CS_lep_HpjHmj_ratio, & & BR_tWpb,BR_tHpjb, & & BR_Hpjcs,BR_Hpjcb,BR_Hpjtaunu) ! This subroutine can be called by the user after subroutine initialize_HiggsBounds ! has been called. ! Arguments (input): theoretical predictions (see manual for definitions) !************************************************************ use usefulbits, only : theo,np,Hplus,inputsub,just_after_run #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !----------------------------------------input double precision,intent(in) :: Mhplus( np(Hplus) ),GammaTotal_Hpj( np(Hplus) ), & & CS_lep_HpjHmj_ratio( np(Hplus) ), & & BR_tWpb,BR_tHpjb( np(Hplus) ), & & BR_Hpjcs( np(Hplus) ),BR_Hpjcb( np(Hplus) ),BR_Hpjtaunu( np(Hplus) ) !--------------------------------------internal integer :: n integer :: subtype !---------------------------------------------- n=1 subtype=2 inputsub(subtype)%stat=inputsub(subtype)%stat+1 if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' endif if(np(Hplus).eq.0)then write(*,*)'subroutine HiggsBounds_charged_input should' write(*,*)'only be called if np(Hplus)>0' stop 'error in subroutine HiggsBounds_charged_input' endif theo(n)%particle(Hplus)%M = Mhplus theo(n)%particle(Hplus)%Mc = Mhplus theo(n)%particle(Hplus)%GammaTot= GammaTotal_Hpj theo(n)%lep%XS_HpjHmj_ratio = CS_lep_HpjHmj_ratio theo(n)%BR_tWpb = BR_tWpb theo(n)%BR_tHpjb = BR_tHpjb theo(n)%BR_Hpjcs = BR_Hpjcs theo(n)%BR_Hpjcb = BR_Hpjcb theo(n)%BR_Hpjtaunu = BR_Hpjtaunu just_after_run=.False. end subroutine HiggsBounds_charged_input !************************************************************ subroutine HiggsBounds_set_mass_uncertainties(dMhneut, dMhch) ! Assigns the mass uncertainties in the subroutine version. ! use usefulbits, only : theo,np,Hneut,Hplus implicit none double precision, intent(in) :: dMhneut(np(Hneut)) double precision, intent(in) :: dMhch(np(Hplus)) theo(1)%particle(Hneut)%dMh = dMhneut theo(1)%particle(Hplus)%dMh = dMhch end subroutine HiggsBounds_set_mass_uncertainties !************************************************************ subroutine get_mass_variation_param(n) use usefulbits, only : theo,np,Hneut,Hplus,diffMhneut,diffMhch,ndmh,dmhsteps,small_mh implicit none integer, intent(in) :: n double precision :: dMhneut(np(Hneut)) double precision :: dMhch(np(Hplus)) integer :: km(np(Hneut)+np(Hplus)) integer :: dm(dmhsteps**(np(Hneut)+np(Hplus)),np(Hneut)+np(Hplus)) integer i,j,k,kp if(np(Hneut).gt.0) dMhneut = theo(n)%particle(Hneut)%dMh if(np(Hplus).gt.0) dMhch = theo(n)%particle(Hplus)%dMh if (modulo(dmhsteps,2).NE.1) then stop 'Wrong number of steps in set_mass_uncertainty: must be odd (>=3)' endif ndmh = 0 do i=1,np(Hneut) IF (dMhneut(i).GT.small_mh) THEN ndmh = ndmh + 1 ENDIF km(i)=-(dmhsteps-1)/2 enddo do i=1,np(Hplus) IF (dMhch(i).GT.small_mh) ndmh = ndmh + 1 km(i+np(Hneut))=-(dmhsteps-1)/2 enddo IF (ndmh.EQ.0) THEN RETURN ENDIF ! print *, "Number of mass uncertainties: ", ndmh if(allocated(diffMhneut)) deallocate(diffMhneut) if(allocated(diffMhch)) deallocate(diffMhch) allocate(diffMhneut(dmhsteps**(np(Hneut)+np(Hplus)),np(Hneut))) allocate(diffMhch(dmhsteps**(np(Hneut)+np(Hplus)),np(Hplus))) k = 1 do i=1,dmhsteps**ndmh do j=1,ndmh dm(i,j) = km(j) enddo km(k) = km(k)+1 do j=2,ndmh IF (modulo(i,dmhsteps**(j-1)).EQ.0) THEN km(j) = km(j)+1 km(j-1) = -1 ENDIF ENDDO enddo do i=1,dmhsteps**ndmh k=1 do j=1,np(Hneut) IF (dMhneut(j).GT.small_mh) THEN diffMhneut(i,j)=theo(n)%particle(Hneut)%M(j)+dm(i,k)*dMhneut(k)/((dmhsteps-1)/2) k = k +1 ELSE diffMhneut(i,j)=theo(n)%particle(Hneut)%M(j) ENDIF enddo kp = k do j=1,np(Hplus) IF (dMhch(j).GT.small_mh) THEN diffMhch(i,j)=theo(n)%particle(Hplus)%M(j)+dm(i,k)*dMhch(k-(kp-1))/((dmhsteps-1)/2) k = k +1 ELSE diffMhch(i,j)=theo(n)%particle(Hplus)%M(j) ENDIF enddo ! print *, i, (diffMhneut(i,j),j=1,np(Hneut)),(diffMhch(i,j),j=1,np(Hplus)) enddo end subroutine get_mass_variation_param subroutine SUSYBounds_neutralinoonly_input(MN,GammaTotal_N, & & CS_NjNi, & & BR_NjqqNi,BR_NjZNi & & ) ! This subroutine can be called by the user after subroutine initialize_HiggsBounds ! has been called. ! Arguments (input): theoretical predictions (see manual for definitions) !************************************************************ use usefulbits, only : theo,np,Chineut,inputsub,just_after_run #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !----------------------------------------input double precision,intent(in) :: MN( np(Chineut) ),GammaTotal_N( np(Chineut) ) , & & CS_NjNi( np(Chineut),np(Chineut) ), & & BR_NjqqNi( np(Chineut),np(Chineut) ),BR_NjZNi( np(Chineut),np(Chineut) ) !--------------------------------------internal integer :: n integer :: subtype !---------------------------------------------- n=1 subtype=3 inputsub(subtype)%stat=inputsub(subtype)%stat+1 if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' endif if(np(Chineut).eq.0)then write(*,*)'subroutine SUSYBounds_neutralinoonly_input should' write(*,*)'only be called if np(Chineut)>0' stop'error in SUSYBounds_neutralinoonly_input' endif theo(n)%particle(Chineut)%M = MN theo(n)%particle(Chineut)%GammaTot= GammaTotal_N theo(n)%lep%XS_NjNi = CS_NjNi theo(n)%BR_NjqqNi = BR_NjqqNi theo(n)%BR_NjZNi = BR_NjZNi just_after_run=.False. end subroutine SUSYBounds_neutralinoonly_input !************************************************************ subroutine SUSYBounds_neutralinochargino_input(MC,GammaTotal_C, & & CS_CpjCmj, & & BR_CjqqNi, & & BR_CjlnuNi, & & BR_CjWNi & & ) ! This subroutine can be called by the user after subroutine initialize_HiggsBounds ! has been called. ! Arguments (input): theoretical predictions (see manual for definitions) !************************************************************ use usefulbits, only : theo,np,Chineut,Chiplus,inputsub,just_after_run #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !----------------------------------------input double precision,intent(in) :: MC( np(Chiplus) ),GammaTotal_C( np(Chiplus) ), & & CS_CpjCmj( np(Chiplus) ), & & BR_CjqqNi( np(Chiplus),np(Chineut) ), & & BR_CjlnuNi( np(Chiplus),np(Chineut) ), & & BR_CjWNi( np(Chiplus),np(Chineut) ) !--------------------------------------internal integer :: n integer :: subtype !---------------------------------------------- n=1 subtype=4 inputsub(subtype)%stat=inputsub(subtype)%stat+1 if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' endif if((np(Chineut).eq.0).or.(np(Chiplus).eq.0))then write(*,*)'subroutine SUSYBounds_neutralinochargino_input should' write(*,*)'only be called if np(Chineut)>0 and np(Chiplus)>0' stop 'error in subroutine SUSYBounds_neutralinochargino_input' endif theo(n)%particle(Chineut)%M = MC theo(n)%particle(Chineut)%GammaTot= GammaTotal_C theo(n)%lep%XS_CpjCmj = CS_CpjCmj theo(n)%BR_CjqqNi = BR_CjqqNi theo(n)%BR_CjlnuNi = BR_CjlnuNi theo(n)%BR_CjWNi = BR_CjWNi just_after_run=.False. end subroutine SUSYBounds_neutralinochargino_input !************************************************************ subroutine run_HiggsBounds(HBresult, chan, obsratio, ncombined) ! This subroutine can be called by the user after HiggsBounds_initialize has been called. ! The input routines, where required, should be called before calling run_HiggsBounds. ! It takes theoretical predictions for a particular parameter point ! in the model and calls subroutines which compare these predictions ! to the experimental limits ! Arguments (output): ! * HBresult = 1 if point is unexcluded, 0 if excluded, -1 if parameter point is invalid ! * chan = number of channel predicted to have the highest statistical sensitivity, as defined in Key.dat ! * obsratio = ratio of the theoretical rate to the observed limit for this channel ! * ncombined = number of Higgs combined in order to calculate this obsratio ! (see manual for more precise definitions)) ! (TS 30/01/2012): Note, that if many data points are tested at the same time (as for ! inputmethod==datfiles), this subroutine only returns the results of ! the last datapoint. The full results are saved in fullHBres. use usefulbits, only : np, Hneut, Hplus, run_HB_classic implicit none integer HBresult, chan, ncombined double precision obsratio integer hbres(0:np(Hneut)+np(Hplus)), hbchan(0:np(Hneut)+np(Hplus)), hbcomb(0:np(Hneut)+np(Hplus)) double precision hbobs(0:np(Hneut)+np(Hplus)) ! Check if we are using the old 'classic' method if (run_HB_classic.EQV..True.) then call run_HiggsBounds_classic(HBresult,chan,obsratio,ncombined) return endif ! Call the new ('full') method call run_HiggsBounds_full(hbres, hbchan, hbobs, hbcomb) ! Combined results are contained in the zero elements of result arrays HBresult = hbres(0) chan = hbchan(0) obsratio = hbobs(0) ncombined = hbcomb(0) end subroutine run_HiggsBounds !************************************************************ subroutine run_HiggsBounds_single(h, HBresult, chan, obsratio, ncombined) ! This subroutine can be used to get the exclusion results ! for a single Higgs boson (specified by the index h). ! ! To obtain individual results from more than one Higgs boson, it ! is more efficient to use run_HiggsBounds_full rather than this method. use usefulbits, only : np, Hneut, Hplus implicit none integer, intent(in) :: h integer, intent(out) :: HBresult, chan, ncombined double precision, intent(out) :: obsratio integer hbres(0:np(Hneut)+np(Hplus)), hbchan(0:np(Hneut)+np(Hplus)), hbcomb(0:np(Hneut)+np(Hplus)) double precision hbobs(0:np(Hneut)+np(Hplus)) IF (h.LT.0) stop "Illegal number of Higgs boson: h < 0" if (h.GT.np(Hneut)+np(Hplus)) stop "Illegal number of Higgs boson" call run_HiggsBounds_full(hbres, hbchan, hbobs, hbcomb) HBresult = hbres(h) chan = hbchan(h) obsratio = hbobs(h) ncombined = hbcomb(h) end subroutine run_HiggsBounds_single !************************************************************ subroutine run_HiggsBounds_full( HBresult,chan, & & obsratio, ncombined ) ! This subroutine can be called by the user after HiggsBounds_initialize has been called. ! The input routines, where required, should be called before calling run_HiggsBounds. ! It takes theoretical predictions for a particular parameter point ! in the model and calls subroutines which compare these predictions ! to the experimental limits. ! ! The results are given as (n+1)-component arrays (starting from 0), ! where n is the total number of Higgs bosons in the model (neutral+charged). ! The zeroth component gives the combined results (equivalent to run_HiggsBounds). ! ! Arguments (output): ! * HBresult = 1 if point is unexcluded, 0 if excluded, -1 if parameter point is invalid ! * chan = number of channel predicted to have the highest statistical sensitivity, as defined in Key.dat ! * obsratio = ratio of the theoretical rate to the observed limit for this channel ! * ncombined = number of Higgs combined in order to calculate this obsratio ! (see manual for more precise definitions)) use usefulbits, only : theo,res,inputsub,just_after_run,ndmh,debug, & & np,Hneut,Hplus,dmhsteps,ndat,fullHBres,small_mh use channels, only : check_channels !use input, only : test_input use theo_manip, only : complete_theo, recalculate_theo_for_datapoint #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !----------------------------------------output integer,intent(out):: HBresult(0:np(Hneut)+np(Hplus)) integer,intent(out):: chan(0:np(Hneut)+np(Hplus)) integer,intent(out):: ncombined(0:np(Hneut)+np(Hplus)) double precision,intent(out) :: obsratio(0:np(Hneut)+np(Hplus)) double precision :: Mhneut(np(Hneut)) double precision :: Mhch(np(Hplus)) !-------------------------------------internal integer :: n,i,j,ind,part !--------------------------------------------- ! print *, "Running HiggsBounds in Normal Mode (most sensitive limit considered for each Higgs boson)" if (lbound(HBresult,dim=1).NE.0) stop "run_HiggsBounds_full: Array HBresult must begin with element 0" if (ubound(HBresult,dim=1).NE.(np(Hneut)+np(Hplus))) then stop "run_HiggsBounds_full: Upper limit of array HBresult must be equal to number of Higgses" endif if (lbound(chan,dim=1).NE.0) stop "run_HiggsBounds_full: Array chan must begin with element 0" if (ubound(chan,dim=1).NE.(np(Hneut)+np(Hplus))) then stop "run_HiggsBounds_full: Upper limit of array chan must be equal to number of Higgses" endif if (lbound(obsratio,dim=1).NE.0) stop "run_HiggsBounds_full: Array obsratio must begin with element 0" if (ubound(obsratio,dim=1).NE.(np(Hneut)+np(Hplus))) then stop "run_HiggsBounds_full: Upper limit of array obsratio must be equal to number of Higgses" endif if (lbound(ncombined,dim=1).NE.0) stop "run_HiggsBounds_full: Array ncombined must begin with element 0" if (ubound(ncombined,dim=1).NE.(np(Hneut)+np(Hplus))) then stop "run_HiggsBounds_full: Upper limit of array ncombined must be equal to number of Higgses" endif if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' endif do i=1,ubound(inputsub,dim=1) if( inputsub(i)%req .ne. inputsub(i)%stat )then write(*,*)'subroutine '//trim(adjustl(inputsub(i)%desc)) write(*,*)'should be called once and only once before each call to' write(*,*)'subroutine run_HiggsBounds.' stop'error in subroutine run_HiggsBounds' endif inputsub(i)%stat=0!now we have used this input, set back to zero enddo call complete_theo do n=1,ndat ! if(debug) then ! write(*,*) "DEBUG BRs: ", theo(n)%BR_hjWW, theo(n)%BR_hjZZ, theo(n)%BR_hjgaga ! endif theo(n)%particle(Hneut)%Mc = theo(n)%particle(Hneut)%M theo(n)%particle(Hplus)%Mc = theo(n)%particle(Hplus)%M call get_mass_variation_param(n) do i=0,ubound(Hbresult,dim=1) obsratio(i) = -999d0 HBresult(i) = 1 chan(i) = -999 ncombined(i) = -999 enddo ! Do we have mass uncertainties to take care off IF (ndmh.GT.0) THEN ! print *, "Running HiggsBounds with Higgs mass uncertainties" ! write(*,*) theo(n)%particle(Hplus)%dM if(np(Hneut).ne.0) Mhneut = theo(n)%particle(Hneut)%M if(np(Hplus).ne.0) Mhch = theo(n)%particle(Hplus)%M ! Loop over all Higgses do i=1,np(Hneut)+np(Hplus) obsratio(i) = 1.D23 IF (i.LE.np(Hneut)) THEN ind = i part = Hneut ELSE ind = i-np(Hneut) part = Hplus ENDIF ! Check for mass steps for this particular Higgs boson IF(theo(n)%particle(part)%dMh(ind).GT.small_mh) THEN ! theo(n)%particle(part)%M(ind)=theo(n)%particle(part)%M(ind) & ! & -(dmhsteps-1)/2*theo(n)%particle(part)%dMh(ind) theo(n)%particle(part)%M(ind)=theo(n)%particle(part)%M(ind) & & -theo(n)%particle(part)%dMh(ind) do j=1,dmhsteps ! print *, theo(n)%particle(Hneut)%M, theo(n)%particle(Hplus)%M call recalculate_theo_for_datapoint(n) call check_channels(theo(n),res(n),i) IF (res(n)%obsratio(1).LT.obsratio(i)) THEN HBresult(i) = res(n)%allowed95(1) chan(i) = res(n)%chan(1) obsratio(i) = res(n)%obsratio(1) ncombined(i) = res(n)%ncombined(1) ENDIF ! print *, i,theo(n)%particle(part)%M(ind),HBresult(i),chan(i),obsratio(i),ncombined(i) theo(n)%particle(part)%M(ind)= theo(n)%particle(part)%M(ind) & & +theo(n)%particle(part)%dMh(ind)/(dmhsteps-1)*2 enddo else call recalculate_theo_for_datapoint(n) call check_channels(theo(n),res(n),i) HBresult(i) = res(n)%allowed95(1) chan(i) = res(n)%chan(1) obsratio(i) = res(n)%obsratio(1) ncombined(i) = res(n)%ncombined(1) endif ! Logical OR between exclusions (one Higgs excluded = combined exclusion) HBresult(0) = HBresult(0) * HBresult(i) ! Save the data for the Higgs that has the highest ratio of theory/obs IF (obsratio(i).GT.obsratio(0)) THEN chan(0) = chan(i) obsratio(0) = obsratio(i) ncombined(0) = ncombined(i) ENDIF theo(n)%particle(Hneut)%M = Mhneut theo(n)%particle(Hplus)%M = Mhch enddo ! return ELSE ! print *, "Running HiggsBounds without Higgs mass uncertainties" call recalculate_theo_for_datapoint(n) ! write(*,*) "Higgses = " , np(Hneut)+np(Hplus) do i=1,np(Hneut)+np(Hplus) call check_channels(theo(n),res(n),i) HBresult(i) = res(n)%allowed95(1) chan(i) = res(n)%chan(1) obsratio(i) = res(n)%obsratio(1) ncombined(i) = res(n)%ncombined(1) HBresult(0) = HBresult(0) * res(n)%allowed95(1) IF (obsratio(i).GT.obsratio(0)) THEN ! write(*,*) "hello: ", n, i chan(0) = res(n)%chan(1) obsratio(0) = res(n)%obsratio(1) ncombined(0) = res(n)%ncombined(1) ENDIF ! IF (i.LE.np(Hneut)) THEN ! print *, i,theo(n)%particle(Hneut)%M(i),HBresult(i),chan(i),obsratio(i),ncombined(i),HBresult(0), obsratio(0) ! ELSE ! print *, i,theo(n)%particle(Hplus)%M(i-np(Hneut)),HBresult(i),chan(i),obsratio(i),ncombined(i),HBresult(0), obsratio(0) ! endif enddo ENDIF fullHBres(n)%allowed95=HBresult(0) fullHBres(n)%chan=chan(0) fullHBres(n)%obsratio=obsratio(0) fullHBres(n)%ncombined=ncombined(0) enddo just_after_run=.True. ! print *, "HB: run done" end subroutine run_HiggsBounds_full !************************************************************ subroutine run_HiggsBounds_classic( HBresult,chan,obsratio,ncombined) ! This subroutine can be called by the user after HiggsBounds_initialize has been called. ! The input routines, where required, should be called before calling run_HiggsBounds. ! It takes theoretical predictions for a particular parameter point ! in the model and calls subroutines which compare these predictions ! to the experimental limits ! Arguments (output): ! * HBresult = 1 if point is unexcluded, 0 if excluded, -1 if parameter point is invalid ! * chan = number of channel predicted to have the highest statistical sensitivity, as defined in Key.dat ! * obsratio = ratio of the theoretical rate to the observed limit for this channel ! * ncombined = number of Higgs combined in order to calculate this obsratio ! (see manual for more precise definitions)) use usefulbits, only : theo,res,debug,inputsub,just_after_run,ndmh,diffmhneut,diffmhch, & np,Hneut,Hplus,full_dmth_variation,dmhsteps, ndat,fullHBres use channels, only : check_channels !use input, only : test_input use theo_manip, only : complete_theo, recalculate_theo_for_datapoint #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !----------------------------------------output integer,intent(out):: HBresult,chan,ncombined double precision,intent(out) :: obsratio double precision :: Mhneut(np(Hneut)) double precision :: Mhch(np(Hplus)) !-------------------------------------internal integer :: n,i integer :: HBresult_tmp,chan_tmp,ncombined_tmp double precision :: obsratio_tmp !--------------------------------------------- ! n=1 ! print *, "Running HiggsBounds in Classic Mode (globally most sensitive limit only)" if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' endif do i=1,ubound(inputsub,dim=1) if( inputsub(i)%req .ne. inputsub(i)%stat )then write(*,*)'subroutine '//trim(adjustl(inputsub(i)%desc)) write(*,*)'should be called once and only once before each call to' write(*,*)'subroutine run_HiggsBounds.' stop'error in subroutine run_HiggsBounds' endif inputsub(i)%stat=0!now we have used this input, set back to zero enddo call complete_theo do n=1,ndat theo(n)%particle(Hneut)%Mc = theo(n)%particle(Hneut)%M call get_mass_variation_param(n) IF (ndmh.GT.0) THEN if(np(Hneut).ne.0) Mhneut = theo(n)%particle(Hneut)%M if(np(Hplus).ne.0) Mhch = theo(n)%particle(Hplus)%M obsratio_tmp = 10.0E6 ! Set to very large initial value do i=1,dmhsteps**ndmh theo(n)%particle(Hneut)%M = diffMhneut(i,:) theo(n)%particle(Hplus)%M = diffMhch(i,:) if(debug)write(*,*)'manipulating input...' ; call flush(6) call recalculate_theo_for_datapoint(n) if(debug)write(*,*)'compare each data point to the experimental bounds...' ; call flush(6) call check_channels(theo(n),res(n),0) HBresult = res(n)%allowed95(1) chan = res(n)%chan(1) obsratio = res(n)%obsratio(1) ncombined = res(n)%ncombined(1) ! print *, HBresult, chan, obsratio, ncombined IF (.NOT.full_dmth_variation) THEN IF (HBresult.EQ.1) THEN ! theo(n)%particle(Hneut)%M = Mhneut ! theo(n)%particle(Hplus)%M = Mhch just_after_run=.True. exit ENDIF ELSE IF (obsratio.lt.obsratio_tmp) THEN HBresult_tmp = HBresult chan_tmp = chan obsratio_tmp = obsratio ncombined_tmp = ncombined ENDIF ENDIF enddo IF (full_dmth_variation) THEN HBresult = HBresult_tmp chan = chan_tmp obsratio = obsratio_tmp ncombined = ncombined ! theo(n)%particle(Hneut)%M = Mhneut ! theo(n)%particle(Hplus)%M = Mhch just_after_run=.True. ! return ENDIF theo(n)%particle(Hneut)%M = Mhneut theo(n)%particle(Hplus)%M = Mhch call recalculate_theo_for_datapoint(n) call check_channels(theo(n),res(n),0) ELSE if(debug)write(*,*)'manipulating input...' ; call flush(6) call recalculate_theo_for_datapoint(n) if(debug)write(*,*)'compare each data point to the experimental bounds...' ; call flush(6) call check_channels(theo(n),res(n),0) HBresult = res(n)%allowed95(1) chan = res(n)%chan(1) obsratio = res(n)%obsratio(1) ncombined = res(n)%ncombined(1) just_after_run=.True. ENDIF fullHBres(n)%allowed95=HBresult fullHBres(n)%chan=chan fullHBres(n)%obsratio=obsratio fullHBres(n)%ncombined=ncombined enddo just_after_run=.True. end subroutine run_HiggsBounds_classic !************************************************************ -subroutine HiggsBounds_get_chisq(analysisID, Hindex, M_av, nc, cbin, llh, obspred) +subroutine HiggsBounds_get_likelihood(analysisID, Hindex, nc, cbin, M, llh, obspred) !************************************************************ use usefulbits, only : theo,np,Hneut,Hplus use theo_manip, only : complete_theo use likelihoods, only : get_likelihood, calcpredratio_llh implicit none integer, intent(in) :: analysisID integer, intent(out) :: Hindex, nc, cbin - double precision, intent(out) :: llh, M_av + double precision, intent(out) :: llh, M character(LEN=*), intent(in) :: obspred integer :: c,i double precision, allocatable :: expllh(:) ! double precision :: fact double precision, allocatable :: mass(:) ! predratio(:) integer, allocatable :: nclist(:) ! call complete_theo ! allocate(predratio(np(Hneut))) ! predratio = 0.0D0 -! write(*,*) "Calling HiggsBounds_get_chisq..." +! write(*,*) "Calling HiggsBounds_get_likelihood..." allocate(expllh(np(Hneut)),mass(np(Hneut)),nclist(np(Hneut))) expllh = 0.0D0 select case(analysisID) case(3316) c=1 case default - stop 'Unknown analysisID in subroutine HiggsBounds_get_chisq!' + stop 'Unknown analysisID in subroutine HiggsBounds_get_likelihood!' end select ! Determine most sensitive combination do i=1,np(Hneut) call get_likelihood(analysisID, i, theo(1), expllh(i), mass(i), nclist(i), cbin, 'pred') enddo Hindex = maxloc(expllh,dim=1) - call get_likelihood(analysisID, Hindex, theo(1), llh, M_av, nc, cbin, obspred) + call get_likelihood(analysisID, Hindex, theo(1), llh, M, nc, cbin, obspred) deallocate(mass,nclist,expllh) !predratio -end subroutine HiggsBounds_get_chisq +end subroutine HiggsBounds_get_likelihood !************************************************************ -subroutine HiggsBounds_get_combined_chisq(analysisID, llh, obspred) +subroutine HiggsBounds_get_combined_likelihood(analysisID, llh, obspred) !************************************************************ use usefulbits, only : theo,np,Hneut,Hplus, vsmall integer, intent(in) :: analysisID character(LEN=*), intent(in), optional :: obspred double precision, intent(out) :: llh - double precision :: M_av, llh_tmp + double precision :: M, llh_tmp integer :: i, j, nc, cbin, Hindex, cbin_end, cbin_in + write(*,*) 'WARNING: The subroutine HiggsBounds_get_combined_likelihood is NOT ' + write(*,*) ' officially validated and approved. Use it on your own risk!' + cbin_end = 0 do i= 1,np(Hneut) cbin_end = cbin_end + 2**(i-1) enddo llh = -1.0D0 cbin_in = 0 llh_tmp = 0.0D0 do while(cbin_in.lt.cbin_end) if(present(obspred)) then - call HiggsBounds_get_maximal_chisq_for_comb(analysisID, obspred, cbin_in, Hindex, cbin, nc, M_av, llh) + call HiggsBounds_get_likelihood_for_comb(analysisID, cbin_in, Hindex, nc, cbin, M, llh, obspred) else - call HiggsBounds_get_maximal_chisq_for_comb(analysisID, 'obs', cbin_in, Hindex, cbin, nc, M_av, llh) + call HiggsBounds_get_likelihood_for_comb(analysisID, cbin_in, Hindex, nc, cbin, M, llh, 'obs') endif if(llh.ge.0.0D0) then llh_tmp = llh_tmp + llh else exit endif cbin_in = cbin_in + cbin enddo if(llh_tmp.gt.0.0D0) then llh = llh_tmp endif -end subroutine HiggsBounds_get_combined_chisq +end subroutine HiggsBounds_get_combined_likelihood !************************************************************ -subroutine HiggsBounds_get_chisq_for_Higgs(analysisID, cbin_in, Hindex, nc, cbin, M_av, llh) +subroutine HiggsBounds_get_likelihood_for_Higgs(analysisID, cbin_in, Hindex, nc, cbin, M, llh, obspred) !************************************************************ use usefulbits, only : theo,np,Hneut,Hplus use theo_manip, only : complete_theo use likelihoods, only : get_likelihood, calcpredratio_llh implicit none integer, intent(in) :: analysisID,Hindex integer, intent(out) :: nc, cbin - double precision, intent(out) :: llh, M_av - integer, intent(in) :: cbin_in + double precision, intent(out) :: llh, M + integer, intent(in) :: cbin_in + character(LEN=*), intent(in) :: obspred integer :: c,i -! write(*,*) "Calling HiggsBounds_get_chisq_for_Higgs..." select case(analysisID) case(3316) c=1 case default - stop 'Unknown analysisID in subroutine HiggsBounds_get_chisq!' + stop 'Unknown analysisID in subroutine HiggsBounds_get_likelihood_for_Higgs!' end select - call get_likelihood(analysisID, Hindex, theo(1), llh, M_av, nc, cbin,'obs',cbin_in) - -! write(*,*) "h(",Hindex,") llh: ", llh, M_av, nc, cbin + call get_likelihood(analysisID, Hindex, theo(1), llh, M, nc, cbin, obspred, cbin_in) -end subroutine HiggsBounds_get_chisq_for_Higgs -!************************************************************ -subroutine HiggsBounds_get_maximal_chisq(analysisID, Hindex, nc, M_av, llh) -! Wrapper subroutine for HiggsBounds_get_maximal_chisq_for_comb considering -! all neutral Higgs bosons +end subroutine HiggsBounds_get_likelihood_for_Higgs !************************************************************ - - use usefulbits, only : theo,np,Hneut,Hplus - - integer, intent(in) :: analysisID - integer, intent(out) :: Hindex, nc - double precision, intent(out) :: llh, M_av - - integer :: cbin - - call HiggsBounds_get_maximal_chisq_for_comb(analysisID, 'obs', 0, Hindex, cbin, nc, M_av, llh) - -end subroutine HiggsBounds_get_maximal_chisq +!subroutine HiggsBounds_get_maximal_likelihood(analysisID, Hindex, nc, M, llh) +!! Wrapper subroutine for HiggsBounds_get_maximal_likelihood_for_comb considering +!! all neutral Higgs bosons +!!************************************************************ +! +! use usefulbits, only : theo,np,Hneut,Hplus +! +! integer, intent(in) :: analysisID +! integer, intent(out) :: Hindex, nc +! double precision, intent(out) :: llh, M +! +! integer :: cbin +! +! call HiggsBounds_get_maximal_likelihood_for_comb(analysisID, 'obs', 0, Hindex, cbin, nc, M, llh) +! +!end subroutine HiggsBounds_get_maximal_likelihood !************************************************************ -subroutine HiggsBounds_get_maximal_chisq_for_comb(analysisID, obspred, cbin_in, Hindex, cbin, nc, M_av, llh) +subroutine HiggsBounds_get_likelihood_for_comb(analysisID, cbin_in, Hindex, nc, cbin, M, llh, obspred) !************************************************************ use usefulbits, only : theo,np,Hneut,Hplus use theo_manip, only : complete_theo use likelihoods, only : get_likelihood, calcpredratio_llh implicit none integer, intent(in) :: analysisID, cbin_in integer, intent(out) :: Hindex, nc, cbin - double precision, intent(out) :: llh, M_av + double precision, intent(out) :: llh, M character(LEN=*), intent(in) :: obspred integer :: c,i double precision, allocatable :: obsllh(:) - -! double precision :: fact - double precision, allocatable :: mass(:) ! predratio(:) + double precision, allocatable :: mass(:) integer, allocatable :: nclist(:), cbinlist(:) -! call complete_theo -! allocate(predratio(np(Hneut))) -! predratio = 0.0D0 - -! write(*,*) "Calling HiggsBounds_get_maximal_chisq_for_comb with dataset: ", obspred allocate(obsllh(np(Hneut)),mass(np(Hneut)),nclist(np(Hneut)),cbinlist(np(Hneut))) obsllh = 0.0D0 select case(analysisID) case(3316) c=1 case default - stop 'Unknown analysisID in subroutine HiggsBounds_get_maximal_chisq!' + stop 'Unknown analysisID in subroutine HiggsBounds_get_likelihood_for_comb!' end select ! Determine most sensitive combination do i=1,np(Hneut) call get_likelihood(analysisID, i, theo(1), obsllh(i), mass(i), nclist(i),cbinlist(i),obspred, cbin_in) enddo Hindex = maxloc(obsllh,dim=1) llh = obsllh(Hindex) - M_av = mass(Hindex) + M = mass(Hindex) nc = nclist(Hindex) cbin = cbinlist(Hindex) - deallocate(mass,nclist,obsllh,cbinlist) !predratio + deallocate(mass,nclist,obsllh,cbinlist) -end subroutine HiggsBounds_get_maximal_chisq_for_comb +end subroutine HiggsBounds_get_likelihood_for_comb !************************************************************ subroutine HiggsBounds_SLHA_output !**** ******************************************************** use usefulbits, only : whichinput,just_after_run use output, only : do_output if(.not.just_after_run)then stop'subroutine run_HiggsBounds should be called before subroutine HiggsBounds_SLHA_output' endif select case(whichinput) case('SLHA') call do_output case default stop'The subroutine HiggsBounds_SLHA_output should only be used when whichinput=SLHA' end select end subroutine HiggsBounds_SLHA_output #ifdef enableCHISQ !************************************************************ subroutine initialize_HiggsBounds_chisqtables ! use S95tables, only : S95_t2 use S95tables_type3 use usefulbits, only : allocate_if_stats_required,theo implicit none if(allocated(theo))then stop 'subroutine initialize_HiggsBounds_chisqtables should be called before subroutine HiggsBounds_initialize' elseif(allocated(clsb_t3))then stop 'subroutine initialize_HiggsBounds_chisqtables has already been called once' endif allocate(clsb_t3(ntable3)) call initializetables_type3_blank(clsb_t3) call initializetables3(clsb_t3) call readclsbfiles_binary if(allocated(allocate_if_stats_required))then stop'error in subroutine initialize_HiggsBounds_chisqtables' else allocate(allocate_if_stats_required(1)) endif end subroutine initialize_HiggsBounds_chisqtables !************************************************************ subroutine finish_HiggsBounds_chisqtables !************************************************************ use S95tables_type3 use usefulbits, only : allocate_if_stats_required implicit none integer :: x if(.not.allocated(clsb_t3))then stop 'initialize_HiggsBounds_chisqtables should be called first' endif do x=lbound(clsb_t3,dim=1),ubound(clsb_t3,dim=1) deallocate(clsb_t3(x)%dat) enddo deallocate(filename) deallocate(clsb_t3) deallocate(allocate_if_stats_required) end subroutine finish_HiggsBounds_chisqtables !************************************************************ subroutine HB_calc_stats(theory_uncertainty_1s,chisq_withouttheory,chisq_withtheory,chan2) !************************************************************ ! this is in the middle of development! DO NOT USE! use usefulbits, only : res,theo,pr,just_after_run,vsmall use interpolate use S95tables_type1 use S95tables_type3 use S95tables use extra_bits_for_chisquared implicit none integer,intent(out)::chan2 integer :: x,c,z,y integer :: id double precision, intent(in) :: theory_uncertainty_1s double precision :: chisq_withouttheory,chisq_withtheory double precision :: low_chisq,sigma x=1 low_chisq=1.0D-2 if(.not.allocated(theo))then stop 'subroutine HiggsBounds_initialize must be called first' elseif(.not.allocated(clsb_t3))then stop 'subroutine initialize_HiggsBounds_chisqtables must be called first' elseif(.not.just_after_run)then stop 'subroutine run_HiggsBounds must be called first' endif sigma=theory_uncertainty_1s if(sigma.lt.vsmall)then write(*,*)'Warning: will not calculate chi^2 with theory uncertainty' endif chisq_withtheory = -2.0D0 chisq_withouttheory = -2.0D0 z=2; c= res(x)%chan(z) chan2=c if(res(x)%allowed95(z).eq.-1)then! labels an unphysical parameter point chisq_withtheory =-1.0D0 chisq_withouttheory =-1.0D0 elseif( c.gt.0 )then ! labels a physical parameter point and a real channel id=S95_t1_or_S95_t2_idfromelementnumber(pr(c)%ttype,pr(c)%tlist) y=clsb_t3elementnumber_from_S95table(pr(c)%ttype,id) if(y.gt.0)then !------------------------------ call get_chisq(sigma,res(x)%axis_i(z),res(x)%axis_j(z),res(x)%sfactor(z), & & y,chisq_withouttheory,chisq_withtheory) !------------------------------- else write(*,*)'hello y=',y stop'problem here with y' endif else chisq_withtheory =0.0D0 chisq_withouttheory =0.0D0 endif end subroutine HB_calc_stats #endif !************************************************************ subroutine finish_HiggsBounds ! This subroutine needs to be called right at the end, to close files ! and deallocate arrays !************************************************************ use usefulbits, only : deallocate_usefulbits,debug,theo,debug,inputsub, & & file_id_debug1,file_id_debug2 use S95tables, only : deallocate_S95tables use theory_BRfunctions, only : deallocate_BRSM #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif if(debug)then close(file_id_debug2) close(file_id_debug1) endif if(.not.allocated(theo))then stop 'HiggsBounds_initialize should be called first' endif if(debug)write(*,*)'finishing off...' ; call flush(6) call deallocate_BRSM call deallocate_S95tables call deallocate_usefulbits if(debug)write(*,*)'finished' ; call flush(6) if(allocated(inputsub)) deallocate(inputsub) end subroutine finish_HiggsBounds ! !!************************************************************ ! !subroutine run_HiggsBounds_effC(nHdummy,Mh,GammaTotal, & ! & g2hjbb,g2hjtautau,g2hjWW,g2hjZZ, & ! & g2hjgaga,g2hjgg,g2hjhiZ_nHbynH, & ! & BR_hjhihi_nHbynH, & ! & HBresult,chan, & ! & obsratio, ncombined ) !! Obsolete subroutine !!************************************************************ ! ! implicit none ! ! !----------------------------------------input ! integer,intent(in) :: nHdummy ! double precision,intent(in) :: Mh(nHdummy),GammaTotal(nHdummy),& ! & g2hjbb(nHdummy),g2hjtautau(nHdummy), & ! & g2hjWW(nHdummy),g2hjZZ(nHdummy), & ! & g2hjgaga(nHdummy),g2hjgg(nHdummy), & ! & g2hjhiZ_nHbynH(nHdummy,nHdummy), & ! & BR_hjhihi_nHbynH(nHdummy,nHdummy) ! !----------------------------------------output ! integer :: HBresult,chan,ncombined ! double precision :: obsratio ! !---------------------------------------------- ! ! call attempting_to_use_an_old_HB_version('effC') ! !end subroutine run_HiggsBounds_effC !!************************************************************ !subroutine run_HiggsBounds_part(nHdummy,Mh, & ! & CS_lep_hjZ_ratio, & ! & CS_lep_hjhi_ratio_nHbynH, & ! & CS_tev_gg_hj_ratio,CS_tev_bb_hj_ratio, & ! & CS_tev_bg_hjb_ratio, & ! & CS_tev_ud_hjWp_ratio,CS_tev_cs_hjWp_ratio, & ! & CS_tev_ud_hjWm_ratio,CS_tev_cs_hjWm_ratio, & ! & CS_tev_dd_hjZ_ratio,CS_tev_uu_hjZ_ratio, & ! & CS_tev_ss_hjZ_ratio,CS_tev_cc_hjZ_ratio, & ! & CS_tev_bb_hjZ_ratio, & ! & CS_tev_pp_vbf_ratio, & ! & BR_hjbb,BR_hjtautau, & ! & BR_hjWW,BR_hjgaga, & ! & BR_hjhihi_nHbynH, & ! & HBresult,chan, & ! & obsratio, ncombined ) !! Obsolete subroutine !!************************************************************ ! ! implicit none ! ! !----------------------------------------input ! integer , intent(in) :: nHdummy ! double precision,intent(in) ::Mh(nHdummy), & ! & CS_lep_hjZ_ratio(nHdummy), & ! & CS_lep_hjhi_ratio_nHbynH(nHdummy,nHdummy), & ! & CS_tev_gg_hj_ratio(nHdummy),CS_tev_bb_hj_ratio(nHdummy), & ! & CS_tev_bg_hjb_ratio(nHdummy), & ! & CS_tev_ud_hjWp_ratio(nHdummy),CS_tev_cs_hjWp_ratio(nHdummy),& ! & CS_tev_ud_hjWm_ratio(nHdummy),CS_tev_cs_hjWm_ratio(nHdummy),& ! & CS_tev_dd_hjZ_ratio(nHdummy),CS_tev_uu_hjZ_ratio(nHdummy), & ! & CS_tev_ss_hjZ_ratio(nHdummy),CS_tev_cc_hjZ_ratio(nHdummy), & ! & CS_tev_bb_hjZ_ratio(nHdummy), & ! & CS_tev_pp_vbf_ratio(nHdummy), & ! & BR_hjbb(nHdummy),BR_hjtautau(nHdummy), & ! & BR_hjWW(nHdummy),BR_hjgaga(nHdummy), & ! & BR_hjhihi_nHbynH(nHdummy,nHdummy) ! !---------------------------------------output ! integer :: HBresult,chan,ncombined ! double precision :: obsratio ! !----------------------------------------------- ! ! call attempting_to_use_an_old_HB_version('part') ! !end subroutine run_HiggsBounds_part !!************************************************************ !subroutine run_HiggsBounds_hadr(nHdummy,Mh, & ! & CS_lep_hjZ_ratio,CS_lep_hjhi_ratio_nHbynH, & ! & CS_tev_pp_hj_ratio, CS_tev_pp_hjb_ratio, & ! & CS_tev_pp_hjW_ratio,CS_tev_pp_hjZ_ratio, & ! & CS_tev_pp_vbf_ratio, & ! & BR_hjbb,BR_hjtautau, & ! & BR_hjWW,BR_hjgaga, & ! & BR_hjhihi_nHbynH, & ! & HBresult,chan, & ! & obsratio, ncombined ) !! Obsolete subroutine !!************************************************************ ! ! implicit none ! !----------------------------------------input ! integer,intent(in) :: nHdummy ! double precision,intent(in) :: Mh(nHdummy), & ! & CS_lep_hjZ_ratio(nHdummy), & ! & CS_lep_hjhi_ratio_nHbynH(nHdummy,nHdummy),& ! & CS_tev_pp_hj_ratio(nHdummy), & ! & CS_tev_pp_hjb_ratio(nHdummy), & ! & CS_tev_pp_hjW_ratio(nHdummy), & ! & CS_tev_pp_hjZ_ratio(nHdummy), & ! & CS_tev_pp_vbf_ratio(nHdummy), & ! & BR_hjbb(nHdummy),BR_hjtautau(nHdummy), & ! & BR_hjWW(nHdummy),BR_hjgaga(nHdummy), & ! & BR_hjhihi_nHbynH(nHdummy,nHdummy) ! !---------------------------------------output ! integer :: HBresult,chan,ncombined ! double precision :: obsratio ! !--------------------------------------------- ! ! call attempting_to_use_an_old_HB_version('hadr') ! ! !end subroutine run_HiggsBounds_hadr !!************************************************************