{-# LANGUAGE ForeignFunctionInterface #-} -- module HROOT.Class.FFI where module HROOT.Hist.TH3D.FFI where import Foreign.C import Foreign.Ptr -- import HROOT.Class.Interface -- #include "" import HROOT.Hist.TH3D.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 "HROOTHistTH3D.h" foreign import ccall "HROOTHistTH3D.h TH3D_fill3" c_th3d_fill3 :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_fill3w" c_th3d_fill3w :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_FitSlicesZ" c_th3d_fitslicesz :: (Ptr RawTH3D) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_getCorrelationFactor3" c_th3d_getcorrelationfactor3 :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_getCovariance3" c_th3d_getcovariance3 :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_rebinX3" c_th3d_rebinx3 :: (Ptr RawTH3D) -> CInt -> CString -> IO (Ptr RawTH3) foreign import ccall "HROOTHistTH3D.h TH3D_rebinY3" c_th3d_rebiny3 :: (Ptr RawTH3D) -> CInt -> CString -> IO (Ptr RawTH3) foreign import ccall "HROOTHistTH3D.h TH3D_rebinZ3" c_th3d_rebinz3 :: (Ptr RawTH3D) -> CInt -> CString -> IO (Ptr RawTH3) foreign import ccall "HROOTHistTH3D.h TH3D_Rebin3D" c_th3d_rebin3d :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3) foreign import ccall "HROOTHistTH3D.h TH3D_Add" c_th3d_add :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_AddBinContent" c_th3d_addbincontent :: (Ptr RawTH3D) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Chi2Test" c_th3d_chi2test :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_ComputeIntegral" c_th3d_computeintegral :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_DirectoryAutoAdd" c_th3d_directoryautoadd :: (Ptr RawTH3D) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Divide" c_th3d_divide :: (Ptr RawTH3D) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_drawCopyTH1" c_th3d_drawcopyth1 :: (Ptr RawTH3D) -> CString -> IO (Ptr RawTH3D) foreign import ccall "HROOTHistTH3D.h TH3D_DrawNormalized" c_th3d_drawnormalized :: (Ptr RawTH3D) -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH3D.h TH3D_drawPanelTH1" c_th3d_drawpanelth1 :: (Ptr RawTH3D) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_BufferEmpty" c_th3d_bufferempty :: (Ptr RawTH3D) -> CInt -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_evalF" c_th3d_evalf :: (Ptr RawTH3D) -> (Ptr RawTF1) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_FFT" c_th3d_fft :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH3D.h TH3D_fill1" c_th3d_fill1 :: (Ptr RawTH3D) -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_fill1w" c_th3d_fill1w :: (Ptr RawTH3D) -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_fillN1" c_th3d_filln1 :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_FillRandom" c_th3d_fillrandom :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_FindBin" c_th3d_findbin :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_FindFixBin" c_th3d_findfixbin :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_FindFirstBinAbove" c_th3d_findfirstbinabove :: (Ptr RawTH3D) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_FindLastBinAbove" c_th3d_findlastbinabove :: (Ptr RawTH3D) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_FitPanelTH1" c_th3d_fitpanelth1 :: (Ptr RawTH3D) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_getNdivisionA" c_th3d_getndivisiona :: (Ptr RawTH3D) -> CString -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_getAxisColorA" c_th3d_getaxiscolora :: (Ptr RawTH3D) -> CString -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_getLabelColorA" c_th3d_getlabelcolora :: (Ptr RawTH3D) -> CString -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_getLabelFontA" c_th3d_getlabelfonta :: (Ptr RawTH3D) -> CString -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_getLabelOffsetA" c_th3d_getlabeloffseta :: (Ptr RawTH3D) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_getLabelSizeA" c_th3d_getlabelsizea :: (Ptr RawTH3D) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_getTitleFontA" c_th3d_gettitlefonta :: (Ptr RawTH3D) -> CString -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_getTitleOffsetA" c_th3d_gettitleoffseta :: (Ptr RawTH3D) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_getTitleSizeA" c_th3d_gettitlesizea :: (Ptr RawTH3D) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_getTickLengthA" c_th3d_getticklengtha :: (Ptr RawTH3D) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBarOffset" c_th3d_getbaroffset :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBarWidth" c_th3d_getbarwidth :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetContour" c_th3d_getcontour :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetContourLevel" c_th3d_getcontourlevel :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetContourLevelPad" c_th3d_getcontourlevelpad :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBin" c_th3d_getbin :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetBinCenter" c_th3d_getbincenter :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBinContent1" c_th3d_getbincontent1 :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBinContent2" c_th3d_getbincontent2 :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBinContent3" c_th3d_getbincontent3 :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBinError1" c_th3d_getbinerror1 :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBinError2" c_th3d_getbinerror2 :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBinError3" c_th3d_getbinerror3 :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBinLowEdge" c_th3d_getbinlowedge :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetBinWidth" c_th3d_getbinwidth :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetCellContent" c_th3d_getcellcontent :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetCellError" c_th3d_getcellerror :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetEntries" c_th3d_getentries :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetEffectiveEntries" c_th3d_geteffectiveentries :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetFunction" c_th3d_getfunction :: (Ptr RawTH3D) -> CString -> IO (Ptr RawTF1) foreign import ccall "HROOTHistTH3D.h TH3D_GetDimension" c_th3d_getdimension :: (Ptr RawTH3D) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetKurtosis" c_th3d_getkurtosis :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetLowEdge" c_th3d_getlowedge :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_getMaximumTH1" c_th3d_getmaximumth1 :: (Ptr RawTH3D) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetMaximumBin" c_th3d_getmaximumbin :: (Ptr RawTH3D) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetMaximumStored" c_th3d_getmaximumstored :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_getMinimumTH1" c_th3d_getminimumth1 :: (Ptr RawTH3D) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetMinimumBin" c_th3d_getminimumbin :: (Ptr RawTH3D) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetMinimumStored" c_th3d_getminimumstored :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetMean" c_th3d_getmean :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetMeanError" c_th3d_getmeanerror :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetNbinsX" c_th3d_getnbinsx :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetNbinsY" c_th3d_getnbinsy :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetNbinsZ" c_th3d_getnbinsz :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_getQuantilesTH1" c_th3d_getquantilesth1 :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetRandom" c_th3d_getrandom :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetStats" c_th3d_getstats :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_GetSumOfWeights" c_th3d_getsumofweights :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetSumw2" c_th3d_getsumw2 :: (Ptr RawTH3D) -> IO (Ptr RawTArrayD) foreign import ccall "HROOTHistTH3D.h TH3D_GetSumw2N" c_th3d_getsumw2n :: (Ptr RawTH3D) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetRMS" c_th3d_getrms :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetRMSError" c_th3d_getrmserror :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_GetSkewness" c_th3d_getskewness :: (Ptr RawTH3D) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_integral1" c_th3d_integral1 :: (Ptr RawTH3D) -> CInt -> CInt -> CString -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_interpolate1" c_th3d_interpolate1 :: (Ptr RawTH3D) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_interpolate2" c_th3d_interpolate2 :: (Ptr RawTH3D) -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_interpolate3" c_th3d_interpolate3 :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_KolmogorovTest" c_th3d_kolmogorovtest :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CString -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_LabelsDeflate" c_th3d_labelsdeflate :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_LabelsInflate" c_th3d_labelsinflate :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_LabelsOption" c_th3d_labelsoption :: (Ptr RawTH3D) -> CString -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_multiflyF" c_th3d_multiflyf :: (Ptr RawTH3D) -> (Ptr RawTF1) -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Multiply" c_th3d_multiply :: (Ptr RawTH3D) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_PutStats" c_th3d_putstats :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Rebin" c_th3d_rebin :: (Ptr RawTH3D) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH3D.h TH3D_RebinAxis" c_th3d_rebinaxis :: (Ptr RawTH3D) -> CDouble -> (Ptr RawTAxis) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Rebuild" c_th3d_rebuild :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_RecursiveRemove" c_th3d_recursiveremove :: (Ptr RawTH3D) -> (Ptr RawTObject) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Reset" c_th3d_reset :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_ResetStats" c_th3d_resetstats :: (Ptr RawTH3D) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Scale" c_th3d_scale :: (Ptr RawTH3D) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setAxisColorA" c_th3d_setaxiscolora :: (Ptr RawTH3D) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetAxisRange" c_th3d_setaxisrange :: (Ptr RawTH3D) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetBarOffset" c_th3d_setbaroffset :: (Ptr RawTH3D) -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetBarWidth" c_th3d_setbarwidth :: (Ptr RawTH3D) -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setBinContent1" c_th3d_setbincontent1 :: (Ptr RawTH3D) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setBinContent2" c_th3d_setbincontent2 :: (Ptr RawTH3D) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setBinContent3" c_th3d_setbincontent3 :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setBinError1" c_th3d_setbinerror1 :: (Ptr RawTH3D) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setBinError2" c_th3d_setbinerror2 :: (Ptr RawTH3D) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setBinError3" c_th3d_setbinerror3 :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setBins1" c_th3d_setbins1 :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setBins2" c_th3d_setbins2 :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setBins3" c_th3d_setbins3 :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetBinsLength" c_th3d_setbinslength :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetBuffer" c_th3d_setbuffer :: (Ptr RawTH3D) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetCellContent" c_th3d_setcellcontent :: (Ptr RawTH3D) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetContent" c_th3d_setcontent :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetContour" c_th3d_setcontour :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetContourLevel" c_th3d_setcontourlevel :: (Ptr RawTH3D) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetDirectory" c_th3d_setdirectory :: (Ptr RawTH3D) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetEntries" c_th3d_setentries :: (Ptr RawTH3D) -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetError" c_th3d_seterror :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setLabelColorA" c_th3d_setlabelcolora :: (Ptr RawTH3D) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setLabelSizeA" c_th3d_setlabelsizea :: (Ptr RawTH3D) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setLabelFontA" c_th3d_setlabelfonta :: (Ptr RawTH3D) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_setLabelOffsetA" c_th3d_setlabeloffseta :: (Ptr RawTH3D) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetMaximum" c_th3d_setmaximum :: (Ptr RawTH3D) -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetMinimum" c_th3d_setminimum :: (Ptr RawTH3D) -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetNormFactor" c_th3d_setnormfactor :: (Ptr RawTH3D) -> CDouble -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetStats" c_th3d_setstats :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetOption" c_th3d_setoption :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetXTitle" c_th3d_setxtitle :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetYTitle" c_th3d_setytitle :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetZTitle" c_th3d_setztitle :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_ShowBackground" c_th3d_showbackground :: (Ptr RawTH3D) -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH3D.h TH3D_ShowPeaks" c_th3d_showpeaks :: (Ptr RawTH3D) -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_Smooth" c_th3d_smooth :: (Ptr RawTH3D) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Sumw2" c_th3d_sumw2 :: (Ptr RawTH3D) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Draw" c_th3d_draw :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_FindObject" c_th3d_findobject :: (Ptr RawTH3D) -> CString -> IO (Ptr RawTObject) foreign import ccall "HROOTHistTH3D.h TH3D_GetName" c_th3d_getname :: (Ptr RawTH3D) -> IO CString foreign import ccall "HROOTHistTH3D.h TH3D_IsA" c_th3d_isa :: (Ptr RawTH3D) -> IO (Ptr RawTClass) foreign import ccall "HROOTHistTH3D.h TH3D_Paint" c_th3d_paint :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_printObj" c_th3d_printobj :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SaveAs" c_th3d_saveas :: (Ptr RawTH3D) -> CString -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_Write" c_th3d_write :: (Ptr RawTH3D) -> CString -> CInt -> CInt -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetLineColor" c_th3d_getlinecolor :: (Ptr RawTH3D) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetLineStyle" c_th3d_getlinestyle :: (Ptr RawTH3D) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetLineWidth" c_th3d_getlinewidth :: (Ptr RawTH3D) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_ResetAttLine" c_th3d_resetattline :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetLineAttributes" c_th3d_setlineattributes :: (Ptr RawTH3D) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetLineColor" c_th3d_setlinecolor :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetLineStyle" c_th3d_setlinestyle :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetLineWidth" c_th3d_setlinewidth :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetFillColor" c_th3d_setfillcolor :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetFillStyle" c_th3d_setfillstyle :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_GetMarkerColor" c_th3d_getmarkercolor :: (Ptr RawTH3D) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetMarkerStyle" c_th3d_getmarkerstyle :: (Ptr RawTH3D) -> IO CInt foreign import ccall "HROOTHistTH3D.h TH3D_GetMarkerSize" c_th3d_getmarkersize :: (Ptr RawTH3D) -> IO CDouble foreign import ccall "HROOTHistTH3D.h TH3D_ResetAttMarker" c_th3d_resetattmarker :: (Ptr RawTH3D) -> CString -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetMarkerAttributes" c_th3d_setmarkerattributes :: (Ptr RawTH3D) -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetMarkerColor" c_th3d_setmarkercolor :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetMarkerStyle" c_th3d_setmarkerstyle :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_SetMarkerSize" c_th3d_setmarkersize :: (Ptr RawTH3D) -> CInt -> IO () foreign import ccall "HROOTHistTH3D.h TH3D_delete" c_th3d_delete :: (Ptr RawTH3D) -> IO ()