Index: trunk/HiggsSignals-2/Expt_tables/LHC13/ATL_H-WW_VBF_13TeV_5.8fb-1_125.0GeV_201611211.txt =================================================================== --- trunk/HiggsSignals-2/Expt_tables/LHC13/ATL_H-WW_VBF_13TeV_5.8fb-1_125.0GeV_201611211.txt (revision 572) +++ trunk/HiggsSignals-2/Expt_tables/LHC13/ATL_H-WW_VBF_13TeV_5.8fb-1_125.0GeV_201611211.txt (revision 573) @@ -1,14 +0,0 @@ -# Data calculated from bottom of p.20 , ATLAS-CONF-2016-112 -# Implemented as pure production mode -201611211 20161121 1 -ATLAS-CONF-2016-112 -LHC, ATL, ATL -(pp)->h->WW (VBF) -13 5.8 0.020 -1 0 -5.0 -125.0 125.0 1.0 -1 -1 -22 - -125.0 0.8 1.7 2.8 Index: trunk/HiggsSignals-2/Expt_tables/LHC13/ATL_H-WW-enumunu_ggH_13TeV_36.1fb-1_125GeV_20180041.stxs =================================================================== --- trunk/HiggsSignals-2/Expt_tables/LHC13/ATL_H-WW-enumunu_ggH_13TeV_36.1fb-1_125GeV_20180041.stxs (revision 0) +++ trunk/HiggsSignals-2/Expt_tables/LHC13/ATL_H-WW-enumunu_ggH_13TeV_36.1fb-1_125GeV_20180041.stxs (revision 573) @@ -0,0 +1,18 @@ +# Stage-0 Simplified Template Cross Section Measurement +# for ggH production. +# Data taken from p9 of ATL-CONF-2018-004 +# Measured XS is given in pb +20180041 +ATL-CONF-2018-004 +LHC, ATL, ATL +(pp)->h->WW-> e nu mu nu (ggH) +13 36.1 0.032 +0 0 + +125.0 +5.0 +1 125.0 +12 +1.0 +10.5 12.6 14.9 +9.8 10.4 11.0 \ No newline at end of file Index: trunk/HiggsSignals-2/Expt_tables/LHC13/ATL_H-WW-enumunu_VBF_13TeV_36.1fb-1_125GeV_20180042.stxs =================================================================== --- trunk/HiggsSignals-2/Expt_tables/LHC13/ATL_H-WW-enumunu_VBF_13TeV_36.1fb-1_125GeV_20180042.stxs (revision 0) +++ trunk/HiggsSignals-2/Expt_tables/LHC13/ATL_H-WW-enumunu_VBF_13TeV_36.1fb-1_125GeV_20180042.stxs (revision 573) @@ -0,0 +1,18 @@ +# Stage-0 Simplified Template Cross Section Measurement +# for VBF production. +# Data taken from p9 of ATL-CONF-2018-004 +# Measured XS is given in pb +20180042 +ATL-CONF-2018-004 +LHC, ATL, ATL +(pp)->h->WW-> e nu mu nu (VBF) +13 36.1 0.032 +0 0 + +125.0 +5.0 +1 125.0 +22 +1.0 +0.21 0.50 0.80 +0.79 0.81 0.83 \ No newline at end of file Index: trunk/HiggsSignals-2/HiggsSignals_subroutines.F90 =================================================================== --- trunk/HiggsSignals-2/HiggsSignals_subroutines.F90 (revision 572) +++ trunk/HiggsSignals-2/HiggsSignals_subroutines.F90 (revision 573) @@ -1,2440 +1,2464 @@ !------------------------------------------------------------ ! This file is part of HiggsSignals (TS 03/03/2013). !------------------------------------------------------------ subroutine initialize_HiggsSignals_latestresults(nHiggsneut,nHiggsplus) !------------------------------------------------------------ ! Wrapper subroutine to intitialize HiggsSignals with the experimental ! dataset "latestresults", avoiding to specify this via a string argument. !------------------------------------------------------------ implicit none !--------------------------------------input integer,intent(in) :: nHiggsneut integer,intent(in) :: nHiggsplus character(LEN=13) :: Expt_string Expt_string = "latestresults" call initialize_HiggsSignals(nHiggsneut,nHiggsplus,Expt_string) end subroutine initialize_HiggsSignals_latestresults !------------------------------------------------------------ subroutine initialize_HiggsSignals_LHC13(nHiggsneut,nHiggsplus) !------------------------------------------------------------ ! Wrapper subroutine to intitialize HiggsSignals with the experimental ! dataset "latestresults", avoiding to specify this via a string argument. !------------------------------------------------------------ implicit none !--------------------------------------input integer,intent(in) :: nHiggsneut integer,intent(in) :: nHiggsplus character(LEN=13) :: Expt_string Expt_string = "LHC13" call initialize_HiggsSignals(nHiggsneut,nHiggsplus,Expt_string) end subroutine initialize_HiggsSignals_LHC13 !------------------------------------------------------------ subroutine initialize_HiggsSignals_empty(nHiggsneut,nHiggsplus) !------------------------------------------------------------ ! Wrapper subroutine to intitialize HiggsSignals without dataset. !------------------------------------------------------------ implicit none !--------------------------------------input integer,intent(in) :: nHiggsneut integer,intent(in) :: nHiggsplus character(LEN=13) :: Expt_string Expt_string = "none" call initialize_HiggsSignals(nHiggsneut,nHiggsplus,Expt_string) end subroutine initialize_HiggsSignals_empty !------------------------------------------------------------ subroutine initialize_HiggsSignals(nHiggsneut,nHiggsplus,Expt_string) !------------------------------------------------------------ ! This the first HiggsSignals subroutine that should be called ! by the user. ! It calls subroutines to read in the tables of Standard Model ! decay and production rates from HiggsBounds, sets up the ! experimental data from Tevatron and LHC, allocate arrays, etc. ! Arguments (input): ! * nHiggs = number of neutral Higgs in the model ! * nHiggsplus = number of singly, positively charged Higgs in the model ! * Expt_string = name of experimental dataset to be used !------------------------------------------------------------ use usefulbits, only : np,Hneut,Hplus,Chineut,Chiplus,debug,inputmethod,& & theo,whichanalyses,just_after_run,& & file_id_debug1,file_id_debug2,allocate_if_stats_required use usefulbits_HS, only : HiggsSignals_info, nanalys, eps, Exptdir, obs use datatables, only: setup_observables, setup_LHC_Run1_combination use STXS, only : load_STXS use input, only : check_number_of_particles,check_whichanalyses use io, only : setup_input_for_hs, setup_output_for_hs use theory_BRfunctions, only : setup_BRSM, BRSM use theory_XS_SM_functions, only : setup_XSSM, XSSM #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none !--------------------------------------input integer,intent(in) :: nHiggsneut integer,intent(in) :: nHiggsplus character(LEN=*), intent(in) :: Expt_string !-----------------------------------internal integer :: i logical :: exptdirpresent = .False. !----------------------------------parameter eps=5.0D0 np(Hneut)=nHiggsneut np(Hplus)=nHiggsplus if(Expt_string.ne.'none') then Exptdir = Expt_string exptdirpresent = .True. endif np(Chineut)=0! not considering bounds on neutralinos here np(Chiplus)=0! not considering bounds on charginos here - debug=.True. + debug=.False. select case(whichanalyses) case('onlyL') whichanalyses='LandH' case('onlyH','onlyP','list ','LandH') case default whichanalyses='onlyH' end select call HiggsSignals_info if(inputmethod=='subrout') then if(allocated(theo))then if(debug) write(*,*) "HiggsBounds/HiggsSignals internal structure already initialized!" else if(debug)write(*,*)'doing other preliminary tasks...' ; call flush(6) call setup_input_for_hs ! allocate(inputsub( 2 )) !(1)np(Hneut)>0 (2)np(Hplus)>0 ! inputsub(1)%desc='HiggsBounds_neutral_input_*' ; inputsub(1)%req=req( 0, 1) ! inputsub(2)%desc='HiggsBounds_charged_input' ; inputsub(2)%req=req( 1, 0) ! ! do i=1,ubound(inputsub,dim=1) ! inputsub(i)%stat=0 ! enddo endif endif if(debug)write(*,*)'reading in Standard Model tables...' ; call flush(6) if(.not.allocated(BRSM)) call setup_BRSM if(.not.allocated(XSSM)) call setup_XSSM call setup_uncertainties if(debug)write(*,*)'reading in experimental data...' ; call flush(6) if(exptdirpresent) call setup_observables if(exptdirpresent) call load_STXS(Expt_string) call setup_LHC_Run1_combination if(debug)write(*,*)'sorting out processes to be checked...'; call flush(6) nanalys = size(obs) if(debug)write(*,*)'preparing output arrays...' ; call flush(6) call setup_output_for_hs if(debug)write(*,*)'HiggsSignals has been initialized...' ; call flush(6) just_after_run=.False. ! contains ! | np ! |Hneu Hcha ! | ==0 ==0 ! function req(Hneu,Hcha) ! integer, intent(in) ::Hneu,Hcha ! integer :: req ! ! req=1 ! if(np(Hneut)==0) req= Hneu * req ! if(np(Hplus)==0) req= Hcha * req ! ! end function req end subroutine initialize_HiggsSignals !------------------------------------------------------------ subroutine HiggsSignals_neutral_input_MassUncertainty(dMh) ! Sets the theoretical mass uncertainty of the Higgs bosons. !------------------------------------------------------------ use usefulbits, only: theo,np,Hneut implicit none double precision,intent(in) :: dMh(np(Hneut)) if(.not.allocated(theo))then stop 'subroutine HiggsSignals_initialize must be called first' endif if(np(Hneut).eq.0)then write(*,*)'subroutine HiggsSignal_neutral_input_MassUncertainty should' write(*,*)'only be called if np(Hneut)>0' stop 'error in subroutine HiggsSignal_neutral_input_MassUncertainty' endif theo(1)%particle(Hneut)%dM = dMh end subroutine HiggsSignals_neutral_input_MassUncertainty !------------------------------------------------------------ subroutine setup_uncertainties !------------------------------------------------------------ use usefulbits, only : file_id_common3 use store_pathname_hs, only : pathname_HS use usefulbits_hs, only : delta_rate use io, only : read_matrix_from_file logical :: BRmodel, BRSM, XSmodel, XSSM call read_matrix_from_file(9,pathname_HS//"BRcov.in",delta_rate%BRcov, BRmodel) call read_matrix_from_file(9,pathname_HS//"BRcovSM.in",delta_rate%BRcovSM, BRSM) call read_matrix_from_file(11,pathname_HS//"XScov.in",delta_rate%CScov, XSmodel) call read_matrix_from_file(11,pathname_HS//"XScovSM.in",delta_rate%CScovSM, XSSM) call read_matrix_from_file(11,pathname_HS//"XScov_13TeV.in",delta_rate%CS13cov, XSmodel) call read_matrix_from_file(11,pathname_HS//"XScovSM_13TeV.in",delta_rate%CS13covSM, XSSM) if(BRmodel.and.BRSM) then delta_rate%BRcov_ok=.True. write(*,*) "Covariance matrix for relative branching ratio uncertainties read in successfully." else write(*,*) "Covariance matrix for relative branching ratio uncertainties not provided. Using default values." endif if(XSmodel.and.XSSM) then delta_rate%CScov_ok=.True. write(*,*) "Covariance matrix for relative cross section uncertainties read in successfully." else write(*,*) "Covariance matrix for relative cross section uncertainties not provided. Using default values." endif end subroutine setup_uncertainties +!------------------------------------------------------------ +subroutine setup_rate_normalization(normalize_to_refmass, normalize_to_refmass_outside_dmtheo) + use usefulbits_hs, only : normalize_rates_to_reference_position,& + & normalize_rates_to_reference_position_outside_dmtheo + implicit none + + logical, intent(in) :: normalize_to_refmass + logical, intent(in) :: normalize_to_refmass_outside_dmtheo + if(normalize_to_refmass) then + write(*,*) "Using SM rate prediction at observed mass for signal strength calculation." + else + write(*,*) "Using SM rate prediction at predicted mass for signal strength calculation." + endif + if(normalize_to_refmass_outside_dmtheo) then + write(*,*) "If predicted mass and observed mass do not agree within theory uncertainty:",& + & " SM rate prediction at observed mass is used for signal strength calculation." + else + write(*,*) "If predicted mass and observed mass do not agree within theory uncertainty:",& + & " SM rate prediction at predicted mass is used for signal strength calculation." + endif + normalize_rates_to_reference_position = normalize_to_refmass + normalize_rates_to_reference_position_outside_dmtheo = normalize_to_refmass_outside_dmtheo + +end subroutine setup_rate_normalization !------------------------------------------------------------ subroutine setup_model_rate_uncertainties(filename_XS, filename_XS13, filename_BR) !------------------------------------------------------------ use usefulbits, only : file_id_common3 use store_pathname_hs, only : pathname_HS use usefulbits_hs, only : delta_rate use io, only : read_matrix_from_file character(LEN=*),intent(in) :: filename_XS, filename_XS13, filename_BR logical :: BRmodel, XSmodel call read_matrix_from_file(9,filename_BR,delta_rate%BRcov, BRmodel) call read_matrix_from_file(11,filename_XS,delta_rate%CScov, XSmodel) call read_matrix_from_file(11,filename_XS13,delta_rate%CS13cov, XSmodel) if(BRmodel.and.XSmodel) then delta_rate%BRcov_ok=.True. delta_rate%CScov_ok=.True. write(*,*) "Covariance matrices for rate uncertainties read in successfully." else write(*,*) "Covariance matrix for rate uncertainties not provided. Using default values." endif end subroutine setup_model_rate_uncertainties !------------------------------------------------------------ subroutine setup_rate_uncertainties( dCS, dBR ) !------------------------------------------------------------ ! Sets (relative) systematic uncertainties of the model for: ! dCS(1) - singleH dBR(1) - gamma gamma ! dCS(2) - VBF dBR(2) - W W ! dCS(3) - HW dBR(3) - Z Z ! dCS(4) - HZ dBR(4) - tau tau ! dCS(5) - ttH dBR(5) - b bbar !------------------------------------------------------------ use usefulbits_hs, only : delta_rate implicit none double precision, intent(in) :: dCS(5) double precision, intent(in) :: dBR(5) integer :: i delta_rate%dCS = dCS do i=lbound(dBR,dim=1),ubound(dBR,dim=1) call setup_dbr(i,dBR(i)) enddo end subroutine setup_rate_uncertainties !------------------------------------------------------------ subroutine setup_dbr(BRid, value) !------------------------------------------------------------ use usefulbits_hs, only : delta_rate integer,intent(in) :: BRid double precision, intent(in) :: value if(BRid.gt.0.and.BRid.lt.10) then delta_rate%dBR(BRid) = value else write(*,*) "Warning in setup_dbr: Unknown decay mode." endif end subroutine setup_dbr !------------------------------------------------------------ subroutine setup_correlations(corr_mu, corr_mh) !------------------------------------------------------------ ! With this subroutine the user may switch off/on correlations ! (default=on) by setting corr = 0/1. !------------------------------------------------------------ use usefulbits_hs, only : correlations_mu, correlations_mh implicit none integer, intent(in) :: corr_mu, corr_mh if(corr_mu.eq.0) then correlations_mu = .False. write(*,*) 'Correlations in signal strength observables are switched off.' elseif(corr_mu.eq.1) then correlations_mu = .True. else stop 'Error: Correlations must be switched on/off by an integer value of 0 or 1.' endif if(corr_mh.eq.0) then correlations_mh = .False. write(*,*) 'Correlations in Higgs mass observables are switched off.' elseif(corr_mh.eq.1) then correlations_mh = .True. else stop 'Error: Correlations must be switched on/off by an integer value of 0 or 1.' endif end subroutine setup_correlations !------------------------------------------------------------ subroutine setup_symmetricerrors(symm) ! Sets the measured rate uncertainties to either a symmetrical average ! of the upper and lower cyan band widths (symm==1) or else uses the ! original (asymmetrical) errors. !------------------------------------------------------------ use usefulbits_hs, only : symmetricerrors implicit none integer, intent(in) :: symm if(symm.eq.1) then write(*,*) "Using averaged (symmetrical) experimental rate uncertainties." symmetricerrors = .True. else write(*,*) "Using original (asymmetrical) experimental rate uncertainties." symmetricerrors = .False. endif end subroutine setup_symmetricerrors !------------------------------------------------------------ subroutine setup_absolute_errors(absol) ! Treats the measured rate uncertainties as either absolute ! uncertainties (1) or relative (0). By default, they are ! treated as relative uncertainties. !------------------------------------------------------------ use usefulbits_hs, only : absolute_errors implicit none integer, intent(in) :: absol if(absol.eq.1) then write(*,*) "Using absolute experimental rate uncertainties." absolute_errors = .True. else write(*,*) "Using relative experimental rate uncertainties." absolute_errors = .False. endif end subroutine setup_absolute_errors !------------------------------------------------------------ subroutine setup_correlated_rate_uncertainties(corr) !------------------------------------------------------------ use usefulbits_hs, only : delta_rate integer, intent(in) :: corr if(corr.eq.0) then delta_rate%usecov = .False. write(*,*) "Deactivated correlated CS and BR uncertainties. Using approximated maximum error." elseif(corr.eq.1) then delta_rate%usecov = .True. write(*,*) "Activated correlated CS and BR uncertainties. Using them if covariance matrices are present." else write(*,*) "Warning in subroutine setup_correlated_rate_uncertainties: Argument ",corr," is not equal to 0 or 1." endif end subroutine setup_correlated_rate_uncertainties !------------------------------------------------------------ subroutine setup_SMweights(useweight) ! If set to 1 (true), HiggsSignals assumes the same signal decomposition ! (weights) as in the SM for the given model. This will enter the determination ! of the theoretical rate uncertainty. !------------------------------------------------------------ use usefulbits_hs, only : useSMweights implicit none integer, intent(in) :: useweight if(useweight.eq.1) then write(*,*) "Using SM weights for theoretical rate uncertainties of the model." useSMweights = .True. else write(*,*) "Using true model weights for theoretical rate uncertainties of the model." useSMweights = .False. endif end subroutine setup_SMweights !------------------------------------------------------------ subroutine setup_anticorrelations_in_mu(acorr) ! Allows for anti-correlations in the signal strength covariance ! matrix if there is a relative sign difference in two mu measurements ! (acorr==1) or else uses only correlations irrespective of the relative ! (acorr==0). !------------------------------------------------------------ use usefulbits_hs, only : anticorrmu implicit none integer, intent(in) :: acorr if(acorr.eq.1) then write(*,*) "Allow anti-correlated signal strength measurements." anticorrmu = .True. else write(*,*) "Prohibit anti-correlated signal strength measurements." anticorrmu = .False. endif end subroutine setup_anticorrelations_in_mu !------------------------------------------------------------ subroutine setup_anticorrelations_in_mh(acorr) ! Allows for anti-correlations in the mass covariance ! matrix if there is a relative sign difference in two mu measurements ! (acorr==1) or else uses only correlations irrespective of the relative ! (acorr==0). !------------------------------------------------------------ use usefulbits_hs, only : anticorrmh implicit none integer, intent(in) :: acorr if(acorr.eq.1) then write(*,*) "Allow anti-correlated mass measurements." anticorrmh = .True. else write(*,*) "Prohibit anti-correlated mass measurements." anticorrmh = .False. endif end subroutine setup_anticorrelations_in_mh !------------------------------------------------------------ subroutine setup_assignmentrange(range) !------------------------------------------------------------ ! This sets up the mass range (in standard deviations) in which ! the Higgs is forced to be assigned to the peak observables. !------------------------------------------------------------ use usefulbits_hs, only : assignmentrange,assignmentrange_massobs, pdf implicit none double precision, intent(in) :: range if(range.le.0.0D0) then write(*,*) "Error: Bad assignment range ",range write(*,*) "Keeping the value ",assignmentrange else assignmentrange = range assignmentrange_massobs = range endif if(assignmentrange.ne.1.0D0.and.pdf.eq.1) then write(*,*) "Note: For a box pdf, only 1s mass range is used to force the Higgs-to-peak assignment." endif end subroutine setup_assignmentrange !------------------------------------------------------------ subroutine setup_assignmentrange_LHCrun1(range) !------------------------------------------------------------ ! This sets up the mass range (in standard deviations) in which ! the Higgs is forced to be assigned to the peak observables. !------------------------------------------------------------ use usefulbits_hs, only : assignmentrange_LHCrun1, pdf implicit none double precision, intent(in) :: range if(range.le.0.0D0) then write(*,*) "Error: Bad assignment range ",range write(*,*) "Keeping the value ",assignmentrange_LHCrun1 else assignmentrange_LHCrun1 = range endif ! if(assignmentrange_LHCrun1.ne.1.0D0.and.pdf.eq.1) then ! write(*,*) "Note: For a box pdf, only 1s mass range is used to force the Higgs-to-peak assignment." ! endif end subroutine setup_assignmentrange_LHCrun1 !------------------------------------------------------------ subroutine setup_assignmentrange_massobservables(range) !------------------------------------------------------------ ! This sets up the mass range (in standard deviations) in which ! the Higgs is forced to be assigned to the peak observables. !------------------------------------------------------------ use usefulbits_hs, only : assignmentrange_massobs, pdf implicit none double precision, intent(in) :: range if(range.le.0.0D0) then write(*,*) "Error: Bad assignment range ",range write(*,*) "Keeping the value ",assignmentrange_massobs else assignmentrange_massobs = range endif if(assignmentrange_massobs.ne.1.0D0.and.pdf.eq.1) then write(*,*) "Note: For a box pdf, only 1s mass range is used to force the Higgs-to-peak assignment." endif end subroutine setup_assignmentrange_massobservables !------------------------------------------------------------ subroutine setup_nparam(Np) !------------------------------------------------------------ use usefulbits_hs, only : Nparam implicit none integer, intent(in) :: Np Nparam = Np end subroutine setup_nparam !------------------------------------------------------------ subroutine setup_Higgs_to_peaks_assignment_iterations(iter) ! Sets the number of iterations for the Higgs-to-peak-assignment. !------------------------------------------------------------ use usefulbits_hs, only : iterations implicit none integer, intent(in) :: iter iterations = iter end subroutine setup_Higgs_to_peaks_assignment_iterations !------------------------------------------------------------ subroutine setup_mcmethod_dm_theory(mode) use mc_chisq, only : mc_mode implicit none integer, intent(in) :: mode character(LEN=14) :: mode_desc(2) = (/'mass variation','convolution '/) if(mode.eq.1.or.mode.eq.2) then mc_mode = mode write(*,'(1X,A,A)') 'The mass-centered chi^2 method will treat the Higgs',& & ' boson mass theory uncertainty by '//trim(mode_desc(mode))//'.' else stop 'Error in subroutine setup_mcmethod_dm_theory: Unknown mode (1 or 2 possible)!' endif end subroutine setup_mcmethod_dm_theory !------------------------------------------------------------ subroutine setup_sm_test(int_SMtest,epsilon) ! With this subroutine the user may switch off the SM likeness test ! (default=on) or change the maximal deviation epsilon (default=5.0D-2) !------------------------------------------------------------ use usefulbits_hs, only : useSMtest, eps implicit none integer, intent(in) :: int_SMtest double precision, intent(in) :: epsilon if(int_SMtest.eq.0) then useSMtest = .False. write(*,*) 'SM likeness test has been switched off.' elseif(int_SMtest.eq.1) then useSMtest = .True. write(*,*) 'SM likeness test has been switched on.' else stop 'Error: SM test must be switched on/off by an integer value of 0 or 1.' endif eps = epsilon end subroutine setup_sm_test !------------------------------------------------------------ subroutine setup_thu_observables(thuobs) use usefulbits_hs, only : THU_included integer, intent(in) :: thuobs if(thuobs.eq.0) then THU_included = .False. write(*,*) 'Observables are assumed to NOT include theory errors.' else THU_included = .True. write(*,*) 'Observables are assumed to include theory errors.' endif end subroutine setup_thu_observables !------------------------------------------------------------ subroutine setup_output_level(level) ! Controls the level of information output: ! 0 : silent mode ! 1 : screen output for each analysis with its peak/mass-centered observables and ! their respective values predicted by the model ! 2 : screen output of detailed information on each analysis with its ! peak/mass-centered observables ! 3 : creates the files peak_information.txt and peak_massesandrates.txt !------------------------------------------------------------ use usefulbits_hs, only : output_level, additional_output implicit none integer, intent(in) :: level if(level.eq.0.or.level.eq.1.or.level.eq.2.or.level.eq.3) then output_level = level else stop 'Error in subroutine setup_output_level: level not equal to 0,1,2 or 3.' endif if(level.eq.3) additional_output = .True. end subroutine setup_output_level !------------------------------------------------------------ subroutine setup_pdf(pdf_in) ! Sets the probability density function for the Higgs mass uncertainty parametrization: ! 1 : box-shaped pdf ! 2 : Gaussian pdf ! 3 : box-shaped theory error + Gaussian experimental pdf !------------------------------------------------------------ use usefulbits_hs, only : pdf, assignmentrange implicit none integer, intent(in) :: pdf_in character(LEN=13) :: pdf_desc(3) = (/'box ','Gaussian ','box+Gaussian'/) pdf=pdf_in if((pdf.eq.1).or.(pdf.eq.2).or.(pdf.eq.3)) then write(*,'(1X,A,A,1I1,A)') 'Use a '//trim(pdf_desc(pdf))//' probability density function ',& & 'for the Higgs mass(es) (pdf=',pdf,')' endif if(assignmentrange.ne.1.0D0.and.pdf.eq.1) then write(*,*) "Note: For a box pdf, only 1s mass range is used to force the Higgs-to-peak assignment." endif end subroutine setup_pdf !------------------------------------------------------------ !subroutine assign_toyvalues_to_observables(ii, peakindex, npeaks, mu_obs, mh_obs) !! Assigns toy values to the peak's mass and mu value for analysis ii. !! ii :: analysis number (entry in mutables) !! peakindex :: index of the peak of analysis ii !! npeaks :: number of peaks found in analysis ii !! mu_obs :: toy value for mu to be given to the peak with peakindex !! mh_obs :: toy value for mh to be given to the peak with peakindex !------------------------------------------------------------ ! use usefulbits_hs, only: obs, usetoys ! ! integer, intent(in) :: ii, peakindex, npeaks ! double precision, intent(in) :: mh_obs, mu_obs ! ! if(peakindex.gt.npeaks) then ! stop 'Error in subroutine assign_toyvalues_to_observables: Observable does not exist!' ! endif ! ! obs(ii)%table%npeaks = npeaks ! if(.not.allocated(obs(ii)%table%Toys_muobs)) allocate(obs(ii)%table%Toys_muobs(npeaks)) ! if(.not.allocated(obs(ii)%table%Toys_mhobs)) allocate(obs(ii)%table%Toys_mhobs(npeaks)) ! ! obs(ii)%table%Toys_muobs(peakindex) = mu_obs ! obs(ii)%table%Toys_mhobs(peakindex) = mh_obs ! ! usetoys = .True. ! !end subroutine assign_toyvalues_to_observables !------------------------------------------------------------ subroutine assign_toyvalues_to_peak(ID, mu_obs, mh_obs) ! Assigns toy values to the peak's mass and mu value to a peak observable. ! ID :: observable ID ! mu_obs :: toy value for mu to be given to the peak ! mh_obs :: toy value for mh to be given to the peak ! ! n.B.: Do we also want to set mu uncertainties here? !------------------------------------------------------------ use usefulbits_hs, only: obs, usetoys implicit none integer, intent(in) :: ID double precision, intent(in) :: mh_obs, mu_obs integer :: pos, ii pos = -1 do ii=lbound(obs,dim=1),ubound(obs,dim=1) if(obs(ii)%id.eq.ID) then pos = ii exit endif enddo if(pos.ne.-1) then obs(pos)%peak%mpeak = mh_obs obs(pos)%peak%mu = mu_obs usetoys = .True. else write(*,*) "WARNING in assign_toyvalues_to_peak: ID unknown." endif end subroutine assign_toyvalues_to_peak !------------------------------------------------------------ subroutine assign_modelefficiencies_to_peak(ID, Nc, eff_ratios) ! Assigns to each channel of the observable the efficiency in the model ! w.r.t the SM efficiency (as a ratio!) ! ! ID :: observable ID ! Nc :: number of channels ! eff_ratios :: array of length (Number of channels) giving the efficiency ratios ! ! Note: You can first employ the subroutine get_peak_channels (io module) to obtain ! the relevant channel information of the observable. !------------------------------------------------------------ use usefulbits_hs, only: obs implicit none integer, intent(in) :: ID, Nc double precision, dimension(Nc), intent(in) :: eff_ratios integer :: pos, ii pos = -1 do ii=lbound(obs,dim=1),ubound(obs,dim=1) if(obs(ii)%id.eq.ID) then pos = ii exit endif enddo if(pos.ne.-1) then if(size(eff_ratios,dim=1).ne.obs(pos)%table%Nc) then write(*,*) "WARNING in assign modelefficiencies_to_peak: Number of channels (",& & size(eff_ratios,dim=1),"!=",obs(pos)%table%Nc,"does not match for observable ID = ",ID else obs(pos)%table%channel_eff_ratios = eff_ratios endif else write(*,*) "WARNING in assign_modelefficiencies_to_peak: ID unknown." endif end subroutine assign_modelefficiencies_to_peak !------------------------------------------------------------ subroutine assign_rate_uncertainty_scalefactor_to_peak(ID, scale_mu) ! Assigns a rate uncertainty scalefactor to the peak specified by ID. ! This scalefactor will only scale the experimental rate uncertainties. ! The theory rate uncertainties must be given manually via setup_rate_uncertainties. ! ! ID :: observable ID of the peak observable ! scale_mu :: scale_mu by which the mu uncertainty is scaled !------------------------------------------------------------ use usefulbits_hs, only: obs, usescalefactor implicit none integer, intent(in) :: ID double precision, intent(in) :: scale_mu integer :: pos, ii pos = -1 do ii=lbound(obs,dim=1),ubound(obs,dim=1) if(obs(ii)%id.eq.ID) then pos = ii exit endif enddo if(pos.ne.-1) then obs(pos)%peak%scale_mu = scale_mu else write(*,*) "WARNING in assign_uncertainty_scalefactors_to_peak: ID unknown." endif usescalefactor = .True. end subroutine assign_rate_uncertainty_scalefactor_to_peak !------------------------------------------------------------ subroutine run_HiggsSignals_LHC_Run1_combination(Chisq_mu, Chisq_mh, Chisq, nobs, Pvalue) use usefulbits, only : theo,just_after_run, ndat use theo_manip, only : HB5_complete_theo use usefulbits_HS, only : HSres, output_level, Nparam implicit none !----------------------------------------output integer,intent(out) :: nobs double precision,intent(out) :: Pvalue, Chisq, Chisq_mu, Chisq_mh !-------------------------------------internal integer :: n,i, nobs_mu, nobs_mh logical :: debug=.False. !--------------------------------------------- if(.not.allocated(theo))then stop 'subroutine HiggsSignals_initialize must be called first' endif call HB5_complete_theo do n=1,ndat call evaluate_LHC_Run1_combination(theo(n),n) Pvalue = HSres(n)%Pvalue_LHCRun1 Chisq = HSres(n)%Chisq_LHCRun1 Chisq_mu = HSres(n)%Chisq_LHCRun1_mu Chisq_mh = HSres(n)%Chisq_LHCRun1_mh nobs_mu = HSres(n)%nobs_LHCRun1_mu nobs_mh = HSres(n)%nobs_LHCRun1_mh nobs = nobs_mu+nobs_mh if(output_level.ne.0) then write(*,*) write(*,*) '#*************************************************************************#' write(*,*) '# HIGGSSIGNALS RESULTS (LHC ATLAS + CMS Run1 combination) #' write(*,*) '#*************************************************************************#' write(*,'(A55,F21.8)') 'chi^2 from signal rate observables = ',Chisq_mu write(*,'(A55,F21.8)') 'chi^2 from Higgs mass observables = ',Chisq_mh write(*,'(A55,F21.8)') 'chi^2 (total) = ',Chisq write(*,'(A55,I21)') 'Number of rate observables = ', nobs_mu write(*,'(A55,I21)') 'Number of mass observables = ', nobs_mh write(*,'(A55,I21)') 'Number of observables (total) = ', nobs write(*,'(A48,I3,A4,F21.8)') 'Probability (ndf =',nobs-Nparam,') = ', Pvalue write(*,*) '#*************************************************************************#' write(*,*) endif enddo just_after_run=.True. end subroutine run_HiggsSignals_LHC_Run1_combination !------------------------------------------------------------ subroutine setup_LHC_combination_run1_SMXS_from_paper(useSMXS_from_paper) !------------------------------------------------------------ use usefulbits_hs, only : LHC_combination_run1_SMXS_from_paper implicit none logical, intent(in) :: useSMXS_from_paper if(useSMXS_from_paper) then write(*,*) "Using SM cross sections from Tab.1 of arXiv:1606.02266 for LHC Run 1 combination chi^2 test." else write(*,*) "Using internal SM cross sections for LHC Run 1 combination chi^2 test." endif LHC_combination_run1_SMXS_from_paper = useSMXS_from_paper end subroutine setup_LHC_combination_run1_SMXS_from_paper !------------------------------------------------------------ subroutine evaluate_LHC_Run1_combination( t , n ) !------------------------------------------------------------ ! !------------------------------------------------------------ use usefulbits, only : np,Hneut,Hplus,dataset,results, vsmall use usefulbits_hs, only : HSresults, output_level, Nparam, & & LHCrun1_rates, LHCrun1_correlationmatrix, useaveragemass, & & assignmentrange_LHCrun1, HSres, normalize_rates_to_reference_position, & & normalize_rates_to_reference_position_outside_dmtheo use pc_chisq, only : csq_mh use numerics, only : invmatrix, matmult, gammp implicit none !--------------------------------------input type(dataset), intent(in) :: t integer, intent(in) :: n !--------------------------------------output ! type(HSresults), intent(inout) :: r !--------------------------------------internal integer :: p, d, id, i, j, k, ncomb double precision, allocatable :: covmat(:,:), invcovmat(:,:) double precision, allocatable :: covmatzero(:,:), invcovmatzero(:,:) double precision, dimension(20) :: v, v2, csq_mu, vzero, vzero2, csq_mu_max double precision, dimension(20,1) :: vmat, vzeromat double precision :: mobs = 125.09D0 double precision :: dmobs = 0.24D0 double precision :: Higgs_signal_k double precision :: num1, num2, dnum1, dnum2, denom1, denom2, mav, dmav allocate(covmat(20,20),invcovmat(20,20)) allocate(covmatzero(20,20),invcovmatzero(20,20)) mav =0.0D0 dmav = 0.0D0 denom1 = 0.0D0 denom2 = 0.0D0 num1 = 0.0D0 num2 = 0.0D0 dnum1 = 0.0D0 dnum2 = 0.0D0 do i=lbound(LHCrun1_rates,dim=1),ubound(LHCrun1_rates,dim=1) id = LHCrun1_rates(i)%channel_id p = int((id-modulo(id,10))/dble(10)) d = modulo(id,10) LHCrun1_rates(i)%r_pred = 0.0D0 ncomb = 0 do k=1,np(Hneut) if(abs(t%particle(Hneut)%M(k)-mobs).le.& & abs(assignmentrange_LHCrun1*dmobs + t%particle(Hneut)%dM(k)) ) then Higgs_signal_k = signalrate(k,p,d,mobs,t%particle(Hneut)%M(k),t%particle(Hneut)%dM(k)) LHCrun1_rates(i)%r_pred = LHCrun1_rates(i)%r_pred + Higgs_signal_k if(id.eq.11) then ! gg -> h_k -> gaga weighted mass average num1 = num1 + Higgs_signal_k * t%particle(Hneut)%M(k) dnum1 = dnum1 + Higgs_signal_k * t%particle(Hneut)%dM(k) else if(id.eq.13) then ! gg -> h_k -> ZZ -> 4l weighted mass average num2 = num2 + Higgs_signal_k * t%particle(Hneut)%M(k) dnum2 = dnum2 + Higgs_signal_k * t%particle(Hneut)%dM(k) endif ncomb = ncomb+1 endif enddo if(id.eq.11) then denom1 = LHCrun1_rates(i)%r_pred else if(id.eq.13) then denom2 = LHCrun1_rates(i)%r_pred endif if(LHCrun1_rates(i)%r_pred.gt.LHCrun1_rates(i)%r) then LHCrun1_rates(i)%dr = LHCrun1_rates(i)%dr_up else LHCrun1_rates(i)%dr = LHCrun1_rates(i)%dr_low endif if(LHCrun1_rates(i)%r.lt.0.0D0) then LHCrun1_rates(i)%dr0 = LHCrun1_rates(i)%dr_up else LHCrun1_rates(i)%dr0 = LHCrun1_rates(i)%dr_low endif v(i) = LHCrun1_rates(i)%r_pred - LHCrun1_rates(i)%r vmat(i,1) = v(i) vzero(i) = LHCrun1_rates(i)%r vzeromat(i,1) = vzero(i) ! write(*,'(2I3,3F10.5)') p, d, LHCrun1_rates(i)%r_pred, LHCrun1_rates(i)%r, LHCrun1_rates(i)%r/LHCrun1_rates(i)%r_pred enddo if(denom1.gt.vsmall.and.denom2.gt.vsmall) then mav = 0.5D0 * (num1/denom1 + num2/denom2) dmav = 0.5D0 * (dnum1/denom1 + dnum2/denom2) ! write(*,*) "Averaged mass is ",mav, " +- ",dmav ! else ! write(*,*) "denom1 and denom2 are ",denom1, denom2 endif do i=lbound(LHCrun1_rates,dim=1),ubound(LHCrun1_rates,dim=1) do j=lbound(LHCrun1_rates,dim=1),ubound(LHCrun1_rates,dim=1) covmat(i,j) = LHCrun1_correlationmatrix(i,j) * & & LHCrun1_rates(i)%dr * LHCrun1_rates(j)%dr covmatzero(i,j) = LHCrun1_correlationmatrix(i,j) * & & LHCrun1_rates(i)%dr0 * LHCrun1_rates(j)%dr0 enddo enddo call invmatrix(covmat, invcovmat) call matmult(invcovmat,vmat,v2,20,1) call invmatrix(covmatzero, invcovmatzero) call matmult(invcovmatzero,vzeromat,vzero2,20,1) do i=1, 20 csq_mu(i) = v(i)*v2(i) enddo do i=1, 20 csq_mu_max(i) = vzero(i)*vzero2(i) enddo if(mav.lt.vsmall) then HSres(n)%Chisq_LHCRun1_mh=0.0D0 else HSres(n)%Chisq_LHCRun1_mh=csq_mh(mav,mobs,dmav,dmobs) endif if((HSres(n)%Chisq_LHCRun1_mh+sum(csq_mu)).gt.sum(csq_mu_max)) then HSres(n)%Chisq_LHCRun1_mu=sum(csq_mu_max) HSres(n)%Chisq_LHCRun1_mh=0.0D0 else HSres(n)%Chisq_LHCRun1_mu=sum(csq_mu) endif HSres(n)%Chisq_LHCRun1= HSres(n)%Chisq_LHCRun1_mu + HSres(n)%Chisq_LHCRun1_mh HSres(n)%nobs_LHCRun1_mu=20 HSres(n)%nobs_LHCRun1_mh=1 if(HSres(n)%Chisq_LHCRun1.gt.vsmall.and.(HSres(n)%nobs_LHCRun1_mu+HSres(n)%nobs_LHCRun1_mh-Nparam).gt.0) then HSres(n)%Pvalue_LHCRun1=1 - gammp(dble(HSres(n)%nobs_LHCRun1_mu + HSres(n)%nobs_LHCRun1_mh-Nparam)/2,HSres(n)%Chisq_LHCRun1/2) endif deallocate(covmat,invcovmat) deallocate(covmatzero,invcovmatzero) contains !------------------------------------------------------------ function signalrate(k,p,d,mobs,m,dmtheo) !------------------------------------------------------------ use usefulbits_hs, only : LHC_combination_run1_SMXS_from_paper !--------------------------------------external functions double precision :: SMCS_lhc8_gg_H,SMCS_lhc8_bb_H,SMCS_lhc8_vbf_H, & & SMCS_lhc8_HW, SMCS_lhc8_HZ, SMCS_lhc8_ttH, SMBR_Hgamgam,SMBR_HWW, & & SMBR_HZZ, SMBR_Htautau, SMBR_Hbb, SMBR_HZgam, SMBR_Hcc, SMBR_Hmumu, & & SMBR_Hgg double precision, intent(in) :: mobs, m, dmtheo integer, intent(in) :: k,p,d double precision :: signalrate, production_rate, decay_rate, mass double precision :: production_rate_scalefactor, decay_rate_scalefactor mass = t%particle(Hneut)%M(k) if(p.eq.1) then if(LHC_combination_run1_SMXS_from_paper) then production_rate= t%lhc8%XS_gg_hj_ratio(k) * 19.2D0 & & + t%lhc8%XS_bb_hj_ratio(k) * 0.203D0 else production_rate= t%lhc8%XS_gg_hj_ratio(k) * SMCS_lhc8_gg_H(mass) & & + t%lhc8%XS_bb_hj_ratio(k) * SMCS_lhc8_bb_H(mass) endif ! NOTE: Here we make a small error in the scalefactor. Correct would be to rescale ! the gg and bb contributions separately. production_rate_scalefactor = (SMCS_lhc8_gg_H(mobs)+SMCS_lhc8_bb_H(mobs))/& & (SMCS_lhc8_gg_H(mass)+SMCS_lhc8_bb_H(mass)) else if(p.eq.2) then if(LHC_combination_run1_SMXS_from_paper) then production_rate= t%lhc8%XS_vbf_ratio(k) * 1.58D0 else production_rate= t%lhc8%XS_vbf_ratio(k) * SMCS_lhc8_vbf_H(mass) endif production_rate_scalefactor = SMCS_lhc8_vbf_H(mobs)/SMCS_lhc8_vbf_H(mass) else if(p.eq.3) then if(LHC_combination_run1_SMXS_from_paper) then production_rate= t%lhc8%XS_hjW_ratio(k) * 0.703D0 else production_rate= t%lhc8%XS_hjW_ratio(k) * SMCS_lhc8_HW(mass) endif production_rate_scalefactor = SMCS_lhc8_HW(mobs)/SMCS_lhc8_HW(mass) else if(p.eq.4) then if(LHC_combination_run1_SMXS_from_paper) then production_rate= t%lhc8%XS_hjZ_ratio(k) * 0.446D0 else production_rate= t%lhc8%XS_hjZ_ratio(k) * SMCS_lhc8_HZ(mass) endif production_rate_scalefactor = SMCS_lhc8_HZ(mobs)/SMCS_lhc8_HZ(mass) else if(p.eq.5) then if(LHC_combination_run1_SMXS_from_paper) then production_rate= t%lhc8%XS_tthj_ratio(k) * 0.129D0 else production_rate= t%lhc8%XS_tthj_ratio(k) * SMCS_lhc8_ttH(mass) endif production_rate_scalefactor = SMCS_lhc8_ttH(mobs)/SMCS_lhc8_ttH(mass) endif if(d.eq.1) then decay_rate = t%BR_hjgaga(k) decay_rate_scalefactor = SMBR_Hgamgam(mobs)/SMBR_Hgamgam(mass) else if(d.eq.2) then decay_rate = t%BR_hjWW(k) decay_rate_scalefactor = SMBR_HWW(mobs)/SMBR_HWW(mass) else if(d.eq.3) then decay_rate = t%BR_hjZZ(k) decay_rate_scalefactor = SMBR_HZZ(mobs)/SMBR_HZZ(mass) else if(d.eq.4) then decay_rate = t%BR_hjtautau(k) decay_rate_scalefactor = SMBR_Htautau(mobs)/SMBR_Htautau(mass) else if(d.eq.5) then decay_rate = t%BR_hjbb(k) decay_rate_scalefactor = SMBR_Hbb(mobs)/SMBR_Hbb(mass) endif if(normalize_rates_to_reference_position) then signalrate = production_rate * decay_rate else signalrate = production_rate * production_rate_scalefactor * & & decay_rate * decay_rate_scalefactor endif if(normalize_rates_to_reference_position_outside_dmtheo) then if(abs(mobs-m).ge.dmtheo) then signalrate = production_rate * decay_rate endif endif end function signalrate !------------------------------------------------------------ end subroutine evaluate_LHC_Run1_combination !------------------------------------------------------------ subroutine run_HiggsSignals_STXS(Chisq_STXS_rates, Chisq_STXS_mh, Chisq_STXS, nobs_STXS, Pvalue_STXS) !------------------------------------------------------------ use STXS, only : evaluate_model_for_STXS, get_chisq_from_STXS, print_STXS, & & get_number_of_STXS_observables, STXSlist, print_STXS_to_file use usefulbits, only : theo,just_after_run, ndat, vsmall use usefulbits_hs, only : HSres, output_level use theo_manip, only : HB5_complete_theo use numerics, only : gammp double precision, intent(out) :: Chisq_STXS_rates, Chisq_STXS_mh, Chisq_STXS, Pvalue_STXS integer, intent(out) :: nobs_STXS double precision :: Pvalue integer :: nobs_STXS_rates, nobs_STXS_mh, i, n call HB5_complete_theo Chisq_STXS_mh = 0.0D0 do n=1, ndat do i=lbound(STXSlist,dim=1), ubound(STXSlist,dim=1) call evaluate_model_for_STXS(STXSlist(i),theo(n)) enddo call get_chisq_from_STXS(Chisq_STXS_rates, Pvalue_STXS) call get_number_of_STXS_observables(nobs_STXS_rates, nobs_STXS_mh) nobs_STXS = nobs_STXS_rates + nobs_STXS_mh ! Add routine for possible mh-observable in STXS here! Chisq_STXS = Chisq_STXS_rates + Chisq_STXS_mh HSres(n)%Chisq_STXS_rates = Chisq_STXS_rates HSres(n)%Chisq_STXS_mh = Chisq_STXS_mh HSres(n)%Chisq_STXS = Chisq_STXS HSres(n)%nobs_STXS_rates = nobs_STXS_rates HSres(n)%nobs_STXS_mh = nobs_STXS_mh HSres(n)%nobs_STXS = nobs_STXS Pvalue = 1.0D0 if(Chisq_STXS.gt.vsmall.and.(nobs_STXS-Nparam).gt.0) then Pvalue = 1 - gammp(dble(nobs_STXS-Nparam)/2,Chisq_STXS/2) endif HSres(n)%Pvalue_STXS = Pvalue enddo if(output_level.eq.1) call print_STXS if(output_level.eq.3) then call print_STXS_to_file endif if(output_level.ne.0) then write(*,*) write(*,*) '#*************************************************************************#' write(*,*) '# HIGGSSIGNALS RESULTS (STXS observables) #' write(*,*) '#*************************************************************************#' write(*,'(A55,F21.8)') 'chi^2 (signal rate) from STXS observables = ',Chisq_STXS_rates write(*,'(A55,F21.8)') 'chi^2 (Higgs mass) from STXS observables = ',Chisq_STXS_mh write(*,'(A55,F21.8)') 'chi^2 (total) = ',Chisq_STXS write(*,'(A55,I21)') 'Number of STXS rate observables = ', nobs_STXS_rates write(*,'(A55,I21)') 'Number of STXS mass observables = ', nobs_STXS_mh write(*,'(A55,I21)') 'Number of STXS observables (total) = ', nobs_STXS write(*,'(A48,I3,A4,F21.8)') 'Probability (ndf =',nobs-Nparam,') = ', Pvalue write(*,*) '#*************************************************************************#' write(*,*) endif end subroutine run_HiggsSignals_STXS !------------------------------------------------------------------------------------ subroutine run_HiggsSignals(mode, Chisq_mu, Chisq_mh, Chisq, nobs, Pvalue) !------------------------------------------------------------ ! This subroutine can be called by the user after HiggsSignals_initialize has been called. ! The input routines, where required, should be called before calling run_HiggsSignals. ! It takes theoretical predictions for a particular parameter point ! in the model and calls subroutines which compare these predictions ! to the experimental results. ! Arguments (output): ! * mode = 1,2 or 3 for peak-centered, mass-centered chi^2 method or both, respectively. ! * Chisq_mu = total chi^2 contribution from signal strength measurements ! * Chisq_mh = total chi^2 contribution from Higgs mass measurements ! * Chisq = total chi^2 value for the combination of the considered Higgs signals ! * nobs = total number of observables ! * Pvalue = total chi^2 probability for the agreement between model and data, ! assuming number of observables == number of degrees of freedom ! (see manual for more precise definitions)) !------------------------------------------------------------ use usefulbits, only : theo,just_after_run, inputmethod, ndat!inputsub, use usefulbits_HS, only : HSres, runmode, output_level, usescalefactor, Nparam,Exptdir use channels, only : check_channels use theo_manip, only : HB5_complete_theo!, HB5_recalculate_theo_for_datapoint #if defined(NAGf90Fortran) use F90_UNIX_IO, only : flush #endif implicit none integer,intent(in) :: mode !----------------------------------------output integer,intent(out) :: nobs double precision,intent(out) :: Pvalue, Chisq, Chisq_mu, Chisq_mh !-------------------------------------internal integer :: n,i - logical :: debug=.True. + logical :: debug=.False. !--------------------------------------------- if(mode.eq.1) then runmode="peak" else if(mode.eq.2) then ! runmode="mass" write(*,*) "Warning: The 'mass' method (runmode = 2) is no longer maintained." write(*,*) " The peak-centered chi^2 method will be used instead." runmode="peak" else if(mode.eq.3) then ! runmode="both" write(*,*) "Warning: The 'both' method (runmode = 3) is no longer maintained." write(*,*) " The peak-centered chi^2 method will be used instead." runmode="peak" else stop'Error in subroutine run_HiggsSignals: mode unknown' endif if(.not.allocated(theo))then stop 'subroutine HiggsSignals_initialize must be called first' endif ! if(inputmethod.eq.'subrout') then ! do i=1,ubound(inputsub,dim=1) ! if( inputsub(i)%req .ne. inputsub(i)%stat )then ! write(*,*) inputsub(i)%req, inputsub(i)%stat ! write(*,*)'subroutine '//trim(adjustl(inputsub(i)%desc)) ! write(*,*)'should be called once and only once before each call to' ! write(*,*)'subroutine run_HiggsSignals.' ! stop'error in subroutine run_HiggsSignals' ! endif ! TS: Have to work on this bit to make it run simultaneously with HiggsBounds. Now, ! commented out the =0 statement. HS thus has to be run before HB. ! inputsub(i)%stat=0!now we have used this input, set back to zero ! enddo ! endif if(debug)write(*,*)'manipulating input...' ; call flush(6) call HB5_complete_theo if(debug)write(*,*)'compare each model to the experimental data...' ; call flush(6) do n=1,ndat ! call recalculate_theo_for_datapoint(n) call evaluate_model(theo(n),n) Pvalue = HSres(n)%Pvalue_peak Chisq = HSres(n)%Chisq_peak Chisq_mu = HSres(n)%Chisq_peak_mu Chisq_mh = HSres(n)%Chisq_peak_mh nobs = HSres(n)%nobs_peak if(output_level.ne.0) then write(*,*) write(*,*) '#*************************************************************************#' write(*,*) '# HIGGSSIGNALS RESULTS (',trim(adjustl(Exptdir)),') -- peak observables #' write(*,*) '#*************************************************************************#' write(*,'(A55,F21.8)') 'chi^2 (signal strength) from peak observables = ',& & HSres(n)%Chisq_peak_mu write(*,'(A55,F21.8)') 'chi^2 (Higgs mass) from peak observables = ',HSres(n)%Chisq_peak_mh ! write(*,'(A55,F21.8)') 'chi^2 from mass-centered observables = ',HSres(n)%Chisq_mpred ! write(*,'(A55,F21.8)') 'chi^2 from signal strength peak observables (total) = ',HSres(n)%Chisq_mu write(*,'(A55,F21.8)') 'chi^2 (total) from peak observables = ',HSres(n)%Chisq write(*,'(A55,I21)') 'Number of signal strength peak observables = ',& & HSres(n)%nobs_peak_mu write(*,'(A55,I21)') 'Number of Higgs mass peak observables = ',HSres(n)%nobs_peak_mh ! write(*,'(A55,I21)') 'Number of mass-centered observables = ',HSres(n)%nobs_mpred write(*,'(A55,I21)') 'Number of peak observables (total) = ',HSres(n)%nobs_peak write(*,'(A48,I3,A4,F21.8)') 'Probability (ndf =',HSres(n)%nobs-Nparam,') using peak observables = ',HSres(n)%Pvalue_peak write(*,*) '#*************************************************************************#' write(*,*) endif enddo just_after_run=.True. usescalefactor=.False. end subroutine run_HiggsSignals !------------------------------------------------------------ subroutine evaluate_model( t , n ) !------------------------------------------------------------ ! This subroutine evaluates the signal strength modifier for every Higgs boson and ! considered analysis. It fills a matrix neutHiggs(:,:) of type neutHiggs with dimensions ! (number(considered analyses),nH). !------------------------------------------------------------ use usefulbits, only : np,Hneut,Hplus,dataset,results, vsmall use usefulbits_hs, only : neutHiggses, nanalys, runmode, HSresults, cov, obs, analyses,& & cov_mhneut, iterations, deallocate_covariance_matrices, & & output_level, Nparam, nanalys use datatables, only : setup_tablelist, check_available_Higgses use pc_chisq use mc_chisq use all_chisq use numerics implicit none !--------------------------------------input type(dataset), intent(in) :: t integer, intent(in) :: n !-------------------------------------output ! type(HSresults), intent(out) :: r integer :: ii, jj, iii, jjj double precision :: totchisq, muchisq, mhchisq, mpchisq, mpredchisq integer :: nobs, Nmu, Nmh, Nmpred character(LEN=100), allocatable :: assignmentgroups(:) integer, allocatable :: assignmentgroups_domH(:) integer, allocatable :: assignmentgroups_Higgs_comb(:,:) allocate(assignmentgroups(nanalys),assignmentgroups_domH(nanalys)) allocate(assignmentgroups_Higgs_comb(nanalys,np(Hneut))) assignmentgroups = '' !---Initialize assignmentgroups arrays with default values do ii=lbound(assignmentgroups_domH,dim=1),ubound(assignmentgroups_domH,dim=1) assignmentgroups_domH(ii) = 0 assignmentgroups_Higgs_comb(ii,:) = 0 enddo !---First, evaluate the model predictions allocate(neutHiggses(nanalys,np(Hneut))) !-Loop over considered analyses do ii=lbound(neutHiggses,dim=1),ubound(neutHiggses,dim=1) !-Loop over the neutral Higgs bosons of the model do jj=lbound(neutHiggses,dim=2),ubound(neutHiggses,dim=2) !! write(*,*) "hello evaluate model:", ii, jj call calc_mupred(jj, t, obs(ii)%table, neutHiggses(ii,jj)) enddo if(.not.allocated(obs(ii)%Higgses)) allocate(obs(ii)%Higgses(np(Hneut))) obs(ii)%Higgses(:) = neutHiggses(ii,:) enddo !-Pass the observables and their predicted Higgs properties (obs%Higgses) !-to the tablelist "analyses" call setup_tablelist ! select case(runmode) ! ! case('peak') !-Peak-centered chisq method jjj=0 do ii=lbound(analyses,dim=1),ubound(analyses,dim=1) call deallocate_covariance_matrices call assign_Higgs_to_peaks(analyses(ii)%table, analyses(ii)%peaks,0) do iii=lbound(analyses(ii)%peaks,dim=1),ubound(analyses(ii)%peaks,dim=1) if(analyses(ii)%table%mhchisq.eq.1.and.& & len(trim(adjustl(analyses(ii)%peaks(iii)%assignmentgroup))).ne.0) then jjj=jjj+1 assignmentgroups(jjj)=analyses(ii)%peaks(iii)%assignmentgroup assignmentgroups_Higgs_comb(jjj,:)=analyses(ii)%peaks(iii)%Higgs_comb assignmentgroups_domH(jjj)=analyses(ii)%peaks(iii)%domH ! write(*,*) "Found leader of group ",assignmentgroups(jjj) ! write(*,*) "ID ",analyses(ii)%peaks(iii)%id ! write(*,*) "with Higgs combination ",assignmentgroups_Higgs_comb(jjj,:) ! write(*,*) "and dominant Higgs boson ",assignmentgroups_domH(jjj) endif enddo enddo do ii=lbound(analyses,dim=1),ubound(analyses,dim=1) do iii=lbound(analyses(ii)%peaks,dim=1),ubound(analyses(ii)%peaks,dim=1) if(analyses(ii)%table%mhchisq.eq.0.and.& & len(trim(adjustl(analyses(ii)%peaks(iii)%assignmentgroup))).ne.0) then !SELECT ASSIGNMENT GROUP FOLLOWERS do jjj=lbound(assignmentgroups,dim=1),ubound(assignmentgroups,dim=1) if(analyses(ii)%peaks(iii)%assignmentgroup.eq.assignmentgroups(jjj)) then !TAKE OVER THE HIGGS ASSIGNMENT OF THE LEADING PEAK analyses(ii)%peaks(iii)%Higgs_comb=assignmentgroups_Higgs_comb(jjj,:) analyses(ii)%peaks(iii)%domH=assignmentgroups_domH(jjj) if(assignmentgroups_domH(jjj).ne.0) then analyses(ii)%peaks(iii)%Higgs_assignment_forced=1 endif call evaluate_peak(analyses(ii)%peaks(iii),analyses(ii)%table) endif enddo endif enddo enddo ! write(*,*) "Starting assignment procedure..." ! Do the iterative Higgs-to-peak-assignment here: call assign_Higgs_to_peaks_with_correlations(iterations) ! write(*,*) "Calculating chi^2..." call calculate_total_pc_chisq(totchisq, muchisq, mhchisq, nobs, Nmu, Nmh) ! write(*,*) "...done." if(output_level.eq.1) call print_peakinformation if(output_level.eq.2) call print_peakinformation_essentials if(output_level.eq.3) then call print_peaks_to_file call print_peaks_signal_rates_to_file endif call add_peaks_to_HSresults(HSres(n)) HSres(n)%Chisq_peak=totchisq HSres(n)%Chisq_peak_mu = muchisq HSres(n)%Chisq_mpred = 0.0D0 HSres(n)%Chisq_peak_mu=muchisq HSres(n)%Chisq_peak_mh=mhchisq HSres(n)%nobs_mpred=0 HSres(n)%nobs_peak_mu=Nmu HSres(n)%nobs_peak_mh=Nmh HSres(n)%nanalysis=size(analyses) HSres(n)%nobs_peak=nobs if(HSres(n)%Chisq.gt.vsmall.and.(HSres(n)%nobs-Nparam).gt.0) then HSres(n)%Pvalue_peak = 1 - gammp(dble(HSres(n)%nobs-Nparam)/2,HSres(n)%Chisq/2) endif ! case('mass') ! do ii=lbound(analyses,dim=1),ubound(analyses,dim=1) ! call fill_mp_obs(ii) ! enddo ! if(mc_mode.eq.1) call mass_variation_by_theory_uncertainty ! call create_covariance_matrix_mp ! call calculate_mpred_chisq(mpchisq, nobs) ! ! if(output_level.eq.1) call print_mc_observables ! if(output_level.eq.2) call print_mc_observables_essentials ! if(output_level.eq.3) then ! call print_mc_tables_to_file ! call print_mc_observables_to_file ! endif ! ! HSres(n)%Chisq=mpchisq ! HSres(n)%Chisq_peak_mu = 0.0D0 ! HSres(n)%Chisq_mpred = mpchisq ! HSres(n)%Chisq_mu=mpchisq ! HSres(n)%Chisq_mh=0.0D0 ! HSres(n)%nobs_mpred=nobs ! HSres(n)%nobs_peak_mu=0 ! HSres(n)%nobs_peak_mh=0 ! HSres(n)%nanalysis=size(analyses) ! HSres(n)%nobs=nobs ! if(HSres(n)%Chisq.gt.vsmall.and.(HSres(n)%nobs-Nparam).gt.0) then ! HSres(n)%Pvalue=1 - gammp(dble(HSres(n)%nobs-Nparam)/2,HSres(n)%Chisq/2) ! endif ! ! case('both') ! jjj=0 ! do ii=lbound(analyses,dim=1),ubound(analyses,dim=1) ! call deallocate_covariance_matrices ! call assign_Higgs_to_peaks(analyses(ii)%table, analyses(ii)%peaks,0) ! do iii=lbound(analyses(ii)%peaks,dim=1),ubound(analyses(ii)%peaks,dim=1) ! if(analyses(ii)%table%mhchisq.eq.1.and.& ! & len(trim(analyses(ii)%peaks(iii)%assignmentgroup)).ne.0) then ! jjj=jjj+1 ! assignmentgroups(jjj)=analyses(ii)%peaks(iii)%assignmentgroup ! assignmentgroups_Higgs_comb(jjj,:)=analyses(ii)%peaks(iii)%Higgs_comb ! assignmentgroups_domH(jjj)=analyses(ii)%peaks(iii)%domH ! endif ! enddo ! enddo ! do ii=lbound(analyses,dim=1),ubound(analyses,dim=1) ! do iii=lbound(analyses(ii)%peaks,dim=1),ubound(analyses(ii)%peaks,dim=1) ! if(analyses(ii)%table%mhchisq.eq.0.and.& ! & len(trim(analyses(ii)%peaks(iii)%assignmentgroup)).ne.0) then ! do jjj=lbound(assignmentgroups,dim=1),ubound(assignmentgroups,dim=1) ! if(analyses(ii)%peaks(iii)%assignmentgroup.eq.assignmentgroups(jjj)) then ! !TAKE OVER THE HIGGS ASSIGNMENT OF THE LEADING PEAK ! analyses(ii)%peaks(iii)%Higgs_comb=assignmentgroups_Higgs_comb(jjj,:) ! analyses(ii)%peaks(iii)%domH=assignmentgroups_domH(jjj) ! if(assignmentgroups_domH(jjj).ne.0) then ! analyses(ii)%peaks(iii)%Higgs_assignment_forced=1 ! endif ! ! TODO: Need to evaluate everything else here! ! call evaluate_peak(analyses(ii)%peaks(iii),analyses(ii)%table) ! endif ! enddo ! endif ! enddo ! enddo ! ! call assign_Higgs_to_peaks_with_correlations(iterations) ! ! do ii=lbound(analyses,dim=1),ubound(analyses,dim=1) ! call check_available_Higgses(ii) ! call fill_mp_obs(ii) ! enddo ! if(mc_mode.eq.1) call mass_variation_by_theory_uncertainty ! ! call calculate_total_chisq(totchisq, muchisq, mhchisq, mpredchisq, nobs, Nmu, Nmh, Nmpred) ! ! !Have to write a new print method ! if(output_level.eq.1) call print_all_observables ! if(output_level.eq.2) call print_peakinformation_essentials ! if(output_level.eq.3) then ! call print_peaks_to_file ! call print_peaks_signal_rates_to_file ! endif ! ! call add_peaks_to_HSresults(r) ! ! HSres(n)%Chisq=totchisq ! HSres(n)%Chisq_peak_mu = muchisq ! HSres(n)%Chisq_mpred = mpredchisq ! HSres(n)%Chisq_mu=muchisq + mpredchisq ! HSres(n)%Chisq_mh=mhchisq ! HSres(n)%nobs_mpred=Nmpred ! HSres(n)%nobs_peak_mu=Nmu ! HSres(n)%nobs_peak_mh=Nmh ! HSres(n)%nanalysis=size(analyses) ! HSres(n)%nobs=nobs ! if(HSres(n)%Chisq.gt.vsmall.and.(HSres(n)%nobs-Nparam).gt.0) then ! HSres(n)%Pvalue=1 - gammp(dble(HSres(n)%nobs-Nparam)/2,HSres(n)%Chisq/2) ! endif ! ! case default ! stop "Error in subroutine evaluate_model: Please specify runmode!" ! ! end select deallocate(neutHiggses) deallocate(assignmentgroups, assignmentgroups_domH, assignmentgroups_Higgs_comb) end subroutine evaluate_model !------------------------------------------------------------ subroutine calc_mupred( j, t, mutab, Higgs ) ! Calculates the model-predicted signal strength modifier !------------------------------------------------------------ use usefulbits, only : dataset, div, vsmall use usefulbits_HS, only : neutHiggs, mutable, useSMtest, eps implicit none integer, intent(in) :: j ! Higgs index type(dataset), intent(in) :: t type(mutable), intent(inout) :: mutab type(neutHiggs), intent(inout) :: Higgs integer :: i double precision :: c, dcbyc integer :: testSMratios logical :: correct_properties Higgs%m = t%particle(mutab%particle_x)%M(j) Higgs%dm = t%particle(mutab%particle_x)%dM(j) Higgs%id = j call get_channelrates( j, t, mutab ) correct_properties=.True. !--Evaluate the predicted signal strength modifier c of the model c=0. do i=1,mutab%Nc !----use a weighted average of the channel rate ratios c=c+mutab%channel_w(i,j)*mutab%channel_mu(i,j) enddo !--Evaluate the deviation of each channel rate ratio to the signal !--strength modifier c and test SM likeness criterium, if this is !--activated. testSMratios= 1 !passes the SM-like ratios test do i=1,mutab%Nc dcbyc=div((mutab%channel_mu(i,j)-c),c,0.0D0,1.0D9) if(dcbyc*mutab%channel_w(i,j).gt.eps.and.useSMtest) then testSMratios= -1 !fails the SM-like ratios test endif enddo if(testSMratios.lt.0) correct_properties=.False. if(correct_properties) then Higgs%mu=c else Higgs%mu=0.0D0 endif end subroutine calc_mupred !------------------------------------------------------------ subroutine get_channelrates( j, t, mutab ) ! This subroutine assignes the rates, weights and systematic rate uncertainty of ! the Higgs boson (j) for the channels considered by the analysis (mutab). ! ! WARNING: if normalize_rates_to_reference_position is true ! The rates are normalized w.r.t. a reference rate at the (peak) mass position. ! This does not work with the mass-centered chi^2 method. ! Also, theoretical mass uncertainties are problematic! !------------------------------------------------------------ use usefulbits, only : dataset, div, small use usefulbits_HS, only : neutHiggs, mutable, delta_rate, normalize_rates_to_reference_position,& & normalize_rates_to_reference_position_outside_dmtheo use theory_XS_SM_functions use theory_BRfunctions integer, intent(in) :: j type(dataset), intent(in) :: t type(mutable), intent(inout) :: mutab integer :: i, p, d ! id integer :: ii, p1, p2, d1, d2 !id1, id2 double precision :: rate, SMrate, modelrate, drsq_SM, drsq, dBR, dBRSM,drcov,drcovSM !!NEW: double precision :: rate_SMref,refmass,BR_SMref!,BR_SMref_mpeak if(size(mutab%mass,dim=1).eq.1) then refmass = mutab%mass(1) else ! write(*,*) "mutab%id", mutab%id, "Mass measurements: ",size(mutab%mass,dim=1) ! write(*,*) "mutab%particle_x = ", mutab%particle_x, " j= ", j refmass = t%particle(mutab%particle_x)%M(j) endif !write(*,*) 'DEBUG HS: id = ', mutab%id !write(*,*) 'DEBUG HS, m = ', t%particle(mutab%particle_x)%M(j) do i=1,mutab%Nc ! id = mutab%channel_id(i) ! p = int((id-modulo(id,10))/dble(10)) ! d = modulo(id,10) p = mutab%channel_p_id(i) d = mutab%channel_d_id(i) !--Do the production rate for the relevant experiment and cms-energy if(mutab%collider.eq.'LHC') then if(abs(mutab%energy-7.0D0).le.small) then if(p.eq.1) then rate=t%lhc7%XS_hj_ratio(j) SMrate=t%lhc7%XS_H_SM(j) rate_SMref=XS_lhc7_gg_H_SM(refmass) mutab%channel_description(i,1)='singleH' else if(p.eq.2) then rate=t%lhc7%XS_vbf_ratio(j) SMrate=t%lhc7%XS_vbf_SM(j) rate_SMref=XS_lhc7_vbf_SM(refmass) mutab%channel_description(i,1)='VBF' else if(p.eq.3) then rate=t%lhc7%XS_hjW_ratio(j) SMrate=t%lhc7%XS_HW_SM(j) rate_SMref=XS_lhc7_HW_SM(refmass) mutab%channel_description(i,1)='HW' else if(p.eq.4) then rate=t%lhc7%XS_hjZ_ratio(j) SMrate=t%lhc7%XS_HZ_SM(j) rate_SMref=XS_lhc7_HZ_SM(refmass) mutab%channel_description(i,1)='HZ' else if(p.eq.5) then rate=t%lhc7%XS_tthj_ratio(j) SMrate=t%lhc7%XS_ttH_SM(j) rate_SMref=XS_lhc7_ttH_SM(refmass) mutab%channel_description(i,1)='ttH' else if(p.eq.6) then rate=t%lhc7%XS_gg_hj_ratio(j) SMrate=t%lhc7%XS_gg_H_SM(j) rate_SMref=XS_lhc7_gg_H_SM(refmass) mutab%channel_description(i,1)='ggH' else if(p.eq.7) then rate=t%lhc7%XS_bb_hj_ratio(j) SMrate=t%lhc7%XS_bb_H_SM(j) rate_SMref=XS_lhc7_bb_H_SM(refmass) mutab%channel_description(i,1)='bbH' else if(p.eq.8) then rate=t%lhc7%XS_thj_tchan_ratio(j) SMrate=t%lhc7%XS_tH_tchan_SM(j) rate_SMref=XS_lhc7_tH_tchan_SM(refmass) mutab%channel_description(i,1)='tH (t-channel)' else if(p.eq.9) then rate=t%lhc7%XS_thj_schan_ratio(j) SMrate=t%lhc7%XS_tH_schan_SM(j) rate_SMref=XS_lhc7_tH_schan_SM(refmass) mutab%channel_description(i,1)='tH (s-channel)' else if(p.eq.10) then rate=t%lhc7%XS_qq_hjZ_ratio(j) SMrate=t%lhc7%XS_qq_HZ_SM(j) rate_SMref=XS_lhc7_HZ_SM(refmass) ! WARNING: This is still the inclusive rate!!! ! rate_SMref=XS_lhc7_qq_HZ_SM(refmass) !Need to create this function yet! mutab%channel_description(i,1)='qq-HZ' else if(p.eq.11) then rate=t%lhc7%XS_gg_hjZ_ratio(j) SMrate=t%lhc7%XS_gg_HZ_SM(j) rate_SMref=XS_lhc7_HZ_SM(refmass) ! WARNING: This is still the inclusive rate!!! ! rate_SMref=XS_lhc7_gg_HZ_SM(refmass) !Need to create this function yet! mutab%channel_description(i,1)='gg-HZ' else if(p.eq.0) then rate=1.0D0 SMrate=1.0D0 rate_SMref=1.0D0 mutab%channel_description(i,1)='none' endif else if(abs(mutab%energy-8.0D0).le.small) then if(p.eq.1) then rate=t%lhc8%XS_hj_ratio(j) SMrate=t%lhc8%XS_H_SM(j) rate_SMref=XS_lhc8_gg_H_SM(refmass) mutab%channel_description(i,1)='singleH' else if(p.eq.2) then rate=t%lhc8%XS_vbf_ratio(j) SMrate=t%lhc8%XS_vbf_SM(j) rate_SMref=XS_lhc8_vbf_SM(refmass) mutab%channel_description(i,1)='VBF' else if(p.eq.3) then rate=t%lhc8%XS_hjW_ratio(j) SMrate=t%lhc8%XS_HW_SM(j) rate_SMref=XS_lhc8_HW_SM(refmass) mutab%channel_description(i,1)='HW' else if(p.eq.4) then rate=t%lhc8%XS_hjZ_ratio(j) SMrate=t%lhc8%XS_HZ_SM(j) rate_SMref=XS_lhc8_HZ_SM(refmass) mutab%channel_description(i,1)='HZ' else if(p.eq.5) then rate=t%lhc8%XS_tthj_ratio(j) SMrate=t%lhc8%XS_ttH_SM(j) rate_SMref=XS_lhc8_ttH_SM(refmass) mutab%channel_description(i,1)='ttH' else if(p.eq.0) then rate=1.0D0 SMrate=1.0D0 rate_SMref=1.0D0 mutab%channel_description(i,1)='none' endif else if(abs(mutab%energy-13.0D0).le.small) then if(p.eq.1) then rate=t%lhc13%XS_hj_ratio(j) SMrate=t%lhc13%XS_H_SM(j) rate_SMref=XS_lhc13_gg_H_SM(refmass) mutab%channel_description(i,1)='singleH' else if(p.eq.2) then rate=t%lhc13%XS_vbf_ratio(j) SMrate=t%lhc13%XS_vbf_SM(j) rate_SMref=XS_lhc13_vbf_SM(refmass) mutab%channel_description(i,1)='VBF' else if(p.eq.3) then rate=t%lhc13%XS_hjW_ratio(j) SMrate=t%lhc13%XS_HW_SM(j) rate_SMref=XS_lhc13_HW_SM(refmass) mutab%channel_description(i,1)='HW' else if(p.eq.4) then rate=t%lhc13%XS_hjZ_ratio(j) SMrate=t%lhc13%XS_HZ_SM(j) rate_SMref=XS_lhc13_HZ_SM(refmass) mutab%channel_description(i,1)='HZ' else if(p.eq.5) then rate=t%lhc13%XS_tthj_ratio(j) SMrate=t%lhc13%XS_ttH_SM(j) rate_SMref=XS_lhc13_ttH_SM(refmass) mutab%channel_description(i,1)='ttH' else if(p.eq.0) then rate=1.0D0 SMrate=1.0D0 rate_SMref=1.0D0 mutab%channel_description(i,1)='none' endif endif else if(mutab%collider.eq.'TEV') then if(p.eq.1) then rate=t%tev%XS_hj_ratio(j) SMrate=t%tev%XS_H_SM(j) rate_SMref=XS_tev_gg_H_SM(refmass) mutab%channel_description(i,1)='singleH' else if(p.eq.2) then rate=t%tev%XS_vbf_ratio(j) SMrate=t%tev%XS_vbf_SM(j) rate_SMref=XS_tev_vbf_SM(refmass) mutab%channel_description(i,1)='VBF' else if(p.eq.3) then rate=t%tev%XS_hjW_ratio(j) SMrate=t%tev%XS_HW_SM(j) rate_SMref=XS_tev_HW_SM(refmass) mutab%channel_description(i,1)='HW' else if(p.eq.4) then rate=t%tev%XS_hjZ_ratio(j) SMrate=t%tev%XS_HZ_SM(j) rate_SMref=XS_tev_HZ_SM(refmass) mutab%channel_description(i,1)='HZ' else if(p.eq.5) then rate=t%tev%XS_tthj_ratio(j) SMrate=t%tev%XS_ttH_SM(j) rate_SMref=XS_tev_ttH_SM(refmass) mutab%channel_description(i,1)='ttH' else if(p.eq.0) then rate=1.0D0 SMrate=1.0D0 rate_SMref=1.0D0 mutab%channel_description(i,1)='none' endif else if(mutab%collider.eq.'ILC') then !--n.B.: As a first attempt, we use the LHC8 normalized cross sections for ZH, VBF, ttH. ! In order to do this properly, a separate input for the ILC cross sections ! has to be provided! It works only for single production mode observables (no ! correct weighting of channels included!)Then, at least in the effective coupling ! approximation, there is no difference to a full implementation. ! The theoretical uncertainty of the ILC production modes will are defined in ! usefulbits_HS.f90. if(p.eq.1.or.p.eq.2) then write(*,*) 'Warning: Unknown ILC production mode (',p,') in table ',mutab%id rate=0.0D0 SMrate=1.0D0 rate_SMref=1.0D0 mutab%channel_description(i,1)='unknown' else if(p.eq.3) then rate=t%lhc8%XS_hjW_ratio(j) SMrate=t%lhc8%XS_HW_SM(j) rate_SMref=XS_lhc8_HW_SM(refmass) mutab%channel_description(i,1)='WBF' else if(p.eq.4) then rate=t%lhc8%XS_hjZ_ratio(j) SMrate=t%lhc8%XS_HZ_SM(j) rate_SMref=XS_lhc8_HZ_SM(refmass) mutab%channel_description(i,1)='HZ' else if(p.eq.5) then rate=t%lhc8%XS_tthj_ratio(j) SMrate=t%lhc8%XS_ttH_SM(j) rate_SMref=XS_lhc8_ttH_SM(refmass) mutab%channel_description(i,1)='ttH' else if(p.eq.0) then rate=1.0D0 SMrate=1.0D0 rate_SMref=1.0D0 mutab%channel_description(i,1)='none' endif endif !--Multiply now by the decay rate if(d.eq.1) then rate=rate*div(t%BR_hjgaga(j),t%BR_Hgaga_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hgaga_SM(j) rate_SMref = rate_SMref*BRSM_Hgaga(refmass) mutab%channel_description(i,2)='gammagamma' else if(d.eq.2) then rate=rate*div(t%BR_hjWW(j),t%BR_HWW_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_HWW_SM(j) rate_SMref = rate_SMref*BRSM_HWW(refmass) mutab%channel_description(i,2)='WW' else if(d.eq.3) then rate=rate*div(t%BR_hjZZ(j),t%BR_HZZ_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_HZZ_SM(j) rate_SMref = rate_SMref*BRSM_HZZ(refmass) mutab%channel_description(i,2)='ZZ' else if(d.eq.4) then rate=rate*div(t%BR_hjtautau(j),t%BR_Htautau_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Htautau_SM(j) rate_SMref = rate_SMref*BRSM_Htautau(refmass) mutab%channel_description(i,2)='tautau' else if(d.eq.5) then rate=rate*div(t%BR_hjbb(j),t%BR_Hbb_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hbb_SM(j) rate_SMref = rate_SMref*BRSM_Hbb(refmass) mutab%channel_description(i,2)='bb' else if(d.eq.6) then rate=rate*div(t%BR_hjZga(j),t%BR_HZga_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_HZga_SM(j) rate_SMref = rate_SMref*BRSM_HZga(refmass) mutab%channel_description(i,2)='Zgamma' else if(d.eq.7) then rate=rate*div(t%BR_hjcc(j),t%BR_Hcc_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hcc_SM(j) rate_SMref = rate_SMref*BRSM_Hcc(refmass) mutab%channel_description(i,2)='cc' else if(d.eq.8) then rate=rate*div(t%BR_hjmumu(j),t%BR_Hmumu_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hmumu_SM(j) rate_SMref = rate_SMref*BRSM_Hmumu(refmass) mutab%channel_description(i,2)='mumu' else if(d.eq.9) then rate=rate*div(t%BR_hjgg(j),t%BR_Hgg_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hgg_SM(j) rate_SMref = rate_SMref*BRSM_Hgg(refmass) mutab%channel_description(i,2)='gg' else if(d.eq.10) then rate=rate*div(t%BR_hjss(j),t%BR_Hss_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Hss_SM(j) rate_SMref = rate_SMref*BRSM_Hss(refmass) mutab%channel_description(i,2)='ss' else if(d.eq.11) then rate=rate*div(t%BR_hjtt(j),t%BR_Htt_SM(j),0.0D0,1.0D0) SMrate=SMrate*t%BR_Htt_SM(j) rate_SMref = rate_SMref*BRSM_Htoptop(refmass) mutab%channel_description(i,2)='tt' else if(d.eq.0) then rate=rate*1.0D0 SMrate=SMrate*1.0D0 rate_SMref = rate_SMref*1.0D0 mutab%channel_description(i,2)='none' endif !------------------------- ! NEW FEATURE (since HB-5.2): Enable to set channelrates directly. if(p.ne.0.and.d.ne.0) then select case(d) case(1) BR_SMref = t%BR_Hgaga_SM(j) ! BR_SMref_mpeak = BRSM_Hgaga(refmass) case(2) BR_SMref = t%BR_HWW_SM(j) ! BR_SMref_mpeak = BRSM_HWW(refmass) case(3) BR_SMref = t%BR_HZZ_SM(j) ! BR_SMref_mpeak = BRSM_HZZ(refmass) case(4) BR_SMref = t%BR_Htautau_SM(j) ! BR_SMref_mpeak = BRSM_Htautau(refmass) case(5) BR_SMref = t%BR_Hbb_SM(j) ! BR_SMref_mpeak = BRSM_Hbb(refmass) case(6) BR_SMref = t%BR_HZga_SM(j) ! BR_SMref_mpeak = BRSM_HZga(refmass) case(7) BR_SMref = t%BR_Hcc_SM(j) ! BR_SMref_mpeak = BRSM_Hcc(refmass) case(8) BR_SMref = t%BR_Hmumu_SM(j) ! BR_SMref_mpeak = BRSM_Hmumu(refmass) case(9) BR_SMref = t%BR_Hgg_SM(j) ! BR_SMref_mpeak = BRSM_Hgg(refmass) case(10) BR_SMref = t%BR_Hss_SM(j) case(11) BR_SMref = t%BR_Htt_SM(j) end select if(mutab%collider.eq.'LHC') then if(abs(mutab%energy-7.0D0).le.small) then if(t%lhc7%channelrates(j,p,d).ge.0.0d0) then rate=div(t%lhc7%channelrates(j,p,d),BR_SMref,0.0D0,1.0D0) endif else if(abs(mutab%energy-8.0D0).le.small) then if(t%lhc8%channelrates(j,p,d).ge.0.0d0) then rate=div(t%lhc8%channelrates(j,p,d),BR_SMref,0.0D0,1.0D0) endif else if(abs(mutab%energy-13.0D0).le.small) then if(t%lhc13%channelrates(j,p,d).ge.0.0d0) then rate=div(t%lhc13%channelrates(j,p,d),BR_SMref,0.0D0,1.0D0) endif endif else if(mutab%collider.eq.'TEV') then if(t%tev%channelrates(j,p,d).ge.0.0d0) then rate=div(t%tev%channelrates(j,p,d),BR_SMref,0.0D0,1.0D0) endif endif endif !------------------------- ! write(*,*) 'DEBUG HS: SM BRs = ', t%BR_HWW_SM(j), t%BR_HZZ_SM(j), t%BR_Hgaga_SM(j) ! write(*,*) 'DEBUG HS: rate, SMrate(i) = ', rate, SMrate ! write(*,*) 'DEBUG HS: eff(i) = ', mutab%channel_eff(i) if(normalize_rates_to_reference_position) then !! THIS IS STILL IN TESTING PHASE !! mutab%channel_mu(i,j)=rate*SMrate/(rate_SMref) else mutab%channel_mu(i,j)=rate !! OLD WAY endif if(normalize_rates_to_reference_position_outside_dmtheo) then if(abs(refmass-t%particle(mutab%particle_x)%M(j)).ge.t%particle(mutab%particle_x)%dM(j)) then mutab%channel_mu(i,j)=rate*SMrate/(rate_SMref) endif endif mutab%channel_w(i,j)=mutab%channel_eff(i)*SMrate ! mutab%channel_w_corrected_eff(i,j)=mutab%channel_eff_ratios(i)*mutab%channel_eff(i)*SMrate enddo ! write(*,*) 'DEBUG HS: BRs = ', t%BR_hjWW, t%BR_hjZZ, t%BR_hjgaga ! write(*,*) 'DEBUG HS: LHC8 = ', t%lhc8%XS_hj_ratio, t%lhc8%XS_vbf_ratio, t%lhc8%XS_hjW_ratio,& ! t%lhc8%XS_hjZ_ratio, t%lhc8%XS_tthj_ratio SMrate=sum(mutab%channel_w(:,j)) ! write(*,*) 'DEBUG HS: SMrate = ', SMrate ! modelrate=sum(mutab%channel_w_corrected_eff(:,j)) do i=1,mutab%Nc mutab%channel_w(i,j)=div(mutab%channel_w(i,j),SMrate,0.0D0,1.0D9) ! mutab%channel_w_corrected_eff(i,j)=div(mutab%channel_w_corrected_eff(i,j),modelrate,0.0D0,1.0D9) enddo ! (TS 30/10/2013): ! write(*,*) "get_channelrates (mu, w, weff):" ! write(*,*) mutab%channel_mu ! write(*,*) mutab%channel_w ! write(*,*) mutab%channel_eff_ratios do i=1,mutab%Nc mutab%channel_w_corrected_eff(i,j)=mutab%channel_eff_ratios(i)*mutab%channel_w(i,j) ! n.b.: model weights are not normalized to 1! enddo ! write(*,*) j,mutab%id, "SM = ", mutab%channel_w(:,j) ! write(*,*) j,mutab%id, "SM effcorr = ",mutab%channel_w_corrected_eff(:,j) do i=1,mutab%Nc drsq_SM = 0.0D0 drsq = 0.0D0 ! id1 = mutab%channel_id(i) ! p1 = int((id1-modulo(id1,10))/dble(10)) ! d1 = modulo(id1,10) p1 = mutab%channel_p_id(i) d1 = mutab%channel_d_id(i) if(mutab%collider.ne.'ILC') then do ii=1,mutab%Nc p2 = mutab%channel_p_id(ii) d2 = mutab%channel_d_id(ii) ! id2 = mutab%channel_id(ii) ! p2 = int((id2-modulo(id2,10))/dble(10)) ! d2 = modulo(id2,10) if(p1.eq.p2.and.p1.ne.0) then if(delta_rate%CScov_ok.and.delta_rate%usecov) then !-- TS 29/03/2017: Add 13 TeV XS covariance matrix here if(abs(mutab%energy-13.0D0).le.small) then drcov=delta_rate%CS13cov(p1,p1) drcovSM=delta_rate%CS13covSM(p1,p1) else drcov=delta_rate%CScov(p1,p1) drcovSM=delta_rate%CScovSM(p1,p1) endif drsq=drsq+drcov*mutab%channel_w_corrected_eff(i,j)*mutab%channel_w_corrected_eff(ii,j) drsq_SM=drsq_SM+drcovSM*mutab%channel_w(i,j)*mutab%channel_w(ii,j) else drsq=drsq+delta_rate%dCS(p1)**2*mutab%channel_w_corrected_eff(i,j)*mutab%channel_w_corrected_eff(ii,j) drsq_SM=drsq_SM+delta_rate%dCS_SM(p1)**2*mutab%channel_w(i,j)*mutab%channel_w(ii,j) endif endif if(d1.eq.d2.and.d1.ne.0) then if(delta_rate%BRcov_ok.and.delta_rate%usecov) then dBRSM = delta_rate%BRcovSM(d1,d1) dBR = delta_rate%BRcov(d1,d1) else dBRSM = delta_rate%dBR_SM(d1)**2 dBR = delta_rate%dBR(d1)**2 endif drsq=drsq+dBR*mutab%channel_w_corrected_eff(i,j)*mutab%channel_w_corrected_eff(ii,j) drsq_SM=drsq_SM+dBRSM*mutab%channel_w(i,j)*mutab%channel_w(ii,j) endif enddo endif mutab%channel_syst(i,j)=sqrt(drsq) mutab%channel_systSM(i,j)=sqrt(drsq_SM) enddo !write(*,*) 'DEBUG HS: mu = ', mutab%channel_mu !write(*,*) 'DEBUG HS: w = ', mutab%channel_w !write(*,*) 'DEBUG HS: eff = ', mutab%channel_eff end subroutine get_channelrates !------------------------------------------------------------ subroutine get_Rvalues(ii,collider,R_H_WW, R_H_ZZ, R_H_gaga, R_H_tautau, R_H_bb, R_VH_bb) ! Returns SM normalized signal rates of some relevant channels (w/o efficiencies) ! for Higgs boson "ii" for a specific collider (see subroutine get_rates). !------------------------------------------------------------ ! use usefulbits, only : theo, np,Hneut ! use usefulbits_HS, only : mutable integer, intent(in) :: ii, collider double precision, intent(out) :: R_H_WW, R_H_ZZ, R_H_gaga, R_H_tautau, R_H_bb, R_VH_bb ! type(mutable) :: dummytable ! integer :: i call get_rates(ii,collider,5,(/ 12, 22, 32, 42, 52 /),R_H_WW) call get_rates(ii,collider,5,(/ 13, 23, 33, 43, 53 /),R_H_ZZ) call get_rates(ii,collider,5,(/ 11, 21, 31, 41, 51 /),R_H_gaga) call get_rates(ii,collider,5,(/ 14, 24, 34, 44, 54 /),R_H_tautau) call get_rates(ii,collider,5,(/ 15, 25, 35, 45, 55 /),R_H_bb) call get_rates(ii,collider,2,(/ 35, 45 /),R_VH_bb) end subroutine get_Rvalues !************************************************************ subroutine get_rates(ii,collider,Nchannels,IDchannels,rate) ! Returns SM normalized signal rates (w/o efficiencies) for Higgs boson "ii" and collider ! experiment "collider"(=1,2,3 for TEV, LHC7, LHC8). "Nchannels" gives the total number ! and IDchannels the two-digit ID of the subchannels, which should be included in the rates. ! IDchannels is an array of size(Nchannels). !------------------------------------------------------------ use usefulbits, only : theo, np,Hneut use usefulbits_HS, only : mutable integer, intent(in) :: ii, collider, Nchannels integer, dimension(Nchannels), intent(in) :: IDchannels double precision, intent(out) :: rate !-Internal type(mutable) :: dummytable integer :: i !-Initialize a dummy mutable in order to run get_channelrates for the channels we want. if(collider.eq.1) then dummytable%collider = 'TEV' else if(collider.eq.2) then dummytable%collider = 'LHC' dummytable%energy = 7.0D0 else if(collider.eq.3) then dummytable%collider = 'LHC' dummytable%energy = 8.0D0 else if(collider.eq.4) then dummytable%collider = 'LHC' dummytable%energy = 13.0D0 else write(*,*) 'WARNING: collider experiment for get_rates unknown.' continue endif dummytable%id = 999999 dummytable%particle_x = 1 dummytable%Nc=Nchannels allocate(dummytable%mass(10)) ! allocate(dummytable%channel_id(Nchannels)) allocate(dummytable%channel_p_id(Nchannels)) allocate(dummytable%channel_d_id(Nchannels)) allocate(dummytable%channel_eff(Nchannels)) allocate(dummytable%channel_eff_ratios(Nchannels)) !-Set all efficiencies equal: dummytable%channel_eff = 1.0D0 dummytable%channel_eff_ratios = 1.0D0 allocate(dummytable%channel_description(Nchannels,2)) allocate(dummytable%channel_w(Nchannels,np(Hneut))) allocate(dummytable%channel_w_corrected_eff(Nchannels,np(Hneut))) allocate(dummytable%channel_systSM(Nchannels,np(Hneut))) allocate(dummytable%channel_syst(Nchannels,np(Hneut))) allocate(dummytable%channel_mu(Nchannels,np(Hneut))) do i=1,Nchannels if(IDchannels(i).le.99) then dummytable%channel_p_id(i) = int((IDchannels(i)-modulo(id,10))/dble(10)) dummytable%channel_d_id(i) = modulo(IDchannels(i),10) else write(*,*) "Error in get_rates: channel-ID not supported. Use get_rates_str instead!" endif enddo call get_channelrates(ii, theo(1), dummytable) rate=0.0D0 do i=lbound(dummytable%channel_mu,dim=1),ubound(dummytable%channel_mu,dim=1) rate = rate + dummytable%channel_mu(i,ii)*dummytable%channel_w(i,ii) enddo deallocate(dummytable%channel_p_id,dummytable%channel_d_id,dummytable%channel_eff,& & dummytable%channel_w,dummytable%channel_systSM,dummytable%channel_syst, & & dummytable%channel_mu,dummytable%channel_eff_ratios,dummytable%channel_description, & & dummytable%channel_w_corrected_eff,dummytable%mass) end subroutine get_rates !************************************************************ subroutine get_rates_str(ii,collider,Nchannels,IDchannels_str,rate) ! Returns SM normalized signal rates (w/o efficiencies) for Higgs boson "ii" and collider ! experiment "collider"(=1,2,3 for TEV, LHC7, LHC8). "Nchannels" gives the total number ! and IDchannels_str the channel ID string of the subchannels, which should be included in the rates. ! IDchannels_str is an array of size(Nchannels). !------------------------------------------------------------ use usefulbits, only : theo, np,Hneut use usefulbits_HS, only : mutable integer, intent(in) :: ii, collider, Nchannels character(LEN=5), dimension(Nchannels), intent(in) :: IDchannels_str double precision, intent(out) :: rate !-Internal type(mutable) :: dummytable integer :: i,id,posperiod !-Initialize a dummy mutable in order to run get_channelrates for the channels we want. if(collider.eq.1) then dummytable%collider = 'TEV' else if(collider.eq.2) then dummytable%collider = 'LHC' dummytable%energy = 7.0D0 else if(collider.eq.3) then dummytable%collider = 'LHC' dummytable%energy = 8.0D0 else if(collider.eq.4) then dummytable%collider = 'LHC' dummytable%energy = 13.0D0 else write(*,*) 'WARNING: collider experiment for get_rates unknown.' continue endif dummytable%id = 999999 dummytable%particle_x = 1 dummytable%Nc=Nchannels allocate(dummytable%mass(10)) ! allocate(dummytable%channel_id(Nchannels)) allocate(dummytable%channel_p_id(Nchannels)) allocate(dummytable%channel_d_id(Nchannels)) allocate(dummytable%channel_eff(Nchannels)) allocate(dummytable%channel_eff_ratios(Nchannels)) !-Set all efficiencies equal: dummytable%channel_eff = 1.0D0 dummytable%channel_eff_ratios = 1.0D0 allocate(dummytable%channel_description(Nchannels,2)) allocate(dummytable%channel_w(Nchannels,np(Hneut))) allocate(dummytable%channel_w_corrected_eff(Nchannels,np(Hneut))) allocate(dummytable%channel_systSM(Nchannels,np(Hneut))) allocate(dummytable%channel_syst(Nchannels,np(Hneut))) allocate(dummytable%channel_mu(Nchannels,np(Hneut))) do i=1,Nchannels posperiod = index(IDchannels_str(i),'.') if(posperiod.eq.0) then if(len(trim(adjustl(IDchannels_str(i)))).eq.2) then read(IDchannels_str(i),*) id dummytable%channel_p_id(i) = int((id-modulo(id,10))/dble(10)) dummytable%channel_d_id(i) = modulo(id,10) else stop " Error in get_rates_str: Cannot handle channel IDs!" endif else read(IDchannels_str(i)(:posperiod-1),*) dummytable%channel_p_id(i) read(IDchannels_str(i)(posperiod+1:),*) dummytable%channel_d_id(i) endif enddo call get_channelrates(ii, theo(1), dummytable) rate=0.0D0 do i=lbound(dummytable%channel_mu,dim=1),ubound(dummytable%channel_mu,dim=1) rate = rate + dummytable%channel_mu(i,ii)*dummytable%channel_w(i,ii) enddo deallocate(dummytable%channel_p_id,dummytable%channel_d_id,dummytable%channel_eff,& & dummytable%channel_w,dummytable%channel_systSM,dummytable%channel_syst, & & dummytable%channel_mu,dummytable%channel_eff_ratios,dummytable%channel_description, & & dummytable%channel_w_corrected_eff,dummytable%mass) end subroutine get_rates_str !------------------------------------------------------------ subroutine get_Pvalue(nparam, Pvalue) ! Calculates the Chi^2 probability for the total Chi^2 value ! and the number of degrees of freedom given by the ! number of observables - nparam !------------------------------------------------------------ use usefulbits, only : vsmall use usefulbits_hs, only: HSres use numerics implicit none integer, intent(in) :: nparam double precision, intent(out) :: Pvalue if(allocated(HSres)) then if(HSres(1)%Chisq.gt.vsmall.and.(HSres(1)%nobs-nparam).gt.0) then HSres(1)%Pvalue = 1 - gammp(dble(HSres(1)%nobs-nparam)/2,HSres(1)%Chisq/2) endif else write(*,*) "Warning: subroutine get_Pvalue should be called after run_HiggsSignals." endif Pvalue = HSres(1)%Pvalue end subroutine get_Pvalue !------------------------------------------------------------ subroutine get_neutral_Higgs_masses(Mh, dMh) ! Sets the theoretical mass uncertainty of the Higgs bosons. !------------------------------------------------------------ use usefulbits, only: theo,np,Hneut implicit none double precision,intent(out) :: Mh(np(Hneut)), dMh(np(Hneut)) if(.not.allocated(theo))then stop 'No model information given!' endif if(np(Hneut).eq.0)then write(*,*)'Cannot access the neutral Higgs boson masses' write(*,*)'because np(Hneut) == 0.' stop 'error in subroutine get_neutral_Higgs_masses' endif Mh = theo(1)%particle(Hneut)%M dMh = theo(1)%particle(Hneut)%dM end subroutine get_neutral_Higgs_masses !------------------------------------------------------------ subroutine complete_HS_results() !------------------------------------------------------------ use usefulbits, only : just_after_run, ndat use usefulbits_HS, only : HSres, Nparam use numerics, only : gammp integer :: n if(just_after_run) then do n=1,ndat HSres(n)%Chisq_mu = HSres(n)%Chisq_peak_mu + & !HSres(n)%Chisq_mpred + & & HSres(n)%Chisq_STXS_rates + HSres(n)%Chisq_LHCRun1_mu HSres(n)%Chisq_mh = HSres(n)%Chisq_peak_mh + HSres(n)%Chisq_LHCRun1_mh + & & HSres(n)%Chisq_STXS_mh HSres(n)%Chisq_STXS = HSres(n)%Chisq_STXS_rates + HSres(n)%Chisq_STXS_mh HSres(n)%Chisq_peak = HSres(n)%Chisq_peak_mu + HSres(n)%Chisq_peak_mh HSres(n)%Chisq_LHCRun1 = HSres(n)%Chisq_LHCRun1_mu + HSres(n)%Chisq_LHCRun1_mh HSres(n)%Chisq = HSres(n)%Chisq_mu + HSres(n)%Chisq_mh HSres(n)%nobs_mu = HSres(n)%nobs_peak_mu + &!HSres(n)%nobs_mpred + & & HSres(n)%nobs_LHCRun1_mu + HSres(n)%nobs_STXS_rates HSres(n)%nobs_mh = HSres(n)%nobs_peak_mh + HSres(n)%nobs_LHCRun1_mh + & & HSres(n)%nobs_STXS_mh HSres(n)%nobs_peak = HSres(n)%nobs_peak_mu + HSres(n)%nobs_peak_mh HSres(n)%nobs_STXS = HSres(n)%nobs_STXS_rates + HSres(n)%nobs_STXS_mh HSres(n)%nobs_LHCRun1 = HSres(n)%nobs_LHCRun1_mu + HSres(n)%nobs_LHCRun1_mh HSres(n)%nobs = HSres(n)%nobs_mu + HSres(n)%nobs_mh if(HSres(n)%Chisq.gt.vsmall.and.(HSres(n)%nobs-Nparam).gt.0) then HSres(n)%Pvalue=1 - gammp(dble(HSres(n)%nobs-Nparam)/2.0D0,HSres(n)%Chisq/2.0D0) endif if(HSres(n)%Chisq_peak.gt.vsmall.and.(HSres(n)%nobs_peak-Nparam).gt.0) then HSres(n)%Pvalue_peak=1 - gammp(dble(HSres(n)%nobs_peak-Nparam)/2.0D0,HSres(n)%Chisq_peak/2.0D0) endif if(HSres(n)%Chisq_LHCRun1.gt.vsmall.and.(HSres(n)%nobs_LHCRun1-Nparam).gt.0) then HSres(n)%Pvalue_LHCRun1=1 - gammp(dble(HSres(n)%nobs_LHCRun1-Nparam)/2.0D0,HSres(n)%Chisq_LHCRun1/2.0D0) endif if(HSres(n)%Chisq_STXS.gt.vsmall.and.(HSres(n)%nobs_STXS-Nparam).gt.0) then HSres(n)%Pvalue_STXS=1 - gammp(dble(HSres(n)%nobs_STXS-Nparam)/2.0D0,HSres(n)%Chisq_STXS/2.0D0) endif enddo else write(*,*) "Warning: complete_HS_results was called but just_after_run is", just_after_run endif !------------------------------------------------------------ end subroutine complete_HS_results !------------------------------------------------------------ subroutine finish_HiggsSignals ! 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_Exptranges use theory_BRfunctions, only : deallocate_BRSM use datatables, only : deallocate_observables use usefulbits_HS, only : deallocate_usefulbits_HS, analyses use mc_chisq, only : deallocate_mc_observables use store_pathname_HS !#if defined(NAGf90Fortran) ! use F90_UNIX_IO, only : flush !#endif if(debug)then close(file_id_debug2) close(file_id_debug1) endif if(debug) write(*,*)'finishing off...' ; call flush(6) if(.not.allocated(theo))then ! stop 'HiggsBounds_initialize should be called first' if(debug) write(*,*) "HiggsBounds/HiggsSignals internal structure already deallocated!" else call deallocate_BRSM call deallocate_Exptranges call deallocate_usefulbits ! if (allocated(inputsub)) deallocate(inputsub) endif ! write(*,*) "before deallocate mc observables." call deallocate_mc_observables ! write(*,*) "after deallocate mc observables." call deallocate_observables if(allocated(analyses)) deallocate(analyses) call deallocate_usefulbits_HS ! call system('rm -f '//trim(adjustl(pathname_HS))//'Expt_tables/analyses.txt') call system('rm -f HS_analyses.txt') if(debug) write(*,*)'finished' ; call flush(6) end subroutine finish_HiggsSignals !------------------------------------------------------------ subroutine finish_HiggsSignals_only !------------------------------------------------------------ use datatables, only : deallocate_observables use usefulbits_HS, only : deallocate_usefulbits_HS, analyses use mc_chisq, only : deallocate_mc_observables use store_pathname_HS call deallocate_mc_observables call deallocate_observables if(allocated(analyses)) deallocate(analyses) call deallocate_usefulbits_HS call system('rm -f HS_analyses.txt') end subroutine finish_HiggsSignals_only !------------------------------------------------------------ ! SOME HANDY WRAPPER SUBROUTINES !------------------------------------------------------------ subroutine initialize_HiggsSignals_for_Fittino(nHiggsneut,nHiggsplus) !------------------------------------------------------------ ! Wrapper subroutine to intitialize HiggsSignals with the experimental ! dataset "latestresults", avoiding to specify this via a string argument. !------------------------------------------------------------ implicit none !--------------------------------------input integer,intent(in) :: nHiggsneut integer,intent(in) :: nHiggsplus ! character(LEN=19) :: Expt_string character(LEN=33) :: Expt_string ! Expt_string = "Moriond2013_Fittino" Expt_string = "latestresults_April2013_inclusive" call initialize_HiggsSignals(nHiggsneut,nHiggsplus,Expt_string) end subroutine initialize_HiggsSignals_for_Fittino !------------------------------------------------------------ subroutine get_number_of_observables_wrapper(ntotal, npeakmu, npeakmh, nmpred, nanalyses) !------------------------------------------------------------ use io, only : get_number_of_observables implicit none integer, intent(out) :: ntotal, npeakmu, npeakmh, nmpred, nanalyses call get_number_of_observables(ntotal, npeakmu, npeakmh, nmpred, nanalyses) end subroutine get_number_of_observables_wrapper !------------------------------------------------------------ subroutine get_ID_of_peakobservable_wrapper(ii, ID) !------------------------------------------------------------ use io, only : get_ID_of_peakobservable implicit none integer, intent(in) :: ii integer, intent(out) :: ID call get_ID_of_peakobservable(ii, ID) end subroutine get_ID_of_peakobservable_wrapper !------------------------------------------------------------ subroutine get_peakinfo_from_HSresults_wrapper(obsID, mupred, domH, nHcomb) !-------------------------------------------------------------------- use io, only : get_peakinfo_from_HSresults implicit none integer, intent(in) :: obsID double precision, intent(out) :: mupred integer, intent(out) :: domH, nHcomb call get_peakinfo_from_HSresults(obsID, mupred, domH, nHcomb) end subroutine get_peakinfo_from_HSresults_wrapper !------------------------------------------------------------ subroutine print_cov_mh_to_file_wrapper(Hindex) !------------------------------------------------------------ use pc_chisq, only : print_cov_mh_to_file implicit none integer, intent(in) :: Hindex call print_cov_mh_to_file(Hindex) end subroutine print_cov_mh_to_file_wrapper !------------------------------------------------------------ subroutine print_cov_mu_to_file_wrapper !------------------------------------------------------------ use pc_chisq, only : print_cov_mu_to_file implicit none call print_cov_mu_to_file end subroutine print_cov_mu_to_file_wrapper !------------------------------------------------------------ subroutine print_corr_mu_to_file_wrapper !------------------------------------------------------------ use pc_chisq, only : print_corr_mu_to_file implicit none call print_corr_mu_to_file end subroutine print_corr_mu_to_file_wrapper !------------------------------------------------------------ Index: trunk/HiggsSignals-2/example_data/SLHA/SLHA_FHexample.fh.1 =================================================================== --- trunk/HiggsSignals-2/example_data/SLHA/SLHA_FHexample.fh.1 (revision 572) +++ trunk/HiggsSignals-2/example_data/SLHA/SLHA_FHexample.fh.1 (revision 573) @@ -1,380 +1,2159 @@ 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 0 # FV BLOCK SMINPUTS 1 1.28936827E+02 # invAlfaMZ 2 1.16639000E-05 # GF 3 1.18000000E-01 # AlfasMZ 4 9.11870000E+01 # MZ 5 4.25000000E+00 # Mb 6 1.75000000E+02 # Mt 7 1.77703000E+00 # Mtau 11 5.10998902E-04 # Me 13 1.05658357E-01 # Mmu 21 6.00000000E-03 # Md 22 3.00000000E-03 # Mu 23 9.50000000E-02 # Ms 24 1.28600000E+00 # Mc BLOCK MINPAR 1 0.00000000E+00 # M0 2 0.00000000E+00 # M12 3 1.00000000E+01 # TB 4 1.00000000E+00 # signMUE 5 -0.00000000E+00 # A BLOCK EXTPAR 0 4.84786694E+02 # Q 1 3.00000000E+02 # M1 2 6.00000000E+02 # M2 3 1.00000000E+03 # M3 11 1.00000000E+03 # At 12 3.00000000E+02 # Ab 13 2.00000000E+02 # Atau 23 1.00000000E+02 # MUE 24 1.40000000E+05 # MA02 25 1.00000000E+01 # TB 26 3.74165739E+02 # MA0 27 3.82704682E+02 # MHp 31 2.06630723E+02 # MSL(1) 32 2.06645846E+02 # MSL(2) 33 1.34514453E+02 # MSL(3) 34 1.43872558E+02 # MSE(1) 35 1.43838140E+02 # MSE(2) 36 2.10401949E+02 # MSE(3) 41 5.64892619E+02 # MSQ(1) 42 5.64902784E+02 # MSQ(2) 43 4.58749215E+02 # MSQ(3) 44 5.47790210E+02 # MSU(1) 45 5.47775859E+02 # MSU(2) 46 5.89079372E+02 # MSU(3) 47 5.47601268E+02 # MSD(1) 48 5.47594947E+02 # MSD(2) 49 5.47471349E+02 # MSD(3) BLOCK MASS 1000012 1.96522387E+02 # MSf(1,1,1) 2000012 1.00000000+123 # MSf(2,1,1) 1000011 1.50049429E+02 # MSf(1,2,1) 2000011 2.12028169E+02 # MSf(2,2,1) 1000002 5.46684341E+02 # MSf(1,3,1) 2000002 5.62350503E+02 # MSf(2,3,1) 1000001 5.48153556E+02 # MSf(1,4,1) 2000001 5.67955726E+02 # MSf(2,4,1) 1000014 1.96538288E+02 # MSf(1,1,2) 2000014 1.00000000+123 # MSf(2,1,2) 1000013 1.50015405E+02 # MSf(1,2,2) 2000013 2.12043684E+02 # MSf(2,2,2) 1000004 5.46585835E+02 # MSf(1,3,2) 2000004 5.62283026E+02 # MSf(2,3,2) 1000003 5.48147074E+02 # MSf(1,4,2) 2000003 5.67966013E+02 # MSf(2,4,2) 1000016 1.18401567E+02 # MSf(1,1,3) 2000016 1.00000000+123 # MSf(2,1,3) 1000015 1.42403224E+02 # MSf(1,2,3) 2000015 2.14862660E+02 # MSf(2,2,3) 1000006 3.29129281E+02 # MSf(1,3,3) 2000006 6.76789745E+02 # MSf(2,3,3) 1000005 4.50942677E+02 # MSf(1,4,3) 2000005 5.51183125E+02 # MSf(2,4,3) 25 1.22651152E+02 # Mh0 35 3.74749649E+02 # MHH 36 3.74165739E+02 # MA0 37 3.82764933E+02 # MHp 1000022 8.77717849E+01 # MNeu(1) 1000023 1.05731705E+02 # MNeu(2) 1000025 3.06628639E+02 # MNeu(3) 1000035 6.11331282E+02 # MNeu(4) 1000024 9.60565070E+01 # MCha(1) 1000037 6.11309165E+02 # MCha(2) 1000021 1.00000000E+03 # MGl BLOCK DMASS 0 1.75000000E+02 # Q 25 9.72174332E-01 # Delta Mh0 35 1.06946442E-02 # Delta MHH 36 0.00000000E+00 # Delta MA0 37 8.06715487E-02 # Delta MHp BLOCK NMIX 1 1 1.47271688E-01 # ZNeu(1,1) 1 2 -1.13979916E-01 # ZNeu(1,2) 1 3 7.30717872E-01 # ZNeu(1,3) 1 4 -6.56788414E-01 # 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 9.86458640E-01 # ZNeu(3,1) 3 2 4.16346543E-02 # ZNeu(3,2) 3 3 -6.05146385E-02 # ZNeu(3,3) 3 4 1.46642030E-01 # ZNeu(3,4) 4 1 -1.92855611E-02 # ZNeu(4,1) 4 2 9.89795429E-01 # ZNeu(4,2) 4 3 3.54417152E-02 # ZNeu(4,3) 4 4 -1.36663681E-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 -6.95590979E-02 # ZNeu(2,1) 2 2 7.47003613E-02 # ZNeu(2,2) 2 3 6.79067931E-01 # ZNeu(2,3) 2 4 7.26944381E-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 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 -4.97233578E-02 # UCha(1,1) 1 2 9.98763029E-01 # UCha(1,2) 2 1 9.98763029E-01 # UCha(2,1) 2 2 4.97233578E-02 # UCha(2,2) BLOCK VMIX 1 1 -1.92962310E-01 # VCha(1,1) 1 2 9.81206170E-01 # VCha(1,2) 2 1 9.81206170E-01 # VCha(2,1) 2 2 1.92962310E-01 # VCha(2,2) BLOCK STAUMIX 1 1 9.98486400E-01 # USf(1,1) 1 2 5.49991646E-02 # USf(1,2) 2 1 -5.49991646E-02 # USf(2,1) 2 2 9.98486400E-01 # USf(2,2) BLOCK STOPMIX 1 1 8.23605275E-01 # USf(1,1) 1 2 -5.67163425E-01 # USf(1,2) 2 1 5.67163425E-01 # USf(2,1) 2 2 8.23605275E-01 # USf(2,2) BLOCK SBOTMIX 1 1 9.99954439E-01 # USf(1,1) 1 2 9.54568581E-03 # USf(1,2) 2 1 -9.54568581E-03 # USf(2,1) 2 2 9.99954439E-01 # USf(2,2) BLOCK ALPHA -1.17451823E-01 # Alpha BLOCK DALPHA 1.46801249E-03 # Delta Alpha BLOCK VCKMIN 1 2.25300000E-01 # lambda 2 8.08000000E-01 # A 3 1.32000000E-01 # rhobar 4 3.41000000E-01 # etabar BLOCK MSL2IN 1 1 4.26962557E+04 # MSL2(1,1) 2 2 4.27025057E+04 # MSL2(2,2) 3 3 1.80941381E+04 # MSL2(3,3) BLOCK MSE2IN 1 1 2.06993129E+04 # MSE2(1,1) 2 2 2.06894105E+04 # MSE2(2,2) 3 3 4.42689801E+04 # MSE2(3,3) BLOCK MSQ2IN 1 1 3.19103671E+05 # MSQ2(1,1) 2 2 3.19115155E+05 # MSQ2(2,2) 3 3 1.99881446E+05 # MSQ2(3,3) BLOCK MSU2IN 1 1 3.00074114E+05 # MSU2(1,1) 2 2 3.00058392E+05 # MSU2(2,2) 3 3 3.16134306E+05 # MSU2(3,3) BLOCK MSD2IN 1 1 2.99867149E+05 # MSD2(1,1) 2 2 2.99860226E+05 # MSD2(2,2) 3 3 3.03181540E+05 # MSD2(3,3) BLOCK TEIN 1 1 5.89936191E-04 # Tf(1,1) 2 2 1.21980083E-01 # Tf(2,2) 3 3 2.05153926E+00 # Tf(3,3) BLOCK TUIN 1 1 1.73171465E-01 # Tf(1,1) 2 2 7.42328349E+01 # Tf(2,2) 3 3 9.53077892E+03 # Tf(3,3) BLOCK TDIN 1 1 1.03902879E-02 # Tf(1,1) 2 2 1.64512892E-01 # Tf(2,2) 3 3 1.56232003E+01 # Tf(3,3) BLOCK CVHMIX 1 1 9.99984377E-01 # UH(1,1) 1 2 5.58985436E-03 # UH(1,2) 1 3 0.00000000E+00 # UH(1,3) 2 1 -5.58985436E-03 # UH(2,1) 2 2 9.99984377E-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 4.58620642E-04 # DeltaRho 2 8.03985711E+01 # MWMSSM 3 8.03727370E+01 # MWSM 4 2.31309273E-01 # SW2effMSSM 5 2.31452470E-01 # SW2effSM 11 1.47612393E-09 # gminus2mu 21 0.00000000E+00 # EDMeTh 22 0.00000000E+00 # EDMn 23 0.00000000E+00 # EDMHg 31 7.83340682E-04 # bsgammaMSSM 32 3.84151628E-04 # bsgammaSM 33 2.29365346E+01 # DeltaMsMSSM 34 2.19915791E+01 # DeltaMsSM DECAY 25 4.66729789E-03 # Gamma(h0) 1.67729727E-03 2 22 22 # BR(h0 -> photon photon) 1.72630719E-02 2 23 23 # BR(h0 -> Z Z) 1.49508769E-01 2 -24 24 # BR(h0 -> W W) 4.98888879E-02 2 21 21 # BR(h0 -> gluon gluon) 5.91016012E-09 2 -11 11 # BR(h0 -> Electron electron) 2.62892978E-04 2 -13 13 # BR(h0 -> Muon muon) 7.57524936E-02 2 -15 15 # BR(h0 -> Tau tau) 1.71225452E-07 2 -2 2 # BR(h0 -> Up up) 2.39510771E-02 2 -4 4 # BR(h0 -> Charm charm) 9.86900853E-07 2 -1 1 # BR(h0 -> Down down) 2.47844298E-04 2 -3 3 # BR(h0 -> Strange strange) 6.81446502E-01 2 -5 5 # BR(h0 -> Bottom bottom) DECAY 35 7.83706554E-01 # Gamma(HH) 3.06707834E-06 2 22 22 # BR(HH -> photon photon) 1.74379832E-03 2 23 23 # BR(HH -> Z Z) 3.80819738E-03 2 -24 24 # BR(HH -> W W) 6.56064077E-04 2 21 21 # BR(HH -> gluon gluon) 7.54257349E-09 2 -11 11 # BR(HH -> Electron electron) 3.35617824E-04 2 -13 13 # BR(HH -> Muon muon) 9.73136619E-02 2 -15 15 # BR(HH -> Tau tau) 3.26751691E-11 2 -2 2 # BR(HH -> Up up) 4.57357974E-06 2 -4 4 # BR(HH -> Charm charm) 2.51100369E-02 2 -6 6 # BR(HH -> Top top) 1.00572923E-06 2 -1 1 # BR(HH -> Down down) 2.52571792E-04 2 -3 3 # BR(HH -> Strange strange) 6.71514561E-01 2 -5 5 # BR(HH -> Bottom bottom) 8.67236607E-02 2 -1000024 1000024 # BR(HH -> Chargino1 chargino1) 4.30707320E-02 2 1000022 1000022 # BR(HH -> neutralino1 neutralino1) 9.07746163E-03 2 1000022 1000023 # BR(HH -> neutralino1 neutralino2) 1.60515467E-02 2 1000023 1000023 # BR(HH -> neutralino2 neutralino2) 3.42640993E-02 2 25 25 # BR(HH -> h0 h0) 4.05662328E-04 2 -1000011 1000011 # BR(HH -> Selectron1 selectron1) 3.21302032E-10 2 -1000011 2000011 # BR(HH -> Selectron1 selectron2) 3.21302032E-10 2 -2000011 1000011 # BR(HH -> Selectron2 selectron1) 4.03871097E-04 2 -1000013 1000013 # BR(HH -> Smuon1 smuon1) 1.37454954E-05 2 -1000013 2000013 # BR(HH -> Smuon1 smuon2) 1.37454954E-05 2 -2000013 1000013 # BR(HH -> Smuon2 smuon1) 1.80571224E-04 2 -1000015 1000015 # BR(HH -> Stau1 stau1) 4.52587015E-03 2 -1000015 2000015 # BR(HH -> Stau1 stau2) 4.52587015E-03 2 -2000015 1000015 # BR(HH -> Stau2 stau1) DECAY 36 8.89538917E-01 # Gamma(A0) 6.11274373E-06 2 22 22 # BR(A0 -> photon photon) 6.30977419E-04 2 21 21 # BR(A0 -> gluon gluon) 6.58260322E-09 2 -11 11 # BR(A0 -> Electron electron) 2.92902511E-04 2 -13 13 # BR(A0 -> Muon muon) 8.49304516E-02 2 -15 15 # BR(A0 -> Tau tau) 1.88836298E-11 2 -2 2 # BR(A0 -> Up up) 2.64328808E-06 2 -4 4 # BR(A0 -> Charm charm) 1.16717546E-01 2 -6 6 # BR(A0 -> Top top) 8.77995484E-07 2 -1 1 # BR(A0 -> Down down) 2.20493704E-04 2 -3 3 # BR(A0 -> Strange strange) 5.86468722E-01 2 -5 5 # BR(A0 -> Bottom bottom) 1.14286977E-01 2 -1000024 1000024 # BR(A0 -> Chargino1 chargino1) 7.10303312E-02 2 1000022 1000022 # BR(A0 -> neutralino1 neutralino1) 8.23874194E-04 2 1000022 1000023 # BR(A0 -> neutralino1 neutralino2) 1.29641313E-02 2 1000023 1000023 # BR(A0 -> neutralino2 neutralino2) 3.87218821E-03 2 23 25 # BR(A0 -> Z h0) 6.41227277E-35 2 25 25 # BR(A0 -> h0 h0) 2.72541936E-10 2 -1000011 2000011 # BR(A0 -> Selectron1 selectron2) 2.72541936E-10 2 -2000011 1000011 # BR(A0 -> Selectron2 selectron1) 1.16605248E-05 2 -1000013 2000013 # BR(A0 -> Smuon1 smuon2) 1.16605248E-05 2 -2000013 1000013 # BR(A0 -> Smuon2 smuon1) 3.86422166E-03 2 -1000015 2000015 # BR(A0 -> Stau1 stau2) 3.86422166E-03 2 -2000015 1000015 # BR(A0 -> Stau2 stau1) DECAY 37 5.77103523E-01 # Gamma(Hp) 1.09735497E-08 2 -11 12 # BR(Hp -> Electron nu_e) 4.69153370E-04 2 -13 14 # BR(Hp -> Muon nu_mu) 1.32702162E-01 2 -15 16 # BR(Hp -> Tau nu_tau) 1.30918860E-06 2 -1 2 # BR(Hp -> Down up) 3.32233240E-04 2 -3 4 # BR(Hp -> Strange charm) 8.18940930E-01 2 -5 6 # BR(Hp -> Bottom top) 1.11828834E-03 2 1000022 1000024 # BR(Hp -> neutralino1 chargino1) 1.56473147E-02 2 1000023 1000024 # BR(Hp -> neutralino2 chargino1) 6.98960586E-03 2 -25 24 # BR(Hp -> H0 W) 7.69953813E-08 2 -35 24 # BR(Hp -> HH W) 1.07948719E-07 2 -36 24 # BR(Hp -> A0 W) 1.33187463E-09 2 -1000011 1000012 # BR(Hp -> Selectron1 snu_e1) 5.69556904E-05 2 -1000013 1000014 # BR(Hp -> Smuon1 snu_mu1) 2.27100515E-03 2 -1000015 1000016 # BR(Hp -> Stau1 snu_tau1) 1.96608875E-02 2 -2000015 1000016 # BR(Hp -> Stau2 snu_tau1) DECAY 6 1.42276225E+00 # Gamma(top) 1.00000000E+00 2 5 24 # BR(top -> bottom W) # Block HiggsBoundsInputHiggsCouplingsBosons # For exact definitions of NormEffCoupSq see HiggsBounds manual 1.01380 3 25 24 24 # higgs-W-W effective coupling^2, normalised to SM 0.224092E-03 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.01380 3 25 23 23 # higgs-Z-Z effective coupling^2, normalised to SM 0.224092E-03 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 0.842307 3 25 21 21 # higgs-gluon-gluon effective coupling^2, normalised to SM 0.303613E-01 3 35 21 21 # higgs-gluon-gluon effective coupling^2, normalised to SM 0.415637E-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.344859E-03 3 36 25 23 # higgs-higgs-Z effective coupling^2, normalised 0.952528 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.4201311968339043 0.0000000000000000 3 25 5 5 # higgs-b-b eff. coupling^2, normalised to SM 94.055378696286240 0.0000000000000000 3 35 5 5 # higgs-b-b eff. coupling^2, normalised to SM 2.11691722613467644E-042 93.199701998261276 3 36 5 5 # higgs-b-b eff. coupling^2, normalised to SM 1.0099456255672334 0.0000000000000000 3 25 6 6 # higgs-top-top eff. coupling^2, normalised to SM 1.33592532043404228E-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.4359623579970071 0.0000000000000000 3 25 15 15 # higgs-tau-tau eff. coupling^2, normalised to SM 100.92889030196287 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.3.1 ||LandH|| # version of HB used to produce these results,the HB setting "whichanalyses" # #CHANNELTYPE 1: channel with the highest statistical sensitivity 1 1 554 # channel id number 1 2 1 # HBresult 1 3 0.44814004376367617 # obsratio 1 4 2 # ncombined 1 5 ||(pp)->h3->tautau, using -2ln(L) reconstruction (CMS-HIG-PAS 14-029)|| # text description of channel # BLOCK HiggsSignalsResults - 0 ||2.2.0beta|| # HiggsSignals version + 0 ||1.4.0|| # HiggsSignals version 1 ||latestresults|| # experimental data set 2 1 # Chi-squared method ("peak"(1) or "mass"(2)-centered or "both"(3)) 3 2 # Parametrization of Higgs mass uncertainty (1:box, 2:gaussian, 3:box+gaussian) - 4 0 # Number of signal strength peak observables - 5 -2106579696 # Number of simplified template cross section (STXS) signal rate observables - 6 32755 # Number of LHC Run-1 signal rate observables - 7 -2105524109 # Number of Higgs mass observables - 8 -1 # Number of observables (total) - 9 0.00000000 # chi^2 (signal strength) from peak observables - 10 0.00000000 # chi^2 (signal strength) from STXS observables - 11 0.00000000 # chi^2 (signal strength) from LHC Run-1 observables - 12 0.00000000 # chi^2 (Higgs mass) from peak observables - 13 0.00000000 # chi^2 (Higgs mass) from STXS observables - 14 0.00000000 # chi^2 (Higgs mass) from LHC Run-1 observables - 15 0.00000000 # chi^2 (signal strength) (total) - 16 0.00000000 # chi^2 (Higgs mass) (total) - 17 0.00000000 # chi^2 (total) - 18 -1.00000000 # Probability for peak observables - 19 -1.00000000 # Probability for LHC-Run1 observables - 20 -1.00000000 # Probability for STXS observables - 21 -1.00000000 # Probability (total chi^2, total number observables) + 4 85 # Number of signal strength peak observables + 5 4 # Number of Higgs mass peak observables + 6 0 # Number of mass-centered observables + 7 89 # Number of observables (total) + 8 118.01595877 # chi^2 from signal strength peak observables + 9 1.06580222 # chi^2 from Higgs mass peak observables + 10 0.00000000 # chi^2 from mass-centered observables + 11 118.01595877 # chi^2 from signal strength (total) + 12 119.08176098 # chi^2 (total) + 13 0.01830391 # Probability (total chi^2, total number observables) +BLOCK HiggsSignalsPeakObservables +# OBS FLAG VALUE # DESCRIPTION + 1 1 201406002 # Analysis ID + 1 2 ||ATL-CONF-2014-060|| # Reference to publication + 1 3 ||(pp)->h->WW->lnulnu(VBFenhanced)|| # Description (Search channel) + 1 4 8.00 # Center-of-mass energy + 1 5 24.80 # Luminosity + 1 6 2.80 # Luminosity uncertainty (in %) + 1 7 8.00 # Mass resolution (GeV) + 1 8 125.36 # Mass value at peak position (in GeV) + 1 9 1.2700 # Observed signal strength modifier (mu) + 1 10 0.4500 # Lower 68%C.L. uncertainty on observed mu + 1 11 0.5300 # Upper 68%C.L. uncertainty on observed mu + 1 12 001 # Assigned Higgs combination + 1 13 1 # Index of dominant Higgs boson + 1 14 25 # pdg number of dominant Higgs boson + 1 15 122.6512 # Mass of dominant Higgs boson + 1 16 0.8080 # Signal strength modifier of dominant Higgs boson + 1 17 0.8080 # Total predicted signal strength modifier mu + 1 18 0.8922 # Chi-squared value (mu-part) + 1 19 0.0000 # Chi-squared value (mh-part) + 1 20 0.8922 # Chi-squared value (total) + 1 21 8.0463 # Chi-squared value for no predicted signal (mu=0) + 2 1 201406001 # Analysis ID + 2 2 ||ATL-CONF-2014-060|| # Reference to publication + 2 3 ||(pp)->h->WW->lnulnu(ggFenhanced)|| # Description (Search channel) + 2 4 8.00 # Center-of-mass energy + 2 5 24.80 # Luminosity + 2 6 2.80 # Luminosity uncertainty (in %) + 2 7 8.00 # Mass resolution (GeV) + 2 8 125.36 # Mass value at peak position (in GeV) + 2 9 1.0100 # Observed signal strength modifier (mu) + 2 10 0.2500 # Lower 68%C.L. uncertainty on observed mu + 2 11 0.2700 # Upper 68%C.L. uncertainty on observed mu + 2 12 001 # Assigned Higgs combination + 2 13 1 # Index of dominant Higgs boson + 2 14 25 # pdg number of dominant Higgs boson + 2 15 122.6512 # Mass of dominant Higgs boson + 2 16 0.7074 # Signal strength modifier of dominant Higgs boson + 2 17 0.7074 # Total predicted signal strength modifier mu + 2 18 1.0800 # Chi-squared value (mu-part) + 2 19 0.0000 # Chi-squared value (mh-part) + 2 20 1.0800 # Chi-squared value (total) + 2 21 17.9750 # Chi-squared value for no predicted signal (mu=0) + 3 1 519103 # Analysis ID + 3 2 ||arXiv:1408.5191|| # Reference to publication + 3 3 ||(pp)->h->ZZ->4l(VBF/VH-like)|| # Description (Search channel) + 3 4 8.00 # Center-of-mass energy + 3 5 25.30 # Luminosity + 3 6 2.80 # Luminosity uncertainty (in %) + 3 7 2.00 # Mass resolution (GeV) + 3 8 125.36 # Mass value at peak position (in GeV) + 3 9 0.2600 # Observed signal strength modifier (mu) + 3 10 0.9400 # Lower 68%C.L. uncertainty on observed mu + 3 11 1.6400 # Upper 68%C.L. uncertainty on observed mu + 3 12 001 # Assigned Higgs combination + 3 13 1 # Index of dominant Higgs boson + 3 14 25 # pdg number of dominant Higgs boson + 3 15 122.6512 # Mass of dominant Higgs boson + 3 16 0.7654 # Signal strength modifier of dominant Higgs boson + 3 17 0.7654 # Total predicted signal strength modifier mu + 3 18 0.1032 # Chi-squared value (mu-part) + 3 19 0.0000 # Chi-squared value (mh-part) + 3 20 0.1032 # Chi-squared value (total) + 3 21 0.0764 # Chi-squared value for no predicted signal (mu=0) + 4 1 519102 # Analysis ID + 4 2 ||arXiv:1408.5191|| # Reference to publication + 4 3 ||(pp)->h->ZZ->4l(ggH-like)|| # Description (Search channel) + 4 4 8.00 # Center-of-mass energy + 4 5 24.80 # Luminosity + 4 6 2.80 # Luminosity uncertainty (in %) + 4 7 0.52 # Mass resolution (GeV) + 4 8 124.51 # Mass value at peak position (in GeV) + 4 9 1.6600 # Observed signal strength modifier (mu) + 4 10 0.4400 # Lower 68%C.L. uncertainty on observed mu + 4 11 0.5100 # Upper 68%C.L. uncertainty on observed mu + 4 12 001 # Assigned Higgs combination + 4 13 1 # Index of dominant Higgs boson + 4 14 25 # pdg number of dominant Higgs boson + 4 15 122.6512 # Mass of dominant Higgs boson + 4 16 0.6939 # Signal strength modifier of dominant Higgs boson + 4 17 0.6939 # Total predicted signal strength modifier mu + 4 18 4.8235 # Chi-squared value (mu-part) + 4 19 -0.6433 # Chi-squared value (mh-part) + 4 20 4.1803 # Chi-squared value (total) + 4 21 16.0800 # Chi-squared value for no predicted signal (mu=0) + 5 1 708405 # Analysis ID + 5 2 ||arXiv:1408.7084|| # Reference to publication + 5 3 ||(pp)->h->gammagamma(VBF-loose)|| # Description (Search channel) + 5 4 8.00 # Center-of-mass energy + 5 5 20.30 # Luminosity + 5 6 2.80 # Luminosity uncertainty (in %) + 5 7 2.00 # Mass resolution (GeV) + 5 8 125.40 # Mass value at peak position (in GeV) + 5 9 1.3270 # Observed signal strength modifier (mu) + 5 10 0.7732 # Lower 68%C.L. uncertainty on observed mu + 5 11 0.9150 # Upper 68%C.L. uncertainty on observed mu + 5 12 000 # Assigned Higgs combination + 5 13 0 # Index of dominant Higgs boson + 5 14 NaN # pdg number of dominant Higgs boson + 5 15 NaN # Mass of the dominant Higgs boson + 5 16 NaN # Signal strength modifier of the dominant Higgs boson + 5 17 0.0000 # Total predicted signal strength modifier mu + 5 18 2.9708 # Chi-squared value (mu-part) + 5 19 0.0000 # Chi-squared value (mh-part) + 5 20 2.9708 # Chi-squared value (total) + 5 21 2.9708 # Chi-squared value for no predicted signal (mu=0) + 6 1 708406 # Analysis ID + 6 2 ||arXiv:1408.7084|| # Reference to publication + 6 3 ||(pp)->h->gammagamma(VBF-tight)|| # Description (Search channel) + 6 4 8.00 # Center-of-mass energy + 6 5 20.30 # Luminosity + 6 6 2.80 # Luminosity uncertainty (in %) + 6 7 2.00 # Mass resolution (GeV) + 6 8 125.40 # Mass value at peak position (in GeV) + 6 9 0.6820 # Observed signal strength modifier (mu) + 6 10 0.5082 # Lower 68%C.L. uncertainty on observed mu + 6 11 0.6670 # Upper 68%C.L. uncertainty on observed mu + 6 12 000 # Assigned Higgs combination + 6 13 0 # Index of dominant Higgs boson + 6 14 NaN # pdg number of dominant Higgs boson + 6 15 NaN # Mass of the dominant Higgs boson + 6 16 NaN # Signal strength modifier of the dominant Higgs boson + 6 17 0.0000 # Total predicted signal strength modifier mu + 6 18 1.8075 # Chi-squared value (mu-part) + 6 19 0.0000 # Chi-squared value (mh-part) + 6 20 1.8075 # Chi-squared value (total) + 6 21 1.8075 # Chi-squared value for no predicted signal (mu=0) + 7 1 708408 # Analysis ID + 7 2 ||arXiv:1408.7084|| # Reference to publication + 7 3 ||(pp)->h->gammagamma(VH-ETmiss)|| # Description (Search channel) + 7 4 8.00 # Center-of-mass energy + 7 5 20.30 # Luminosity + 7 6 2.80 # Luminosity uncertainty (in %) + 7 7 1.56 # Mass resolution (GeV) + 7 8 125.40 # Mass value at peak position (in GeV) + 7 9 3.5100 # Observed signal strength modifier (mu) + 7 10 2.4170 # Lower 68%C.L. uncertainty on observed mu + 7 11 3.3040 # Upper 68%C.L. uncertainty on observed mu + 7 12 000 # Assigned Higgs combination + 7 13 0 # Index of dominant Higgs boson + 7 14 NaN # pdg number of dominant Higgs boson + 7 15 NaN # Mass of the dominant Higgs boson + 7 16 NaN # Signal strength modifier of the dominant Higgs boson + 7 17 0.0000 # Total predicted signal strength modifier mu + 7 18 2.1147 # Chi-squared value (mu-part) + 7 19 0.0000 # Chi-squared value (mh-part) + 7 20 2.1147 # Chi-squared value (total) + 7 21 2.1147 # Chi-squared value for no predicted signal (mu=0) + 8 1 708407 # Analysis ID + 8 2 ||arXiv:1408.7084|| # Reference to publication + 8 3 ||(pp)->h->gammagamma(VH-dijet)|| # Description (Search channel) + 8 4 8.00 # Center-of-mass energy + 8 5 20.30 # Luminosity + 8 6 2.80 # Luminosity uncertainty (in %) + 8 7 2.00 # Mass resolution (GeV) + 8 8 125.40 # Mass value at peak position (in GeV) + 8 9 0.2268 # Observed signal strength modifier (mu) + 8 10 1.3878 # Lower 68%C.L. uncertainty on observed mu + 8 11 1.6742 # Upper 68%C.L. uncertainty on observed mu + 8 12 000 # Assigned Higgs combination + 8 13 0 # Index of dominant Higgs boson + 8 14 NaN # pdg number of dominant Higgs boson + 8 15 NaN # Mass of the dominant Higgs boson + 8 16 NaN # Signal strength modifier of the dominant Higgs boson + 8 17 0.0000 # Total predicted signal strength modifier mu + 8 18 0.0267 # Chi-squared value (mu-part) + 8 19 0.0000 # Chi-squared value (mh-part) + 8 20 0.0267 # Chi-squared value (total) + 8 21 0.0267 # Chi-squared value for no predicted signal (mu=0) + 9 1 708409 # Analysis ID + 9 2 ||arXiv:1408.7084|| # Reference to publication + 9 3 ||(pp)->h->gammagamma(VH-onelepton)|| # Description (Search channel) + 9 4 8.00 # Center-of-mass energy + 9 5 20.30 # Luminosity + 9 6 2.80 # Luminosity uncertainty (in %) + 9 7 2.00 # Mass resolution (GeV) + 9 8 125.40 # Mass value at peak position (in GeV) + 9 9 0.4080 # Observed signal strength modifier (mu) + 9 10 1.0560 # Lower 68%C.L. uncertainty on observed mu + 9 11 1.4270 # Upper 68%C.L. uncertainty on observed mu + 9 12 000 # Assigned Higgs combination + 9 13 0 # Index of dominant Higgs boson + 9 14 NaN # pdg number of dominant Higgs boson + 9 15 NaN # Mass of the dominant Higgs boson + 9 16 NaN # Signal strength modifier of the dominant Higgs boson + 9 17 0.0000 # Total predicted signal strength modifier mu + 9 18 0.1493 # Chi-squared value (mu-part) + 9 19 0.0000 # Chi-squared value (mh-part) + 9 20 0.1493 # Chi-squared value (total) + 9 21 0.1493 # Chi-squared value for no predicted signal (mu=0) + 10 1 708402 # Analysis ID + 10 2 ||arXiv:1408.7084|| # Reference to publication + 10 3 ||(pp)->h->gammagamma(central-highpT)|| # Description (Search channel) + 10 4 8.00 # Center-of-mass energy + 10 5 20.30 # Luminosity + 10 6 2.80 # Luminosity uncertainty (in %) + 10 7 2.00 # Mass resolution (GeV) + 10 8 125.40 # Mass value at peak position (in GeV) + 10 9 1.6190 # Observed signal strength modifier (mu) + 10 10 0.8311 # Lower 68%C.L. uncertainty on observed mu + 10 11 1.0030 # Upper 68%C.L. uncertainty on observed mu + 10 12 000 # Assigned Higgs combination + 10 13 0 # Index of dominant Higgs boson + 10 14 NaN # pdg number of dominant Higgs boson + 10 15 NaN # Mass of the dominant Higgs boson + 10 16 NaN # Signal strength modifier of the dominant Higgs boson + 10 17 0.0000 # Total predicted signal strength modifier mu + 10 18 3.8902 # Chi-squared value (mu-part) + 10 19 0.0000 # Chi-squared value (mh-part) + 10 20 3.8902 # Chi-squared value (total) + 10 21 3.8902 # Chi-squared value for no predicted signal (mu=0) + 11 1 708401 # Analysis ID + 11 2 ||arXiv:1408.7084|| # Reference to publication + 11 3 ||(pp)->h->gammagamma(central-lowpT)|| # Description (Search channel) + 11 4 8.00 # Center-of-mass energy + 11 5 20.30 # Luminosity + 11 6 2.80 # Luminosity uncertainty (in %) + 11 7 0.50 # Mass resolution (GeV) + 11 8 125.98 # Mass value at peak position (in GeV) + 11 9 0.6244 # Observed signal strength modifier (mu) + 11 10 0.3976 # Lower 68%C.L. uncertainty on observed mu + 11 11 0.4246 # Upper 68%C.L. uncertainty on observed mu + 11 12 000 # Assigned Higgs combination + 11 13 0 # Index of dominant Higgs boson + 11 14 NaN # pdg number of dominant Higgs boson + 11 15 NaN # Mass of the dominant Higgs boson + 11 16 NaN # Signal strength modifier of the dominant Higgs boson + 11 17 0.0000 # Total predicted signal strength modifier mu + 11 18 2.5294 # Chi-squared value (mu-part) + 11 19 0.0000 # Chi-squared value (mh-part) + 11 20 2.5294 # Chi-squared value (total) + 11 21 2.5294 # Chi-squared value for no predicted signal (mu=0) + 12 1 708404 # Analysis ID + 12 2 ||arXiv:1408.7084|| # Reference to publication + 12 3 ||(pp)->h->gammagamma(forward-highpT)|| # Description (Search channel) + 12 4 8.00 # Center-of-mass energy + 12 5 20.30 # Luminosity + 12 6 2.80 # Luminosity uncertainty (in %) + 12 7 2.00 # Mass resolution (GeV) + 12 8 125.40 # Mass value at peak position (in GeV) + 12 9 1.7290 # Observed signal strength modifier (mu) + 12 10 1.1800 # Lower 68%C.L. uncertainty on observed mu + 12 11 1.3430 # Upper 68%C.L. uncertainty on observed mu + 12 12 000 # Assigned Higgs combination + 12 13 0 # Index of dominant Higgs boson + 12 14 NaN # pdg number of dominant Higgs boson + 12 15 NaN # Mass of the dominant Higgs boson + 12 16 NaN # Signal strength modifier of the dominant Higgs boson + 12 17 0.0000 # Total predicted signal strength modifier mu + 12 18 2.1763 # Chi-squared value (mu-part) + 12 19 0.0000 # Chi-squared value (mh-part) + 12 20 2.1763 # Chi-squared value (total) + 12 21 2.1763 # Chi-squared value for no predicted signal (mu=0) + 13 1 708403 # Analysis ID + 13 2 ||arXiv:1408.7084|| # Reference to publication + 13 3 ||(pp)->h->gammagamma(forward-lowpT)|| # Description (Search channel) + 13 4 8.00 # Center-of-mass energy + 13 5 20.30 # Luminosity + 13 6 2.80 # Luminosity uncertainty (in %) + 13 7 2.00 # Mass resolution (GeV) + 13 8 125.40 # Mass value at peak position (in GeV) + 13 9 2.0340 # Observed signal strength modifier (mu) + 13 10 0.5260 # Lower 68%C.L. uncertainty on observed mu + 13 11 0.5700 # Upper 68%C.L. uncertainty on observed mu + 13 12 000 # Assigned Higgs combination + 13 13 0 # Index of dominant Higgs boson + 13 14 NaN # pdg number of dominant Higgs boson + 13 15 NaN # Mass of the dominant Higgs boson + 13 16 NaN # Signal strength modifier of the dominant Higgs boson + 13 17 0.0000 # Total predicted signal strength modifier mu + 13 18 17.5779 # Chi-squared value (mu-part) + 13 19 0.0000 # Chi-squared value (mh-part) + 13 20 17.5779 # Chi-squared value (total) + 13 21 17.5779 # Chi-squared value for no predicted signal (mu=0) + 14 1 708410 # Analysis ID + 14 2 ||arXiv:1408.7084|| # Reference to publication + 14 3 ||(pp)->h->gammagamma(ttH-hadronic)|| # Description (Search channel) + 14 4 8.00 # Center-of-mass energy + 14 5 20.30 # Luminosity + 14 6 2.80 # Luminosity uncertainty (in %) + 14 7 2.00 # Mass resolution (GeV) + 14 8 125.40 # Mass value at peak position (in GeV) + 14 9 -0.8424 # Observed signal strength modifier (mu) + 14 10 1.2503 # Lower 68%C.L. uncertainty on observed mu + 14 11 3.2294 # Upper 68%C.L. uncertainty on observed mu + 14 12 000 # Assigned Higgs combination + 14 13 0 # Index of dominant Higgs boson + 14 14 NaN # pdg number of dominant Higgs boson + 14 15 NaN # Mass of the dominant Higgs boson + 14 16 NaN # Signal strength modifier of the dominant Higgs boson + 14 17 0.0000 # Total predicted signal strength modifier mu + 14 18 0.0681 # Chi-squared value (mu-part) + 14 19 0.0000 # Chi-squared value (mh-part) + 14 20 0.0681 # Chi-squared value (total) + 14 21 0.0681 # Chi-squared value for no predicted signal (mu=0) + 15 1 708411 # Analysis ID + 15 2 ||arXiv:1408.7084|| # Reference to publication + 15 3 ||(pp)->h->gammagamma(ttH-leptonic)|| # Description (Search channel) + 15 4 8.00 # Center-of-mass energy + 15 5 20.30 # Luminosity + 15 6 2.80 # Luminosity uncertainty (in %) + 15 7 2.00 # Mass resolution (GeV) + 15 8 125.40 # Mass value at peak position (in GeV) + 15 9 2.4230 # Observed signal strength modifier (mu) + 15 10 2.0681 # Lower 68%C.L. uncertainty on observed mu + 15 11 3.2120 # Upper 68%C.L. uncertainty on observed mu + 15 12 000 # Assigned Higgs combination + 15 13 0 # Index of dominant Higgs boson + 15 14 NaN # pdg number of dominant Higgs boson + 15 15 NaN # Mass of the dominant Higgs boson + 15 16 NaN # Signal strength modifier of the dominant Higgs boson + 15 17 0.0000 # Total predicted signal strength modifier mu + 15 18 1.3851 # Chi-squared value (mu-part) + 15 19 0.0000 # Chi-squared value (mh-part) + 15 20 1.3851 # Chi-squared value (total) + 15 21 1.3851 # Chi-squared value for no predicted signal (mu=0) + 16 1 201406106 # Analysis ID + 16 2 ||ATLAS-CONF-2014-061|| # Reference to publication + 16 3 ||(pp)->h->tautau(VBF,hadhad)|| # Description (Search channel) + 16 4 8.00 # Center-of-mass energy + 16 5 24.80 # Luminosity + 16 6 2.80 # Luminosity uncertainty (in %) + 16 7 20.00 # Mass resolution (GeV) + 16 8 125.36 # Mass value at peak position (in GeV) + 16 9 1.4000 # Observed signal strength modifier (mu) + 16 10 0.7000 # Lower 68%C.L. uncertainty on observed mu + 16 11 0.9000 # Upper 68%C.L. uncertainty on observed mu + 16 12 001 # Assigned Higgs combination + 16 13 1 # Index of dominant Higgs boson + 16 14 25 # pdg number of dominant Higgs boson + 16 15 122.6512 # Mass of dominant Higgs boson + 16 16 1.0965 # Signal strength modifier of dominant Higgs boson + 16 17 1.0965 # Total predicted signal strength modifier mu + 16 18 0.0641 # Chi-squared value (mu-part) + 16 19 0.0000 # Chi-squared value (mh-part) + 16 20 0.0641 # Chi-squared value (total) + 16 21 4.0180 # Chi-squared value for no predicted signal (mu=0) + 17 1 201406105 # Analysis ID + 17 2 ||ATLAS-CONF-2014-061|| # Reference to publication + 17 3 ||(pp)->h->tautau(boosted,hadhad)|| # Description (Search channel) + 17 4 8.00 # Center-of-mass energy + 17 5 24.80 # Luminosity + 17 6 2.80 # Luminosity uncertainty (in %) + 17 7 20.00 # Mass resolution (GeV) + 17 8 125.36 # Mass value at peak position (in GeV) + 17 9 3.6000 # Observed signal strength modifier (mu) + 17 10 1.6000 # Lower 68%C.L. uncertainty on observed mu + 17 11 2.0000 # Upper 68%C.L. uncertainty on observed mu + 17 12 001 # Assigned Higgs combination + 17 13 1 # Index of dominant Higgs boson + 17 14 25 # pdg number of dominant Higgs boson + 17 15 122.6512 # Mass of dominant Higgs boson + 17 16 1.0235 # Signal strength modifier of dominant Higgs boson + 17 17 1.0235 # Total predicted signal strength modifier mu + 17 18 2.2951 # Chi-squared value (mu-part) + 17 19 0.0000 # Chi-squared value (mh-part) + 17 20 2.2951 # Chi-squared value (total) + 17 21 5.2142 # Chi-squared value for no predicted signal (mu=0) + 18 1 201406104 # Analysis ID + 18 2 ||ATLAS-CONF-2014-061|| # Reference to publication + 18 3 ||(pp)->h->tautau(VBF,lephad)|| # Description (Search channel) + 18 4 8.00 # Center-of-mass energy + 18 5 24.80 # Luminosity + 18 6 2.80 # Luminosity uncertainty (in %) + 18 7 20.00 # Mass resolution (GeV) + 18 8 125.36 # Mass value at peak position (in GeV) + 18 9 1.0000 # Observed signal strength modifier (mu) + 18 10 0.5000 # Lower 68%C.L. uncertainty on observed mu + 18 11 0.6000 # Upper 68%C.L. uncertainty on observed mu + 18 12 001 # Assigned Higgs combination + 18 13 1 # Index of dominant Higgs boson + 18 14 25 # pdg number of dominant Higgs boson + 18 15 122.6512 # Mass of dominant Higgs boson + 18 16 1.1211 # Signal strength modifier of dominant Higgs boson + 18 17 1.1211 # Total predicted signal strength modifier mu + 18 18 0.0968 # Chi-squared value (mu-part) + 18 19 0.0000 # Chi-squared value (mh-part) + 18 20 0.0968 # Chi-squared value (total) + 18 21 3.9914 # Chi-squared value for no predicted signal (mu=0) + 19 1 201406103 # Analysis ID + 19 2 ||ATL-CONF-2014-061|| # Reference to publication + 19 3 ||(pp)->h->tautau(boosted,lephad)|| # Description (Search channel) + 19 4 8.00 # Center-of-mass energy + 19 5 24.80 # Luminosity + 19 6 2.80 # Luminosity uncertainty (in %) + 19 7 20.00 # Mass resolution (GeV) + 19 8 125.36 # Mass value at peak position (in GeV) + 19 9 0.9000 # Observed signal strength modifier (mu) + 19 10 0.9000 # Lower 68%C.L. uncertainty on observed mu + 19 11 1.0000 # Upper 68%C.L. uncertainty on observed mu + 19 12 001 # Assigned Higgs combination + 19 13 1 # Index of dominant Higgs boson + 19 14 25 # pdg number of dominant Higgs boson + 19 15 122.6512 # Mass of dominant Higgs boson + 19 16 1.0168 # Signal strength modifier of dominant Higgs boson + 19 17 1.0168 # Total predicted signal strength modifier mu + 19 18 0.0541 # Chi-squared value (mu-part) + 19 19 0.0000 # Chi-squared value (mh-part) + 19 20 0.0541 # Chi-squared value (total) + 19 21 0.9988 # Chi-squared value for no predicted signal (mu=0) + 20 1 201406102 # Analysis ID + 20 2 ||ATL-CONF-2014-061|| # Reference to publication + 20 3 ||(pp)->h->tautau(VBF,leplep)|| # Description (Search channel) + 20 4 8.00 # Center-of-mass energy + 20 5 24.80 # Luminosity + 20 6 2.80 # Luminosity uncertainty (in %) + 20 7 20.00 # Mass resolution (GeV) + 20 8 125.36 # Mass value at peak position (in GeV) + 20 9 1.8000 # Observed signal strength modifier (mu) + 20 10 0.9000 # Lower 68%C.L. uncertainty on observed mu + 20 11 1.1000 # Upper 68%C.L. uncertainty on observed mu + 20 12 001 # Assigned Higgs combination + 20 13 1 # Index of dominant Higgs boson + 20 14 25 # pdg number of dominant Higgs boson + 20 15 122.6512 # Mass of dominant Higgs boson + 20 16 1.1245 # Signal strength modifier of dominant Higgs boson + 20 17 1.1245 # Total predicted signal strength modifier mu + 20 18 0.4362 # Chi-squared value (mu-part) + 20 19 0.0000 # Chi-squared value (mh-part) + 20 20 0.4362 # Chi-squared value (total) + 20 21 4.0219 # Chi-squared value for no predicted signal (mu=0) + 21 1 201406101 # Analysis ID + 21 2 ||ATL-CONF-2014-061|| # Reference to publication + 21 3 ||(pp)->h->tautau(boosted,leplep)|| # Description (Search channel) + 21 4 8.00 # Center-of-mass energy + 21 5 24.80 # Luminosity + 21 6 2.80 # Luminosity uncertainty (in %) + 21 7 20.00 # Mass resolution (GeV) + 21 8 125.36 # Mass value at peak position (in GeV) + 21 9 3.0000 # Observed signal strength modifier (mu) + 21 10 1.7000 # Lower 68%C.L. uncertainty on observed mu + 21 11 1.9000 # Upper 68%C.L. uncertainty on observed mu + 21 12 001 # Assigned Higgs combination + 21 13 1 # Index of dominant Higgs boson + 21 14 25 # pdg number of dominant Higgs boson + 21 15 122.6512 # Mass of dominant Higgs boson + 21 16 1.0204 # Signal strength modifier of dominant Higgs boson + 21 17 1.0204 # Total predicted signal strength modifier mu + 21 18 1.0167 # Chi-squared value (mu-part) + 21 19 0.0000 # Chi-squared value (mh-part) + 21 20 1.0167 # Chi-squared value (total) + 21 21 3.1714 # Chi-squared value for no predicted signal (mu=0) + 22 1 621201 # Analysis ID + 22 2 ||arXiv:1409.6212|| # Reference to publication + 22 3 ||(pp)->Vh->Vbb(0lepton)|| # Description (Search channel) + 22 4 8.00 # Center-of-mass energy + 22 5 25.00 # Luminosity + 22 6 2.80 # Luminosity uncertainty (in %) + 22 7 15.00 # Mass resolution (GeV) + 22 8 125.00 # Mass value at peak position (in GeV) + 22 9 -0.3500 # Observed signal strength modifier (mu) + 22 10 0.5200 # Lower 68%C.L. uncertainty on observed mu + 22 11 0.5500 # Upper 68%C.L. uncertainty on observed mu + 22 12 001 # Assigned Higgs combination + 22 13 1 # Index of dominant Higgs boson + 22 14 25 # pdg number of dominant Higgs boson + 22 15 122.6512 # Mass of dominant Higgs boson + 22 16 1.1325 # Signal strength modifier of dominant Higgs boson + 22 17 1.1325 # Total predicted signal strength modifier mu + 22 18 7.1153 # Chi-squared value (mu-part) + 22 19 0.0000 # Chi-squared value (mh-part) + 22 20 7.1153 # Chi-squared value (total) + 22 21 0.4020 # Chi-squared value for no predicted signal (mu=0) + 23 1 621202 # Analysis ID + 23 2 ||arXiv:1409.6212|| # Reference to publication + 23 3 ||(pp)->Vh->Vbb(1lepton)|| # Description (Search channel) + 23 4 8.00 # Center-of-mass energy + 23 5 25.00 # Luminosity + 23 6 2.60 # Luminosity uncertainty (in %) + 23 7 15.00 # Mass resolution (GeV) + 23 8 125.00 # Mass value at peak position (in GeV) + 23 9 1.1700 # Observed signal strength modifier (mu) + 23 10 0.6000 # Lower 68%C.L. uncertainty on observed mu + 23 11 0.6600 # Upper 68%C.L. uncertainty on observed mu + 23 12 001 # Assigned Higgs combination + 23 13 1 # Index of dominant Higgs boson + 23 14 25 # pdg number of dominant Higgs boson + 23 15 122.6512 # Mass of dominant Higgs boson + 23 16 1.1325 # Signal strength modifier of dominant Higgs boson + 23 17 1.1325 # Total predicted signal strength modifier mu + 23 18 0.0004 # Chi-squared value (mu-part) + 23 19 0.0000 # Chi-squared value (mh-part) + 23 20 0.0004 # Chi-squared value (total) + 23 21 3.8027 # Chi-squared value for no predicted signal (mu=0) + 24 1 621203 # Analysis ID + 24 2 ||arXiv:1409.6212|| # Reference to publication + 24 3 ||(pp)->Vh->Vbb(2lepton)|| # Description (Search channel) + 24 4 8.00 # Center-of-mass energy + 24 5 25.00 # Luminosity + 24 6 2.80 # Luminosity uncertainty (in %) + 24 7 15.00 # Mass resolution (GeV) + 24 8 125.00 # Mass value at peak position (in GeV) + 24 9 0.9400 # Observed signal strength modifier (mu) + 24 10 0.7900 # Lower 68%C.L. uncertainty on observed mu + 24 11 0.8800 # Upper 68%C.L. uncertainty on observed mu + 24 12 001 # Assigned Higgs combination + 24 13 1 # Index of dominant Higgs boson + 24 14 25 # pdg number of dominant Higgs boson + 24 15 122.6512 # Mass of dominant Higgs boson + 24 16 1.1325 # Signal strength modifier of dominant Higgs boson + 24 17 1.1325 # Total predicted signal strength modifier mu + 24 18 0.0539 # Chi-squared value (mu-part) + 24 19 0.0000 # Chi-squared value (mh-part) + 24 20 0.0539 # Chi-squared value (total) + 24 21 1.4138 # Chi-squared value for no predicted signal (mu=0) + 25 1 20150053 # Analysis ID + 25 2 ||ATL-CONF-2015-005|| # Reference to publication + 25 3 ||(pp)->Vh->VWW(2l)|| # Description (Search channel) + 25 4 8.00 # Center-of-mass energy + 25 5 24.80 # Luminosity + 25 6 2.80 # Luminosity uncertainty (in %) + 25 7 20.00 # Mass resolution (GeV) + 25 8 125.36 # Mass value at peak position (in GeV) + 25 9 3.7000 # Observed signal strength modifier (mu) + 25 10 1.8000 # Lower 68%C.L. uncertainty on observed mu + 25 11 1.9000 # Upper 68%C.L. uncertainty on observed mu + 25 12 001 # Assigned Higgs combination + 25 13 1 # Index of dominant Higgs boson + 25 14 25 # pdg number of dominant Higgs boson + 25 15 122.6512 # Mass of dominant Higgs boson + 25 16 0.8413 # Signal strength modifier of dominant Higgs boson + 25 17 0.8413 # Total predicted signal strength modifier mu + 25 18 2.3955 # Chi-squared value (mu-part) + 25 19 0.0000 # Chi-squared value (mh-part) + 25 20 2.3955 # Chi-squared value (total) + 25 21 4.2451 # Chi-squared value for no predicted signal (mu=0) + 26 1 20150052 # Analysis ID + 26 2 ||ATL-CONF-2015-005|| # Reference to publication + 26 3 ||(pp)->Vh->VWW(3l)|| # Description (Search channel) + 26 4 8.00 # Center-of-mass energy + 26 5 24.80 # Luminosity + 26 6 2.80 # Luminosity uncertainty (in %) + 26 7 20.00 # Mass resolution (GeV) + 26 8 125.36 # Mass value at peak position (in GeV) + 26 9 0.7200 # Observed signal strength modifier (mu) + 26 10 1.1000 # Lower 68%C.L. uncertainty on observed mu + 26 11 1.3000 # Upper 68%C.L. uncertainty on observed mu + 26 12 001 # Assigned Higgs combination + 26 13 1 # Index of dominant Higgs boson + 26 14 25 # pdg number of dominant Higgs boson + 26 15 122.6512 # Mass of dominant Higgs boson + 26 16 0.8413 # Signal strength modifier of dominant Higgs boson + 26 17 0.8413 # Total predicted signal strength modifier mu + 26 18 0.0113 # Chi-squared value (mu-part) + 26 19 0.0000 # Chi-squared value (mh-part) + 26 20 0.0113 # Chi-squared value (total) + 26 21 0.4283 # Chi-squared value for no predicted signal (mu=0) + 27 1 20150051 # Analysis ID + 27 2 ||ATL-CONF-2015-005|| # Reference to publication + 27 3 ||(pp)->Vh->VWW(4l)|| # Description (Search channel) + 27 4 8.00 # Center-of-mass energy + 27 5 24.80 # Luminosity + 27 6 2.80 # Luminosity uncertainty (in %) + 27 7 20.00 # Mass resolution (GeV) + 27 8 125.36 # Mass value at peak position (in GeV) + 27 9 4.9000 # Observed signal strength modifier (mu) + 27 10 3.1000 # Lower 68%C.L. uncertainty on observed mu + 27 11 4.6000 # Upper 68%C.L. uncertainty on observed mu + 27 12 001 # Assigned Higgs combination + 27 13 1 # Index of dominant Higgs boson + 27 14 25 # pdg number of dominant Higgs boson + 27 15 122.6512 # Mass of dominant Higgs boson + 27 16 0.8413 # Signal strength modifier of dominant Higgs boson + 27 17 0.8413 # Total predicted signal strength modifier mu + 27 18 1.6358 # Chi-squared value (mu-part) + 27 19 0.0000 # Chi-squared value (mh-part) + 27 20 1.6358 # Chi-squared value (total) + 27 21 2.5130 # Chi-squared value for no predicted signal (mu=0) + 28 1 20150065 # Analysis ID + 28 2 ||ATL-CONF-2015-006|| # Reference to publication + 28 3 ||(pp)->tth->multilepton(1l2tau_had)|| # Description (Search channel) + 28 4 8.00 # Center-of-mass energy + 28 5 20.30 # Luminosity + 28 6 2.80 # Luminosity uncertainty (in %) + 28 7 20.00 # Mass resolution (GeV) + 28 8 125.00 # Mass value at peak position (in GeV) + 28 9 -9.6000 # Observed signal strength modifier (mu) + 28 10 9.7000 # Lower 68%C.L. uncertainty on observed mu + 28 11 9.6000 # Upper 68%C.L. uncertainty on observed mu + 28 12 001 # Assigned Higgs combination + 28 13 1 # Index of dominant Higgs boson + 28 14 25 # pdg number of dominant Higgs boson + 28 15 122.6512 # Mass of dominant Higgs boson + 28 16 1.1386 # Signal strength modifier of dominant Higgs boson + 28 17 1.1386 # Total predicted signal strength modifier mu + 28 18 1.2293 # Chi-squared value (mu-part) + 28 19 0.0000 # Chi-squared value (mh-part) + 28 20 1.2293 # Chi-squared value (total) + 28 21 1.0117 # Chi-squared value for no predicted signal (mu=0) + 29 1 20150061 # Analysis ID + 29 2 ||ATL-CONF-2015-006|| # Reference to publication + 29 3 ||(pp)->tth->multilepton(2l0tau_had)|| # Description (Search channel) + 29 4 8.00 # Center-of-mass energy + 29 5 20.30 # Luminosity + 29 6 2.80 # Luminosity uncertainty (in %) + 29 7 20.00 # Mass resolution (GeV) + 29 8 125.00 # Mass value at peak position (in GeV) + 29 9 2.8000 # Observed signal strength modifier (mu) + 29 10 1.9000 # Lower 68%C.L. uncertainty on observed mu + 29 11 2.1000 # Upper 68%C.L. uncertainty on observed mu + 29 12 001 # Assigned Higgs combination + 29 13 1 # Index of dominant Higgs boson + 29 14 25 # pdg number of dominant Higgs boson + 29 15 122.6512 # Mass of dominant Higgs boson + 29 16 0.9006 # Signal strength modifier of dominant Higgs boson + 29 17 0.9006 # Total predicted signal strength modifier mu + 29 18 0.9176 # Chi-squared value (mu-part) + 29 19 0.0000 # Chi-squared value (mh-part) + 29 20 0.9176 # Chi-squared value (total) + 29 21 2.2203 # Chi-squared value for no predicted signal (mu=0) + 30 1 20150063 # Analysis ID + 30 2 ||ATL-CONF-2015-006|| # Reference to publication + 30 3 ||(pp)->tth->multilepton(2l1tau_had)|| # Description (Search channel) + 30 4 8.00 # Center-of-mass energy + 30 5 20.30 # Luminosity + 30 6 2.80 # Luminosity uncertainty (in %) + 30 7 20.00 # Mass resolution (GeV) + 30 8 125.00 # Mass value at peak position (in GeV) + 30 9 -0.9000 # Observed signal strength modifier (mu) + 30 10 2.0000 # Lower 68%C.L. uncertainty on observed mu + 30 11 3.1000 # Upper 68%C.L. uncertainty on observed mu + 30 12 001 # Assigned Higgs combination + 30 13 1 # Index of dominant Higgs boson + 30 14 25 # pdg number of dominant Higgs boson + 30 15 122.6512 # Mass of dominant Higgs boson + 30 16 1.0496 # Signal strength modifier of dominant Higgs boson + 30 17 1.0496 # Total predicted signal strength modifier mu + 30 18 0.4066 # Chi-squared value (mu-part) + 30 19 0.0000 # Chi-squared value (mh-part) + 30 20 0.4066 # Chi-squared value (total) + 30 21 0.0843 # Chi-squared value for no predicted signal (mu=0) + 31 1 20150062 # Analysis ID + 31 2 ||ATL-CONF-2015-006|| # Reference to publication + 31 3 ||(pp)->tth->multilepton(3l)|| # Description (Search channel) + 31 4 8.00 # Center-of-mass energy + 31 5 20.30 # Luminosity + 31 6 2.80 # Luminosity uncertainty (in %) + 31 7 20.00 # Mass resolution (GeV) + 31 8 125.00 # Mass value at peak position (in GeV) + 31 9 2.8000 # Observed signal strength modifier (mu) + 31 10 1.8000 # Lower 68%C.L. uncertainty on observed mu + 31 11 2.2000 # Upper 68%C.L. uncertainty on observed mu + 31 12 001 # Assigned Higgs combination + 31 13 1 # Index of dominant Higgs boson + 31 14 25 # pdg number of dominant Higgs boson + 31 15 122.6512 # Mass of dominant Higgs boson + 31 16 0.9064 # Signal strength modifier of dominant Higgs boson + 31 17 0.9064 # Total predicted signal strength modifier mu + 31 18 1.0188 # Chi-squared value (mu-part) + 31 19 0.0000 # Chi-squared value (mh-part) + 31 20 1.0188 # Chi-squared value (total) + 31 21 2.4799 # Chi-squared value for no predicted signal (mu=0) + 32 1 20150064 # Analysis ID + 32 2 ||ATL-CONF-2015-006|| # Reference to publication + 32 3 ||(pp)->tth->multilepton(4l)|| # Description (Search channel) + 32 4 8.00 # Center-of-mass energy + 32 5 20.30 # Luminosity + 32 6 2.80 # Luminosity uncertainty (in %) + 32 7 20.00 # Mass resolution (GeV) + 32 8 125.00 # Mass value at peak position (in GeV) + 32 9 1.8000 # Observed signal strength modifier (mu) + 32 10 6.9000 # Lower 68%C.L. uncertainty on observed mu + 32 11 6.9000 # Upper 68%C.L. uncertainty on observed mu + 32 12 001 # Assigned Higgs combination + 32 13 1 # Index of dominant Higgs boson + 32 14 25 # pdg number of dominant Higgs boson + 32 15 122.6512 # Mass of dominant Higgs boson + 32 16 0.9013 # Signal strength modifier of dominant Higgs boson + 32 17 0.9013 # Total predicted signal strength modifier mu + 32 18 0.0140 # Chi-squared value (mu-part) + 32 19 0.0000 # Chi-squared value (mh-part) + 32 20 0.0140 # Chi-squared value (total) + 32 21 0.0681 # Chi-squared value for no predicted signal (mu=0) + 33 1 50661 # Analysis ID + 33 2 ||arXiv:1503.05066|| # Reference to publication + 33 3 ||(pp)->tth->tt(bb)|| # Description (Search channel) + 33 4 8.00 # Center-of-mass energy + 33 5 20.30 # Luminosity + 33 6 2.80 # Luminosity uncertainty (in %) + 33 7 25.00 # Mass resolution (GeV) + 33 8 125.00 # Mass value at peak position (in GeV) + 33 9 1.5000 # Observed signal strength modifier (mu) + 33 10 1.1000 # Lower 68%C.L. uncertainty on observed mu + 33 11 1.1000 # Upper 68%C.L. uncertainty on observed mu + 33 12 001 # Assigned Higgs combination + 33 13 1 # Index of dominant Higgs boson + 33 14 25 # pdg number of dominant Higgs boson + 33 15 122.6512 # Mass of dominant Higgs boson + 33 16 1.1282 # Signal strength modifier of dominant Higgs boson + 33 17 1.1282 # Total predicted signal strength modifier mu + 33 18 0.0715 # Chi-squared value (mu-part) + 33 19 0.0000 # Chi-squared value (mh-part) + 33 20 0.0715 # Chi-squared value (total) + 33 21 1.8766 # Chi-squared value for no predicted signal (mu=0) + 34 1 130166683 # Analysis ID + 34 2 ||arXiv:1301.6668|| # Reference to publication + 34 3 ||(ppbar)->h->WW|| # Description (Search channel) + 34 4 1.96 # Center-of-mass energy + 34 5 9.70 # Luminosity + 34 6 6.00 # Luminosity uncertainty (in %) + 34 7 30.00 # Mass resolution (GeV) + 34 8 125.00 # Mass value at peak position (in GeV) + 34 9 0.0000 # Observed signal strength modifier (mu) + 34 10 1.7800 # Lower 68%C.L. uncertainty on observed mu + 34 11 1.7800 # Upper 68%C.L. uncertainty on observed mu + 34 12 001 # Assigned Higgs combination + 34 13 1 # Index of dominant Higgs boson + 34 14 25 # pdg number of dominant Higgs boson + 34 15 122.6512 # Mass of dominant Higgs boson + 34 16 0.7351 # Signal strength modifier of dominant Higgs boson + 34 17 0.7351 # Total predicted signal strength modifier mu + 34 18 0.1852 # Chi-squared value (mu-part) + 34 19 0.0000 # Chi-squared value (mh-part) + 34 20 0.1852 # Chi-squared value (total) + 34 21 0.0000 # Chi-squared value for no predicted signal (mu=0) + 35 1 130166682 # Analysis ID + 35 2 ||arXiv:1301.6668|| # Reference to publication + 35 3 ||(ppbar)->h->gammagamma|| # Description (Search channel) + 35 4 1.96 # Center-of-mass energy + 35 5 9.70 # Luminosity + 35 6 6.00 # Luminosity uncertainty (in %) + 35 7 5.00 # Mass resolution (GeV) + 35 8 125.00 # Mass value at peak position (in GeV) + 35 9 7.8100 # Observed signal strength modifier (mu) + 35 10 4.4200 # Lower 68%C.L. uncertainty on observed mu + 35 11 4.6100 # Upper 68%C.L. uncertainty on observed mu + 35 12 001 # Assigned Higgs combination + 35 13 1 # Index of dominant Higgs boson + 35 14 25 # pdg number of dominant Higgs boson + 35 15 122.6512 # Mass of dominant Higgs boson + 35 16 0.6591 # Signal strength modifier of dominant Higgs boson + 35 17 0.6591 # Total predicted signal strength modifier mu + 35 18 2.6218 # Chi-squared value (mu-part) + 35 19 0.0000 # Chi-squared value (mh-part) + 35 20 2.6218 # Chi-squared value (total) + 35 21 3.1939 # Chi-squared value for no predicted signal (mu=0) + 36 1 130166684 # Analysis ID + 36 2 ||arXiv:1301.6668|| # Reference to publication + 36 3 ||(ppbar)->h->tautau|| # Description (Search channel) + 36 4 1.96 # Center-of-mass energy + 36 5 9.70 # Luminosity + 36 6 6.00 # Luminosity uncertainty (in %) + 36 7 25.00 # Mass resolution (GeV) + 36 8 125.00 # Mass value at peak position (in GeV) + 36 9 0.0000 # Observed signal strength modifier (mu) + 36 10 8.4400 # Lower 68%C.L. uncertainty on observed mu + 36 11 8.4400 # Upper 68%C.L. uncertainty on observed mu + 36 12 001 # Assigned Higgs combination + 36 13 1 # Index of dominant Higgs boson + 36 14 25 # pdg number of dominant Higgs boson + 36 15 122.6512 # Mass of dominant Higgs boson + 36 16 1.0080 # Signal strength modifier of dominant Higgs boson + 36 17 1.0080 # Total predicted signal strength modifier mu + 36 18 0.0155 # Chi-squared value (mu-part) + 36 19 0.0000 # Chi-squared value (mh-part) + 36 20 0.0155 # Chi-squared value (total) + 36 21 0.0000 # Chi-squared value for no predicted signal (mu=0) + 37 1 130166685 # Analysis ID + 37 2 ||arXiv:1301.6668|| # Reference to publication + 37 3 ||(ppbar)->Vh->Vbb|| # Description (Search channel) + 37 4 1.96 # Center-of-mass energy + 37 5 9.70 # Luminosity + 37 6 6.00 # Luminosity uncertainty (in %) + 37 7 20.00 # Mass resolution (GeV) + 37 8 125.00 # Mass value at peak position (in GeV) + 37 9 1.7200 # Observed signal strength modifier (mu) + 37 10 0.8700 # Lower 68%C.L. uncertainty on observed mu + 37 11 0.9200 # Upper 68%C.L. uncertainty on observed mu + 37 12 001 # Assigned Higgs combination + 37 13 1 # Index of dominant Higgs boson + 37 14 25 # pdg number of dominant Higgs boson + 37 15 122.6512 # Mass of dominant Higgs boson + 37 16 1.1325 # Signal strength modifier of dominant Higgs boson + 37 17 1.1325 # Total predicted signal strength modifier mu + 37 18 0.4461 # Chi-squared value (mu-part) + 37 19 0.0000 # Chi-squared value (mh-part) + 37 20 0.4461 # Chi-squared value (total) + 37 21 3.9140 # Chi-squared value for no predicted signal (mu=0) + 38 1 130166681 # Analysis ID + 38 2 ||arXiv:1301.6668|| # Reference to publication + 38 3 ||(ppbar)->tth->ttbb|| # Description (Search channel) + 38 4 1.96 # Center-of-mass energy + 38 5 9.70 # Luminosity + 38 6 6.00 # Luminosity uncertainty (in %) + 38 7 30.00 # Mass resolution (GeV) + 38 8 125.00 # Mass value at peak position (in GeV) + 38 9 9.4900 # Observed signal strength modifier (mu) + 38 10 6.2800 # Lower 68%C.L. uncertainty on observed mu + 38 11 6.6000 # Upper 68%C.L. uncertainty on observed mu + 38 12 001 # Assigned Higgs combination + 38 13 1 # Index of dominant Higgs boson + 38 14 25 # pdg number of dominant Higgs boson + 38 15 122.6512 # Mass of dominant Higgs boson + 38 16 1.1282 # Signal strength modifier of dominant Higgs boson + 38 17 1.1282 # Total predicted signal strength modifier mu + 38 18 1.7717 # Chi-squared value (mu-part) + 38 19 0.0000 # Chi-squared value (mh-part) + 38 20 1.7717 # Chi-squared value (total) + 38 21 2.3432 # Chi-squared value for no predicted signal (mu=0) + 39 1 131211291 # Analysis ID + 39 2 ||arXiv:1312.1129|| # Reference to publication + 39 3 ||(pp)->h->WW->2l2nu(0/1jet)|| # Description (Search channel) + 39 4 8.00 # Center-of-mass energy + 39 5 25.30 # Luminosity + 39 6 2.60 # Luminosity uncertainty (in %) + 39 7 20.00 # Mass resolution (GeV) + 39 8 125.60 # Mass value at peak position (in GeV) + 39 9 0.7400 # Observed signal strength modifier (mu) + 39 10 0.2000 # Lower 68%C.L. uncertainty on observed mu + 39 11 0.2200 # Upper 68%C.L. uncertainty on observed mu + 39 12 001 # Assigned Higgs combination + 39 13 1 # Index of dominant Higgs boson + 39 14 25 # pdg number of dominant Higgs boson + 39 15 122.6512 # Mass of dominant Higgs boson + 39 16 0.7238 # Signal strength modifier of dominant Higgs boson + 39 17 0.7238 # Total predicted signal strength modifier mu + 39 18 -0.0368 # Chi-squared value (mu-part) + 39 19 0.0000 # Chi-squared value (mh-part) + 39 20 -0.0368 # Chi-squared value (total) + 39 21 13.8348 # Chi-squared value for no predicted signal (mu=0) + 40 1 131211292 # Analysis ID + 40 2 ||arXiv:1312.1129|| # Reference to publication + 40 3 ||(pp)->h->WW->2l2nu(VBF)|| # Description (Search channel) + 40 4 8.00 # Center-of-mass energy + 40 5 25.30 # Luminosity + 40 6 2.60 # Luminosity uncertainty (in %) + 40 7 20.00 # Mass resolution (GeV) + 40 8 125.60 # Mass value at peak position (in GeV) + 40 9 0.6000 # Observed signal strength modifier (mu) + 40 10 0.4600 # Lower 68%C.L. uncertainty on observed mu + 40 11 0.5700 # Upper 68%C.L. uncertainty on observed mu + 40 12 001 # Assigned Higgs combination + 40 13 1 # Index of dominant Higgs boson + 40 14 25 # pdg number of dominant Higgs boson + 40 15 122.6512 # Mass of dominant Higgs boson + 40 16 0.8080 # Signal strength modifier of dominant Higgs boson + 40 17 0.8080 # Total predicted signal strength modifier mu + 40 18 0.1628 # Chi-squared value (mu-part) + 40 19 0.0000 # Chi-squared value (mh-part) + 40 20 0.1628 # Chi-squared value (total) + 40 21 1.6969 # Chi-squared value for no predicted signal (mu=0) + 41 1 1400901 # Analysis ID + 41 2 ||CMS-PAS-HIG-14-009,arXiv:1312.5353|| # Reference to publication + 41 3 ||(pp)->h->ZZ->4l(0/1jet)|| # Description (Search channel) + 41 4 8.00 # Center-of-mass energy + 41 5 24.70 # Luminosity + 41 6 2.80 # Luminosity uncertainty (in %) + 41 7 0.45 # Mass resolution (GeV) + 41 8 125.63 # Mass value at peak position (in GeV) + 41 9 0.8830 # Observed signal strength modifier (mu) + 41 10 0.2720 # Lower 68%C.L. uncertainty on observed mu + 41 11 0.3360 # Upper 68%C.L. uncertainty on observed mu + 41 12 000 # Assigned Higgs combination + 41 13 0 # Index of dominant Higgs boson + 41 14 NaN # pdg number of dominant Higgs boson + 41 15 NaN # Mass of the dominant Higgs boson + 41 16 NaN # Signal strength modifier of the dominant Higgs boson + 41 17 0.0000 # Total predicted signal strength modifier mu + 41 18 11.7565 # Chi-squared value (mu-part) + 41 19 0.0000 # Chi-squared value (mh-part) + 41 20 11.7565 # Chi-squared value (total) + 41 21 11.7565 # Chi-squared value for no predicted signal (mu=0) + 42 1 1400902 # Analysis ID + 42 2 ||CMS-PAS-HIG-14-009,arXiv:1312.5353|| # Reference to publication + 42 3 ||(pp)->h->ZZ->4l(2jet)|| # Description (Search channel) + 42 4 8.00 # Center-of-mass energy + 42 5 24.70 # Luminosity + 42 6 4.40 # Luminosity uncertainty (in %) + 42 7 2.00 # Mass resolution (GeV) + 42 8 125.00 # Mass value at peak position (in GeV) + 42 9 1.5490 # Observed signal strength modifier (mu) + 42 10 0.6610 # Lower 68%C.L. uncertainty on observed mu + 42 11 0.9530 # Upper 68%C.L. uncertainty on observed mu + 42 12 000 # Assigned Higgs combination + 42 13 0 # Index of dominant Higgs boson + 42 14 NaN # pdg number of dominant Higgs boson + 42 15 NaN # Mass of the dominant Higgs boson + 42 16 NaN # Signal strength modifier of the dominant Higgs boson + 42 17 0.0000 # Total predicted signal strength modifier mu + 42 18 5.7125 # Chi-squared value (mu-part) + 42 19 0.0000 # Chi-squared value (mh-part) + 42 20 5.7125 # Chi-squared value (total) + 42 21 5.7125 # Chi-squared value for no predicted signal (mu=0) + 43 1 55805 # Analysis ID + 43 2 ||arXiv:1407.0558|| # Reference to publication + 43 3 ||(pp)->h->gammagamma(VBFdijet0)|| # Description (Search channel) + 43 4 7.00 # Center-of-mass energy + 43 5 5.10 # Luminosity + 43 6 2.20 # Luminosity uncertainty (in %) + 43 7 2.00 # Mass resolution (GeV) + 43 8 124.70 # Mass value at peak position (in GeV) + 43 9 4.8470 # Observed signal strength modifier (mu) + 43 10 1.7590 # Lower 68%C.L. uncertainty on observed mu + 43 11 2.1700 # Upper 68%C.L. uncertainty on observed mu + 43 12 001 # Assigned Higgs combination + 43 13 1 # Index of dominant Higgs boson + 43 14 25 # pdg number of dominant Higgs boson + 43 15 122.6512 # Mass of dominant Higgs boson + 43 16 0.7296 # Signal strength modifier of dominant Higgs boson + 43 17 0.7296 # Total predicted signal strength modifier mu + 43 18 4.9779 # Chi-squared value (mu-part) + 43 19 0.0000 # Chi-squared value (mh-part) + 43 20 4.9779 # Chi-squared value (total) + 43 21 7.7092 # Chi-squared value for no predicted signal (mu=0) + 44 1 55816 # Analysis ID + 44 2 ||arXiv:1407.0558|| # Reference to publication + 44 3 ||(pp)->h->gammagamma(VBFdijet0)|| # Description (Search channel) + 44 4 8.00 # Center-of-mass energy + 44 5 19.60 # Luminosity + 44 6 2.60 # Luminosity uncertainty (in %) + 44 7 2.00 # Mass resolution (GeV) + 44 8 124.70 # Mass value at peak position (in GeV) + 44 9 0.8170 # Observed signal strength modifier (mu) + 44 10 0.5780 # Lower 68%C.L. uncertainty on observed mu + 44 11 0.7520 # Upper 68%C.L. uncertainty on observed mu + 44 12 001 # Assigned Higgs combination + 44 13 1 # Index of dominant Higgs boson + 44 14 25 # pdg number of dominant Higgs boson + 44 15 122.6512 # Mass of dominant Higgs boson + 44 16 0.7323 # Signal strength modifier of dominant Higgs boson + 44 17 0.7323 # Total predicted signal strength modifier mu + 44 18 0.0210 # Chi-squared value (mu-part) + 44 19 0.0000 # Chi-squared value (mh-part) + 44 20 0.0210 # Chi-squared value (total) + 44 21 1.9996 # Chi-squared value for no predicted signal (mu=0) + 45 1 55806 # Analysis ID + 45 2 ||arXiv:1407.0558|| # Reference to publication + 45 3 ||(pp)->h->gammagamma(VBFdijet1)|| # Description (Search channel) + 45 4 7.00 # Center-of-mass energy + 45 5 5.10 # Luminosity + 45 6 2.20 # Luminosity uncertainty (in %) + 45 7 2.00 # Mass resolution (GeV) + 45 8 124.70 # Mass value at peak position (in GeV) + 45 9 2.6000 # Observed signal strength modifier (mu) + 45 10 1.7570 # Lower 68%C.L. uncertainty on observed mu + 45 11 2.1610 # Upper 68%C.L. uncertainty on observed mu + 45 12 001 # Assigned Higgs combination + 45 13 1 # Index of dominant Higgs boson + 45 14 25 # pdg number of dominant Higgs boson + 45 15 122.6512 # Mass of dominant Higgs boson + 45 16 0.7059 # Signal strength modifier of dominant Higgs boson + 45 17 0.7059 # Total predicted signal strength modifier mu + 45 18 0.8235 # Chi-squared value (mu-part) + 45 19 0.0000 # Chi-squared value (mh-part) + 45 20 0.8235 # Chi-squared value (total) + 45 21 2.2027 # Chi-squared value for no predicted signal (mu=0) + 46 1 55817 # Analysis ID + 46 2 ||arXiv:1407.0558|| # Reference to publication + 46 3 ||(pp)->h->gammagamma(VBFdijet1)|| # Description (Search channel) + 46 4 8.00 # Center-of-mass energy + 46 5 19.60 # Luminosity + 46 6 2.60 # Luminosity uncertainty (in %) + 46 7 2.00 # Mass resolution (GeV) + 46 8 124.70 # Mass value at peak position (in GeV) + 46 9 -0.2090 # Observed signal strength modifier (mu) + 46 10 0.6890 # Lower 68%C.L. uncertainty on observed mu + 46 11 0.7460 # Upper 68%C.L. uncertainty on observed mu + 46 12 001 # Assigned Higgs combination + 46 13 1 # Index of dominant Higgs boson + 46 14 25 # pdg number of dominant Higgs boson + 46 15 122.6512 # Mass of dominant Higgs boson + 46 16 0.7190 # Signal strength modifier of dominant Higgs boson + 46 17 0.7190 # Total predicted signal strength modifier mu + 46 18 1.7417 # Chi-squared value (mu-part) + 46 19 0.0000 # Chi-squared value (mh-part) + 46 20 1.7417 # Chi-squared value (total) + 46 21 0.0783 # Chi-squared value for no predicted signal (mu=0) + 47 1 55818 # Analysis ID + 47 2 ||arXiv:1407.0558|| # Reference to publication + 47 3 ||(pp)->h->gammagamma(VBFdijet2)|| # Description (Search channel) + 47 4 8.00 # Center-of-mass energy + 47 5 19.60 # Luminosity + 47 6 2.60 # Luminosity uncertainty (in %) + 47 7 2.00 # Mass resolution (GeV) + 47 8 124.70 # Mass value at peak position (in GeV) + 47 9 2.5960 # Observed signal strength modifier (mu) + 47 10 0.9940 # Lower 68%C.L. uncertainty on observed mu + 47 11 1.3260 # Upper 68%C.L. uncertainty on observed mu + 47 12 001 # Assigned Higgs combination + 47 13 1 # Index of dominant Higgs boson + 47 14 25 # pdg number of dominant Higgs boson + 47 15 122.6512 # Mass of dominant Higgs boson + 47 16 0.7002 # Signal strength modifier of dominant Higgs boson + 47 17 0.7002 # Total predicted signal strength modifier mu + 47 18 3.5791 # Chi-squared value (mu-part) + 47 19 0.0000 # Chi-squared value (mh-part) + 47 20 3.5791 # Chi-squared value (total) + 47 21 6.9631 # Chi-squared value for no predicted signal (mu=0) + 48 1 55808 # Analysis ID + 48 2 ||arXiv:1407.0558|| # Reference to publication + 48 3 ||(pp)->h->gammagamma(VHETmiss)|| # Description (Search channel) + 48 4 7.00 # Center-of-mass energy + 48 5 5.10 # Luminosity + 48 6 2.20 # Luminosity uncertainty (in %) + 48 7 2.00 # Mass resolution (GeV) + 48 8 124.70 # Mass value at peak position (in GeV) + 48 9 4.3240 # Observed signal strength modifier (mu) + 48 10 4.1520 # Lower 68%C.L. uncertainty on observed mu + 48 11 6.7180 # Upper 68%C.L. uncertainty on observed mu + 48 12 001 # Assigned Higgs combination + 48 13 1 # Index of dominant Higgs boson + 48 14 25 # pdg number of dominant Higgs boson + 48 15 122.6512 # Mass of dominant Higgs boson + 48 16 0.7482 # Signal strength modifier of dominant Higgs boson + 48 17 0.7482 # Total predicted signal strength modifier mu + 48 18 0.7140 # Chi-squared value (mu-part) + 48 19 0.0000 # Chi-squared value (mh-part) + 48 20 0.7140 # Chi-squared value (total) + 48 21 1.0860 # Chi-squared value for no predicted signal (mu=0) + 49 1 55821 # Analysis ID + 49 2 ||arXiv:1407.0558|| # Reference to publication + 49 3 ||(pp)->h->gammagamma(VHETmiss)|| # Description (Search channel) + 49 4 8.00 # Center-of-mass energy + 49 5 19.60 # Luminosity + 49 6 2.60 # Luminosity uncertainty (in %) + 49 7 2.00 # Mass resolution (GeV) + 49 8 124.70 # Mass value at peak position (in GeV) + 49 9 0.0760 # Observed signal strength modifier (mu) + 49 10 1.2770 # Lower 68%C.L. uncertainty on observed mu + 49 11 1.8620 # Upper 68%C.L. uncertainty on observed mu + 49 12 001 # Assigned Higgs combination + 49 13 1 # Index of dominant Higgs boson + 49 14 25 # pdg number of dominant Higgs boson + 49 15 122.6512 # Mass of dominant Higgs boson + 49 16 0.7341 # Signal strength modifier of dominant Higgs boson + 49 17 0.7341 # Total predicted signal strength modifier mu + 49 18 0.1268 # Chi-squared value (mu-part) + 49 19 0.0000 # Chi-squared value (mh-part) + 49 20 0.1268 # Chi-squared value (total) + 49 21 0.0035 # Chi-squared value for no predicted signal (mu=0) + 50 1 55809 # Analysis ID + 50 2 ||arXiv:1407.0558|| # Reference to publication + 50 3 ||(pp)->h->gammagamma(VHdijet)|| # Description (Search channel) + 50 4 7.00 # Center-of-mass energy + 50 5 5.10 # Luminosity + 50 6 2.20 # Luminosity uncertainty (in %) + 50 7 2.00 # Mass resolution (GeV) + 50 8 124.70 # Mass value at peak position (in GeV) + 50 9 7.8550 # Observed signal strength modifier (mu) + 50 10 6.3990 # Lower 68%C.L. uncertainty on observed mu + 50 11 8.8550 # Upper 68%C.L. uncertainty on observed mu + 50 12 001 # Assigned Higgs combination + 50 13 1 # Index of dominant Higgs boson + 50 14 25 # pdg number of dominant Higgs boson + 50 15 122.6512 # Mass of dominant Higgs boson + 50 16 0.7197 # Signal strength modifier of dominant Higgs boson + 50 17 0.7197 # Total predicted signal strength modifier mu + 50 18 1.1501 # Chi-squared value (mu-part) + 50 19 0.0000 # Chi-squared value (mh-part) + 50 20 1.1501 # Chi-squared value (total) + 50 21 1.5109 # Chi-squared value for no predicted signal (mu=0) + 51 1 55822 # Analysis ID + 51 2 ||arXiv:1407.0558|| # Reference to publication + 51 3 ||(pp)->h->gammagamma(VHdijet)|| # Description (Search channel) + 51 4 8.00 # Center-of-mass energy + 51 5 19.60 # Luminosity + 51 6 2.60 # Luminosity uncertainty (in %) + 51 7 2.00 # Mass resolution (GeV) + 51 8 124.70 # Mass value at peak position (in GeV) + 51 9 0.3920 # Observed signal strength modifier (mu) + 51 10 1.4820 # Lower 68%C.L. uncertainty on observed mu + 51 11 2.1580 # Upper 68%C.L. uncertainty on observed mu + 51 12 001 # Assigned Higgs combination + 51 13 1 # Index of dominant Higgs boson + 51 14 25 # pdg number of dominant Higgs boson + 51 15 122.6512 # Mass of dominant Higgs boson + 51 16 0.7175 # Signal strength modifier of dominant Higgs boson + 51 17 0.7175 # Total predicted signal strength modifier mu + 51 18 0.0270 # Chi-squared value (mu-part) + 51 19 0.0000 # Chi-squared value (mh-part) + 51 20 0.0270 # Chi-squared value (total) + 51 21 0.0699 # Chi-squared value for no predicted signal (mu=0) + 52 1 55807 # Analysis ID + 52 2 ||arXiv:1407.0558|| # Reference to publication + 52 3 ||(pp)->h->gammagamma(VHloose)|| # Description (Search channel) + 52 4 7.00 # Center-of-mass energy + 52 5 5.10 # Luminosity + 52 6 2.20 # Luminosity uncertainty (in %) + 52 7 2.00 # Mass resolution (GeV) + 52 8 124.70 # Mass value at peak position (in GeV) + 52 9 3.1000 # Observed signal strength modifier (mu) + 52 10 5.3420 # Lower 68%C.L. uncertainty on observed mu + 52 11 8.2890 # Upper 68%C.L. uncertainty on observed mu + 52 12 001 # Assigned Higgs combination + 52 13 1 # Index of dominant Higgs boson + 52 14 25 # pdg number of dominant Higgs boson + 52 15 122.6512 # Mass of dominant Higgs boson + 52 16 0.7497 # Signal strength modifier of dominant Higgs boson + 52 17 0.7497 # Total predicted signal strength modifier mu + 52 18 0.1854 # Chi-squared value (mu-part) + 52 19 0.0000 # Chi-squared value (mh-part) + 52 20 0.1854 # Chi-squared value (total) + 52 21 0.3369 # Chi-squared value for no predicted signal (mu=0) + 53 1 55820 # Analysis ID + 53 2 ||arXiv:1407.0558|| # Reference to publication + 53 3 ||(pp)->h->gammagamma(VHloose)|| # Description (Search channel) + 53 4 8.00 # Center-of-mass energy + 53 5 19.60 # Luminosity + 53 6 2.60 # Luminosity uncertainty (in %) + 53 7 2.00 # Mass resolution (GeV) + 53 8 124.70 # Mass value at peak position (in GeV) + 53 9 1.2430 # Observed signal strength modifier (mu) + 53 10 2.6240 # Lower 68%C.L. uncertainty on observed mu + 53 11 3.6940 # Upper 68%C.L. uncertainty on observed mu + 53 12 001 # Assigned Higgs combination + 53 13 1 # Index of dominant Higgs boson + 53 14 25 # pdg number of dominant Higgs boson + 53 15 122.6512 # Mass of dominant Higgs boson + 53 16 0.7510 # Signal strength modifier of dominant Higgs boson + 53 17 0.7510 # Total predicted signal strength modifier mu + 53 18 0.0326 # Chi-squared value (mu-part) + 53 19 0.0000 # Chi-squared value (mh-part) + 53 20 0.0326 # Chi-squared value (total) + 53 21 0.2244 # Chi-squared value for no predicted signal (mu=0) + 54 1 55819 # Analysis ID + 54 2 ||arXiv:1407.0558|| # Reference to publication + 54 3 ||(pp)->h->gammagamma(VHtight)|| # Description (Search channel) + 54 4 8.00 # Center-of-mass energy + 54 5 19.60 # Luminosity + 54 6 2.60 # Luminosity uncertainty (in %) + 54 7 2.00 # Mass resolution (GeV) + 54 8 124.70 # Mass value at peak position (in GeV) + 54 9 -0.3430 # Observed signal strength modifier (mu) + 54 10 0.6290 # Lower 68%C.L. uncertainty on observed mu + 54 11 1.3000 # Upper 68%C.L. uncertainty on observed mu + 54 12 001 # Assigned Higgs combination + 54 13 1 # Index of dominant Higgs boson + 54 14 25 # pdg number of dominant Higgs boson + 54 15 122.6512 # Mass of dominant Higgs boson + 54 16 0.7539 # Signal strength modifier of dominant Higgs boson + 54 17 0.7539 # Total predicted signal strength modifier mu + 54 18 0.7800 # Chi-squared value (mu-part) + 54 19 0.0000 # Chi-squared value (mh-part) + 54 20 0.7800 # Chi-squared value (total) + 54 21 0.0696 # Chi-squared value for no predicted signal (mu=0) + 55 1 55824 # Analysis ID + 55 2 ||arXiv:1407.0558|| # Reference to publication + 55 3 ||(pp)->h->gammagamma(ttHmultijet)|| # Description (Search channel) + 55 4 8.00 # Center-of-mass energy + 55 5 19.60 # Luminosity + 55 6 2.60 # Luminosity uncertainty (in %) + 55 7 2.00 # Mass resolution (GeV) + 55 8 124.70 # Mass value at peak position (in GeV) + 55 9 1.2430 # Observed signal strength modifier (mu) + 55 10 2.6970 # Lower 68%C.L. uncertainty on observed mu + 55 11 4.2350 # Upper 68%C.L. uncertainty on observed mu + 55 12 001 # Assigned Higgs combination + 55 13 1 # Index of dominant Higgs boson + 55 14 25 # pdg number of dominant Higgs boson + 55 15 122.6512 # Mass of dominant Higgs boson + 55 16 0.7466 # Signal strength modifier of dominant Higgs boson + 55 17 0.7466 # Total predicted signal strength modifier mu + 55 18 0.0260 # Chi-squared value (mu-part) + 55 19 0.0000 # Chi-squared value (mh-part) + 55 20 0.0260 # Chi-squared value (total) + 55 21 0.2127 # Chi-squared value for no predicted signal (mu=0) + 56 1 55823 # Analysis ID + 56 2 ||arXiv:1407.0558|| # Reference to publication + 56 3 ||(pp)->h->gammagamma(ttHlepton)|| # Description (Search channel) + 56 4 8.00 # Center-of-mass energy + 56 5 19.60 # Luminosity + 56 6 2.60 # Luminosity uncertainty (in %) + 56 7 2.00 # Mass resolution (GeV) + 56 8 124.70 # Mass value at peak position (in GeV) + 56 9 3.5210 # Observed signal strength modifier (mu) + 56 10 2.4500 # Lower 68%C.L. uncertainty on observed mu + 56 11 3.8920 # Upper 68%C.L. uncertainty on observed mu + 56 12 001 # Assigned Higgs combination + 56 13 1 # Index of dominant Higgs boson + 56 14 25 # pdg number of dominant Higgs boson + 56 15 122.6512 # Mass of dominant Higgs boson + 56 16 0.7515 # Signal strength modifier of dominant Higgs boson + 56 17 0.7515 # Total predicted signal strength modifier mu + 56 18 0.7705 # Chi-squared value (mu-part) + 56 19 0.0000 # Chi-squared value (mh-part) + 56 20 0.7705 # Chi-squared value (total) + 56 21 2.1101 # Chi-squared value for no predicted signal (mu=0) + 57 1 55810 # Analysis ID + 57 2 ||arXiv:1407.0558|| # Reference to publication + 57 3 ||(pp)->h->gammagamma(ttHtags)|| # Description (Search channel) + 57 4 7.00 # Center-of-mass energy + 57 5 5.10 # Luminosity + 57 6 2.20 # Luminosity uncertainty (in %) + 57 7 2.00 # Mass resolution (GeV) + 57 8 124.70 # Mass value at peak position (in GeV) + 57 9 0.7140 # Observed signal strength modifier (mu) + 57 10 3.5630 # Lower 68%C.L. uncertainty on observed mu + 57 11 6.1970 # Upper 68%C.L. uncertainty on observed mu + 57 12 001 # Assigned Higgs combination + 57 13 1 # Index of dominant Higgs boson + 57 14 25 # pdg number of dominant Higgs boson + 57 15 122.6512 # Mass of dominant Higgs boson + 57 16 0.7465 # Signal strength modifier of dominant Higgs boson + 57 17 0.7465 # Total predicted signal strength modifier mu + 57 18 0.0001 # Chi-squared value (mu-part) + 57 19 0.0000 # Chi-squared value (mh-part) + 57 20 0.0001 # Chi-squared value (total) + 57 21 0.0402 # Chi-squared value for no predicted signal (mu=0) + 58 1 55801 # Analysis ID + 58 2 ||arXiv:1407.0558|| # Reference to publication + 58 3 ||(pp)->h->gammagamma(untagged0)|| # Description (Search channel) + 58 4 7.00 # Center-of-mass energy + 58 5 5.10 # Luminosity + 58 6 2.20 # Luminosity uncertainty (in %) + 58 7 2.00 # Mass resolution (GeV) + 58 8 124.70 # Mass value at peak position (in GeV) + 58 9 1.9730 # Observed signal strength modifier (mu) + 58 10 1.2500 # Lower 68%C.L. uncertainty on observed mu + 58 11 1.5050 # Upper 68%C.L. uncertainty on observed mu + 58 12 001 # Assigned Higgs combination + 58 13 1 # Index of dominant Higgs boson + 58 14 25 # pdg number of dominant Higgs boson + 58 15 122.6512 # Mass of dominant Higgs boson + 58 16 0.6551 # Signal strength modifier of dominant Higgs boson + 58 17 0.6551 # Total predicted signal strength modifier mu + 58 18 1.1027 # Chi-squared value (mu-part) + 58 19 0.0000 # Chi-squared value (mh-part) + 58 20 1.1027 # Chi-squared value (total) + 58 21 2.5354 # Chi-squared value for no predicted signal (mu=0) + 59 1 55811 # Analysis ID + 59 2 ||arXiv:1407.0558|| # Reference to publication + 59 3 ||(pp)->h->gammagamma(untagged0)|| # Description (Search channel) + 59 4 8.00 # Center-of-mass energy + 59 5 19.60 # Luminosity + 59 6 2.60 # Luminosity uncertainty (in %) + 59 7 2.00 # Mass resolution (GeV) + 59 8 124.70 # Mass value at peak position (in GeV) + 59 9 0.1300 # Observed signal strength modifier (mu) + 59 10 0.7440 # Lower 68%C.L. uncertainty on observed mu + 59 11 1.0940 # Upper 68%C.L. uncertainty on observed mu + 59 12 001 # Assigned Higgs combination + 59 13 1 # Index of dominant Higgs boson + 59 14 25 # pdg number of dominant Higgs boson + 59 15 122.6512 # Mass of dominant Higgs boson + 59 16 0.6614 # Signal strength modifier of dominant Higgs boson + 59 17 0.6614 # Total predicted signal strength modifier mu + 59 18 0.2608 # Chi-squared value (mu-part) + 59 19 0.0000 # Chi-squared value (mh-part) + 59 20 0.2608 # Chi-squared value (total) + 59 21 0.0304 # Chi-squared value for no predicted signal (mu=0) + 60 1 55802 # Analysis ID + 60 2 ||arXiv:1407.0558|| # Reference to publication + 60 3 ||(pp)->h->gammagamma(untagged1)|| # Description (Search channel) + 60 4 7.00 # Center-of-mass energy + 60 5 5.10 # Luminosity + 60 6 2.20 # Luminosity uncertainty (in %) + 60 7 2.00 # Mass resolution (GeV) + 60 8 124.70 # Mass value at peak position (in GeV) + 60 9 1.2330 # Observed signal strength modifier (mu) + 60 10 0.8800 # Lower 68%C.L. uncertainty on observed mu + 60 11 0.9790 # Upper 68%C.L. uncertainty on observed mu + 60 12 001 # Assigned Higgs combination + 60 13 1 # Index of dominant Higgs boson + 60 14 25 # pdg number of dominant Higgs boson + 60 15 122.6512 # Mass of dominant Higgs boson + 60 16 0.6409 # Signal strength modifier of dominant Higgs boson + 60 17 0.6409 # Total predicted signal strength modifier mu + 60 18 0.4920 # Chi-squared value (mu-part) + 60 19 0.0000 # Chi-squared value (mh-part) + 60 20 0.4920 # Chi-squared value (total) + 60 21 1.9918 # Chi-squared value for no predicted signal (mu=0) + 61 1 55812 # Analysis ID + 61 2 ||arXiv:1407.0558|| # Reference to publication + 61 3 ||(pp)->h->gammagamma(untagged1)|| # Description (Search channel) + 61 4 8.00 # Center-of-mass energy + 61 5 19.60 # Luminosity + 61 6 2.60 # Luminosity uncertainty (in %) + 61 7 2.00 # Mass resolution (GeV) + 61 8 124.70 # Mass value at peak position (in GeV) + 61 9 0.9190 # Observed signal strength modifier (mu) + 61 10 0.4870 # Lower 68%C.L. uncertainty on observed mu + 61 11 0.5670 # Upper 68%C.L. uncertainty on observed mu + 61 12 001 # Assigned Higgs combination + 61 13 1 # Index of dominant Higgs boson + 61 14 25 # pdg number of dominant Higgs boson + 61 15 122.6512 # Mass of dominant Higgs boson + 61 16 0.6498 # Signal strength modifier of dominant Higgs boson + 61 17 0.6498 # Total predicted signal strength modifier mu + 61 18 0.3071 # Chi-squared value (mu-part) + 61 19 0.0000 # Chi-squared value (mh-part) + 61 20 0.3071 # Chi-squared value (total) + 61 21 3.6185 # Chi-squared value for no predicted signal (mu=0) + 62 1 55803 # Analysis ID + 62 2 ||arXiv:1407.0558|| # Reference to publication + 62 3 ||(pp)->h->gammagamma(untagged2)|| # Description (Search channel) + 62 4 7.00 # Center-of-mass energy + 62 5 5.10 # Luminosity + 62 6 2.20 # Luminosity uncertainty (in %) + 62 7 2.00 # Mass resolution (GeV) + 62 8 124.70 # Mass value at peak position (in GeV) + 62 9 1.6020 # Observed signal strength modifier (mu) + 62 10 1.1740 # Lower 68%C.L. uncertainty on observed mu + 62 11 1.2460 # Upper 68%C.L. uncertainty on observed mu + 62 12 001 # Assigned Higgs combination + 62 13 1 # Index of dominant Higgs boson + 62 14 25 # pdg number of dominant Higgs boson + 62 15 122.6512 # Mass of dominant Higgs boson + 62 16 0.6409 # Signal strength modifier of dominant Higgs boson + 62 17 0.6409 # Total predicted signal strength modifier mu + 62 18 0.7360 # Chi-squared value (mu-part) + 62 19 0.0000 # Chi-squared value (mh-part) + 62 20 0.7360 # Chi-squared value (total) + 62 21 1.8916 # Chi-squared value for no predicted signal (mu=0) + 63 1 55813 # Analysis ID + 63 2 ||arXiv:1407.0558|| # Reference to publication + 63 3 ||(pp)->h->gammagamma(untagged2)|| # Description (Search channel) + 63 4 8.00 # Center-of-mass energy + 63 5 19.60 # Luminosity + 63 6 2.60 # Luminosity uncertainty (in %) + 63 7 0.34 # Mass resolution (GeV) + 63 8 124.70 # Mass value at peak position (in GeV) + 63 9 1.1020 # Observed signal strength modifier (mu) + 63 10 0.4400 # Lower 68%C.L. uncertainty on observed mu + 63 11 0.4770 # Upper 68%C.L. uncertainty on observed mu + 63 12 001 # Assigned Higgs combination + 63 13 1 # Index of dominant Higgs boson + 63 14 25 # pdg number of dominant Higgs boson + 63 15 122.6512 # Mass of dominant Higgs boson + 63 16 0.6424 # Signal strength modifier of dominant Higgs boson + 63 17 0.6424 # Total predicted signal strength modifier mu + 63 18 1.0171 # Chi-squared value (mu-part) + 63 19 1.7091 # Chi-squared value (mh-part) + 63 20 2.7261 # Chi-squared value (total) + 63 21 6.5393 # Chi-squared value for no predicted signal (mu=0) + 64 1 55804 # Analysis ID + 64 2 ||arXiv:1407.0558|| # Reference to publication + 64 3 ||(pp)->h->gammagamma(untagged3)|| # Description (Search channel) + 64 4 7.00 # Center-of-mass energy + 64 5 5.10 # Luminosity + 64 6 2.20 # Luminosity uncertainty (in %) + 64 7 2.00 # Mass resolution (GeV) + 64 8 124.70 # Mass value at peak position (in GeV) + 64 9 2.6120 # Observed signal strength modifier (mu) + 64 10 1.6530 # Lower 68%C.L. uncertainty on observed mu + 64 11 1.7380 # Upper 68%C.L. uncertainty on observed mu + 64 12 001 # Assigned Higgs combination + 64 13 1 # Index of dominant Higgs boson + 64 14 25 # pdg number of dominant Higgs boson + 64 15 122.6512 # Mass of dominant Higgs boson + 64 16 0.6406 # Signal strength modifier of dominant Higgs boson + 64 17 0.6406 # Total predicted signal strength modifier mu + 64 18 1.4480 # Chi-squared value (mu-part) + 64 19 0.0000 # Chi-squared value (mh-part) + 64 20 1.4480 # Chi-squared value (total) + 64 21 2.5569 # Chi-squared value for no predicted signal (mu=0) + 65 1 55814 # Analysis ID + 65 2 ||arXiv:1407.0558|| # Reference to publication + 65 3 ||(pp)->h->gammagamma(untagged3)|| # Description (Search channel) + 65 4 8.00 # Center-of-mass energy + 65 5 19.60 # Luminosity + 65 6 2.60 # Luminosity uncertainty (in %) + 65 7 2.00 # Mass resolution (GeV) + 65 8 124.70 # Mass value at peak position (in GeV) + 65 9 0.6480 # Observed signal strength modifier (mu) + 65 10 0.8870 # Lower 68%C.L. uncertainty on observed mu + 65 11 0.6530 # Upper 68%C.L. uncertainty on observed mu + 65 12 001 # Assigned Higgs combination + 65 13 1 # Index of dominant Higgs boson + 65 14 25 # pdg number of dominant Higgs boson + 65 15 122.6512 # Mass of dominant Higgs boson + 65 16 0.6420 # Signal strength modifier of dominant Higgs boson + 65 17 0.6420 # Total predicted signal strength modifier mu + 65 18 -0.0000 # Chi-squared value (mu-part) + 65 19 0.0000 # Chi-squared value (mh-part) + 65 20 -0.0000 # Chi-squared value (total) + 65 21 0.5338 # Chi-squared value for no predicted signal (mu=0) + 66 1 55815 # Analysis ID + 66 2 ||arXiv:1407.0558|| # Reference to publication + 66 3 ||(pp)->h->gammagamma(untagged4)|| # Description (Search channel) + 66 4 8.00 # Center-of-mass energy + 66 5 19.60 # Luminosity + 66 6 2.60 # Luminosity uncertainty (in %) + 66 7 2.00 # Mass resolution (GeV) + 66 8 124.70 # Mass value at peak position (in GeV) + 66 9 1.4570 # Observed signal strength modifier (mu) + 66 10 1.2380 # Lower 68%C.L. uncertainty on observed mu + 66 11 1.2890 # Upper 68%C.L. uncertainty on observed mu + 66 12 001 # Assigned Higgs combination + 66 13 1 # Index of dominant Higgs boson + 66 14 25 # pdg number of dominant Higgs boson + 66 15 122.6512 # Mass of dominant Higgs boson + 66 16 0.6400 # Signal strength modifier of dominant Higgs boson + 66 17 0.6400 # Total predicted signal strength modifier mu + 66 18 0.3777 # Chi-squared value (mu-part) + 66 19 0.0000 # Chi-squared value (mh-part) + 66 20 0.3777 # Chi-squared value (total) + 66 21 1.4010 # Chi-squared value for no predicted signal (mu=0) + 67 1 1300701 # Analysis ID + 67 2 ||CMS-PAS-HIG-13-007|| # Reference to publication + 67 3 ||(pp)->h->mumu|| # Description (Search channel) + 67 4 8.00 # Center-of-mass energy + 67 5 25.40 # Luminosity + 67 6 2.60 # Luminosity uncertainty (in %) + 67 7 2.00 # Mass resolution (GeV) + 67 8 125.70 # Mass value at peak position (in GeV) + 67 9 2.9000 # Observed signal strength modifier (mu) + 67 10 2.7000 # Lower 68%C.L. uncertainty on observed mu + 67 11 2.8000 # Upper 68%C.L. uncertainty on observed mu + 67 12 000 # Assigned Higgs combination + 67 13 0 # Index of dominant Higgs boson + 67 14 NaN # pdg number of dominant Higgs boson + 67 15 NaN # Mass of the dominant Higgs boson + 67 16 NaN # Signal strength modifier of the dominant Higgs boson + 67 17 0.0000 # Total predicted signal strength modifier mu + 67 18 1.1680 # Chi-squared value (mu-part) + 67 19 0.0000 # Chi-squared value (mh-part) + 67 20 1.1680 # Chi-squared value (total) + 67 21 1.1680 # Chi-squared value for no predicted signal (mu=0) + 68 1 1300401 # Analysis ID + 68 2 ||CMS-PAS-HIG-13-004|| # Reference to publication + 68 3 ||(pp)->h->tautau(0jet)|| # Description (Search channel) + 68 4 8.00 # Center-of-mass energy + 68 5 24.30 # Luminosity + 68 6 2.60 # Luminosity uncertainty (in %) + 68 7 25.00 # Mass resolution (GeV) + 68 8 125.00 # Mass value at peak position (in GeV) + 68 9 0.4000 # Observed signal strength modifier (mu) + 68 10 1.1300 # Lower 68%C.L. uncertainty on observed mu + 68 11 0.7300 # Upper 68%C.L. uncertainty on observed mu + 68 12 001 # Assigned Higgs combination + 68 13 1 # Index of dominant Higgs boson + 68 14 25 # pdg number of dominant Higgs boson + 68 15 122.6512 # Mass of dominant Higgs boson + 68 16 0.9686 # Signal strength modifier of dominant Higgs boson + 68 17 0.9686 # Total predicted signal strength modifier mu + 68 18 0.7388 # Chi-squared value (mu-part) + 68 19 0.0000 # Chi-squared value (mh-part) + 68 20 0.7388 # Chi-squared value (total) + 68 21 0.1244 # Chi-squared value for no predicted signal (mu=0) + 69 1 1300402 # Analysis ID + 69 2 ||CMS-PAS-HIG-13-004|| # Reference to publication + 69 3 ||(pp)->h->tautau(1jet)|| # Description (Search channel) + 69 4 8.00 # Center-of-mass energy + 69 5 24.30 # Luminosity + 69 6 2.60 # Luminosity uncertainty (in %) + 69 7 25.00 # Mass resolution (GeV) + 69 8 125.00 # Mass value at peak position (in GeV) + 69 9 1.0600 # Observed signal strength modifier (mu) + 69 10 0.4700 # Lower 68%C.L. uncertainty on observed mu + 69 11 0.4700 # Upper 68%C.L. uncertainty on observed mu + 69 12 001 # Assigned Higgs combination + 69 13 1 # Index of dominant Higgs boson + 69 14 25 # pdg number of dominant Higgs boson + 69 15 122.6512 # Mass of dominant Higgs boson + 69 16 1.0040 # Signal strength modifier of dominant Higgs boson + 69 17 1.0040 # Total predicted signal strength modifier mu + 69 18 -0.0184 # Chi-squared value (mu-part) + 69 19 0.0000 # Chi-squared value (mh-part) + 69 20 -0.0184 # Chi-squared value (total) + 69 21 5.1188 # Chi-squared value for no predicted signal (mu=0) + 70 1 1300404 # Analysis ID + 70 2 ||CMS-PAS-HIG-13-004|| # Reference to publication + 70 3 ||(pp)->h->tautau(VBF)|| # Description (Search channel) + 70 4 8.00 # Center-of-mass energy + 70 5 24.50 # Luminosity + 70 6 2.60 # Luminosity uncertainty (in %) + 70 7 20.00 # Mass resolution (GeV) + 70 8 125.00 # Mass value at peak position (in GeV) + 70 9 0.9300 # Observed signal strength modifier (mu) + 70 10 0.4100 # Lower 68%C.L. uncertainty on observed mu + 70 11 0.4100 # Upper 68%C.L. uncertainty on observed mu + 70 12 001 # Assigned Higgs combination + 70 13 1 # Index of dominant Higgs boson + 70 14 25 # pdg number of dominant Higgs boson + 70 15 122.6512 # Mass of dominant Higgs boson + 70 16 1.1139 # Signal strength modifier of dominant Higgs boson + 70 17 1.1139 # Total predicted signal strength modifier mu + 70 18 0.2735 # Chi-squared value (mu-part) + 70 19 0.0000 # Chi-squared value (mh-part) + 70 20 0.2735 # Chi-squared value (total) + 70 21 5.1208 # Chi-squared value for no predicted signal (mu=0) + 71 1 131211293 # Analysis ID + 71 2 ||arXiv:1312.1129|| # Reference to publication + 71 3 ||(pp)->h->WW->2l2nu(VH)|| # Description (Search channel) + 71 4 8.00 # Center-of-mass energy + 71 5 25.30 # Luminosity + 71 6 2.60 # Luminosity uncertainty (in %) + 71 7 20.00 # Mass resolution (GeV) + 71 8 125.60 # Mass value at peak position (in GeV) + 71 9 0.3900 # Observed signal strength modifier (mu) + 71 10 1.8700 # Lower 68%C.L. uncertainty on observed mu + 71 11 1.9700 # Upper 68%C.L. uncertainty on observed mu + 71 12 001 # Assigned Higgs combination + 71 13 1 # Index of dominant Higgs boson + 71 14 25 # pdg number of dominant Higgs boson + 71 15 122.6512 # Mass of dominant Higgs boson + 71 16 0.7597 # Signal strength modifier of dominant Higgs boson + 71 17 0.7597 # Total predicted signal strength modifier mu + 71 18 0.0412 # Chi-squared value (mu-part) + 71 19 0.0000 # Chi-squared value (mh-part) + 71 20 0.0412 # Chi-squared value (total) + 71 21 0.0435 # Chi-squared value for no predicted signal (mu=0) + 72 1 1301701 # Analysis ID + 72 2 ||CMS-PAS-HIG-13-017|| # Reference to publication + 72 3 ||(pp)->Vh->VWW(hadronicV)|| # Description (Search channel) + 72 4 8.00 # Center-of-mass energy + 72 5 25.40 # Luminosity + 72 6 4.40 # Luminosity uncertainty (in %) + 72 7 20.00 # Mass resolution (GeV) + 72 8 125.00 # Mass value at peak position (in GeV) + 72 9 1.0000 # Observed signal strength modifier (mu) + 72 10 2.0000 # Lower 68%C.L. uncertainty on observed mu + 72 11 2.0000 # Upper 68%C.L. uncertainty on observed mu + 72 12 001 # Assigned Higgs combination + 72 13 1 # Index of dominant Higgs boson + 72 14 25 # pdg number of dominant Higgs boson + 72 15 122.6512 # Mass of dominant Higgs boson + 72 16 0.7548 # Signal strength modifier of dominant Higgs boson + 72 17 0.7548 # Total predicted signal strength modifier mu + 72 18 0.0082 # Chi-squared value (mu-part) + 72 19 0.0000 # Chi-squared value (mh-part) + 72 20 0.0082 # Chi-squared value (total) + 72 21 0.2502 # Chi-squared value for no predicted signal (mu=0) + 73 1 1301201 # Analysis ID + 73 2 ||CMS-PAS-HIG-13-012|| # Reference to publication + 73 3 ||(pp)->Vh->Vbb|| # Description (Search channel) + 73 4 8.00 # Center-of-mass energy + 73 5 24.00 # Luminosity + 73 6 4.40 # Luminosity uncertainty (in %) + 73 7 12.50 # Mass resolution (GeV) + 73 8 125.70 # Mass value at peak position (in GeV) + 73 9 1.0000 # Observed signal strength modifier (mu) + 73 10 0.4857 # Lower 68%C.L. uncertainty on observed mu + 73 11 0.5070 # Upper 68%C.L. uncertainty on observed mu + 73 12 001 # Assigned Higgs combination + 73 13 1 # Index of dominant Higgs boson + 73 14 25 # pdg number of dominant Higgs boson + 73 15 122.6512 # Mass of dominant Higgs boson + 73 16 1.1325 # Signal strength modifier of dominant Higgs boson + 73 17 1.1325 # Total predicted signal strength modifier mu + 73 18 0.0923 # Chi-squared value (mu-part) + 73 19 0.0000 # Chi-squared value (mh-part) + 73 20 0.0923 # Chi-squared value (total) + 73 21 4.2236 # Chi-squared value for no predicted signal (mu=0) + 74 1 1300403 # Analysis ID + 74 2 ||CMS-PAS-HIG-13-004|| # Reference to publication + 74 3 ||(pp)->Vh->tautau|| # Description (Search channel) + 74 4 8.00 # Center-of-mass energy + 74 5 24.30 # Luminosity + 74 6 4.40 # Luminosity uncertainty (in %) + 74 7 20.00 # Mass resolution (GeV) + 74 8 125.70 # Mass value at peak position (in GeV) + 74 9 0.9810 # Observed signal strength modifier (mu) + 74 10 1.4960 # Lower 68%C.L. uncertainty on observed mu + 74 11 1.6800 # Upper 68%C.L. uncertainty on observed mu + 74 12 001 # Assigned Higgs combination + 74 13 1 # Index of dominant Higgs boson + 74 14 25 # pdg number of dominant Higgs boson + 74 15 122.6512 # Mass of dominant Higgs boson + 74 16 1.0871 # Signal strength modifier of dominant Higgs boson + 74 17 1.0871 # Total predicted signal strength modifier mu + 74 18 0.0064 # Chi-squared value (mu-part) + 74 19 0.0000 # Chi-squared value (mh-part) + 74 20 0.0064 # Chi-squared value (total) + 74 21 0.4298 # Chi-squared value for no predicted signal (mu=0) + 75 1 131211294 # Analysis ID + 75 2 ||arXiv:1312.1129|| # Reference to publication + 75 3 ||(pp)->h->WW->3l3nu(WH)|| # Description (Search channel) + 75 4 8.00 # Center-of-mass energy + 75 5 25.30 # Luminosity + 75 6 2.60 # Luminosity uncertainty (in %) + 75 7 20.00 # Mass resolution (GeV) + 75 8 125.60 # Mass value at peak position (in GeV) + 75 9 0.5600 # Observed signal strength modifier (mu) + 75 10 0.9500 # Lower 68%C.L. uncertainty on observed mu + 75 11 1.2700 # Upper 68%C.L. uncertainty on observed mu + 75 12 001 # Assigned Higgs combination + 75 13 1 # Index of dominant Higgs boson + 75 14 25 # pdg number of dominant Higgs boson + 75 15 122.6512 # Mass of dominant Higgs boson + 75 16 0.8413 # Signal strength modifier of dominant Higgs boson + 75 17 0.8413 # Total predicted signal strength modifier mu + 75 18 0.0534 # Chi-squared value (mu-part) + 75 19 0.0000 # Chi-squared value (mh-part) + 75 20 0.0534 # Chi-squared value (total) + 75 21 0.3473 # Chi-squared value for no predicted signal (mu=0) + 76 1 168204 # Analysis ID + 76 2 ||arXiv:1408.1682|| # Reference to publication + 76 3 ||(pp)->tth->2leptons(samesign)|| # Description (Search channel) + 76 4 8.00 # Center-of-mass energy + 76 5 19.60 # Luminosity + 76 6 2.60 # Luminosity uncertainty (in %) + 76 7 25.00 # Mass resolution (GeV) + 76 8 125.60 # Mass value at peak position (in GeV) + 76 9 5.3000 # Observed signal strength modifier (mu) + 76 10 1.8000 # Lower 68%C.L. uncertainty on observed mu + 76 11 2.1000 # Upper 68%C.L. uncertainty on observed mu + 76 12 001 # Assigned Higgs combination + 76 13 1 # Index of dominant Higgs boson + 76 14 25 # pdg number of dominant Higgs boson + 76 15 122.6512 # Mass of dominant Higgs boson + 76 16 0.9231 # Signal strength modifier of dominant Higgs boson + 76 17 0.9231 # Total predicted signal strength modifier mu + 76 18 6.1892 # Chi-squared value (mu-part) + 76 19 0.0000 # Chi-squared value (mh-part) + 76 20 6.1892 # Chi-squared value (total) + 76 21 9.5729 # Chi-squared value for no predicted signal (mu=0) + 77 1 168205 # Analysis ID + 77 2 ||arXiv:1408.1682|| # Reference to publication + 77 3 ||(pp)->tth->3leptons|| # Description (Search channel) + 77 4 8.00 # Center-of-mass energy + 77 5 19.60 # Luminosity + 77 6 2.60 # Luminosity uncertainty (in %) + 77 7 25.00 # Mass resolution (GeV) + 77 8 125.60 # Mass value at peak position (in GeV) + 77 9 3.1000 # Observed signal strength modifier (mu) + 77 10 2.0000 # Lower 68%C.L. uncertainty on observed mu + 77 11 2.4000 # Upper 68%C.L. uncertainty on observed mu + 77 12 001 # Assigned Higgs combination + 77 13 1 # Index of dominant Higgs boson + 77 14 25 # pdg number of dominant Higgs boson + 77 15 122.6512 # Mass of dominant Higgs boson + 77 16 0.9256 # Signal strength modifier of dominant Higgs boson + 77 17 0.9256 # Total predicted signal strength modifier mu + 77 18 1.1100 # Chi-squared value (mu-part) + 77 19 0.0000 # Chi-squared value (mh-part) + 77 20 1.1100 # Chi-squared value (total) + 77 21 2.4628 # Chi-squared value for no predicted signal (mu=0) + 78 1 168206 # Analysis ID + 78 2 ||arXiv:1408.1682|| # Reference to publication + 78 3 ||(pp)->tth->4leptons|| # Description (Search channel) + 78 4 8.00 # Center-of-mass energy + 78 5 19.60 # Luminosity + 78 6 2.60 # Luminosity uncertainty (in %) + 78 7 25.00 # Mass resolution (GeV) + 78 8 125.60 # Mass value at peak position (in GeV) + 78 9 -4.7000 # Observed signal strength modifier (mu) + 78 10 1.3000 # Lower 68%C.L. uncertainty on observed mu + 78 11 5.0000 # Upper 68%C.L. uncertainty on observed mu + 78 12 001 # Assigned Higgs combination + 78 13 1 # Index of dominant Higgs boson + 78 14 25 # pdg number of dominant Higgs boson + 78 15 122.6512 # Mass of dominant Higgs boson + 78 16 0.9447 # Signal strength modifier of dominant Higgs boson + 78 17 0.9447 # Total predicted signal strength modifier mu + 78 18 1.2690 # Chi-squared value (mu-part) + 78 19 0.0000 # Chi-squared value (mh-part) + 78 20 1.2690 # Chi-squared value (total) + 78 21 0.8920 # Chi-squared value for no predicted signal (mu=0) + 79 1 168202 # Analysis ID + 79 2 ||arXiv:1408.1682|| # Reference to publication + 79 3 ||(pp)->tth->tt(bb)|| # Description (Search channel) + 79 4 8.00 # Center-of-mass energy + 79 5 24.50 # Luminosity + 79 6 2.60 # Luminosity uncertainty (in %) + 79 7 25.00 # Mass resolution (GeV) + 79 8 125.60 # Mass value at peak position (in GeV) + 79 9 0.7000 # Observed signal strength modifier (mu) + 79 10 1.9000 # Lower 68%C.L. uncertainty on observed mu + 79 11 1.9000 # Upper 68%C.L. uncertainty on observed mu + 79 12 001 # Assigned Higgs combination + 79 13 1 # Index of dominant Higgs boson + 79 14 25 # pdg number of dominant Higgs boson + 79 15 122.6512 # Mass of dominant Higgs boson + 79 16 1.1282 # Signal strength modifier of dominant Higgs boson + 79 17 1.1282 # Total predicted signal strength modifier mu + 79 18 0.0632 # Chi-squared value (mu-part) + 79 19 0.0000 # Chi-squared value (mh-part) + 79 20 0.0632 # Chi-squared value (total) + 79 21 0.1354 # Chi-squared value for no predicted signal (mu=0) + 80 1 168201 # Analysis ID + 80 2 ||arXiv:1408.1682|| # Reference to publication + 80 3 ||(pp)->tth->tt(gammagamma)|| # Description (Search channel) + 80 4 8.00 # Center-of-mass energy + 80 5 19.60 # Luminosity + 80 6 2.60 # Luminosity uncertainty (in %) + 80 7 15.00 # Mass resolution (GeV) + 80 8 125.60 # Mass value at peak position (in GeV) + 80 9 2.7000 # Observed signal strength modifier (mu) + 80 10 1.8000 # Lower 68%C.L. uncertainty on observed mu + 80 11 2.6000 # Upper 68%C.L. uncertainty on observed mu + 80 12 001 # Assigned Higgs combination + 80 13 1 # Index of dominant Higgs boson + 80 14 25 # pdg number of dominant Higgs boson + 80 15 122.6512 # Mass of dominant Higgs boson + 80 16 0.7514 # Signal strength modifier of dominant Higgs boson + 80 17 0.7514 # Total predicted signal strength modifier mu + 80 18 1.1049 # Chi-squared value (mu-part) + 80 19 0.0000 # Chi-squared value (mh-part) + 80 20 1.1049 # Chi-squared value (total) + 80 21 2.3054 # Chi-squared value for no predicted signal (mu=0) + 81 1 168203 # Analysis ID + 81 2 ||arXiv:1408.1682|| # Reference to publication + 81 3 ||(pp)->tth->tt(tautau)|| # Description (Search channel) + 81 4 8.00 # Center-of-mass energy + 81 5 24.50 # Luminosity + 81 6 2.60 # Luminosity uncertainty (in %) + 81 7 25.00 # Mass resolution (GeV) + 81 8 125.60 # Mass value at peak position (in GeV) + 81 9 -1.3000 # Observed signal strength modifier (mu) + 81 10 5.5000 # Lower 68%C.L. uncertainty on observed mu + 81 11 6.3000 # Upper 68%C.L. uncertainty on observed mu + 81 12 001 # Assigned Higgs combination + 81 13 1 # Index of dominant Higgs boson + 81 14 25 # pdg number of dominant Higgs boson + 81 15 122.6512 # Mass of dominant Higgs boson + 81 16 1.1492 # Signal strength modifier of dominant Higgs boson + 81 17 1.1492 # Total predicted signal strength modifier mu + 81 18 0.1546 # Chi-squared value (mu-part) + 81 19 0.0000 # Chi-squared value (mh-part) + 81 20 0.1546 # Chi-squared value (total) + 81 21 0.0426 # Chi-squared value for no predicted signal (mu=0) + 82 1 130308232 # Analysis ID + 82 2 ||arXiv:1303.0823|| # Reference to publication + 82 3 ||(ppbar)->h->WW|| # Description (Search channel) + 82 4 1.96 # Center-of-mass energy + 82 5 9.70 # Luminosity + 82 6 6.10 # Luminosity uncertainty (in %) + 82 7 25.00 # Mass resolution (GeV) + 82 8 125.00 # Mass value at peak position (in GeV) + 82 9 1.9000 # Observed signal strength modifier (mu) + 82 10 1.5200 # Lower 68%C.L. uncertainty on observed mu + 82 11 1.6300 # Upper 68%C.L. uncertainty on observed mu + 82 12 001 # Assigned Higgs combination + 82 13 1 # Index of dominant Higgs boson + 82 14 25 # pdg number of dominant Higgs boson + 82 15 122.6512 # Mass of dominant Higgs boson + 82 16 0.7351 # Signal strength modifier of dominant Higgs boson + 82 17 0.7351 # Total predicted signal strength modifier mu + 82 18 0.5550 # Chi-squared value (mu-part) + 82 19 0.0000 # Chi-squared value (mh-part) + 82 20 0.5550 # Chi-squared value (total) + 82 21 1.5777 # Chi-squared value for no predicted signal (mu=0) + 83 1 130308234 # Analysis ID + 83 2 ||arXiv:1303.0823|| # Reference to publication + 83 3 ||(ppbar)->h->bb|| # Description (Search channel) + 83 4 1.96 # Center-of-mass energy + 83 5 9.70 # Luminosity + 83 6 6.10 # Luminosity uncertainty (in %) + 83 7 25.00 # Mass resolution (GeV) + 83 8 125.00 # Mass value at peak position (in GeV) + 83 9 1.2300 # Observed signal strength modifier (mu) + 83 10 1.1700 # Lower 68%C.L. uncertainty on observed mu + 83 11 1.2400 # Upper 68%C.L. uncertainty on observed mu + 83 12 001 # Assigned Higgs combination + 83 13 1 # Index of dominant Higgs boson + 83 14 25 # pdg number of dominant Higgs boson + 83 15 122.6512 # Mass of dominant Higgs boson + 83 16 1.1325 # Signal strength modifier of dominant Higgs boson + 83 17 1.1325 # Total predicted signal strength modifier mu + 83 18 0.0071 # Chi-squared value (mu-part) + 83 19 0.0000 # Chi-squared value (mh-part) + 83 20 0.0071 # Chi-squared value (total) + 83 21 1.1049 # Chi-squared value for no predicted signal (mu=0) + 84 1 130308231 # Analysis ID + 84 2 ||arXiv:1303.0823|| # Reference to publication + 84 3 ||(ppbar)->h->gammagamma|| # Description (Search channel) + 84 4 1.96 # Center-of-mass energy + 84 5 9.70 # Luminosity + 84 6 6.10 # Luminosity uncertainty (in %) + 84 7 5.00 # Mass resolution (GeV) + 84 8 125.00 # Mass value at peak position (in GeV) + 84 9 4.2000 # Observed signal strength modifier (mu) + 84 10 4.2000 # Lower 68%C.L. uncertainty on observed mu + 84 11 4.6000 # Upper 68%C.L. uncertainty on observed mu + 84 12 001 # Assigned Higgs combination + 84 13 1 # Index of dominant Higgs boson + 84 14 25 # pdg number of dominant Higgs boson + 84 15 122.6512 # Mass of dominant Higgs boson + 84 16 0.6591 # Signal strength modifier of dominant Higgs boson + 84 17 0.6591 # Total predicted signal strength modifier mu + 84 18 0.6982 # Chi-squared value (mu-part) + 84 19 0.0000 # Chi-squared value (mh-part) + 84 20 0.6982 # Chi-squared value (total) + 84 21 1.0071 # Chi-squared value for no predicted signal (mu=0) + 85 1 130308233 # Analysis ID + 85 2 ||arXiv:1303.0823|| # Reference to publication + 85 3 ||(ppbar)->h->tautau|| # Description (Search channel) + 85 4 1.96 # Center-of-mass energy + 85 5 9.70 # Luminosity + 85 6 6.10 # Luminosity uncertainty (in %) + 85 7 25.00 # Mass resolution (GeV) + 85 8 125.00 # Mass value at peak position (in GeV) + 85 9 3.9600 # Observed signal strength modifier (mu) + 85 10 3.3800 # Lower 68%C.L. uncertainty on observed mu + 85 11 4.1100 # Upper 68%C.L. uncertainty on observed mu + 85 12 001 # Assigned Higgs combination + 85 13 1 # Index of dominant Higgs boson + 85 14 25 # pdg number of dominant Higgs boson + 85 15 122.6512 # Mass of dominant Higgs boson + 85 16 1.0080 # Signal strength modifier of dominant Higgs boson + 85 17 1.0080 # Total predicted signal strength modifier mu + 85 18 0.7414 # Chi-squared value (mu-part) + 85 19 0.0000 # Chi-squared value (mh-part) + 85 20 0.7414 # Chi-squared value (total) + 85 21 1.3860 # Chi-squared value for no predicted signal (mu=0) Index: trunk/HiggsSignals-2/run_tests.bat =================================================================== --- trunk/HiggsSignals-2/run_tests.bat (revision 572) +++ trunk/HiggsSignals-2/run_tests.bat (revision 573) @@ -1,199 +1,217 @@ #!/bin/bash startdir="$PWD" # Checking for a eps viewer if hash gv 2>/dev/null; then openeps=gv elif hash open 2>/dev/null; then openeps=open elif hash ggv 2>/dev/null; then openeps=ggv elif hash eog 2>/dev/null; then openeps=eog else echo 'Note: No eps viewer found. The .eps files will not be displayed.' openeps='#' fi +# Checking for a eps viewer +if hash open 2>/dev/null; then + openpdf=open +elif hash acroread 2>/dev/null; then + openpdf=acroread +else + echo 'Note: No pdf viewer found. The .pdf files will not be displayed.' + openpdf='#' +fi + + # Checking for a gnuplot if hash gnuplot 2>/dev/null; then gnplt=gnuplot else echo 'Note: Gnuplot not found. Will not run plotting scripts.' gnplt='#' fi +if hash python 2>/dev/null; then + pthn=python +else + echo 'Note: python not found. Will not run plotting scripts.' + pthn='#' +fi + echo '*********************************************************************' echo '* Running HiggsSignals test script *' echo '* *' echo '* This may take a while so better go and get a cup of coffee/tea... *' echo '*********************************************************************' echo 'cleaning HiggsSignals distribution...' rm temp_error*.txt temp_output*.txt > /dev/null make hyperclean 2>> temp_error.txt 1>> temp_output.txt echo 'running configure script...' ./configure 2>> temp_error.txt 1>> temp_output.txt echo 'make HiggsSignals...' make HiggsSignals 2>> temp_error.txt 1>> temp_output.txt if [ $(grep -c 'Error' temp_error.txt) == 0 ]; then echo 'Compilation successfully.' else echo 'Compilation failed with' grep 'Error' temp_error.txt echo '---------------------------------------------------------------------' echo 'Here are some things you might want to check:' echo ' - Have you set the HiggsBounds path correctly in the configure script?' echo ' - Does the HiggsBounds library exist?' echo ' - Is it compiled with the same Fortran compiler?' echo '---------------------------------------------------------------------' exit 0 fi echo '---------------------------------------------------------------------' echo ' TEST 1: Run HiggsSignals command-line version on random test points:' echo '---------------------------------------------------------------------' -echo './HiggsSignals latestresults peak 2 effC 3 1 example_data/random/HB_randomtest50points_' -./HiggsSignals latestresults peak 2 effC 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt +echo './HiggsSignals latestresults peak 2 effC 3 1 example_data/rmhmodplus/mhmod+_' +./HiggsSignals latestresults peak 2 effC 3 1 example_data/mhmodplus/mhmod+_ 2>> temp_error1.txt 1>> temp_output1.txt # echo './HiggsSignals latestresults peak 2 part 3 1 example_data/random/HB_randomtest50points_' # ./HiggsSignals latestresults peak 2 part 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt # echo './HiggsSignals latestresults peak 2 hadr 3 1 example_data/random/HB_randomtest50points_' # ./HiggsSignals latestresults peak 2 hadr 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt # echo './HiggsSignals latestresults mass 2 effC 3 1 example_data/random/HB_randomtest50points_' # ./HiggsSignals latestresults mass 2 effC 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt -echo './HiggsSignals latestresults mass 2 part 3 1 example_data/random/HB_randomtest50points_' -./HiggsSignals latestresults mass 2 part 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt +# echo './HiggsSignals latestresults mass 2 part 3 1 example_data/random/HB_randomtest50points_' +# ./HiggsSignals latestresults mass 2 part 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt # echo './HiggsSignals latestresults mass 2 hadr 3 1 example_data/random/HB_randomtest50points_' # ./HiggsSignals latestresults mass 2 hadr 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt # echo './HiggsSignals latestresults both 2 effC 3 1 example_data/random/HB_randomtest50points_' # ./HiggsSignals latestresults both 2 effC 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt # echo './HiggsSignals latestresults both 2 part 3 1 example_data/random/HB_randomtest50points_' -/./HiggsSignals latestresults both 2 part 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt +# /./HiggsSignals latestresults both 2 part 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt # echo './HiggsSignals latestresults both 2 hadr 3 1 example_data/random/HB_randomtest50points_' -./HiggsSignals latestresults both 2 hadr 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt +# ./HiggsSignals latestresults both 2 hadr 3 1 example_data/random/HB_randomtest50points_ 2>> temp_error1.txt 1>> temp_output1.txt echo '---------------------------------------------------------------------' echo 'There were' $(grep -c 'WARNING' temp_output1.txt) 'warnings.' echo 'There were' $(grep -c 'Interrupt' temp_error1.txt) 'interrupts.' echo 'There were' $(grep -c 'Error' temp_error1.txt) 'errors.' echo 'There were' $(grep -c 'stop' temp_error1.txt) 'stops.' echo '---------------------------------------------------------------------' echo 'make HiggsSignals example programs...' make HSexamples 2> temp_error.txt 1> temp_output.txt if [ $(grep -c 'Error' temp_error.txt) == 0 ]; then echo 'Compilation successfully.' else echo 'Compilation failed with' grep 'Error' temp_error.txt fi echo '---------------------------------------------------------------------' echo ' TEST 2: Run HiggsSignals example programs:' echo '---------------------------------------------------------------------' # echo -n '1) Running HSscaleUncertainties...' # cd example_programs # ./HSscaleUncertainties 2 > ../temp_error2.txt 1 > ../temp_output2.txt # if [ $(grep -c 'Error' ../temp_error2.txt) == 0 ] || [ $(grep -c 'stop' ../temp_error2.txt) == 0 ]; then # echo ' done.' # echo -n ' Running gnuplot script...' # cd results # $gnplt plot_scaleUncertainties.gnu > /dev/null # echo 'done (created example_programs/results/scaling_mu.eps).' # $openeps scaling_dmu.eps 2>/dev/null & # cd .. # else # echo ' an error occured. Going to next example...' # fi echo -n '2) Running HS_2Higgses...' cd example_programs ./HS_2Higgses 2 > ../temp_error2.txt 1 > ../temp_output2.txt if [ $(grep -c 'Error' ../temp_error2.txt) == 0 ] || [ $(grep -c 'stop' ../temp_error2.txt) == 0 ]; then echo ' done.' - echo -n ' Running gnuplot script...' + echo -n ' Running python script...' cd results - $gnplt plot_2Higgses.gnu > /dev/null - echo 'done (created example_programs/results/2Higgses.eps).' - $openeps 2Higgses.eps 2>/dev/null & + $pthn plot_2Higgses.py > /dev/null + echo 'done (created example_programs/results/2Higgses.pdf).' + $openpdf 2Higgses.pdf 2>/dev/null & cd .. else echo ' an error occured. Going to next example...' fi # echo -n '2) Running HShadr...' # ./HShadr 2 > ../temp_error2.txt 1 > ../temp_output2.txt # if [ $(grep -c 'Error' ../temp_error2.txt) == 0 ] || [ $(grep -c 'stop' ../temp_error2.txt) == 0 ]; then # echo ' done.' # echo -n ' Running gnuplot script...' # cd results # $gnplt plot_CSscaling.gnu > /dev/null # echo 'done (created example_programs/results/CSscaling.eps).' # $openeps CSscaling.eps 2>/dev/null & # cd .. # else # echo ' an error occured. Going to next example...' # fi echo -n '3) Running HSeffC...' ./HSeffC 2 > ../temp_error2.txt 1 > ../temp_output2.txt if [ $(grep -c 'Error' ../temp_error2.txt) == 0 ] || [ $(grep -c 'stop' ../temp_error2.txt) == 0 ]; then echo ' done.' echo -n ' Running gnuplot script...' cd results $gnplt plot_HSeffC.gnu > /dev/null echo 'done (created example_programs/results/Hgg_Hbb.eps).' $openeps Hgg_Hbb.eps 2>/dev/null & cd .. else echo ' an error occured. Going to next example...' fi echo -n '4) Running HSwithSLHA on provided example SLHA file...' ./HSwithSLHA 1 ../example_data/SLHA/SLHA_FHexample.fh 2> ../temp_error2.txt 1> ../temp_output2.txt if [ $(grep -c 'Error' ../temp_error2.txt) == 0 ] || [ $(grep -c 'stop' ../temp_error2.txt) == 0 ]; then echo ' done.' else echo ' an error occured. Going to next example...' fi echo -n '5) Running HBandHSwithSLHA on provided example SLHA file...' ./HBandHSwithSLHA 1 ../example_data/SLHA/SLHA_FHexample.fh 2> ../temp_error2.txt 1> ../temp_output2.txt if [ $(grep -c 'Error' ../temp_error2.txt) == 0 ] || [ $(grep -c 'stop' ../temp_error2.txt) == 0 ]; then echo ' done.' else echo ' an error occured. Going to next example...' fi echo -n '6) Running HSwithToys...' ./HSwithToys 2 > ../temp_error2.txt 1 > ../temp_output2.txt if [ $(grep -c 'Error' ../temp_error2.txt) == 0 ]; then echo ' done.' else echo ' an error occured. Going to next example...' fi echo -n '7) Running HS_mass...' ./HS_mass 2 > ../temp_error2.txt 1 > ../temp_output2.txt if [ $(grep -c 'Error' ../temp_error2.txt) == 0 ] || [ $(grep -c 'stop' ../temp_error2.txt) == 0 ]; then echo ' done.' echo -n ' Running gnuplot script...' cd results $gnplt plot_mh.gnu > /dev/null echo 'done (created example_programs/results/HS_mass.eps).' $openeps HS_mass.eps 2>/dev/null & cd .. else echo ' an error occured. Going to next example...' fi echo -n '8) Running HS_efficiencies...' ./HS_efficiencies 2 > ../temp_error2.txt 1 > ../temp_output2.txt if [ $(grep -c 'Error' ../temp_error2.txt) == 0 ] || [ $(grep -c 'stop' ../temp_error2.txt) == 0 ]; then echo ' done.' echo -n ' Running gnuplot script...' cd results $gnplt plot_efficiencies.gnu > /dev/null echo 'done (created example_programs/results/HS_efficiencies.eps).' $openeps HS_efficiencies.eps 2>/dev/null & cd .. else echo ' an error occured.' fi echo '---------------------------------------------------------------------' echo ' FINISHED WITH ALL TESTS. ENJOY!' echo '---------------------------------------------------------------------' rm -f results/tmp/* \ No newline at end of file Index: trunk/HiggsSignals-2/example_programs/results/plot_2Higgses.py =================================================================== --- trunk/HiggsSignals-2/example_programs/results/plot_2Higgses.py (revision 0) +++ trunk/HiggsSignals-2/example_programs/results/plot_2Higgses.py (revision 573) @@ -0,0 +1,89 @@ +import matplotlib.pyplot as plt +import pylab as P +import numpy as np + +P.rc('text', usetex=True) +P.rc('text.latex', preamble='\usepackage{amsmath}\usepackage{color}') +font = {'size' : 14} +P.rc('font', **font) +P.rc('grid', linewidth=1,color='#666666') + +data1 = np.loadtxt("2Higgses_pdf1.dat") +data1T = zip(*data1) + +data2 = np.loadtxt("2Higgses_pdf2.dat") +data2T = zip(*data2) + +data3 = np.loadtxt("2Higgses_pdf3.dat") +data3T = zip(*data3) + + +plt.close('all') + +fig, axes = plt.subplots(nrows = 2, ncols = 3,sharex='col',sharey='row') + +# fig.clf() +# for a in axes: +# for aa in a: +# aa.axis('off') +# plt.tick_params(axis='both', left='off', top='off', right='off', bottom='off', labelleft='off', labeltop='off', labelright='off', labelbottom='off') +# plt.show() + + +plts = [[0,0,data1T,8,"Box pdf (1)"],\ + [0,1,data2T,8,"Gaussian pdf (2)"],\ + [0,2,data3T,8,"Box+Gaussian pdf (3)"],\ + [1,0,data1T,11,""],\ + [1,1,data2T,11,""],\ + [1,2,data3T,11,""]] + +for p in plts: +# print p + +# axes[p[0],p[1]].cla() + +# axes[p[0],p[1]].scatter(p[2][0],p[2][1]) + + chi2min = min(p[2][p[3]]) + minindex = p[2][p[3]].index(chi2min) + + print chi2min, p[2][0][minindex],p[2][1][minindex] + +# if p[0] == 1: +# make these tick labels invisible +# axes[p[0],p[1]].cla() +# plt.setp(axes[p[0],p[1]].get_xticklabels(), visible=False) + + # 1/2sigma filled regions: + axes[p[0],p[1]].tricontourf(p[2][0],p[2][1],map(lambda d: d-chi2min, p[2][p[3]]),levels=np.arange(0,10,step=0.5),cmap=plt.cm.YlOrRd)#,colors=['green','yellow','none'] + # 1/2sigma contours: + axes[p[0],p[1]].tricontour(p[2][0],p[2][1],map(lambda d: d-chi2min, p[2][p[3]]),levels=[2.3,5.99],colors=['k','k'],linewidths=2) + axes[p[0],p[1]].plot(p[2][0][minindex],p[2][1][minindex],'*',markersize=10,color='w') + + axes[p[0],p[1]].set_xlim([min(p[2][0]),max(p[2][0])]) + axes[p[0],p[1]].set_ylim([min(p[2][1]),max(p[2][1])]) + + axes[p[0],p[1]].set_xticks(np.arange(min(p[2][0]),max(p[2][0])+1,step=1.)) + axes[p[0],p[1]].set_yticks(np.arange(min(p[2][1]),max(p[2][1])+1,step=1.)) +# axes[p[0],p[1]].relim() + axes[p[0],p[1]].grid() + + if p[0] == 1: + axes[p[0],p[1]].set_xlabel(r'$M_1~[\mathrm{GeV}]$') + if p[1] == 0: + axes[p[0],p[1]].set_ylabel(r'$M_2~[\mathrm{GeV}]$') + + if p[0] == 0: + axes[p[0],p[1]].set_title(p[4],fontsize=14) +# make these tick labels invisible +# plt.setp(axes[p[0],p[1]].get_xticklabels(), visible=False) +# axes[p[0],p[1]].label_outer() + +plt.subplots_adjust(hspace=0.10, wspace=0.20) +# +# fig.tight_layout() + + + +plt.savefig('2Higgses.pdf') + Index: trunk/HiggsSignals-2/example_programs/HS_2Higgses.f90 =================================================================== --- trunk/HiggsSignals-2/example_programs/HS_2Higgses.f90 (revision 572) +++ trunk/HiggsSignals-2/example_programs/HS_2Higgses.f90 (revision 573) @@ -1,141 +1,156 @@ !-------------------------------------------------------------------------------------- ! This example program is part of HiggsSignals (TS 30/10/2014). ! ! In this example we scan over the masses of two Higgs bosons, for fixed values of ! universal signal strength scale factors (scale1, scale2) and theoretical mass un- ! certainties (dm(1), dm(2)). We loop over the three different pdf choices. ! The output (total chi^2) can be plotted by using the gnuplot script plot_2Higgses.gnu. !-------------------------------------------------------------------------------------- program HS_2Higgses !-------------------------------------------------------------------------------------- use theory_colliderSfunctions use usefulbits, only : vsmall + use usefulbits_hs, only : HSres use pc_chisq, only : print_inverse_cov_mh_to_file, get_masschi2_from_separation implicit none integer :: nHzero, nHplus, ndf, i, j, k, ii, jj double precision :: obsratio, mass, Pvalue, Chisq, mu, Chisq_mu, Chisq_mh + double precision :: Chisq_mu_LHCRun1, Chisq_mh_LHCRun1, Chisq_LHCRun1, Pvalue_LHCRun1 + double precision :: Chisq_STXS_rates, Chisq_STXS_mh, Chisq_STXS, Pvalue_STXS + integer :: nobs_LHCRun1, nobs_STXS double precision :: SMGammaTotal(2) double precision :: scale_bbh, scale_ggh, dggh, dbbh - double precision :: Mh(2),GammaTotal(2),g2hjss_s(2),g2hjss_p(2),g2hjcc_s(2),g2hjcc_p(2), & -& g2hjbb_s(2),g2hjbb_p(2),g2hjtt_s(2),g2hjtt_p(2), & -& g2hjmumu_s(2),g2hjmumu_p(2),g2hjtautau_s(2),g2hjtautau_p(2), & -& g2hjWW(2),g2hjZZ(2),g2hjZga(2),g2hjgaga(2),g2hjgg(2),g2hjggZ(2), & -& g2hjhiZ(2,2),BR_hjhihi(2,2),BR_hjinvisible(2,2) + double precision :: Mh(2),GammaTotal(2),ghjss_s(2),ghjss_p(2),ghjcc_s(2),ghjcc_p(2), & +& ghjbb_s(2),ghjbb_p(2),ghjtt_s(2),ghjtt_p(2), & +& ghjmumu_s(2),ghjmumu_p(2),ghjtautau_s(2),ghjtautau_p(2), & +& ghjWW(2),ghjZZ(2),ghjZga(2),ghjgaga(2),ghjgg(2), & +& ghjhiZ(2,2) character(len=100)::filename character(len=1)::pdfchar double precision :: dm(2) integer :: pdf !-HiggsBounds internal functions to obtain SM branching ratios double precision :: SMBR_Htoptop,SMBR_Hss, SMBR_Hcc, SMBR_Hbb, SMBR_Hmumu, SMBR_Htautau,& & SMBR_HWW, SMBR_HZZ, SMBR_HZgam, SMBR_Hgamgam, SMBR_Hgg,SMGamma_h double precision :: scale1, scale2, csq_sep nHzero=2 nHplus=0 !--Enter the Higgs mass and its theory uncertainty here: - Mh = (/ 125.0D0, 127.0D0 /) - dm = (/ 0.5D0, 1.0D0 /) + Mh = (/ 125.0D0, 125.0D0 /) + dm = (/ 1.0D0, 1.0D0 /) ! dm = (/ 0.0D0, 0.0D0 /) !---- Initialize HiggsSignals and pass the name of the experimental analysis folder ----! - call initialize_HiggsSignals(nHzero,nHplus,"latestresults-1.3.0-LHCinclusive") + call initialize_HiggsSignals(nHzero,nHplus,"LHC13") !---- Set the output level (0: silent, 1: screen output, 2: even more output,...) ----! call setup_output_level(0) ! call setup_anticorrelations_in_mh(1) ! call setup_assignmentrange_massobservables(2.0D0) +! Always normalize rate prediction w.r.t. to predicted Higgs mass + call setup_rate_normalization(.False.,.False.) !---- Pass the Higgs mass uncertainty to HiggsSignals ----! call HiggsSignals_neutral_input_MassUncertainty(dm) +! Set number of free parameters (for p-value evaluation) + call setup_nparam(2) do pdf = 1,3 !---- Set the Higgs mass parametrization (1: box, 2:gaussian, 3:box+gaussian) ----! call setup_pdf(pdf) write(pdfchar,'(I1)') pdf - filename='results/pdf'//pdfchar//'.dat' + filename='results/2Higgses_pdf'//pdfchar//'.dat' open(21,file=trim(adjustl(filename))) - write(21,*) '# Mh(1) Mh(2) dm(1) dm(2) mu(1) mu(2) chisq_mu chisq_mh chisq ndf Pvalue chisq_sep' + write(21,*) '# Mh(1) Mh(2) dm(1) dm(2) scale(1) scale(2) chisq_mu chisq_mh chisq ndf Pvalue chisq_sep' write(21,*) '#--------------------------------------------------------------------------' - do i=1,31 - do j=1,31 - Mh(1) = 122.0D0 + (i-1)*0.2D0 - Mh(2) = 122.0D0 + (j-1)*0.2D0 - - scale1 = 0.75D0 - scale2 = 0.25D0 + scale1 = sqrt(0.5D0) + scale2 = sqrt(1.0D0-scale1**2.0D0) + ghjss_s(1) = scale1 + ghjss_s(2) = scale2 + ghjss_p=0.0d0 + ghjcc_s(1) = scale1 + ghjcc_s(2) = scale2 + ghjcc_p=0.0d0 + ghjbb_s(1) = scale1 + ghjbb_s(2) = scale2 + ghjbb_p=0.0d0 + ghjtt_s(1) = scale1 + ghjtt_s(2) = scale2 + ghjtt_p=0.0d0 + ghjmumu_s(1) = scale1 + ghjmumu_s(2) = scale2 + ghjmumu_p=0.0d0 + ghjtautau_s(1) = scale1 + ghjtautau_s(2) = scale2 + ghjtautau_p=0.0d0 + ghjWW(1) = scale1 + ghjWW(2) = scale2 + ghjZZ(1) = scale1 + ghjZZ(2) = scale2 + ghjZga(1) = scale1 + ghjZga(2) = scale2 + ghjgg(1) = scale1 + ghjgg(2) = scale2 +! ghjggZ(1) = scale1 +! ghjggZ(2) = scale2 + ghjhiZ=0d0 + ghjgaga(1) = scale1 + ghjgaga(2) = scale2 + + do i=1,17 + do j=1,17 + Mh(1) = 123.0D0 + (i-1)*0.25D0 + Mh(2) = 123.0D0 + (j-1)*0.25D0 + SMGammaTotal(1)=SMGamma_h(Mh(1)) SMGammaTotal(2)=SMGamma_h(Mh(2)) - - g2hjss_s(1) = scale1 - g2hjss_s(2) = scale2 - g2hjss_p=0.0d0 - g2hjcc_s(1) = scale1 - g2hjcc_s(2) = scale2 - g2hjcc_p=0.0d0 - g2hjbb_s(1) = scale1 - g2hjbb_s(2) = scale2 - g2hjbb_p=0.0d0 - g2hjtt_s(1) = scale1 - g2hjtt_s(2) = scale2 - g2hjtt_p=0.0d0 - g2hjmumu_s(1) = scale1 - g2hjmumu_s(2) = scale2 - g2hjmumu_p=0.0d0 - g2hjtautau_s(1) = scale1 - g2hjtautau_s(2) = scale2 - g2hjtautau_p=0.0d0 - g2hjWW(1) = scale1 - g2hjWW(2) = scale2 - g2hjZZ(1) = scale1 - g2hjZZ(2) = scale2 - g2hjZga(1) = scale1 - g2hjZga(2) = scale2 - g2hjgg(1) = scale1 - g2hjgg(2) = scale2 - g2hjggZ(1) = scale1 - g2hjggZ(2) = scale2 - g2hjhiZ=0d0 - g2hjgaga(1) = scale1 - g2hjgaga(2) = scale2 - BR_hjhihi=0d0 - BR_hjinvisible=0d0 !----Calculate the new total decay width: GammaTotal(1) = SMGammaTotal(1)*(1 + & - & (g2hjWW(1) - 1)*SMBR_HWW(Mh(1))+(g2hjZZ(1) - 1)*SMBR_HZZ(Mh(1)) + & - & (g2hjgg(1) - 1)*SMBR_Hgg(Mh(1))+(g2hjtt_s(1) - 1)*SMBR_Htoptop(Mh(1))+ & - & (g2hjbb_s(1) - 1)*SMBR_Hbb(Mh(1))+(g2hjtautau_s(1) - 1)*SMBR_Htautau(Mh(1))+ & - & (g2hjss_s(1) - 1)*SMBR_Hss(Mh(1))+(g2hjcc_s(1) - 1)*SMBR_Hcc(Mh(1))+ & - & (g2hjZga(1) - 1)*SMBR_HZgam(Mh(1))+(g2hjmumu_s(1) - 1)*SMBR_Hmumu(Mh(1))+ & - & (g2hjgaga(1) - 1)*SMBR_Hgamgam(Mh(1)) ) + & (ghjWW(1)**2.0D0 - 1)*SMBR_HWW(Mh(1))+(ghjZZ(1)**2.0D0 - 1)*SMBR_HZZ(Mh(1)) + & + & (ghjgg(1)**2.0D0 - 1)*SMBR_Hgg(Mh(1))+(ghjtt_s(1)**2.0D0 - 1)*SMBR_Htoptop(Mh(1))+ & + & (ghjbb_s(1)**2.0D0 - 1)*SMBR_Hbb(Mh(1))+(ghjtautau_s(1)**2.0D0 - 1)*SMBR_Htautau(Mh(1))+ & + & (ghjss_s(1)**2.0D0 - 1)*SMBR_Hss(Mh(1))+(ghjcc_s(1)**2.0D0 - 1)*SMBR_Hcc(Mh(1))+ & + & (ghjZga(1)**2.0D0 - 1)*SMBR_HZgam(Mh(1))+(ghjmumu_s(1)**2.0D0 - 1)*SMBR_Hmumu(Mh(1))+ & + & (ghjgaga(1)**2.0D0 - 1)*SMBR_Hgamgam(Mh(1)) ) GammaTotal(2) = SMGammaTotal(2)*(1 + & - & (g2hjWW(2) - 1)*SMBR_HWW(Mh(2))+(g2hjZZ(2) - 1)*SMBR_HZZ(Mh(2)) + & - & (g2hjgg(2) - 1)*SMBR_Hgg(Mh(2))+(g2hjtt_s(2) - 1)*SMBR_Htoptop(Mh(2))+ & - & (g2hjbb_s(2) - 1)*SMBR_Hbb(Mh(2))+(g2hjtautau_s(2) - 1)*SMBR_Htautau(Mh(2))+ & - & (g2hjss_s(2) - 1)*SMBR_Hss(Mh(2))+(g2hjcc_s(2) - 1)*SMBR_Hcc(Mh(2))+ & - & (g2hjZga(2) - 1)*SMBR_HZgam(Mh(2))+(g2hjmumu_s(2) - 1)*SMBR_Hmumu(Mh(2))+ & - & (g2hjgaga(2) - 1)*SMBR_Hgamgam(Mh(2)) ) - - call HiggsBounds_neutral_input_effC(Mh,GammaTotal, & - & g2hjss_s,g2hjss_p,g2hjcc_s,g2hjcc_p,g2hjbb_s,g2hjbb_p, & - & g2hjtt_s,g2hjtt_p, & - & g2hjmumu_s,g2hjmumu_p,g2hjtautau_s,g2hjtautau_p, & - & g2hjWW,g2hjZZ,g2hjZga,g2hjgaga,g2hjgg,g2hjggZ, & - & g2hjhiZ, BR_hjinvisible,BR_hjhihi) + & (ghjWW(2)**2.0D0 - 1)*SMBR_HWW(Mh(2))+(ghjZZ(2)**2.0D0 - 1)*SMBR_HZZ(Mh(2)) + & + & (ghjgg(2)**2.0D0 - 1)*SMBR_Hgg(Mh(2))+(ghjtt_s(2)**2.0D0 - 1)*SMBR_Htoptop(Mh(2))+ & + & (ghjbb_s(2)**2.0D0 - 1)*SMBR_Hbb(Mh(2))+(ghjtautau_s(2)**2.0D0 - 1)*SMBR_Htautau(Mh(2))+ & + & (ghjss_s(2)**2.0D0 - 1)*SMBR_Hss(Mh(2))+(ghjcc_s(2)**2.0D0 - 1)*SMBR_Hcc(Mh(2))+ & + & (ghjZga(2)**2.0D0 - 1)*SMBR_HZgam(Mh(2))+(ghjmumu_s(2)**2.0D0 - 1)*SMBR_Hmumu(Mh(2))+ & + & (ghjgaga(2)**2.0D0 - 1)*SMBR_Hgamgam(Mh(2)) ) + + call HiggsBounds_neutral_input_properties(Mh,GammaTotal,(/1, 1/)) + + call HiggsBounds_neutral_input_effC( & + & ghjss_s,ghjss_p,ghjcc_s,ghjcc_p, & + & ghjbb_s,ghjbb_p,ghjtt_s,ghjtt_p, & + & ghjmumu_s,ghjmumu_p, & + & ghjtautau_s,ghjtautau_p, & + & ghjWW,ghjZZ,ghjZga, & + & ghjgaga,ghjgg,ghjhiZ) call run_HiggsSignals( 1, Chisq_mu, Chisq_mh, Chisq, ndf, Pvalue) + call run_HiggsSignals_LHC_Run1_combination(Chisq_mu_LHCRun1, Chisq_mh_LHCRun1, Chisq_LHCRun1, nobs_LHCRun1, Pvalue_LHCRun1) + + call run_HiggsSignals_STXS(Chisq_STXS_rates, Chisq_STXS_mh, Chisq_STXS, nobs_STXS, Pvalue_STXS) + + call complete_HS_results() + call get_masschi2_from_separation(csq_sep) - write(21,*) Mh,dm,scale1,scale2,Chisq_mu,Chisq_mh,Chisq,ndf,Pvalue, csq_sep + write(21,*) Mh,dm,scale1,scale2,HSres(1)%Chisq_mu,HSres(1)%Chisq_mh,HSres(1)%Chisq,HSres(1)%nobs-2,HSres(1)%Pvalue, csq_sep enddo enddo close(21) enddo write(*,*) "Finishing HiggsSignals..." call finish_HiggsSignals end program HS_2Higgses