{-# LANGUAGE ForeignFunctionInterface #-} -- module HROOT.Class.FFI where module HROOT.Class.TH2S.FFI where import Foreign.C import Foreign.Ptr -- import HROOT.Class.Interface -- #include "" import HROOT.Class.TH2S.RawType import HROOT.Class.TH1D.RawType import HROOT.Class.TH2.RawType import HROOT.Class.TH1.RawType import HROOT.Class.TF1.RawType import HROOT.Class.TObjArray.RawType import HROOT.Class.TDirectory.RawType import HROOT.Class.TArrayD.RawType import HROOT.Class.TAxis.RawType import HROOT.Class.TObject.RawType import HROOT.Class.TClass.RawType #include "HROOTTH2S.h" foreign import ccall "HROOTTH2S.h TH2S_fill2" c_th2s_fill2 :: (Ptr RawTH2S) -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_fill2w" c_th2s_fill2w :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_fillN2" c_th2s_filln2 :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_fillRandom2" c_th2s_fillrandom2 :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_findFirstBinAbove2" c_th2s_findfirstbinabove2 :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_findLastBinAbove2" c_th2s_findlastbinabove2 :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_FitSlicesX" c_th2s_fitslicesx :: (Ptr RawTH2S) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO () foreign import ccall "HROOTTH2S.h TH2S_FitSlicesY" c_th2s_fitslicesy :: (Ptr RawTH2S) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO () foreign import ccall "HROOTTH2S.h TH2S_getCorrelationFactor2" c_th2s_getcorrelationfactor2 :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_getCovariance2" c_th2s_getcovariance2 :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_integral2" c_th2s_integral2 :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_rebinX2" c_th2s_rebinx2 :: (Ptr RawTH2S) -> CInt -> CString -> IO (Ptr RawTH2) foreign import ccall "HROOTTH2S.h TH2S_rebinY2" c_th2s_rebiny2 :: (Ptr RawTH2S) -> CInt -> CString -> IO (Ptr RawTH2) foreign import ccall "HROOTTH2S.h TH2S_Rebin2D" c_th2s_rebin2d :: (Ptr RawTH2S) -> CInt -> CInt -> CString -> IO (Ptr RawTH2) foreign import ccall "HROOTTH2S.h TH2S_SetShowProjectionX" c_th2s_setshowprojectionx :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetShowProjectionY" c_th2s_setshowprojectiony :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_Add" c_th2s_add :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_AddBinContent" c_th2s_addbincontent :: (Ptr RawTH2S) -> CInt -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_Chi2Test" c_th2s_chi2test :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_ComputeIntegral" c_th2s_computeintegral :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_DirectoryAutoAdd" c_th2s_directoryautoadd :: (Ptr RawTH2S) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTTH2S.h TH2S_Divide" c_th2s_divide :: (Ptr RawTH2S) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_drawCopyTH1" c_th2s_drawcopyth1 :: (Ptr RawTH2S) -> CString -> IO (Ptr RawTH2S) foreign import ccall "HROOTTH2S.h TH2S_DrawNormalized" c_th2s_drawnormalized :: (Ptr RawTH2S) -> CString -> CDouble -> IO (Ptr RawTH1) foreign import ccall "HROOTTH2S.h TH2S_drawPanelTH1" c_th2s_drawpanelth1 :: (Ptr RawTH2S) -> IO () foreign import ccall "HROOTTH2S.h TH2S_BufferEmpty" c_th2s_bufferempty :: (Ptr RawTH2S) -> CInt -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_evalF" c_th2s_evalf :: (Ptr RawTH2S) -> (Ptr RawTF1) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_FFT" c_th2s_fft :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTTH2S.h TH2S_fill1" c_th2s_fill1 :: (Ptr RawTH2S) -> CDouble -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_fill1w" c_th2s_fill1w :: (Ptr RawTH2S) -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_fillN1" c_th2s_filln1 :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_FillRandom" c_th2s_fillrandom :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_FindBin" c_th2s_findbin :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_FindFixBin" c_th2s_findfixbin :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_FindFirstBinAbove" c_th2s_findfirstbinabove :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_FindLastBinAbove" c_th2s_findlastbinabove :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_FitPanelTH1" c_th2s_fitpanelth1 :: (Ptr RawTH2S) -> IO () foreign import ccall "HROOTTH2S.h TH2S_getNdivisionA" c_th2s_getndivisiona :: (Ptr RawTH2S) -> CString -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_getAxisColorA" c_th2s_getaxiscolora :: (Ptr RawTH2S) -> CString -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_getLabelColorA" c_th2s_getlabelcolora :: (Ptr RawTH2S) -> CString -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_getLabelFontA" c_th2s_getlabelfonta :: (Ptr RawTH2S) -> CString -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_getLabelOffsetA" c_th2s_getlabeloffseta :: (Ptr RawTH2S) -> CString -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_getLabelSizeA" c_th2s_getlabelsizea :: (Ptr RawTH2S) -> CString -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_getTitleFontA" c_th2s_gettitlefonta :: (Ptr RawTH2S) -> CString -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_getTitleOffsetA" c_th2s_gettitleoffseta :: (Ptr RawTH2S) -> CString -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_getTitleSizeA" c_th2s_gettitlesizea :: (Ptr RawTH2S) -> CString -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_getTickLengthA" c_th2s_getticklengtha :: (Ptr RawTH2S) -> CString -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBarOffset" c_th2s_getbaroffset :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBarWidth" c_th2s_getbarwidth :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetContour" c_th2s_getcontour :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetContourLevel" c_th2s_getcontourlevel :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetContourLevelPad" c_th2s_getcontourlevelpad :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBin" c_th2s_getbin :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetBinCenter" c_th2s_getbincenter :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBinContent1" c_th2s_getbincontent1 :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBinContent2" c_th2s_getbincontent2 :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBinContent3" c_th2s_getbincontent3 :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBinError1" c_th2s_getbinerror1 :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBinError2" c_th2s_getbinerror2 :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBinError3" c_th2s_getbinerror3 :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBinLowEdge" c_th2s_getbinlowedge :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetBinWidth" c_th2s_getbinwidth :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetCellContent" c_th2s_getcellcontent :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetCellError" c_th2s_getcellerror :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetEntries" c_th2s_getentries :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetEffectiveEntries" c_th2s_geteffectiveentries :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetFunction" c_th2s_getfunction :: (Ptr RawTH2S) -> CString -> IO (Ptr RawTF1) foreign import ccall "HROOTTH2S.h TH2S_GetDimension" c_th2s_getdimension :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetKurtosis" c_th2s_getkurtosis :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetLowEdge" c_th2s_getlowedge :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTTH2S.h TH2S_getMaximumTH1" c_th2s_getmaximumth1 :: (Ptr RawTH2S) -> CDouble -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetMaximumBin" c_th2s_getmaximumbin :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetMaximumStored" c_th2s_getmaximumstored :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_getMinimumTH1" c_th2s_getminimumth1 :: (Ptr RawTH2S) -> CDouble -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetMinimumBin" c_th2s_getminimumbin :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetMinimumStored" c_th2s_getminimumstored :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetMean" c_th2s_getmean :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetMeanError" c_th2s_getmeanerror :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetNbinsX" c_th2s_getnbinsx :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetNbinsY" c_th2s_getnbinsy :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetNbinsZ" c_th2s_getnbinsz :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_getQuantilesTH1" c_th2s_getquantilesth1 :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetRandom" c_th2s_getrandom :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetStats" c_th2s_getstats :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTTH2S.h TH2S_GetSumOfWeights" c_th2s_getsumofweights :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetSumw2" c_th2s_getsumw2 :: (Ptr RawTH2S) -> IO (Ptr RawTArrayD) foreign import ccall "HROOTTH2S.h TH2S_GetSumw2N" c_th2s_getsumw2n :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetRMS" c_th2s_getrms :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetRMSError" c_th2s_getrmserror :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_GetSkewness" c_th2s_getskewness :: (Ptr RawTH2S) -> CInt -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_integral1" c_th2s_integral1 :: (Ptr RawTH2S) -> CInt -> CInt -> CString -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_interpolate1" c_th2s_interpolate1 :: (Ptr RawTH2S) -> CDouble -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_interpolate2" c_th2s_interpolate2 :: (Ptr RawTH2S) -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_interpolate3" c_th2s_interpolate3 :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_KolmogorovTest" c_th2s_kolmogorovtest :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CString -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_LabelsDeflate" c_th2s_labelsdeflate :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_LabelsInflate" c_th2s_labelsinflate :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_LabelsOption" c_th2s_labelsoption :: (Ptr RawTH2S) -> CString -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_multiflyF" c_th2s_multiflyf :: (Ptr RawTH2S) -> (Ptr RawTF1) -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_Multiply" c_th2s_multiply :: (Ptr RawTH2S) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_PutStats" c_th2s_putstats :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTTH2S.h TH2S_Rebin" c_th2s_rebin :: (Ptr RawTH2S) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1) foreign import ccall "HROOTTH2S.h TH2S_RebinAxis" c_th2s_rebinaxis :: (Ptr RawTH2S) -> CDouble -> (Ptr RawTAxis) -> IO () foreign import ccall "HROOTTH2S.h TH2S_Rebuild" c_th2s_rebuild :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_Reset" c_th2s_reset :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_ResetStats" c_th2s_resetstats :: (Ptr RawTH2S) -> IO () foreign import ccall "HROOTTH2S.h TH2S_Scale" c_th2s_scale :: (Ptr RawTH2S) -> CDouble -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_setAxisColorA" c_th2s_setaxiscolora :: (Ptr RawTH2S) -> CInt -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetAxisRange" c_th2s_setaxisrange :: (Ptr RawTH2S) -> CDouble -> CDouble -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetBarOffset" c_th2s_setbaroffset :: (Ptr RawTH2S) -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetBarWidth" c_th2s_setbarwidth :: (Ptr RawTH2S) -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_setBinContent1" c_th2s_setbincontent1 :: (Ptr RawTH2S) -> CInt -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_setBinContent2" c_th2s_setbincontent2 :: (Ptr RawTH2S) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_setBinContent3" c_th2s_setbincontent3 :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_setBinError1" c_th2s_setbinerror1 :: (Ptr RawTH2S) -> CInt -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_setBinError2" c_th2s_setbinerror2 :: (Ptr RawTH2S) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_setBinError3" c_th2s_setbinerror3 :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_setBins1" c_th2s_setbins1 :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTTH2S.h TH2S_setBins2" c_th2s_setbins2 :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTTH2S.h TH2S_setBins3" c_th2s_setbins3 :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetBinsLength" c_th2s_setbinslength :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetBuffer" c_th2s_setbuffer :: (Ptr RawTH2S) -> CInt -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetCellContent" c_th2s_setcellcontent :: (Ptr RawTH2S) -> CInt -> CInt -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetContent" c_th2s_setcontent :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetContour" c_th2s_setcontour :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetContourLevel" c_th2s_setcontourlevel :: (Ptr RawTH2S) -> CInt -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetDirectory" c_th2s_setdirectory :: (Ptr RawTH2S) -> (Ptr RawTDirectory) -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetEntries" c_th2s_setentries :: (Ptr RawTH2S) -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetError" c_th2s_seterror :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO () foreign import ccall "HROOTTH2S.h TH2S_setLabelColorA" c_th2s_setlabelcolora :: (Ptr RawTH2S) -> CInt -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_setLabelSizeA" c_th2s_setlabelsizea :: (Ptr RawTH2S) -> CDouble -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_setLabelFontA" c_th2s_setlabelfonta :: (Ptr RawTH2S) -> CInt -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_setLabelOffsetA" c_th2s_setlabeloffseta :: (Ptr RawTH2S) -> CDouble -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetMaximum" c_th2s_setmaximum :: (Ptr RawTH2S) -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetMinimum" c_th2s_setminimum :: (Ptr RawTH2S) -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetNormFactor" c_th2s_setnormfactor :: (Ptr RawTH2S) -> CDouble -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetStats" c_th2s_setstats :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetOption" c_th2s_setoption :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetXTitle" c_th2s_setxtitle :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetYTitle" c_th2s_setytitle :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetZTitle" c_th2s_setztitle :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_ShowBackground" c_th2s_showbackground :: (Ptr RawTH2S) -> CInt -> CString -> IO (Ptr RawTH1) foreign import ccall "HROOTTH2S.h TH2S_ShowPeaks" c_th2s_showpeaks :: (Ptr RawTH2S) -> CDouble -> CString -> CDouble -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_Smooth" c_th2s_smooth :: (Ptr RawTH2S) -> CInt -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_Sumw2" c_th2s_sumw2 :: (Ptr RawTH2S) -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetName" c_th2s_setname :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetNameTitle" c_th2s_setnametitle :: (Ptr RawTH2S) -> CString -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetTitle" c_th2s_settitle :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_GetLineColor" c_th2s_getlinecolor :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetLineStyle" c_th2s_getlinestyle :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetLineWidth" c_th2s_getlinewidth :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_ResetAttLine" c_th2s_resetattline :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetLineAttributes" c_th2s_setlineattributes :: (Ptr RawTH2S) -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetLineColor" c_th2s_setlinecolor :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetLineStyle" c_th2s_setlinestyle :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetLineWidth" c_th2s_setlinewidth :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetFillColor" c_th2s_setfillcolor :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetFillStyle" c_th2s_setfillstyle :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_GetMarkerColor" c_th2s_getmarkercolor :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetMarkerStyle" c_th2s_getmarkerstyle :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_GetMarkerSize" c_th2s_getmarkersize :: (Ptr RawTH2S) -> IO CDouble foreign import ccall "HROOTTH2S.h TH2S_ResetAttMarker" c_th2s_resetattmarker :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetMarkerAttributes" c_th2s_setmarkerattributes :: (Ptr RawTH2S) -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetMarkerColor" c_th2s_setmarkercolor :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetMarkerStyle" c_th2s_setmarkerstyle :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_SetMarkerSize" c_th2s_setmarkersize :: (Ptr RawTH2S) -> CInt -> IO () foreign import ccall "HROOTTH2S.h TH2S_Draw" c_th2s_draw :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_FindObject" c_th2s_findobject :: (Ptr RawTH2S) -> CString -> IO (Ptr RawTObject) foreign import ccall "HROOTTH2S.h TH2S_GetName" c_th2s_getname :: (Ptr RawTH2S) -> IO CString foreign import ccall "HROOTTH2S.h TH2S_IsA" c_th2s_isa :: (Ptr RawTH2S) -> IO (Ptr RawTClass) foreign import ccall "HROOTTH2S.h TH2S_IsFolder" c_th2s_isfolder :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_IsEqual" c_th2s_isequal :: (Ptr RawTH2S) -> (Ptr RawTObject) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_IsSortable" c_th2s_issortable :: (Ptr RawTH2S) -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_Paint" c_th2s_paint :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_printObj" c_th2s_printobj :: (Ptr RawTH2S) -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_RecursiveRemove" c_th2s_recursiveremove :: (Ptr RawTH2S) -> (Ptr RawTObject) -> IO () foreign import ccall "HROOTTH2S.h TH2S_SaveAs" c_th2s_saveas :: (Ptr RawTH2S) -> CString -> CString -> IO () foreign import ccall "HROOTTH2S.h TH2S_UseCurrentStyle" c_th2s_usecurrentstyle :: (Ptr RawTH2S) -> IO () foreign import ccall "HROOTTH2S.h TH2S_Write" c_th2s_write :: (Ptr RawTH2S) -> CString -> CInt -> CInt -> IO CInt foreign import ccall "HROOTTH2S.h TH2S_delete" c_th2s_delete :: (Ptr RawTH2S) -> IO ()