{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Core.TArrayS.Implementation where import FFICXX.Runtime.Cast import HROOT.Core.TArrayS.RawType import HROOT.Core.TArrayS.FFI import HROOT.Core.TArrayS.Interface import HROOT.Core.TArrayS.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 ITArrayS TArrayS where instance ITArray TArrayS where instance IDeletable TArrayS where delete = xform0 c_tarrays_delete instance ITArrayS (Exist TArrayS) where instance ITArray (Exist TArrayS) where instance IDeletable (Exist TArrayS) where delete (ETArrayS x) = delete x instance FPtr (Exist TArrayS) where type Raw (Exist TArrayS) = RawTArrayS get_fptr (ETArrayS obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETArrayS (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrayS) :: TArrayS)