{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TCollection.Implementation where import HROOT.TypeCast import HROOT.Class.TCollection.RawType import HROOT.Class.TCollection.FFI import HROOT.Class.TCollection.Interface import HROOT.Class.TCollection.Cast import HROOT.Class.TClass.RawType import HROOT.Class.TClass.Cast import HROOT.Class.TClass.Interface import HROOT.Class.TObject.RawType import HROOT.Class.TObject.Cast import HROOT.Class.TObject.Interface import HROOT.Class.Deletable.RawType import HROOT.Class.Deletable.Cast import HROOT.Class.Deletable.Interface import Data.Word -- import Foreign.C -- import Foreign.Ptr import Foreign.ForeignPtr import System.IO.Unsafe instance ITCollection TCollection where instance ITObject TCollection where draw = xform1 c_tcollection_draw findObject = xform1 c_tcollection_findobject getName = xform0 c_tcollection_getname isA = xform0 c_tcollection_isa isFolder = xform0 c_tcollection_isfolder isEqual = xform1 c_tcollection_isequal isSortable = xform0 c_tcollection_issortable paint = xform1 c_tcollection_paint printObj = xform1 c_tcollection_printobj recursiveRemove = xform1 c_tcollection_recursiveremove saveAs = xform2 c_tcollection_saveas useCurrentStyle = xform0 c_tcollection_usecurrentstyle write = xform3 c_tcollection_write instance IDeletable TCollection where delete = xform0 c_tcollection_delete instance ITCollection (Exist TCollection) where instance ITObject (Exist TCollection) where draw (ETCollection x) = draw x findObject (ETCollection x) = findObject x getName (ETCollection x) = getName x isA (ETCollection x) = isA x isFolder (ETCollection x) = isFolder x isEqual (ETCollection x) = isEqual x isSortable (ETCollection x) = isSortable x paint (ETCollection x) = paint x printObj (ETCollection x) = printObj x recursiveRemove (ETCollection x) = recursiveRemove x saveAs (ETCollection x) = saveAs x useCurrentStyle (ETCollection x) = useCurrentStyle x write (ETCollection x) = write x instance IDeletable (Exist TCollection) where delete (ETCollection x) = delete x instance FPtr (Exist TCollection) where type Raw (Exist TCollection) = RawTCollection get_fptr (ETCollection obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETCollection (cast_fptr_to_obj (fptr :: ForeignPtr RawTCollection) :: TCollection)