contiguous-0.6.5.0: Unified interface for primitive arrays
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Primitive.Contiguous.Class

Description

The Contiguous typeclass parameterises over a contiguous array type. It provides the core primitives necessary to implement the common API in Data.Primitive.Contiguous. This allows us to have a common API to a number of contiguous array types and their mutable counterparts.

Synopsis

Documentation

class Contiguous (arr :: Type -> Type) where Source #

The Contiguous typeclass as an interface to a multitude of contiguous structures.

Some functions do not make sense on slices; for those, see ContiguousU.

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.

type Sliced arr :: Type -> Type Source #

The slice type of this array. The slice of a raw array type t should be 'Slice t', whereas the slice of a slice should be the same slice type.

Since: 0.6.0

type MutableSliced arr :: Type -> Type -> Type Source #

The mutable slice type of this array. The mutable slice of a raw array type t should be 'MutableSlice t', whereas the mutable slice of a mutable slice should be the same slice type.

Since: 0.6.0

Methods

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

Allocate a new mutable array of the given size.

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

replicateMut n x is a mutable array of length n with x the value of every element.

shrink Source #

Arguments

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

new length

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

Resize an array without growing it. It may be shrunk in place.

Since: 0.6.0

empty :: arr a Source #

The empty array.

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

Create a singleton array.

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

Create a doubleton array.

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

Create a tripleton array.

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

Create a quadrupleton array.

quintupleton :: Element arr a => a -> a -> a -> a -> a -> arr a Source #

Create a quintupleton array.

sextupleton :: Element arr a => a -> a -> a -> a -> a -> a -> arr a Source #

Create a sextupleton array.

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

Index into an array at the given index.

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

Index into an array at the given index, yielding an unboxed one-tuple of the element.

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

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

Read a mutable array at the given index.

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

Write to a mutable array at the given index.

null :: arr b -> Bool Source #

Test whether the array is empty.

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

The size of the array

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

The size of the mutable array

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

Test the two arrays for equality.

equalsMut :: Mutable arr s a -> Mutable arr s a -> Bool Source #

Test the two mutable arrays for pointer equality. Does not check equality of elements.

slice :: Element arr a => arr a -> Int -> Int -> Sliced arr a Source #

Create a Slice of an array.

O(1).

Since: 0.6.0

sliceMut :: Element arr a => Mutable arr s a -> Int -> Int -> MutableSliced arr s a Source #

Create a MutableSlice of a mutable array.

O(1).

Since: 0.6.0

toSlice :: Element arr a => arr a -> Sliced arr a Source #

Create a Slice that covers the entire array.

Since: 0.6.0

toSliceMut :: (PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> m (MutableSliced arr (PrimState m) a) Source #

Create a MutableSlice that covers the entire array.

Since: 0.6.0

clone Source #

Arguments

:: Element arr b 
=> Sliced arr b

slice to copy

-> arr b 

Clone a slice of an array.

default clone :: (Sliced arr ~ Slice arr, ContiguousU arr, Element arr b) => Sliced arr b -> arr b Source #

clone_ :: Element arr a => arr a -> Int -> Int -> arr a Source #

Clone a slice of an array without using the Slice type. These methods are required to implement 'Contiguous (Slice arr)' for any `Contiguous arr`; they are not really meant for direct use.

Since: 0.6.0

cloneMut Source #

Arguments

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

Array to copy a slice of

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

Clone a slice of a mutable array.

default cloneMut :: (MutableSliced arr ~ MutableSlice arr, ContiguousU arr, PrimMonad m, Element arr b) => MutableSliced arr (PrimState m) b -> m (Mutable arr (PrimState m) b) Source #

cloneMut_ Source #

Arguments

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

Array to copy a slice of

-> Int

offset

-> Int

length

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

Clone a slice of a mutable array without using the MutableSlice type. These methods are required to implement 'Contiguous (Slice arr)' for any `Contiguous arr`; they are not really meant for direct use.

Since: 0.6.0

freeze :: (PrimMonad m, Element arr a) => MutableSliced arr (PrimState m) a -> m (arr a) Source #

Turn a mutable array slice an immutable array by copying.

Since: 0.6.0

default freeze :: (MutableSliced arr ~ MutableSlice arr, ContiguousU arr, PrimMonad m, Element arr a) => MutableSliced arr (PrimState m) a -> m (arr a) Source #

freeze_ Source #

Arguments

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

offset

-> Int

length

-> m (arr b) 

Turn a slice of a mutable array into an immutable one with copying, without using the MutableSlice type. These methods are required to implement 'Contiguous (Slice arr)' for any `Contiguous arr`; they are not really meant for direct use.

Since: 0.6.0

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

Turn a mutable array into an immutable one without copying. The mutable array should not be used after this conversion.

unsafeShrinkAndFreeze Source #

Arguments

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

final size

-> m (arr a) 

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

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

default thaw :: (Sliced arr ~ Slice arr, ContiguousU arr, PrimMonad m, Element arr b) => Sliced arr b -> m (Mutable arr (PrimState m) b) Source #

thaw_ Source #

Arguments

:: (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 without using the Slice type. These methods are required to implement 'Contiguous (Slice arr)' for any `Contiguous arr`; they are not really meant for direct use.

Since: 0.6.0

copy Source #

Arguments

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

destination array

-> Int

offset into destination array

-> Sliced arr b

source slice

-> m () 

Copy a slice of an array into a mutable array.

default copy :: (Sliced arr ~ Slice arr, ContiguousU arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Sliced arr b -> m () Source #

copy_ Source #

Arguments

:: (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 without using the Slice type. These methods are required to implement 'Contiguous (Slice arr)' for any `Contiguous arr`; they are not really meant for direct use.

Since: 0.6.0

copyMut Source #

Arguments

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

destination array

-> Int

offset into destination array

-> MutableSliced arr (PrimState m) b

source slice

-> m () 

Copy a slice of a mutable array into another mutable array. In the case that the destination and source arrays are the same, the regions may overlap.

default copyMut :: (MutableSliced arr ~ MutableSlice arr, ContiguousU arr, PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> MutableSliced arr (PrimState m) b -> m () Source #

copyMut_ Source #

Arguments

:: (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 without using the Slice type. These methods are required to implement 'Contiguous (Slice arr)' for any `Contiguous arr`; they are not really meant for direct use.

Since: 0.6.0

insertAt Source #

Arguments

:: Element arr b 
=> arr b

slice to copy from

-> Int

index in the output array to insert at

-> b

element to insert

-> arr b 

Copy a slice of an array and then insert an element into that array.

The default implementation performs a memset which would be unnecessary except that the garbage collector might trace the uninitialized array.

Was previously insertSlicing @since 0.6.0

default insertAt :: (Element arr b, ContiguousU arr) => arr b -> Int -> b -> arr b Source #

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

Reduce the array and all of its elements to WHNF.

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

Run an effectful computation that produces an array.

Instances

Instances details
Contiguous Array Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

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

type Element Array :: Type -> Constraint Source #

type Sliced Array :: Type -> Type Source #

type MutableSliced Array :: Type -> Type -> Type Source #

Methods

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

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

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

empty :: Array a 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 #

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

sextupleton :: Element Array a => a -> a -> a -> a -> a -> a -> Array a 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 #

null :: Array b -> Bool Source #

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

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

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

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

slice :: Element Array a => Array a -> Int -> Int -> Sliced Array a Source #

sliceMut :: Element Array a => Mutable Array s a -> Int -> Int -> MutableSliced Array s a Source #

toSlice :: Element Array a => Array a -> Sliced Array a Source #

toSliceMut :: (PrimMonad m, Element Array a) => Mutable Array (PrimState m) a -> m (MutableSliced Array (PrimState m) a) Source #

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

clone_ :: Element Array a => Array a -> Int -> Int -> Array a Source #

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

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

freeze :: (PrimMonad m, Element Array a) => MutableSliced Array (PrimState m) a -> m (Array a) Source #

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

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

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

thaw :: (PrimMonad m, Element Array b) => Sliced Array b -> m (Mutable Array (PrimState m) 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 -> Sliced Array b -> m () Source #

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

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

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

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

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

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

Contiguous PrimArray Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Methods

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

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

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

empty :: PrimArray a 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 #

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

sextupleton :: Element PrimArray a => a -> a -> a -> a -> a -> a -> PrimArray a 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 #

null :: PrimArray b -> Bool Source #

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

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

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

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

slice :: Element PrimArray a => PrimArray a -> Int -> Int -> Sliced PrimArray a Source #

sliceMut :: Element PrimArray a => Mutable PrimArray s a -> Int -> Int -> MutableSliced PrimArray s a Source #

toSlice :: Element PrimArray a => PrimArray a -> Sliced PrimArray a Source #

toSliceMut :: (PrimMonad m, Element PrimArray a) => Mutable PrimArray (PrimState m) a -> m (MutableSliced PrimArray (PrimState m) a) Source #

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

clone_ :: Element PrimArray a => PrimArray a -> Int -> Int -> PrimArray a Source #

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

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

freeze :: (PrimMonad m, Element PrimArray a) => MutableSliced PrimArray (PrimState m) a -> m (PrimArray a) Source #

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

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

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

thaw :: (PrimMonad m, Element PrimArray b) => Sliced PrimArray b -> m (Mutable PrimArray (PrimState m) 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 -> Sliced PrimArray b -> m () Source #

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

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

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

insertAt :: Element PrimArray b => PrimArray b -> Int -> b -> PrimArray b 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.Class

Methods

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

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

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

empty :: SmallArray a 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 #

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

sextupleton :: Element SmallArray a => a -> a -> a -> a -> a -> a -> SmallArray a 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 #

null :: SmallArray b -> Bool Source #

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

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

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

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

slice :: Element SmallArray a => SmallArray a -> Int -> Int -> Sliced SmallArray a Source #

sliceMut :: Element SmallArray a => Mutable SmallArray s a -> Int -> Int -> MutableSliced SmallArray s a Source #

toSlice :: Element SmallArray a => SmallArray a -> Sliced SmallArray a Source #

toSliceMut :: (PrimMonad m, Element SmallArray a) => Mutable SmallArray (PrimState m) a -> m (MutableSliced SmallArray (PrimState m) a) Source #

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

clone_ :: Element SmallArray a => SmallArray a -> Int -> Int -> SmallArray a Source #

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

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

freeze :: (PrimMonad m, Element SmallArray a) => MutableSliced SmallArray (PrimState m) a -> m (SmallArray a) Source #

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

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

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

thaw :: (PrimMonad m, Element SmallArray b) => Sliced SmallArray b -> m (Mutable SmallArray (PrimState m) 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 -> Sliced SmallArray b -> m () Source #

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

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

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

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

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

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

ContiguousU arr => Contiguous (Slice arr) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

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

type Element (Slice arr) :: Type -> Constraint Source #

type Sliced (Slice arr) :: Type -> Type Source #

type MutableSliced (Slice arr) :: Type -> Type -> Type Source #

Methods

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

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

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

empty :: Slice arr a Source #

singleton :: Element (Slice arr) a => a -> Slice arr a Source #

doubleton :: Element (Slice arr) a => a -> a -> Slice arr a Source #

tripleton :: Element (Slice arr) a => a -> a -> a -> Slice arr a Source #

quadrupleton :: Element (Slice arr) a => a -> a -> a -> a -> Slice arr a Source #

quintupleton :: Element (Slice arr) a => a -> a -> a -> a -> a -> Slice arr a Source #

sextupleton :: Element (Slice arr) a => a -> a -> a -> a -> a -> a -> Slice arr a Source #

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

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

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

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

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

null :: Slice arr b -> Bool Source #

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

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

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

equalsMut :: Mutable (Slice arr) s a -> Mutable (Slice arr) s a -> Bool Source #

slice :: Element (Slice arr) a => Slice arr a -> Int -> Int -> Sliced (Slice arr) a Source #

sliceMut :: Element (Slice arr) a => Mutable (Slice arr) s a -> Int -> Int -> MutableSliced (Slice arr) s a Source #

toSlice :: Element (Slice arr) a => Slice arr a -> Sliced (Slice arr) a Source #

toSliceMut :: (PrimMonad m, Element (Slice arr) a) => Mutable (Slice arr) (PrimState m) a -> m (MutableSliced (Slice arr) (PrimState m) a) Source #

clone :: Element (Slice arr) b => Sliced (Slice arr) b -> Slice arr b Source #

clone_ :: Element (Slice arr) a => Slice arr a -> Int -> Int -> Slice arr a Source #

cloneMut :: (PrimMonad m, Element (Slice arr) b) => MutableSliced (Slice arr) (PrimState m) b -> m (Mutable (Slice arr) (PrimState m) b) Source #

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

freeze :: (PrimMonad m, Element (Slice arr) a) => MutableSliced (Slice arr) (PrimState m) a -> m (Slice arr a) Source #

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

unsafeFreeze :: (PrimMonad m, Element (Slice arr) b) => Mutable (Slice arr) (PrimState m) b -> m (Slice arr b) Source #

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

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

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

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

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

copyMut :: (PrimMonad m, Element (Slice arr) b) => Mutable (Slice arr) (PrimState m) b -> Int -> MutableSliced (Slice arr) (PrimState m) b -> m () Source #

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

insertAt :: Element (Slice arr) b => Slice arr b -> Int -> b -> Slice arr b Source #

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

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

Contiguous (UnliftedArray_ unlifted_a) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

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

type Element (UnliftedArray_ unlifted_a) :: Type -> Constraint Source #

type Sliced (UnliftedArray_ unlifted_a) :: Type -> Type Source #

type MutableSliced (UnliftedArray_ unlifted_a) :: Type -> Type -> Type Source #

Methods

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

replicateMut :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => Int -> b -> m (Mutable (UnliftedArray_ unlifted_a) (PrimState m) b) Source #

shrink :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) a) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) a -> Int -> m (Mutable (UnliftedArray_ unlifted_a) (PrimState m) a) Source #

empty :: UnliftedArray_ unlifted_a a Source #

singleton :: Element (UnliftedArray_ unlifted_a) a => a -> UnliftedArray_ unlifted_a a Source #

doubleton :: Element (UnliftedArray_ unlifted_a) a => a -> a -> UnliftedArray_ unlifted_a a Source #

tripleton :: Element (UnliftedArray_ unlifted_a) a => a -> a -> a -> UnliftedArray_ unlifted_a a Source #

quadrupleton :: Element (UnliftedArray_ unlifted_a) a => a -> a -> a -> a -> UnliftedArray_ unlifted_a a Source #

quintupleton :: Element (UnliftedArray_ unlifted_a) a => a -> a -> a -> a -> a -> UnliftedArray_ unlifted_a a Source #

sextupleton :: Element (UnliftedArray_ unlifted_a) a => a -> a -> a -> a -> a -> a -> UnliftedArray_ unlifted_a a Source #

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

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

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

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

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

null :: UnliftedArray_ unlifted_a b -> Bool Source #

size :: Element (UnliftedArray_ unlifted_a) b => UnliftedArray_ unlifted_a b -> Int Source #

sizeMut :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) b -> m Int Source #

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

equalsMut :: Mutable (UnliftedArray_ unlifted_a) s a -> Mutable (UnliftedArray_ unlifted_a) s a -> Bool Source #

slice :: Element (UnliftedArray_ unlifted_a) a => UnliftedArray_ unlifted_a a -> Int -> Int -> Sliced (UnliftedArray_ unlifted_a) a Source #

sliceMut :: Element (UnliftedArray_ unlifted_a) a => Mutable (UnliftedArray_ unlifted_a) s a -> Int -> Int -> MutableSliced (UnliftedArray_ unlifted_a) s a Source #

toSlice :: Element (UnliftedArray_ unlifted_a) a => UnliftedArray_ unlifted_a a -> Sliced (UnliftedArray_ unlifted_a) a Source #

toSliceMut :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) a) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) a -> m (MutableSliced (UnliftedArray_ unlifted_a) (PrimState m) a) Source #

clone :: Element (UnliftedArray_ unlifted_a) b => Sliced (UnliftedArray_ unlifted_a) b -> UnliftedArray_ unlifted_a b Source #

clone_ :: Element (UnliftedArray_ unlifted_a) a => UnliftedArray_ unlifted_a a -> Int -> Int -> UnliftedArray_ unlifted_a a Source #

cloneMut :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => MutableSliced (UnliftedArray_ unlifted_a) (PrimState m) b -> m (Mutable (UnliftedArray_ unlifted_a) (PrimState m) b) Source #

cloneMut_ :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) b -> Int -> Int -> m (Mutable (UnliftedArray_ unlifted_a) (PrimState m) b) Source #

freeze :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) a) => MutableSliced (UnliftedArray_ unlifted_a) (PrimState m) a -> m (UnliftedArray_ unlifted_a a) Source #

freeze_ :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) b -> Int -> Int -> m (UnliftedArray_ unlifted_a b) Source #

unsafeFreeze :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) b -> m (UnliftedArray_ unlifted_a b) Source #

unsafeShrinkAndFreeze :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) a) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) a -> Int -> m (UnliftedArray_ unlifted_a a) Source #

thaw :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => Sliced (UnliftedArray_ unlifted_a) b -> m (Mutable (UnliftedArray_ unlifted_a) (PrimState m) b) Source #

thaw_ :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => UnliftedArray_ unlifted_a b -> Int -> Int -> m (Mutable (UnliftedArray_ unlifted_a) (PrimState m) b) Source #

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

copy_ :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) b -> Int -> UnliftedArray_ unlifted_a b -> Int -> Int -> m () Source #

copyMut :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) b -> Int -> MutableSliced (UnliftedArray_ unlifted_a) (PrimState m) b -> m () Source #

copyMut_ :: (PrimMonad m, Element (UnliftedArray_ unlifted_a) b) => Mutable (UnliftedArray_ unlifted_a) (PrimState m) b -> Int -> Mutable (UnliftedArray_ unlifted_a) (PrimState m) b -> Int -> Int -> m () Source #

insertAt :: Element (UnliftedArray_ unlifted_a) b => UnliftedArray_ unlifted_a b -> Int -> b -> UnliftedArray_ unlifted_a b Source #

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

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

Contiguous (SmallUnliftedArray_ unlifted_a) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

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

type Element (SmallUnliftedArray_ unlifted_a) :: Type -> Constraint Source #

type Sliced (SmallUnliftedArray_ unlifted_a) :: Type -> Type Source #

type MutableSliced (SmallUnliftedArray_ unlifted_a) :: Type -> Type -> Type Source #

Methods

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

replicateMut :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => Int -> b -> m (Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b) Source #

shrink :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) a) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) a -> Int -> m (Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) a) Source #

empty :: SmallUnliftedArray_ unlifted_a a Source #

singleton :: Element (SmallUnliftedArray_ unlifted_a) a => a -> SmallUnliftedArray_ unlifted_a a Source #

doubleton :: Element (SmallUnliftedArray_ unlifted_a) a => a -> a -> SmallUnliftedArray_ unlifted_a a Source #

tripleton :: Element (SmallUnliftedArray_ unlifted_a) a => a -> a -> a -> SmallUnliftedArray_ unlifted_a a Source #

quadrupleton :: Element (SmallUnliftedArray_ unlifted_a) a => a -> a -> a -> a -> SmallUnliftedArray_ unlifted_a a Source #

quintupleton :: Element (SmallUnliftedArray_ unlifted_a) a => a -> a -> a -> a -> a -> SmallUnliftedArray_ unlifted_a a Source #

sextupleton :: Element (SmallUnliftedArray_ unlifted_a) a => a -> a -> a -> a -> a -> a -> SmallUnliftedArray_ unlifted_a a Source #

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

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

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

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

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

null :: SmallUnliftedArray_ unlifted_a b -> Bool Source #

size :: Element (SmallUnliftedArray_ unlifted_a) b => SmallUnliftedArray_ unlifted_a b -> Int Source #

sizeMut :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> m Int Source #

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

equalsMut :: Mutable (SmallUnliftedArray_ unlifted_a) s a -> Mutable (SmallUnliftedArray_ unlifted_a) s a -> Bool Source #

slice :: Element (SmallUnliftedArray_ unlifted_a) a => SmallUnliftedArray_ unlifted_a a -> Int -> Int -> Sliced (SmallUnliftedArray_ unlifted_a) a Source #

sliceMut :: Element (SmallUnliftedArray_ unlifted_a) a => Mutable (SmallUnliftedArray_ unlifted_a) s a -> Int -> Int -> MutableSliced (SmallUnliftedArray_ unlifted_a) s a Source #

toSlice :: Element (SmallUnliftedArray_ unlifted_a) a => SmallUnliftedArray_ unlifted_a a -> Sliced (SmallUnliftedArray_ unlifted_a) a Source #

toSliceMut :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) a) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) a -> m (MutableSliced (SmallUnliftedArray_ unlifted_a) (PrimState m) a) Source #

clone :: Element (SmallUnliftedArray_ unlifted_a) b => Sliced (SmallUnliftedArray_ unlifted_a) b -> SmallUnliftedArray_ unlifted_a b Source #

clone_ :: Element (SmallUnliftedArray_ unlifted_a) a => SmallUnliftedArray_ unlifted_a a -> Int -> Int -> SmallUnliftedArray_ unlifted_a a Source #

cloneMut :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => MutableSliced (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> m (Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b) Source #

cloneMut_ :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> Int -> Int -> m (Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b) Source #

freeze :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) a) => MutableSliced (SmallUnliftedArray_ unlifted_a) (PrimState m) a -> m (SmallUnliftedArray_ unlifted_a a) Source #

freeze_ :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> Int -> Int -> m (SmallUnliftedArray_ unlifted_a b) Source #

unsafeFreeze :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> m (SmallUnliftedArray_ unlifted_a b) Source #

unsafeShrinkAndFreeze :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) a) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) a -> Int -> m (SmallUnliftedArray_ unlifted_a a) Source #

thaw :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => Sliced (SmallUnliftedArray_ unlifted_a) b -> m (Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b) Source #

thaw_ :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => SmallUnliftedArray_ unlifted_a b -> Int -> Int -> m (Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b) Source #

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

copy_ :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> Int -> SmallUnliftedArray_ unlifted_a b -> Int -> Int -> m () Source #

copyMut :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> Int -> MutableSliced (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> m () Source #

copyMut_ :: (PrimMonad m, Element (SmallUnliftedArray_ unlifted_a) b) => Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> Int -> Mutable (SmallUnliftedArray_ unlifted_a) (PrimState m) b -> Int -> Int -> m () Source #

insertAt :: Element (SmallUnliftedArray_ unlifted_a) b => SmallUnliftedArray_ unlifted_a b -> Int -> b -> SmallUnliftedArray_ unlifted_a b Source #

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

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

data Slice arr a Source #

Slices of immutable arrays: packages an offset and length with a backing array.

Since: 0.6.0

Constructors

Slice 

Fields

Instances

Instances details
ContiguousU arr => Contiguous (Slice arr) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

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

type Element (Slice arr) :: Type -> Constraint Source #

type Sliced (Slice arr) :: Type -> Type Source #

type MutableSliced (Slice arr) :: Type -> Type -> Type Source #

Methods

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

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

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

empty :: Slice arr a Source #

singleton :: Element (Slice arr) a => a -> Slice arr a Source #

doubleton :: Element (Slice arr) a => a -> a -> Slice arr a Source #

tripleton :: Element (Slice arr) a => a -> a -> a -> Slice arr a Source #

quadrupleton :: Element (Slice arr) a => a -> a -> a -> a -> Slice arr a Source #

quintupleton :: Element (Slice arr) a => a -> a -> a -> a -> a -> Slice arr a Source #

sextupleton :: Element (Slice arr) a => a -> a -> a -> a -> a -> a -> Slice arr a Source #

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

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

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

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

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

null :: Slice arr b -> Bool Source #

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

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

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

equalsMut :: Mutable (Slice arr) s a -> Mutable (Slice arr) s a -> Bool Source #

slice :: Element (Slice arr) a => Slice arr a -> Int -> Int -> Sliced (Slice arr) a Source #

sliceMut :: Element (Slice arr) a => Mutable (Slice arr) s a -> Int -> Int -> MutableSliced (Slice arr) s a Source #

toSlice :: Element (Slice arr) a => Slice arr a -> Sliced (Slice arr) a Source #

toSliceMut :: (PrimMonad m, Element (Slice arr) a) => Mutable (Slice arr) (PrimState m) a -> m (MutableSliced (Slice arr) (PrimState m) a) Source #

clone :: Element (Slice arr) b => Sliced (Slice arr) b -> Slice arr b Source #

clone_ :: Element (Slice arr) a => Slice arr a -> Int -> Int -> Slice arr a Source #

cloneMut :: (PrimMonad m, Element (Slice arr) b) => MutableSliced (Slice arr) (PrimState m) b -> m (Mutable (Slice arr) (PrimState m) b) Source #

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

freeze :: (PrimMonad m, Element (Slice arr) a) => MutableSliced (Slice arr) (PrimState m) a -> m (Slice arr a) Source #

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

unsafeFreeze :: (PrimMonad m, Element (Slice arr) b) => Mutable (Slice arr) (PrimState m) b -> m (Slice arr b) Source #

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

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

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

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

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

copyMut :: (PrimMonad m, Element (Slice arr) b) => Mutable (Slice arr) (PrimState m) b -> Int -> MutableSliced (Slice arr) (PrimState m) b -> m () Source #

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

insertAt :: Element (Slice arr) b => Slice arr b -> Int -> b -> Slice arr b Source #

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

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

type Element (Slice arr) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

type Element (Slice arr) = Element arr
type Mutable (Slice arr) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

type Mutable (Slice arr) = MutableSlice arr
type MutableSliced (Slice arr) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

type Sliced (Slice arr) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

type Sliced (Slice arr) = Slice arr

data MutableSlice arr s a Source #

Slices of mutable arrays: packages an offset and length with a mutable backing array.

Since: 0.6.0

Constructors

MutableSlice 

Fields

class Contiguous arr => ContiguousU arr where Source #

The ContiguousU typeclass is an extension of the Contiguous typeclass, but includes operations that make sense only on unsliced contiguous structures.

Since: 0.6.0

Associated Types

type Unlifted arr = (r :: Type -> TYPE UnliftedRep) | r -> arr Source #

The unifted version of the immutable array type (i.e. eliminates an indirection through a thunk).

type UnliftedMut arr = (r :: Type -> Type -> TYPE UnliftedRep) | r -> arr Source #

The unifted version of the mutable array type (i.e. eliminates an indirection through a thunk).

Methods

resize :: (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. If the array is grown, then reading from any newly introduced element before writing to it is undefined behavior. The current behavior is that anything backed by MutableByteArray# ends with uninitialized memory at these indices. But for SmallMutableArray or Array, these are set to an error thunk, so reading from them and forcing the result causes the program to crash. For UnliftedArray, the new elements have undefined values of an unknown type. If the array is not grown, it may (or may not) be modified in place.

unlift :: arr b -> Unlifted arr b Source #

Unlift an array (i.e. point to the data without an intervening thunk).

Since: 0.6.0

unliftMut :: Mutable arr s b -> UnliftedMut arr s b Source #

Unlift a mutable array (i.e. point to the data without an intervening thunk).

Since: 0.6.0

lift :: Unlifted arr b -> arr b Source #

Lift an array (i.e. point to the data through an intervening thunk).

Since: 0.6.0

liftMut :: UnliftedMut arr s b -> Mutable arr s b Source #

Lift a mutable array (i.e. point to the data through an intervening thunk).

Since: 0.6.0

Instances

Instances details
ContiguousU Array Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

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

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

ContiguousU PrimArray Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

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

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

ContiguousU SmallArray Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

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

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

ContiguousU (UnliftedArray_ unlifted_a) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

type Unlifted (UnliftedArray_ unlifted_a) = (r :: Type -> UnliftedType) Source #

type UnliftedMut (UnliftedArray_ unlifted_a) = (r :: Type -> Type -> UnliftedType) Source #

Methods

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

unlift :: UnliftedArray_ unlifted_a b -> Unlifted (UnliftedArray_ unlifted_a) b Source #

unliftMut :: Mutable (UnliftedArray_ unlifted_a) s b -> UnliftedMut (UnliftedArray_ unlifted_a) s b Source #

lift :: Unlifted (UnliftedArray_ unlifted_a) b -> UnliftedArray_ unlifted_a b Source #

liftMut :: UnliftedMut (UnliftedArray_ unlifted_a) s b -> Mutable (UnliftedArray_ unlifted_a) s b Source #

ContiguousU (SmallUnliftedArray_ unlifted_a) Source # 
Instance details

Defined in Data.Primitive.Contiguous.Class

Associated Types

type Unlifted (SmallUnliftedArray_ unlifted_a) = (r :: Type -> UnliftedType) Source #

type UnliftedMut (SmallUnliftedArray_ unlifted_a) = (r :: Type -> Type -> UnliftedType) Source #

Methods

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

unlift :: SmallUnliftedArray_ unlifted_a b -> Unlifted (SmallUnliftedArray_ unlifted_a) b Source #

unliftMut :: Mutable (SmallUnliftedArray_ unlifted_a) s b -> UnliftedMut (SmallUnliftedArray_ unlifted_a) s b Source #

lift :: Unlifted (SmallUnliftedArray_ unlifted_a) b -> SmallUnliftedArray_ unlifted_a b Source #

liftMut :: UnliftedMut (SmallUnliftedArray_ unlifted_a) s b -> Mutable (SmallUnliftedArray_ unlifted_a) s b 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.Class