License | BSD-style |
---|---|
Maintainer | haskell@henning-thielemann.de |
Stability | experimental |
Portability | portable, requires ffi |
Safe Haskell | None |
Language | Haskell98 |
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 ()
- 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 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)
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.Lazy> VL.unpack $ Control.Monad.ST.Lazy.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.