module HROOT.Class.TObject.Implementation where
import HROOT.TypeCast
import HROOT.Class.TObject.RawType
import HROOT.Class.TObject.FFI
import HROOT.Class.TObject.Interface
import HROOT.Class.TObject.Cast
import HROOT.Class.TClass.RawType
import HROOT.Class.TClass.Cast
import HROOT.Class.TClass.Interface
import HROOT.Class.Deletable.RawType
import HROOT.Class.Deletable.Cast
import HROOT.Class.Deletable.Interface
import Data.Word
import Foreign.ForeignPtr
import System.IO.Unsafe
instance ITObject TObject where
draw = xform1 c_tobject_draw
findObject = xform1 c_tobject_findobject
getName = xform0 c_tobject_getname
isA = xform0 c_tobject_isa
isFolder = xform0 c_tobject_isfolder
isEqual = xform1 c_tobject_isequal
isSortable = xform0 c_tobject_issortable
paint = xform1 c_tobject_paint
printObj = xform1 c_tobject_printobj
recursiveRemove = xform1 c_tobject_recursiveremove
saveAs = xform2 c_tobject_saveas
useCurrentStyle = xform0 c_tobject_usecurrentstyle
write = xform3 c_tobject_write
instance IDeletable TObject where
delete = xform0 c_tobject_delete
instance ITObject (Exist TObject) where
draw (ETObject x) = draw x
findObject (ETObject x) = findObject x
getName (ETObject x) = getName x
isA (ETObject x) = isA x
isFolder (ETObject x) = isFolder x
isEqual (ETObject x) = isEqual x
isSortable (ETObject x) = isSortable x
paint (ETObject x) = paint x
printObj (ETObject x) = printObj x
recursiveRemove (ETObject x) = recursiveRemove x
saveAs (ETObject x) = saveAs x
useCurrentStyle (ETObject x) = useCurrentStyle x
write (ETObject x) = write x
instance IDeletable (Exist TObject) where
delete (ETObject x) = delete x
newTObject :: IO TObject
newTObject = xformnull c_tobject_newtobject
tObjectIsOnHeap :: TObject -> IO Int
tObjectIsOnHeap = xform0 c_tobject_tobjectisonheap
tObjectIsZombie :: TObject -> IO Int
tObjectIsZombie = xform0 c_tobject_tobjectiszombie
tObjectGetObjectStat :: IO Int
tObjectGetObjectStat = xformnull c_tobject_tobjectgetobjectstat
tObjectSetObjectStat :: Int -> IO ()
tObjectSetObjectStat = xform0 c_tobject_tobjectsetobjectstat
instance FPtr (Exist TObject) where
type Raw (Exist TObject) = RawTObject
get_fptr (ETObject obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETObject (cast_fptr_to_obj (fptr :: ForeignPtr RawTObject) :: TObject)