{-# LINE 1 "src/HROOT/Hist/TH1K/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-}
module HROOT.Hist.TH1K.FFI where
import Data.Word
import Data.Int
import Foreign.C
import Foreign.Ptr
import HROOT.Hist.TH1K.RawType
import HROOT.Hist.TH1K.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 "HROOTHistTH1K.h TH1K_Add"
               c_th1k_add :: Ptr RawTH1K -> Ptr RawTH1 -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_AddBinContent" c_th1k_addbincontent ::
               Ptr RawTH1K -> CInt -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Chi2Test"
               c_th1k_chi2test ::
               Ptr RawTH1K -> Ptr RawTH1 -> CString -> Ptr CDouble -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_DirectoryAutoAdd" c_th1k_directoryautoadd ::
               Ptr RawTH1K -> Ptr RawTDirectory -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Divide"
               c_th1k_divide ::
               Ptr RawTH1K ->
                 Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_drawCopyTH1" c_th1k_drawcopyth1 ::
               Ptr RawTH1K -> CString -> IO (Ptr RawTH1K)

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_DrawNormalized" c_th1k_drawnormalized ::
               Ptr RawTH1K -> CString -> CDouble -> IO (Ptr RawTH1)

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_drawPanelTH1" c_th1k_drawpanelth1 ::
               Ptr RawTH1K -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_BufferEmpty" c_th1k_bufferempty ::
               Ptr RawTH1K -> CInt -> IO CInt

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_evalF"
               c_th1k_evalf :: Ptr RawTH1K -> Ptr RawTF1 -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_FFT"
               c_th1k_fft ::
               Ptr RawTH1K -> Ptr RawTH1 -> CString -> IO (Ptr RawTH1)

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_fill1"
               c_th1k_fill1 :: Ptr RawTH1K -> CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_fill1w"
               c_th1k_fill1w :: Ptr RawTH1K -> CDouble -> CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_fillN1"
               c_th1k_filln1 ::
               Ptr RawTH1K -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_FillRandom" c_th1k_fillrandom ::
               Ptr RawTH1K -> Ptr RawTH1 -> CInt -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_FindBin"
               c_th1k_findbin ::
               Ptr RawTH1K -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_FindFixBin" c_th1k_findfixbin ::
               Ptr RawTH1K -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_FindFirstBinAbove" c_th1k_findfirstbinabove
               :: Ptr RawTH1K -> CDouble -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_FindLastBinAbove" c_th1k_findlastbinabove ::
               Ptr RawTH1K -> CDouble -> CInt -> IO CInt

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Fit"
               c_th1k_fit ::
               Ptr RawTH1K ->
                 Ptr RawTF1 -> CString -> CString -> CDouble -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_FitPanelTH1" c_th1k_fitpanelth1 ::
               Ptr RawTH1K -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getNdivisionA" c_th1k_getndivisiona ::
               Ptr RawTH1K -> CString -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getAxisColorA" c_th1k_getaxiscolora ::
               Ptr RawTH1K -> CString -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getLabelColorA" c_th1k_getlabelcolora ::
               Ptr RawTH1K -> CString -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getLabelFontA" c_th1k_getlabelfonta ::
               Ptr RawTH1K -> CString -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getLabelOffsetA" c_th1k_getlabeloffseta ::
               Ptr RawTH1K -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getLabelSizeA" c_th1k_getlabelsizea ::
               Ptr RawTH1K -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getTitleFontA" c_th1k_gettitlefonta ::
               Ptr RawTH1K -> CString -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getTitleOffsetA" c_th1k_gettitleoffseta ::
               Ptr RawTH1K -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getTitleSizeA" c_th1k_gettitlesizea ::
               Ptr RawTH1K -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getTickLengthA" c_th1k_getticklengtha ::
               Ptr RawTH1K -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBarOffset" c_th1k_getbaroffset ::
               Ptr RawTH1K -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBarWidth" c_th1k_getbarwidth ::
               Ptr RawTH1K -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetContour" c_th1k_getcontour ::
               Ptr RawTH1K -> Ptr CDouble -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetContourLevel" c_th1k_getcontourlevel ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetContourLevelPad" c_th1k_getcontourlevelpad
               :: Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetBin"
               c_th1k_getbin :: Ptr RawTH1K -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBinCenter" c_th1k_getbincenter ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBinContent1" c_th1k_getbincontent1 ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBinContent2" c_th1k_getbincontent2 ::
               Ptr RawTH1K -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBinContent3" c_th1k_getbincontent3 ::
               Ptr RawTH1K -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBinError1" c_th1k_getbinerror1 ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBinError2" c_th1k_getbinerror2 ::
               Ptr RawTH1K -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBinError3" c_th1k_getbinerror3 ::
               Ptr RawTH1K -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBinLowEdge" c_th1k_getbinlowedge ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetBinWidth" c_th1k_getbinwidth ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetCellContent" c_th1k_getcellcontent ::
               Ptr RawTH1K -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetCellError" c_th1k_getcellerror ::
               Ptr RawTH1K -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetEntries" c_th1k_getentries ::
               Ptr RawTH1K -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetEffectiveEntries"
               c_th1k_geteffectiveentries :: Ptr RawTH1K -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetFunction" c_th1k_getfunction ::
               Ptr RawTH1K -> CString -> IO (Ptr RawTF1)

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetDimension" c_th1k_getdimension ::
               Ptr RawTH1K -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetKurtosis" c_th1k_getkurtosis ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetLowEdge" c_th1k_getlowedge ::
               Ptr RawTH1K -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getMaximumTH1" c_th1k_getmaximumth1 ::
               Ptr RawTH1K -> CDouble -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetMaximumBin" c_th1k_getmaximumbin ::
               Ptr RawTH1K -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetMaximumStored" c_th1k_getmaximumstored ::
               Ptr RawTH1K -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getMinimumTH1" c_th1k_getminimumth1 ::
               Ptr RawTH1K -> CDouble -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetMinimumBin" c_th1k_getminimumbin ::
               Ptr RawTH1K -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetMinimumStored" c_th1k_getminimumstored ::
               Ptr RawTH1K -> IO CDouble

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetMean"
               c_th1k_getmean :: Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetMeanError" c_th1k_getmeanerror ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetNbinsX"
               c_th1k_getnbinsx :: Ptr RawTH1K -> IO CDouble

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetNbinsY"
               c_th1k_getnbinsy :: Ptr RawTH1K -> IO CDouble

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetNbinsZ"
               c_th1k_getnbinsz :: Ptr RawTH1K -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_getQuantilesTH1" c_th1k_getquantilesth1 ::
               Ptr RawTH1K -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetRandom"
               c_th1k_getrandom :: Ptr RawTH1K -> IO CDouble

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetStats"
               c_th1k_getstats :: Ptr RawTH1K -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetSumOfWeights" c_th1k_getsumofweights ::
               Ptr RawTH1K -> IO CDouble

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetSumw2"
               c_th1k_getsumw2 :: Ptr RawTH1K -> IO (Ptr RawTArrayD)

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetSumw2N"
               c_th1k_getsumw2n :: Ptr RawTH1K -> IO CInt

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetRMS"
               c_th1k_getrms :: Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetRMSError" c_th1k_getrmserror ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetSkewness" c_th1k_getskewness ::
               Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_interpolate3" c_th1k_interpolate3 ::
               Ptr RawTH1K -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_KolmogorovTest" c_th1k_kolmogorovtest ::
               Ptr RawTH1K -> Ptr RawTH1 -> CString -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_LabelsDeflate" c_th1k_labelsdeflate ::
               Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_LabelsInflate" c_th1k_labelsinflate ::
               Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_LabelsOption" c_th1k_labelsoption ::
               Ptr RawTH1K -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_multiflyF"
               c_th1k_multiflyf :: Ptr RawTH1K -> Ptr RawTF1 -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Multiply"
               c_th1k_multiply ::
               Ptr RawTH1K ->
                 Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_PutStats"
               c_th1k_putstats :: Ptr RawTH1K -> Ptr CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Rebin"
               c_th1k_rebin ::
               Ptr RawTH1K -> CInt -> CString -> Ptr CDouble -> IO (Ptr RawTH1)

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_RebinAxis"
               c_th1k_rebinaxis :: Ptr RawTH1K -> CDouble -> Ptr RawTAxis -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Rebuild"
               c_th1k_rebuild :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_RecursiveRemove" c_th1k_recursiveremove ::
               Ptr RawTH1K -> Ptr RawTObject -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Reset"
               c_th1k_reset :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_ResetStats" c_th1k_resetstats ::
               Ptr RawTH1K -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Scale"
               c_th1k_scale :: Ptr RawTH1K -> CDouble -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setAxisColorA" c_th1k_setaxiscolora ::
               Ptr RawTH1K -> CShort -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetAxisRange" c_th1k_setaxisrange ::
               Ptr RawTH1K -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetBarOffset" c_th1k_setbaroffset ::
               Ptr RawTH1K -> CFloat -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetBarWidth" c_th1k_setbarwidth ::
               Ptr RawTH1K -> CFloat -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setBinContent1" c_th1k_setbincontent1 ::
               Ptr RawTH1K -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setBinContent2" c_th1k_setbincontent2 ::
               Ptr RawTH1K -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setBinContent3" c_th1k_setbincontent3 ::
               Ptr RawTH1K -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setBinError1" c_th1k_setbinerror1 ::
               Ptr RawTH1K -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setBinError2" c_th1k_setbinerror2 ::
               Ptr RawTH1K -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setBinError3" c_th1k_setbinerror3 ::
               Ptr RawTH1K -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_setBins1"
               c_th1k_setbins1 :: Ptr RawTH1K -> CInt -> Ptr CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_setBins2"
               c_th1k_setbins2 ::
               Ptr RawTH1K -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_setBins3"
               c_th1k_setbins3 ::
               Ptr RawTH1K ->
                 CInt ->
                   Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetBinsLength" c_th1k_setbinslength ::
               Ptr RawTH1K -> CInt -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetBuffer"
               c_th1k_setbuffer :: Ptr RawTH1K -> CInt -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetCellContent" c_th1k_setcellcontent ::
               Ptr RawTH1K -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetContent" c_th1k_setcontent ::
               Ptr RawTH1K -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetContour" c_th1k_setcontour ::
               Ptr RawTH1K -> CInt -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetContourLevel" c_th1k_setcontourlevel ::
               Ptr RawTH1K -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetDirectory" c_th1k_setdirectory ::
               Ptr RawTH1K -> Ptr RawTDirectory -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetEntries" c_th1k_setentries ::
               Ptr RawTH1K -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetError"
               c_th1k_seterror :: Ptr RawTH1K -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setLabelColorA" c_th1k_setlabelcolora ::
               Ptr RawTH1K -> CShort -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setLabelSizeA" c_th1k_setlabelsizea ::
               Ptr RawTH1K -> CFloat -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setLabelFontA" c_th1k_setlabelfonta ::
               Ptr RawTH1K -> CShort -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_setLabelOffsetA" c_th1k_setlabeloffseta ::
               Ptr RawTH1K -> CFloat -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetMaximum" c_th1k_setmaximum ::
               Ptr RawTH1K -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetMinimum" c_th1k_setminimum ::
               Ptr RawTH1K -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetNormFactor" c_th1k_setnormfactor ::
               Ptr RawTH1K -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetStats"
               c_th1k_setstats :: Ptr RawTH1K -> CBool -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetOption"
               c_th1k_setoption :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetXTitle"
               c_th1k_setxtitle :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetYTitle"
               c_th1k_setytitle :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetZTitle"
               c_th1k_setztitle :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_ShowBackground" c_th1k_showbackground ::
               Ptr RawTH1K -> CInt -> CString -> IO (Ptr RawTH1)

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_ShowPeaks"
               c_th1k_showpeaks ::
               Ptr RawTH1K -> CDouble -> CString -> CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Smooth"
               c_th1k_smooth :: Ptr RawTH1K -> CInt -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Sumw2"
               c_th1k_sumw2 :: Ptr RawTH1K -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetName"
               c_th1k_setname :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetNameTitle" c_th1k_setnametitle ::
               Ptr RawTH1K -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetTitle"
               c_th1k_settitle :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetLineColor" c_th1k_getlinecolor ::
               Ptr RawTH1K -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetLineStyle" c_th1k_getlinestyle ::
               Ptr RawTH1K -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetLineWidth" c_th1k_getlinewidth ::
               Ptr RawTH1K -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_ResetAttLine" c_th1k_resetattline ::
               Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetLineAttributes" c_th1k_setlineattributes
               :: Ptr RawTH1K -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetLineColor" c_th1k_setlinecolor ::
               Ptr RawTH1K -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetLineStyle" c_th1k_setlinestyle ::
               Ptr RawTH1K -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetLineWidth" c_th1k_setlinewidth ::
               Ptr RawTH1K -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetFillColor" c_th1k_setfillcolor ::
               Ptr RawTH1K -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetFillStyle" c_th1k_setfillstyle ::
               Ptr RawTH1K -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetMarkerColor" c_th1k_getmarkercolor ::
               Ptr RawTH1K -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetMarkerStyle" c_th1k_getmarkerstyle ::
               Ptr RawTH1K -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_GetMarkerSize" c_th1k_getmarkersize ::
               Ptr RawTH1K -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_ResetAttMarker" c_th1k_resetattmarker ::
               Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetMarkerAttributes"
               c_th1k_setmarkerattributes :: Ptr RawTH1K -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetMarkerColor" c_th1k_setmarkercolor ::
               Ptr RawTH1K -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetMarkerStyle" c_th1k_setmarkerstyle ::
               Ptr RawTH1K -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_SetMarkerSize" c_th1k_setmarkersize ::
               Ptr RawTH1K -> CShort -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Clear"
               c_th1k_clear :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Draw"
               c_th1k_draw :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH1K.h TH1K_FindObject" c_th1k_findobject ::
               Ptr RawTH1K -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetName"
               c_th1k_getname :: Ptr RawTH1K -> IO CString

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_IsA"
               c_th1k_isa :: Ptr RawTH1K -> IO (Ptr RawTClass)

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Paint"
               c_th1k_paint :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_printObj"
               c_th1k_printobj :: Ptr RawTH1K -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SaveAs"
               c_th1k_saveas :: Ptr RawTH1K -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Write"
               c_th1k_write :: Ptr RawTH1K -> CString -> CInt -> CInt -> IO CInt

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_Write_"
               c_th1k_write_ :: Ptr RawTH1K -> IO CInt

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_delete"
               c_th1k_delete :: Ptr RawTH1K -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_GetAt"
               c_th1k_getat :: Ptr RawTH1K -> CInt -> IO CDouble

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetArray"
               c_th1k_setarray :: Ptr RawTH1K -> CInt -> IO ()

foreign import ccall interruptible "HROOTHistTH1K.h TH1K_SetAt"
               c_th1k_setat :: Ptr RawTH1K -> CDouble -> CInt -> IO ()