{-# LINE 1 "src/HROOT/Hist/TFitResult/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-}
module HROOT.Hist.TFitResult.FFI where
import Data.Word
import Data.Int
import Foreign.C
import Foreign.Ptr
import HROOT.Hist.TFitResult.RawType
import HROOT.Hist.TFitResult.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_SetName" c_tfitresult_setname ::
               Ptr RawTFitResult -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_SetNameTitle"
               c_tfitresult_setnametitle ::
               Ptr RawTFitResult -> CString -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_SetTitle" c_tfitresult_settitle
               :: Ptr RawTFitResult -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_Clear" c_tfitresult_clear ::
               Ptr RawTFitResult -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_Draw" c_tfitresult_draw ::
               Ptr RawTFitResult -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_FindObject"
               c_tfitresult_findobject ::
               Ptr RawTFitResult -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_GetName" c_tfitresult_getname ::
               Ptr RawTFitResult -> IO CString

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_IsA" c_tfitresult_isa ::
               Ptr RawTFitResult -> IO (Ptr RawTClass)

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_Paint" c_tfitresult_paint ::
               Ptr RawTFitResult -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_printObj" c_tfitresult_printobj
               :: Ptr RawTFitResult -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_SaveAs" c_tfitresult_saveas ::
               Ptr RawTFitResult -> CString -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_Write" c_tfitresult_write ::
               Ptr RawTFitResult -> CString -> CInt -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_Write_" c_tfitresult_write_ ::
               Ptr RawTFitResult -> IO CInt

foreign import ccall interruptible
               "HROOTHistTFitResult.h TFitResult_delete" c_tfitresult_delete ::
               Ptr RawTFitResult -> IO ()