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

Control.Monad.Scoped.Internal

Description

Internal module for Scoped, ScopedResource & co.

Only import this if you need to wrap an otherwise unsafe interface around resources

Synopsis

definitions of Scoped and ScopedResource and functions to work with them

newtype 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.

Constructors

UnsafeMkScoped 

Fields

  • unsafeRunScoped :: forall (b :: k). (a -> m b) -> m b

    Unsafely runs a scoped block. Use scoped instead, otherwise resources might escape

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.

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

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 # 
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', m' ~~ 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 #

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

You can fail in a Scoped block

Instance details

Defined in Control.Monad.Scoped.Internal

Methods

fail :: String -> Scoped s m a #

newtype 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.

Constructors

UnsafeMkScopedResource 

Fields

  • unsafeUnwrapScopedResource :: a

    Unsafely runs a scoped resource. It forgets the scope of the resource and may now be escaped incorrectly

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

class Scoping (ss :: [Type]) (m :: k -> TYPE r) (n :: Type -> Type) | n -> m ss where Source #

the Scoping class is there to give overloading to blocks, s.t. we don't have to run different functions depending on whether we run a final block or not.

This type class is internal since there should not be any more instances and since it is expected that the contraint on scoped is immediately discharged

Methods

scoped :: (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

Instances

Instances details
(Applicative m, m ~ n, l ~ ('[] :: [Type])) => Scoping l (m :: Type -> Type) n Source # 
Instance details

Defined in Control.Monad.Scoped.Internal

Methods

scoped :: (forall s. Scoped (s ': l) m a) -> n a Source #

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 #

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

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

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

Helpers to create your own Scoped wrappers around resources

bracketScoped Source #

Arguments

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

an action that allocates a resource of type a

-> (a -> m b)

an action that deallocates a resource of type a

-> Scoped (s ': ss) m (ScopedResource s a) 

A wrapper around bracket to allocate a resource safely in a Scoped block

It returns a ScopedResource that belongs to the Scoped block it was allocated in