Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal module for Scoped
, ScopedResource
& co.
Only import this if you need to wrap an otherwise unsafe interface around resources
Synopsis
- newtype Scoped (s :: [Type]) (m :: k -> TYPE rep) a = UnsafeMkScoped {
- unsafeRunScoped :: forall (b :: k). (a -> m b) -> m b
- newtype ScopedResource s a = UnsafeMkScopedResource {}
- class Scoping (ss :: [Type]) (m :: k -> TYPE r) (n :: Type -> Type) | n -> m ss where
- registerHandler :: forall m a (ss :: [Type]). MonadUnliftIO m => m a -> Scoped ss m ()
- class s :< (ss :: [Type])
- bracketScoped :: forall m a b s (ss :: [Type]). MonadUnliftIO m => m a -> (a -> m b) -> Scoped (s ': ss) m (ScopedResource s a)
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.
UnsafeMkScoped | |
|
Instances
Monad m => Scoping (s ': ss) (m :: Type -> Type) (Scoped (s ': ss) m) Source # | |
MonadTrans (Scoped s :: (Type -> Type) -> Type -> Type) Source # | You can use all the actions you can use in the underlying monad |
Defined in Control.Monad.Scoped.Internal | |
(MonadIO m', m' ~~ m) => MonadIO (Scoped s m) Source # | You can perform |
Defined in Control.Monad.Scoped.Internal | |
(Alternative m', m' ~~ m) => Alternative (Scoped s m) Source # | |
Applicative (Scoped s m) Source # | |
Defined in Control.Monad.Scoped.Internal | |
Functor (Scoped s m) Source # | |
Monad (Scoped s m) Source # | |
(Alternative m', m' ~~ m) => MonadPlus (Scoped s m) Source # | |
(MonadFail m', m' ~~ m) => MonadFail (Scoped s m) Source # | You can |
Defined in Control.Monad.Scoped.Internal |
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.
UnsafeMkScopedResource | |
|
Instances
Show a => Show (ScopedResource s a) Source # | |
Defined in Control.Monad.Scoped.Internal showsPrec :: Int -> ScopedResource s a -> ShowS # show :: ScopedResource s a -> String # showList :: [ScopedResource s a] -> ShowS # | |
Eq a => Eq (ScopedResource s a) Source # | |
Defined in Control.Monad.Scoped.Internal (==) :: ScopedResource s a -> ScopedResource s a -> Bool # (/=) :: ScopedResource s a -> ScopedResource s a -> Bool # | |
Ord a => Ord (ScopedResource s a) Source # | |
Defined in Control.Monad.Scoped.Internal compare :: ScopedResource s a -> ScopedResource s a -> Ordering # (<) :: ScopedResource s a -> ScopedResource s a -> Bool # (<=) :: ScopedResource s a -> ScopedResource s a -> Bool # (>) :: ScopedResource s a -> ScopedResource s a -> Bool # (>=) :: ScopedResource s a -> ScopedResource s a -> Bool # max :: ScopedResource s a -> ScopedResource s a -> ScopedResource s a # min :: ScopedResource s a -> ScopedResource s a -> ScopedResource s a # |
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
:: forall m a (ss :: [Type]). MonadUnliftIO m | |
=> m a | the handler to be registered |
-> Scoped ss m () |
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
s :< (s ': (s'' ': ss)) Source # | |
Defined in Control.Monad.Scoped.Internal | |
s :< '[s] Source # | |
Defined in Control.Monad.Scoped.Internal | |
s :< (s'' ': ss) => s :< (s' ': (s'' ': ss)) Source # | |
Defined in Control.Monad.Scoped.Internal |
Helpers to create your own Scoped
wrappers around resources
:: forall m a b s (ss :: [Type]). MonadUnliftIO m | |
=> m a | an action that allocates a resource of type |
-> (a -> m b) | an action that deallocates a resource of type |
-> 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