{-# LANGUAGE ForeignFunctionInterface #-} module HROOT.Hist.TH1F.FFI where import Foreign.C import Foreign.Ptr import HROOT.Hist.TH1F.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 "HROOTHistTH1F.h TH1F_Add" c_th1f_add :: Ptr RawTH1F -> Ptr RawTH1 -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_AddBinContent" c_th1f_addbincontent :: Ptr RawTH1F -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Chi2Test" c_th1f_chi2test :: Ptr RawTH1F -> Ptr RawTH1 -> CString -> (Ptr CDouble) -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_ComputeIntegral" c_th1f_computeintegral :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_DirectoryAutoAdd" c_th1f_directoryautoadd :: Ptr RawTH1F -> Ptr RawTDirectory -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Divide" c_th1f_divide :: Ptr RawTH1F -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_drawCopyTH1" c_th1f_drawcopyth1 :: Ptr RawTH1F -> CString -> IO (Ptr RawTH1F) foreign import ccall safe "HROOTHistTH1F.h TH1F_DrawNormalized" c_th1f_drawnormalized :: Ptr RawTH1F -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall safe "HROOTHistTH1F.h TH1F_drawPanelTH1" c_th1f_drawpanelth1 :: Ptr RawTH1F -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_BufferEmpty" c_th1f_bufferempty :: Ptr RawTH1F -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_evalF" c_th1f_evalf :: Ptr RawTH1F -> Ptr RawTF1 -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_FFT" c_th1f_fft :: Ptr RawTH1F -> Ptr RawTH1 -> CString -> IO (Ptr RawTH1) foreign import ccall safe "HROOTHistTH1F.h TH1F_fill1" c_th1f_fill1 :: Ptr RawTH1F -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_fill1w" c_th1f_fill1w :: Ptr RawTH1F -> CDouble -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_fillN1" c_th1f_filln1 :: Ptr RawTH1F -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_FillRandom" c_th1f_fillrandom :: Ptr RawTH1F -> Ptr RawTH1 -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_FindBin" c_th1f_findbin :: Ptr RawTH1F -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_FindFixBin" c_th1f_findfixbin :: Ptr RawTH1F -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_FindFirstBinAbove" c_th1f_findfirstbinabove :: Ptr RawTH1F -> CDouble -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_FindLastBinAbove" c_th1f_findlastbinabove :: Ptr RawTH1F -> CDouble -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_Fit" c_th1f_fit :: Ptr RawTH1F -> Ptr RawTF1 -> CString -> CString -> CDouble -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_FitPanelTH1" c_th1f_fitpanelth1 :: Ptr RawTH1F -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_getNdivisionA" c_th1f_getndivisiona :: Ptr RawTH1F -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_getAxisColorA" c_th1f_getaxiscolora :: Ptr RawTH1F -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_getLabelColorA" c_th1f_getlabelcolora :: Ptr RawTH1F -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_getLabelFontA" c_th1f_getlabelfonta :: Ptr RawTH1F -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_getLabelOffsetA" c_th1f_getlabeloffseta :: Ptr RawTH1F -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_getLabelSizeA" c_th1f_getlabelsizea :: Ptr RawTH1F -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_getTitleFontA" c_th1f_gettitlefonta :: Ptr RawTH1F -> CString -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_getTitleOffsetA" c_th1f_gettitleoffseta :: Ptr RawTH1F -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_getTitleSizeA" c_th1f_gettitlesizea :: Ptr RawTH1F -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_getTickLengthA" c_th1f_getticklengtha :: Ptr RawTH1F -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBarOffset" c_th1f_getbaroffset :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBarWidth" c_th1f_getbarwidth :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetContour" c_th1f_getcontour :: Ptr RawTH1F -> (Ptr CDouble) -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetContourLevel" c_th1f_getcontourlevel :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetContourLevelPad" c_th1f_getcontourlevelpad :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBin" c_th1f_getbin :: Ptr RawTH1F -> CInt -> CInt -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBinCenter" c_th1f_getbincenter :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBinContent1" c_th1f_getbincontent1 :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBinContent2" c_th1f_getbincontent2 :: Ptr RawTH1F -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBinContent3" c_th1f_getbincontent3 :: Ptr RawTH1F -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBinError1" c_th1f_getbinerror1 :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBinError2" c_th1f_getbinerror2 :: Ptr RawTH1F -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBinError3" c_th1f_getbinerror3 :: Ptr RawTH1F -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBinLowEdge" c_th1f_getbinlowedge :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetBinWidth" c_th1f_getbinwidth :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetCellContent" c_th1f_getcellcontent :: Ptr RawTH1F -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetCellError" c_th1f_getcellerror :: Ptr RawTH1F -> CInt -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetEntries" c_th1f_getentries :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetEffectiveEntries" c_th1f_geteffectiveentries :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetFunction" c_th1f_getfunction :: Ptr RawTH1F -> CString -> IO (Ptr RawTF1) foreign import ccall safe "HROOTHistTH1F.h TH1F_GetDimension" c_th1f_getdimension :: Ptr RawTH1F -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetKurtosis" c_th1f_getkurtosis :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetLowEdge" c_th1f_getlowedge :: Ptr RawTH1F -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_getMaximumTH1" c_th1f_getmaximumth1 :: Ptr RawTH1F -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetMaximumBin" c_th1f_getmaximumbin :: Ptr RawTH1F -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetMaximumStored" c_th1f_getmaximumstored :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_getMinimumTH1" c_th1f_getminimumth1 :: Ptr RawTH1F -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetMinimumBin" c_th1f_getminimumbin :: Ptr RawTH1F -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetMinimumStored" c_th1f_getminimumstored :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetMean" c_th1f_getmean :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetMeanError" c_th1f_getmeanerror :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetNbinsX" c_th1f_getnbinsx :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetNbinsY" c_th1f_getnbinsy :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetNbinsZ" c_th1f_getnbinsz :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_getQuantilesTH1" c_th1f_getquantilesth1 :: Ptr RawTH1F -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetRandom" c_th1f_getrandom :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetStats" c_th1f_getstats :: Ptr RawTH1F -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_GetSumOfWeights" c_th1f_getsumofweights :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetSumw2" c_th1f_getsumw2 :: Ptr RawTH1F -> IO (Ptr RawTArrayD) foreign import ccall safe "HROOTHistTH1F.h TH1F_GetSumw2N" c_th1f_getsumw2n :: Ptr RawTH1F -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetRMS" c_th1f_getrms :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetRMSError" c_th1f_getrmserror :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_GetSkewness" c_th1f_getskewness :: Ptr RawTH1F -> CInt -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_integral1" c_th1f_integral1 :: Ptr RawTH1F -> CInt -> CInt -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_interpolate1" c_th1f_interpolate1 :: Ptr RawTH1F -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_interpolate2" c_th1f_interpolate2 :: Ptr RawTH1F -> CDouble -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_interpolate3" c_th1f_interpolate3 :: Ptr RawTH1F -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_KolmogorovTest" c_th1f_kolmogorovtest :: Ptr RawTH1F -> Ptr RawTH1 -> CString -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_LabelsDeflate" c_th1f_labelsdeflate :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_LabelsInflate" c_th1f_labelsinflate :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_LabelsOption" c_th1f_labelsoption :: Ptr RawTH1F -> CString -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_multiflyF" c_th1f_multiflyf :: Ptr RawTH1F -> Ptr RawTF1 -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Multiply" c_th1f_multiply :: Ptr RawTH1F -> Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_PutStats" c_th1f_putstats :: Ptr RawTH1F -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Rebin" c_th1f_rebin :: Ptr RawTH1F -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1) foreign import ccall safe "HROOTHistTH1F.h TH1F_RebinAxis" c_th1f_rebinaxis :: Ptr RawTH1F -> CDouble -> Ptr RawTAxis -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Rebuild" c_th1f_rebuild :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_RecursiveRemove" c_th1f_recursiveremove :: Ptr RawTH1F -> Ptr RawTObject -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Reset" c_th1f_reset :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_ResetStats" c_th1f_resetstats :: Ptr RawTH1F -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Scale" c_th1f_scale :: Ptr RawTH1F -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setAxisColorA" c_th1f_setaxiscolora :: Ptr RawTH1F -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetAxisRange" c_th1f_setaxisrange :: Ptr RawTH1F -> CDouble -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetBarOffset" c_th1f_setbaroffset :: Ptr RawTH1F -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetBarWidth" c_th1f_setbarwidth :: Ptr RawTH1F -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setBinContent1" c_th1f_setbincontent1 :: Ptr RawTH1F -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setBinContent2" c_th1f_setbincontent2 :: Ptr RawTH1F -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setBinContent3" c_th1f_setbincontent3 :: Ptr RawTH1F -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setBinError1" c_th1f_setbinerror1 :: Ptr RawTH1F -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setBinError2" c_th1f_setbinerror2 :: Ptr RawTH1F -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setBinError3" c_th1f_setbinerror3 :: Ptr RawTH1F -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setBins1" c_th1f_setbins1 :: Ptr RawTH1F -> CInt -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setBins2" c_th1f_setbins2 :: Ptr RawTH1F -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setBins3" c_th1f_setbins3 :: Ptr RawTH1F -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetBinsLength" c_th1f_setbinslength :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetBuffer" c_th1f_setbuffer :: Ptr RawTH1F -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetCellContent" c_th1f_setcellcontent :: Ptr RawTH1F -> CInt -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetContent" c_th1f_setcontent :: Ptr RawTH1F -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetContour" c_th1f_setcontour :: Ptr RawTH1F -> CInt -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetContourLevel" c_th1f_setcontourlevel :: Ptr RawTH1F -> CInt -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetDirectory" c_th1f_setdirectory :: Ptr RawTH1F -> Ptr RawTDirectory -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetEntries" c_th1f_setentries :: Ptr RawTH1F -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetError" c_th1f_seterror :: Ptr RawTH1F -> (Ptr CDouble) -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setLabelColorA" c_th1f_setlabelcolora :: Ptr RawTH1F -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setLabelSizeA" c_th1f_setlabelsizea :: Ptr RawTH1F -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setLabelFontA" c_th1f_setlabelfonta :: Ptr RawTH1F -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_setLabelOffsetA" c_th1f_setlabeloffseta :: Ptr RawTH1F -> CDouble -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetMaximum" c_th1f_setmaximum :: Ptr RawTH1F -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetMinimum" c_th1f_setminimum :: Ptr RawTH1F -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetNormFactor" c_th1f_setnormfactor :: Ptr RawTH1F -> CDouble -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetStats" c_th1f_setstats :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetOption" c_th1f_setoption :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetXTitle" c_th1f_setxtitle :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetYTitle" c_th1f_setytitle :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetZTitle" c_th1f_setztitle :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_ShowBackground" c_th1f_showbackground :: Ptr RawTH1F -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall safe "HROOTHistTH1F.h TH1F_ShowPeaks" c_th1f_showpeaks :: Ptr RawTH1F -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_Smooth" c_th1f_smooth :: Ptr RawTH1F -> CInt -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Sumw2" c_th1f_sumw2 :: Ptr RawTH1F -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetName" c_th1f_setname :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetNameTitle" c_th1f_setnametitle :: Ptr RawTH1F -> CString -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetTitle" c_th1f_settitle :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_GetLineColor" c_th1f_getlinecolor :: Ptr RawTH1F -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetLineStyle" c_th1f_getlinestyle :: Ptr RawTH1F -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetLineWidth" c_th1f_getlinewidth :: Ptr RawTH1F -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_ResetAttLine" c_th1f_resetattline :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetLineAttributes" c_th1f_setlineattributes :: Ptr RawTH1F -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetLineColor" c_th1f_setlinecolor :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetLineStyle" c_th1f_setlinestyle :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetLineWidth" c_th1f_setlinewidth :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetFillColor" c_th1f_setfillcolor :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetFillStyle" c_th1f_setfillstyle :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_GetMarkerColor" c_th1f_getmarkercolor :: Ptr RawTH1F -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetMarkerStyle" c_th1f_getmarkerstyle :: Ptr RawTH1F -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_GetMarkerSize" c_th1f_getmarkersize :: Ptr RawTH1F -> IO CDouble foreign import ccall safe "HROOTHistTH1F.h TH1F_ResetAttMarker" c_th1f_resetattmarker :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetMarkerAttributes" c_th1f_setmarkerattributes :: Ptr RawTH1F -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetMarkerColor" c_th1f_setmarkercolor :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetMarkerStyle" c_th1f_setmarkerstyle :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SetMarkerSize" c_th1f_setmarkersize :: Ptr RawTH1F -> CInt -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Draw" c_th1f_draw :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_FindObject" c_th1f_findobject :: Ptr RawTH1F -> CString -> IO (Ptr RawTObject) foreign import ccall safe "HROOTHistTH1F.h TH1F_GetName" c_th1f_getname :: Ptr RawTH1F -> IO CString foreign import ccall safe "HROOTHistTH1F.h TH1F_IsA" c_th1f_isa :: Ptr RawTH1F -> IO (Ptr RawTClass) foreign import ccall safe "HROOTHistTH1F.h TH1F_Paint" c_th1f_paint :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_printObj" c_th1f_printobj :: Ptr RawTH1F -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_SaveAs" c_th1f_saveas :: Ptr RawTH1F -> CString -> CString -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_Write" c_th1f_write :: Ptr RawTH1F -> CString -> CInt -> CInt -> IO CInt foreign import ccall safe "HROOTHistTH1F.h TH1F_delete" c_th1f_delete :: Ptr RawTH1F -> IO () foreign import ccall safe "HROOTHistTH1F.h TH1F_newTH1F" c_th1f_newth1f :: CString -> CString -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH1F)