Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A version of the SmallArray
interface
specialized to ST
. This is intended primarily so library
developers can easily check whether the basic operations are
unboxed properly, but its more constrained type signatures
also offer somewhat better type inference where applicable.
Synopsis
- data SmallUnliftedArray_ a unlifted_a = SmallUnliftedArray (SmallUnliftedArray# unlifted_a)
- type SmallUnliftedArray a = SmallUnliftedArray_ a (Unlifted a)
- data SmallMutableUnliftedArray_ s a unlifted_a = SmallMutableUnliftedArray (SmallMutableUnliftedArray# s unlifted_a)
- type SmallMutableUnliftedArray s a = SmallMutableUnliftedArray_ s a (Unlifted a)
- newSmallUnliftedArray :: PrimUnlifted a => Int -> a -> ST s (SmallMutableUnliftedArray s a)
- unsafeNewSmallUnliftedArray :: Int -> ST s (SmallMutableUnliftedArray s a)
- sizeofSmallUnliftedArray :: SmallUnliftedArray e -> Int
- getSizeofSmallMutableUnliftedArray :: SmallMutableUnliftedArray s e -> ST s Int
- sameSmallMutableUnliftedArray :: SmallMutableUnliftedArray s a -> SmallMutableUnliftedArray s a -> Bool
- shrinkSmallMutableUnliftedArray :: SmallMutableUnliftedArray s a -> Int -> ST s ()
- writeSmallUnliftedArray :: PrimUnlifted a => SmallMutableUnliftedArray s a -> Int -> a -> ST s ()
- readSmallUnliftedArray :: PrimUnlifted a => SmallMutableUnliftedArray s a -> Int -> ST s a
- indexSmallUnliftedArray :: PrimUnlifted a => SmallUnliftedArray a -> Int -> a
- unsafeFreezeSmallUnliftedArray :: SmallMutableUnliftedArray s a -> ST s (SmallUnliftedArray a)
- freezeSmallUnliftedArray :: SmallMutableUnliftedArray s a -> Int -> Int -> ST s (SmallUnliftedArray a)
- thawSmallUnliftedArray :: SmallUnliftedArray a -> Int -> Int -> ST s (SmallMutableUnliftedArray s a)
- unsafeThawSmallUnliftedArray :: SmallUnliftedArray a -> ST s (SmallMutableUnliftedArray s a)
- setSmallUnliftedArray :: PrimUnlifted a => SmallMutableUnliftedArray s a -> a -> Int -> Int -> ST s ()
- copySmallUnliftedArray :: SmallMutableUnliftedArray s a -> Int -> SmallUnliftedArray a -> Int -> Int -> ST s ()
- copySmallMutableUnliftedArray :: SmallMutableUnliftedArray s a -> Int -> SmallMutableUnliftedArray s a -> Int -> Int -> ST s ()
- cloneSmallUnliftedArray :: SmallUnliftedArray a -> Int -> Int -> SmallUnliftedArray a
- cloneSmallMutableUnliftedArray :: SmallMutableUnliftedArray s a -> Int -> Int -> ST s (SmallMutableUnliftedArray s a)
- emptySmallUnliftedArray :: SmallUnliftedArray a
- singletonSmallUnliftedArray :: PrimUnlifted a => a -> SmallUnliftedArray a
- runSmallUnliftedArray :: (forall s. ST s (SmallMutableUnliftedArray s a)) -> SmallUnliftedArray a
- dupableRunSmallUnliftedArray :: (forall s. ST s (SmallMutableUnliftedArray s a)) -> SmallUnliftedArray a
- smallUnliftedArrayToList :: PrimUnlifted a => SmallUnliftedArray a -> [a]
- smallUnliftedArrayFromList :: PrimUnlifted a => [a] -> SmallUnliftedArray a
- smallUnliftedArrayFromListN :: forall a. PrimUnlifted a => Int -> [a] -> SmallUnliftedArray a
- foldrSmallUnliftedArray :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> SmallUnliftedArray a -> b
- foldrSmallUnliftedArray' :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> SmallUnliftedArray a -> b
- foldlSmallUnliftedArray :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> SmallUnliftedArray a -> b
- foldlSmallUnliftedArray' :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> SmallUnliftedArray a -> b
- foldlSmallUnliftedArrayM' :: (PrimUnlifted a, Monad m) => (b -> a -> m b) -> b -> SmallUnliftedArray a -> m b
- traverseSmallUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (a -> m b) -> SmallUnliftedArray a -> m ()
- itraverseSmallUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (Int -> a -> m b) -> SmallUnliftedArray a -> m ()
- mapSmallUnliftedArray :: (PrimUnlifted a, PrimUnlifted b) => (a -> b) -> SmallUnliftedArray a -> SmallUnliftedArray b
Types
data SmallUnliftedArray_ a unlifted_a Source #
A SmallUnliftedArray_ 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.
SmallUnliftedArray (SmallUnliftedArray# unlifted_a) |
Instances
type SmallUnliftedArray a = SmallUnliftedArray_ a (Unlifted a) Source #
A type synonym for a SmallUnliftedArray_
containing lifted values of
a particular type. As a general rule, this type synonym should not be used in
class instances—use SmallUnliftedArray_
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 SmallUnliftedArray_
instead.
data SmallMutableUnliftedArray_ s a unlifted_a Source #
SmallMutableUnliftedArray (SmallMutableUnliftedArray# s unlifted_a) |
Instances
unlifted_a ~ Unlifted a => Eq (SmallMutableUnliftedArray_ s a unlifted_a) Source # | |
Defined in Data.Primitive.Unlifted.SmallArray.ST (==) :: SmallMutableUnliftedArray_ s a unlifted_a -> SmallMutableUnliftedArray_ s a unlifted_a -> Bool # (/=) :: SmallMutableUnliftedArray_ s a unlifted_a -> SmallMutableUnliftedArray_ s a unlifted_a -> Bool # | |
unlifted_a ~ Unlifted a => PrimUnlifted (SmallMutableUnliftedArray_ s a unlifted_a) Source # | |
Defined in Data.Primitive.Unlifted.SmallArray.ST type Unlifted (SmallMutableUnliftedArray_ s a unlifted_a) :: UnliftedType Source # toUnlifted# :: SmallMutableUnliftedArray_ s a unlifted_a -> Unlifted (SmallMutableUnliftedArray_ s a unlifted_a) Source # fromUnlifted# :: Unlifted (SmallMutableUnliftedArray_ s a unlifted_a) -> SmallMutableUnliftedArray_ s a unlifted_a Source # | |
type Unlifted (SmallMutableUnliftedArray_ s a unlifted_a) Source # | |
Defined in Data.Primitive.Unlifted.SmallArray.ST |
type SmallMutableUnliftedArray s a = SmallMutableUnliftedArray_ s a (Unlifted a) Source #
Operations
newSmallUnliftedArray Source #
:: PrimUnlifted a | |
=> Int | size |
-> a | initial value |
-> ST s (SmallMutableUnliftedArray s a) |
Creates a new MutableUnliftedArray
with the specified value as initial
contents.
unsafeNewSmallUnliftedArray Source #
:: Int | size |
-> ST s (SmallMutableUnliftedArray 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
sizeofSmallUnliftedArray :: SmallUnliftedArray e -> Int Source #
Yields the length of an UnliftedArray
.
getSizeofSmallMutableUnliftedArray :: SmallMutableUnliftedArray s e -> ST s Int Source #
Yields the length of a MutableUnliftedArray
.
sameSmallMutableUnliftedArray :: SmallMutableUnliftedArray s a -> SmallMutableUnliftedArray s a -> Bool Source #
Determines whether two MutableUnliftedArray
values are the same. This is
object/pointer identity, not based on the contents.
shrinkSmallMutableUnliftedArray :: SmallMutableUnliftedArray s a -> Int -> ST s () Source #
Shrink a mutable array to the specified size. The new size argument must be less than or equal to the current size.
writeSmallUnliftedArray :: PrimUnlifted a => SmallMutableUnliftedArray s a -> Int -> a -> ST s () Source #
readSmallUnliftedArray :: PrimUnlifted a => SmallMutableUnliftedArray s a -> Int -> ST s a Source #
indexSmallUnliftedArray :: PrimUnlifted a => SmallUnliftedArray a -> Int -> a Source #
unsafeFreezeSmallUnliftedArray :: SmallMutableUnliftedArray s a -> ST s (SmallUnliftedArray a) Source #
Freezes a SmallMutableUnliftedArray_
, yielding a SmallUnliftedArray_
.
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.
freezeSmallUnliftedArray Source #
:: SmallMutableUnliftedArray s a | source |
-> Int | offset |
-> Int | length |
-> ST s (SmallUnliftedArray 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.
thawSmallUnliftedArray Source #
:: SmallUnliftedArray a | source |
-> Int | offset |
-> Int | length |
-> ST s (SmallMutableUnliftedArray s a) |
Thaws a portion of a SmallUnliftedArray_
, yielding a SmallMutableUnliftedArray_
.
This copies the thawed portion, so mutations will not affect the original
array.
unsafeThawSmallUnliftedArray Source #
:: SmallUnliftedArray a | source |
-> ST s (SmallMutableUnliftedArray s a) |
Thaws a SmallUnliftedArray_
, yielding a SmallMutableUnliftedArray_
.
This does not make a copy.
setSmallUnliftedArray Source #
:: PrimUnlifted a | |
=> SmallMutableUnliftedArray s a | destination |
-> a | value to fill with |
-> Int | offset |
-> Int | length |
-> ST s () |
copySmallUnliftedArray Source #
:: SmallMutableUnliftedArray s a | destination |
-> Int | offset into destination |
-> SmallUnliftedArray 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.
copySmallMutableUnliftedArray Source #
:: SmallMutableUnliftedArray s a | destination |
-> Int | offset into destination |
-> SmallMutableUnliftedArray s a | source |
-> Int | offset into source |
-> Int | number of elements to copy |
-> ST s () |
Copies the contents of one mutable array into another.
cloneSmallUnliftedArray Source #
:: SmallUnliftedArray a | source |
-> Int | offset |
-> Int | length |
-> SmallUnliftedArray a |
Creates a copy of a portion of a SmallUnliftedArray_
cloneSmallMutableUnliftedArray Source #
:: SmallMutableUnliftedArray s a | source |
-> Int | offset |
-> Int | length |
-> ST s (SmallMutableUnliftedArray s a) |
Creates a new MutableUnliftedArray
containing a copy of a portion of
another mutable array.
singletonSmallUnliftedArray :: PrimUnlifted a => a -> SmallUnliftedArray a Source #
runSmallUnliftedArray :: (forall s. ST s (SmallMutableUnliftedArray s a)) -> SmallUnliftedArray a Source #
Execute a stateful computation and freeze the resulting array.
dupableRunSmallUnliftedArray :: (forall s. ST s (SmallMutableUnliftedArray s a)) -> SmallUnliftedArray 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
smallUnliftedArrayToList :: PrimUnlifted a => SmallUnliftedArray a -> [a] Source #
Convert the unlifted array to a list.
smallUnliftedArrayFromList :: PrimUnlifted a => [a] -> SmallUnliftedArray a Source #
smallUnliftedArrayFromListN :: forall a. PrimUnlifted a => Int -> [a] -> SmallUnliftedArray a Source #
Folding
foldrSmallUnliftedArray :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> SmallUnliftedArray a -> b Source #
foldrSmallUnliftedArray' :: forall a b. PrimUnlifted a => (a -> b -> b) -> b -> SmallUnliftedArray a -> b Source #
Strict right-associated fold over the elements of an 'SmallUnliftedArray.
foldlSmallUnliftedArray :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> SmallUnliftedArray a -> b Source #
Lazy left-associated fold over the elements of an SmallUnliftedArray_
.
foldlSmallUnliftedArray' :: forall a b. PrimUnlifted a => (b -> a -> b) -> b -> SmallUnliftedArray a -> b Source #
Strict left-associated fold over the elements of an SmallUnliftedArray_
.
foldlSmallUnliftedArrayM' :: (PrimUnlifted a, Monad m) => (b -> a -> m b) -> b -> SmallUnliftedArray a -> m b Source #
Strict effectful left-associated fold over the elements of an SmallUnliftedArray_
.
Traversals
traverseSmallUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (a -> m b) -> SmallUnliftedArray a -> m () Source #
Effectfully traverse the elements of an SmallUnliftedArray_
, discarding
the resulting values.
itraverseSmallUnliftedArray_ :: (PrimUnlifted a, Applicative m) => (Int -> a -> m b) -> SmallUnliftedArray a -> m () Source #
Effectful indexed traversal of the elements of an SmallUnliftedArray_
,
discarding the resulting values.
Mapping
mapSmallUnliftedArray :: (PrimUnlifted a, PrimUnlifted b) => (a -> b) -> SmallUnliftedArray a -> SmallUnliftedArray b Source #
Map over the elements of an SmallUnliftedArray_
.