monad-stlike-io-0.2.2: ST-like monad capturing variables to regions and supporting IO.

Control.Monad.STLike.IO

Contents

Synopsis

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.

Instances

runRegion :: (NotShared ty, RegionMonad m region s) => Regioned s ty -> STLike m region 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.

unfoldRegion :: Foldable t => Regioned s (t a) -> [Regioned s a]Source

Utilities

class STLikeImpl m => RegionMonad m region s Source

Instances

(STLikeImpl m, TypeCast reg (:< any rest), RegionMonad m rest s) => RegionMonad m reg s 
STLikeImpl m => RegionMonad m s s 

data a :< b Source

withRIORSource

Arguments

:: IOS o resource

Open the resource

-> (resource -> IOS o ())

Close it.

-> (forall s. Regioned (s :< o) resource -> IOS (s :< o) result)

Compute with it.

-> IOS o result 

Use a resource with IOS. Like bracket.

rbsFromPtr :: Ptr a -> Int -> IOS s (Regioned s ByteString)Source

Create a ByteString representing the pointer and length. No copying done, O(1).

rbsToBS :: RegionMonad m s reg => Regioned s ByteString -> STLike m reg 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 :: (RegionMonad m s reg, Ord key) => Regioned s key -> Map key value -> STLike m reg (Maybe value)Source

Lookup inside a Map with a regioned ByteString.