Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data PrimArray a = PrimArray ByteArray#
- data MutablePrimArray s a = MutablePrimArray (MutableByteArray# s)
- newPrimArray :: forall m a. (HasCallStack, PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a)
- resizeMutablePrimArray :: forall m a. (HasCallStack, PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> m (MutablePrimArray (PrimState m) a)
- shrinkMutablePrimArray :: forall m a. (HasCallStack, PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> m ()
- readPrimArray :: (HasCallStack, Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -> Int -> m a
- writePrimArray :: (HasCallStack, Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -> Int -> a -> m ()
- indexPrimArray :: forall a. Prim a => PrimArray a -> Int -> a
- unsafeFreezePrimArray :: PrimMonad m => MutablePrimArray (PrimState m) a -> m (PrimArray a)
- unsafeThawPrimArray :: PrimMonad m => PrimArray a -> m (MutablePrimArray (PrimState m) a)
- copyPrimArray :: forall m a. (HasCallStack, PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> PrimArray a -> Int -> Int -> m ()
- copyMutablePrimArray :: forall m a. (HasCallStack, PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> MutablePrimArray (PrimState m) a -> Int -> Int -> m ()
- copyPrimArrayToPtr :: (PrimMonad m, Prim a) => Ptr a -> PrimArray a -> Int -> Int -> m ()
- copyMutablePrimArrayToPtr :: (PrimMonad m, Prim a) => Ptr a -> MutablePrimArray (PrimState m) a -> Int -> Int -> m ()
- setPrimArray :: forall m a. (HasCallStack, Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
- sameMutablePrimArray :: MutablePrimArray s a -> MutablePrimArray s a -> Bool
- getSizeofMutablePrimArray :: (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> m Int
- sizeofMutablePrimArray :: Prim a => MutablePrimArray s a -> Int
- sizeofPrimArray :: Prim a => PrimArray a -> Int
- foldrPrimArray :: Prim a => (a -> b -> b) -> b -> PrimArray a -> b
- foldrPrimArray' :: Prim a => (a -> b -> b) -> b -> PrimArray a -> b
- foldlPrimArray :: Prim a => (b -> a -> b) -> b -> PrimArray a -> b
- foldlPrimArray' :: Prim a => (b -> a -> b) -> b -> PrimArray a -> b
- foldlPrimArrayM' :: (Prim a, Monad m) => (b -> a -> m b) -> b -> PrimArray a -> m b
- traversePrimArray_ :: (Applicative f, Prim a) => (a -> f b) -> PrimArray a -> f ()
- itraversePrimArray_ :: (Applicative f, Prim a) => (Int -> a -> f b) -> PrimArray a -> f ()
- mapPrimArray :: (Prim a, Prim b) => (a -> b) -> PrimArray a -> PrimArray b
- imapPrimArray :: (Prim a, Prim b) => (Int -> a -> b) -> PrimArray a -> PrimArray b
- generatePrimArray :: Prim a => Int -> (Int -> a) -> PrimArray a
- replicatePrimArray :: Prim a => Int -> a -> PrimArray a
- filterPrimArray :: Prim a => (a -> Bool) -> PrimArray a -> PrimArray a
- mapMaybePrimArray :: (Prim a, Prim b) => (a -> Maybe b) -> PrimArray a -> PrimArray b
- traversePrimArray :: (Applicative f, Prim a, Prim b) => (a -> f b) -> PrimArray a -> f (PrimArray b)
- itraversePrimArray :: (Applicative f, Prim a, Prim b) => (Int -> a -> f b) -> PrimArray a -> f (PrimArray b)
- generatePrimArrayA :: (Applicative f, Prim a) => Int -> (Int -> f a) -> f (PrimArray a)
- replicatePrimArrayA :: (Applicative f, Prim a) => Int -> f a -> f (PrimArray a)
- filterPrimArrayA :: (Applicative f, Prim a) => (a -> f Bool) -> PrimArray a -> f (PrimArray a)
- mapMaybePrimArrayA :: (Applicative f, Prim a, Prim b) => (a -> f (Maybe b)) -> PrimArray a -> f (PrimArray b)
- traversePrimArrayP :: (PrimMonad m, Prim a, Prim b) => (a -> m b) -> PrimArray a -> m (PrimArray b)
- itraversePrimArrayP :: (Prim a, Prim b, PrimMonad m) => (Int -> a -> m b) -> PrimArray a -> m (PrimArray b)
- generatePrimArrayP :: (PrimMonad m, Prim a) => Int -> (Int -> m a) -> m (PrimArray a)
- replicatePrimArrayP :: (PrimMonad m, Prim a) => Int -> m a -> m (PrimArray a)
- filterPrimArrayP :: (PrimMonad m, Prim a) => (a -> m Bool) -> PrimArray a -> m (PrimArray a)
- mapMaybePrimArrayP :: (PrimMonad m, Prim a, Prim b) => (a -> m (Maybe b)) -> PrimArray a -> m (PrimArray b)
Types
Arrays of unboxed elements. This accepts types like Double
, Char
,
Int
, and Word
, as well as their fixed-length variants (Word8
,
Word16
, etc.). Since the elements are unboxed, a PrimArray
is strict
in its elements. This differs from the behavior of Array
, which is lazy
in its elements.
Instances
Prim a => IsList (PrimArray a) | Since: primitive-0.6.4.0 |
(Eq a, Prim a) => Eq (PrimArray a) | Since: primitive-0.6.4.0 |
(Ord a, Prim a) => Ord (PrimArray a) | Lexicographic ordering. Subject to change between major versions. Since: primitive-0.6.4.0 |
Defined in Data.Primitive.PrimArray | |
(Show a, Prim a) => Show (PrimArray a) | Since: primitive-0.6.4.0 |
Semigroup (PrimArray a) | Since: primitive-0.6.4.0 |
Monoid (PrimArray a) | Since: primitive-0.6.4.0 |
PrimUnlifted (PrimArray a) | Since: primitive-0.6.4.0 |
Defined in Data.Primitive.UnliftedArray toArrayArray# :: PrimArray a -> ArrayArray# # fromArrayArray# :: ArrayArray# -> PrimArray a # | |
type Item (PrimArray a) | |
Defined in Data.Primitive.PrimArray |
data MutablePrimArray s a #
Mutable primitive arrays associated with a primitive state token.
These can be written to and read from in a monadic context that supports
sequencing such as IO
or ST
. Typically, a mutable primitive array will
be built and then convert to an immutable primitive array using
unsafeFreezePrimArray
. However, it is also acceptable to simply discard
a mutable primitive array since it lives in managed memory and will be
garbage collected when no longer referenced.
Instances
PrimUnlifted (MutablePrimArray s a) | Since: primitive-0.6.4.0 |
Defined in Data.Primitive.UnliftedArray toArrayArray# :: MutablePrimArray s a -> ArrayArray# # fromArrayArray# :: ArrayArray# -> MutablePrimArray s a # |
Allocation
newPrimArray :: forall m a. (HasCallStack, PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) Source #
resizeMutablePrimArray Source #
:: (HasCallStack, PrimMonad m, Prim a) | |
=> MutablePrimArray (PrimState m) a | |
-> Int | new size |
-> m (MutablePrimArray (PrimState m) a) |
shrinkMutablePrimArray Source #
:: (HasCallStack, PrimMonad m, Prim a) | |
=> MutablePrimArray (PrimState m) a | |
-> Int | new size |
-> m () |
Element Access
readPrimArray :: (HasCallStack, Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -> Int -> m a Source #
:: (HasCallStack, Prim a, PrimMonad m) | |
=> MutablePrimArray (PrimState m) a | array |
-> Int | index |
-> a | element |
-> m () |
Freezing and Thawing
unsafeFreezePrimArray :: PrimMonad m => MutablePrimArray (PrimState m) a -> m (PrimArray a) #
Convert a mutable byte array to an immutable one without copying. The array should not be modified after the conversion.
unsafeThawPrimArray :: PrimMonad m => PrimArray a -> m (MutablePrimArray (PrimState m) a) #
Convert an immutable array to a mutable one without copying. The original array should not be used after the conversion.
Block Operations
:: (HasCallStack, PrimMonad m, Prim a) | |
=> MutablePrimArray (PrimState m) a | destination array |
-> Int | offset into destination array |
-> PrimArray a | source array |
-> Int | offset into source array |
-> Int | number of elements to copy |
-> m () |
:: (HasCallStack, PrimMonad m, Prim a) | |
=> MutablePrimArray (PrimState m) a | destination array |
-> Int | offset into destination array |
-> MutablePrimArray (PrimState m) a | source array |
-> Int | offset into source array |
-> Int | number of elements to copy |
-> m () |
:: (PrimMonad m, Prim a) | |
=> Ptr a | destination pointer |
-> PrimArray a | source array |
-> Int | offset into source array |
-> Int | number of prims to copy |
-> m () |
Copy a slice of an immutable primitive array to an address.
The offset and length are given in elements of type a
.
This function assumes that the Prim
instance of a
agrees with the Storable
instance. This function is only
available when building with GHC 7.8 or newer.
:: (PrimMonad m, Prim a) | |
=> Ptr a | destination pointer |
-> MutablePrimArray (PrimState m) a | source array |
-> Int | offset into source array |
-> Int | number of prims to copy |
-> m () |
Copy a slice of an immutable primitive array to an address.
The offset and length are given in elements of type a
.
This function assumes that the Prim
instance of a
agrees with the Storable
instance. This function is only
available when building with GHC 7.8 or newer.
:: (HasCallStack, Prim a, PrimMonad m) | |
=> MutablePrimArray (PrimState m) a | array to fill |
-> Int | offset into array |
-> Int | number of values to fill |
-> a | value to fill with |
-> m () |
Information
sameMutablePrimArray :: MutablePrimArray s a -> MutablePrimArray s a -> Bool #
Check if the two arrays refer to the same memory block.
:: (PrimMonad m, Prim a) | |
=> MutablePrimArray (PrimState m) a | array |
-> m Int |
Get the size of a mutable primitive array in elements. Unlike sizeofMutablePrimArray
,
this function ensures sequencing in the presence of resizing.
sizeofMutablePrimArray :: Prim a => MutablePrimArray s a -> Int #
Size of the mutable primitive array in elements. This function shall not
be used on primitive arrays that are an argument to or a result of
resizeMutablePrimArray
or shrinkMutablePrimArray
.
sizeofPrimArray :: Prim a => PrimArray a -> Int #
Get the size, in elements, of the primitive array.
Folding
foldrPrimArray :: Prim a => (a -> b -> b) -> b -> PrimArray a -> b #
Lazy right-associated fold over the elements of a PrimArray
.
foldrPrimArray' :: Prim a => (a -> b -> b) -> b -> PrimArray a -> b #
Strict right-associated fold over the elements of a PrimArray
.
foldlPrimArray :: Prim a => (b -> a -> b) -> b -> PrimArray a -> b #
Lazy left-associated fold over the elements of a PrimArray
.
foldlPrimArray' :: Prim a => (b -> a -> b) -> b -> PrimArray a -> b #
Strict left-associated fold over the elements of a PrimArray
.
foldlPrimArrayM' :: (Prim a, Monad m) => (b -> a -> m b) -> b -> PrimArray a -> m b #
Strict left-associated fold over the elements of a PrimArray
.
Effectful Folding
traversePrimArray_ :: (Applicative f, Prim a) => (a -> f b) -> PrimArray a -> f () #
Traverse the primitive array, discarding the results. There
is no PrimMonad
variant of this function since it would not provide
any performance benefit.
itraversePrimArray_ :: (Applicative f, Prim a) => (Int -> a -> f b) -> PrimArray a -> f () #
Traverse the primitive array with the indices, discarding the results.
There is no PrimMonad
variant of this function since it would not
provide any performance benefit.
Map/Create
mapPrimArray :: (Prim a, Prim b) => (a -> b) -> PrimArray a -> PrimArray b #
Map over the elements of a primitive array.
imapPrimArray :: (Prim a, Prim b) => (Int -> a -> b) -> PrimArray a -> PrimArray b #
Indexed map over the elements of a primitive array.
Generate a primitive array.
Create a primitive array by copying the element the given number of times.
filterPrimArray :: Prim a => (a -> Bool) -> PrimArray a -> PrimArray a #
Filter elements of a primitive array according to a predicate.
mapMaybePrimArray :: (Prim a, Prim b) => (a -> Maybe b) -> PrimArray a -> PrimArray b #
Map over a primitive array, optionally discarding some elements. This
has the same behavior as Data.Maybe.mapMaybe
.
Effectful Map/Create
:: (Applicative f, Prim a, Prim b) | |
=> (a -> f b) | mapping function |
-> PrimArray a | primitive array |
-> f (PrimArray b) |
Traverse a primitive array. The traversal performs all of the applicative effects before forcing the resulting values and writing them to the new primitive array. Consequently:
>>>
traversePrimArray (\x -> print x $> bool x undefined (x == 2)) (fromList [1, 2, 3 :: Int])
1 2 3 *** Exception: Prelude.undefined
The function traversePrimArrayP
always outperforms this function, but it
requires a PrimAffineMonad
constraint, and it forces the values as
it performs the effects.
itraversePrimArray :: (Applicative f, Prim a, Prim b) => (Int -> a -> f b) -> PrimArray a -> f (PrimArray b) #
Traverse a primitive array with the index of each element.
:: (Applicative f, Prim a) | |
=> Int | length |
-> (Int -> f a) | element from index |
-> f (PrimArray a) |
Generate a primitive array by evaluating the applicative generator function at each index.
:: (Applicative f, Prim a) | |
=> Int | length |
-> f a | applicative element producer |
-> f (PrimArray a) |
Execute the applicative action the given number of times and store the results in a vector.
:: (Applicative f, Prim a) | |
=> (a -> f Bool) | mapping function |
-> PrimArray a | primitive array |
-> f (PrimArray a) |
Filter the primitive array, keeping the elements for which the monadic predicate evaluates true.
:: (Applicative f, Prim a, Prim b) | |
=> (a -> f (Maybe b)) | mapping function |
-> PrimArray a | primitive array |
-> f (PrimArray b) |
Map over the primitive array, keeping the elements for which the applicative
predicate provides a Just
.
Strict Primitive Monadic
traversePrimArrayP :: (PrimMonad m, Prim a, Prim b) => (a -> m b) -> PrimArray a -> m (PrimArray b) #
Traverse a primitive array. The traversal forces the resulting values and writes them to the new primitive array as it performs the monadic effects. Consequently:
>>>
traversePrimArrayP (\x -> print x $> bool x undefined (x == 2)) (fromList [1, 2, 3 :: Int])
1 2 *** Exception: Prelude.undefined
In many situations, traversePrimArrayP
can replace traversePrimArray
,
changing the strictness characteristics of the traversal but typically improving
the performance. Consider the following short-circuiting traversal:
incrPositiveA :: PrimArray Int -> Maybe (PrimArray Int) incrPositiveA xs = traversePrimArray (\x -> bool Nothing (Just (x + 1)) (x > 0)) xs
This can be rewritten using traversePrimArrayP
. To do this, we must
change the traversal context to MaybeT (ST s)
, which has a PrimMonad
instance:
incrPositiveB :: PrimArray Int -> Maybe (PrimArray Int) incrPositiveB xs = runST $ runMaybeT $ traversePrimArrayP (\x -> bool (MaybeT (return Nothing)) (MaybeT (return (Just (x + 1)))) (x > 0)) xs
Benchmarks demonstrate that the second implementation runs 150 times faster than the first. It also results in fewer allocations.
itraversePrimArrayP :: (Prim a, Prim b, PrimMonad m) => (Int -> a -> m b) -> PrimArray a -> m (PrimArray b) #
Traverse a primitive array with the indices. The traversal forces the resulting values and writes them to the new primitive array as it performs the monadic effects.
Generate a primitive array by evaluating the monadic generator function at each index.
replicatePrimArrayP :: (PrimMonad m, Prim a) => Int -> m a -> m (PrimArray a) #
Execute the monadic action the given number of times and store the results in a primitive array.