primitive-indexed-0.1.0.0

Safe HaskellNone
LanguageHaskell2010

Data.Primitive.Indexed.Types

Description

All of the folding functions in this module are strict in the accumulator.

Synopsis

Documentation

data Index n Source #

An integer that can be used to index into an array of length n.

Instances

Eq (Index k n) Source # 

Methods

(==) :: Index k n -> Index k n -> Bool #

(/=) :: Index k n -> Index k n -> Bool #

Ord (Index k n) Source # 

Methods

compare :: Index k n -> Index k n -> Ordering #

(<) :: Index k n -> Index k n -> Bool #

(<=) :: Index k n -> Index k n -> Bool #

(>) :: Index k n -> Index k n -> Bool #

(>=) :: Index k n -> Index k n -> Bool #

max :: Index k n -> Index k n -> Index k n #

min :: Index k n -> Index k n -> Index k n #

Show (Index k n) Source # 

Methods

showsPrec :: Int -> Index k n -> ShowS #

show :: Index k n -> String #

showList :: [Index k n] -> ShowS #

Prim (Index k n) Source # 

data Length n Source #

A value-level representation of length n.

Instances

Eq (Length k n) Source # 

Methods

(==) :: Length k n -> Length k n -> Bool #

(/=) :: Length k n -> Length k n -> Bool #

Ord (Length k n) Source # 

Methods

compare :: Length k n -> Length k n -> Ordering #

(<) :: Length k n -> Length k n -> Bool #

(<=) :: Length k n -> Length k n -> Bool #

(>) :: Length k n -> Length k n -> Bool #

(>=) :: Length k n -> Length k n -> Bool #

max :: Length k n -> Length k n -> Length k n #

min :: Length k n -> Length k n -> Length k n #

Show (Length k n) Source # 

Methods

showsPrec :: Int -> Length k n -> ShowS #

show :: Length k n -> String #

showList :: [Length k n] -> ShowS #

Prim (Length k n) Source # 

data Vector n a Source #

Instances

Functor (Vector k n) Source # 

Methods

fmap :: (a -> b) -> Vector k n a -> Vector k n b #

(<$) :: a -> Vector k n b -> Vector k n a #

Foldable (Vector k n) Source # 

Methods

fold :: Monoid m => Vector k n m -> m #

foldMap :: Monoid m => (a -> m) -> Vector k n a -> m #

foldr :: (a -> b -> b) -> b -> Vector k n a -> b #

foldr' :: (a -> b -> b) -> b -> Vector k n a -> b #

foldl :: (b -> a -> b) -> b -> Vector k n a -> b #

foldl' :: (b -> a -> b) -> b -> Vector k n a -> b #

foldr1 :: (a -> a -> a) -> Vector k n a -> a #

foldl1 :: (a -> a -> a) -> Vector k n a -> a #

toList :: Vector k n a -> [a] #

null :: Vector k n a -> Bool #

length :: Vector k n a -> Int #

elem :: Eq a => a -> Vector k n a -> Bool #

maximum :: Ord a => Vector k n a -> a #

minimum :: Ord a => Vector k n a -> a #

sum :: Num a => Vector k n a -> a #

product :: Num a => Vector k n a -> a #

Traversable (Vector k n) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Vector k n a -> f (Vector k n b) #

sequenceA :: Applicative f => Vector k n (f a) -> f (Vector k n a) #

mapM :: Monad m => (a -> m b) -> Vector k n a -> m (Vector k n b) #

sequence :: Monad m => Vector k n (m a) -> m (Vector k n a) #

Eq a => Eq (Vector k n a) Source # 

Methods

(==) :: Vector k n a -> Vector k n a -> Bool #

(/=) :: Vector k n a -> Vector k n a -> Bool #

Ord a => Ord (Vector k n a) Source # 

Methods

compare :: Vector k n a -> Vector k n a -> Ordering #

(<) :: Vector k n a -> Vector k n a -> Bool #

(<=) :: Vector k n a -> Vector k n a -> Bool #

(>) :: Vector k n a -> Vector k n a -> Bool #

(>=) :: Vector k n a -> Vector k n a -> Bool #

max :: Vector k n a -> Vector k n a -> Vector k n a #

min :: Vector k n a -> Vector k n a -> Vector k n a #

data PrimVector n a Source #

Instances

(Prim a, Eq a) => Eq (PrimVector k n a) Source # 

Methods

(==) :: PrimVector k n a -> PrimVector k n a -> Bool #

(/=) :: PrimVector k n a -> PrimVector k n a -> Bool #

(Prim a, Ord a) => Ord (PrimVector k n a) Source # 

Methods

compare :: PrimVector k n a -> PrimVector k n a -> Ordering #

(<) :: PrimVector k n a -> PrimVector k n a -> Bool #

(<=) :: PrimVector k n a -> PrimVector k n a -> Bool #

(>) :: PrimVector k n a -> PrimVector k n a -> Bool #

(>=) :: PrimVector k n a -> PrimVector k n a -> Bool #

max :: PrimVector k n a -> PrimVector k n a -> PrimVector k n a #

min :: PrimVector k n a -> PrimVector k n a -> PrimVector k n a #

ascendM :: forall m n a. (Monoid a, Monad m) => (Index n -> m a) -> Length n -> m a Source #

A strict left monadic fold over the ascending indices from zero up to a given length.

descendM :: forall m n a. (Monoid a, Monad m) => (Index n -> m a) -> Length n -> m a Source #

A strict monadic left fold over the descending indices from a given length down to zero.

ascend :: forall n a. (a -> Index n -> a) -> a -> Length n -> a Source #

A strict left fold over the ascending indices from zero up to a given length.

descend :: forall n a. (a -> Index n -> a) -> a -> Length n -> a Source #

A strict left fold over the descending indices from a given length down to zero.

with :: Int -> (forall n. Index n -> a) -> a Source #

Pass an integer length to a function that can accept any length. If the integer is below zero, this truncates it to zero.

reflect :: Length n -> Index n -> Index n Source #

Reflect an index about the middle of the length. For a length of 5 this has the following effect:

0 ==> 4
1 ==> 3
2 ==> 2
3 ==> 1
4 ==> 0

offset :: Length n -> Int -> Index n -> Index n Source #

Add an offset to an index and reduce in modulo the length to ensure that the resulting index is in bounds.

zero :: Index n -> Index n Source #

The existence of any index is evidence that there an index into the zero position is valid.

unindex :: Index n -> Int Source #

Convert an index to an integer, discarding the information about how it relates to a length.

unlength :: Length n -> Int Source #

Convert a length to an integer, discarding the information about how it relates to indices and other lengths.