{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-} module HROOT.Hist.TH1S.FFI where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import HROOT.Hist.TH1S.RawType import HROOT.Hist.TH1S.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 "HROOTHistTH1S.h TH1S_Add" c_th1s_add :: Ptr RawTH1S -> Ptr RawTH1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_AddBinContent" c_th1s_addbincontent :: Ptr RawTH1S -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Chi2Test" c_th1s_chi2test :: Ptr RawTH1S -> Ptr RawTH1 -> CString -> Ptr CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_DirectoryAutoAdd" c_th1s_directoryautoadd :: Ptr RawTH1S -> Ptr RawTDirectory -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Divide" c_th1s_divide :: Ptr RawTH1S -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_drawCopyTH1" c_th1s_drawcopyth1 :: Ptr RawTH1S -> CString -> IO (Ptr RawTH1S) foreign import ccall interruptible "HROOTHistTH1S.h TH1S_DrawNormalized" c_th1s_drawnormalized :: Ptr RawTH1S -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1S.h TH1S_drawPanelTH1" c_th1s_drawpanelth1 :: Ptr RawTH1S -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_BufferEmpty" c_th1s_bufferempty :: Ptr RawTH1S -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_evalF" c_th1s_evalf :: Ptr RawTH1S -> Ptr RawTF1 -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_FFT" c_th1s_fft :: Ptr RawTH1S -> Ptr RawTH1 -> CString -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1S.h TH1S_fill1" c_th1s_fill1 :: Ptr RawTH1S -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_fill1w" c_th1s_fill1w :: Ptr RawTH1S -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_fillN1" c_th1s_filln1 :: Ptr RawTH1S -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_FillRandom" c_th1s_fillrandom :: Ptr RawTH1S -> Ptr RawTH1 -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_FindBin" c_th1s_findbin :: Ptr RawTH1S -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_FindFixBin" c_th1s_findfixbin :: Ptr RawTH1S -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_FindFirstBinAbove" c_th1s_findfirstbinabove :: Ptr RawTH1S -> CDouble -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_FindLastBinAbove" c_th1s_findlastbinabove :: Ptr RawTH1S -> CDouble -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Fit" c_th1s_fit :: Ptr RawTH1S -> Ptr RawTF1 -> CString -> CString -> CDouble -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_FitPanelTH1" c_th1s_fitpanelth1 :: Ptr RawTH1S -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getNdivisionA" c_th1s_getndivisiona :: Ptr RawTH1S -> CString -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getAxisColorA" c_th1s_getaxiscolora :: Ptr RawTH1S -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getLabelColorA" c_th1s_getlabelcolora :: Ptr RawTH1S -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getLabelFontA" c_th1s_getlabelfonta :: Ptr RawTH1S -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getLabelOffsetA" c_th1s_getlabeloffseta :: Ptr RawTH1S -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getLabelSizeA" c_th1s_getlabelsizea :: Ptr RawTH1S -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getTitleFontA" c_th1s_gettitlefonta :: Ptr RawTH1S -> CString -> IO CShort foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getTitleOffsetA" c_th1s_gettitleoffseta :: Ptr RawTH1S -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getTitleSizeA" c_th1s_gettitlesizea :: Ptr RawTH1S -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getTickLengthA" c_th1s_getticklengtha :: Ptr RawTH1S -> CString -> IO CFloat foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBarOffset" c_th1s_getbaroffset :: Ptr RawTH1S -> IO CFloat foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBarWidth" c_th1s_getbarwidth :: Ptr RawTH1S -> IO CFloat foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetContour" c_th1s_getcontour :: Ptr RawTH1S -> Ptr CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetContourLevel" c_th1s_getcontourlevel :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetContourLevelPad" c_th1s_getcontourlevelpad :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBin" c_th1s_getbin :: Ptr RawTH1S -> CInt -> CInt -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBinCenter" c_th1s_getbincenter :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBinContent1" c_th1s_getbincontent1 :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBinContent2" c_th1s_getbincontent2 :: Ptr RawTH1S -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBinContent3" c_th1s_getbincontent3 :: Ptr RawTH1S -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBinError1" c_th1s_getbinerror1 :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBinError2" c_th1s_getbinerror2 :: Ptr RawTH1S -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBinError3" c_th1s_getbinerror3 :: Ptr RawTH1S -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBinLowEdge" c_th1s_getbinlowedge :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetBinWidth" c_th1s_getbinwidth :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetCellContent" c_th1s_getcellcontent :: Ptr RawTH1S -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetCellError" c_th1s_getcellerror :: Ptr RawTH1S -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetEntries" c_th1s_getentries :: Ptr RawTH1S -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetEffectiveEntries" c_th1s_geteffectiveentries :: Ptr RawTH1S -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetFunction" c_th1s_getfunction :: Ptr RawTH1S -> CString -> IO (Ptr RawTF1) foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetDimension" c_th1s_getdimension :: Ptr RawTH1S -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetKurtosis" c_th1s_getkurtosis :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetLowEdge" c_th1s_getlowedge :: Ptr RawTH1S -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getMaximumTH1" c_th1s_getmaximumth1 :: Ptr RawTH1S -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetMaximumBin" c_th1s_getmaximumbin :: Ptr RawTH1S -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetMaximumStored" c_th1s_getmaximumstored :: Ptr RawTH1S -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getMinimumTH1" c_th1s_getminimumth1 :: Ptr RawTH1S -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetMinimumBin" c_th1s_getminimumbin :: Ptr RawTH1S -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetMinimumStored" c_th1s_getminimumstored :: Ptr RawTH1S -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetMean" c_th1s_getmean :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetMeanError" c_th1s_getmeanerror :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetNbinsX" c_th1s_getnbinsx :: Ptr RawTH1S -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetNbinsY" c_th1s_getnbinsy :: Ptr RawTH1S -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetNbinsZ" c_th1s_getnbinsz :: Ptr RawTH1S -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_getQuantilesTH1" c_th1s_getquantilesth1 :: Ptr RawTH1S -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetRandom" c_th1s_getrandom :: Ptr RawTH1S -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetStats" c_th1s_getstats :: Ptr RawTH1S -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetSumOfWeights" c_th1s_getsumofweights :: Ptr RawTH1S -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetSumw2" c_th1s_getsumw2 :: Ptr RawTH1S -> IO (Ptr RawTArrayD) foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetSumw2N" c_th1s_getsumw2n :: Ptr RawTH1S -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetRMS" c_th1s_getrms :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetRMSError" c_th1s_getrmserror :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetSkewness" c_th1s_getskewness :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_interpolate3" c_th1s_interpolate3 :: Ptr RawTH1S -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_KolmogorovTest" c_th1s_kolmogorovtest :: Ptr RawTH1S -> Ptr RawTH1 -> CString -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_LabelsDeflate" c_th1s_labelsdeflate :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_LabelsInflate" c_th1s_labelsinflate :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_LabelsOption" c_th1s_labelsoption :: Ptr RawTH1S -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_multiflyF" c_th1s_multiflyf :: Ptr RawTH1S -> Ptr RawTF1 -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Multiply" c_th1s_multiply :: Ptr RawTH1S -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_PutStats" c_th1s_putstats :: Ptr RawTH1S -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Rebin" c_th1s_rebin :: Ptr RawTH1S -> CInt -> CString -> Ptr CDouble -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1S.h TH1S_RebinAxis" c_th1s_rebinaxis :: Ptr RawTH1S -> CDouble -> Ptr RawTAxis -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Rebuild" c_th1s_rebuild :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_RecursiveRemove" c_th1s_recursiveremove :: Ptr RawTH1S -> Ptr RawTObject -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Reset" c_th1s_reset :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_ResetStats" c_th1s_resetstats :: Ptr RawTH1S -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Scale" c_th1s_scale :: Ptr RawTH1S -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setAxisColorA" c_th1s_setaxiscolora :: Ptr RawTH1S -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetAxisRange" c_th1s_setaxisrange :: Ptr RawTH1S -> CDouble -> CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetBarOffset" c_th1s_setbaroffset :: Ptr RawTH1S -> CFloat -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetBarWidth" c_th1s_setbarwidth :: Ptr RawTH1S -> CFloat -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setBinContent1" c_th1s_setbincontent1 :: Ptr RawTH1S -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setBinContent2" c_th1s_setbincontent2 :: Ptr RawTH1S -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setBinContent3" c_th1s_setbincontent3 :: Ptr RawTH1S -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setBinError1" c_th1s_setbinerror1 :: Ptr RawTH1S -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setBinError2" c_th1s_setbinerror2 :: Ptr RawTH1S -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setBinError3" c_th1s_setbinerror3 :: Ptr RawTH1S -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setBins1" c_th1s_setbins1 :: Ptr RawTH1S -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setBins2" c_th1s_setbins2 :: Ptr RawTH1S -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setBins3" c_th1s_setbins3 :: Ptr RawTH1S -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetBinsLength" c_th1s_setbinslength :: Ptr RawTH1S -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetBuffer" c_th1s_setbuffer :: Ptr RawTH1S -> CInt -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetCellContent" c_th1s_setcellcontent :: Ptr RawTH1S -> CInt -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetContent" c_th1s_setcontent :: Ptr RawTH1S -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetContour" c_th1s_setcontour :: Ptr RawTH1S -> CInt -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetContourLevel" c_th1s_setcontourlevel :: Ptr RawTH1S -> CInt -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetDirectory" c_th1s_setdirectory :: Ptr RawTH1S -> Ptr RawTDirectory -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetEntries" c_th1s_setentries :: Ptr RawTH1S -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetError" c_th1s_seterror :: Ptr RawTH1S -> Ptr CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setLabelColorA" c_th1s_setlabelcolora :: Ptr RawTH1S -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setLabelSizeA" c_th1s_setlabelsizea :: Ptr RawTH1S -> CFloat -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setLabelFontA" c_th1s_setlabelfonta :: Ptr RawTH1S -> CShort -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_setLabelOffsetA" c_th1s_setlabeloffseta :: Ptr RawTH1S -> CFloat -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetMaximum" c_th1s_setmaximum :: Ptr RawTH1S -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetMinimum" c_th1s_setminimum :: Ptr RawTH1S -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetNormFactor" c_th1s_setnormfactor :: Ptr RawTH1S -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetStats" c_th1s_setstats :: Ptr RawTH1S -> CBool -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetOption" c_th1s_setoption :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetXTitle" c_th1s_setxtitle :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetYTitle" c_th1s_setytitle :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetZTitle" c_th1s_setztitle :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_ShowBackground" c_th1s_showbackground :: Ptr RawTH1S -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall interruptible "HROOTHistTH1S.h TH1S_ShowPeaks" c_th1s_showpeaks :: Ptr RawTH1S -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Smooth" c_th1s_smooth :: Ptr RawTH1S -> CInt -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Sumw2" c_th1s_sumw2 :: Ptr RawTH1S -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetName" c_th1s_setname :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetNameTitle" c_th1s_setnametitle :: Ptr RawTH1S -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetTitle" c_th1s_settitle :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetLineColor" c_th1s_getlinecolor :: Ptr RawTH1S -> IO CShort foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetLineStyle" c_th1s_getlinestyle :: Ptr RawTH1S -> IO CShort foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetLineWidth" c_th1s_getlinewidth :: Ptr RawTH1S -> IO CShort foreign import ccall interruptible "HROOTHistTH1S.h TH1S_ResetAttLine" c_th1s_resetattline :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetLineAttributes" c_th1s_setlineattributes :: Ptr RawTH1S -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetLineColor" c_th1s_setlinecolor :: Ptr RawTH1S -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetLineStyle" c_th1s_setlinestyle :: Ptr RawTH1S -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetLineWidth" c_th1s_setlinewidth :: Ptr RawTH1S -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetFillColor" c_th1s_setfillcolor :: Ptr RawTH1S -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetFillStyle" c_th1s_setfillstyle :: Ptr RawTH1S -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetMarkerColor" c_th1s_getmarkercolor :: Ptr RawTH1S -> IO CShort foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetMarkerStyle" c_th1s_getmarkerstyle :: Ptr RawTH1S -> IO CShort foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetMarkerSize" c_th1s_getmarkersize :: Ptr RawTH1S -> IO CFloat foreign import ccall interruptible "HROOTHistTH1S.h TH1S_ResetAttMarker" c_th1s_resetattmarker :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetMarkerAttributes" c_th1s_setmarkerattributes :: Ptr RawTH1S -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetMarkerColor" c_th1s_setmarkercolor :: Ptr RawTH1S -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetMarkerStyle" c_th1s_setmarkerstyle :: Ptr RawTH1S -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetMarkerSize" c_th1s_setmarkersize :: Ptr RawTH1S -> CShort -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Clear" c_th1s_clear :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Draw" c_th1s_draw :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_FindObject" c_th1s_findobject :: Ptr RawTH1S -> CString -> IO (Ptr RawTObject) foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetName" c_th1s_getname :: Ptr RawTH1S -> IO CString foreign import ccall interruptible "HROOTHistTH1S.h TH1S_IsA" c_th1s_isa :: Ptr RawTH1S -> IO (Ptr RawTClass) foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Paint" c_th1s_paint :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_printObj" c_th1s_printobj :: Ptr RawTH1S -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SaveAs" c_th1s_saveas :: Ptr RawTH1S -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Write" c_th1s_write :: Ptr RawTH1S -> CString -> CInt -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_Write_" c_th1s_write_ :: Ptr RawTH1S -> IO CInt foreign import ccall interruptible "HROOTHistTH1S.h TH1S_delete" c_th1s_delete :: Ptr RawTH1S -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_GetAt" c_th1s_getat :: Ptr RawTH1S -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetArray" c_th1s_setarray :: Ptr RawTH1S -> CInt -> IO () foreign import ccall interruptible "HROOTHistTH1S.h TH1S_SetAt" c_th1s_setat :: Ptr RawTH1S -> CDouble -> CInt -> IO ()