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

-- module HROOT.Class.FFI where

module HROOT.Math.TRandom.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Math.TRandom.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType


{-# LINE 20 "src/HROOT/Math/TRandom/FFI.hsc" #-}

foreign import ccall "HROOTMathTRandom.h TRandom_SetName" c_trandom_setname 
  :: (Ptr RawTRandom) -> CString -> IO ()

foreign import ccall "HROOTMathTRandom.h TRandom_SetNameTitle" c_trandom_setnametitle 
  :: (Ptr RawTRandom) -> CString -> CString -> IO ()

foreign import ccall "HROOTMathTRandom.h TRandom_SetTitle" c_trandom_settitle 
  :: (Ptr RawTRandom) -> CString -> IO ()

foreign import ccall "HROOTMathTRandom.h TRandom_Draw" c_trandom_draw 
  :: (Ptr RawTRandom) -> CString -> IO ()

foreign import ccall "HROOTMathTRandom.h TRandom_FindObject" c_trandom_findobject 
  :: (Ptr RawTRandom) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTMathTRandom.h TRandom_GetName" c_trandom_getname 
  :: (Ptr RawTRandom) -> IO CString

foreign import ccall "HROOTMathTRandom.h TRandom_IsA" c_trandom_isa 
  :: (Ptr RawTRandom) -> IO (Ptr RawTClass)

foreign import ccall "HROOTMathTRandom.h TRandom_Paint" c_trandom_paint 
  :: (Ptr RawTRandom) -> CString -> IO ()

foreign import ccall "HROOTMathTRandom.h TRandom_printObj" c_trandom_printobj 
  :: (Ptr RawTRandom) -> CString -> IO ()

foreign import ccall "HROOTMathTRandom.h TRandom_SaveAs" c_trandom_saveas 
  :: (Ptr RawTRandom) -> CString -> CString -> IO ()

foreign import ccall "HROOTMathTRandom.h TRandom_Write" c_trandom_write 
  :: (Ptr RawTRandom) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTMathTRandom.h TRandom_delete" c_trandom_delete 
  :: (Ptr RawTRandom) -> IO ()

foreign import ccall "HROOTMathTRandom.h TRandom_newTRandom" c_trandom_newtrandom 
  :: CInt -> IO (Ptr RawTRandom)

foreign import ccall "HROOTMathTRandom.h TRandom_GetSeed" c_trandom_getseed 
  :: (Ptr RawTRandom) -> IO CInt

foreign import ccall "HROOTMathTRandom.h TRandom_Gaus" c_trandom_gaus 
  :: (Ptr RawTRandom) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTMathTRandom.h TRandom_SetSeed" c_trandom_setseed 
  :: (Ptr RawTRandom) -> CInt -> IO ()

foreign import ccall "HROOTMathTRandom.h TRandom_Uniform" c_trandom_uniform 
  :: (Ptr RawTRandom) -> CDouble -> CDouble -> IO CDouble