Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class Contiguous (arr :: Type -> Type) where
- type Mutable arr = (r :: Type -> Type -> Type) | r -> arr
- type Element arr :: Type -> Constraint
- type Sliced arr :: Type -> Type
- type MutableSliced arr :: Type -> Type -> Type
- new :: (PrimMonad m, Element arr b) => Int -> m (Mutable arr (PrimState m) b)
- replicateMut :: (PrimMonad m, Element arr b) => Int -> b -> m (Mutable arr (PrimState m) b)
- shrink :: (PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> Int -> m (Mutable arr (PrimState m) a)
- empty :: arr a
- singleton :: Element arr a => a -> arr a
- doubleton :: Element arr a => a -> a -> arr a
- tripleton :: Element arr a => a -> a -> a -> arr a
- quadrupleton :: Element arr a => a -> a -> a -> a -> arr a
- index :: Element arr b => arr b -> Int -> b
- index# :: Element arr b => arr b -> Int -> (# b #)
- indexM :: (Element arr b, Monad m) => arr b -> Int -> m b
- read :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m b
- write :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> b -> m ()
- null :: arr b -> Bool
- size :: Element arr b => arr b -> Int
- sizeMut :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m Int
- equals :: (Element arr b, Eq b) => arr b -> arr b -> Bool
- equalsMut :: Mutable arr s a -> Mutable arr s a -> Bool
- slice :: Element arr a => arr a -> Int -> Int -> Sliced arr a
- sliceMut :: Element arr a => Mutable arr s a -> Int -> Int -> MutableSliced arr s a
- toSlice :: Element arr a => arr a -> Sliced arr a
- toSliceMut :: (PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> m (MutableSliced arr (PrimState m) a)
- clone :: Element arr b => Sliced arr b -> arr b
- clone_ :: Element arr a => arr a -> Int -> Int -> arr a
- cloneMut :: (PrimMonad m, Element arr b) => MutableSliced arr (PrimState m) b -> m (Mutable arr (PrimState m) b)
- cloneMut_ :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Int -> m (Mutable arr (PrimState m) b)
- freeze :: (PrimMonad m, Element arr a) => MutableSliced arr (PrimState m) a -> m (arr a)
- freeze_ :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Int -> m (arr b)
- unsafeFreeze :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> m (arr b)
- unsafeShrinkAndFreeze :: (PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> Int -> m (arr a)
- thaw :: (PrimMonad m, Element arr b) => Sliced arr b -> m (Mutable arr (PrimState m) b)
- thaw_ :: (PrimMonad m, Element arr b) => arr b -> Int -> Int -> m (Mutable arr (PrimState m) b)
- copy :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Sliced arr b -> m ()
- copy_ :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> arr b -> Int -> Int -> m ()
- copyMut :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> MutableSliced arr (PrimState m) b -> m ()
- copyMut_ :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> Mutable arr (PrimState m) b -> Int -> Int -> m ()
- insertAt :: Element arr b => arr b -> Int -> b -> arr b
- rnf :: (NFData a, Element arr a) => arr a -> ()
- run :: (forall s. ST s (arr a)) -> arr a
- data Slice arr a = Slice {}
- data MutableSlice arr s a = MutableSlice {}
- class Contiguous arr => ContiguousU arr where
- type Unlifted arr = (r :: Type -> TYPE 'UnliftedRep) | r -> arr
- type UnliftedMut arr = (r :: Type -> Type -> TYPE 'UnliftedRep) | r -> arr
- resize :: (PrimMonad m, Element arr b) => Mutable arr (PrimState m) b -> Int -> m (Mutable arr (PrimState m) b)
- unlift :: arr b -> Unlifted arr b
- unliftMut :: Mutable arr s b -> UnliftedMut arr s b
- lift :: Unlifted arr b -> arr b
- liftMut :: UnliftedMut arr s b -> Mutable arr s b
- class Always a
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
.
new, replicateMut, empty, singleton, doubleton, tripleton, quadrupleton, index, index#, indexM, read, write, null, size, sizeMut, equals, equalsMut, slice, sliceMut, toSlice, toSliceMut, clone_, cloneMut_, freeze_, thaw_, copy_, copyMut_, rnf, run
type Mutable arr = (r :: Type -> Type -> Type) | r -> arr Source #
The Mutable counterpart to the array.
type Element arr :: Type -> Constraint Source #
The constraint needed to store elements in the array.
type Sliced arr :: Type -> Type Source #
The slice type of this array.
The slice of a raw array type t
should be 'Slice t',
whereas the slice of a slice should be the same slice type.
Since: 0.6.0
type MutableSliced arr :: Type -> Type -> Type Source #
The mutable slice type of this array.
The mutable slice of a raw array type t
should be 'MutableSlice t',
whereas the mutable slice of a mutable slice should be the same slice type.
Since: 0.6.0
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 #
is a mutable array of length replicateMut
n xn
with x
the
value of every element.
:: (PrimMonad m, Element arr a) | |
=> Mutable arr (PrimState m) a | |
-> Int | new length |
-> m (Mutable arr (PrimState m) a) |
Resize an array without growing it.
Since: 0.6.0
default shrink :: (ContiguousU arr, PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> Int -> m (Mutable arr (PrimState m) 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.
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 #
sliceMut :: Element arr a => Mutable arr s a -> Int -> Int -> MutableSliced arr s a Source #
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 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
:: (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 #
:: (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 #
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 #
default unsafeShrinkAndFreeze :: (ContiguousU arr, PrimMonad m, Element arr a) => Mutable arr (PrimState m) a -> Int -> m (arr a) Source #
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 #
:: (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
:: (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 #
:: (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
:: (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 #
:: (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
:: 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
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
Slices of immutable arrays: packages an offset and length with a backing array.
Since: 0.6.0
Instances
data MutableSlice arr s a Source #
Slices of mutable arrays: packages an offset and length with a mutable backing array.
Since: 0.6.0
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 uncliced contiguous structures.
Since: 0.6.0
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).
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.
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
A typeclass that is satisfied by all types. This is used
used to provide a fake constraint for Array
and SmallArray
.
Instances
Always a Source # | |
Defined in Data.Primitive.Contiguous.Class |