monad-stlike-io-0.1: ST-like monad capturing variables to regions and supporting IO.Source codeContentsIndex
Control.Monad.STLike.IO
Contents
IOS monad
Regioned monad
Utilities
Synopsis
type IOS s t = STLike IO s t
io :: IO t -> IOS s t
runIOS :: (forall s. IOS s t) -> IO t
data Regioned s t
runRegion :: (NotShared ty, STLikeImpl m) => Regioned s ty -> STLike m s ty
region :: t -> Regioned s t
rbsFromPtr :: Ptr a -> Int -> IOS s (Regioned s ByteString)
rbsToBS :: STLikeImpl m => Regioned s ByteString -> STLike m s ByteString
withRbsPtr :: Regioned s ByteString -> (Ptr any -> Int -> IOS s t) -> IOS s t
rbsMapLookup :: (STLikeImpl m, Ord key) => Regioned s key -> Map key value -> STLike m s (Maybe value)
IOS monad
type IOS s t = STLike IO s tSource
Monad for scoped IO computations The underlying monad must be strict here.
io :: IO t -> IOS s tSource
Lift IO computations into IOS. liftIO also works.
runIOS :: (forall s. IOS s t) -> IO tSource
Run an IOS computation in the IO monad.
Regioned monad
data Regioned s t Source
Regioned variables. A regioned variable is safe i.e. no references to it may escape the current IOS.
show/hide Instances
runRegion :: (NotShared ty, STLikeImpl m) => Regioned s ty -> STLike m s tySource
Run a computation on regioned data and return the result in a strict fashion.
region :: t -> Regioned s tSource
Regions a value. Synonym for return.
Utilities
rbsFromPtr :: Ptr a -> Int -> IOS s (Regioned s ByteString)Source
Create a ByteString representing the pointer and length. No copying done, O(1).
rbsToBS :: STLikeImpl m => Regioned s ByteString -> STLike m s ByteStringSource
Create a copy of a regioned ByteString as a normal ByteString. O(n).
withRbsPtr :: Regioned s ByteString -> (Ptr any -> Int -> IOS s t) -> IOS s tSource
Use a regioned ByteString as a pointer. O(1). The pointer points to the region contents, so be cafeful with it.
rbsMapLookup :: (STLikeImpl m, Ord key) => Regioned s key -> Map key value -> STLike m s (Maybe value)Source
Lookup inside a Map with a regioned ByteString.
Produced by Haddock version 2.6.0