streamly-0.7.2: Beautiful Streaming, Concurrent and Reactive Composition

Copyright(c) Roman Leshchinskiy 2009-2012
LicenseBSD-style
Maintainerstreamly@composewell.com
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Streamly.Internal.Data.Prim.Array.Types

Contents

Description

Arrays of unboxed primitive types. The function provided by this module match the behavior of those provided by Data.Primitive.ByteArray, and the underlying types and primops that back them are the same. However, the type constructors PrimArray and MutablePrimArray take one additional argument than their respective counterparts ByteArray and MutableByteArray. This argument is used to designate the type of element in the array. Consequently, all function this modules accepts length and incides in terms of elements, not bytes.

Since: 0.6.4.0

Synopsis

Types

data PrimArray a Source #

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.

Constructors

PrimArray ByteArray# 
Instances
(Eq a, Prim a) => Eq (PrimArray a) Source #

Since: 0.6.4.0

Instance details

Defined in Streamly.Internal.Data.Prim.Array.Types

Methods

(==) :: PrimArray a -> PrimArray a -> Bool #

(/=) :: PrimArray a -> PrimArray a -> Bool #

(Ord a, Prim a) => Ord (PrimArray a) Source #

Lexicographic ordering. Subject to change between major versions.

Since: 0.6.4.0

Instance details

Defined in Streamly.Internal.Data.Prim.Array.Types

(Show a, Prim a) => Show (PrimArray a) Source #

Since: 0.6.4.0

Instance details

Defined in Streamly.Internal.Data.Prim.Array.Types

Prim a => NFData (PrimArray a) Source # 
Instance details

Defined in Streamly.Internal.Data.Prim.Array

Methods

rnf :: PrimArray a -> () #

data MutablePrimArray s a Source #

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.

Allocation

newPrimArray :: forall m a. (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) Source #

Create a new mutable primitive array of the given length. The underlying memory is left uninitialized.

resizeMutablePrimArray Source #

Arguments

:: (PrimMonad m, Prim a) 
=> MutablePrimArray (PrimState m) a 
-> Int

new size

-> m (MutablePrimArray (PrimState m) a) 

Resize a mutable primitive array. The new size is given in elements.

This will either resize the array in-place or, if not possible, allocate the contents into a new, unpinned array and copy the original array's contents.

To avoid undefined behaviour, the original MutablePrimArray shall not be accessed anymore after a resizeMutablePrimArray has been performed. Moreover, no reference to the old one should be kept in order to allow garbage collection of the original MutablePrimArray in case a new MutablePrimArray had to be allocated.

shrinkMutablePrimArray Source #

Arguments

:: (PrimMonad m, Prim a) 
=> MutablePrimArray (PrimState m) a 
-> Int

new size

-> m () 

Shrink a mutable primitive array. The new size is given in elements. It must be smaller than the old size. The array will be resized in place. This function is only available when compiling with GHC 7.10 or newer.

Element Access

writePrimArray Source #

Arguments

:: (Prim a, PrimMonad m) 
=> MutablePrimArray (PrimState m) a

array

-> Int

index

-> a

element

-> m () 

Write an element to the given index.

indexPrimArray :: forall a. Prim a => PrimArray a -> Int -> a Source #

Read a primitive value from the primitive array.

Freezing and Thawing

unsafeFreezePrimArray :: PrimMonad m => MutablePrimArray (PrimState m) a -> m (PrimArray a) Source #

Convert a mutable byte array to an immutable one without copying. The array should not be modified after the conversion.

Information

sizeofPrimArray :: forall a. Prim a => PrimArray a -> Int Source #

Get the size, in elements, of the primitive array.

Folding

foldrPrimArray :: forall a b. Prim a => (a -> b -> b) -> b -> PrimArray a -> b Source #

Lazy right-associated fold over the elements of a PrimArray.

foldlPrimArray' :: forall a b. Prim a => (b -> a -> b) -> b -> PrimArray a -> b Source #

Strict left-associated fold over the elements of a PrimArray.