{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TSeqCollection.Implementation where import HROOT.TypeCast import HROOT.Class.TSeqCollection.RawType import HROOT.Class.TSeqCollection.FFI import HROOT.Class.TSeqCollection.Interface import HROOT.Class.TSeqCollection.Cast import HROOT.Class.TClass.RawType import HROOT.Class.TClass.Cast import HROOT.Class.TClass.Interface import HROOT.Class.TCollection.RawType import HROOT.Class.TCollection.Cast import HROOT.Class.TCollection.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 ITSeqCollection TSeqCollection where instance ITCollection TSeqCollection where instance ITObject TSeqCollection where draw = xform1 c_tseqcollection_draw findObject = xform1 c_tseqcollection_findobject getName = xform0 c_tseqcollection_getname isA = xform0 c_tseqcollection_isa isFolder = xform0 c_tseqcollection_isfolder isEqual = xform1 c_tseqcollection_isequal isSortable = xform0 c_tseqcollection_issortable paint = xform1 c_tseqcollection_paint printObj = xform1 c_tseqcollection_printobj recursiveRemove = xform1 c_tseqcollection_recursiveremove saveAs = xform2 c_tseqcollection_saveas useCurrentStyle = xform0 c_tseqcollection_usecurrentstyle write = xform3 c_tseqcollection_write instance IDeletable TSeqCollection where delete = xform0 c_tseqcollection_delete instance ITSeqCollection (Exist TSeqCollection) where instance ITCollection (Exist TSeqCollection) where instance ITObject (Exist TSeqCollection) where draw (ETSeqCollection x) = draw x findObject (ETSeqCollection x) = findObject x getName (ETSeqCollection x) = getName x isA (ETSeqCollection x) = isA x isFolder (ETSeqCollection x) = isFolder x isEqual (ETSeqCollection x) = isEqual x isSortable (ETSeqCollection x) = isSortable x paint (ETSeqCollection x) = paint x printObj (ETSeqCollection x) = printObj x recursiveRemove (ETSeqCollection x) = recursiveRemove x saveAs (ETSeqCollection x) = saveAs x useCurrentStyle (ETSeqCollection x) = useCurrentStyle x write (ETSeqCollection x) = write x instance IDeletable (Exist TSeqCollection) where delete (ETSeqCollection x) = delete x instance FPtr (Exist TSeqCollection) where type Raw (Exist TSeqCollection) = RawTSeqCollection get_fptr (ETSeqCollection obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETSeqCollection (cast_fptr_to_obj (fptr :: ForeignPtr RawTSeqCollection) :: TSeqCollection)