scoped-codensity-0.2.0.0: CPS resource allocation but as a Monad and completely safe
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Scoped

Description

The Scoped monad to safely allocate and deallocate resources.

Since: 0.1.0.0

Synopsis

Scoped computations and ScopedResources

data Scoped (s :: [Type]) (m :: k -> TYPE rep) 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.

Scoped also works for wrapping unboxed and unlifted monad transformers.

Since: 0.1.0.0

Instances

Instances details
Monad m => Scoping (s ': ss) (m :: Type -> Type) (Scoped (s ': ss) m) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Methods

scoped :: (forall s0. Scoped (s0 ': (s ': ss)) m a) -> Scoped (s ': ss) m a Source #

MonadTrans (Scoped s :: (Type -> Type) -> Type -> Type) Source #

You can use all the actions you can use in the underlying monad m also in the Scoped monad by lifting into it.

Since: 0.1.0.0

Instance details

Defined in Control.Monad.Scoped.Internal

Methods

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

(MonadIO m', m' ~~ m) => MonadIO (Scoped s m) Source #

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

Since: 0.1.0.0

Instance details

Defined in Control.Monad.Scoped.Internal

Methods

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

(Alternative m', m' ~~ m) => Alternative (Scoped s m) Source #

Since: 0.1.0.0

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 #

Since: 0.1.0.0

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 #

Since: 0.1.0.0

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 #

Since: 0.1.0.0

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', m' ~~ m) => MonadPlus (Scoped s m) Source #

Since: 0.1.0.0

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 #

(MonadFail m', m' ~~ m) => MonadFail (Scoped s m) Source #

You can fail in a Scoped block

Since: 0.1.0.0

Instance details

Defined in Control.Monad.Scoped.Internal

Methods

fail :: String -> 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.

Since: 0.1.0.0

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 :: Scoping ss m n => (forall s. Scoped (s ': ss) m a) -> n a Source #

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

Since: 0.1.0.0

registerHandler Source #

Arguments

:: forall m a (ss :: [Type]). MonadUnliftIO m 
=> m a

the handler to be registered

-> Scoped ss 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

Mind that this uses finally under the hood and thus does not mask the handler with an uninterruptible mask

Since: 0.1.0.0

class s :< (ss :: [Type]) Source #

when using a resource, all that matters is that the resource can only be used in the scope that it was created in or any scope that is farther in than that scope

This constraint has to be put to connect the resource and the scope that it was created in

Since: 0.1.0.0

Instances

Instances details
s :< (s ': (s'' ': ss)) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

s :< '[s] Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

s :< (s'' ': ss) => s :< (s' ': (s'' ': ss)) Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Safely work with Ptrs

type Ptr s a = ScopedResource s (Ptr a) Source #

A Ptr that is associated to a scope

Since: 0.1.0.0

foreignPtr :: forall (m :: Type -> Type) a s (ss :: [Type]). MonadUnliftIO m => ForeignPtr a -> Scoped (s ': ss) m (Ptr s a) Source #

this is a wrapper around withForeignPtr to allow for safe usage of this function in a scope

Since: 0.1.0.2

wrapScoped :: forall m s (ss :: [Type]) a r. (Monad m, s :< ss) => (Ptr a -> m r) -> Ptr s a -> Scoped ss m r Source #

takes a function that does something with a Ptr and makes it safe

Since: 0.1.0.2

newPtr :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadUnliftIO m) => a -> Scoped (s ': ss) m (Ptr s a) Source #

Acquire mutable memory for the duration of a scope. The value is automatically dropped at the end of the scope.

Since: 0.2.0.0

setPtr :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadIO m, s :< ss) => Ptr s a -> a -> Scoped ss m () Source #

write a value to a pointer

Since: 0.2.0.0

getPtr :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadIO m, s :< ss) => Ptr s a -> Scoped ss m a Source #

read a value from a pointer

Since: 0.2.0.0

Safely work with Asyncs

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

Just like Async but bound to a Scoped block

Since: 0.1.0.0

async :: forall m a s (ss :: [Type]). MonadUnliftIO m => m a -> Scoped (s ': ss) m (ScopedAsync s a) Source #

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

Since: 0.1.0.0

asyncBound :: forall m a s (ss :: [Type]). MonadUnliftIO m => m a -> Scoped (s ': ss) m (ScopedAsync s a) Source #

Like async but uses forkOS internally

Since: 0.1.0.0

wait :: forall (m :: Type -> Type) s (ss :: [Type]) a. (MonadIO m, s :< ss) => ScopedAsync s a -> Scoped ss m a Source #

Wait for the ScopedAsync to finish immediately

Since: 0.1.0.0

waitCatch :: forall (m :: Type -> Type) s (ss :: [Type]) a. (MonadIO m, s :< ss) => ScopedAsync s a -> Scoped ss m (Either SomeException a) Source #

Like wait but return either Left SomeException or Right a

Since: 0.1.0.0

waitScoped :: forall (m :: Type -> Type) s (ss :: [Type]) a. (MonadUnliftIO m, s :< ss) => ScopedAsync s a -> Scoped ss m () Source #

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

Since: 0.1.0.0

waitCatchScoped :: forall (m :: Type -> Type) s (ss :: [Type]) a. (MonadUnliftIO m, s :< ss) => ScopedAsync s a -> Scoped ss m () Source #

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

Since: 0.1.0.0

Safely work with Handles

type ScopedHandle s = ScopedResource s Handle Source #

Just like Handle but bound to a Scoped block

Since: 0.1.0.0

file :: forall (m :: Type -> Type) s (ss :: [Type]). MonadUnliftIO m => FilePath -> IOMode -> Scoped (s ': ss) m (ScopedHandle s) Source #

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

Since: 0.1.0.0

data IOMode #

Instances

Instances details
Enum IOMode

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Ix IOMode

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Read IOMode

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Show IOMode

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Eq IOMode

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Methods

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

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

Ord IOMode

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

hPutStrLn :: forall (m :: Type -> Type) s (ss :: [Type]). (MonadIO m, s :< ss) => ScopedHandle s -> Text -> Scoped ss m () Source #

Like hPutStrLn but for ScopedHandle

Since: 0.1.0.0

hPutStr :: forall (m :: Type -> Type) s (ss :: [Type]). (MonadIO m, s :< ss) => ScopedHandle s -> Text -> Scoped ss m () Source #

Like hPutStr but for ScopedHandle

Since: 0.1.0.0

hGetLine :: forall (m :: Type -> Type) s (ss :: [Type]). (MonadIO m, s :< ss) => ScopedHandle s -> Scoped ss m Text Source #

Like hGetLine but for ScopedHandle

Since: 0.1.0.0

hGetContents :: forall (m :: Type -> Type) s (ss :: [Type]). (MonadIO m, s :< ss) => ScopedHandle s -> Scoped ss m Text Source #

Like hGetContents but for ScopedHandle

Since: 0.1.0.0

Safely work with tempfiles

tempFile :: forall (m :: Type -> Type) s (ss :: [Type]). MonadUnliftIO m => FilePath -> String -> Scoped (s ': ss) m (FilePath, ScopedHandle s) Source #

Like withTempFile but for Scoped

Since: 0.1.0.0

systemTempFile :: forall (m :: Type -> Type) s (ss :: [Type]). MonadUnliftIO m => String -> Scoped (s ': ss) m (FilePath, ScopedHandle s) Source #

Like withSystemTempFile but for Scoped

Since: 0.1.0.0