contiguous-0.5.2: Unified interface for primitive arrays
Safe HaskellNone
LanguageHaskell2010

Data.Primitive.Contiguous

Description

The contiguous typeclass parameterises over a contiguous array type. This allows us to have a common API to a number of contiguous array types and their mutable counterparts.

Synopsis

Accessors

Length Information

size :: (Contiguous arr, Element arr b) => arr b -> Int Source #

The size of the array

sizeMutable :: (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 #

replicate n x is an array of length n with x the value of every element.

replicateMutable :: (Contiguous arr, PrimMonad m, Element arr b) => Int -> b -> m (Mutable arr (PrimState m) b) Source #

replicateMutable n x is a mutable array of length n 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.

iterateN :: (Contiguous arr, Element arr a) => Int -> (a -> a) -> a -> arr a Source #

Apply a function n times to a value and construct an array where each consecutive element is the result of an additional application of this function. The zeroth element is the original value.

iterateN 5 (+ 1) 0 = fromListN 5 [0,1,2,3,4]

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

replicateMutableM :: (PrimMonad m, Contiguous arr, Element arr a) => Int -> m a -> m (Mutable arr (PrimState m) a) Source #

replicateMutableM n act performs the action n times, gathering the results.

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

unfoldr :: (Contiguous arr, Element arr a) => (b -> Maybe (a, b)) -> b -> arr a Source #

Construct an array by repeatedly applying a generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

>>> unfoldr (\n -> if n == 0 then Nothing else Just (n,n-1) 10
    <10,9,8,7,6,5,4,3,2,1>

unfoldrN :: (Contiguous arr, Element arr a) => Int -> (b -> Maybe (a, b)) -> b -> arr a Source #

Construct an array with at most n elements by repeatedly applying the generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

unfoldrMutable :: (Contiguous arr, Element arr a, PrimMonad m) => (b -> Maybe (a, b)) -> b -> m (Mutable arr (PrimState m) a) Source #

Construct a mutable array by repeatedly applying a generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

>>> unfoldrMutable (\n -> if n == 0 then Nothing else Just (n,n-1) 10
    <10,9,8,7,6,5,4,3,2,1>

Enumeration

enumFromN :: (Contiguous arr, Element arr a, Enum a) => a -> Int -> arr a Source #

Yield an array of the given length containing the values x, succ x, succ (succ x) etc.

enumFromMutableN :: (Contiguous arr, Element arr a, PrimMonad m, Enum a) => a -> Int -> m (Mutable arr (PrimState m) a) Source #

Yield a mutable array of the given length containing the values x, succ x, succ (succ x) etc.

Concatenation

append :: (Contiguous arr, Element arr a) => arr a -> arr a -> arr a Source #

Append two arrays.

Splitting and Splicing

insertAt :: (Contiguous arr, Element arr a) => arr a -> Int -> a -> arr a Source #

Insert an element into an array at the given index.

insertSlicing Source #

Arguments

:: (Contiguous arr, Element arr b) 
=> arr b

array to copy a slice from

-> Int

offset into source array

-> Int

length of the slice

-> Int

index in the output array to insert at

-> b

element to insert

-> arr b 

Copy a slice of an array an 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.

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 #

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 #

Variant of modifyAtF that forces the result before installing it in the array. Note that this requires Monad rather than Functor.

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.

reverseSlice Source #

Arguments

:: (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 :: (Contiguous 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.

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 #

The mapMaybe function is a version of map which can throw out elements. In particular, the functional arguments returns something of type Maybe b. If this is Nothing, no element is added on to the result array. If it is Just b, then b is included in the result array.

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 #

zipWith generalises zip by zipping with the function given as the first argument, instead of a tupling function. For example, zipWith (+) is applied to two arrays to produce an array of the corresponding sums.

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 #

The catMaybes function takes a list of Maybes and returns a list of all the Just values.

lefts :: forall arr a b. (Contiguous arr, Element arr a, Element arr (Either a b)) => arr (Either a b) -> arr a Source #

Extracts from an array of Either all the Left elements. All the Left elements are extracted in order.

rights :: forall arr a b. (Contiguous arr, Element arr b, Element arr (Either a b)) => arr (Either a b) -> arr b Source #

Extracts from an array of Either all the Right elements. All the Right elements are extracted in order.

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 #

Partitions an array of Either into two arrays. All the Left elements are extracted, in order, to the first component of the output. Similarly the Right elements are extracted to the second component of the output.

Searching

find :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> Maybe a Source #

find takes a predicate and an array, and returns the leftmost element of the array matching the prediate, or Nothing if there is no such element.

findIndex :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> Maybe Int Source #

findIndex takes a predicate and an array, and returns the index of the leftmost element of the array matching the prediate, or Nothing if there is no such element.

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.

equalsMutable :: 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 :: Contiguous 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 #

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"

all :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> Bool Source #

any :: (Contiguous arr, Element arr a) => (a -> Bool) -> arr a -> Bool Source #

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, Contiguous arr2, Element arr1 a, 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.

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 #

forM is mapM with its arguments flipped. For a version that ignores its results, see forM_.

mapM_ :: (Contiguous arr, Element arr a, Element arr b, Applicative f) => (a -> f b) -> arr a -> f () Source #

Map each element of a structure to a monadic action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see mapM.

mapM_ = traverse_

forM_ :: (Contiguous arr, Element arr a, Element arr b, Applicative f) => arr a -> (a -> f b) -> f () Source #

forM_ is mapM_ with its arguments flipped. For a version that doesn't ignore its results, see forM.

for :: (Contiguous arr1, Contiguous arr2, Element arr1 a, Element arr2 b, Applicative f) => arr1 a -> (a -> f b) -> f (arr2 b) Source #

for is traverse with its arguments flipped. For a version that ignores the results see for_.

for_ :: (Contiguous arr, Element arr a, Applicative f) => arr a -> (a -> f b) -> f () Source #

for_ is traverse_ with its arguments flipped. For a version that doesn't ignore the results see for.

>>> for_ (C.fromList [1..4] :: PrimArray Int) print
1
2
3
4

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 is similar to foldl, but returns an array of successive reduced values from the left:

scanl f z [x1, x2, ...] = [z, f z x1, f (f z x1) x2, ...]

Note that

last (toList (scanl f z xs)) == foldl f z xs.

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.

fromListN :: (Contiguous arr, Element arr a) => Int -> [a] -> arr a Source #

Given an Int that is representative of the length of the list, convert the list into a mutable array of the given length.

Note: calls error if the given length is incorrect.

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 #

Given an Int that is representative of the length of the list, convert the list into a mutable array of the given length.

Note: calls error if the given length is incorrect.

unsafeFromListN Source #

Arguments

:: (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 :: Contiguous arr => ArrayArray# -> arr b Source #

Lift an ArrayArray# into an array.

unlift :: Contiguous arr => arr b -> ArrayArray# Source #

Unlift an array into an ArrayArray#.

Between mutable and immutable variants

clone Source #

Arguments

:: (Contiguous arr, Element arr b) 
=> arr b

Array to copy a slice of

-> Int

Offset into the array

-> Int

Length of the slice

-> arr b 

Clone a slice of an array.

cloneMutable Source #

Arguments

:: (Contiguous arr, PrimMonad m, Element arr b) 
=> Mutable arr (PrimState m) b

Array to copy a slice of

-> Int

Offset into the array

-> Int

Length of the slice

-> m (Mutable arr (PrimState m) b) 

Clone a slice of a mutable array.

copy Source #

Arguments

:: (Contiguous arr, PrimMonad m, Element arr b) 
=> Mutable arr (PrimState m) b

destination array

-> Int

offset into destination array

-> arr b

source array

-> Int

offset into source array

-> Int

number of elements to copy

-> m () 

Copy a slice of an array into a mutable array.

copyMutable Source #

Arguments

:: (Contiguous arr, PrimMonad m, Element arr b) 
=> Mutable arr (PrimState m) b

destination array

-> Int

offset into destination array

-> Mutable arr (PrimState m) b

source array

-> Int

offset into source array

-> Int

number of elements to copy

-> 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 Source #

Arguments

:: (Contiguous arr, PrimMonad m, Element arr b) 
=> Mutable arr (PrimState m) b 
-> Int

offset into the array

-> Int

length of the slice

-> m (arr b) 

Turn a mutable array into an immutable one with copying, using a slice of the mutable array.

thaw Source #

Arguments

:: (Contiguous arr, PrimMonad m, Element arr b) 
=> arr b 
-> Int

offset into the array

-> Int

length of the slice

-> m (Mutable arr (PrimState m) b) 

Copy a slice of an immutable array into a new mutable array.

unsafeFreeze :: (Contiguous arr, PrimMonad m) => 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.

Associated Types

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.

Instances

Instances details
Contiguous PrimArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

type Mutable PrimArray = (r :: Type -> Type -> Type) Source #

type Element PrimArray :: Type -> Constraint Source #

Methods

empty :: PrimArray a Source #

null :: PrimArray b -> Bool Source #

new :: (PrimMonad m, Element PrimArray b) => Int -> m (Mutable PrimArray (PrimState m) b) Source #

replicateMutable :: (PrimMonad m, Element PrimArray b) => Int -> b -> m (Mutable PrimArray (PrimState m) b) Source #

index :: Element PrimArray b => PrimArray b -> Int -> b Source #

index# :: Element PrimArray b => PrimArray b -> Int -> (# b #) Source #

indexM :: (Element PrimArray b, Monad m) => PrimArray b -> Int -> m b Source #

read :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> m (Mutable PrimArray (PrimState m) b) Source #

size :: Element PrimArray b => PrimArray b -> Int Source #

sizeMutable :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable PrimArray (PrimState m) b -> m (PrimArray b) Source #

freeze :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> Int -> m (PrimArray b) Source #

thaw :: (PrimMonad m, Element PrimArray b) => PrimArray b -> Int -> Int -> m (Mutable PrimArray (PrimState m) b) Source #

copy :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> PrimArray b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> Mutable PrimArray (PrimState m) b -> Int -> Int -> m () Source #

clone :: Element PrimArray b => PrimArray b -> Int -> Int -> PrimArray b Source #

cloneMutable :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> Int -> m (Mutable PrimArray (PrimState m) b) Source #

insertSlicing :: Element PrimArray b => PrimArray b -> Int -> Int -> Int -> b -> PrimArray b Source #

equals :: (Element PrimArray b, Eq b) => PrimArray b -> PrimArray b -> Bool Source #

equalsMutable :: Mutable PrimArray s a -> Mutable PrimArray s a -> Bool Source #

unlift :: PrimArray b -> ArrayArray# Source #

lift :: ArrayArray# -> PrimArray b Source #

singleton :: Element PrimArray a => a -> PrimArray a Source #

doubleton :: Element PrimArray a => a -> a -> PrimArray a Source #

tripleton :: Element PrimArray a => a -> a -> a -> PrimArray a Source #

quadrupleton :: Element PrimArray a => a -> a -> a -> a -> PrimArray a Source #

rnf :: (NFData a, Element PrimArray a) => PrimArray a -> () Source #

run :: (forall s. ST s (PrimArray a)) -> PrimArray a Source #

Contiguous SmallArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

type Mutable SmallArray = (r :: Type -> Type -> Type) Source #

type Element SmallArray :: Type -> Constraint Source #

Methods

empty :: SmallArray a Source #

null :: SmallArray b -> Bool Source #

new :: (PrimMonad m, Element SmallArray b) => Int -> m (Mutable SmallArray (PrimState m) b) Source #

replicateMutable :: (PrimMonad m, Element SmallArray b) => Int -> b -> m (Mutable SmallArray (PrimState m) b) Source #

index :: Element SmallArray b => SmallArray b -> Int -> b Source #

index# :: Element SmallArray b => SmallArray b -> Int -> (# b #) Source #

indexM :: (Element SmallArray b, Monad m) => SmallArray b -> Int -> m b Source #

read :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> m (Mutable SmallArray (PrimState m) b) Source #

size :: Element SmallArray b => SmallArray b -> Int Source #

sizeMutable :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable SmallArray (PrimState m) b -> m (SmallArray b) Source #

freeze :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> Int -> m (SmallArray b) Source #

thaw :: (PrimMonad m, Element SmallArray b) => SmallArray b -> Int -> Int -> m (Mutable SmallArray (PrimState m) b) Source #

copy :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> SmallArray b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> Mutable SmallArray (PrimState m) b -> Int -> Int -> m () Source #

clone :: Element SmallArray b => SmallArray b -> Int -> Int -> SmallArray b Source #

cloneMutable :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> Int -> m (Mutable SmallArray (PrimState m) b) Source #

insertSlicing :: Element SmallArray b => SmallArray b -> Int -> Int -> Int -> b -> SmallArray b Source #

equals :: (Element SmallArray b, Eq b) => SmallArray b -> SmallArray b -> Bool Source #

equalsMutable :: Mutable SmallArray s a -> Mutable SmallArray s a -> Bool Source #

unlift :: SmallArray b -> ArrayArray# Source #

lift :: ArrayArray# -> SmallArray b Source #

singleton :: Element SmallArray a => a -> SmallArray a Source #

doubleton :: Element SmallArray a => a -> a -> SmallArray a Source #

tripleton :: Element SmallArray a => a -> a -> a -> SmallArray a Source #

quadrupleton :: Element SmallArray a => a -> a -> a -> a -> SmallArray a Source #

rnf :: (NFData a, Element SmallArray a) => SmallArray a -> () Source #

run :: (forall s. ST s (SmallArray a)) -> SmallArray a Source #

Contiguous Array Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

type Mutable Array = (r :: Type -> Type -> Type) Source #

type Element Array :: Type -> Constraint Source #

Methods

empty :: Array a Source #

null :: Array b -> Bool Source #

new :: (PrimMonad m, Element Array b) => Int -> m (Mutable Array (PrimState m) b) Source #

replicateMutable :: (PrimMonad m, Element Array b) => Int -> b -> m (Mutable Array (PrimState m) b) Source #

index :: Element Array b => Array b -> Int -> b Source #

index# :: Element Array b => Array b -> Int -> (# b #) Source #

indexM :: (Element Array b, Monad m) => Array b -> Int -> m b Source #

read :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> m (Mutable Array (PrimState m) b) Source #

size :: Element Array b => Array b -> Int Source #

sizeMutable :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable Array (PrimState m) b -> m (Array b) Source #

freeze :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Int -> m (Array b) Source #

thaw :: (PrimMonad m, Element Array b) => Array b -> Int -> Int -> m (Mutable Array (PrimState m) b) Source #

copy :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Array b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Mutable Array (PrimState m) b -> Int -> Int -> m () Source #

clone :: Element Array b => Array b -> Int -> Int -> Array b Source #

cloneMutable :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Int -> m (Mutable Array (PrimState m) b) Source #

insertSlicing :: Element Array b => Array b -> Int -> Int -> Int -> b -> Array b Source #

equals :: (Element Array b, Eq b) => Array b -> Array b -> Bool Source #

equalsMutable :: Mutable Array s a -> Mutable Array s a -> Bool Source #

unlift :: Array b -> ArrayArray# Source #

lift :: ArrayArray# -> Array b Source #

singleton :: Element Array a => a -> Array a Source #

doubleton :: Element Array a => a -> a -> Array a Source #

tripleton :: Element Array a => a -> a -> a -> Array a Source #

quadrupleton :: Element Array a => a -> a -> a -> a -> Array a Source #

rnf :: (NFData a, Element Array a) => Array a -> () Source #

run :: (forall s. ST s (Array a)) -> Array a Source #

Contiguous UnliftedArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

type Mutable UnliftedArray = (r :: Type -> Type -> Type) Source #

type Element UnliftedArray :: Type -> Constraint Source #

Methods

empty :: UnliftedArray a Source #

null :: UnliftedArray b -> Bool Source #

new :: (PrimMonad m, Element UnliftedArray b) => Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

replicateMutable :: (PrimMonad m, Element UnliftedArray b) => Int -> b -> m (Mutable UnliftedArray (PrimState m) b) Source #

index :: Element UnliftedArray b => UnliftedArray b -> Int -> b Source #

index# :: Element UnliftedArray b => UnliftedArray b -> Int -> (# b #) Source #

indexM :: (Element UnliftedArray b, Monad m) => UnliftedArray b -> Int -> m b Source #

read :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

size :: Element UnliftedArray b => UnliftedArray b -> Int Source #

sizeMutable :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable UnliftedArray (PrimState m) b -> m (UnliftedArray b) Source #

freeze :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> Int -> m (UnliftedArray b) Source #

thaw :: (PrimMonad m, Element UnliftedArray b) => UnliftedArray b -> Int -> Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

copy :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> UnliftedArray b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> Mutable UnliftedArray (PrimState m) b -> Int -> Int -> m () Source #

clone :: Element UnliftedArray b => UnliftedArray b -> Int -> Int -> UnliftedArray b Source #

cloneMutable :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

insertSlicing :: Element UnliftedArray b => UnliftedArray b -> Int -> Int -> Int -> b -> UnliftedArray b Source #

equals :: (Element UnliftedArray b, Eq b) => UnliftedArray b -> UnliftedArray b -> Bool Source #

equalsMutable :: Mutable UnliftedArray s a -> Mutable UnliftedArray s a -> Bool Source #

unlift :: UnliftedArray b -> ArrayArray# Source #

lift :: ArrayArray# -> UnliftedArray b Source #

singleton :: Element UnliftedArray a => a -> UnliftedArray a Source #

doubleton :: Element UnliftedArray a => a -> a -> UnliftedArray a Source #

tripleton :: Element UnliftedArray a => a -> a -> a -> UnliftedArray a Source #

quadrupleton :: Element UnliftedArray a => a -> a -> a -> a -> UnliftedArray a Source #

rnf :: (NFData a, Element UnliftedArray a) => UnliftedArray a -> () Source #

run :: (forall s. ST s (UnliftedArray a)) -> UnliftedArray a Source #

class Always a Source #

A typeclass that is satisfied by all types. This is used used to provide a fake constraint for Array and SmallArray.

Instances

Instances details
Always a Source # 
Instance details

Defined in Data.Primitive.Contiguous

Re-Exports

data Array a #

Boxed arrays

Instances

Instances details
Monad Array 
Instance details

Defined in Data.Primitive.Array

Methods

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

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

return :: a -> Array a #

Functor Array 
Instance details

Defined in Data.Primitive.Array

Methods

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

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

MonadFix Array 
Instance details

Defined in Data.Primitive.Array

Methods

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

MonadFail Array 
Instance details

Defined in Data.Primitive.Array

Methods

fail :: String -> Array a #

Applicative Array 
Instance details

Defined in Data.Primitive.Array

Methods

pure :: a -> Array a #

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

liftA2 :: (a -> b -> c) -> Array a -> Array b -> Array c #

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

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

Foldable Array 
Instance details

Defined in Data.Primitive.Array

Methods

fold :: Monoid m => Array m -> m #

foldMap :: Monoid m => (a -> m) -> Array a -> m #

foldMap' :: Monoid m => (a -> m) -> Array a -> m #

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

foldr' :: (a -> b -> b) -> b -> Array a -> b #

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

foldl' :: (b -> a -> b) -> b -> Array a -> b #

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

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

toList :: Array a -> [a] #

null :: Array a -> Bool #

length :: Array a -> Int #

elem :: Eq a => a -> Array a -> Bool #

maximum :: Ord a => Array a -> a #

minimum :: Ord a => Array a -> a #

sum :: Num a => Array a -> a #

product :: Num a => Array a -> a #

Traversable Array 
Instance details

Defined in Data.Primitive.Array

Methods

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

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

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

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

Eq1 Array

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.Array

Methods

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

Ord1 Array

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.Array

Methods

liftCompare :: (a -> b -> Ordering) -> Array a -> Array b -> Ordering #

Read1 Array

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.Array

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Array a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Array a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Array a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Array a] #

Show1 Array

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.Array

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Array a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Array a] -> ShowS #

MonadZip Array 
Instance details

Defined in Data.Primitive.Array

Methods

mzip :: Array a -> Array b -> Array (a, b) #

mzipWith :: (a -> b -> c) -> Array a -> Array b -> Array c #

munzip :: Array (a, b) -> (Array a, Array b) #

Alternative Array 
Instance details

Defined in Data.Primitive.Array

Methods

empty :: Array a #

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

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

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

MonadPlus Array 
Instance details

Defined in Data.Primitive.Array

Methods

mzero :: Array a #

mplus :: Array a -> Array a -> Array a #

NFData1 Array 
Instance details

Defined in Data.Primitive.Array

Methods

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

Contiguous Array Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

type Mutable Array = (r :: Type -> Type -> Type) Source #

type Element Array :: Type -> Constraint Source #

Methods

empty :: Array a Source #

null :: Array b -> Bool Source #

new :: (PrimMonad m, Element Array b) => Int -> m (Mutable Array (PrimState m) b) Source #

replicateMutable :: (PrimMonad m, Element Array b) => Int -> b -> m (Mutable Array (PrimState m) b) Source #

index :: Element Array b => Array b -> Int -> b Source #

index# :: Element Array b => Array b -> Int -> (# b #) Source #

indexM :: (Element Array b, Monad m) => Array b -> Int -> m b Source #

read :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> m (Mutable Array (PrimState m) b) Source #

size :: Element Array b => Array b -> Int Source #

sizeMutable :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable Array (PrimState m) b -> m (Array b) Source #

freeze :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Int -> m (Array b) Source #

thaw :: (PrimMonad m, Element Array b) => Array b -> Int -> Int -> m (Mutable Array (PrimState m) b) Source #

copy :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Array b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Mutable Array (PrimState m) b -> Int -> Int -> m () Source #

clone :: Element Array b => Array b -> Int -> Int -> Array b Source #

cloneMutable :: (PrimMonad m, Element Array b) => Mutable Array (PrimState m) b -> Int -> Int -> m (Mutable Array (PrimState m) b) Source #

insertSlicing :: Element Array b => Array b -> Int -> Int -> Int -> b -> Array b Source #

equals :: (Element Array b, Eq b) => Array b -> Array b -> Bool Source #

equalsMutable :: Mutable Array s a -> Mutable Array s a -> Bool Source #

unlift :: Array b -> ArrayArray# Source #

lift :: ArrayArray# -> Array b Source #

singleton :: Element Array a => a -> Array a Source #

doubleton :: Element Array a => a -> a -> Array a Source #

tripleton :: Element Array a => a -> a -> a -> Array a Source #

quadrupleton :: Element Array a => a -> a -> a -> a -> Array a Source #

rnf :: (NFData a, Element Array a) => Array a -> () Source #

run :: (forall s. ST s (Array a)) -> Array a Source #

IsList (Array a) 
Instance details

Defined in Data.Primitive.Array

Associated Types

type Item (Array a) #

Methods

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

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

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

Eq a => Eq (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

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

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

Data a => Data (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

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

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

toConstr :: Array a -> Constr #

dataTypeOf :: Array a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Array a)

Lexicographic ordering. Subject to change between major versions.

Instance details

Defined in Data.Primitive.Array

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 #

Read a => Read (Array a) 
Instance details

Defined in Data.Primitive.Array

Show a => Show (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

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

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Semigroup (Array a)

Since: primitive-0.6.3.0

Instance details

Defined in Data.Primitive.Array

Methods

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

sconcat :: NonEmpty (Array a) -> Array a #

stimes :: Integral b => b -> Array a -> Array a #

Monoid (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

mempty :: Array a #

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

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

NFData a => NFData (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

rnf :: Array a -> () #

type Mutable Array Source # 
Instance details

Defined in Data.Primitive.Contiguous

type Element Array Source # 
Instance details

Defined in Data.Primitive.Contiguous

type Item (Array a) 
Instance details

Defined in Data.Primitive.Array

type Item (Array a) = a

data MutableArray s a #

Mutable boxed arrays associated with a primitive state token.

Instances

Instances details
Eq (MutableArray s a) 
Instance details

Defined in Data.Primitive.Array

Methods

(==) :: MutableArray s a -> MutableArray s a -> Bool #

(/=) :: MutableArray s a -> MutableArray s a -> Bool #

(Typeable s, Typeable a) => Data (MutableArray s a) 
Instance details

Defined in Data.Primitive.Array

Methods

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

Instances details
Monad SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

(>>=) :: SmallArray a -> (a -> SmallArray b) -> SmallArray b #

(>>) :: SmallArray a -> SmallArray b -> SmallArray b #

return :: a -> SmallArray a #

Functor SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

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

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

MonadFix SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

mfix :: (a -> SmallArray a) -> SmallArray a #

MonadFail SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

fail :: String -> SmallArray a #

Applicative SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

pure :: a -> SmallArray a #

(<*>) :: SmallArray (a -> b) -> SmallArray a -> SmallArray b #

liftA2 :: (a -> b -> c) -> SmallArray a -> SmallArray b -> SmallArray c #

(*>) :: SmallArray a -> SmallArray b -> SmallArray b #

(<*) :: SmallArray a -> SmallArray b -> SmallArray a #

Foldable SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

fold :: Monoid m => SmallArray m -> m #

foldMap :: Monoid m => (a -> m) -> SmallArray a -> m #

foldMap' :: Monoid m => (a -> m) -> SmallArray a -> m #

foldr :: (a -> b -> b) -> b -> SmallArray a -> b #

foldr' :: (a -> b -> b) -> b -> SmallArray a -> b #

foldl :: (b -> a -> b) -> b -> SmallArray a -> b #

foldl' :: (b -> a -> b) -> b -> SmallArray a -> b #

foldr1 :: (a -> a -> a) -> SmallArray a -> a #

foldl1 :: (a -> a -> a) -> SmallArray a -> a #

toList :: SmallArray a -> [a] #

null :: SmallArray a -> Bool #

length :: SmallArray a -> Int #

elem :: Eq a => a -> SmallArray a -> Bool #

maximum :: Ord a => SmallArray a -> a #

minimum :: Ord a => SmallArray a -> a #

sum :: Num a => SmallArray a -> a #

product :: Num a => SmallArray a -> a #

Traversable SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

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

sequenceA :: Applicative f => SmallArray (f a) -> f (SmallArray a) #

mapM :: Monad m => (a -> m b) -> SmallArray a -> m (SmallArray b) #

sequence :: Monad m => SmallArray (m a) -> m (SmallArray a) #

Eq1 SmallArray

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.SmallArray

Methods

liftEq :: (a -> b -> Bool) -> SmallArray a -> SmallArray b -> Bool #

Ord1 SmallArray

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.SmallArray

Methods

liftCompare :: (a -> b -> Ordering) -> SmallArray a -> SmallArray b -> Ordering #

Read1 SmallArray

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.SmallArray

Show1 SmallArray

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.SmallArray

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> SmallArray a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [SmallArray a] -> ShowS #

MonadZip SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

mzip :: SmallArray a -> SmallArray b -> SmallArray (a, b) #

mzipWith :: (a -> b -> c) -> SmallArray a -> SmallArray b -> SmallArray c #

munzip :: SmallArray (a, b) -> (SmallArray a, SmallArray b) #

Alternative SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

MonadPlus SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

NFData1 SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

liftRnf :: (a -> ()) -> SmallArray a -> () #

Contiguous SmallArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

type Mutable SmallArray = (r :: Type -> Type -> Type) Source #

type Element SmallArray :: Type -> Constraint Source #

Methods

empty :: SmallArray a Source #

null :: SmallArray b -> Bool Source #

new :: (PrimMonad m, Element SmallArray b) => Int -> m (Mutable SmallArray (PrimState m) b) Source #

replicateMutable :: (PrimMonad m, Element SmallArray b) => Int -> b -> m (Mutable SmallArray (PrimState m) b) Source #

index :: Element SmallArray b => SmallArray b -> Int -> b Source #

index# :: Element SmallArray b => SmallArray b -> Int -> (# b #) Source #

indexM :: (Element SmallArray b, Monad m) => SmallArray b -> Int -> m b Source #

read :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> m (Mutable SmallArray (PrimState m) b) Source #

size :: Element SmallArray b => SmallArray b -> Int Source #

sizeMutable :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable SmallArray (PrimState m) b -> m (SmallArray b) Source #

freeze :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> Int -> m (SmallArray b) Source #

thaw :: (PrimMonad m, Element SmallArray b) => SmallArray b -> Int -> Int -> m (Mutable SmallArray (PrimState m) b) Source #

copy :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> SmallArray b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> Mutable SmallArray (PrimState m) b -> Int -> Int -> m () Source #

clone :: Element SmallArray b => SmallArray b -> Int -> Int -> SmallArray b Source #

cloneMutable :: (PrimMonad m, Element SmallArray b) => Mutable SmallArray (PrimState m) b -> Int -> Int -> m (Mutable SmallArray (PrimState m) b) Source #

insertSlicing :: Element SmallArray b => SmallArray b -> Int -> Int -> Int -> b -> SmallArray b Source #

equals :: (Element SmallArray b, Eq b) => SmallArray b -> SmallArray b -> Bool Source #

equalsMutable :: Mutable SmallArray s a -> Mutable SmallArray s a -> Bool Source #

unlift :: SmallArray b -> ArrayArray# Source #

lift :: ArrayArray# -> SmallArray b Source #

singleton :: Element SmallArray a => a -> SmallArray a Source #

doubleton :: Element SmallArray a => a -> a -> SmallArray a Source #

tripleton :: Element SmallArray a => a -> a -> a -> SmallArray a Source #

quadrupleton :: Element SmallArray a => a -> a -> a -> a -> SmallArray a Source #

rnf :: (NFData a, Element SmallArray a) => SmallArray a -> () Source #

run :: (forall s. ST s (SmallArray a)) -> SmallArray a Source #

IsList (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Associated Types

type Item (SmallArray a) #

Eq a => Eq (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Methods

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

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

Data a => Data (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Methods

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

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

toConstr :: SmallArray a -> Constr #

dataTypeOf :: SmallArray a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (SmallArray a)

Lexicographic ordering. Subject to change between major versions.

Instance details

Defined in Data.Primitive.SmallArray

Read a => Read (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Show a => Show (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Semigroup (SmallArray a)

Since: primitive-0.6.3.0

Instance details

Defined in Data.Primitive.SmallArray

Monoid (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

NFData a => NFData (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Methods

rnf :: SmallArray a -> () #

type Mutable SmallArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

type Element SmallArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

type Item (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

type Item (SmallArray a) = a

data SmallMutableArray s a #

Instances

Instances details
Eq (SmallMutableArray s a) 
Instance details

Defined in Data.Primitive.SmallArray

(Typeable s, Typeable a) => Data (SmallMutableArray s a) 
Instance details

Defined in Data.Primitive.SmallArray

Methods

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) #

data PrimArray 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

Instances details
Contiguous PrimArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

type Mutable PrimArray = (r :: Type -> Type -> Type) Source #

type Element PrimArray :: Type -> Constraint Source #

Methods

empty :: PrimArray a Source #

null :: PrimArray b -> Bool Source #

new :: (PrimMonad m, Element PrimArray b) => Int -> m (Mutable PrimArray (PrimState m) b) Source #

replicateMutable :: (PrimMonad m, Element PrimArray b) => Int -> b -> m (Mutable PrimArray (PrimState m) b) Source #

index :: Element PrimArray b => PrimArray b -> Int -> b Source #

index# :: Element PrimArray b => PrimArray b -> Int -> (# b #) Source #

indexM :: (Element PrimArray b, Monad m) => PrimArray b -> Int -> m b Source #

read :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> m (Mutable PrimArray (PrimState m) b) Source #

size :: Element PrimArray b => PrimArray b -> Int Source #

sizeMutable :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable PrimArray (PrimState m) b -> m (PrimArray b) Source #

freeze :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> Int -> m (PrimArray b) Source #

thaw :: (PrimMonad m, Element PrimArray b) => PrimArray b -> Int -> Int -> m (Mutable PrimArray (PrimState m) b) Source #

copy :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> PrimArray b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> Mutable PrimArray (PrimState m) b -> Int -> Int -> m () Source #

clone :: Element PrimArray b => PrimArray b -> Int -> Int -> PrimArray b Source #

cloneMutable :: (PrimMonad m, Element PrimArray b) => Mutable PrimArray (PrimState m) b -> Int -> Int -> m (Mutable PrimArray (PrimState m) b) Source #

insertSlicing :: Element PrimArray b => PrimArray b -> Int -> Int -> Int -> b -> PrimArray b Source #

equals :: (Element PrimArray b, Eq b) => PrimArray b -> PrimArray b -> Bool Source #

equalsMutable :: Mutable PrimArray s a -> Mutable PrimArray s a -> Bool Source #

unlift :: PrimArray b -> ArrayArray# Source #

lift :: ArrayArray# -> PrimArray b Source #

singleton :: Element PrimArray a => a -> PrimArray a Source #

doubleton :: Element PrimArray a => a -> a -> PrimArray a Source #

tripleton :: Element PrimArray a => a -> a -> a -> PrimArray a Source #

quadrupleton :: Element PrimArray a => a -> a -> a -> a -> PrimArray a Source #

rnf :: (NFData a, Element PrimArray a) => PrimArray a -> () Source #

run :: (forall s. ST s (PrimArray a)) -> PrimArray a Source #

Prim a => IsList (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

Associated Types

type Item (PrimArray a) #

Methods

fromList :: [Item (PrimArray a)] -> PrimArray a #

fromListN :: Int -> [Item (PrimArray a)] -> PrimArray a #

toList :: PrimArray a -> [Item (PrimArray a)] #

(Eq a, Prim a) => Eq (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

Methods

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

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

(Ord a, Prim a) => Ord (PrimArray a)

Lexicographic ordering. Subject to change between major versions.

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

(Show a, Prim a) => Show (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

Semigroup (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

Methods

(<>) :: PrimArray a -> PrimArray a -> PrimArray a #

sconcat :: NonEmpty (PrimArray a) -> PrimArray a #

stimes :: Integral b => b -> PrimArray a -> PrimArray a #

Monoid (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

NFData (PrimArray a) 
Instance details

Defined in Data.Primitive.PrimArray

Methods

rnf :: PrimArray a -> () #

PrimUnlifted (PrimArray a) 
Instance details

Defined in Data.Primitive.Unlifted.Class

Associated Types

type Unlifted (PrimArray a) :: TYPE 'UnliftedRep #

type Mutable PrimArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

type Element PrimArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

type Item (PrimArray a) 
Instance details

Defined in Data.Primitive.PrimArray

type Item (PrimArray a) = a
type Unlifted (PrimArray a) 
Instance details

Defined in Data.Primitive.Unlifted.Class

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 convert 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.

data UnliftedArray a #

Instances

Instances details
Contiguous UnliftedArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

Associated Types

type Mutable UnliftedArray = (r :: Type -> Type -> Type) Source #

type Element UnliftedArray :: Type -> Constraint Source #

Methods

empty :: UnliftedArray a Source #

null :: UnliftedArray b -> Bool Source #

new :: (PrimMonad m, Element UnliftedArray b) => Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

replicateMutable :: (PrimMonad m, Element UnliftedArray b) => Int -> b -> m (Mutable UnliftedArray (PrimState m) b) Source #

index :: Element UnliftedArray b => UnliftedArray b -> Int -> b Source #

index# :: Element UnliftedArray b => UnliftedArray b -> Int -> (# b #) Source #

indexM :: (Element UnliftedArray b, Monad m) => UnliftedArray b -> Int -> m b Source #

read :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> m b Source #

write :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> b -> m () Source #

resize :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

size :: Element UnliftedArray b => UnliftedArray b -> Int Source #

sizeMutable :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> m Int Source #

unsafeFreeze :: PrimMonad m => Mutable UnliftedArray (PrimState m) b -> m (UnliftedArray b) Source #

freeze :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> Int -> m (UnliftedArray b) Source #

thaw :: (PrimMonad m, Element UnliftedArray b) => UnliftedArray b -> Int -> Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

copy :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> UnliftedArray b -> Int -> Int -> m () Source #

copyMutable :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> Mutable UnliftedArray (PrimState m) b -> Int -> Int -> m () Source #

clone :: Element UnliftedArray b => UnliftedArray b -> Int -> Int -> UnliftedArray b Source #

cloneMutable :: (PrimMonad m, Element UnliftedArray b) => Mutable UnliftedArray (PrimState m) b -> Int -> Int -> m (Mutable UnliftedArray (PrimState m) b) Source #

insertSlicing :: Element UnliftedArray b => UnliftedArray b -> Int -> Int -> Int -> b -> UnliftedArray b Source #

equals :: (Element UnliftedArray b, Eq b) => UnliftedArray b -> UnliftedArray b -> Bool Source #

equalsMutable :: Mutable UnliftedArray s a -> Mutable UnliftedArray s a -> Bool Source #

unlift :: UnliftedArray b -> ArrayArray# Source #

lift :: ArrayArray# -> UnliftedArray b Source #

singleton :: Element UnliftedArray a => a -> UnliftedArray a Source #

doubleton :: Element UnliftedArray a => a -> a -> UnliftedArray a Source #

tripleton :: Element UnliftedArray a => a -> a -> a -> UnliftedArray a Source #

quadrupleton :: Element UnliftedArray a => a -> a -> a -> a -> UnliftedArray a Source #

rnf :: (NFData a, Element UnliftedArray a) => UnliftedArray a -> () Source #

run :: (forall s. ST s (UnliftedArray a)) -> UnliftedArray a Source #

PrimUnlifted a => IsList (UnliftedArray a) 
Instance details

Defined in Data.Primitive.Unlifted.Array

Associated Types

type Item (UnliftedArray a) #

(Eq a, PrimUnlifted a) => Eq (UnliftedArray a) 
Instance details

Defined in Data.Primitive.Unlifted.Array

(Show a, PrimUnlifted a) => Show (UnliftedArray a) 
Instance details

Defined in Data.Primitive.Unlifted.Array

PrimUnlifted a => Semigroup (UnliftedArray a) 
Instance details

Defined in Data.Primitive.Unlifted.Array

PrimUnlifted a => Monoid (UnliftedArray a) 
Instance details

Defined in Data.Primitive.Unlifted.Array

type Mutable UnliftedArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

type Element UnliftedArray Source # 
Instance details

Defined in Data.Primitive.Contiguous

type Item (UnliftedArray a) 
Instance details

Defined in Data.Primitive.Unlifted.Array

type Item (UnliftedArray a) = a

data MutableUnliftedArray s a #

Instances

Instances details
Eq (MutableUnliftedArray s a) 
Instance details

Defined in Data.Primitive.Unlifted.Array