{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-} module HROOT.Hist.TH1.FFI where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import HROOT.Hist.TH1.RawType import HROOT.Hist.TH1.RawType import HROOT.Core.TObject.RawType import HROOT.Core.TClass.RawType import HROOT.Core.TDirectory.RawType import HROOT.Hist.TF1.RawType import HROOT.Core.TArrayD.RawType import HROOT.Hist.TAxis.RawType foreign import ccall interruptible "HROOTHistTH1.h TH1_SetName" c_th1_setname :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetNameTitle" c_th1_setnametitle :: Ptr RawTH1 -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetTitle" c_th1_settitle :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_GetLineColor" c_th1_getlinecolor :: Ptr RawTH1 -> IO CShort foreign import ccall interruptible "HROOTHistTH1.h TH1_GetLineStyle" c_th1_getlinestyle :: Ptr RawTH1 -> IO CShort foreign import ccall interruptible "HROOTHistTH1.h TH1_GetLineWidth" c_th1_getlinewidth :: Ptr RawTH1 -> IO CShort foreign import ccall interruptible "HROOTHistTH1.h TH1_ResetAttLine" c_th1_resetattline :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetLineAttributes" c_th1_setlineattributes :: Ptr RawTH1 -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetLineColor" c_th1_setlinecolor :: Ptr RawTH1 -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetLineStyle" c_th1_setlinestyle :: Ptr RawTH1 -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetLineWidth" c_th1_setlinewidth :: Ptr RawTH1 -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetFillColor" c_th1_setfillcolor :: Ptr RawTH1 -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetFillStyle" c_th1_setfillstyle :: Ptr RawTH1 -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_GetMarkerColor" c_th1_getmarkercolor :: Ptr RawTH1 -> IO CShort foreign import ccall interruptible "HROOTHistTH1.h TH1_GetMarkerStyle" c_th1_getmarkerstyle :: Ptr RawTH1 -> IO CShort foreign import ccall interruptible "HROOTHistTH1.h TH1_GetMarkerSize" c_th1_getmarkersize :: Ptr RawTH1 -> IO CFloat foreign import ccall interruptible "HROOTHistTH1.h TH1_ResetAttMarker" c_th1_resetattmarker :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetMarkerAttributes" c_th1_setmarkerattributes :: Ptr RawTH1 -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetMarkerColor" c_th1_setmarkercolor :: Ptr RawTH1 -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetMarkerStyle" c_th1_setmarkerstyle :: Ptr RawTH1 -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetMarkerSize" c_th1_setmarkersize :: Ptr RawTH1 -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Clear" c_th1_clear :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Draw" c_th1_draw :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_FindObject" c_th1_findobject :: Ptr RawTH1 -> CString -> IO (Ptr RawTObject) foreign import ccall interruptible "HROOTHistTH1.h TH1_GetName" c_th1_getname :: Ptr RawTH1 -> IO CString foreign import ccall interruptible "HROOTHistTH1.h TH1_IsA" c_th1_isa :: Ptr RawTH1 -> IO (Ptr RawTClass) foreign import ccall interruptible "HROOTHistTH1.h TH1_Paint" c_th1_paint :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_printObj" c_th1_printobj :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SaveAs" c_th1_saveas :: Ptr RawTH1 -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Write" c_th1_write :: Ptr RawTH1 -> CString -> CInt -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_Write_" c_th1_write_ :: Ptr RawTH1 -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_delete" c_th1_delete :: Ptr RawTH1 -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Add" c_th1_add :: Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_AddBinContent" c_th1_addbincontent :: Ptr RawTH1 -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Chi2Test" c_th1_chi2test :: Ptr RawTH1 -> Ptr RawTH1 -> CString -> Ptr CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_DirectoryAutoAdd" c_th1_directoryautoadd :: Ptr RawTH1 -> Ptr RawTDirectory -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Divide" c_th1_divide :: Ptr RawTH1 -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_drawCopyTH1" c_th1_drawcopyth1 :: Ptr RawTH1 -> CString -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1.h TH1_DrawNormalized" c_th1_drawnormalized :: Ptr RawTH1 -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1.h TH1_drawPanelTH1" c_th1_drawpanelth1 :: Ptr RawTH1 -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_BufferEmpty" c_th1_bufferempty :: Ptr RawTH1 -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_evalF" c_th1_evalf :: Ptr RawTH1 -> Ptr RawTF1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_FFT" c_th1_fft :: Ptr RawTH1 -> Ptr RawTH1 -> CString -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1.h TH1_fill1" c_th1_fill1 :: Ptr RawTH1 -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_fill1w" c_th1_fill1w :: Ptr RawTH1 -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_fillN1" c_th1_filln1 :: Ptr RawTH1 -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_FillRandom" c_th1_fillrandom :: Ptr RawTH1 -> Ptr RawTH1 -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_FindBin" c_th1_findbin :: Ptr RawTH1 -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_FindFixBin" c_th1_findfixbin :: Ptr RawTH1 -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_FindFirstBinAbove" c_th1_findfirstbinabove :: Ptr RawTH1 -> CDouble -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_FindLastBinAbove" c_th1_findlastbinabove :: Ptr RawTH1 -> CDouble -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_Fit" c_th1_fit :: Ptr RawTH1 -> Ptr RawTF1 -> CString -> CString -> CDouble -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_FitPanelTH1" c_th1_fitpanelth1 :: Ptr RawTH1 -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_GetAsymmetry" c_th1_th1_getasymmetry :: Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_GetBufferLength" c_th1_th1_getbufferlength :: Ptr RawTH1 -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_GetBufferSize" c_th1_th1_getbuffersize :: Ptr RawTH1 -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_GetDefaultBufferSize" c_th1_th1_getdefaultbuffersize :: IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_getNdivisionA" c_th1_getndivisiona :: Ptr RawTH1 -> CString -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_getAxisColorA" c_th1_getaxiscolora :: Ptr RawTH1 -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1.h TH1_getLabelColorA" c_th1_getlabelcolora :: Ptr RawTH1 -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1.h TH1_getLabelFontA" c_th1_getlabelfonta :: Ptr RawTH1 -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1.h TH1_getLabelOffsetA" c_th1_getlabeloffseta :: Ptr RawTH1 -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1.h TH1_getLabelSizeA" c_th1_getlabelsizea :: Ptr RawTH1 -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1.h TH1_getTitleFontA" c_th1_gettitlefonta :: Ptr RawTH1 -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1.h TH1_getTitleOffsetA" c_th1_gettitleoffseta :: Ptr RawTH1 -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1.h TH1_getTitleSizeA" c_th1_gettitlesizea :: Ptr RawTH1 -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1.h TH1_getTickLengthA" c_th1_getticklengtha :: Ptr RawTH1 -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBarOffset" c_th1_getbaroffset :: Ptr RawTH1 -> IO CFloat foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBarWidth" c_th1_getbarwidth :: Ptr RawTH1 -> IO CFloat foreign import ccall interruptible "HROOTHistTH1.h TH1_GetContour" c_th1_getcontour :: Ptr RawTH1 -> Ptr CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_GetContourLevel" c_th1_getcontourlevel :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetContourLevelPad" c_th1_getcontourlevelpad :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBin" c_th1_getbin :: Ptr RawTH1 -> CInt -> CInt -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBinCenter" c_th1_getbincenter :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBinContent1" c_th1_getbincontent1 :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBinContent2" c_th1_getbincontent2 :: Ptr RawTH1 -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBinContent3" c_th1_getbincontent3 :: Ptr RawTH1 -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBinError1" c_th1_getbinerror1 :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBinError2" c_th1_getbinerror2 :: Ptr RawTH1 -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBinError3" c_th1_getbinerror3 :: Ptr RawTH1 -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBinLowEdge" c_th1_getbinlowedge :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetBinWidth" c_th1_getbinwidth :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetCellContent" c_th1_getcellcontent :: Ptr RawTH1 -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetCellError" c_th1_getcellerror :: Ptr RawTH1 -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_GetDefaultSumw2" c_th1_th1_getdefaultsumw2 :: IO CBool foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_GetDirectory" c_th1_th1_getdirectory :: Ptr RawTH1 -> IO (Ptr RawTDirectory) foreign import ccall interruptible "HROOTHistTH1.h TH1_GetEntries" c_th1_getentries :: Ptr RawTH1 -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetEffectiveEntries" c_th1_geteffectiveentries :: Ptr RawTH1 -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetFunction" c_th1_getfunction :: Ptr RawTH1 -> CString -> IO (Ptr RawTF1) foreign import ccall interruptible "HROOTHistTH1.h TH1_GetDimension" c_th1_getdimension :: Ptr RawTH1 -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_GetKurtosis" c_th1_getkurtosis :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetLowEdge" c_th1_getlowedge :: Ptr RawTH1 -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_getMaximumTH1" c_th1_getmaximumth1 :: Ptr RawTH1 -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetMaximumBin" c_th1_getmaximumbin :: Ptr RawTH1 -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_GetMaximumStored" c_th1_getmaximumstored :: Ptr RawTH1 -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_getMinimumTH1" c_th1_getminimumth1 :: Ptr RawTH1 -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetMinimumBin" c_th1_getminimumbin :: Ptr RawTH1 -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_GetMinimumStored" c_th1_getminimumstored :: Ptr RawTH1 -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetMean" c_th1_getmean :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetMeanError" c_th1_getmeanerror :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetNbinsX" c_th1_getnbinsx :: Ptr RawTH1 -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetNbinsY" c_th1_getnbinsy :: Ptr RawTH1 -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetNbinsZ" c_th1_getnbinsz :: Ptr RawTH1 -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_getQuantilesTH1" c_th1_getquantilesth1 :: Ptr RawTH1 -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_GetRandom" c_th1_getrandom :: Ptr RawTH1 -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetStats" c_th1_getstats :: Ptr RawTH1 -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_GetSumOfWeights" c_th1_getsumofweights :: Ptr RawTH1 -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetSumw2" c_th1_getsumw2 :: Ptr RawTH1 -> IO (Ptr RawTArrayD) foreign import ccall interruptible "HROOTHistTH1.h TH1_GetSumw2N" c_th1_getsumw2n :: Ptr RawTH1 -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_GetRMS" c_th1_getrms :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetRMSError" c_th1_getrmserror :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_GetSkewness" c_th1_getskewness :: Ptr RawTH1 -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_GetXaxis" c_th1_th1_getxaxis :: Ptr RawTH1 -> IO (Ptr RawTAxis) foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_GetYaxis" c_th1_th1_getyaxis :: Ptr RawTH1 -> IO (Ptr RawTAxis) foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_GetZaxis" c_th1_th1_getzaxis :: Ptr RawTH1 -> IO (Ptr RawTAxis) foreign import ccall interruptible "HROOTHistTH1.h TH1_interpolate3" c_th1_interpolate3 :: Ptr RawTH1 -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_IsBinOverflow" c_th1_th1_isbinoverflow :: Ptr RawTH1 -> CInt -> IO CBool foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_IsBinUnderflow" c_th1_th1_isbinunderflow :: Ptr RawTH1 -> CInt -> IO CBool foreign import ccall interruptible "HROOTHistTH1.h TH1_KolmogorovTest" c_th1_kolmogorovtest :: Ptr RawTH1 -> Ptr RawTH1 -> CString -> IO CDouble foreign import ccall interruptible "HROOTHistTH1.h TH1_LabelsDeflate" c_th1_labelsdeflate :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_LabelsInflate" c_th1_labelsinflate :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_LabelsOption" c_th1_labelsoption :: Ptr RawTH1 -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_multiflyF" c_th1_multiflyf :: Ptr RawTH1 -> Ptr RawTF1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Multiply" c_th1_multiply :: Ptr RawTH1 -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_PutStats" c_th1_putstats :: Ptr RawTH1 -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Rebin" c_th1_rebin :: Ptr RawTH1 -> CInt -> CString -> Ptr CDouble -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1.h TH1_RebinAxis" c_th1_rebinaxis :: Ptr RawTH1 -> CDouble -> Ptr RawTAxis -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Rebuild" c_th1_rebuild :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_RecursiveRemove" c_th1_recursiveremove :: Ptr RawTH1 -> Ptr RawTObject -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Reset" c_th1_reset :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_ResetStats" c_th1_resetstats :: Ptr RawTH1 -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Scale" c_th1_scale :: Ptr RawTH1 -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setAxisColorA" c_th1_setaxiscolora :: Ptr RawTH1 -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetAxisRange" c_th1_setaxisrange :: Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetBarOffset" c_th1_setbaroffset :: Ptr RawTH1 -> CFloat -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetBarWidth" c_th1_setbarwidth :: Ptr RawTH1 -> CFloat -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setBinContent1" c_th1_setbincontent1 :: Ptr RawTH1 -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setBinContent2" c_th1_setbincontent2 :: Ptr RawTH1 -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setBinContent3" c_th1_setbincontent3 :: Ptr RawTH1 -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setBinError1" c_th1_setbinerror1 :: Ptr RawTH1 -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setBinError2" c_th1_setbinerror2 :: Ptr RawTH1 -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setBinError3" c_th1_setbinerror3 :: Ptr RawTH1 -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setBins1" c_th1_setbins1 :: Ptr RawTH1 -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setBins2" c_th1_setbins2 :: Ptr RawTH1 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setBins3" c_th1_setbins3 :: Ptr RawTH1 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetBinsLength" c_th1_setbinslength :: Ptr RawTH1 -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetBuffer" c_th1_setbuffer :: Ptr RawTH1 -> CInt -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetCellContent" c_th1_setcellcontent :: Ptr RawTH1 -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetContent" c_th1_setcontent :: Ptr RawTH1 -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetContour" c_th1_setcontour :: Ptr RawTH1 -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetContourLevel" c_th1_setcontourlevel :: Ptr RawTH1 -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_SetDefaultBufferSize" c_th1_th1_setdefaultbuffersize :: CInt -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_SetDefaultSumw2" c_th1_th1_setdefaultsumw2 :: CBool -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetDirectory" c_th1_setdirectory :: Ptr RawTH1 -> Ptr RawTDirectory -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetEntries" c_th1_setentries :: Ptr RawTH1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetError" c_th1_seterror :: Ptr RawTH1 -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setLabelColorA" c_th1_setlabelcolora :: Ptr RawTH1 -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setLabelSizeA" c_th1_setlabelsizea :: Ptr RawTH1 -> CFloat -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setLabelFontA" c_th1_setlabelfonta :: Ptr RawTH1 -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_setLabelOffsetA" c_th1_setlabeloffseta :: Ptr RawTH1 -> CFloat -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetMaximum" c_th1_setmaximum :: Ptr RawTH1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetMinimum" c_th1_setminimum :: Ptr RawTH1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetNormFactor" c_th1_setnormfactor :: Ptr RawTH1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetStats" c_th1_setstats :: Ptr RawTH1 -> CBool -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetOption" c_th1_setoption :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetXTitle" c_th1_setxtitle :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetYTitle" c_th1_setytitle :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_SetZTitle" c_th1_setztitle :: Ptr RawTH1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_ShowBackground" c_th1_showbackground :: Ptr RawTH1 -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1.h TH1_ShowPeaks" c_th1_showpeaks :: Ptr RawTH1 -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1.h TH1_Smooth" c_th1_smooth :: Ptr RawTH1 -> CInt -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_SmoothArray" c_th1_th1_smootharray :: CInt -> Ptr CDouble -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_StatOverflows" c_th1_th1_statoverflows :: CBool -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_Sumw2" c_th1_sumw2 :: Ptr RawTH1 -> IO () foreign import ccall interruptible "HROOTHistTH1.h TH1_tH1_UseCurrentStyle" c_th1_th1_usecurrentstyle :: Ptr RawTH1 -> IO ()