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

-- module HROOT.Class.FFI where

module HROOT.Hist.TFormula.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Hist.TFormula.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType


{-# LINE 20 "src/HROOT/Hist/TFormula/FFI.hsc" #-}

foreign import ccall "HROOTHistTFormula.h TFormula_SetName" c_tformula_setname 
  :: (Ptr RawTFormula) -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_SetNameTitle" c_tformula_setnametitle 
  :: (Ptr RawTFormula) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_SetTitle" c_tformula_settitle 
  :: (Ptr RawTFormula) -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_Draw" c_tformula_draw 
  :: (Ptr RawTFormula) -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_FindObject" c_tformula_findobject 
  :: (Ptr RawTFormula) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTFormula.h TFormula_GetName" c_tformula_getname 
  :: (Ptr RawTFormula) -> IO CString

foreign import ccall "HROOTHistTFormula.h TFormula_IsA" c_tformula_isa 
  :: (Ptr RawTFormula) -> IO (Ptr RawTClass)

foreign import ccall "HROOTHistTFormula.h TFormula_Paint" c_tformula_paint 
  :: (Ptr RawTFormula) -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_printObj" c_tformula_printobj 
  :: (Ptr RawTFormula) -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_SaveAs" c_tformula_saveas 
  :: (Ptr RawTFormula) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_Write" c_tformula_write 
  :: (Ptr RawTFormula) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTFormula.h TFormula_delete" c_tformula_delete 
  :: (Ptr RawTFormula) -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_newTFormula" c_tformula_newtformula 
  :: CString -> CString -> IO (Ptr RawTFormula)

foreign import ccall "HROOTHistTFormula.h TFormula_tFormulaOptimize" c_tformula_tformulaoptimize 
  :: (Ptr RawTFormula) -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_Compile" c_tformula_compile 
  :: (Ptr RawTFormula) -> CString -> IO CInt

foreign import ccall "HROOTHistTFormula.h TFormula_Clear" c_tformula_clear 
  :: (Ptr RawTFormula) -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_DefinedValue" c_tformula_definedvalue 
  :: (Ptr RawTFormula) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTFormula.h TFormula_Eval" c_tformula_eval 
  :: (Ptr RawTFormula) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTFormula.h TFormula_EvalParOld" c_tformula_evalparold 
  :: (Ptr RawTFormula) -> (Ptr CDouble) -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTFormula.h TFormula_EvalPar" c_tformula_evalpar 
  :: (Ptr RawTFormula) -> (Ptr CDouble) -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTFormula.h TFormula_GetNdim" c_tformula_getndim 
  :: (Ptr RawTFormula) -> IO CInt

foreign import ccall "HROOTHistTFormula.h TFormula_GetNpar" c_tformula_getnpar 
  :: (Ptr RawTFormula) -> IO CInt

foreign import ccall "HROOTHistTFormula.h TFormula_GetNumber" c_tformula_getnumber 
  :: (Ptr RawTFormula) -> IO CInt

foreign import ccall "HROOTHistTFormula.h TFormula_tFormulaGetParameter" c_tformula_tformulagetparameter 
  :: (Ptr RawTFormula) -> CString -> IO CDouble

foreign import ccall "HROOTHistTFormula.h TFormula_GetParNumber" c_tformula_getparnumber 
  :: (Ptr RawTFormula) -> CString -> IO CInt

foreign import ccall "HROOTHistTFormula.h TFormula_IsLinear" c_tformula_islinear 
  :: (Ptr RawTFormula) -> IO CInt

foreign import ccall "HROOTHistTFormula.h TFormula_IsNormalized" c_tformula_isnormalized 
  :: (Ptr RawTFormula) -> IO CInt

foreign import ccall "HROOTHistTFormula.h TFormula_SetNumber" c_tformula_setnumber 
  :: (Ptr RawTFormula) -> CInt -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_SetParameter" c_tformula_setparameter 
  :: (Ptr RawTFormula) -> CString -> CDouble -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_SetParameters" c_tformula_setparameters 
  :: (Ptr RawTFormula) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_SetParName" c_tformula_setparname 
  :: (Ptr RawTFormula) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_SetParNames" c_tformula_setparnames 
  :: (Ptr RawTFormula) -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTFormula.h TFormula_Update" c_tformula_update 
  :: (Ptr RawTFormula) -> IO ()