Safe Haskell | None |
---|---|
Language | Haskell2010 |
The contiguous package presents a common API to a number of contiguous
array types and their mutable counterparts. This is enabled with the
Contiguous
typeclass, which parameterises over a contiguous array type and
defines the core operations. However, the stable part of the interface is
contained in this module, which combines those primitives into common,
efficient array algorithms suitable for replacing pointer-heavy list
manipulations.
Synopsis
- size :: (Contiguous arr, Element arr b) => arr b -> Int
- sizeMut :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m Int
- null :: Contiguous arr => arr b -> Bool
- index :: (Contiguous arr, Element arr b) => arr b -> Int -> b
- index# :: (Contiguous arr, Element arr b) => arr b -> Int -> (# b #)
- read :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m b
- indexM :: (Contiguous arr, Element arr b, Monad m) => arr b -> Int -> m b
- empty :: Contiguous arr => arr a
- new :: (Contiguous arr, PrimMonad m, Element arr b) => Int -> m (Mutable arr (PrimState m) b)
- singleton :: (Contiguous arr, Element arr a) => a -> arr a
- doubleton :: (Contiguous arr, Element arr a) => a -> a -> arr a
- tripleton :: (Contiguous arr, Element arr a) => a -> a -> a -> arr a
- quadrupleton :: (Contiguous arr, Element arr a) => a -> a -> a -> a -> arr a
- replicate :: (Contiguous arr, Element arr a) => Int -> a -> arr a
- replicateMut :: (Contiguous arr, PrimMonad m, Element arr b) => Int -> b -> m (Mutable arr (PrimState m) b)
- generate :: (Contiguous arr, Element arr a) => Int -> (Int -> a) -> arr a
- generateM :: (Contiguous arr, Element arr a, Monad m) => Int -> (Int -> m a) -> m (arr a)
- generateMutable :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> (Int -> a) -> m (Mutable arr (PrimState m) a)
- iterateN :: (Contiguous arr, Element arr a) => Int -> (a -> a) -> a -> arr a
- iterateMutableN :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> (a -> a) -> a -> m (Mutable arr (PrimState m) a)
- write :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> b -> m ()
- run :: Contiguous arr => (forall s. ST s (arr a)) -> arr a
- replicateMutM :: (PrimMonad m, Contiguous arr, Element arr a) => Int -> m a -> m (Mutable arr (PrimState m) a)
- generateMutableM :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> (Int -> m a) -> m (Mutable arr (PrimState m) a)
- iterateMutableNM :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> (a -> m a) -> a -> m (Mutable arr (PrimState m) a)
- create :: (Contiguous arr, Element arr a) => (forall s. ST s (Mutable arr s a)) -> arr a
- createT :: (Contiguous arr, Element arr a, Traversable f) => (forall s. ST s (f (Mutable arr s a))) -> f (arr a)
- unfoldr :: (Contiguous arr, Element arr a) => (b -> Maybe (a, b)) -> b -> arr a
- unfoldrN :: (Contiguous arr, Element arr a) => Int -> (b -> Maybe (a, b)) -> b -> arr a
- unfoldrMutable :: (Contiguous arr, Element arr a, PrimMonad m) => (b -> Maybe (a, b)) -> b -> m (Mutable arr (PrimState m) a)
- enumFromN :: (Contiguous arr, Element arr a, Enum a) => a -> Int -> arr a
- enumFromMutableN :: (Contiguous arr, Element arr a, PrimMonad m, Enum a) => a -> Int -> m (Mutable arr (PrimState m) a)
- append :: (Contiguous arr, Element arr a) => arr a -> arr a -> arr a
- insertAt :: (Contiguous arr, Element arr b) => arr b -> Int -> b -> arr b
- data Slice arr a
- data MutableSlice arr s a
- slice :: (Contiguous arr, Element arr a) => arr a -> Int -> Int -> Sliced arr a
- sliceMut :: (Contiguous arr, Element arr a) => Mutable arr s a -> Int -> Int -> MutableSliced arr s a
- toSlice :: (Contiguous arr, Element arr a) => arr a -> Sliced arr a
- toSliceMut :: (Contiguous arr, PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> m (MutableSliced arr (PrimState m) a)
- replaceAt :: (Contiguous arr, Element arr a) => arr a -> Int -> a -> arr a
- modifyAt :: (Contiguous arr, Element arr a) => (a -> a) -> arr a -> Int -> arr a
- modifyAt' :: (Contiguous arr, Element arr a) => (a -> a) -> arr a -> Int -> arr a
- modifyAtF :: (Contiguous arr, Element arr a, Functor f) => (a -> f a) -> arr a -> Int -> f (arr a)
- modifyAtF' :: (Contiguous arr, Element arr a, Monad f) => (a -> f a) -> arr a -> Int -> f (arr a)
- deleteAt :: (Contiguous arr, Element arr a) => arr a -> Int -> arr a
- reverse :: (Contiguous arr, Element arr a) => arr a -> arr a
- reverseMutable :: (Contiguous arr, Element arr a, PrimMonad m) => Mutable arr (PrimState m) a -> m ()
- reverseSlice :: (Contiguous arr, Element arr a, PrimMonad m) => Mutable arr (PrimState m) a -> Int -> Int -> m ()
- resize :: (ContiguousU arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m (Mutable arr (PrimState m) b)
- shrink :: (Contiguous arr, PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> Int -> m (Mutable arr (PrimState m) a)
- unsafeShrinkAndFreeze :: (Contiguous arr, PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> Int -> m (arr a)
- map :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (b -> c) -> arr1 b -> arr2 c
- map' :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (b -> c) -> arr1 b -> arr2 c
- mapMutable :: (Contiguous arr, Element arr a, PrimMonad m) => (a -> a) -> Mutable arr (PrimState m) a -> m ()
- mapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (a -> a) -> Mutable arr (PrimState m) a -> m ()
- imap :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (Int -> b -> c) -> arr1 b -> arr2 c
- imap' :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (Int -> b -> c) -> arr1 b -> arr2 c
- imapMutable :: (Contiguous arr, Element arr a, PrimMonad m) => (Int -> a -> a) -> Mutable arr (PrimState m) a -> m ()
- imapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (Int -> a -> a) -> Mutable arr (PrimState m) a -> m ()
- modify :: (Contiguous arr, Element arr a, PrimMonad m) => (a -> a) -> Mutable arr (PrimState m) a -> m ()
- modify' :: (Contiguous arr, Element arr a, PrimMonad m) => (a -> a) -> Mutable arr (PrimState m) a -> m ()
- mapMaybe :: forall arr1 arr2 a b. (Contiguous arr1, Element arr1 a, Contiguous arr2, Element arr2 b) => (a -> Maybe b) -> arr1 a -> arr2 b
- zip :: (Contiguous arr1, Contiguous arr2, Contiguous arr3, Element arr1 a, Element arr2 b, Element arr3 (a, b)) => arr1 a -> arr2 b -> arr3 (a, b)
- zipWith :: (Contiguous arr1, Contiguous arr2, Contiguous arr3, Element arr1 a, Element arr2 b, Element arr3 c) => (a -> b -> c) -> arr1 a -> arr2 b -> arr3 c
- izipWith :: (Contiguous arr1, Contiguous arr2, Contiguous arr3, Element arr1 a, Element arr2 b, Element arr3 c) => (Int -> a -> b -> c) -> arr1 a -> arr2 b -> arr3 c
- swap :: (Contiguous arr, Element arr a, PrimMonad m) => Mutable arr (PrimState m) a -> Int -> Int -> m ()
- filter :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> arr a
- ifilter :: (Contiguous arr, Element arr a) => (Int -> a -> Bool) -> arr a -> arr a
- catMaybes :: (Contiguous arr, Element arr a, Element arr (Maybe a)) => arr (Maybe a) -> arr a
- lefts :: forall arr a b. (Contiguous arr, Element arr a, Element arr (Either a b)) => arr (Either a b) -> arr a
- rights :: forall arr a b. (Contiguous arr, Element arr b, Element arr (Either a b)) => arr (Either a b) -> arr b
- partitionEithers :: forall arr a b. (Contiguous arr, Element arr a, Element arr b, Element arr (Either a b)) => arr (Either a b) -> (arr a, arr b)
- find :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> Maybe a
- findIndex :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> Maybe Int
- elem :: (Contiguous arr, Element arr a, Eq a) => a -> arr a -> Bool
- maximum :: (Contiguous arr, Element arr a, Ord a) => arr a -> Maybe a
- minimum :: (Contiguous arr, Element arr a, Ord a) => arr a -> Maybe a
- maximumBy :: (Contiguous arr, Element arr a) => (a -> a -> Ordering) -> arr a -> Maybe a
- minimumBy :: (Contiguous arr, Element arr a) => (a -> a -> Ordering) -> arr a -> Maybe a
- equals :: (Contiguous arr, Element arr b, Eq b) => arr b -> arr b -> Bool
- equalsMut :: Contiguous arr => Mutable arr s a -> Mutable arr s a -> Bool
- same :: ContiguousU arr => arr a -> arr a -> Bool
- foldl :: (Contiguous arr, Element arr a) => (b -> a -> b) -> b -> arr a -> b
- foldl' :: (Contiguous arr, Element arr a) => (b -> a -> b) -> b -> arr a -> b
- foldr :: (Contiguous arr, Element arr a) => (a -> b -> b) -> b -> arr a -> b
- foldr' :: (Contiguous arr, Element arr a) => (a -> b -> b) -> b -> arr a -> b
- foldMap :: (Contiguous arr, Element arr a, Monoid m) => (a -> m) -> arr a -> m
- foldMap' :: (Contiguous arr, Element arr a, Monoid m) => (a -> m) -> arr a -> m
- foldlMap' :: (Contiguous arr, Element arr a, Monoid m) => (a -> m) -> arr a -> m
- ifoldl' :: (Contiguous arr, Element arr a) => (b -> Int -> a -> b) -> b -> arr a -> b
- ifoldr :: (Contiguous arr, Element arr a) => (Int -> a -> b -> b) -> b -> arr a -> b
- ifoldr' :: (Contiguous arr, Element arr a) => (Int -> a -> b -> b) -> b -> arr a -> b
- ifoldlMap' :: (Contiguous arr, Element arr a, Monoid m) => (Int -> a -> m) -> arr a -> m
- ifoldlMap1' :: (Contiguous arr, Element arr a, Semigroup m) => (Int -> a -> m) -> arr a -> m
- foldlM' :: (Contiguous arr, Element arr a, Monad m) => (b -> a -> m b) -> b -> arr a -> m b
- ifoldlM' :: (Contiguous arr, Element arr a, Monad m) => (b -> Int -> a -> m b) -> b -> arr a -> m b
- asum :: (Contiguous arr, Element arr (f a), Alternative f) => arr (f a) -> f a
- all :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> Bool
- any :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> Bool
- foldrZipWith :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (a -> b -> c -> c) -> c -> arr1 a -> arr2 b -> c
- ifoldrZipWith :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> a -> b -> c -> c) -> c -> arr1 a -> arr2 b -> c
- foldlZipWithM' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Monad m) => (c -> a -> b -> m c) -> c -> arr1 a -> arr2 b -> m c
- ifoldlZipWithM' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Monad m) => (Int -> c -> a -> b -> m c) -> c -> arr1 a -> arr2 b -> m c
- traverse :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Applicative f) => (a -> f b) -> arr1 a -> f (arr2 b)
- traverse_ :: (Contiguous arr, Element arr a, Applicative f) => (a -> f b) -> arr a -> f ()
- itraverse :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Applicative f) => (Int -> a -> f b) -> arr1 a -> f (arr2 b)
- itraverse_ :: (Contiguous arr, Element arr a, Applicative f) => (Int -> a -> f b) -> arr a -> f ()
- traverseP :: (PrimMonad m, Contiguous arr1, Element arr1 a, Contiguous arr2, Element arr2 b) => (a -> m b) -> arr1 a -> m (arr2 b)
- itraverseP :: (PrimMonad m, Contiguous arr1, Element arr1 a, Contiguous arr2, Element arr2 b) => (Int -> a -> m b) -> arr1 a -> m (arr2 b)
- mapM :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Monad m) => (a -> m b) -> arr1 a -> m (arr2 b)
- forM :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Monad m) => arr1 a -> (a -> m b) -> m (arr2 b)
- mapM_ :: (Contiguous arr, Element arr a, Element arr b, Applicative f) => (a -> f b) -> arr a -> f ()
- forM_ :: (Contiguous arr, Element arr a, Element arr b, Applicative f) => arr a -> (a -> f b) -> f ()
- for :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Applicative f) => arr1 a -> (a -> f b) -> f (arr2 b)
- for_ :: (Contiguous arr, Element arr a, Applicative f) => arr a -> (a -> f b) -> f ()
- sequence :: (Contiguous arr1, Contiguous arr2, Element arr1 (f a), Element arr2 a, Applicative f) => arr1 (f a) -> f (arr2 a)
- sequence_ :: (Contiguous arr, Element arr (f a), Applicative f) => arr (f a) -> f ()
- (<$) :: (Contiguous arr1, Contiguous arr2, Element arr1 b, Element arr2 a) => a -> arr1 b -> arr2 a
- ap :: (Contiguous arr1, Contiguous arr2, Contiguous arr3, Element arr1 (a -> b), Element arr2 a, Element arr3 b) => arr1 (a -> b) -> arr2 a -> arr3 b
- scanl :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (b -> a -> b) -> b -> arr1 a -> arr2 b
- scanl' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (b -> a -> b) -> b -> arr1 a -> arr2 b
- iscanl :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> b -> a -> b) -> b -> arr1 a -> arr2 b
- iscanl' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> b -> a -> b) -> b -> arr1 a -> arr2 b
- prescanl :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (b -> a -> b) -> b -> arr1 a -> arr2 b
- prescanl' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (b -> a -> b) -> b -> arr1 a -> arr2 b
- iprescanl :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> b -> a -> b) -> b -> arr1 a -> arr2 b
- iprescanl' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> b -> a -> b) -> b -> arr1 a -> arr2 b
- mapAccum' :: forall arr1 arr2 a b c. (Contiguous arr1, Contiguous arr2, Element arr1 b, Element arr2 c, Monoid a) => (b -> (a, c)) -> arr1 b -> (a, arr2 c)
- mapAccumLM' :: (Contiguous arr1, Contiguous arr2, Element arr1 b, Element arr2 c, Monad m) => (a -> b -> m (a, c)) -> a -> arr1 b -> m (a, arr2 c)
- fromList :: (Contiguous arr, Element arr a) => [a] -> arr a
- fromListN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a
- fromListMutable :: (Contiguous arr, Element arr a, PrimMonad m) => [a] -> m (Mutable arr (PrimState m) a)
- fromListMutableN :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> [a] -> m (Mutable arr (PrimState m) a)
- unsafeFromListN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a
- unsafeFromListReverseN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a
- unsafeFromListReverseMutableN :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> [a] -> m (Mutable arr (PrimState m) a)
- toList :: (Contiguous arr, Element arr a) => arr a -> [a]
- toListMutable :: (Contiguous arr, Element arr a, PrimMonad m) => Mutable arr (PrimState m) a -> m [a]
- convert :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 b) => arr1 b -> arr2 b
- lift :: ContiguousU arr => Unlifted arr b -> arr b
- liftMut :: ContiguousU arr => UnliftedMut arr s b -> Mutable arr s b
- unlift :: ContiguousU arr => arr b -> Unlifted arr b
- unliftMut :: ContiguousU arr => Mutable arr s b -> UnliftedMut arr s b
- clone :: (Contiguous arr, Element arr b) => Sliced arr b -> arr b
- cloneMut :: (Contiguous arr, PrimMonad m, Element arr b) => MutableSliced arr (PrimState m) b -> m (Mutable arr (PrimState m) b)
- copy :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Sliced arr b -> m ()
- copyMut :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> MutableSliced arr (PrimState m) b -> m ()
- freeze :: (Contiguous arr, PrimMonad m, Element arr a) => MutableSliced arr (PrimState m) a -> m (arr a)
- thaw :: (Contiguous arr, PrimMonad m, Element arr b) => Sliced arr b -> m (Mutable arr (PrimState m) b)
- unsafeFreeze :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m (arr b)
- liftHashWithSalt :: (Contiguous arr, Element arr a) => (Int -> a -> Int) -> Int -> arr a -> Int
- rnf :: (Contiguous arr, NFData a, Element arr a) => arr a -> ()
- class Contiguous (arr :: Type -> Type) where
- class Contiguous arr => ContiguousU arr
- class Always a
- data Array a
- data MutableArray s a
- data SmallArray a
- data SmallMutableArray s a
- data PrimArray a
- data MutablePrimArray s a
- data UnliftedArray a
- data MutableUnliftedArray s a
Accessors
Length Information
sizeMut :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m Int Source #
The size of the mutable array
null :: Contiguous arr => arr b -> Bool Source #
Test whether the array is empty.
Indexing
index :: (Contiguous arr, Element arr b) => arr b -> Int -> b Source #
Index into an array at the given index.
index# :: (Contiguous arr, Element arr b) => arr b -> Int -> (# b #) Source #
Index into an array at the given index, yielding an unboxed one-tuple of the element.
read :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m b Source #
Read a mutable array at the given index.
Monadic indexing
indexM :: (Contiguous arr, Element arr b, Monad m) => arr b -> Int -> m b Source #
Indexing in a monad.
The monad allows operations to be strict in the array when necessary. Suppose array copying is implemented like this:
copy mv v = ... write mv i (v ! i) ...
For lazy arrays, v ! i
would not be not be evaluated,
which means that mv
would unnecessarily retain a reference
to v
in each element written.
With indexM
, copying can be implemented like this instead:
copy mv v = ... do x <- indexM v i write mv i x
Here, no references to v
are retained because indexing
(but not the elements) is evaluated eagerly.
Construction
Initialisation
empty :: Contiguous arr => arr a Source #
The empty array.
new :: (Contiguous arr, PrimMonad m, Element arr b) => Int -> m (Mutable arr (PrimState m) b) Source #
Allocate a new mutable array of the given size.
singleton :: (Contiguous arr, Element arr a) => a -> arr a Source #
Create a singleton array.
doubleton :: (Contiguous arr, Element arr a) => a -> a -> arr a Source #
Create a doubleton array.
tripleton :: (Contiguous arr, Element arr a) => a -> a -> a -> arr a Source #
Create a tripleton array.
quadrupleton :: (Contiguous arr, Element arr a) => a -> a -> a -> a -> arr a Source #
Create a quadrupleton array.
replicate :: (Contiguous arr, Element arr a) => Int -> a -> arr a Source #
is an array of length replicate
n xn
with x
the value of every element.
replicateMut :: (Contiguous arr, PrimMonad m, Element arr b) => Int -> b -> m (Mutable arr (PrimState m) b) Source #
is a mutable array of length replicateMut
n xn
with x
the
value of every element.
generate :: (Contiguous arr, Element arr a) => Int -> (Int -> a) -> arr a Source #
Construct an array of the given length by applying the function to each index.
generateM :: (Contiguous arr, Element arr a, Monad m) => Int -> (Int -> m a) -> m (arr a) Source #
Construct an array of the given length by applying the monadic action to each index.
generateMutable :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> (Int -> a) -> m (Mutable arr (PrimState m) a) Source #
Construct a mutable array of the given length by applying the function to each index.
iterateMutableN :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> (a -> a) -> a -> m (Mutable arr (PrimState m) a) Source #
Apply a function n
times to a value and construct a mutable array
where each consecutive element is the result of an additional
application of this function. The zeroth element is the original value.
write :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> b -> m () Source #
Write to a mutable array at the given index.
Running
run :: Contiguous arr => (forall s. ST s (arr a)) -> arr a Source #
Run an effectful computation that produces an array.
Monadic initialisation
replicateMutM :: (PrimMonad m, Contiguous arr, Element arr a) => Int -> m a -> m (Mutable arr (PrimState m) a) Source #
performs the action n times, gathering the results.replicateMutM
n act
generateMutableM :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> (Int -> m a) -> m (Mutable arr (PrimState m) a) Source #
Construct a mutable array of the given length by applying the monadic action to each index.
iterateMutableNM :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> (a -> m a) -> a -> m (Mutable arr (PrimState m) a) Source #
Apply a monadic function n
times to a value and construct a mutable array
where each consecutive element is the result of an additional
application of this function. The zeroth element is the original value.
create :: (Contiguous arr, Element arr a) => (forall s. ST s (Mutable arr s a)) -> arr a Source #
Execute the monad action and freeze the resulting array.
createT :: (Contiguous arr, Element arr a, Traversable f) => (forall s. ST s (f (Mutable arr s a))) -> f (arr a) Source #
Execute the monadic action and freeze the resulting array.
Unfolding
unfoldrMutable :: (Contiguous arr, Element arr a, PrimMonad m) => (b -> Maybe (a, b)) -> b -> m (Mutable arr (PrimState m) a) Source #
Enumeration
enumFromMutableN :: (Contiguous arr, Element arr a, PrimMonad m, Enum a) => a -> Int -> m (Mutable arr (PrimState m) a) Source #
Concatenation
append :: (Contiguous arr, Element arr a) => arr a -> arr a -> arr a Source #
Append two arrays.
Splitting and Splicing
:: (Contiguous arr, Element arr b) | |
=> arr b | slice to copy from |
-> Int | index in the output array to insert at |
-> b | element to insert |
-> arr b |
Copy a slice of an array and then insert an element into that array.
The default implementation performs a memset which would be unnecessary except that the garbage collector might trace the uninitialized array.
Was previously insertSlicing
@since 0.6.0
Slicing
Slices of immutable arrays: packages an offset and length with a backing array.
Since: 0.6.0
Instances
data MutableSlice arr s a Source #
Slices of mutable arrays: packages an offset and length with a mutable backing array.
Since: 0.6.0
sliceMut :: (Contiguous arr, Element arr a) => Mutable arr s a -> Int -> Int -> MutableSliced arr s a Source #
toSlice :: (Contiguous arr, Element arr a) => arr a -> Sliced arr a Source #
Create a Slice
that covers the entire array.
Since: 0.6.0
toSliceMut :: (Contiguous arr, PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> m (MutableSliced arr (PrimState m) a) Source #
Create a MutableSlice
that covers the entire array.
Since: 0.6.0
Modifying arrays
replaceAt :: (Contiguous arr, Element arr a) => arr a -> Int -> a -> arr a Source #
Create a copy of an array except the element at the index is replaced with the given value.
modifyAt' :: (Contiguous arr, Element arr a) => (a -> a) -> arr a -> Int -> arr a Source #
Variant of modifyAt that forces the result before installing it in the array.
modifyAtF :: (Contiguous arr, Element arr a, Functor f) => (a -> f a) -> arr a -> Int -> f (arr a) Source #
modifyAtF' :: (Contiguous arr, Element arr a, Monad f) => (a -> f a) -> arr a -> Int -> f (arr a) Source #
deleteAt :: (Contiguous arr, Element arr a) => arr a -> Int -> arr a Source #
Delete the element at the given position.
Permutations
reverse :: (Contiguous arr, Element arr a) => arr a -> arr a Source #
Reverse the elements of an array.
reverseMutable :: (Contiguous arr, Element arr a, PrimMonad m) => Mutable arr (PrimState m) a -> m () Source #
Reverse the elements of a mutable array, in-place.
:: (Contiguous arr, Element arr a, PrimMonad m) | |
=> Mutable arr (PrimState m) a | |
-> Int | start index |
-> Int | end index |
-> m () |
Reverse the elements of a slice of a mutable array, in-place.
Resizing
resize :: (ContiguousU arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m (Mutable arr (PrimState m) b) Source #
Resize an array into one with the given size.
:: (Contiguous arr, PrimMonad m, Element arr a) | |
=> Mutable arr (PrimState m) a | |
-> Int | new length |
-> m (Mutable arr (PrimState m) a) |
Resize an array without growing it.
Since: 0.6.0
Elementwise operations
Mapping
map :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (b -> c) -> arr1 b -> arr2 c Source #
Map over the elements of an array.
Note that because a new array must be created, the resulting array type can be different than the original.
map' :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (b -> c) -> arr1 b -> arr2 c Source #
Map strictly over the elements of an array.
Note that because a new array must be created, the resulting array type can be different than the original.
mapMutable :: (Contiguous arr, Element arr a, PrimMonad m) => (a -> a) -> Mutable arr (PrimState m) a -> m () Source #
Map over a mutable array, modifying the elements in place.
mapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (a -> a) -> Mutable arr (PrimState m) a -> m () Source #
Strictly map over a mutable array, modifying the elements in place.
imap :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (Int -> b -> c) -> arr1 b -> arr2 c Source #
Map over the elements of an array with the index.
imap' :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 c) => (Int -> b -> c) -> arr1 b -> arr2 c Source #
Map strictly over the elements of an array with the index.
Note that because a new array must be created, the resulting array type can be different than the original.
imapMutable :: (Contiguous arr, Element arr a, PrimMonad m) => (Int -> a -> a) -> Mutable arr (PrimState m) a -> m () Source #
Map over a mutable array with indices, modifying the elements in place.
imapMutable' :: (PrimMonad m, Contiguous arr, Element arr a) => (Int -> a -> a) -> Mutable arr (PrimState m) a -> m () Source #
Strictly map over a mutable array with indices, modifying the elements in place.
modify :: (Contiguous arr, Element arr a, PrimMonad m) => (a -> a) -> Mutable arr (PrimState m) a -> m () Source #
Modify the elements of a mutable array in-place.
modify' :: (Contiguous arr, Element arr a, PrimMonad m) => (a -> a) -> Mutable arr (PrimState m) a -> m () Source #
Strictly modify the elements of a mutable array in-place.
mapMaybe :: forall arr1 arr2 a b. (Contiguous arr1, Element arr1 a, Contiguous arr2, Element arr2 b) => (a -> Maybe b) -> arr1 a -> arr2 b Source #
Zipping
zip :: (Contiguous arr1, Contiguous arr2, Contiguous arr3, Element arr1 a, Element arr2 b, Element arr3 (a, b)) => arr1 a -> arr2 b -> arr3 (a, b) Source #
zip
takes two arrays and returns an array of
corresponding pairs.
zip [1, 2] ['a', 'b'] = [(1, 'a'), (2, 'b')]
If one input array is shorter than the other, excess elements of the longer array are discarded:
zip [1] ['a', 'b'] = [(1, 'a')] zip [1, 2] ['a'] = [(1, 'a')]
zipWith :: (Contiguous arr1, Contiguous arr2, Contiguous arr3, Element arr1 a, Element arr2 b, Element arr3 c) => (a -> b -> c) -> arr1 a -> arr2 b -> arr3 c Source #
izipWith :: (Contiguous arr1, Contiguous arr2, Contiguous arr3, Element arr1 a, Element arr2 b, Element arr3 c) => (Int -> a -> b -> c) -> arr1 a -> arr2 b -> arr3 c Source #
Variant of zipWith
that provides the index of each pair of elements.
Specific elements
swap :: (Contiguous arr, Element arr a, PrimMonad m) => Mutable arr (PrimState m) a -> Int -> Int -> m () Source #
Swap the elements of the mutable array at the given indices.
Working with predicates
Filtering
filter :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> arr a Source #
Drop elements that do not satisfy the predicate.
ifilter :: (Contiguous arr, Element arr a) => (Int -> a -> Bool) -> arr a -> arr a Source #
Drop elements that do not satisfy the predicate which is applied to values and their indices.
catMaybes :: (Contiguous arr, Element arr a, Element arr (Maybe a)) => arr (Maybe a) -> arr a Source #
lefts :: forall arr a b. (Contiguous arr, Element arr a, Element arr (Either a b)) => arr (Either a b) -> arr a Source #
rights :: forall arr a b. (Contiguous arr, Element arr b, Element arr (Either a b)) => arr (Either a b) -> arr b Source #
partitionEithers :: forall arr a b. (Contiguous arr, Element arr a, Element arr b, Element arr (Either a b)) => arr (Either a b) -> (arr a, arr b) Source #
Searching
elem :: (Contiguous arr, Element arr a, Eq a) => a -> arr a -> Bool Source #
Does the element occur in the structure?
maximum :: (Contiguous arr, Element arr a, Ord a) => arr a -> Maybe a Source #
The largest element of a structure.
minimum :: (Contiguous arr, Element arr a, Ord a) => arr a -> Maybe a Source #
The least element of a structure.
maximumBy :: (Contiguous arr, Element arr a) => (a -> a -> Ordering) -> arr a -> Maybe a Source #
The largest element of a structure with respect to the given comparison function.
minimumBy :: (Contiguous arr, Element arr a) => (a -> a -> Ordering) -> arr a -> Maybe a Source #
The least element of a structure with respect to the given comparison function.
Comparing for equality
equals :: (Contiguous arr, Element arr b, Eq b) => arr b -> arr b -> Bool Source #
Test the two arrays for equality.
equalsMut :: Contiguous arr => Mutable arr s a -> Mutable arr s a -> Bool Source #
Test the two mutable arrays for pointer equality. Does not check equality of elements.
same :: ContiguousU arr => arr a -> arr a -> Bool Source #
This function does not behave deterministically. Optimization level and
inlining can affect its results. However, the one thing that can be counted
on is that if it returns True
, the two immutable arrays are definitely the
same. This is useful as shortcut for equality tests. However, keep in mind
that a result of False
tells us nothing about the arguments.
Folds
foldl :: (Contiguous arr, Element arr a) => (b -> a -> b) -> b -> arr a -> b Source #
Left fold over the elements of an array.
foldl' :: (Contiguous arr, Element arr a) => (b -> a -> b) -> b -> arr a -> b Source #
Strict left fold over the elements of an array.
foldr :: (Contiguous arr, Element arr a) => (a -> b -> b) -> b -> arr a -> b Source #
Right fold over the element of an array.
foldr' :: (Contiguous arr, Element arr a) => (a -> b -> b) -> b -> arr a -> b Source #
Strict right fold over the elements of an array.
foldMap :: (Contiguous arr, Element arr a, Monoid m) => (a -> m) -> arr a -> m Source #
Monoidal fold over the element of an array.
foldMap' :: (Contiguous arr, Element arr a, Monoid m) => (a -> m) -> arr a -> m Source #
Strict monoidal fold over the elements of an array.
foldlMap' :: (Contiguous arr, Element arr a, Monoid m) => (a -> m) -> arr a -> m Source #
Strict left monoidal fold over the elements of an array.
ifoldl' :: (Contiguous arr, Element arr a) => (b -> Int -> a -> b) -> b -> arr a -> b Source #
Strict left fold over the elements of an array, where the accumulating function cares about the index of the element.
ifoldr :: (Contiguous arr, Element arr a) => (Int -> a -> b -> b) -> b -> arr a -> b Source #
Right fold over the element of an array, lazy in the accumulator, provides index to the step function.
ifoldr' :: (Contiguous arr, Element arr a) => (Int -> a -> b -> b) -> b -> arr a -> b Source #
Strict right fold over the elements of an array, where the accumulating function cares about the index of the element.
ifoldlMap' :: (Contiguous arr, Element arr a, Monoid m) => (Int -> a -> m) -> arr a -> m Source #
Strict monoidal fold over the elements of an array.
ifoldlMap1' :: (Contiguous arr, Element arr a, Semigroup m) => (Int -> a -> m) -> arr a -> m Source #
Strict monoidal fold over the elements of an array.
foldlM' :: (Contiguous arr, Element arr a, Monad m) => (b -> a -> m b) -> b -> arr a -> m b Source #
Strict left monadic fold over the elements of an array.
ifoldlM' :: (Contiguous arr, Element arr a, Monad m) => (b -> Int -> a -> m b) -> b -> arr a -> m b Source #
Strict left monadic fold over the elements of an array.
asum :: (Contiguous arr, Element arr (f a), Alternative f) => arr (f a) -> f a Source #
The sum of a collection of actions, generalizing concat
.
>>>
asum (C.fromList ['Just' "Hello", 'Nothing', Just "World"] :: Array String)
Just "Hello"
Zipping Folds
foldrZipWith :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (a -> b -> c -> c) -> c -> arr1 a -> arr2 b -> c Source #
Variant of zipWith
that accepts an accumulator, performing a lazy
right fold over both arrays.
ifoldrZipWith :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> a -> b -> c -> c) -> c -> arr1 a -> arr2 b -> c Source #
Variant of foldrZipWith
that provides the index of each pair of elements.
foldlZipWithM' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Monad m) => (c -> a -> b -> m c) -> c -> arr1 a -> arr2 b -> m c Source #
Variant of zipWith
that accepts an accumulator, performing a strict
left monadic fold over both arrays.
ifoldlZipWithM' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Monad m) => (Int -> c -> a -> b -> m c) -> c -> arr1 a -> arr2 b -> m c Source #
Variant of 'foldlZipWithM'' that provides the index of each pair of elements.
Traversals
traverse :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Applicative f) => (a -> f b) -> arr1 a -> f (arr2 b) Source #
Map each element of the array to an action, evaluate these
actions from left to right, and collect the results.
For a version that ignores the results, see traverse_
.
traverse_ :: (Contiguous arr, Element arr a, Applicative f) => (a -> f b) -> arr a -> f () Source #
Map each element of the array to an action, evaluate these
actions from left to right, and ignore the results.
For a version that doesn't ignore the results, see traverse
.
itraverse :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Applicative f) => (Int -> a -> f b) -> arr1 a -> f (arr2 b) Source #
Map each element of the array and its index to an action, evaluating these actions from left to right.
itraverse_ :: (Contiguous arr, Element arr a, Applicative f) => (Int -> a -> f b) -> arr a -> f () Source #
Map each element of the array and its index to an action,
evaluate these actions from left to right, and ignore the results.
For a version that doesn't ignore the results, see itraverse
.
traverseP :: (PrimMonad m, Contiguous arr1, Element arr1 a, Contiguous arr2, Element arr2 b) => (a -> m b) -> arr1 a -> m (arr2 b) Source #
Map each element of the array to an action, evaluate these actions from left to right, and collect the results in a new array.
itraverseP :: (PrimMonad m, Contiguous arr1, Element arr1 a, Contiguous arr2, Element arr2 b) => (Int -> a -> m b) -> arr1 a -> m (arr2 b) Source #
Map each element of the array to an action, evaluate these actions from left to right, and collect the results in a new array.
mapM :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Monad m) => (a -> m b) -> arr1 a -> m (arr2 b) Source #
Map each element of a structure to a monadic action,
evaluate these actions from left to right, and collect
the results. for a version that ignores the results see
mapM_
.
forM :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Monad m) => arr1 a -> (a -> m b) -> m (arr2 b) Source #
mapM_ :: (Contiguous arr, Element arr a, Element arr b, Applicative f) => (a -> f b) -> arr a -> f () Source #
forM_ :: (Contiguous arr, Element arr a, Element arr b, Applicative f) => arr a -> (a -> f b) -> f () Source #
for :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Applicative f) => arr1 a -> (a -> f b) -> f (arr2 b) Source #
for_ :: (Contiguous arr, Element arr a, Applicative f) => arr a -> (a -> f b) -> f () Source #
sequence :: (Contiguous arr1, Contiguous arr2, Element arr1 (f a), Element arr2 a, Applicative f) => arr1 (f a) -> f (arr2 a) Source #
Evaluate each action in the structure from left to right
and collect the results. For a version that ignores the
results see sequence_
.
sequence_ :: (Contiguous arr, Element arr (f a), Applicative f) => arr (f a) -> f () Source #
Evaluate each action in the structure from left to right
and ignore the results. For a version that doesn't ignore
the results see sequence
.
Typeclass method defaults
(<$) :: (Contiguous arr1, Contiguous arr2, Element arr1 b, Element arr2 a) => a -> arr1 b -> arr2 a Source #
Replace all locations in the input with the same value.
Equivalent to Data.Functor.<$
.
ap :: (Contiguous arr1, Contiguous arr2, Contiguous arr3, Element arr1 (a -> b), Element arr2 a, Element arr3 b) => arr1 (a -> b) -> arr2 a -> arr3 b Source #
Sequential application.
Equivalent to Control.Applicative.<*>
.
Prefix sums (scans)
scanl :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (b -> a -> b) -> b -> arr1 a -> arr2 b Source #
scanl' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (b -> a -> b) -> b -> arr1 a -> arr2 b Source #
A strictly accumulating version of scanl
.
iscanl :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> b -> a -> b) -> b -> arr1 a -> arr2 b Source #
A variant of scanl
whose function argument takes the current
index as an argument.
iscanl' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> b -> a -> b) -> b -> arr1 a -> arr2 b Source #
A strictly accumulating version of iscanl
.
prescanl :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (b -> a -> b) -> b -> arr1 a -> arr2 b Source #
A prescan.
prescanl f z = init . scanl f z
Example: prescanl (+) 0 <1,2,3,4> = <0,1,3,6>
prescanl' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (b -> a -> b) -> b -> arr1 a -> arr2 b Source #
Like prescanl
, but with a strict accumulator.
iprescanl :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> b -> a -> b) -> b -> arr1 a -> arr2 b Source #
A variant of prescanl
where the function argument takes
the current index of the array as an additional argument.
iprescanl' :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b) => (Int -> b -> a -> b) -> b -> arr1 a -> arr2 b Source #
Like iprescanl
, but with a strict accumulator.
mapAccum' :: forall arr1 arr2 a b c. (Contiguous arr1, Contiguous arr2, Element arr1 b, Element arr2 c, Monoid a) => (b -> (a, c)) -> arr1 b -> (a, arr2 c) Source #
mapAccumLM' :: (Contiguous arr1, Contiguous arr2, Element arr1 b, Element arr2 c, Monad m) => (a -> b -> m (a, c)) -> a -> arr1 b -> m (a, arr2 c) Source #
Monadic accumulating strict left fold over the elements on an array.
Conversions
Lists
fromList :: (Contiguous arr, Element arr a) => [a] -> arr a Source #
Convert a list into an array.
fromListMutable :: (Contiguous arr, Element arr a, PrimMonad m) => [a] -> m (Mutable arr (PrimState m) a) Source #
Convert a list into a mutable array of the given length.
fromListMutableN :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> [a] -> m (Mutable arr (PrimState m) a) Source #
:: (Contiguous arr, Element arr a) | |
=> Int | length of list |
-> [a] | list |
-> arr a |
Create an array from a list. If the given length does not match the actual length, this function has undefined behavior.
unsafeFromListReverseN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a Source #
Create an array from a list, reversing the order of the elements. If the given length does not match the actual length, this function has undefined behavior.
unsafeFromListReverseMutableN :: (Contiguous arr, Element arr a, PrimMonad m) => Int -> [a] -> m (Mutable arr (PrimState m) a) Source #
Create a mutable array from a list, reversing the order of the elements. If the given length does not match the actual length, this function has undefined behavior.
toList :: (Contiguous arr, Element arr a) => arr a -> [a] Source #
Convert an array to a list.
toListMutable :: (Contiguous arr, Element arr a, PrimMonad m) => Mutable arr (PrimState m) a -> m [a] Source #
Convert a mutable array to a list.
Other array types
convert :: (Contiguous arr1, Element arr1 b, Contiguous arr2, Element arr2 b) => arr1 b -> arr2 b Source #
Convert one type of array into another.
lift :: ContiguousU arr => Unlifted arr b -> arr b Source #
Lift an array (i.e. point to the data through an intervening thunk).
Since: 0.6.0
liftMut :: ContiguousU arr => UnliftedMut arr s b -> Mutable arr s b Source #
Lift a mutable array (i.e. point to the data through an intervening thunk).
Since: 0.6.0
unlift :: ContiguousU arr => arr b -> Unlifted arr b Source #
Unlift an array (i.e. point to the data without an intervening thunk).
Since: 0.6.0
unliftMut :: ContiguousU arr => Mutable arr s b -> UnliftedMut arr s b Source #
Unlift a mutable array (i.e. point to the data without an intervening thunk).
Since: 0.6.0
Between mutable and immutable variants
:: (Contiguous arr, Element arr b) | |
=> Sliced arr b | slice to copy |
-> arr b |
Clone a slice of an array.
:: (Contiguous arr, PrimMonad m, Element arr b) | |
=> MutableSliced arr (PrimState m) b | Array to copy a slice of |
-> m (Mutable arr (PrimState m) b) |
Clone a slice of a mutable array.
:: (Contiguous arr, PrimMonad m, Element arr b) | |
=> Mutable arr (PrimState m) b | destination array |
-> Int | offset into destination array |
-> Sliced arr b | source slice |
-> m () |
Copy a slice of an array into a mutable array.
:: (Contiguous arr, PrimMonad m, Element arr b) | |
=> Mutable arr (PrimState m) b | destination array |
-> Int | offset into destination array |
-> MutableSliced arr (PrimState m) b | source slice |
-> m () |
Copy a slice of a mutable array into another mutable array. In the case that the destination and source arrays are the same, the regions may overlap.
freeze :: (Contiguous arr, PrimMonad m, Element arr a) => MutableSliced arr (PrimState m) a -> m (arr a) Source #
Turn a mutable array slice an immutable array by copying.
Since: 0.6.0
thaw :: (Contiguous arr, PrimMonad m, Element arr b) => Sliced arr b -> m (Mutable arr (PrimState m) b) Source #
Copy a slice of an immutable array into a new mutable array.
unsafeFreeze :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m (arr b) Source #
Turn a mutable array into an immutable one without copying. The mutable array should not be used after this conversion.
Hashing
liftHashWithSalt :: (Contiguous arr, Element arr a) => (Int -> a -> Int) -> Int -> arr a -> Int Source #
Lift an accumulating hash function over the elements of the array, returning the final accumulated hash.
Forcing an array and its contents
rnf :: (Contiguous arr, NFData a, Element arr a) => arr a -> () Source #
Reduce the array and all of its elements to WHNF.
Classes
class Contiguous (arr :: Type -> Type) Source #
The Contiguous
typeclass as an interface to a multitude of
contiguous structures.
Some functions do not make sense on slices; for those, see ContiguousU
.
new, replicateMut, empty, singleton, doubleton, tripleton, quadrupleton, index, index#, indexM, read, write, null, size, sizeMut, equals, equalsMut, slice, sliceMut, toSlice, toSliceMut, clone_, cloneMut_, freeze_, thaw_, copy_, copyMut_, rnf, run
type Mutable arr = (r :: Type -> Type -> Type) | r -> arr Source #
The Mutable counterpart to the array.
type Element arr :: Type -> Constraint Source #
The constraint needed to store elements in the array.
type Sliced arr :: Type -> Type Source #
The slice type of this array.
The slice of a raw array type t
should be 'Slice t',
whereas the slice of a slice should be the same slice type.
Since: 0.6.0
type MutableSliced arr :: Type -> Type -> Type Source #
The mutable slice type of this array.
The mutable slice of a raw array type t
should be 'MutableSlice t',
whereas the mutable slice of a mutable slice should be the same slice type.
Since: 0.6.0
Instances
class Contiguous arr => ContiguousU arr Source #
The ContiguousU
typeclass is an extension of the Contiguous
typeclass,
but includes operations that make sense only on uncliced contiguous structures.
Since: 0.6.0
Instances
A typeclass that is satisfied by all types. This is used
used to provide a fake constraint for Array
and SmallArray
.
Instances
Always a Source # | |
Defined in Data.Primitive.Contiguous.Class |
Re-Exports
Boxed arrays.
Instances
data MutableArray s a #
Mutable boxed arrays associated with a primitive state token.
Instances
Eq (MutableArray s a) | |
Defined in Data.Primitive.Array (==) :: MutableArray s a -> MutableArray s a -> Bool # (/=) :: MutableArray s a -> MutableArray s a -> Bool # | |
(Typeable s, Typeable a) => Data (MutableArray s a) | |
Defined in Data.Primitive.Array gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MutableArray s a -> c (MutableArray s a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MutableArray s a) # toConstr :: MutableArray s a -> Constr # dataTypeOf :: MutableArray s a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MutableArray s a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MutableArray s a)) # gmapT :: (forall b. Data b => b -> b) -> MutableArray s a -> MutableArray s a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MutableArray s a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MutableArray s a -> r # gmapQ :: (forall d. Data d => d -> u) -> MutableArray s a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MutableArray s a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # |
data SmallArray a #
Instances
data SmallMutableArray s a #
Instances
Eq (SmallMutableArray s a) | |
Defined in Data.Primitive.SmallArray (==) :: SmallMutableArray s a -> SmallMutableArray s a -> Bool # (/=) :: SmallMutableArray s a -> SmallMutableArray s a -> Bool # | |
(Typeable s, Typeable a) => Data (SmallMutableArray s a) | |
Defined in Data.Primitive.SmallArray gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SmallMutableArray s a -> c (SmallMutableArray s a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SmallMutableArray s a) # toConstr :: SmallMutableArray s a -> Constr # dataTypeOf :: SmallMutableArray s a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SmallMutableArray s a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SmallMutableArray s a)) # gmapT :: (forall b. Data b => b -> b) -> SmallMutableArray s a -> SmallMutableArray s a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SmallMutableArray s a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SmallMutableArray s a -> r # gmapQ :: (forall d. Data d => d -> u) -> SmallMutableArray s a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SmallMutableArray s a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # |
Arrays of unboxed elements. This accepts types like Double
, Char
,
Int
and Word
, as well as their fixed-length variants (Word8
,
Word16
, etc.). Since the elements are unboxed, a PrimArray
is strict
in its elements. This differs from the behavior of Array
,
which is lazy in its elements.
Instances
data MutablePrimArray s a #
Mutable primitive arrays associated with a primitive state token.
These can be written to and read from in a monadic context that supports
sequencing, such as IO
or ST
. Typically, a mutable primitive array will
be built and then converted to an immutable primitive array using
unsafeFreezePrimArray
. However, it is also acceptable to simply discard
a mutable primitive array since it lives in managed memory and will be
garbage collected when no longer referenced.
Instances
Eq (MutablePrimArray s a) | |
Defined in Data.Primitive.PrimArray (==) :: MutablePrimArray s a -> MutablePrimArray s a -> Bool # (/=) :: MutablePrimArray s a -> MutablePrimArray s a -> Bool # | |
NFData (MutablePrimArray s a) | |
Defined in Data.Primitive.PrimArray rnf :: MutablePrimArray s a -> () # | |
PrimUnlifted (MutablePrimArray s a) | |
Defined in Data.Primitive.Unlifted.Class type Unlifted (MutablePrimArray s a) :: TYPE UnliftedRep # toUnlifted# :: MutablePrimArray s a -> Unlifted (MutablePrimArray s a) # fromUnlifted# :: Unlifted (MutablePrimArray s a) -> MutablePrimArray s a # writeUnliftedArray# :: MutableArrayArray# s0 -> Int# -> MutablePrimArray s a -> State# s0 -> State# s0 # readUnliftedArray# :: MutableArrayArray# s0 -> Int# -> State# s0 -> (# State# s0, MutablePrimArray s a #) # indexUnliftedArray# :: ArrayArray# -> Int# -> MutablePrimArray s a # | |
type Unlifted (MutablePrimArray s a) | |
Defined in Data.Primitive.Unlifted.Class |
data UnliftedArray a #
Instances
data MutableUnliftedArray s a #
Instances
Eq (MutableUnliftedArray s a) | |
Defined in Data.Primitive.Unlifted.Array (==) :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool # (/=) :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool # |