{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module HROOT.Math.TRandom.Implementation where import Data.Monoid import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import Language.Haskell.TH import Language.Haskell.TH.Syntax import System.IO.Unsafe import FFICXX.Runtime.Cast import FFICXX.Runtime.CodeGen.Cxx import FFICXX.Runtime.TH import HROOT.Math.TRandom.RawType import HROOT.Math.TRandom.FFI import HROOT.Math.TRandom.Interface import HROOT.Math.TRandom.Cast import HROOT.Math.TRandom.RawType import HROOT.Math.TRandom.Cast import HROOT.Math.TRandom.Interface import HROOT.Core.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Core.TNamed.RawType import HROOT.Core.TNamed.Cast import HROOT.Core.TNamed.Interface import HROOT.Core.TObject.RawType import HROOT.Core.TObject.Cast import HROOT.Core.TObject.Interface import STD.Deletable.RawType import STD.Deletable.Cast import STD.Deletable.Interface instance () => ITRandom (TRandom) where getSeed = xform0 c_trandom_getseed gaus = xform2 c_trandom_gaus setSeed = xform1 c_trandom_setseed uniform = xform2 c_trandom_uniform instance () => ITNamed (TRandom) where setName = xform1 c_trandom_setname setNameTitle = xform2 c_trandom_setnametitle setTitle = xform1 c_trandom_settitle instance () => ITObject (TRandom) where clear = xform1 c_trandom_clear draw = xform1 c_trandom_draw findObject = xform1 c_trandom_findobject getName = xform0 c_trandom_getname isA = xform0 c_trandom_isa paint = xform1 c_trandom_paint printObj = xform1 c_trandom_printobj saveAs = xform2 c_trandom_saveas write = xform3 c_trandom_write write_ = xform0 c_trandom_write_ instance () => IDeletable (TRandom) where delete = xform0 c_trandom_delete newTRandom :: () => CInt -> IO TRandom newTRandom = xform0 c_trandom_newtrandom