{-# LANGUAGE ForeignFunctionInterface #-} -- module HROOT.Class.FFI where module HROOT.Hist.TH2F.FFI where import Foreign.C import Foreign.Ptr -- import HROOT.Class.Interface -- #include "" import HROOT.Hist.TH2F.RawType import HROOT.Hist.TH1D.RawType import HROOT.Hist.TH2.RawType import HROOT.Hist.TH1.RawType import HROOT.Hist.TF1.RawType import HROOT.Core.TObjArray.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 "HROOTHistTH2F.h" foreign import ccall "HROOTHistTH2F.h TH2F_fill2" c_th2f_fill2 :: (Ptr RawTH2F) -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_fill2w" c_th2f_fill2w :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_fillN2" c_th2f_filln2 :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_fillRandom2" c_th2f_fillrandom2 :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_findFirstBinAbove2" c_th2f_findfirstbinabove2 :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_findLastBinAbove2" c_th2f_findlastbinabove2 :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_FitSlicesX" c_th2f_fitslicesx :: (Ptr RawTH2F) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_FitSlicesY" c_th2f_fitslicesy :: (Ptr RawTH2F) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_getCorrelationFactor2" c_th2f_getcorrelationfactor2 :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_getCovariance2" c_th2f_getcovariance2 :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_integral2" c_th2f_integral2 :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_rebinX2" c_th2f_rebinx2 :: (Ptr RawTH2F) -> CInt -> CString -> IO (Ptr RawTH2) foreign import ccall "HROOTHistTH2F.h TH2F_rebinY2" c_th2f_rebiny2 :: (Ptr RawTH2F) -> CInt -> CString -> IO (Ptr RawTH2) foreign import ccall "HROOTHistTH2F.h TH2F_Rebin2D" c_th2f_rebin2d :: (Ptr RawTH2F) -> CInt -> CInt -> CString -> IO (Ptr RawTH2) foreign import ccall "HROOTHistTH2F.h TH2F_SetShowProjectionX" c_th2f_setshowprojectionx :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetShowProjectionY" c_th2f_setshowprojectiony :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Add" c_th2f_add :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_AddBinContent" c_th2f_addbincontent :: (Ptr RawTH2F) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Chi2Test" c_th2f_chi2test :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_ComputeIntegral" c_th2f_computeintegral :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_DirectoryAutoAdd" c_th2f_directoryautoadd :: (Ptr RawTH2F) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Divide" c_th2f_divide :: (Ptr RawTH2F) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_drawCopyTH1" c_th2f_drawcopyth1 :: (Ptr RawTH2F) -> CString -> IO (Ptr RawTH2F) foreign import ccall "HROOTHistTH2F.h TH2F_DrawNormalized" c_th2f_drawnormalized :: (Ptr RawTH2F) -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH2F.h TH2F_drawPanelTH1" c_th2f_drawpanelth1 :: (Ptr RawTH2F) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_BufferEmpty" c_th2f_bufferempty :: (Ptr RawTH2F) -> CInt -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_evalF" c_th2f_evalf :: (Ptr RawTH2F) -> (Ptr RawTF1) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_FFT" c_th2f_fft :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH2F.h TH2F_fill1" c_th2f_fill1 :: (Ptr RawTH2F) -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_fill1w" c_th2f_fill1w :: (Ptr RawTH2F) -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_fillN1" c_th2f_filln1 :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_FillRandom" c_th2f_fillrandom :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_FindBin" c_th2f_findbin :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_FindFixBin" c_th2f_findfixbin :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_FindFirstBinAbove" c_th2f_findfirstbinabove :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_FindLastBinAbove" c_th2f_findlastbinabove :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_FitPanelTH1" c_th2f_fitpanelth1 :: (Ptr RawTH2F) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_getNdivisionA" c_th2f_getndivisiona :: (Ptr RawTH2F) -> CString -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_getAxisColorA" c_th2f_getaxiscolora :: (Ptr RawTH2F) -> CString -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_getLabelColorA" c_th2f_getlabelcolora :: (Ptr RawTH2F) -> CString -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_getLabelFontA" c_th2f_getlabelfonta :: (Ptr RawTH2F) -> CString -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_getLabelOffsetA" c_th2f_getlabeloffseta :: (Ptr RawTH2F) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_getLabelSizeA" c_th2f_getlabelsizea :: (Ptr RawTH2F) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_getTitleFontA" c_th2f_gettitlefonta :: (Ptr RawTH2F) -> CString -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_getTitleOffsetA" c_th2f_gettitleoffseta :: (Ptr RawTH2F) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_getTitleSizeA" c_th2f_gettitlesizea :: (Ptr RawTH2F) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_getTickLengthA" c_th2f_getticklengtha :: (Ptr RawTH2F) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBarOffset" c_th2f_getbaroffset :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBarWidth" c_th2f_getbarwidth :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetContour" c_th2f_getcontour :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetContourLevel" c_th2f_getcontourlevel :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetContourLevelPad" c_th2f_getcontourlevelpad :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBin" c_th2f_getbin :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetBinCenter" c_th2f_getbincenter :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBinContent1" c_th2f_getbincontent1 :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBinContent2" c_th2f_getbincontent2 :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBinContent3" c_th2f_getbincontent3 :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBinError1" c_th2f_getbinerror1 :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBinError2" c_th2f_getbinerror2 :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBinError3" c_th2f_getbinerror3 :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBinLowEdge" c_th2f_getbinlowedge :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetBinWidth" c_th2f_getbinwidth :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetCellContent" c_th2f_getcellcontent :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetCellError" c_th2f_getcellerror :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetEntries" c_th2f_getentries :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetEffectiveEntries" c_th2f_geteffectiveentries :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetFunction" c_th2f_getfunction :: (Ptr RawTH2F) -> CString -> IO (Ptr RawTF1) foreign import ccall "HROOTHistTH2F.h TH2F_GetDimension" c_th2f_getdimension :: (Ptr RawTH2F) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetKurtosis" c_th2f_getkurtosis :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetLowEdge" c_th2f_getlowedge :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_getMaximumTH1" c_th2f_getmaximumth1 :: (Ptr RawTH2F) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetMaximumBin" c_th2f_getmaximumbin :: (Ptr RawTH2F) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetMaximumStored" c_th2f_getmaximumstored :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_getMinimumTH1" c_th2f_getminimumth1 :: (Ptr RawTH2F) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetMinimumBin" c_th2f_getminimumbin :: (Ptr RawTH2F) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetMinimumStored" c_th2f_getminimumstored :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetMean" c_th2f_getmean :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetMeanError" c_th2f_getmeanerror :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetNbinsX" c_th2f_getnbinsx :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetNbinsY" c_th2f_getnbinsy :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetNbinsZ" c_th2f_getnbinsz :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_getQuantilesTH1" c_th2f_getquantilesth1 :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetRandom" c_th2f_getrandom :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetStats" c_th2f_getstats :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_GetSumOfWeights" c_th2f_getsumofweights :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetSumw2" c_th2f_getsumw2 :: (Ptr RawTH2F) -> IO (Ptr RawTArrayD) foreign import ccall "HROOTHistTH2F.h TH2F_GetSumw2N" c_th2f_getsumw2n :: (Ptr RawTH2F) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetRMS" c_th2f_getrms :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetRMSError" c_th2f_getrmserror :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_GetSkewness" c_th2f_getskewness :: (Ptr RawTH2F) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_integral1" c_th2f_integral1 :: (Ptr RawTH2F) -> CInt -> CInt -> CString -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_interpolate1" c_th2f_interpolate1 :: (Ptr RawTH2F) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_interpolate2" c_th2f_interpolate2 :: (Ptr RawTH2F) -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_interpolate3" c_th2f_interpolate3 :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_KolmogorovTest" c_th2f_kolmogorovtest :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_LabelsDeflate" c_th2f_labelsdeflate :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_LabelsInflate" c_th2f_labelsinflate :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_LabelsOption" c_th2f_labelsoption :: (Ptr RawTH2F) -> CString -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_multiflyF" c_th2f_multiflyf :: (Ptr RawTH2F) -> (Ptr RawTF1) -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Multiply" c_th2f_multiply :: (Ptr RawTH2F) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_PutStats" c_th2f_putstats :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Rebin" c_th2f_rebin :: (Ptr RawTH2F) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH2F.h TH2F_RebinAxis" c_th2f_rebinaxis :: (Ptr RawTH2F) -> CDouble -> (Ptr RawTAxis) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Rebuild" c_th2f_rebuild :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_RecursiveRemove" c_th2f_recursiveremove :: (Ptr RawTH2F) -> (Ptr RawTObject) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Reset" c_th2f_reset :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_ResetStats" c_th2f_resetstats :: (Ptr RawTH2F) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Scale" c_th2f_scale :: (Ptr RawTH2F) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setAxisColorA" c_th2f_setaxiscolora :: (Ptr RawTH2F) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetAxisRange" c_th2f_setaxisrange :: (Ptr RawTH2F) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetBarOffset" c_th2f_setbaroffset :: (Ptr RawTH2F) -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetBarWidth" c_th2f_setbarwidth :: (Ptr RawTH2F) -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setBinContent1" c_th2f_setbincontent1 :: (Ptr RawTH2F) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setBinContent2" c_th2f_setbincontent2 :: (Ptr RawTH2F) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setBinContent3" c_th2f_setbincontent3 :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setBinError1" c_th2f_setbinerror1 :: (Ptr RawTH2F) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setBinError2" c_th2f_setbinerror2 :: (Ptr RawTH2F) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setBinError3" c_th2f_setbinerror3 :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setBins1" c_th2f_setbins1 :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setBins2" c_th2f_setbins2 :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setBins3" c_th2f_setbins3 :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetBinsLength" c_th2f_setbinslength :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetBuffer" c_th2f_setbuffer :: (Ptr RawTH2F) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetCellContent" c_th2f_setcellcontent :: (Ptr RawTH2F) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetContent" c_th2f_setcontent :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetContour" c_th2f_setcontour :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetContourLevel" c_th2f_setcontourlevel :: (Ptr RawTH2F) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetDirectory" c_th2f_setdirectory :: (Ptr RawTH2F) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetEntries" c_th2f_setentries :: (Ptr RawTH2F) -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetError" c_th2f_seterror :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setLabelColorA" c_th2f_setlabelcolora :: (Ptr RawTH2F) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setLabelSizeA" c_th2f_setlabelsizea :: (Ptr RawTH2F) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setLabelFontA" c_th2f_setlabelfonta :: (Ptr RawTH2F) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_setLabelOffsetA" c_th2f_setlabeloffseta :: (Ptr RawTH2F) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetMaximum" c_th2f_setmaximum :: (Ptr RawTH2F) -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetMinimum" c_th2f_setminimum :: (Ptr RawTH2F) -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetNormFactor" c_th2f_setnormfactor :: (Ptr RawTH2F) -> CDouble -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetStats" c_th2f_setstats :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetOption" c_th2f_setoption :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetXTitle" c_th2f_setxtitle :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetYTitle" c_th2f_setytitle :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetZTitle" c_th2f_setztitle :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_ShowBackground" c_th2f_showbackground :: (Ptr RawTH2F) -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH2F.h TH2F_ShowPeaks" c_th2f_showpeaks :: (Ptr RawTH2F) -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_Smooth" c_th2f_smooth :: (Ptr RawTH2F) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Sumw2" c_th2f_sumw2 :: (Ptr RawTH2F) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Draw" c_th2f_draw :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_FindObject" c_th2f_findobject :: (Ptr RawTH2F) -> CString -> IO (Ptr RawTObject) foreign import ccall "HROOTHistTH2F.h TH2F_GetName" c_th2f_getname :: (Ptr RawTH2F) -> IO CString foreign import ccall "HROOTHistTH2F.h TH2F_IsA" c_th2f_isa :: (Ptr RawTH2F) -> IO (Ptr RawTClass) foreign import ccall "HROOTHistTH2F.h TH2F_Paint" c_th2f_paint :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_printObj" c_th2f_printobj :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SaveAs" c_th2f_saveas :: (Ptr RawTH2F) -> CString -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_Write" c_th2f_write :: (Ptr RawTH2F) -> CString -> CInt -> CInt -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetLineColor" c_th2f_getlinecolor :: (Ptr RawTH2F) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetLineStyle" c_th2f_getlinestyle :: (Ptr RawTH2F) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetLineWidth" c_th2f_getlinewidth :: (Ptr RawTH2F) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_ResetAttLine" c_th2f_resetattline :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetLineAttributes" c_th2f_setlineattributes :: (Ptr RawTH2F) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetLineColor" c_th2f_setlinecolor :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetLineStyle" c_th2f_setlinestyle :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetLineWidth" c_th2f_setlinewidth :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetFillColor" c_th2f_setfillcolor :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetFillStyle" c_th2f_setfillstyle :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_GetMarkerColor" c_th2f_getmarkercolor :: (Ptr RawTH2F) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetMarkerStyle" c_th2f_getmarkerstyle :: (Ptr RawTH2F) -> IO CInt foreign import ccall "HROOTHistTH2F.h TH2F_GetMarkerSize" c_th2f_getmarkersize :: (Ptr RawTH2F) -> IO CDouble foreign import ccall "HROOTHistTH2F.h TH2F_ResetAttMarker" c_th2f_resetattmarker :: (Ptr RawTH2F) -> CString -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetMarkerAttributes" c_th2f_setmarkerattributes :: (Ptr RawTH2F) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetMarkerColor" c_th2f_setmarkercolor :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetMarkerStyle" c_th2f_setmarkerstyle :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_SetMarkerSize" c_th2f_setmarkersize :: (Ptr RawTH2F) -> CInt -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_delete" c_th2f_delete :: (Ptr RawTH2F) -> IO () foreign import ccall "HROOTHistTH2F.h TH2F_newTH2F" c_th2f_newth2f :: CString -> CString -> CInt -> CDouble -> CDouble -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH2F)