{-# LANGUAGE ForeignFunctionInterface #-} module HROOT.Hist.TH1D.FFI where import Foreign.C import Foreign.Ptr import HROOT.Hist.TH1D.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 safe "HROOTHistTH1D.h TH1D_Add" c_th1d_add :: Ptr RawTH1D -> Ptr RawTH1 -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_AddBinContent" c_th1d_addbincontent :: Ptr RawTH1D -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Chi2Test" c_th1d_chi2test :: Ptr RawTH1D -> Ptr RawTH1 -> CString -> (Ptr CDouble) -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_ComputeIntegral" c_th1d_computeintegral :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_DirectoryAutoAdd" c_th1d_directoryautoadd :: Ptr RawTH1D -> Ptr RawTDirectory -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Divide" c_th1d_divide :: Ptr RawTH1D -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_drawCopyTH1" c_th1d_drawcopyth1 :: Ptr RawTH1D -> CString -> IO (Ptr RawTH1D) foreign import ccall safe "HROOTHistTH1D.h TH1D_DrawNormalized" c_th1d_drawnormalized :: Ptr RawTH1D -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall safe "HROOTHistTH1D.h TH1D_drawPanelTH1" c_th1d_drawpanelth1 :: Ptr RawTH1D -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_BufferEmpty" c_th1d_bufferempty :: Ptr RawTH1D -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_evalF" c_th1d_evalf :: Ptr RawTH1D -> Ptr RawTF1 -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_FFT" c_th1d_fft :: Ptr RawTH1D -> Ptr RawTH1 -> CString -> IO (Ptr RawTH1) foreign import ccall safe "HROOTHistTH1D.h TH1D_fill1" c_th1d_fill1 :: Ptr RawTH1D -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_fill1w" c_th1d_fill1w :: Ptr RawTH1D -> CDouble -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_fillN1" c_th1d_filln1 :: Ptr RawTH1D -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_FillRandom" c_th1d_fillrandom :: Ptr RawTH1D -> Ptr RawTH1 -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_FindBin" c_th1d_findbin :: Ptr RawTH1D -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_FindFixBin" c_th1d_findfixbin :: Ptr RawTH1D -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_FindFirstBinAbove" c_th1d_findfirstbinabove :: Ptr RawTH1D -> CDouble -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_FindLastBinAbove" c_th1d_findlastbinabove :: Ptr RawTH1D -> CDouble -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_Fit" c_th1d_fit :: Ptr RawTH1D -> Ptr RawTF1 -> CString -> CString -> CDouble -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_FitPanelTH1" c_th1d_fitpanelth1 :: Ptr RawTH1D -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_getNdivisionA" c_th1d_getndivisiona :: Ptr RawTH1D -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_getAxisColorA" c_th1d_getaxiscolora :: Ptr RawTH1D -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_getLabelColorA" c_th1d_getlabelcolora :: Ptr RawTH1D -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_getLabelFontA" c_th1d_getlabelfonta :: Ptr RawTH1D -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_getLabelOffsetA" c_th1d_getlabeloffseta :: Ptr RawTH1D -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_getLabelSizeA" c_th1d_getlabelsizea :: Ptr RawTH1D -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_getTitleFontA" c_th1d_gettitlefonta :: Ptr RawTH1D -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_getTitleOffsetA" c_th1d_gettitleoffseta :: Ptr RawTH1D -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_getTitleSizeA" c_th1d_gettitlesizea :: Ptr RawTH1D -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_getTickLengthA" c_th1d_getticklengtha :: Ptr RawTH1D -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBarOffset" c_th1d_getbaroffset :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBarWidth" c_th1d_getbarwidth :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetContour" c_th1d_getcontour :: Ptr RawTH1D -> (Ptr CDouble) -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetContourLevel" c_th1d_getcontourlevel :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetContourLevelPad" c_th1d_getcontourlevelpad :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBin" c_th1d_getbin :: Ptr RawTH1D -> CInt -> CInt -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBinCenter" c_th1d_getbincenter :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBinContent1" c_th1d_getbincontent1 :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBinContent2" c_th1d_getbincontent2 :: Ptr RawTH1D -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBinContent3" c_th1d_getbincontent3 :: Ptr RawTH1D -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBinError1" c_th1d_getbinerror1 :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBinError2" c_th1d_getbinerror2 :: Ptr RawTH1D -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBinError3" c_th1d_getbinerror3 :: Ptr RawTH1D -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBinLowEdge" c_th1d_getbinlowedge :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetBinWidth" c_th1d_getbinwidth :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetCellContent" c_th1d_getcellcontent :: Ptr RawTH1D -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetCellError" c_th1d_getcellerror :: Ptr RawTH1D -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetEntries" c_th1d_getentries :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetEffectiveEntries" c_th1d_geteffectiveentries :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetFunction" c_th1d_getfunction :: Ptr RawTH1D -> CString -> IO (Ptr RawTF1) foreign import ccall safe "HROOTHistTH1D.h TH1D_GetDimension" c_th1d_getdimension :: Ptr RawTH1D -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetKurtosis" c_th1d_getkurtosis :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetLowEdge" c_th1d_getlowedge :: Ptr RawTH1D -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_getMaximumTH1" c_th1d_getmaximumth1 :: Ptr RawTH1D -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetMaximumBin" c_th1d_getmaximumbin :: Ptr RawTH1D -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetMaximumStored" c_th1d_getmaximumstored :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_getMinimumTH1" c_th1d_getminimumth1 :: Ptr RawTH1D -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetMinimumBin" c_th1d_getminimumbin :: Ptr RawTH1D -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetMinimumStored" c_th1d_getminimumstored :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetMean" c_th1d_getmean :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetMeanError" c_th1d_getmeanerror :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetNbinsX" c_th1d_getnbinsx :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetNbinsY" c_th1d_getnbinsy :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetNbinsZ" c_th1d_getnbinsz :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_getQuantilesTH1" c_th1d_getquantilesth1 :: Ptr RawTH1D -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetRandom" c_th1d_getrandom :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetStats" c_th1d_getstats :: Ptr RawTH1D -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_GetSumOfWeights" c_th1d_getsumofweights :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetSumw2" c_th1d_getsumw2 :: Ptr RawTH1D -> IO (Ptr RawTArrayD) foreign import ccall safe "HROOTHistTH1D.h TH1D_GetSumw2N" c_th1d_getsumw2n :: Ptr RawTH1D -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetRMS" c_th1d_getrms :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetRMSError" c_th1d_getrmserror :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_GetSkewness" c_th1d_getskewness :: Ptr RawTH1D -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_integral1" c_th1d_integral1 :: Ptr RawTH1D -> CInt -> CInt -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_interpolate1" c_th1d_interpolate1 :: Ptr RawTH1D -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_interpolate2" c_th1d_interpolate2 :: Ptr RawTH1D -> CDouble -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_interpolate3" c_th1d_interpolate3 :: Ptr RawTH1D -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_KolmogorovTest" c_th1d_kolmogorovtest :: Ptr RawTH1D -> Ptr RawTH1 -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_LabelsDeflate" c_th1d_labelsdeflate :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_LabelsInflate" c_th1d_labelsinflate :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_LabelsOption" c_th1d_labelsoption :: Ptr RawTH1D -> CString -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_multiflyF" c_th1d_multiflyf :: Ptr RawTH1D -> Ptr RawTF1 -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Multiply" c_th1d_multiply :: Ptr RawTH1D -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_PutStats" c_th1d_putstats :: Ptr RawTH1D -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Rebin" c_th1d_rebin :: Ptr RawTH1D -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1) foreign import ccall safe "HROOTHistTH1D.h TH1D_RebinAxis" c_th1d_rebinaxis :: Ptr RawTH1D -> CDouble -> Ptr RawTAxis -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Rebuild" c_th1d_rebuild :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_RecursiveRemove" c_th1d_recursiveremove :: Ptr RawTH1D -> Ptr RawTObject -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Reset" c_th1d_reset :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_ResetStats" c_th1d_resetstats :: Ptr RawTH1D -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Scale" c_th1d_scale :: Ptr RawTH1D -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setAxisColorA" c_th1d_setaxiscolora :: Ptr RawTH1D -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetAxisRange" c_th1d_setaxisrange :: Ptr RawTH1D -> CDouble -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetBarOffset" c_th1d_setbaroffset :: Ptr RawTH1D -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetBarWidth" c_th1d_setbarwidth :: Ptr RawTH1D -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setBinContent1" c_th1d_setbincontent1 :: Ptr RawTH1D -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setBinContent2" c_th1d_setbincontent2 :: Ptr RawTH1D -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setBinContent3" c_th1d_setbincontent3 :: Ptr RawTH1D -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setBinError1" c_th1d_setbinerror1 :: Ptr RawTH1D -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setBinError2" c_th1d_setbinerror2 :: Ptr RawTH1D -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setBinError3" c_th1d_setbinerror3 :: Ptr RawTH1D -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setBins1" c_th1d_setbins1 :: Ptr RawTH1D -> CInt -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setBins2" c_th1d_setbins2 :: Ptr RawTH1D -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setBins3" c_th1d_setbins3 :: Ptr RawTH1D -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetBinsLength" c_th1d_setbinslength :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetBuffer" c_th1d_setbuffer :: Ptr RawTH1D -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetCellContent" c_th1d_setcellcontent :: Ptr RawTH1D -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetContent" c_th1d_setcontent :: Ptr RawTH1D -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetContour" c_th1d_setcontour :: Ptr RawTH1D -> CInt -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetContourLevel" c_th1d_setcontourlevel :: Ptr RawTH1D -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetDirectory" c_th1d_setdirectory :: Ptr RawTH1D -> Ptr RawTDirectory -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetEntries" c_th1d_setentries :: Ptr RawTH1D -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetError" c_th1d_seterror :: Ptr RawTH1D -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setLabelColorA" c_th1d_setlabelcolora :: Ptr RawTH1D -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setLabelSizeA" c_th1d_setlabelsizea :: Ptr RawTH1D -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setLabelFontA" c_th1d_setlabelfonta :: Ptr RawTH1D -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_setLabelOffsetA" c_th1d_setlabeloffseta :: Ptr RawTH1D -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetMaximum" c_th1d_setmaximum :: Ptr RawTH1D -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetMinimum" c_th1d_setminimum :: Ptr RawTH1D -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetNormFactor" c_th1d_setnormfactor :: Ptr RawTH1D -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetStats" c_th1d_setstats :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetOption" c_th1d_setoption :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetXTitle" c_th1d_setxtitle :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetYTitle" c_th1d_setytitle :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetZTitle" c_th1d_setztitle :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_ShowBackground" c_th1d_showbackground :: Ptr RawTH1D -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall safe "HROOTHistTH1D.h TH1D_ShowPeaks" c_th1d_showpeaks :: Ptr RawTH1D -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_Smooth" c_th1d_smooth :: Ptr RawTH1D -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Sumw2" c_th1d_sumw2 :: Ptr RawTH1D -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetName" c_th1d_setname :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetNameTitle" c_th1d_setnametitle :: Ptr RawTH1D -> CString -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetTitle" c_th1d_settitle :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_GetLineColor" c_th1d_getlinecolor :: Ptr RawTH1D -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetLineStyle" c_th1d_getlinestyle :: Ptr RawTH1D -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetLineWidth" c_th1d_getlinewidth :: Ptr RawTH1D -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_ResetAttLine" c_th1d_resetattline :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetLineAttributes" c_th1d_setlineattributes :: Ptr RawTH1D -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetLineColor" c_th1d_setlinecolor :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetLineStyle" c_th1d_setlinestyle :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetLineWidth" c_th1d_setlinewidth :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetFillColor" c_th1d_setfillcolor :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetFillStyle" c_th1d_setfillstyle :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_GetMarkerColor" c_th1d_getmarkercolor :: Ptr RawTH1D -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetMarkerStyle" c_th1d_getmarkerstyle :: Ptr RawTH1D -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_GetMarkerSize" c_th1d_getmarkersize :: Ptr RawTH1D -> IO CDouble foreign import ccall safe "HROOTHistTH1D.h TH1D_ResetAttMarker" c_th1d_resetattmarker :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetMarkerAttributes" c_th1d_setmarkerattributes :: Ptr RawTH1D -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetMarkerColor" c_th1d_setmarkercolor :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetMarkerStyle" c_th1d_setmarkerstyle :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SetMarkerSize" c_th1d_setmarkersize :: Ptr RawTH1D -> CInt -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Draw" c_th1d_draw :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_FindObject" c_th1d_findobject :: Ptr RawTH1D -> CString -> IO (Ptr RawTObject) foreign import ccall safe "HROOTHistTH1D.h TH1D_GetName" c_th1d_getname :: Ptr RawTH1D -> IO CString foreign import ccall safe "HROOTHistTH1D.h TH1D_IsA" c_th1d_isa :: Ptr RawTH1D -> IO (Ptr RawTClass) foreign import ccall safe "HROOTHistTH1D.h TH1D_Paint" c_th1d_paint :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_printObj" c_th1d_printobj :: Ptr RawTH1D -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_SaveAs" c_th1d_saveas :: Ptr RawTH1D -> CString -> CString -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_Write" c_th1d_write :: Ptr RawTH1D -> CString -> CInt -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1D.h TH1D_delete" c_th1d_delete :: Ptr RawTH1D -> IO () foreign import ccall safe "HROOTHistTH1D.h TH1D_newTH1D" c_th1d_newth1d :: CString -> CString -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH1D)