contiguous-0.4: Unified interface for primitive arrays

Safe HaskellNone
LanguageHaskell2010

Data.Primitive.Contiguous

Contents

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.

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.

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.

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.

Modifying arrays

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.

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.

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.

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.

Traversals

traverse :: (Contiguous arr, Element arr a, Element arr b, Applicative f) => (a -> f b) -> arr a -> f (arr 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 arr, Element arr a, Element arr b, Applicative f) => (Int -> a -> f b) -> arr a -> f (arr 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.

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 :: (Contiguous arr, Element arr b) => arr b -> Int -> Int -> arr b Source #

Clone a slice of an array.

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

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 :: (Contiguous arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Int -> m (arr b) Source #

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

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

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

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 #

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

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 #

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 #

rnf :: (NFData a, Element 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 #

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 #

rnf :: (NFData a, Element 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 #

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 #

rnf :: (NFData a, Element Array a) => Array 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
Always a Source # 
Instance details

Defined in Data.Primitive.Contiguous