module Data.Vector.Fixed.Boxed (
Vec
, Vec2
, Vec3
, Vec4
, Vec5
, MVec
) where
import Control.Applicative (Applicative(..))
import Data.Primitive.Array
import Data.Typeable (Typeable)
import qualified Data.Foldable as F
import qualified Data.Traversable as T
import Prelude hiding (length,replicate,zipWith,map,foldl,foldr)
import Data.Vector.Fixed hiding (index)
import Data.Vector.Fixed.Mutable
newtype Vec n a = Vec (Array a)
deriving (Typeable)
newtype MVec n s a = MVec (MutableArray s a)
deriving (Typeable)
type Vec2 = Vec (S (S Z))
type Vec3 = Vec (S (S (S Z)))
type Vec4 = Vec (S (S (S (S Z))))
type Vec5 = Vec (S (S (S (S (S Z)))))
instance (Arity n, Show a) => Show (Vec n a) where
show v = "fromList " ++ show (toList v)
type instance Mutable (Vec n) = MVec n
instance (Arity n) => MVector (MVec n) a where
overlaps (MVec v) (MVec u) = sameMutableArray v u
new = do
v <- newArray (arity (undefined :: n)) uninitialised
return $ MVec v
copy = move
move (MVec dst) (MVec src) = copyMutableArray dst 0 src 0 (arity (undefined :: n))
unsafeRead (MVec v) i = readArray v i
unsafeWrite (MVec v) i x = writeArray v i x
instance (Arity n) => IVector (Vec n) a where
unsafeFreeze (MVec v) = do { a <- unsafeFreezeArray v; return $! Vec a }
unsafeThaw (Vec v) = do { a <- unsafeThawArray v; return $! MVec a }
unsafeIndex (Vec v) i = indexArray v i
type instance Dim (Vec n) = n
type instance DimM (MVec n) = n
instance (Arity n) => Vector (Vec n) a where
construct = constructVec
inspect = inspectVec
basicIndex = index
instance (Arity n) => VectorN Vec n a
instance (Arity n, Eq a) => Eq (Vec n a) where
(==) = eq
instance (Arity n, Ord a) => Ord (Vec n a) where
compare = ord
instance Arity n => Functor (Vec n) where
fmap = map
instance Arity n => Applicative (Vec n) where
pure = replicate
(<*>) = zipWith ($)
instance Arity n => F.Foldable (Vec n) where
foldr = foldr
instance Arity n => T.Traversable (Vec n) where
sequenceA = sequenceA
traverse = traverse
uninitialised :: a
uninitialised = error "Data.Vector.Fixed.Boxed: uninitialised element"