{-# LANGUAGE ForeignFunctionInterface #-} -- module HROOT.Class.FFI where module HROOT.Hist.TH3I.FFI where import Foreign.C import Foreign.Ptr -- import HROOT.Class.Interface -- #include "" import HROOT.Hist.TH3I.RawType import HROOT.Hist.TH1D.RawType import HROOT.Hist.TH1.RawType import HROOT.Hist.TH3.RawType import HROOT.Hist.TF1.RawType import HROOT.Core.TDirectory.RawType import HROOT.Core.TArrayD.RawType import HROOT.Hist.TAxis.RawType import HROOT.Core.TObject.RawType import HROOT.Core.TClass.RawType #include "HROOTHistTH3I.h" foreign import ccall "HROOTHistTH3I.h TH3I_fill3" c_th3i_fill3 :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_fill3w" c_th3i_fill3w :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_FitSlicesZ" c_th3i_fitslicesz :: (Ptr RawTH3I) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_getCorrelationFactor3" c_th3i_getcorrelationfactor3 :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_getCovariance3" c_th3i_getcovariance3 :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_rebinX3" c_th3i_rebinx3 :: (Ptr RawTH3I) -> CInt -> CString -> IO (Ptr RawTH3) foreign import ccall "HROOTHistTH3I.h TH3I_rebinY3" c_th3i_rebiny3 :: (Ptr RawTH3I) -> CInt -> CString -> IO (Ptr RawTH3) foreign import ccall "HROOTHistTH3I.h TH3I_rebinZ3" c_th3i_rebinz3 :: (Ptr RawTH3I) -> CInt -> CString -> IO (Ptr RawTH3) foreign import ccall "HROOTHistTH3I.h TH3I_Rebin3D" c_th3i_rebin3d :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3) foreign import ccall "HROOTHistTH3I.h TH3I_Add" c_th3i_add :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_AddBinContent" c_th3i_addbincontent :: (Ptr RawTH3I) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Chi2Test" c_th3i_chi2test :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_ComputeIntegral" c_th3i_computeintegral :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_DirectoryAutoAdd" c_th3i_directoryautoadd :: (Ptr RawTH3I) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Divide" c_th3i_divide :: (Ptr RawTH3I) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_drawCopyTH1" c_th3i_drawcopyth1 :: (Ptr RawTH3I) -> CString -> IO (Ptr RawTH3I) foreign import ccall "HROOTHistTH3I.h TH3I_DrawNormalized" c_th3i_drawnormalized :: (Ptr RawTH3I) -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH3I.h TH3I_drawPanelTH1" c_th3i_drawpanelth1 :: (Ptr RawTH3I) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_BufferEmpty" c_th3i_bufferempty :: (Ptr RawTH3I) -> CInt -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_evalF" c_th3i_evalf :: (Ptr RawTH3I) -> (Ptr RawTF1) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_FFT" c_th3i_fft :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH3I.h TH3I_fill1" c_th3i_fill1 :: (Ptr RawTH3I) -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_fill1w" c_th3i_fill1w :: (Ptr RawTH3I) -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_fillN1" c_th3i_filln1 :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_FillRandom" c_th3i_fillrandom :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_FindBin" c_th3i_findbin :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_FindFixBin" c_th3i_findfixbin :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_FindFirstBinAbove" c_th3i_findfirstbinabove :: (Ptr RawTH3I) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_FindLastBinAbove" c_th3i_findlastbinabove :: (Ptr RawTH3I) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_FitPanelTH1" c_th3i_fitpanelth1 :: (Ptr RawTH3I) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_getNdivisionA" c_th3i_getndivisiona :: (Ptr RawTH3I) -> CString -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_getAxisColorA" c_th3i_getaxiscolora :: (Ptr RawTH3I) -> CString -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_getLabelColorA" c_th3i_getlabelcolora :: (Ptr RawTH3I) -> CString -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_getLabelFontA" c_th3i_getlabelfonta :: (Ptr RawTH3I) -> CString -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_getLabelOffsetA" c_th3i_getlabeloffseta :: (Ptr RawTH3I) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_getLabelSizeA" c_th3i_getlabelsizea :: (Ptr RawTH3I) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_getTitleFontA" c_th3i_gettitlefonta :: (Ptr RawTH3I) -> CString -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_getTitleOffsetA" c_th3i_gettitleoffseta :: (Ptr RawTH3I) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_getTitleSizeA" c_th3i_gettitlesizea :: (Ptr RawTH3I) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_getTickLengthA" c_th3i_getticklengtha :: (Ptr RawTH3I) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBarOffset" c_th3i_getbaroffset :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBarWidth" c_th3i_getbarwidth :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetContour" c_th3i_getcontour :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetContourLevel" c_th3i_getcontourlevel :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetContourLevelPad" c_th3i_getcontourlevelpad :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBin" c_th3i_getbin :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetBinCenter" c_th3i_getbincenter :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBinContent1" c_th3i_getbincontent1 :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBinContent2" c_th3i_getbincontent2 :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBinContent3" c_th3i_getbincontent3 :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBinError1" c_th3i_getbinerror1 :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBinError2" c_th3i_getbinerror2 :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBinError3" c_th3i_getbinerror3 :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBinLowEdge" c_th3i_getbinlowedge :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetBinWidth" c_th3i_getbinwidth :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetCellContent" c_th3i_getcellcontent :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetCellError" c_th3i_getcellerror :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetEntries" c_th3i_getentries :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetEffectiveEntries" c_th3i_geteffectiveentries :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetFunction" c_th3i_getfunction :: (Ptr RawTH3I) -> CString -> IO (Ptr RawTF1) foreign import ccall "HROOTHistTH3I.h TH3I_GetDimension" c_th3i_getdimension :: (Ptr RawTH3I) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetKurtosis" c_th3i_getkurtosis :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetLowEdge" c_th3i_getlowedge :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_getMaximumTH1" c_th3i_getmaximumth1 :: (Ptr RawTH3I) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetMaximumBin" c_th3i_getmaximumbin :: (Ptr RawTH3I) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetMaximumStored" c_th3i_getmaximumstored :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_getMinimumTH1" c_th3i_getminimumth1 :: (Ptr RawTH3I) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetMinimumBin" c_th3i_getminimumbin :: (Ptr RawTH3I) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetMinimumStored" c_th3i_getminimumstored :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetMean" c_th3i_getmean :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetMeanError" c_th3i_getmeanerror :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetNbinsX" c_th3i_getnbinsx :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetNbinsY" c_th3i_getnbinsy :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetNbinsZ" c_th3i_getnbinsz :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_getQuantilesTH1" c_th3i_getquantilesth1 :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetRandom" c_th3i_getrandom :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetStats" c_th3i_getstats :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_GetSumOfWeights" c_th3i_getsumofweights :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetSumw2" c_th3i_getsumw2 :: (Ptr RawTH3I) -> IO (Ptr RawTArrayD) foreign import ccall "HROOTHistTH3I.h TH3I_GetSumw2N" c_th3i_getsumw2n :: (Ptr RawTH3I) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetRMS" c_th3i_getrms :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetRMSError" c_th3i_getrmserror :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_GetSkewness" c_th3i_getskewness :: (Ptr RawTH3I) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_integral1" c_th3i_integral1 :: (Ptr RawTH3I) -> CInt -> CInt -> CString -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_interpolate1" c_th3i_interpolate1 :: (Ptr RawTH3I) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_interpolate2" c_th3i_interpolate2 :: (Ptr RawTH3I) -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_interpolate3" c_th3i_interpolate3 :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_KolmogorovTest" c_th3i_kolmogorovtest :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_LabelsDeflate" c_th3i_labelsdeflate :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_LabelsInflate" c_th3i_labelsinflate :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_LabelsOption" c_th3i_labelsoption :: (Ptr RawTH3I) -> CString -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_multiflyF" c_th3i_multiflyf :: (Ptr RawTH3I) -> (Ptr RawTF1) -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Multiply" c_th3i_multiply :: (Ptr RawTH3I) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_PutStats" c_th3i_putstats :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Rebin" c_th3i_rebin :: (Ptr RawTH3I) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH3I.h TH3I_RebinAxis" c_th3i_rebinaxis :: (Ptr RawTH3I) -> CDouble -> (Ptr RawTAxis) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Rebuild" c_th3i_rebuild :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_RecursiveRemove" c_th3i_recursiveremove :: (Ptr RawTH3I) -> (Ptr RawTObject) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Reset" c_th3i_reset :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_ResetStats" c_th3i_resetstats :: (Ptr RawTH3I) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Scale" c_th3i_scale :: (Ptr RawTH3I) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setAxisColorA" c_th3i_setaxiscolora :: (Ptr RawTH3I) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetAxisRange" c_th3i_setaxisrange :: (Ptr RawTH3I) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetBarOffset" c_th3i_setbaroffset :: (Ptr RawTH3I) -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetBarWidth" c_th3i_setbarwidth :: (Ptr RawTH3I) -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setBinContent1" c_th3i_setbincontent1 :: (Ptr RawTH3I) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setBinContent2" c_th3i_setbincontent2 :: (Ptr RawTH3I) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setBinContent3" c_th3i_setbincontent3 :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setBinError1" c_th3i_setbinerror1 :: (Ptr RawTH3I) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setBinError2" c_th3i_setbinerror2 :: (Ptr RawTH3I) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setBinError3" c_th3i_setbinerror3 :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setBins1" c_th3i_setbins1 :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setBins2" c_th3i_setbins2 :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setBins3" c_th3i_setbins3 :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetBinsLength" c_th3i_setbinslength :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetBuffer" c_th3i_setbuffer :: (Ptr RawTH3I) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetCellContent" c_th3i_setcellcontent :: (Ptr RawTH3I) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetContent" c_th3i_setcontent :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetContour" c_th3i_setcontour :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetContourLevel" c_th3i_setcontourlevel :: (Ptr RawTH3I) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetDirectory" c_th3i_setdirectory :: (Ptr RawTH3I) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetEntries" c_th3i_setentries :: (Ptr RawTH3I) -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetError" c_th3i_seterror :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setLabelColorA" c_th3i_setlabelcolora :: (Ptr RawTH3I) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setLabelSizeA" c_th3i_setlabelsizea :: (Ptr RawTH3I) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setLabelFontA" c_th3i_setlabelfonta :: (Ptr RawTH3I) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_setLabelOffsetA" c_th3i_setlabeloffseta :: (Ptr RawTH3I) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetMaximum" c_th3i_setmaximum :: (Ptr RawTH3I) -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetMinimum" c_th3i_setminimum :: (Ptr RawTH3I) -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetNormFactor" c_th3i_setnormfactor :: (Ptr RawTH3I) -> CDouble -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetStats" c_th3i_setstats :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetOption" c_th3i_setoption :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetXTitle" c_th3i_setxtitle :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetYTitle" c_th3i_setytitle :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetZTitle" c_th3i_setztitle :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_ShowBackground" c_th3i_showbackground :: (Ptr RawTH3I) -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH3I.h TH3I_ShowPeaks" c_th3i_showpeaks :: (Ptr RawTH3I) -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_Smooth" c_th3i_smooth :: (Ptr RawTH3I) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Sumw2" c_th3i_sumw2 :: (Ptr RawTH3I) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Draw" c_th3i_draw :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_FindObject" c_th3i_findobject :: (Ptr RawTH3I) -> CString -> IO (Ptr RawTObject) foreign import ccall "HROOTHistTH3I.h TH3I_GetName" c_th3i_getname :: (Ptr RawTH3I) -> IO CString foreign import ccall "HROOTHistTH3I.h TH3I_IsA" c_th3i_isa :: (Ptr RawTH3I) -> IO (Ptr RawTClass) foreign import ccall "HROOTHistTH3I.h TH3I_Paint" c_th3i_paint :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_printObj" c_th3i_printobj :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SaveAs" c_th3i_saveas :: (Ptr RawTH3I) -> CString -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_Write" c_th3i_write :: (Ptr RawTH3I) -> CString -> CInt -> CInt -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetLineColor" c_th3i_getlinecolor :: (Ptr RawTH3I) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetLineStyle" c_th3i_getlinestyle :: (Ptr RawTH3I) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetLineWidth" c_th3i_getlinewidth :: (Ptr RawTH3I) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_ResetAttLine" c_th3i_resetattline :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetLineAttributes" c_th3i_setlineattributes :: (Ptr RawTH3I) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetLineColor" c_th3i_setlinecolor :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetLineStyle" c_th3i_setlinestyle :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetLineWidth" c_th3i_setlinewidth :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetFillColor" c_th3i_setfillcolor :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetFillStyle" c_th3i_setfillstyle :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_GetMarkerColor" c_th3i_getmarkercolor :: (Ptr RawTH3I) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetMarkerStyle" c_th3i_getmarkerstyle :: (Ptr RawTH3I) -> IO CInt foreign import ccall "HROOTHistTH3I.h TH3I_GetMarkerSize" c_th3i_getmarkersize :: (Ptr RawTH3I) -> IO CDouble foreign import ccall "HROOTHistTH3I.h TH3I_ResetAttMarker" c_th3i_resetattmarker :: (Ptr RawTH3I) -> CString -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetMarkerAttributes" c_th3i_setmarkerattributes :: (Ptr RawTH3I) -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetMarkerColor" c_th3i_setmarkercolor :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetMarkerStyle" c_th3i_setmarkerstyle :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_SetMarkerSize" c_th3i_setmarkersize :: (Ptr RawTH3I) -> CInt -> IO () foreign import ccall "HROOTHistTH3I.h TH3I_delete" c_th3i_delete :: (Ptr RawTH3I) -> IO ()