{-# LANGUAGE ForeignFunctionInterface #-} -- module HROOT.Class.FFI where module HROOT.Hist.TH2C.FFI where import Foreign.C import Foreign.Ptr -- import HROOT.Class.Interface -- #include "" import HROOT.Hist.TH2C.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 "HROOTHistTH2C.h" foreign import ccall "HROOTHistTH2C.h TH2C_fill2" c_th2c_fill2 :: (Ptr RawTH2C) -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_fill2w" c_th2c_fill2w :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_fillN2" c_th2c_filln2 :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_fillRandom2" c_th2c_fillrandom2 :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_findFirstBinAbove2" c_th2c_findfirstbinabove2 :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_findLastBinAbove2" c_th2c_findlastbinabove2 :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_FitSlicesX" c_th2c_fitslicesx :: (Ptr RawTH2C) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_FitSlicesY" c_th2c_fitslicesy :: (Ptr RawTH2C) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_getCorrelationFactor2" c_th2c_getcorrelationfactor2 :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_getCovariance2" c_th2c_getcovariance2 :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_integral2" c_th2c_integral2 :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_rebinX2" c_th2c_rebinx2 :: (Ptr RawTH2C) -> CInt -> CString -> IO (Ptr RawTH2) foreign import ccall "HROOTHistTH2C.h TH2C_rebinY2" c_th2c_rebiny2 :: (Ptr RawTH2C) -> CInt -> CString -> IO (Ptr RawTH2) foreign import ccall "HROOTHistTH2C.h TH2C_Rebin2D" c_th2c_rebin2d :: (Ptr RawTH2C) -> CInt -> CInt -> CString -> IO (Ptr RawTH2) foreign import ccall "HROOTHistTH2C.h TH2C_SetShowProjectionX" c_th2c_setshowprojectionx :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetShowProjectionY" c_th2c_setshowprojectiony :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Add" c_th2c_add :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_AddBinContent" c_th2c_addbincontent :: (Ptr RawTH2C) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Chi2Test" c_th2c_chi2test :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_ComputeIntegral" c_th2c_computeintegral :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_DirectoryAutoAdd" c_th2c_directoryautoadd :: (Ptr RawTH2C) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Divide" c_th2c_divide :: (Ptr RawTH2C) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_drawCopyTH1" c_th2c_drawcopyth1 :: (Ptr RawTH2C) -> CString -> IO (Ptr RawTH2C) foreign import ccall "HROOTHistTH2C.h TH2C_DrawNormalized" c_th2c_drawnormalized :: (Ptr RawTH2C) -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH2C.h TH2C_drawPanelTH1" c_th2c_drawpanelth1 :: (Ptr RawTH2C) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_BufferEmpty" c_th2c_bufferempty :: (Ptr RawTH2C) -> CInt -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_evalF" c_th2c_evalf :: (Ptr RawTH2C) -> (Ptr RawTF1) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_FFT" c_th2c_fft :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH2C.h TH2C_fill1" c_th2c_fill1 :: (Ptr RawTH2C) -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_fill1w" c_th2c_fill1w :: (Ptr RawTH2C) -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_fillN1" c_th2c_filln1 :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_FillRandom" c_th2c_fillrandom :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_FindBin" c_th2c_findbin :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_FindFixBin" c_th2c_findfixbin :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_FindFirstBinAbove" c_th2c_findfirstbinabove :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_FindLastBinAbove" c_th2c_findlastbinabove :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_FitPanelTH1" c_th2c_fitpanelth1 :: (Ptr RawTH2C) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_getNdivisionA" c_th2c_getndivisiona :: (Ptr RawTH2C) -> CString -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_getAxisColorA" c_th2c_getaxiscolora :: (Ptr RawTH2C) -> CString -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_getLabelColorA" c_th2c_getlabelcolora :: (Ptr RawTH2C) -> CString -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_getLabelFontA" c_th2c_getlabelfonta :: (Ptr RawTH2C) -> CString -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_getLabelOffsetA" c_th2c_getlabeloffseta :: (Ptr RawTH2C) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_getLabelSizeA" c_th2c_getlabelsizea :: (Ptr RawTH2C) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_getTitleFontA" c_th2c_gettitlefonta :: (Ptr RawTH2C) -> CString -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_getTitleOffsetA" c_th2c_gettitleoffseta :: (Ptr RawTH2C) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_getTitleSizeA" c_th2c_gettitlesizea :: (Ptr RawTH2C) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_getTickLengthA" c_th2c_getticklengtha :: (Ptr RawTH2C) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBarOffset" c_th2c_getbaroffset :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBarWidth" c_th2c_getbarwidth :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetContour" c_th2c_getcontour :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetContourLevel" c_th2c_getcontourlevel :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetContourLevelPad" c_th2c_getcontourlevelpad :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBin" c_th2c_getbin :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetBinCenter" c_th2c_getbincenter :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBinContent1" c_th2c_getbincontent1 :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBinContent2" c_th2c_getbincontent2 :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBinContent3" c_th2c_getbincontent3 :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBinError1" c_th2c_getbinerror1 :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBinError2" c_th2c_getbinerror2 :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBinError3" c_th2c_getbinerror3 :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBinLowEdge" c_th2c_getbinlowedge :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetBinWidth" c_th2c_getbinwidth :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetCellContent" c_th2c_getcellcontent :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetCellError" c_th2c_getcellerror :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetEntries" c_th2c_getentries :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetEffectiveEntries" c_th2c_geteffectiveentries :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetFunction" c_th2c_getfunction :: (Ptr RawTH2C) -> CString -> IO (Ptr RawTF1) foreign import ccall "HROOTHistTH2C.h TH2C_GetDimension" c_th2c_getdimension :: (Ptr RawTH2C) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetKurtosis" c_th2c_getkurtosis :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetLowEdge" c_th2c_getlowedge :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_getMaximumTH1" c_th2c_getmaximumth1 :: (Ptr RawTH2C) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetMaximumBin" c_th2c_getmaximumbin :: (Ptr RawTH2C) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetMaximumStored" c_th2c_getmaximumstored :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_getMinimumTH1" c_th2c_getminimumth1 :: (Ptr RawTH2C) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetMinimumBin" c_th2c_getminimumbin :: (Ptr RawTH2C) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetMinimumStored" c_th2c_getminimumstored :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetMean" c_th2c_getmean :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetMeanError" c_th2c_getmeanerror :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetNbinsX" c_th2c_getnbinsx :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetNbinsY" c_th2c_getnbinsy :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetNbinsZ" c_th2c_getnbinsz :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_getQuantilesTH1" c_th2c_getquantilesth1 :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetRandom" c_th2c_getrandom :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetStats" c_th2c_getstats :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_GetSumOfWeights" c_th2c_getsumofweights :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetSumw2" c_th2c_getsumw2 :: (Ptr RawTH2C) -> IO (Ptr RawTArrayD) foreign import ccall "HROOTHistTH2C.h TH2C_GetSumw2N" c_th2c_getsumw2n :: (Ptr RawTH2C) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetRMS" c_th2c_getrms :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetRMSError" c_th2c_getrmserror :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_GetSkewness" c_th2c_getskewness :: (Ptr RawTH2C) -> CInt -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_integral1" c_th2c_integral1 :: (Ptr RawTH2C) -> CInt -> CInt -> CString -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_interpolate1" c_th2c_interpolate1 :: (Ptr RawTH2C) -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_interpolate2" c_th2c_interpolate2 :: (Ptr RawTH2C) -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_interpolate3" c_th2c_interpolate3 :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_KolmogorovTest" c_th2c_kolmogorovtest :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CString -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_LabelsDeflate" c_th2c_labelsdeflate :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_LabelsInflate" c_th2c_labelsinflate :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_LabelsOption" c_th2c_labelsoption :: (Ptr RawTH2C) -> CString -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_multiflyF" c_th2c_multiflyf :: (Ptr RawTH2C) -> (Ptr RawTF1) -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Multiply" c_th2c_multiply :: (Ptr RawTH2C) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_PutStats" c_th2c_putstats :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Rebin" c_th2c_rebin :: (Ptr RawTH2C) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH2C.h TH2C_RebinAxis" c_th2c_rebinaxis :: (Ptr RawTH2C) -> CDouble -> (Ptr RawTAxis) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Rebuild" c_th2c_rebuild :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_RecursiveRemove" c_th2c_recursiveremove :: (Ptr RawTH2C) -> (Ptr RawTObject) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Reset" c_th2c_reset :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_ResetStats" c_th2c_resetstats :: (Ptr RawTH2C) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Scale" c_th2c_scale :: (Ptr RawTH2C) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setAxisColorA" c_th2c_setaxiscolora :: (Ptr RawTH2C) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetAxisRange" c_th2c_setaxisrange :: (Ptr RawTH2C) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetBarOffset" c_th2c_setbaroffset :: (Ptr RawTH2C) -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetBarWidth" c_th2c_setbarwidth :: (Ptr RawTH2C) -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setBinContent1" c_th2c_setbincontent1 :: (Ptr RawTH2C) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setBinContent2" c_th2c_setbincontent2 :: (Ptr RawTH2C) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setBinContent3" c_th2c_setbincontent3 :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setBinError1" c_th2c_setbinerror1 :: (Ptr RawTH2C) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setBinError2" c_th2c_setbinerror2 :: (Ptr RawTH2C) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setBinError3" c_th2c_setbinerror3 :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setBins1" c_th2c_setbins1 :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setBins2" c_th2c_setbins2 :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setBins3" c_th2c_setbins3 :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetBinsLength" c_th2c_setbinslength :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetBuffer" c_th2c_setbuffer :: (Ptr RawTH2C) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetCellContent" c_th2c_setcellcontent :: (Ptr RawTH2C) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetContent" c_th2c_setcontent :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetContour" c_th2c_setcontour :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetContourLevel" c_th2c_setcontourlevel :: (Ptr RawTH2C) -> CInt -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetDirectory" c_th2c_setdirectory :: (Ptr RawTH2C) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetEntries" c_th2c_setentries :: (Ptr RawTH2C) -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetError" c_th2c_seterror :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setLabelColorA" c_th2c_setlabelcolora :: (Ptr RawTH2C) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setLabelSizeA" c_th2c_setlabelsizea :: (Ptr RawTH2C) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setLabelFontA" c_th2c_setlabelfonta :: (Ptr RawTH2C) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_setLabelOffsetA" c_th2c_setlabeloffseta :: (Ptr RawTH2C) -> CDouble -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetMaximum" c_th2c_setmaximum :: (Ptr RawTH2C) -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetMinimum" c_th2c_setminimum :: (Ptr RawTH2C) -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetNormFactor" c_th2c_setnormfactor :: (Ptr RawTH2C) -> CDouble -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetStats" c_th2c_setstats :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetOption" c_th2c_setoption :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetXTitle" c_th2c_setxtitle :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetYTitle" c_th2c_setytitle :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetZTitle" c_th2c_setztitle :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_ShowBackground" c_th2c_showbackground :: (Ptr RawTH2C) -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTHistTH2C.h TH2C_ShowPeaks" c_th2c_showpeaks :: (Ptr RawTH2C) -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_Smooth" c_th2c_smooth :: (Ptr RawTH2C) -> CInt -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Sumw2" c_th2c_sumw2 :: (Ptr RawTH2C) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Draw" c_th2c_draw :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_FindObject" c_th2c_findobject :: (Ptr RawTH2C) -> CString -> IO (Ptr RawTObject) foreign import ccall "HROOTHistTH2C.h TH2C_GetName" c_th2c_getname :: (Ptr RawTH2C) -> IO CString foreign import ccall "HROOTHistTH2C.h TH2C_IsA" c_th2c_isa :: (Ptr RawTH2C) -> IO (Ptr RawTClass) foreign import ccall "HROOTHistTH2C.h TH2C_Paint" c_th2c_paint :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_printObj" c_th2c_printobj :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SaveAs" c_th2c_saveas :: (Ptr RawTH2C) -> CString -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_Write" c_th2c_write :: (Ptr RawTH2C) -> CString -> CInt -> CInt -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetLineColor" c_th2c_getlinecolor :: (Ptr RawTH2C) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetLineStyle" c_th2c_getlinestyle :: (Ptr RawTH2C) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetLineWidth" c_th2c_getlinewidth :: (Ptr RawTH2C) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_ResetAttLine" c_th2c_resetattline :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetLineAttributes" c_th2c_setlineattributes :: (Ptr RawTH2C) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetLineColor" c_th2c_setlinecolor :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetLineStyle" c_th2c_setlinestyle :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetLineWidth" c_th2c_setlinewidth :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetFillColor" c_th2c_setfillcolor :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetFillStyle" c_th2c_setfillstyle :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_GetMarkerColor" c_th2c_getmarkercolor :: (Ptr RawTH2C) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetMarkerStyle" c_th2c_getmarkerstyle :: (Ptr RawTH2C) -> IO CInt foreign import ccall "HROOTHistTH2C.h TH2C_GetMarkerSize" c_th2c_getmarkersize :: (Ptr RawTH2C) -> IO CDouble foreign import ccall "HROOTHistTH2C.h TH2C_ResetAttMarker" c_th2c_resetattmarker :: (Ptr RawTH2C) -> CString -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetMarkerAttributes" c_th2c_setmarkerattributes :: (Ptr RawTH2C) -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetMarkerColor" c_th2c_setmarkercolor :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetMarkerStyle" c_th2c_setmarkerstyle :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_SetMarkerSize" c_th2c_setmarkersize :: (Ptr RawTH2C) -> CInt -> IO () foreign import ccall "HROOTHistTH2C.h TH2C_delete" c_th2c_delete :: (Ptr RawTH2C) -> IO ()