Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Internal module for Scoped
, ScopedResource
& co.
Only import this if you need to wrap an otherwise some still interface around resources
Synopsis
- newtype Scoped s m a = UnsafeMkScoped {
- unsafeRunScoped :: forall b. (a -> m b) -> m b
- newtype ScopedResource s a = UnsafeMkScopedResource {}
- scoped :: forall m a. Applicative m => (forall s. Scoped s m a) -> m a
- registerHandler :: MonadUnliftIO m => m a -> Scoped s m ()
- bracketScoped :: MonadUnliftIO m => m a -> (a -> m b) -> Scoped s m (ScopedResource s a)
definitions of Scoped
and ScopedResource
and functions to work with them
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.
UnsafeMkScoped | |
|
Instances
MonadTrans (Scoped s :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Control.Monad.Scoped.Internal | |
MonadFail m => MonadFail (Scoped s m) Source # | |
Defined in Control.Monad.Scoped.Internal | |
MonadIO m => MonadIO (Scoped s m) Source # | You can perform |
Defined in Control.Monad.Scoped.Internal | |
Alternative 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 => MonadPlus (Scoped s m) Source # | |
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 # |
:: forall m a. Applicative m | |
=> (forall s. Scoped s m a) | the scoped computation to be run |
-> m a |
:: MonadUnliftIO m | |
=> m a | the handler to be registered |
-> Scoped s m () |
Helpers to create your own Scoped
wrappers around resources
:: 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 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