Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC contains three general classes of value types:
- Unboxed types: values are machine values made up of fixed numbers of bytes
- Unlifted types: values are pointers, but strictly evaluated
- Lifted types: values are pointers, lazily evaluated
The first category can be stored in a ByteArray
, and this allows types in
category 3 that are simple wrappers around category 1 types to be stored
more efficiently using a ByteArray
. This module provides the same facility
for category 2 types.
GHC has two primitive types, ArrayArray#
and MutableArrayArray#
. These
are arrays of pointers, but of category 2 values, so they are known to not
be bottom. This allows types that are wrappers around such types to be stored
in an array without an extra level of indirection.
The way that the ArrayArray#
API works is that one can read and write
ArrayArray#
values to the positions. This works because all category 2
types share a uniform representation, unlike unboxed values which are
represented by varying (by type) numbers of bytes. However, using the
this makes the internal API very unsafe to use, as one has to coerce values
to and from ArrayArray#
.
The API presented by this module is more type safe. UnliftedArray
and
MutableUnliftedArray
are parameterized by the type of arrays they contain, and
the coercions necessary are abstracted into a class, PrimUnlifted
, of things
that are eligible to be stored.
Synopsis
- data UnliftedArray a = UnliftedArray ArrayArray#
- data MutableUnliftedArray s a = MutableUnliftedArray (MutableArrayArray# s)
- newUnliftedArray :: (PrimMonad m, PrimUnlifted a) => Int -> a -> m (MutableUnliftedArray (PrimState m) a)
- unsafeNewUnliftedArray :: PrimMonad m => Int -> m (MutableUnliftedArray (PrimState m) a)
- sizeofUnliftedArray :: UnliftedArray e -> Int
- sizeofMutableUnliftedArray :: MutableUnliftedArray s e -> Int
- sameMutableUnliftedArray :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool
- writeUnliftedArray :: (PrimMonad m, PrimUnlifted a) => MutableUnliftedArray (PrimState m) a -> Int -> a -> m ()
- readUnliftedArray :: (PrimMonad m, PrimUnlifted a) => MutableUnliftedArray (PrimState m) a -> Int -> m a
- indexUnliftedArray :: PrimUnlifted a => UnliftedArray a -> Int -> a
- unsafeFreezeUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> m (UnliftedArray a)
- freezeUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> Int -> m (UnliftedArray a)
- thawUnliftedArray :: PrimMonad m => UnliftedArray a -> Int -> Int -> m (MutableUnliftedArray (PrimState m) a)
- setUnliftedArray :: (PrimMonad m, PrimUnlifted a) => MutableUnliftedArray (PrimState m) a -> a -> Int -> Int -> m ()
- copyUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> UnliftedArray a -> Int -> Int -> m ()
- copyMutableUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> MutableUnliftedArray (PrimState m) a -> Int -> Int -> m ()
- cloneUnliftedArray :: UnliftedArray a -> Int -> Int -> UnliftedArray a
- cloneMutableUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> Int -> m (MutableUnliftedArray (PrimState m) a)
- emptyUnliftedArray :: UnliftedArray a
- singletonUnliftedArray :: PrimUnlifted a => a -> UnliftedArray a
- runUnliftedArray :: (forall s. ST s (MutableUnliftedArray s a)) -> UnliftedArray a
- unliftedArrayToList :: PrimUnlifted a => UnliftedArray a -> [a]
- unliftedArrayFromList :: PrimUnlifted a => [a] -> UnliftedArray a
- unliftedArrayFromListN :: forall a. PrimUnlifted a => Int -> [a] -> UnliftedArray a
- foldrUnliftedArray :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> UnliftedArray a -> b
- foldrUnliftedArray' :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> UnliftedArray a -> b
- foldlUnliftedArray :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> UnliftedArray a -> b
- foldlUnliftedArray' :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> UnliftedArray a -> b
- foldlUnliftedArrayM' :: (PrimUnlifted a, Monad m) => (b -> a -> m b) -> b -> UnliftedArray a -> m b
- traverseUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (a -> m b) -> UnliftedArray a -> m ()
- itraverseUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (Int -> a -> m b) -> UnliftedArray a -> m ()
- mapUnliftedArray :: (PrimUnlifted a, PrimUnlifted b) => (a -> b) -> UnliftedArray a -> UnliftedArray b
Types
data UnliftedArray a Source #
Instances
data MutableUnliftedArray s a Source #
Instances
Eq (MutableUnliftedArray s a) Source # | |
Defined in Data.Primitive.Unlifted.Array (==) :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool # (/=) :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool # |
Operations
:: (PrimMonad m, PrimUnlifted a) | |
=> Int | size |
-> a | initial value |
-> m (MutableUnliftedArray (PrimState m) a) |
Creates a new MutableUnliftedArray
with the specified value as initial
contents. This is slower than unsafeNewUnliftedArray
, but safer.
unsafeNewUnliftedArray Source #
:: PrimMonad m | |
=> Int | size |
-> m (MutableUnliftedArray (PrimState m) a) |
Creates a new MutableUnliftedArray
. This function is unsafe because it
initializes all elements of the array as pointers to the array itself. Attempting
to read one of these elements before writing to it is in effect an unsafe
coercion from the
to the element type.MutableUnliftedArray
s a
sizeofUnliftedArray :: UnliftedArray e -> Int Source #
Yields the length of an UnliftedArray
.
sizeofMutableUnliftedArray :: MutableUnliftedArray s e -> Int Source #
Yields the length of a MutableUnliftedArray
.
sameMutableUnliftedArray :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool Source #
Determines whether two MutableUnliftedArray
values are the same. This is
object/pointer identity, not based on the contents.
writeUnliftedArray :: (PrimMonad m, PrimUnlifted a) => MutableUnliftedArray (PrimState m) a -> Int -> a -> m () Source #
readUnliftedArray :: (PrimMonad m, PrimUnlifted a) => MutableUnliftedArray (PrimState m) a -> Int -> m a Source #
indexUnliftedArray :: PrimUnlifted a => UnliftedArray a -> Int -> a Source #
unsafeFreezeUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> m (UnliftedArray a) Source #
Freezes a MutableUnliftedArray
, yielding an UnliftedArray
. This simply
marks the array as frozen in place, so it should only be used when no further
modifications to the mutable array will be performed.
:: PrimMonad m | |
=> MutableUnliftedArray (PrimState m) a | source |
-> Int | offset |
-> Int | length |
-> m (UnliftedArray a) |
Freezes a portion of a MutableUnliftedArray
, yielding an UnliftedArray
.
This operation is safe, in that it copies the frozen portion, and the
existing mutable array may still be used afterward.
:: PrimMonad m | |
=> UnliftedArray a | source |
-> Int | offset |
-> Int | length |
-> m (MutableUnliftedArray (PrimState m) a) |
Thaws a portion of an UnliftedArray
, yielding a MutableUnliftedArray
.
This copies the thawed portion, so mutations will not affect the original
array.
:: (PrimMonad m, PrimUnlifted a) | |
=> MutableUnliftedArray (PrimState m) a | destination |
-> a | value to fill with |
-> Int | offset |
-> Int | length |
-> m () |
:: PrimMonad m | |
=> MutableUnliftedArray (PrimState m) a | destination |
-> Int | offset into destination |
-> UnliftedArray a | source |
-> Int | offset into source |
-> Int | number of elements to copy |
-> m () |
Copies the contents of an immutable array into a mutable array.
copyMutableUnliftedArray Source #
:: PrimMonad m | |
=> MutableUnliftedArray (PrimState m) a | destination |
-> Int | offset into destination |
-> MutableUnliftedArray (PrimState m) a | source |
-> Int | offset into source |
-> Int | number of elements to copy |
-> m () |
Copies the contents of one mutable array into another.
:: UnliftedArray a | source |
-> Int | offset |
-> Int | length |
-> UnliftedArray a |
Creates a copy of a portion of an UnliftedArray
cloneMutableUnliftedArray Source #
:: PrimMonad m | |
=> MutableUnliftedArray (PrimState m) a | source |
-> Int | offset |
-> Int | length |
-> m (MutableUnliftedArray (PrimState m) a) |
Creates a new MutableUnliftedArray
containing a copy of a portion of
another mutable array.
singletonUnliftedArray :: PrimUnlifted a => a -> UnliftedArray a Source #
runUnliftedArray :: (forall s. ST s (MutableUnliftedArray s a)) -> UnliftedArray a Source #
Execute a stateful computation and freeze the resulting array.
List Conversion
unliftedArrayToList :: PrimUnlifted a => UnliftedArray a -> [a] Source #
Convert the unlifted array to a list.
unliftedArrayFromList :: PrimUnlifted a => [a] -> UnliftedArray a Source #
unliftedArrayFromListN :: forall a. PrimUnlifted a => Int -> [a] -> UnliftedArray a Source #
Folding
foldrUnliftedArray :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> UnliftedArray a -> b Source #
foldrUnliftedArray' :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> UnliftedArray a -> b Source #
Strict right-associated fold over the elements of an 'UnliftedArray.
foldlUnliftedArray :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> UnliftedArray a -> b Source #
Lazy left-associated fold over the elements of an UnliftedArray
.
foldlUnliftedArray' :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> UnliftedArray a -> b Source #
Strict left-associated fold over the elements of an UnliftedArray
.
foldlUnliftedArrayM' :: (PrimUnlifted a, Monad m) => (b -> a -> m b) -> b -> UnliftedArray a -> m b Source #
Strict effectful left-associated fold over the elements of an UnliftedArray
.
Traversals
traverseUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (a -> m b) -> UnliftedArray a -> m () Source #
Effectfully traverse the elements of an UnliftedArray
, discarding
the resulting values.
itraverseUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (Int -> a -> m b) -> UnliftedArray a -> m () Source #
Effectful indexed traversal of the elements of an UnliftedArray
,
discarding the resulting values.
Mapping
mapUnliftedArray :: (PrimUnlifted a, PrimUnlifted b) => (a -> b) -> UnliftedArray a -> UnliftedArray b Source #
Map over the elements of an UnliftedArray
.