{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-} module HROOT.Hist.TH1I.FFI where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import HROOT.Hist.TH1I.RawType import HROOT.Hist.TH1I.RawType import HROOT.Hist.TH1.RawType import HROOT.Core.TDirectory.RawType import HROOT.Hist.TF1.RawType import HROOT.Core.TArrayD.RawType import HROOT.Hist.TAxis.RawType import HROOT.Core.TObject.RawType import HROOT.Core.TClass.RawType foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Add" c_th1i_add :: Ptr RawTH1I -> Ptr RawTH1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_AddBinContent" c_th1i_addbincontent :: Ptr RawTH1I -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Chi2Test" c_th1i_chi2test :: Ptr RawTH1I -> Ptr RawTH1 -> CString -> Ptr CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_DirectoryAutoAdd" c_th1i_directoryautoadd :: Ptr RawTH1I -> Ptr RawTDirectory -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Divide" c_th1i_divide :: Ptr RawTH1I -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_drawCopyTH1" c_th1i_drawcopyth1 :: Ptr RawTH1I -> CString -> IO (Ptr RawTH1I) foreign import ccall interruptible "HROOTHistTH1I.h TH1I_DrawNormalized" c_th1i_drawnormalized :: Ptr RawTH1I -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1I.h TH1I_drawPanelTH1" c_th1i_drawpanelth1 :: Ptr RawTH1I -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_BufferEmpty" c_th1i_bufferempty :: Ptr RawTH1I -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_evalF" c_th1i_evalf :: Ptr RawTH1I -> Ptr RawTF1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_FFT" c_th1i_fft :: Ptr RawTH1I -> Ptr RawTH1 -> CString -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1I.h TH1I_fill1" c_th1i_fill1 :: Ptr RawTH1I -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_fill1w" c_th1i_fill1w :: Ptr RawTH1I -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_fillN1" c_th1i_filln1 :: Ptr RawTH1I -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_FillRandom" c_th1i_fillrandom :: Ptr RawTH1I -> Ptr RawTH1 -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_FindBin" c_th1i_findbin :: Ptr RawTH1I -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_FindFixBin" c_th1i_findfixbin :: Ptr RawTH1I -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_FindFirstBinAbove" c_th1i_findfirstbinabove :: Ptr RawTH1I -> CDouble -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_FindLastBinAbove" c_th1i_findlastbinabove :: Ptr RawTH1I -> CDouble -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Fit" c_th1i_fit :: Ptr RawTH1I -> Ptr RawTF1 -> CString -> CString -> CDouble -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_FitPanelTH1" c_th1i_fitpanelth1 :: Ptr RawTH1I -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getNdivisionA" c_th1i_getndivisiona :: Ptr RawTH1I -> CString -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getAxisColorA" c_th1i_getaxiscolora :: Ptr RawTH1I -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getLabelColorA" c_th1i_getlabelcolora :: Ptr RawTH1I -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getLabelFontA" c_th1i_getlabelfonta :: Ptr RawTH1I -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getLabelOffsetA" c_th1i_getlabeloffseta :: Ptr RawTH1I -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getLabelSizeA" c_th1i_getlabelsizea :: Ptr RawTH1I -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getTitleFontA" c_th1i_gettitlefonta :: Ptr RawTH1I -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getTitleOffsetA" c_th1i_gettitleoffseta :: Ptr RawTH1I -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getTitleSizeA" c_th1i_gettitlesizea :: Ptr RawTH1I -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getTickLengthA" c_th1i_getticklengtha :: Ptr RawTH1I -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBarOffset" c_th1i_getbaroffset :: Ptr RawTH1I -> IO CFloat foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBarWidth" c_th1i_getbarwidth :: Ptr RawTH1I -> IO CFloat foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetContour" c_th1i_getcontour :: Ptr RawTH1I -> Ptr CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetContourLevel" c_th1i_getcontourlevel :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetContourLevelPad" c_th1i_getcontourlevelpad :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBin" c_th1i_getbin :: Ptr RawTH1I -> CInt -> CInt -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBinCenter" c_th1i_getbincenter :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBinContent1" c_th1i_getbincontent1 :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBinContent2" c_th1i_getbincontent2 :: Ptr RawTH1I -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBinContent3" c_th1i_getbincontent3 :: Ptr RawTH1I -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBinError1" c_th1i_getbinerror1 :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBinError2" c_th1i_getbinerror2 :: Ptr RawTH1I -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBinError3" c_th1i_getbinerror3 :: Ptr RawTH1I -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBinLowEdge" c_th1i_getbinlowedge :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetBinWidth" c_th1i_getbinwidth :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetCellContent" c_th1i_getcellcontent :: Ptr RawTH1I -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetCellError" c_th1i_getcellerror :: Ptr RawTH1I -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetEntries" c_th1i_getentries :: Ptr RawTH1I -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetEffectiveEntries" c_th1i_geteffectiveentries :: Ptr RawTH1I -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetFunction" c_th1i_getfunction :: Ptr RawTH1I -> CString -> IO (Ptr RawTF1) foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetDimension" c_th1i_getdimension :: Ptr RawTH1I -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetKurtosis" c_th1i_getkurtosis :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetLowEdge" c_th1i_getlowedge :: Ptr RawTH1I -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getMaximumTH1" c_th1i_getmaximumth1 :: Ptr RawTH1I -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetMaximumBin" c_th1i_getmaximumbin :: Ptr RawTH1I -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetMaximumStored" c_th1i_getmaximumstored :: Ptr RawTH1I -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getMinimumTH1" c_th1i_getminimumth1 :: Ptr RawTH1I -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetMinimumBin" c_th1i_getminimumbin :: Ptr RawTH1I -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetMinimumStored" c_th1i_getminimumstored :: Ptr RawTH1I -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetMean" c_th1i_getmean :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetMeanError" c_th1i_getmeanerror :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetNbinsX" c_th1i_getnbinsx :: Ptr RawTH1I -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetNbinsY" c_th1i_getnbinsy :: Ptr RawTH1I -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetNbinsZ" c_th1i_getnbinsz :: Ptr RawTH1I -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_getQuantilesTH1" c_th1i_getquantilesth1 :: Ptr RawTH1I -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetRandom" c_th1i_getrandom :: Ptr RawTH1I -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetStats" c_th1i_getstats :: Ptr RawTH1I -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetSumOfWeights" c_th1i_getsumofweights :: Ptr RawTH1I -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetSumw2" c_th1i_getsumw2 :: Ptr RawTH1I -> IO (Ptr RawTArrayD) foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetSumw2N" c_th1i_getsumw2n :: Ptr RawTH1I -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetRMS" c_th1i_getrms :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetRMSError" c_th1i_getrmserror :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetSkewness" c_th1i_getskewness :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_interpolate3" c_th1i_interpolate3 :: Ptr RawTH1I -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_KolmogorovTest" c_th1i_kolmogorovtest :: Ptr RawTH1I -> Ptr RawTH1 -> CString -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_LabelsDeflate" c_th1i_labelsdeflate :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_LabelsInflate" c_th1i_labelsinflate :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_LabelsOption" c_th1i_labelsoption :: Ptr RawTH1I -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_multiflyF" c_th1i_multiflyf :: Ptr RawTH1I -> Ptr RawTF1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Multiply" c_th1i_multiply :: Ptr RawTH1I -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_PutStats" c_th1i_putstats :: Ptr RawTH1I -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Rebin" c_th1i_rebin :: Ptr RawTH1I -> CInt -> CString -> Ptr CDouble -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1I.h TH1I_RebinAxis" c_th1i_rebinaxis :: Ptr RawTH1I -> CDouble -> Ptr RawTAxis -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Rebuild" c_th1i_rebuild :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_RecursiveRemove" c_th1i_recursiveremove :: Ptr RawTH1I -> Ptr RawTObject -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Reset" c_th1i_reset :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_ResetStats" c_th1i_resetstats :: Ptr RawTH1I -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Scale" c_th1i_scale :: Ptr RawTH1I -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setAxisColorA" c_th1i_setaxiscolora :: Ptr RawTH1I -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetAxisRange" c_th1i_setaxisrange :: Ptr RawTH1I -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetBarOffset" c_th1i_setbaroffset :: Ptr RawTH1I -> CFloat -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetBarWidth" c_th1i_setbarwidth :: Ptr RawTH1I -> CFloat -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setBinContent1" c_th1i_setbincontent1 :: Ptr RawTH1I -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setBinContent2" c_th1i_setbincontent2 :: Ptr RawTH1I -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setBinContent3" c_th1i_setbincontent3 :: Ptr RawTH1I -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setBinError1" c_th1i_setbinerror1 :: Ptr RawTH1I -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setBinError2" c_th1i_setbinerror2 :: Ptr RawTH1I -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setBinError3" c_th1i_setbinerror3 :: Ptr RawTH1I -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setBins1" c_th1i_setbins1 :: Ptr RawTH1I -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setBins2" c_th1i_setbins2 :: Ptr RawTH1I -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setBins3" c_th1i_setbins3 :: Ptr RawTH1I -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetBinsLength" c_th1i_setbinslength :: Ptr RawTH1I -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetBuffer" c_th1i_setbuffer :: Ptr RawTH1I -> CInt -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetCellContent" c_th1i_setcellcontent :: Ptr RawTH1I -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetContent" c_th1i_setcontent :: Ptr RawTH1I -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetContour" c_th1i_setcontour :: Ptr RawTH1I -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetContourLevel" c_th1i_setcontourlevel :: Ptr RawTH1I -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetDirectory" c_th1i_setdirectory :: Ptr RawTH1I -> Ptr RawTDirectory -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetEntries" c_th1i_setentries :: Ptr RawTH1I -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetError" c_th1i_seterror :: Ptr RawTH1I -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setLabelColorA" c_th1i_setlabelcolora :: Ptr RawTH1I -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setLabelSizeA" c_th1i_setlabelsizea :: Ptr RawTH1I -> CFloat -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setLabelFontA" c_th1i_setlabelfonta :: Ptr RawTH1I -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_setLabelOffsetA" c_th1i_setlabeloffseta :: Ptr RawTH1I -> CFloat -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetMaximum" c_th1i_setmaximum :: Ptr RawTH1I -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetMinimum" c_th1i_setminimum :: Ptr RawTH1I -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetNormFactor" c_th1i_setnormfactor :: Ptr RawTH1I -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetStats" c_th1i_setstats :: Ptr RawTH1I -> CBool -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetOption" c_th1i_setoption :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetXTitle" c_th1i_setxtitle :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetYTitle" c_th1i_setytitle :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetZTitle" c_th1i_setztitle :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_ShowBackground" c_th1i_showbackground :: Ptr RawTH1I -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1I.h TH1I_ShowPeaks" c_th1i_showpeaks :: Ptr RawTH1I -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Smooth" c_th1i_smooth :: Ptr RawTH1I -> CInt -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Sumw2" c_th1i_sumw2 :: Ptr RawTH1I -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetName" c_th1i_setname :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetNameTitle" c_th1i_setnametitle :: Ptr RawTH1I -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetTitle" c_th1i_settitle :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetLineColor" c_th1i_getlinecolor :: Ptr RawTH1I -> IO CShort foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetLineStyle" c_th1i_getlinestyle :: Ptr RawTH1I -> IO CShort foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetLineWidth" c_th1i_getlinewidth :: Ptr RawTH1I -> IO CShort foreign import ccall interruptible "HROOTHistTH1I.h TH1I_ResetAttLine" c_th1i_resetattline :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetLineAttributes" c_th1i_setlineattributes :: Ptr RawTH1I -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetLineColor" c_th1i_setlinecolor :: Ptr RawTH1I -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetLineStyle" c_th1i_setlinestyle :: Ptr RawTH1I -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetLineWidth" c_th1i_setlinewidth :: Ptr RawTH1I -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetFillColor" c_th1i_setfillcolor :: Ptr RawTH1I -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetFillStyle" c_th1i_setfillstyle :: Ptr RawTH1I -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetMarkerColor" c_th1i_getmarkercolor :: Ptr RawTH1I -> IO CShort foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetMarkerStyle" c_th1i_getmarkerstyle :: Ptr RawTH1I -> IO CShort foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetMarkerSize" c_th1i_getmarkersize :: Ptr RawTH1I -> IO CFloat foreign import ccall interruptible "HROOTHistTH1I.h TH1I_ResetAttMarker" c_th1i_resetattmarker :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetMarkerAttributes" c_th1i_setmarkerattributes :: Ptr RawTH1I -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetMarkerColor" c_th1i_setmarkercolor :: Ptr RawTH1I -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetMarkerStyle" c_th1i_setmarkerstyle :: Ptr RawTH1I -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetMarkerSize" c_th1i_setmarkersize :: Ptr RawTH1I -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Clear" c_th1i_clear :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Draw" c_th1i_draw :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_FindObject" c_th1i_findobject :: Ptr RawTH1I -> CString -> IO (Ptr RawTObject) foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetName" c_th1i_getname :: Ptr RawTH1I -> IO CString foreign import ccall interruptible "HROOTHistTH1I.h TH1I_IsA" c_th1i_isa :: Ptr RawTH1I -> IO (Ptr RawTClass) foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Paint" c_th1i_paint :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_printObj" c_th1i_printobj :: Ptr RawTH1I -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SaveAs" c_th1i_saveas :: Ptr RawTH1I -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Write" c_th1i_write :: Ptr RawTH1I -> CString -> CInt -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_Write_" c_th1i_write_ :: Ptr RawTH1I -> IO CInt foreign import ccall interruptible "HROOTHistTH1I.h TH1I_delete" c_th1i_delete :: Ptr RawTH1I -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_GetAt" c_th1i_getat :: Ptr RawTH1I -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetArray" c_th1i_setarray :: Ptr RawTH1I -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1I.h TH1I_SetAt" c_th1i_setat :: Ptr RawTH1I -> CDouble -> CInt -> IO ()