streamly-core-0.1.0: Streaming, parsers, arrays and more
Copyright(c) 2019 Composewell Technologies
LicenseBSD3
Maintainerstreamly@composewell.com
Stabilityreleased
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Data.Array

Description

Unboxed immutable arrays with streaming interfaces.

Please refer to Streamly.Internal.Data.Array for functions that have not yet been released.

For arrays that work on boxed types, not requiring the Unbox constraint, please refer to Streamly.Data.Array.Generic. For arrays that can be mutated in-place, please see Streamly.Data.MutArray.

Synopsis

Setup

To execute the code examples provided in this module in ghci, please run the following commands first.

>>> :m
>>> :set -XFlexibleContexts
>>> import Data.Function ((&))
>>> import Data.Functor.Identity (Identity(..))
>>> import System.IO.Unsafe (unsafePerformIO)
>>> import Streamly.Data.Array (Array)
>>> import Streamly.Data.Stream (Stream)
>>> import qualified Streamly.Data.Array as Array
>>> import qualified Streamly.Data.Fold as Fold
>>> import qualified Streamly.Data.Stream as Stream

Overview

This module provides APIs to create and use unboxed immutable arrays. Once created, their contents cannot be modified. Only types that are unboxable via the Unbox type class can be stored in these arrays. Note that the array memory grows automatically when creating a new array, therefore, an array can be created from a variable length stream.

Folding Arrays

Convert array to stream, and fold the stream:

>>> fold f arr = Stream.unfold Array.reader arr & Stream.fold f
>>> fold Fold.sum (Array.fromList [1,2,3::Int])
6

Transforming Arrays

Convert array to stream, transform, and fold back to array:

>>> amap f arr = Stream.unfold Array.reader arr & fmap f & Stream.fold Array.write
>>> amap (+1) (Array.fromList [1,2,3::Int])
fromList [2,3,4]

Pinned and Unpinned Arrays

The array type can use both pinned and unpinned memory under the hood. Currently the array creation APIs create arrays in pinned memory but it will change to unpinned in future releases. The change should not affect users functionally unless they are directly accessing the internal memory of the array via internal APIs. As of now unpinned arrays can be created using unreleased APIs.

Unpinned arrays have the advantage of allowing automatic defragmentation of the memory by GC. Whereas pinned arrays have the advantage of not requiring a copy by GC. Normally you would want to use unpinned arrays. However, in some cases, for example, for long lived large data storage, and for interfacing with the operating system or foreign (non-Haskell) consumers you may want to use pinned arrays.

Creating Arrays from Non-IO Streams

Array creation folds require MonadIO because they need to sequence effects in IO streams. To operate on streams in pure Monads like Identity you can morph it to IO monad as follows:

The MonadIO based folds can be morphed to Identity stream folds:

>>> purely = Fold.morphInner (Identity . unsafePerformIO)
>>> Stream.fold (purely Array.write) $ Stream.fromList [1,2,3::Int]
Identity fromList [1,2,3]

Since it is a pure stream we can use unsafePerformIO to extract the result of fold from IO.

Alternatively, Identity streams can be generalized to IO streams:

>>> pure = Stream.fromList [1,2,3] :: Stream Identity Int
>>> generally = Stream.morphInner (return . runIdentity)
>>> Stream.fold Array.write (generally pure :: Stream IO Int)
fromList [1,2,3]

Programming Tips

This module is designed to be imported qualified:

>>> import qualified Streamly.Data.Array as Array

The Array Type

data Array a Source #

Instances

Instances details
a ~ Char => IsString (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

fromString :: String -> Array a #

Unbox a => Monoid (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

Unbox a => Semigroup (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

(<>) :: Array a -> Array a -> Array a #

sconcat :: NonEmpty (Array a) -> Array a #

stimes :: Integral b => b -> Array a -> Array a #

Unbox a => IsList (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Associated Types

type Item (Array a) #

Methods

fromList :: [Item (Array a)] -> Array a #

fromListN :: Int -> [Item (Array a)] -> Array a #

toList :: Array a -> [Item (Array a)] #

(Unbox a, Read a, Show a) => Read (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

(Show a, Unbox a) => Show (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

(Unbox a, Eq a) => Eq (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

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

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

(Unbox a, Ord a) => Ord (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

compare :: Array a -> Array a -> Ordering #

(<) :: Array a -> Array a -> Bool #

(<=) :: Array a -> Array a -> Bool #

(>) :: Array a -> Array a -> Bool #

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

max :: Array a -> Array a -> Array a #

min :: Array a -> Array a -> Array a #

type Item (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

type Item (Array a) = a

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 Source #

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 Source #

Create an Array from a list. The list must be of finite size.

writeN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) Source #

writeN n folds a maximum of n elements from the input stream to an Array.

write :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a) Source #

Fold the whole input to a single array.

Caution! Do not use this on infinite streams.

writeLastN :: (Storable a, Unbox a, MonadIO m) => Int -> Fold m a (Array a) Source #

writeLastN n folds a maximum of n elements from the end of the input stream to an Array.

Conversion

toList :: Unbox a => Array a -> [a] Source #

Convert an Array into a list.

Unfolds

reader :: forall m a. (Monad m, Unbox a) => Unfold m (Array a) a Source #

Unfold an array into a stream.

readerRev :: forall m a. (Monad m, Unbox a) => Unfold m (Array a) a Source #

Unfold an array into a stream in reverse order.

Casting

cast :: forall a b. Unbox b => Array a -> Maybe (Array b) Source #

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.

asBytes :: Array a -> Array Word8 Source #

Cast an Array a into an Array Word8.

Random Access

length :: Unbox a => Array a -> Int Source #

O(1) Get the length of the array i.e. the number of elements in the array.

getIndex :: forall a. Unbox a => Int -> Array a -> Maybe a Source #

O(1) Lookup the element at the given index. Index starts from 0.

Unbox Type Class

class Unbox a where Source #

A type implementing the Unbox interface supplies operations for reading and writing the type from and to a mutable byte array (an unboxed representation of the type) in memory. The read operation peekByteIndex deserializes the boxed type from the mutable byte array. The write operation pokeByteIndex serializes the boxed type to the mutable byte array.

Instances can be derived via Generic. Note that the data type must be non-recursive. Here is an example, for deriving an instance of this type class.

>>> import GHC.Generics (Generic)
>>> :{
data Object = Object
    { _int0 :: Int
    , _int1 :: Int
    } deriving Generic
:}

WARNING! Generic deriving hangs for recursive data types.

>>> import Streamly.Data.Array (Unbox(..))
>>> instance Unbox Object

If you want to write the instance manually:

>>> :{
instance Unbox Object where
    sizeOf _ = 16
    peekByteIndex i arr = do
        x0 <- peekByteIndex i arr
        x1 <- peekByteIndex (i + 8) arr
        return $ Object x0 x1
    pokeByteIndex i arr (Object x0 x1) = do
        pokeByteIndex i arr x0
        pokeByteIndex (i + 8) arr x1
:}

Minimal complete definition

Nothing

Methods

sizeOf :: Proxy a -> Int Source #

Get the size. Size cannot be zero.

default sizeOf :: SizeOfRep (Rep a) => Proxy a -> Int Source #

peekByteIndex :: Int -> MutableByteArray -> IO a Source #

Read an element of type "a" from a MutableByteArray given the byte index.

IMPORTANT: The implementation of this interface may not check the bounds of the array, the caller must not assume that.

default peekByteIndex :: (Generic a, PeekRep (Rep a)) => Int -> MutableByteArray -> IO a Source #

pokeByteIndex :: Int -> MutableByteArray -> a -> IO () Source #

Write an element of type "a" to a MutableByteArray given the byte index.

IMPORTANT: The implementation of this interface may not check the bounds of the array, the caller must not assume that.

default pokeByteIndex :: (Generic a, PokeRep (Rep a)) => Int -> MutableByteArray -> a -> IO () Source #

Instances

Instances details
Unbox IntPtr Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox WordPtr Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Fingerprint Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int16 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int32 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int64 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int8 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox IoSubSystem Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word16 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word32 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word64 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word8 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox MicroSecond64 Source # 
Instance details

Defined in Streamly.Internal.Data.Time.Units

Unbox MilliSecond64 Source # 
Instance details

Defined in Streamly.Internal.Data.Time.Units

Unbox NanoSecond64 Source # 
Instance details

Defined in Streamly.Internal.Data.Time.Units

Unbox () Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Bool Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Char Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Double Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Float Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Complex a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Identity a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Down a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox (FunPtr a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox (Ptr a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Ratio a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox (StablePtr a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Const a b) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Deprecated

read :: (Monad m, Unbox a) => Unfold m (Array a) a Source #

Deprecated: Please use reader instead

Same as reader

readRev :: (Monad m, Unbox a) => Unfold m (Array a) a Source #

Deprecated: Please use readerRev instead

Same as readerRev