{-# LANGUAGE EmptyDataDecls, FlexibleInstances,
  MultiParamTypeClasses, TypeFamilies #-}
module STD.Vector.Template where
import Foreign.C.Types
import Foreign.Ptr
import FFICXX.Runtime.Cast
import STD.VectorIterator.Template

data RawVector tp1

newtype Vector tp1 = Vector (Ptr (RawVector tp1))

class () => IVector tp1 where
        newVector :: IO (Vector tp1)
        
        begin :: Vector tp1 -> IO (VectorIterator tp1)
        
        end :: Vector tp1 -> IO (VectorIterator tp1)
        
        push_back :: Vector tp1 -> tp1 -> IO ()
        
        pop_back :: Vector tp1 -> IO ()
        
        at :: Vector tp1 -> CInt -> IO tp1
        
        size :: Vector tp1 -> IO CInt
        
        deleteVector :: Vector tp1 -> IO ()

instance () => FPtr (Vector tp1) where
        type Raw (Vector tp1) = RawVector tp1
        get_fptr :: Vector tp1 -> Ptr (Raw (Vector tp1))
get_fptr (Vector Ptr (RawVector tp1)
ptr) = Ptr (Raw (Vector tp1))
Ptr (RawVector tp1)
ptr
        cast_fptr_to_obj :: Ptr (Raw (Vector tp1)) -> Vector tp1
cast_fptr_to_obj = Ptr (Raw (Vector tp1)) -> Vector tp1
Ptr (RawVector tp1) -> Vector tp1
forall tp1. Ptr (RawVector tp1) -> Vector tp1
Vector

instance () => Castable (Vector tp1) (Ptr (RawVector tp1)) where
        cast :: forall r. Vector tp1 -> (Ptr (RawVector tp1) -> IO r) -> IO r
cast Vector tp1
x Ptr (RawVector tp1) -> IO r
f = Ptr (RawVector tp1) -> IO r
f (Ptr (RawVector tp1) -> Ptr (RawVector tp1)
forall a b. Ptr a -> Ptr b
castPtr (Vector tp1 -> Ptr (Raw (Vector tp1))
forall a. FPtr a => a -> Ptr (Raw a)
get_fptr Vector tp1
x))
        uncast :: forall r. Ptr (RawVector tp1) -> (Vector tp1 -> IO r) -> IO r
uncast Ptr (RawVector tp1)
x Vector tp1 -> IO r
f = Vector tp1 -> IO r
f (Ptr (Raw (Vector tp1)) -> Vector tp1
forall a. FPtr a => Ptr (Raw a) -> a
cast_fptr_to_obj (Ptr (RawVector tp1) -> Ptr (RawVector tp1)
forall a b. Ptr a -> Ptr b
castPtr Ptr (RawVector tp1)
x))