{-# LINE 1 "src/HROOT/Graf/TCutG/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "src/HROOT/Graf/TCutG/FFI.hsc" #-}

-- module HROOT.Class.FFI where

module HROOT.Graf.TCutG.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Graf.TCutG.RawType
import HROOT.Hist.TF1.RawType
import HROOT.Hist.TH1F.RawType
import HROOT.Hist.TAxis.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType


{-# LINE 23 "src/HROOT/Graf/TCutG/FFI.hsc" #-}

foreign import ccall "HROOTGrafTCutG.h TCutG_Apply" c_tcutg_apply 
  :: (Ptr RawTCutG) -> (Ptr RawTF1) -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_Chisquare" c_tcutg_chisquare 
  :: (Ptr RawTCutG) -> (Ptr RawTF1) -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_DrawGraph" c_tcutg_drawgraph 
  :: (Ptr RawTCutG) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_drawPanelTGraph" c_tcutg_drawpaneltgraph 
  :: (Ptr RawTCutG) -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_Expand" c_tcutg_expand 
  :: (Ptr RawTCutG) -> CInt -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_FitPanelTGraph" c_tcutg_fitpaneltgraph 
  :: (Ptr RawTCutG) -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_getCorrelationFactorTGraph" c_tcutg_getcorrelationfactortgraph 
  :: (Ptr RawTCutG) -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_getCovarianceTGraph" c_tcutg_getcovariancetgraph 
  :: (Ptr RawTCutG) -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_getMeanTGraph" c_tcutg_getmeantgraph 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_getRMSTGraph" c_tcutg_getrmstgraph 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_GetErrorX" c_tcutg_geterrorx 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_GetErrorY" c_tcutg_geterrory 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_GetErrorXhigh" c_tcutg_geterrorxhigh 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_GetErrorXlow" c_tcutg_geterrorxlow 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_GetErrorYhigh" c_tcutg_geterroryhigh 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_GetErrorYlow" c_tcutg_geterrorylow 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_InitExpo" c_tcutg_initexpo 
  :: (Ptr RawTCutG) -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_InitGaus" c_tcutg_initgaus 
  :: (Ptr RawTCutG) -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_InitPolynom" c_tcutg_initpolynom 
  :: (Ptr RawTCutG) -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_InsertPoint" c_tcutg_insertpoint 
  :: (Ptr RawTCutG) -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_integralTGraph" c_tcutg_integraltgraph 
  :: (Ptr RawTCutG) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_IsEditable" c_tcutg_iseditable 
  :: (Ptr RawTCutG) -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_isInsideTGraph" c_tcutg_isinsidetgraph 
  :: (Ptr RawTCutG) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_LeastSquareFit" c_tcutg_leastsquarefit 
  :: (Ptr RawTCutG) -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_PaintStats" c_tcutg_paintstats 
  :: (Ptr RawTCutG) -> (Ptr RawTF1) -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_RemovePoint" c_tcutg_removepoint 
  :: (Ptr RawTCutG) -> CInt -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_SetEditable" c_tcutg_seteditable 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetHistogram" c_tcutg_sethistogram 
  :: (Ptr RawTCutG) -> (Ptr RawTH1F) -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_setMaximumTGraph" c_tcutg_setmaximumtgraph 
  :: (Ptr RawTCutG) -> CDouble -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_setMinimumTGraph" c_tcutg_setminimumtgraph 
  :: (Ptr RawTCutG) -> CDouble -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_Set" c_tcutg_set 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetPoint" c_tcutg_setpoint 
  :: (Ptr RawTCutG) -> CInt -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetName" c_tcutg_setname 
  :: (Ptr RawTCutG) -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetNameTitle" c_tcutg_setnametitle 
  :: (Ptr RawTCutG) -> CString -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetTitle" c_tcutg_settitle 
  :: (Ptr RawTCutG) -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_GetLineColor" c_tcutg_getlinecolor 
  :: (Ptr RawTCutG) -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_GetLineStyle" c_tcutg_getlinestyle 
  :: (Ptr RawTCutG) -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_GetLineWidth" c_tcutg_getlinewidth 
  :: (Ptr RawTCutG) -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_ResetAttLine" c_tcutg_resetattline 
  :: (Ptr RawTCutG) -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetLineAttributes" c_tcutg_setlineattributes 
  :: (Ptr RawTCutG) -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetLineColor" c_tcutg_setlinecolor 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetLineStyle" c_tcutg_setlinestyle 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetLineWidth" c_tcutg_setlinewidth 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetFillColor" c_tcutg_setfillcolor 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetFillStyle" c_tcutg_setfillstyle 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_GetMarkerColor" c_tcutg_getmarkercolor 
  :: (Ptr RawTCutG) -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_GetMarkerStyle" c_tcutg_getmarkerstyle 
  :: (Ptr RawTCutG) -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_GetMarkerSize" c_tcutg_getmarkersize 
  :: (Ptr RawTCutG) -> IO CDouble

foreign import ccall "HROOTGrafTCutG.h TCutG_ResetAttMarker" c_tcutg_resetattmarker 
  :: (Ptr RawTCutG) -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetMarkerAttributes" c_tcutg_setmarkerattributes 
  :: (Ptr RawTCutG) -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetMarkerColor" c_tcutg_setmarkercolor 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetMarkerStyle" c_tcutg_setmarkerstyle 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SetMarkerSize" c_tcutg_setmarkersize 
  :: (Ptr RawTCutG) -> CInt -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_Draw" c_tcutg_draw 
  :: (Ptr RawTCutG) -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_FindObject" c_tcutg_findobject 
  :: (Ptr RawTCutG) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTGrafTCutG.h TCutG_GetName" c_tcutg_getname 
  :: (Ptr RawTCutG) -> IO CString

foreign import ccall "HROOTGrafTCutG.h TCutG_IsA" c_tcutg_isa 
  :: (Ptr RawTCutG) -> IO (Ptr RawTClass)

foreign import ccall "HROOTGrafTCutG.h TCutG_Paint" c_tcutg_paint 
  :: (Ptr RawTCutG) -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_printObj" c_tcutg_printobj 
  :: (Ptr RawTCutG) -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_SaveAs" c_tcutg_saveas 
  :: (Ptr RawTCutG) -> CString -> CString -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_Write" c_tcutg_write 
  :: (Ptr RawTCutG) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTGrafTCutG.h TCutG_delete" c_tcutg_delete 
  :: (Ptr RawTCutG) -> IO ()

foreign import ccall "HROOTGrafTCutG.h TCutG_newTCutG" c_tcutg_newtcutg 
  :: CString -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTCutG)