| Portability | portable, requires ffi | 
|---|---|
| Stability | experimental | 
| Maintainer | haskell@henning-thielemann.de | 
| Safe Haskell | None | 
Data.StorableVector.ST.Strict
Description
Tested with : GHC 6.4.1
Interface for access to a mutable StorableVector.
- data Vector s a
- new :: Storable e => Int -> e -> ST s (Vector s e)
- new_ :: Storable e => Int -> ST s (Vector s e)
- read :: Storable e => Vector s e -> Int -> ST s e
- write :: Storable e => Vector s e -> Int -> e -> ST s ()
- modify :: Storable e => Vector s e -> Int -> (e -> e) -> ST s ()
- maybeRead :: Storable e => Vector s e -> Int -> ST s (Maybe e)
- maybeWrite :: Storable e => Vector s e -> Int -> e -> ST s Bool
- maybeModify :: Storable e => Vector s e -> Int -> (e -> e) -> ST s Bool
- unsafeRead :: Storable e => Vector s e -> Int -> ST s e
- unsafeWrite :: Storable e => Vector s e -> Int -> e -> ST s ()
- unsafeModify :: Storable e => Vector s e -> Int -> (e -> e) -> ST s ()
- freeze :: Storable e => Vector s e -> ST s (Vector e)
- unsafeFreeze :: Storable e => Vector s e -> ST s (Vector e)
- thaw :: Storable e => Vector e -> ST s (Vector s e)
- length :: Vector s e -> Int
- runSTVector :: Storable e => (forall s. ST s (Vector s e)) -> Vector e
- mapST :: (Storable a, Storable b) => (a -> ST s b) -> Vector a -> ST s (Vector b)
- mapSTLazy :: (Storable a, Storable b) => (a -> ST s b) -> Vector a -> ST s (Vector b)
Documentation
read :: Storable e => Vector s e -> Int -> ST s eSource
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
maybeWrite :: Storable e => Vector s e -> Int -> e -> ST s BoolSource
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 BoolSource
Similar to maybeWrite.
In future maybeModify will replace modify.
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.
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.