Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | released |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Deprecated: Please use Streamly.Data.Array module from the streamly-core package.
This module provides immutable arrays in pinned memory (non GC memory) suitable for long lived data storage, random access and for interfacing with the operating system.
Arrays in this module are chunks of pinned memory that hold a sequence of
Storable
values of a given type, they cannot store non-serializable data
like functions. Once created an array cannot be modified. Pinned memory
allows efficient buffering of long lived data without adding any impact to
GC. One array is just one pointer visible to GC and it does not have to be
copied across generations. Moreover, pinned memory allows communication
with foreign consumers and producers (e.g. file or network IO) without
copying the data.
Programmer Notes
Array creation APIs require a MonadIO
Monad, except fromList
which is a
pure API. To operate on streams in pure Monads like Identity
you can hoist
it to IO monad as follows:
>>>
import Data.Functor.Identity (Identity, runIdentity)
>>>
s = Stream.fromList [1..10] :: SerialT Identity Int
>>>
s1 = Stream.hoist (return . runIdentity) s :: SerialT IO Int
>>>
Stream.fold Array.write s1 :: IO (Array Int)
fromList [1,2,3,4,5,6,7,8,9,10]
unsafePerformIO
can be used to get a pure API from IO, as long as you know
it is safe to do so:
>>>
import System.IO.Unsafe (unsafePerformIO)
>>>
unsafePerformIO $ Stream.fold Array.write s1 :: Array Int
fromList [1,2,3,4,5,6,7,8,9,10]
To apply a transformation to an array use read
to unfold the array into a
stream, apply a transformation on the stream and then use write
to fold it
back to an array.
This module is designed to be imported qualified:
import qualified Streamly.Data.Array as Array
For experimental APIs see Streamly.Internal.Data.Array.
Synopsis
- data Array a
- fromListN :: Unbox a => Int -> [a] -> Array a
- fromList :: Unbox a => [a] -> Array a
- writeN :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a)
- write :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (Array a)
- writeLastN :: forall a (m :: Type -> Type). (Storable a, Unbox a, MonadIO m) => Int -> Fold m a (Array a)
- toList :: Unbox a => Array a -> [a]
- read :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Array a -> Stream m a
- readRev :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Array a -> Stream m a
- cast :: forall a b. Unbox b => Array a -> Maybe (Array b)
- asBytes :: Array a -> Array Word8
- length :: Unbox a => Array a -> Int
- getIndex :: Unbox a => Int -> Array a -> Maybe a
Documentation
Instances
NFData1 Array Source # | |
Defined in Streamly.Data.Array.Foreign | |
a ~ Char => IsString (Array a) | |
Defined in Streamly.Internal.Data.Array.Type fromString :: String -> Array a # | |
Unbox a => Monoid (Array a) | |
Unbox a => Semigroup (Array a) | This should not be used for combining many or N arrays as it would copy
the two arrays everytime to a new array. For coalescing multiple arrays use
|
Unbox a => IsList (Array a) | |
(Unbox a, Read a, Show a) => Read (Array a) | |
(Show a, Unbox a) => Show (Array a) | |
NFData (Array a) Source # | |
Defined in Streamly.Data.Array.Foreign | |
Eq (Array Int16) | |
Eq (Array Int32) | |
Eq (Array Int64) | |
Eq (Array Int8) | |
Eq (Array Word16) | |
Eq (Array Word32) | |
Eq (Array Word64) | |
Eq (Array Word8) | |
Eq (Array Char) | |
Eq (Array Int) | |
(Unbox a, Eq a) => Eq (Array a) | If the type allows a byte-by-byte comparison this instance can be
overlapped by a more specific instance that uses |
(Unbox a, Ord a) => Ord (Array a) | |
Defined in Streamly.Internal.Data.Array.Type | |
type Item (Array a) | |
Defined in Streamly.Internal.Data.Array.Type |
Arrays
Construction
When performance matters, the fastest way to generate an array is
writeN
. IsList
and IsString
instances can be
used to conveniently construct arrays from literal values.
OverloadedLists
extension or fromList
can be used to construct an
array from a list literal. Similarly, OverloadedStrings
extension or
fromList
can be used to construct an array from a string literal.
fromListN :: Unbox a => Int -> [a] -> Array a #
Create an Array
from the first N elements of a list. The array is
allocated to size N, if the list terminates before N elements then the
array may hold less than N elements.
fromList :: Unbox a => [a] -> Array a #
Create an Array
from a list. The list must be of finite size.
writeLastN :: forall a (m :: Type -> Type). (Storable a, Unbox a, MonadIO m) => Int -> Fold m a (Array a) #
writeLastN n
folds a maximum of n
elements from the end of the input
stream to an Array
.
Elimination
read :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Array a -> Stream m a #
Convert an Array
into a stream.
Pre-release
readRev :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Array a -> Stream m a #
Convert an Array
into a stream in reverse order.
Pre-release
Casting
cast :: forall a b. Unbox b => Array a -> Maybe (Array b) #
Cast an array having elements of type a
into an array having elements of
type b
. The length of the array should be a multiple of the size of the
target element otherwise Nothing
is returned.
Random Access
length :: Unbox a => Array a -> Int #
O(1) Get the length of the array i.e. the number of elements in the array.
getIndex :: Unbox a => Int -> Array a -> Maybe a #
O(1) Lookup the element at the given index. Index starts from 0.