{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-} module HROOT.Hist.TH1C.FFI where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import HROOT.Hist.TH1C.RawType import HROOT.Hist.TH1C.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 "HROOTHistTH1C.h TH1C_Add" c_th1c_add :: Ptr RawTH1C -> Ptr RawTH1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_AddBinContent" c_th1c_addbincontent :: Ptr RawTH1C -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Chi2Test" c_th1c_chi2test :: Ptr RawTH1C -> Ptr RawTH1 -> CString -> Ptr CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_DirectoryAutoAdd" c_th1c_directoryautoadd :: Ptr RawTH1C -> Ptr RawTDirectory -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Divide" c_th1c_divide :: Ptr RawTH1C -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_drawCopyTH1" c_th1c_drawcopyth1 :: Ptr RawTH1C -> CString -> IO (Ptr RawTH1C) foreign import ccall interruptible "HROOTHistTH1C.h TH1C_DrawNormalized" c_th1c_drawnormalized :: Ptr RawTH1C -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1C.h TH1C_drawPanelTH1" c_th1c_drawpanelth1 :: Ptr RawTH1C -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_BufferEmpty" c_th1c_bufferempty :: Ptr RawTH1C -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_evalF" c_th1c_evalf :: Ptr RawTH1C -> Ptr RawTF1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_FFT" c_th1c_fft :: Ptr RawTH1C -> Ptr RawTH1 -> CString -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1C.h TH1C_fill1" c_th1c_fill1 :: Ptr RawTH1C -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_fill1w" c_th1c_fill1w :: Ptr RawTH1C -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_fillN1" c_th1c_filln1 :: Ptr RawTH1C -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_FillRandom" c_th1c_fillrandom :: Ptr RawTH1C -> Ptr RawTH1 -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_FindBin" c_th1c_findbin :: Ptr RawTH1C -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_FindFixBin" c_th1c_findfixbin :: Ptr RawTH1C -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_FindFirstBinAbove" c_th1c_findfirstbinabove :: Ptr RawTH1C -> CDouble -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_FindLastBinAbove" c_th1c_findlastbinabove :: Ptr RawTH1C -> CDouble -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Fit" c_th1c_fit :: Ptr RawTH1C -> Ptr RawTF1 -> CString -> CString -> CDouble -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_FitPanelTH1" c_th1c_fitpanelth1 :: Ptr RawTH1C -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getNdivisionA" c_th1c_getndivisiona :: Ptr RawTH1C -> CString -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getAxisColorA" c_th1c_getaxiscolora :: Ptr RawTH1C -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getLabelColorA" c_th1c_getlabelcolora :: Ptr RawTH1C -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getLabelFontA" c_th1c_getlabelfonta :: Ptr RawTH1C -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getLabelOffsetA" c_th1c_getlabeloffseta :: Ptr RawTH1C -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getLabelSizeA" c_th1c_getlabelsizea :: Ptr RawTH1C -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getTitleFontA" c_th1c_gettitlefonta :: Ptr RawTH1C -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getTitleOffsetA" c_th1c_gettitleoffseta :: Ptr RawTH1C -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getTitleSizeA" c_th1c_gettitlesizea :: Ptr RawTH1C -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getTickLengthA" c_th1c_getticklengtha :: Ptr RawTH1C -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBarOffset" c_th1c_getbaroffset :: Ptr RawTH1C -> IO CFloat foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBarWidth" c_th1c_getbarwidth :: Ptr RawTH1C -> IO CFloat foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetContour" c_th1c_getcontour :: Ptr RawTH1C -> Ptr CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetContourLevel" c_th1c_getcontourlevel :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetContourLevelPad" c_th1c_getcontourlevelpad :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBin" c_th1c_getbin :: Ptr RawTH1C -> CInt -> CInt -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBinCenter" c_th1c_getbincenter :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBinContent1" c_th1c_getbincontent1 :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBinContent2" c_th1c_getbincontent2 :: Ptr RawTH1C -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBinContent3" c_th1c_getbincontent3 :: Ptr RawTH1C -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBinError1" c_th1c_getbinerror1 :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBinError2" c_th1c_getbinerror2 :: Ptr RawTH1C -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBinError3" c_th1c_getbinerror3 :: Ptr RawTH1C -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBinLowEdge" c_th1c_getbinlowedge :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetBinWidth" c_th1c_getbinwidth :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetCellContent" c_th1c_getcellcontent :: Ptr RawTH1C -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetCellError" c_th1c_getcellerror :: Ptr RawTH1C -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetEntries" c_th1c_getentries :: Ptr RawTH1C -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetEffectiveEntries" c_th1c_geteffectiveentries :: Ptr RawTH1C -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetFunction" c_th1c_getfunction :: Ptr RawTH1C -> CString -> IO (Ptr RawTF1) foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetDimension" c_th1c_getdimension :: Ptr RawTH1C -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetKurtosis" c_th1c_getkurtosis :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetLowEdge" c_th1c_getlowedge :: Ptr RawTH1C -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getMaximumTH1" c_th1c_getmaximumth1 :: Ptr RawTH1C -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetMaximumBin" c_th1c_getmaximumbin :: Ptr RawTH1C -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetMaximumStored" c_th1c_getmaximumstored :: Ptr RawTH1C -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getMinimumTH1" c_th1c_getminimumth1 :: Ptr RawTH1C -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetMinimumBin" c_th1c_getminimumbin :: Ptr RawTH1C -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetMinimumStored" c_th1c_getminimumstored :: Ptr RawTH1C -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetMean" c_th1c_getmean :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetMeanError" c_th1c_getmeanerror :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetNbinsX" c_th1c_getnbinsx :: Ptr RawTH1C -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetNbinsY" c_th1c_getnbinsy :: Ptr RawTH1C -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetNbinsZ" c_th1c_getnbinsz :: Ptr RawTH1C -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_getQuantilesTH1" c_th1c_getquantilesth1 :: Ptr RawTH1C -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetRandom" c_th1c_getrandom :: Ptr RawTH1C -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetStats" c_th1c_getstats :: Ptr RawTH1C -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetSumOfWeights" c_th1c_getsumofweights :: Ptr RawTH1C -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetSumw2" c_th1c_getsumw2 :: Ptr RawTH1C -> IO (Ptr RawTArrayD) foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetSumw2N" c_th1c_getsumw2n :: Ptr RawTH1C -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetRMS" c_th1c_getrms :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetRMSError" c_th1c_getrmserror :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetSkewness" c_th1c_getskewness :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_interpolate3" c_th1c_interpolate3 :: Ptr RawTH1C -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_KolmogorovTest" c_th1c_kolmogorovtest :: Ptr RawTH1C -> Ptr RawTH1 -> CString -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_LabelsDeflate" c_th1c_labelsdeflate :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_LabelsInflate" c_th1c_labelsinflate :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_LabelsOption" c_th1c_labelsoption :: Ptr RawTH1C -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_multiflyF" c_th1c_multiflyf :: Ptr RawTH1C -> Ptr RawTF1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Multiply" c_th1c_multiply :: Ptr RawTH1C -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_PutStats" c_th1c_putstats :: Ptr RawTH1C -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Rebin" c_th1c_rebin :: Ptr RawTH1C -> CInt -> CString -> Ptr CDouble -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1C.h TH1C_RebinAxis" c_th1c_rebinaxis :: Ptr RawTH1C -> CDouble -> Ptr RawTAxis -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Rebuild" c_th1c_rebuild :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_RecursiveRemove" c_th1c_recursiveremove :: Ptr RawTH1C -> Ptr RawTObject -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Reset" c_th1c_reset :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_ResetStats" c_th1c_resetstats :: Ptr RawTH1C -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Scale" c_th1c_scale :: Ptr RawTH1C -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setAxisColorA" c_th1c_setaxiscolora :: Ptr RawTH1C -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetAxisRange" c_th1c_setaxisrange :: Ptr RawTH1C -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetBarOffset" c_th1c_setbaroffset :: Ptr RawTH1C -> CFloat -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetBarWidth" c_th1c_setbarwidth :: Ptr RawTH1C -> CFloat -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setBinContent1" c_th1c_setbincontent1 :: Ptr RawTH1C -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setBinContent2" c_th1c_setbincontent2 :: Ptr RawTH1C -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setBinContent3" c_th1c_setbincontent3 :: Ptr RawTH1C -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setBinError1" c_th1c_setbinerror1 :: Ptr RawTH1C -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setBinError2" c_th1c_setbinerror2 :: Ptr RawTH1C -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setBinError3" c_th1c_setbinerror3 :: Ptr RawTH1C -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setBins1" c_th1c_setbins1 :: Ptr RawTH1C -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setBins2" c_th1c_setbins2 :: Ptr RawTH1C -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setBins3" c_th1c_setbins3 :: Ptr RawTH1C -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetBinsLength" c_th1c_setbinslength :: Ptr RawTH1C -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetBuffer" c_th1c_setbuffer :: Ptr RawTH1C -> CInt -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetCellContent" c_th1c_setcellcontent :: Ptr RawTH1C -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetContent" c_th1c_setcontent :: Ptr RawTH1C -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetContour" c_th1c_setcontour :: Ptr RawTH1C -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetContourLevel" c_th1c_setcontourlevel :: Ptr RawTH1C -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetDirectory" c_th1c_setdirectory :: Ptr RawTH1C -> Ptr RawTDirectory -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetEntries" c_th1c_setentries :: Ptr RawTH1C -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetError" c_th1c_seterror :: Ptr RawTH1C -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setLabelColorA" c_th1c_setlabelcolora :: Ptr RawTH1C -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setLabelSizeA" c_th1c_setlabelsizea :: Ptr RawTH1C -> CFloat -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setLabelFontA" c_th1c_setlabelfonta :: Ptr RawTH1C -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_setLabelOffsetA" c_th1c_setlabeloffseta :: Ptr RawTH1C -> CFloat -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetMaximum" c_th1c_setmaximum :: Ptr RawTH1C -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetMinimum" c_th1c_setminimum :: Ptr RawTH1C -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetNormFactor" c_th1c_setnormfactor :: Ptr RawTH1C -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetStats" c_th1c_setstats :: Ptr RawTH1C -> CBool -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetOption" c_th1c_setoption :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetXTitle" c_th1c_setxtitle :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetYTitle" c_th1c_setytitle :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetZTitle" c_th1c_setztitle :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_ShowBackground" c_th1c_showbackground :: Ptr RawTH1C -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1C.h TH1C_ShowPeaks" c_th1c_showpeaks :: Ptr RawTH1C -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Smooth" c_th1c_smooth :: Ptr RawTH1C -> CInt -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Sumw2" c_th1c_sumw2 :: Ptr RawTH1C -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetName" c_th1c_setname :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetNameTitle" c_th1c_setnametitle :: Ptr RawTH1C -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetTitle" c_th1c_settitle :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetLineColor" c_th1c_getlinecolor :: Ptr RawTH1C -> IO CShort foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetLineStyle" c_th1c_getlinestyle :: Ptr RawTH1C -> IO CShort foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetLineWidth" c_th1c_getlinewidth :: Ptr RawTH1C -> IO CShort foreign import ccall interruptible "HROOTHistTH1C.h TH1C_ResetAttLine" c_th1c_resetattline :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetLineAttributes" c_th1c_setlineattributes :: Ptr RawTH1C -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetLineColor" c_th1c_setlinecolor :: Ptr RawTH1C -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetLineStyle" c_th1c_setlinestyle :: Ptr RawTH1C -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetLineWidth" c_th1c_setlinewidth :: Ptr RawTH1C -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetFillColor" c_th1c_setfillcolor :: Ptr RawTH1C -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetFillStyle" c_th1c_setfillstyle :: Ptr RawTH1C -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetMarkerColor" c_th1c_getmarkercolor :: Ptr RawTH1C -> IO CShort foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetMarkerStyle" c_th1c_getmarkerstyle :: Ptr RawTH1C -> IO CShort foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetMarkerSize" c_th1c_getmarkersize :: Ptr RawTH1C -> IO CFloat foreign import ccall interruptible "HROOTHistTH1C.h TH1C_ResetAttMarker" c_th1c_resetattmarker :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetMarkerAttributes" c_th1c_setmarkerattributes :: Ptr RawTH1C -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetMarkerColor" c_th1c_setmarkercolor :: Ptr RawTH1C -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetMarkerStyle" c_th1c_setmarkerstyle :: Ptr RawTH1C -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetMarkerSize" c_th1c_setmarkersize :: Ptr RawTH1C -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Clear" c_th1c_clear :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Draw" c_th1c_draw :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_FindObject" c_th1c_findobject :: Ptr RawTH1C -> CString -> IO (Ptr RawTObject) foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetName" c_th1c_getname :: Ptr RawTH1C -> IO CString foreign import ccall interruptible "HROOTHistTH1C.h TH1C_IsA" c_th1c_isa :: Ptr RawTH1C -> IO (Ptr RawTClass) foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Paint" c_th1c_paint :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_printObj" c_th1c_printobj :: Ptr RawTH1C -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SaveAs" c_th1c_saveas :: Ptr RawTH1C -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Write" c_th1c_write :: Ptr RawTH1C -> CString -> CInt -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_Write_" c_th1c_write_ :: Ptr RawTH1C -> IO CInt foreign import ccall interruptible "HROOTHistTH1C.h TH1C_delete" c_th1c_delete :: Ptr RawTH1C -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_GetAt" c_th1c_getat :: Ptr RawTH1C -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetArray" c_th1c_setarray :: Ptr RawTH1C -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1C.h TH1C_SetAt" c_th1c_setat :: Ptr RawTH1C -> CDouble -> CInt -> IO ()