fixed-vector-0.9.0.0: Generic vectors with statically known size.

Safe HaskellNone
LanguageHaskell98

Data.Vector.Fixed.Primitive

Contents

Description

Unboxed vectors with fixed length. Vectors from Data.Vector.Fixed.Unboxed provide more flexibility at no performeance cost.

Synopsis

Immutable

data Vec n a Source #

Unboxed vector with fixed length

Instances

(Arity n, Prim a) => VectorN Vec n a Source # 
(Arity n, Prim a) => Vector (Vec n) a Source # 

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

(Arity n, Prim a) => IVector (Vec n) a Source # 

Methods

unsafeFreeze :: PrimMonad m => Mutable (Vec n) (PrimState m) a -> m (Vec n a) Source #

unsafeThaw :: PrimMonad m => Vec n a -> m (Mutable (Vec n) (PrimState m) a) Source #

unsafeIndex :: Vec n a -> Int -> a Source #

(Arity n, Prim a, Eq a) => Eq (Vec n a) Source # 

Methods

(==) :: Vec n a -> Vec n a -> Bool #

(/=) :: Vec n a -> Vec n a -> Bool #

(Typeable * n, Arity n, Prim a, Data a) => Data (Vec n a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vec n a -> c (Vec n a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vec n a) #

toConstr :: Vec n a -> Constr #

dataTypeOf :: Vec n a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Vec n a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vec n a)) #

gmapT :: (forall b. Data b => b -> b) -> Vec n a -> Vec n a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vec n a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vec n a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Vec n a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vec n a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vec n a -> m (Vec n a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vec n a -> m (Vec n a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vec n a -> m (Vec n a) #

(Arity n, Prim a, Ord a) => Ord (Vec n a) Source # 

Methods

compare :: Vec n a -> Vec n a -> Ordering #

(<) :: Vec n a -> Vec n a -> Bool #

(<=) :: Vec n a -> Vec n a -> Bool #

(>) :: Vec n a -> Vec n a -> Bool #

(>=) :: Vec n a -> Vec n a -> Bool #

max :: Vec n a -> Vec n a -> Vec n a #

min :: Vec n a -> Vec n a -> Vec n a #

(Arity n, Prim a, Show a) => Show (Vec n a) Source # 

Methods

showsPrec :: Int -> Vec n a -> ShowS #

show :: Vec n a -> String #

showList :: [Vec n a] -> ShowS #

(Arity n, Prim a, Monoid a) => Monoid (Vec n a) Source # 

Methods

mempty :: Vec n a #

mappend :: Vec n a -> Vec n a -> Vec n a #

mconcat :: [Vec n a] -> Vec n a #

(Storable a, Prim a, Arity n) => Storable (Vec n a) Source # 

Methods

sizeOf :: Vec n a -> Int #

alignment :: Vec n a -> Int #

peekElemOff :: Ptr (Vec n a) -> Int -> IO (Vec n a) #

pokeElemOff :: Ptr (Vec n a) -> Int -> Vec n a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Vec n a) #

pokeByteOff :: Ptr b -> Int -> Vec n a -> IO () #

peek :: Ptr (Vec n a) -> IO (Vec n a) #

poke :: Ptr (Vec n a) -> Vec n a -> IO () #

(Arity n, Prim a, NFData a) => NFData (Vec n a) Source # 

Methods

rnf :: Vec n a -> () #

type Dim (Vec n) Source # 
type Dim (Vec n) = n
type Mutable (Vec n) Source # 
type Mutable (Vec n) = MVec n

type Vec1 = Vec (S Z) Source #

type Vec2 = Vec (S (S Z)) Source #

type Vec3 = Vec (S (S (S Z))) Source #

type Vec4 = Vec (S (S (S (S Z)))) Source #

type Vec5 = Vec (S (S (S (S (S Z))))) Source #

Mutable

data MVec n s a Source #

Mutable unboxed vector with fixed length

Instances

(Arity n, Prim a) => MVector (MVec n) a Source # 

Methods

overlaps :: MVec n s a -> MVec n s a -> Bool Source #

copy :: PrimMonad m => MVec n (PrimState m) a -> MVec n (PrimState m) a -> m () Source #

move :: PrimMonad m => MVec n (PrimState m) a -> MVec n (PrimState m) a -> m () Source #

new :: PrimMonad m => m (MVec n (PrimState m) a) Source #

unsafeRead :: PrimMonad m => MVec n (PrimState m) a -> Int -> m a Source #

unsafeWrite :: PrimMonad m => MVec n (PrimState m) a -> Int -> a -> m () Source #

type DimM (MVec n) Source # 
type DimM (MVec n) = n

Type classes

class Prim a #

Class of types supporting primitive array operations

Instances

Prim Char 
Prim Double 
Prim Float 
Prim Int 
Prim Int8 
Prim Int16 
Prim Int32 
Prim Int64 
Prim Word 
Prim Word8 
Prim Word16 
Prim Word32 
Prim Word64 
Prim Addr