storablevector-0.2.9.1: Fast, packed, strict storable arrays with a list interface like ByteString

LicenseBSD-style
Maintainerhaskell@henning-thielemann.de
Stabilityexperimental
Portabilityportable, requires ffi
Safe HaskellNone
LanguageHaskell98

Data.StorableVector.ST.Strict

Description

Tested with : GHC 6.4.1

Interface for access to a mutable StorableVector.

Synopsis

Documentation

data Vector s a Source

new :: Storable e => Int -> e -> ST s (Vector s e) Source

new_ :: Storable e => Int -> ST s (Vector s e) Source

read :: Storable e => Vector s e -> Int -> ST s e Source

Control.Monad.ST.runST (do arr <- new_ 10; Monad.zipWithM_ (write arr) [9,8..0] ['a'..]; read arr 3)

write :: Storable e => Vector s e -> Int -> e -> ST s () Source

VS.unpack $ runSTVector (do arr <- new_ 10; Monad.zipWithM_ (write arr) [9,8..0] ['a'..]; return arr)

modify :: Storable e => Vector s e -> Int -> (e -> e) -> ST s () Source

VS.unpack $ runSTVector (do arr <- new 10 'a'; Monad.mapM_ (\n -> modify arr (mod n 8) succ) [0..10]; return arr)

maybeRead :: Storable e => Vector s e -> Int -> ST s (Maybe e) Source

Returns Just e, when the element e could be read and Nothing if the index was out of range. This way you can avoid duplicate index checks that may be needed when using read.

Control.Monad.ST.runST (do arr <- new_ 10; Monad.zipWithM_ (write arr) [9,8..0] ['a'..]; read arr 3)

In future maybeRead will replace read.

maybeWrite :: Storable e => Vector s e -> Int -> e -> ST s Bool Source

Returns True if the element could be written and False if the index was out of range.

runSTVector (do arr <- new_ 10; foldr (\c go i -> maybeWrite arr i c >>= \cont -> if cont then go (succ i) else return arr) (error "unreachable") ['a'..] 0)

In future maybeWrite will replace write.

maybeModify :: Storable e => Vector s e -> Int -> (e -> e) -> ST s Bool Source

Similar to maybeWrite.

In future maybeModify will replace modify.

unsafeRead :: Storable e => Vector s e -> Int -> ST s e Source

unsafeWrite :: Storable e => Vector s e -> Int -> e -> ST s () Source

unsafeModify :: Storable e => Vector s e -> Int -> (e -> e) -> ST s () Source

freeze :: Storable e => Vector s e -> ST s (Vector e) Source

unsafeFreeze :: Storable e => Vector s e -> ST s (Vector e) Source

This is like freeze but it does not copy the vector. You must make sure that you never write again to the array. It is best to use unsafeFreeze only at the end of a block, that is run by runST.

thaw :: Storable e => Vector e -> ST s (Vector s e) Source

runSTVector :: Storable e => (forall s. ST s (Vector s e)) -> Vector e Source

mapST :: (Storable a, Storable b) => (a -> ST s b) -> Vector a -> ST s (Vector b) Source

:module + Data.STRef
VS.unpack $ Control.Monad.ST.runST (do ref <- newSTRef 'a'; mapST (\ _n -> do c <- readSTRef ref; modifySTRef ref succ; return c) (VS.pack [1,2,3,4::Data.Int.Int16]))

mapSTLazy :: (Storable a, Storable b) => (a -> ST s b) -> Vector a -> ST s (Vector b) Source

*Data.StorableVector.ST.Strict Data.STRef> VL.unpack $ Control.Monad.ST.runST (do ref <- newSTRef 'a'; mapSTLazy (\ _n -> do c <- readSTRef ref; modifySTRef ref succ; return c) (VL.pack VL.defaultChunkSize [1,2,3,4::Data.Int.Int16]))
"abcd"

The following should not work on infinite streams, since we are in ST with strict >>=. But it works. Why?

*Data.StorableVector.ST.Strict Data.STRef> VL.unpack $ Control.Monad.ST.runST (do ref <- newSTRef 'a'; mapSTLazy (\ _n -> do c <- readSTRef ref; modifySTRef ref succ; return c) (VL.pack VL.defaultChunkSize [0::Data.Int.Int16 ..]))
"Interrupted.