scoped-codensity-0.1.0.0: CPS resource allocation but as a Monad and completely safe
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Scoped

Description

The Scoped monad to safely allocate and deallocate resources.

Synopsis

Scoped computations and ScopedResources

data Scoped s m a Source #

The Scoped monad that provides the possibility to safely scope the allocation of a resource

It is used to abstract over all of the CPS style withSomething functions, like withFile

Be sure to properly mask handlers if you are using UnsafeMkScoped. Use safe helper functions like registerHandler or bracketScoped where possible.

Instances

Instances details
MonadTrans (Scoped s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Methods

lift :: Monad m => m a -> Scoped s m a #

MonadFail m => MonadFail (Scoped s m) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Methods

fail :: String -> Scoped s m a #

MonadIO m => MonadIO (Scoped s m) Source #

You can perform IO in a scoped block, but it does not inherit its safety guarantees

Instance details

Defined in Control.Monad.Scoped.Internal

Methods

liftIO :: IO a -> Scoped s m a #

Alternative m => Alternative (Scoped s m) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Methods

empty :: Scoped s m a #

(<|>) :: Scoped s m a -> Scoped s m a -> Scoped s m a #

some :: Scoped s m a -> Scoped s m [a] #

many :: Scoped s m a -> Scoped s m [a] #

Applicative (Scoped s m) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Methods

pure :: a -> Scoped s m a #

(<*>) :: Scoped s m (a -> b) -> Scoped s m a -> Scoped s m b #

liftA2 :: (a -> b -> c) -> Scoped s m a -> Scoped s m b -> Scoped s m c #

(*>) :: Scoped s m a -> Scoped s m b -> Scoped s m b #

(<*) :: Scoped s m a -> Scoped s m b -> Scoped s m a #

Functor (Scoped s m) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Methods

fmap :: (a -> b) -> Scoped s m a -> Scoped s m b #

(<$) :: a -> Scoped s m b -> Scoped s m a #

Monad (Scoped s m) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Methods

(>>=) :: Scoped s m a -> (a -> Scoped s m b) -> Scoped s m b #

(>>) :: Scoped s m a -> Scoped s m b -> Scoped s m b #

return :: a -> Scoped s m a #

Alternative m => MonadPlus (Scoped s m) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Methods

mzero :: Scoped s m a #

mplus :: Scoped s m a -> Scoped s m a -> Scoped s m a #

data ScopedResource s a Source #

A scoped resource with token s belonging to a Scoped block with the same token.

If you are creating a ScopedResource, make sure the resource is deallocated properly when the Scoped block is exited.

Instances

Instances details
Show a => Show (ScopedResource s a) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Eq a => Eq (ScopedResource s a) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Ord a => Ord (ScopedResource s a) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Safely work with scopes

scoped Source #

Arguments

:: forall m a. Applicative m 
=> (forall s. Scoped s m a)

the scoped computation to be run

-> m a 

Run a Scoped block safely, making sure that none of the safely allocated resources can escape it, using the same trick as ST

All of the allocated resources will live until the end of the block is reached

registerHandler Source #

Arguments

:: MonadUnliftIO m 
=> m a

the handler to be registered

-> Scoped s m () 

Run a handler masked for async exception when the Scoped block ends

You can register a handler wherever in your Scoped block you want, but it will nonetheless be run in reverse order that the handlers have been registered, after the scoped block's actions have been finished

Safely work with Asyncs

type ScopedAsync s a = ScopedResource s (Async a) Source #

Just like Async but bound to a Scoped block

async :: MonadUnliftIO m => m a -> Scoped s m (ScopedAsync s a) Source #

Run an IO action asynchronously in a Scoped block. When the Scoped block ends, the Async is cancelled

asyncBound :: MonadUnliftIO m => m a -> Scoped s m (ScopedAsync s a) Source #

Like async but uses forkOS internally

wait :: MonadIO m => ScopedAsync s a -> Scoped s m a Source #

Wait for the ScopedAsync to finish immediately

waitCatch :: MonadIO m => ScopedAsync s a -> Scoped s m (Either SomeException a) Source #

Like wait but return either Left SomeException or Right a

waitScoped :: MonadUnliftIO m => ScopedAsync s a -> Scoped s m () Source #

Like wait but wait as part of the handlers of the Scoped block

waitCatchScoped :: MonadUnliftIO m => ScopedAsync s a -> Scoped s m () Source #

Like waitCatch but wait as part of the handlers of the Scoped block

Safely work with Handles

type ScopedHandle s = ScopedResource s Handle Source #

Just like Handle but bound to a Scoped block

file :: MonadUnliftIO m => FilePath -> IOMode -> Scoped s m (ScopedHandle s) Source #

Given a FilePath, safely allocates and deallocates a ScopedHandle in a Scoped block

data IOMode #

Instances

Instances details
Enum IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Ix IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Read IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Show IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Eq IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Methods

(==) :: IOMode -> IOMode -> Bool #

(/=) :: IOMode -> IOMode -> Bool #

Ord IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

hPutStr :: MonadIO m => ScopedHandle s -> Text -> Scoped s m () Source #

Like hPutStr but for ScopedHandle

Safely work with tempfiles