Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data UnliftedArray_ unlifted_a a = UnliftedArray (UnliftedArray# unlifted_a)
- type UnliftedArray a = UnliftedArray_ (Unlifted a) a
- data MutableUnliftedArray_ unlifted_a s a = MutableUnliftedArray (MutableUnliftedArray# s unlifted_a)
- type MutableUnliftedArray s a = MutableUnliftedArray_ (Unlifted a) s a
- newUnliftedArray :: PrimUnlifted a => Int -> a -> ST s (MutableUnliftedArray s a)
- unsafeNewUnliftedArray :: Int -> ST s (MutableUnliftedArray s a)
- sizeofUnliftedArray :: UnliftedArray e -> Int
- sizeofMutableUnliftedArray :: MutableUnliftedArray s e -> Int
- sameMutableUnliftedArray :: MutableUnliftedArray_ unlifted_a s a -> MutableUnliftedArray_ unlifted_a s a -> Bool
- writeUnliftedArray :: PrimUnlifted a => MutableUnliftedArray s a -> Int -> a -> ST s ()
- readUnliftedArray :: PrimUnlifted a => MutableUnliftedArray s a -> Int -> ST s a
- indexUnliftedArray :: PrimUnlifted a => UnliftedArray a -> Int -> a
- unsafeFreezeUnliftedArray :: MutableUnliftedArray s a -> ST s (UnliftedArray a)
- freezeUnliftedArray :: MutableUnliftedArray s a -> Int -> Int -> ST s (UnliftedArray a)
- thawUnliftedArray :: UnliftedArray a -> Int -> Int -> ST s (MutableUnliftedArray s a)
- unsafeThawUnliftedArray :: UnliftedArray a -> ST s (MutableUnliftedArray s a)
- setUnliftedArray :: PrimUnlifted a => MutableUnliftedArray s a -> a -> Int -> Int -> ST s ()
- copyUnliftedArray :: MutableUnliftedArray s a -> Int -> UnliftedArray a -> Int -> Int -> ST s ()
- copyMutableUnliftedArray :: MutableUnliftedArray s a -> Int -> MutableUnliftedArray s a -> Int -> Int -> ST s ()
- cloneUnliftedArray :: UnliftedArray a -> Int -> Int -> UnliftedArray a
- cloneMutableUnliftedArray :: MutableUnliftedArray s a -> Int -> Int -> ST s (MutableUnliftedArray s a)
- emptyUnliftedArray :: UnliftedArray_ unlifted_a a
- singletonUnliftedArray :: PrimUnlifted a => a -> UnliftedArray a
- runUnliftedArray :: (forall s. ST s (MutableUnliftedArray s a)) -> UnliftedArray a
- dupableRunUnliftedArray :: (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_ unlifted_a a Source #
An UnliftedArray_ a unlifted_a
represents an array of values of a
lifted type a
that wrap values of an unlifted type unlifted_a
.
It is expected that unlifted_a ~ Unlifted a
, but imposing that constraint
here would force the type roles to nominal
, which is often undesirable
when arrays are used as components of larger datatypes.
UnliftedArray (UnliftedArray# unlifted_a) |
Instances
type UnliftedArray a = UnliftedArray_ (Unlifted a) a Source #
A type synonym for an UnliftedArray_
containing lifted values of
a particular type. As a general rule, this type synonym should not be used in
class instances—use UnliftedArray_
with an equality constraint instead.
It also should not be used when defining newtypes or datatypes, unless those
will have restrictive type roles regardless—use UnliftedArray_
instead.
data MutableUnliftedArray_ unlifted_a s a Source #
A mutable version of UnliftedArray_
.
MutableUnliftedArray (MutableUnliftedArray# s unlifted_a) |
Instances
unlifted_a ~ Unlifted a => Eq (MutableUnliftedArray_ unlifted_a s a) Source # | |
Defined in Data.Primitive.Unlifted.Array.ST (==) :: MutableUnliftedArray_ unlifted_a s a -> MutableUnliftedArray_ unlifted_a s a -> Bool # (/=) :: MutableUnliftedArray_ unlifted_a s a -> MutableUnliftedArray_ unlifted_a s a -> Bool # | |
unlifted_a ~ Unlifted a => PrimUnlifted (MutableUnliftedArray_ unlifted_a s a) Source # | |
Defined in Data.Primitive.Unlifted.Array.ST type Unlifted (MutableUnliftedArray_ unlifted_a s a) :: UnliftedType Source # toUnlifted# :: MutableUnliftedArray_ unlifted_a s a -> Unlifted (MutableUnliftedArray_ unlifted_a s a) Source # fromUnlifted# :: Unlifted (MutableUnliftedArray_ unlifted_a s a) -> MutableUnliftedArray_ unlifted_a s a Source # | |
type Unlifted (MutableUnliftedArray_ unlifted_a s a) Source # | |
Defined in Data.Primitive.Unlifted.Array.ST |
type MutableUnliftedArray s a = MutableUnliftedArray_ (Unlifted a) s a Source #
A mutable version of MutableUnliftedArray_
.
Operations
:: PrimUnlifted a | |
=> Int | size |
-> a | initial value |
-> ST s (MutableUnliftedArray s a) |
Creates a new MutableUnliftedArray_
with the specified value as initial
contents.
unsafeNewUnliftedArray Source #
:: Int | size |
-> ST s (MutableUnliftedArray s a) |
Creates a new MutableUnliftedArray_
. This function is unsafe because it
initializes all elements of the array as pointers to the empty array. Attempting
to read one of these elements before writing to it is in effect an unsafe
coercion from
to the element type.UnliftedArray_
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_ unlifted_a s a -> MutableUnliftedArray_ unlifted_a s a -> Bool Source #
Determines whether two MutableUnliftedArray_
values are the same. This is
object/pointer identity, not based on the contents.
writeUnliftedArray :: PrimUnlifted a => MutableUnliftedArray s a -> Int -> a -> ST s () Source #
readUnliftedArray :: PrimUnlifted a => MutableUnliftedArray s a -> Int -> ST s a Source #
indexUnliftedArray :: PrimUnlifted a => UnliftedArray a -> Int -> a Source #
unsafeFreezeUnliftedArray :: MutableUnliftedArray s a -> ST s (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.
:: MutableUnliftedArray s a | source |
-> Int | offset |
-> Int | length |
-> ST s (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.
:: UnliftedArray a | source |
-> Int | offset |
-> Int | length |
-> ST s (MutableUnliftedArray s a) |
Thaws a portion of an UnliftedArray_
, yielding a MutableUnliftedArray_
.
This copies the thawed portion, so mutations will not affect the original
array.
unsafeThawUnliftedArray Source #
:: UnliftedArray a | source |
-> ST s (MutableUnliftedArray s a) |
Thaws an UnliftedArray_
, yielding a MutableUnliftedArray_
. This
does not make a copy.
:: PrimUnlifted a | |
=> MutableUnliftedArray s a | destination |
-> a | value to fill with |
-> Int | offset |
-> Int | length |
-> ST s () |
:: MutableUnliftedArray s a | destination |
-> Int | offset into destination |
-> UnliftedArray a | source |
-> Int | offset into source |
-> Int | number of elements to copy |
-> ST s () |
Copies the contents of an immutable array into a mutable array.
copyMutableUnliftedArray Source #
:: MutableUnliftedArray s a | destination |
-> Int | offset into destination |
-> MutableUnliftedArray s a | source |
-> Int | offset into source |
-> Int | number of elements to copy |
-> ST s () |
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 #
:: MutableUnliftedArray s a | source |
-> Int | offset |
-> Int | length |
-> ST s (MutableUnliftedArray s a) |
Creates a new MutableUnliftedArray_
containing a copy of a portion of
another mutable array.
emptyUnliftedArray :: UnliftedArray_ unlifted_a a Source #
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.
dupableRunUnliftedArray :: (forall s. ST s (MutableUnliftedArray s a)) -> UnliftedArray a Source #
Execute a stateful computation and freeze the resulting array. It is possible, but unlikely, that the computation will be run multiple times in multiple threads.
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_
.