Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class PrimUnlifted a where
- writeUnliftedArray# :: MutableArrayArray# s -> Int# -> a -> State# s -> State# s
- readUnliftedArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, a #)
- indexUnliftedArray# :: ArrayArray# -> Int# -> a
- data MutableUnliftedArray s a = MutableUnliftedArray (MutableArrayArray# s)
- data UnliftedArray a = UnliftedArray ArrayArray#
- unsafeNewUnliftedArray :: PrimMonad m => Int -> m (MutableUnliftedArray (PrimState m) a)
- newUnliftedArray :: (PrimMonad m, PrimUnlifted a) => Int -> a -> m (MutableUnliftedArray (PrimState m) a)
- setUnliftedArray :: (PrimMonad m, PrimUnlifted a) => MutableUnliftedArray (PrimState m) a -> Int -> Int -> a -> m ()
- sizeofUnliftedArray :: UnliftedArray e -> Int
- sizeofMutableUnliftedArray :: MutableUnliftedArray s e -> Int
- 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)
- sameMutableUnliftedArray :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool
- 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 ()
- freezeUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> Int -> m (UnliftedArray a)
- thawUnliftedArray :: PrimMonad m => UnliftedArray a -> Int -> Int -> m (MutableUnliftedArray (PrimState m) a)
- cloneUnliftedArray :: UnliftedArray a -> Int -> Int -> UnliftedArray a
- cloneMutableUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> Int -> m (MutableUnliftedArray (PrimState m) a)
Documentation
class PrimUnlifted a where Source #
writeUnliftedArray# :: MutableArrayArray# s -> Int# -> a -> State# s -> State# s Source #
readUnliftedArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, a #) Source #
indexUnliftedArray# :: ArrayArray# -> Int# -> a Source #
Instances
data UnliftedArray a Source #
Instances
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
:: (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.
:: (PrimMonad m, PrimUnlifted a) | |
=> MutableUnliftedArray (PrimState m) a | destination |
-> Int | offset |
-> Int | length |
-> a | value to fill with |
-> m () |
sizeofUnliftedArray :: UnliftedArray e -> Int Source #
Yields the length of an UnliftedArray
.
sizeofMutableUnliftedArray :: MutableUnliftedArray s e -> Int Source #
Yields the length of a MutableUnliftedArray
.
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.
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.
:: 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.
:: 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.
:: 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.