module HROOT.Core.TArrayI.Implementation where
import FFICXX.Runtime.Cast
import HROOT.Core.TArrayI.RawType
import HROOT.Core.TArrayI.FFI
import HROOT.Core.TArrayI.Interface
import HROOT.Core.TArrayI.Cast
import HROOT.Core.TArray.RawType
import HROOT.Core.TArray.Cast
import HROOT.Core.TArray.Interface
import HROOT.Core.Deletable.RawType
import HROOT.Core.Deletable.Cast
import HROOT.Core.Deletable.Interface
import Data.Word
import Foreign.C
import Foreign.Ptr
import Foreign.ForeignPtr
import System.IO.Unsafe
instance ITArrayI TArrayI where
instance ITArray TArrayI where
instance IDeletable TArrayI where
delete = xform0 c_tarrayi_delete
instance ITArrayI (Exist TArrayI) where
instance ITArray (Exist TArrayI) where
instance IDeletable (Exist TArrayI) where
delete (ETArrayI x) = delete x
instance FPtr (Exist TArrayI) where
type Raw (Exist TArrayI) = RawTArrayI
get_fptr (ETArrayI obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArrayI (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrayI) :: TArrayI)