foundation-0.0.11: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Array

Description

Simple Array and Almost-Array-like data structure

Generally accessible in o(1)

Synopsis

Documentation

data Array a Source #

Array of a

Instances

Functor Array Source # 

Methods

fmap :: (a -> b) -> Array a -> Array b #

(<$) :: a -> Array b -> Array a #

Mappable Array Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Array a -> f (Array b) Source #

sequenceA :: Applicative f => Array (f a) -> f (Array a) Source #

mapM :: (Applicative m, Monad m) => (a -> m b) -> Array a -> m (Array b) Source #

sequence :: (Applicative m, Monad m) => Array (m a) -> m (Array a) Source #

IsList (Array ty) Source # 

Associated Types

type Item (Array ty) :: * #

Methods

fromList :: [Item (Array ty)] -> Array ty #

fromListN :: Int -> [Item (Array ty)] -> Array ty #

toList :: Array ty -> [Item (Array ty)] #

Eq a => Eq (Array a) Source # 

Methods

(==) :: Array a -> Array a -> Bool #

(/=) :: Array a -> Array a -> Bool #

Data ty => Data (Array ty) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Array ty -> c (Array ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array ty) #

toConstr :: Array ty -> Constr #

dataTypeOf :: Array ty -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Array ty)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array ty)) #

gmapT :: (forall b. Data b => b -> b) -> Array ty -> Array ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array ty -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Array ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Array ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array ty -> m (Array ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array ty -> m (Array ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array ty -> m (Array ty) #

Ord a => Ord (Array a) Source # 

Methods

compare :: Array a -> Array a -> Ordering #

(<) :: Array a -> Array a -> Bool #

(<=) :: Array a -> Array a -> Bool #

(>) :: Array a -> Array a -> Bool #

(>=) :: Array a -> Array a -> Bool #

max :: Array a -> Array a -> Array a #

min :: Array a -> Array a -> Array a #

Show a => Show (Array a) Source # 

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Monoid (Array a) Source # 

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

NormalForm a => NormalForm (Array a) Source # 

Methods

toNormalForm :: Array a -> () Source #

Copy (Array ty) Source # 

Methods

copy :: Array ty -> Array ty Source #

Buildable (Array ty) Source # 

Associated Types

type Mutable (Array ty) :: * -> * Source #

type Step (Array ty) :: * Source #

Methods

append :: PrimMonad prim => Element (Array ty) -> Builder (Array ty) (Mutable (Array ty)) (Step (Array ty)) prim err () Source #

build :: PrimMonad prim => Int -> Builder (Array ty) (Mutable (Array ty)) (Step (Array ty)) prim err () -> prim (Either err (Array ty)) Source #

Collection (Array ty) Source # 

Methods

null :: Array ty -> Bool Source #

length :: Array ty -> CountOf (Element (Array ty)) Source #

elem :: (Eq a, (* ~ a) (Element (Array ty))) => Element (Array ty) -> Array ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (Array ty))) => Element (Array ty) -> Array ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (Array ty))) => NonEmpty (Array ty) -> Element (Array ty) Source #

minimum :: (Ord a, (* ~ a) (Element (Array ty))) => NonEmpty (Array ty) -> Element (Array ty) Source #

any :: (Element (Array ty) -> Bool) -> Array ty -> Bool Source #

all :: (Element (Array ty) -> Bool) -> Array ty -> Bool Source #

Foldable (Array ty) Source # 

Methods

foldl' :: (a -> Element (Array ty) -> a) -> a -> Array ty -> a Source #

foldr :: (Element (Array ty) -> a -> a) -> a -> Array ty -> a Source #

foldr' :: (Element (Array ty) -> a -> a) -> a -> Array ty -> a Source #

IndexedCollection (Array ty) Source # 

Methods

(!) :: Array ty -> Offset (Element (Array ty)) -> Maybe (Element (Array ty)) Source #

findIndex :: (Element (Array ty) -> Bool) -> Array ty -> Maybe (Offset (Element (Array ty))) Source #

InnerFunctor (Array ty) Source # 

Methods

imap :: (Element (Array ty) -> Element (Array ty)) -> Array ty -> Array ty Source #

Sequential (Array ty) Source # 

Methods

take :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

revTake :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

drop :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

revDrop :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

splitAt :: CountOf (Element (Array ty)) -> Array ty -> (Array ty, Array ty) Source #

revSplitAt :: CountOf (Element (Array ty)) -> Array ty -> (Array ty, Array ty) Source #

splitOn :: (Element (Array ty) -> Bool) -> Array ty -> [Array ty] Source #

break :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

breakElem :: Element (Array ty) -> Array ty -> (Array ty, Array ty) Source #

takeWhile :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

dropWhile :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

intersperse :: Element (Array ty) -> Array ty -> Array ty Source #

intercalate :: Element (Array ty) -> Array ty -> Element (Array ty) Source #

span :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

filter :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

partition :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

reverse :: Array ty -> Array ty Source #

uncons :: Array ty -> Maybe (Element (Array ty), Array ty) Source #

unsnoc :: Array ty -> Maybe (Array ty, Element (Array ty)) Source #

snoc :: Array ty -> Element (Array ty) -> Array ty Source #

cons :: Element (Array ty) -> Array ty -> Array ty Source #

find :: (Element (Array ty) -> Bool) -> Array ty -> Maybe (Element (Array ty)) Source #

sortBy :: (Element (Array ty) -> Element (Array ty) -> Ordering) -> Array ty -> Array ty Source #

singleton :: Element (Array ty) -> Array ty Source #

head :: NonEmpty (Array ty) -> Element (Array ty) Source #

last :: NonEmpty (Array ty) -> Element (Array ty) Source #

tail :: NonEmpty (Array ty) -> Array ty Source #

init :: NonEmpty (Array ty) -> Array ty Source #

replicate :: CountOf (Element (Array ty)) -> Element (Array ty) -> Array ty Source #

isPrefixOf :: Array ty -> Array ty -> Bool Source #

isSuffixOf :: Array ty -> Array ty -> Bool Source #

isInfixOf :: Array ty -> Array ty -> Bool Source #

BoxedZippable (Array ty) Source # 

Methods

zip :: (Sequential a, Sequential b, (* ~ Element (Array ty)) (Element a, Element b)) => a -> b -> Array ty Source #

zip3 :: (Sequential a, Sequential b, Sequential c, (* ~ Element (Array ty)) (Element a, Element b, Element c)) => a -> b -> c -> Array ty Source #

zip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d)) => a -> b -> c -> d -> Array ty Source #

zip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e)) => a -> b -> c -> d -> e -> Array ty Source #

zip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f)) => a -> b -> c -> d -> e -> f -> Array ty Source #

zip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => a -> b -> c -> d -> e -> f -> g -> Array ty Source #

unzip :: (Sequential a, Sequential b, (* ~ Element (Array ty)) (Element a, Element b)) => Array ty -> (a, b) Source #

unzip3 :: (Sequential a, Sequential b, Sequential c, (* ~ Element (Array ty)) (Element a, Element b, Element c)) => Array ty -> (a, b, c) Source #

unzip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d)) => Array ty -> (a, b, c, d) Source #

unzip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e)) => Array ty -> (a, b, c, d, e) Source #

unzip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f)) => Array ty -> (a, b, c, d, e, f) Source #

unzip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => Array ty -> (a, b, c, d, e, f, g) Source #

Zippable (Array ty) Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element (Array ty)) -> a -> b -> Array ty Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element (Array ty)) -> a -> b -> c -> Array ty Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element (Array ty)) -> a -> b -> c -> d -> Array ty Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element (Array ty)) -> a -> b -> c -> d -> e -> Array ty Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element (Array ty)) -> a -> b -> c -> d -> e -> f -> Array ty Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element (Array ty)) -> a -> b -> c -> d -> e -> f -> g -> Array ty Source #

type Item (Array ty) Source # 
type Item (Array ty) = ty
type Element (Array ty) Source # 
type Element (Array ty) = ty
type Mutable (Array ty) Source # 
type Mutable (Array ty) = MArray ty
type Step (Array ty) Source # 
type Step (Array ty) = ty

data MArray a st Source #

Mutable Array of a

Instances

MutableCollection (MArray ty) Source # 

Associated Types

type MutableFreezed (MArray ty :: * -> *) :: * Source #

type MutableKey (MArray ty :: * -> *) :: * Source #

type MutableValue (MArray ty :: * -> *) :: * Source #

Methods

unsafeThaw :: PrimMonad prim => MutableFreezed (MArray ty) -> prim (MArray ty (PrimState prim)) Source #

unsafeFreeze :: PrimMonad prim => MArray ty (PrimState prim) -> prim (MutableFreezed (MArray ty)) Source #

thaw :: PrimMonad prim => MutableFreezed (MArray ty) -> prim (MArray ty (PrimState prim)) Source #

freeze :: PrimMonad prim => MArray ty (PrimState prim) -> prim (MutableFreezed (MArray ty)) Source #

mutNew :: PrimMonad prim => CountOf (MutableValue (MArray ty)) -> prim (MArray ty (PrimState prim)) Source #

mutUnsafeWrite :: PrimMonad prim => MArray ty (PrimState prim) -> MutableKey (MArray ty) -> MutableValue (MArray ty) -> prim () Source #

mutWrite :: PrimMonad prim => MArray ty (PrimState prim) -> MutableKey (MArray ty) -> MutableValue (MArray ty) -> prim () Source #

mutUnsafeRead :: PrimMonad prim => MArray ty (PrimState prim) -> MutableKey (MArray ty) -> prim (MutableValue (MArray ty)) Source #

mutRead :: PrimMonad prim => MArray ty (PrimState prim) -> MutableKey (MArray ty) -> prim (MutableValue (MArray ty)) Source #

type MutableFreezed (MArray ty) Source # 
type MutableFreezed (MArray ty) = Array ty
type MutableKey (MArray ty) Source # 
type MutableKey (MArray ty) = Offset ty
type MutableValue (MArray ty) Source # 
type MutableValue (MArray ty) = ty

data UArray ty Source #

An array of type built on top of GHC primitive.

The elements need to have fixed sized and the representation is a packed contiguous array in memory that can easily be passed to foreign interface

Instances

PrimType ty => IsList (UArray ty) Source # 

Associated Types

type Item (UArray ty) :: * #

Methods

fromList :: [Item (UArray ty)] -> UArray ty #

fromListN :: Int -> [Item (UArray ty)] -> UArray ty #

toList :: UArray ty -> [Item (UArray ty)] #

(PrimType ty, Eq ty) => Eq (UArray ty) Source # 

Methods

(==) :: UArray ty -> UArray ty -> Bool #

(/=) :: UArray ty -> UArray ty -> Bool #

Data ty => Data (UArray ty) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UArray ty -> c (UArray ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UArray ty) #

toConstr :: UArray ty -> Constr #

dataTypeOf :: UArray ty -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (UArray ty)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (UArray ty)) #

gmapT :: (forall b. Data b => b -> b) -> UArray ty -> UArray ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> UArray ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UArray ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) #

(PrimType ty, Ord ty) => Ord (UArray ty) Source # 

Methods

compare :: UArray ty -> UArray ty -> Ordering #

(<) :: UArray ty -> UArray ty -> Bool #

(<=) :: UArray ty -> UArray ty -> Bool #

(>) :: UArray ty -> UArray ty -> Bool #

(>=) :: UArray ty -> UArray ty -> Bool #

max :: UArray ty -> UArray ty -> UArray ty #

min :: UArray ty -> UArray ty -> UArray ty #

(PrimType ty, Show ty) => Show (UArray ty) Source # 

Methods

showsPrec :: Int -> UArray ty -> ShowS #

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

PrimType ty => Monoid (UArray ty) Source # 

Methods

mempty :: UArray ty #

mappend :: UArray ty -> UArray ty -> UArray ty #

mconcat :: [UArray ty] -> UArray ty #

NormalForm (UArray ty) Source # 

Methods

toNormalForm :: UArray ty -> () Source #

PrimType ty => Copy (UArray ty) Source # 

Methods

copy :: UArray ty -> UArray ty Source #

PrimType ty => Buildable (UArray ty) Source # 

Associated Types

type Mutable (UArray ty) :: * -> * Source #

type Step (UArray ty) :: * Source #

Methods

append :: PrimMonad prim => Element (UArray ty) -> Builder (UArray ty) (Mutable (UArray ty)) (Step (UArray ty)) prim err () Source #

build :: PrimMonad prim => Int -> Builder (UArray ty) (Mutable (UArray ty)) (Step (UArray ty)) prim err () -> prim (Either err (UArray ty)) Source #

PrimType ty => Collection (UArray ty) Source # 

Methods

null :: UArray ty -> Bool Source #

length :: UArray ty -> CountOf (Element (UArray ty)) Source #

elem :: (Eq a, (* ~ a) (Element (UArray ty))) => Element (UArray ty) -> UArray ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (UArray ty))) => Element (UArray ty) -> UArray ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (UArray ty))) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

minimum :: (Ord a, (* ~ a) (Element (UArray ty))) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

any :: (Element (UArray ty) -> Bool) -> UArray ty -> Bool Source #

all :: (Element (UArray ty) -> Bool) -> UArray ty -> Bool Source #

PrimType ty => Foldable (UArray ty) Source # 

Methods

foldl' :: (a -> Element (UArray ty) -> a) -> a -> UArray ty -> a Source #

foldr :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

foldr' :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

PrimType ty => IndexedCollection (UArray ty) Source # 

Methods

(!) :: UArray ty -> Offset (Element (UArray ty)) -> Maybe (Element (UArray ty)) Source #

findIndex :: (Element (UArray ty) -> Bool) -> UArray ty -> Maybe (Offset (Element (UArray ty))) Source #

PrimType ty => InnerFunctor (UArray ty) Source # 

Methods

imap :: (Element (UArray ty) -> Element (UArray ty)) -> UArray ty -> UArray ty Source #

PrimType ty => Sequential (UArray ty) Source # 

Methods

take :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revTake :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

drop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revDrop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

splitAt :: CountOf (Element (UArray ty)) -> UArray ty -> (UArray ty, UArray ty) Source #

revSplitAt :: CountOf (Element (UArray ty)) -> UArray ty -> (UArray ty, UArray ty) Source #

splitOn :: (Element (UArray ty) -> Bool) -> UArray ty -> [UArray ty] Source #

break :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

breakElem :: Element (UArray ty) -> UArray ty -> (UArray ty, UArray ty) Source #

takeWhile :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

dropWhile :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

intersperse :: Element (UArray ty) -> UArray ty -> UArray ty Source #

intercalate :: Element (UArray ty) -> UArray ty -> Element (UArray ty) Source #

span :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

filter :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

partition :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

reverse :: UArray ty -> UArray ty Source #

uncons :: UArray ty -> Maybe (Element (UArray ty), UArray ty) Source #

unsnoc :: UArray ty -> Maybe (UArray ty, Element (UArray ty)) Source #

snoc :: UArray ty -> Element (UArray ty) -> UArray ty Source #

cons :: Element (UArray ty) -> UArray ty -> UArray ty Source #

find :: (Element (UArray ty) -> Bool) -> UArray ty -> Maybe (Element (UArray ty)) Source #

sortBy :: (Element (UArray ty) -> Element (UArray ty) -> Ordering) -> UArray ty -> UArray ty Source #

singleton :: Element (UArray ty) -> UArray ty Source #

head :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

last :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

tail :: NonEmpty (UArray ty) -> UArray ty Source #

init :: NonEmpty (UArray ty) -> UArray ty Source #

replicate :: CountOf (Element (UArray ty)) -> Element (UArray ty) -> UArray ty Source #

isPrefixOf :: UArray ty -> UArray ty -> Bool Source #

isSuffixOf :: UArray ty -> UArray ty -> Bool Source #

isInfixOf :: UArray ty -> UArray ty -> Bool Source #

PrimType ty => Zippable (UArray ty) Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element (UArray ty)) -> a -> b -> UArray ty Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element (UArray ty)) -> a -> b -> c -> UArray ty Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element (UArray ty)) -> a -> b -> c -> d -> UArray ty Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element (UArray ty)) -> a -> b -> c -> d -> e -> UArray ty Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element (UArray ty)) -> a -> b -> c -> d -> e -> f -> UArray ty Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element (UArray ty)) -> a -> b -> c -> d -> e -> f -> g -> UArray ty Source #

PrimType a => Hashable (UArray a) Source # 

Methods

hashMix :: Hasher st => UArray a -> st -> st Source #

type Item (UArray ty) Source # 
type Item (UArray ty) = ty
type Element (UArray ty) Source # 
type Element (UArray ty) = ty
type Mutable (UArray ty) Source # 
type Mutable (UArray ty) = MUArray ty
type Step (UArray ty) Source # 
type Step (UArray ty) = ty

data MUArray ty st Source #

A Mutable array of types built on top of GHC primitive.

Element in this array can be modified in place.

Instances

PrimType ty => MutableCollection (MUArray ty) Source # 

Associated Types

type MutableFreezed (MUArray ty :: * -> *) :: * Source #

type MutableKey (MUArray ty :: * -> *) :: * Source #

type MutableValue (MUArray ty :: * -> *) :: * Source #

Methods

unsafeThaw :: PrimMonad prim => MutableFreezed (MUArray ty) -> prim (MUArray ty (PrimState prim)) Source #

unsafeFreeze :: PrimMonad prim => MUArray ty (PrimState prim) -> prim (MutableFreezed (MUArray ty)) Source #

thaw :: PrimMonad prim => MutableFreezed (MUArray ty) -> prim (MUArray ty (PrimState prim)) Source #

freeze :: PrimMonad prim => MUArray ty (PrimState prim) -> prim (MutableFreezed (MUArray ty)) Source #

mutNew :: PrimMonad prim => CountOf (MutableValue (MUArray ty)) -> prim (MUArray ty (PrimState prim)) Source #

mutUnsafeWrite :: PrimMonad prim => MUArray ty (PrimState prim) -> MutableKey (MUArray ty) -> MutableValue (MUArray ty) -> prim () Source #

mutWrite :: PrimMonad prim => MUArray ty (PrimState prim) -> MutableKey (MUArray ty) -> MutableValue (MUArray ty) -> prim () Source #

mutUnsafeRead :: PrimMonad prim => MUArray ty (PrimState prim) -> MutableKey (MUArray ty) -> prim (MutableValue (MUArray ty)) Source #

mutRead :: PrimMonad prim => MUArray ty (PrimState prim) -> MutableKey (MUArray ty) -> prim (MutableValue (MUArray ty)) Source #

type MutableFreezed (MUArray ty) Source # 
type MutableKey (MUArray ty) Source # 
type MutableKey (MUArray ty) = Offset ty
type MutableValue (MUArray ty) Source # 
type MutableValue (MUArray ty) = ty

data ChunkedUArray ty Source #

Instances

PrimType ty => IsList (ChunkedUArray ty) Source # 

Associated Types

type Item (ChunkedUArray ty) :: * #

PrimType ty => Eq (ChunkedUArray ty) Source # 
(Ord ty, PrimType ty) => Ord (ChunkedUArray ty) Source # 
(Show ty, PrimType ty) => Show (ChunkedUArray ty) Source # 
Monoid (ChunkedUArray a) Source # 
NormalForm (ChunkedUArray ty) Source # 

Methods

toNormalForm :: ChunkedUArray ty -> () Source #

PrimType ty => Collection (ChunkedUArray ty) Source # 
PrimType ty => Foldable (ChunkedUArray ty) Source # 

Methods

foldl' :: (a -> Element (ChunkedUArray ty) -> a) -> a -> ChunkedUArray ty -> a Source #

foldr :: (Element (ChunkedUArray ty) -> a -> a) -> a -> ChunkedUArray ty -> a Source #

foldr' :: (Element (ChunkedUArray ty) -> a -> a) -> a -> ChunkedUArray ty -> a Source #

PrimType ty => IndexedCollection (ChunkedUArray ty) Source # 
PrimType ty => Sequential (ChunkedUArray ty) Source # 

Methods

take :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

revTake :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

drop :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

revDrop :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

splitAt :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

revSplitAt :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

splitOn :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> [ChunkedUArray ty] Source #

break :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

breakElem :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

takeWhile :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> ChunkedUArray ty Source #

dropWhile :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> ChunkedUArray ty Source #

intersperse :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> ChunkedUArray ty Source #

intercalate :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> Element (ChunkedUArray ty) Source #

span :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

filter :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> ChunkedUArray ty Source #

partition :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

reverse :: ChunkedUArray ty -> ChunkedUArray ty Source #

uncons :: ChunkedUArray ty -> Maybe (Element (ChunkedUArray ty), ChunkedUArray ty) Source #

unsnoc :: ChunkedUArray ty -> Maybe (ChunkedUArray ty, Element (ChunkedUArray ty)) Source #

snoc :: ChunkedUArray ty -> Element (ChunkedUArray ty) -> ChunkedUArray ty Source #

cons :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> ChunkedUArray ty Source #

find :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> Maybe (Element (ChunkedUArray ty)) Source #

sortBy :: (Element (ChunkedUArray ty) -> Element (ChunkedUArray ty) -> Ordering) -> ChunkedUArray ty -> ChunkedUArray ty Source #

singleton :: Element (ChunkedUArray ty) -> ChunkedUArray ty Source #

head :: NonEmpty (ChunkedUArray ty) -> Element (ChunkedUArray ty) Source #

last :: NonEmpty (ChunkedUArray ty) -> Element (ChunkedUArray ty) Source #

tail :: NonEmpty (ChunkedUArray ty) -> ChunkedUArray ty Source #

init :: NonEmpty (ChunkedUArray ty) -> ChunkedUArray ty Source #

replicate :: CountOf (Element (ChunkedUArray ty)) -> Element (ChunkedUArray ty) -> ChunkedUArray ty Source #

isPrefixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

isSuffixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

isInfixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

type Item (ChunkedUArray ty) Source # 
type Item (ChunkedUArray ty) = ty
type Element (ChunkedUArray ty) Source # 
type Element (ChunkedUArray ty) = ty

data Bitmap Source #

Instances

IsList Bitmap Source # 

Associated Types

type Item Bitmap :: * #

Eq Bitmap Source # 

Methods

(==) :: Bitmap -> Bitmap -> Bool #

(/=) :: Bitmap -> Bitmap -> Bool #

Ord Bitmap Source # 
Show Bitmap Source # 
Monoid Bitmap Source # 
Collection Bitmap Source # 
Foldable Bitmap Source # 

Methods

foldl' :: (a -> Element Bitmap -> a) -> a -> Bitmap -> a Source #

foldr :: (Element Bitmap -> a -> a) -> a -> Bitmap -> a Source #

foldr' :: (Element Bitmap -> a -> a) -> a -> Bitmap -> a Source #

IndexedCollection Bitmap Source # 
InnerFunctor Bitmap Source # 
Sequential Bitmap Source # 

Methods

take :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

revTake :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

drop :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

revDrop :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

splitAt :: CountOf (Element Bitmap) -> Bitmap -> (Bitmap, Bitmap) Source #

revSplitAt :: CountOf (Element Bitmap) -> Bitmap -> (Bitmap, Bitmap) Source #

splitOn :: (Element Bitmap -> Bool) -> Bitmap -> [Bitmap] Source #

break :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

breakElem :: Element Bitmap -> Bitmap -> (Bitmap, Bitmap) Source #

takeWhile :: (Element Bitmap -> Bool) -> Bitmap -> Bitmap Source #

dropWhile :: (Element Bitmap -> Bool) -> Bitmap -> Bitmap Source #

intersperse :: Element Bitmap -> Bitmap -> Bitmap Source #

intercalate :: Element Bitmap -> Bitmap -> Element Bitmap Source #

span :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

filter :: (Element Bitmap -> Bool) -> Bitmap -> Bitmap Source #

partition :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

reverse :: Bitmap -> Bitmap Source #

uncons :: Bitmap -> Maybe (Element Bitmap, Bitmap) Source #

unsnoc :: Bitmap -> Maybe (Bitmap, Element Bitmap) Source #

snoc :: Bitmap -> Element Bitmap -> Bitmap Source #

cons :: Element Bitmap -> Bitmap -> Bitmap Source #

find :: (Element Bitmap -> Bool) -> Bitmap -> Maybe (Element Bitmap) Source #

sortBy :: (Element Bitmap -> Element Bitmap -> Ordering) -> Bitmap -> Bitmap Source #

singleton :: Element Bitmap -> Bitmap Source #

head :: NonEmpty Bitmap -> Element Bitmap Source #

last :: NonEmpty Bitmap -> Element Bitmap Source #

tail :: NonEmpty Bitmap -> Bitmap Source #

init :: NonEmpty Bitmap -> Bitmap Source #

replicate :: CountOf (Element Bitmap) -> Element Bitmap -> Bitmap Source #

isPrefixOf :: Bitmap -> Bitmap -> Bool Source #

isSuffixOf :: Bitmap -> Bitmap -> Bool Source #

isInfixOf :: Bitmap -> Bitmap -> Bool Source #

type Item Bitmap Source # 
type Element Bitmap Source # 

data MutableBitmap st Source #

Instances

MutableCollection MutableBitmap Source # 
type MutableFreezed MutableBitmap Source # 
type MutableKey MutableBitmap Source # 
type MutableValue MutableBitmap Source # 

class Eq ty => PrimType ty Source #

Represent the accessor for types that can be stored in the UArray and MUArray.

Types need to be a instance of storable and have fixed sized.

Instances

PrimType Char Source # 
PrimType Double Source # 
PrimType Float Source # 
PrimType Int Source # 
PrimType Int8 Source # 
PrimType Int16 Source # 
PrimType Int32 Source # 
PrimType Int64 Source # 
PrimType Word Source # 
PrimType Word8 Source # 
PrimType Word16 Source # 
PrimType Word32 Source # 
PrimType Word64 Source # 
PrimType CChar Source # 
PrimType CUChar Source # 
PrimType Seconds Source # 
PrimType NanoSeconds Source # 
PrimType a => PrimType (BE a) Source # 

Methods

primSizeInBytes :: Proxy * (BE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (BE a) -> BE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> prim (BE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> BE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (BE a) -> BE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (BE a) -> prim (BE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (BE a) -> BE a -> prim () Source #

PrimType a => PrimType (LE a) Source # 

Methods

primSizeInBytes :: Proxy * (LE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (LE a) -> LE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> prim (LE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> LE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (LE a) -> LE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (LE a) -> prim (LE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (LE a) -> LE a -> prim () Source #

data OutOfBound Source #

Exception during an operation accessing the vector out of bound

Represent the type of operation, the index accessed, and the total length of the vector.