Safe Haskell | None |
---|---|
Language | Haskell2010 |
Control.Monad.Scoped
Description
The Scoped
monad to safely allocate and deallocate resources.
Since: 0.1.0.0
Synopsis
- data Scoped (s :: [Type]) (m :: k -> TYPE rep) a
- data ScopedResource s a
- scoped :: Scoping ss m n => (forall s. Scoped (s ': ss) m a) -> n a
- registerHandler :: forall m a (ss :: [Type]). MonadUnliftIO m => m a -> Scoped ss m ()
- class s :< (ss :: [Type])
- type Ptr s a = ScopedResource s (Ptr a)
- foreignPtr :: forall (m :: Type -> Type) a s (ss :: [Type]). MonadUnliftIO m => ForeignPtr a -> Scoped (s ': ss) m (Ptr s a)
- wrapScoped :: forall m s (ss :: [Type]) a r. (Monad m, s :< ss) => (Ptr a -> m r) -> Ptr s a -> Scoped ss m r
- newPtr :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadUnliftIO m) => a -> Scoped (s ': ss) m (Ptr s a)
- setPtr :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadIO m, s :< ss) => Ptr s a -> a -> Scoped ss m ()
- getPtr :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadIO m, s :< ss) => Ptr s a -> Scoped ss m a
- type ScopedAsync s a = ScopedResource s (Async a)
- async :: forall m a s (ss :: [Type]). MonadUnliftIO m => m a -> Scoped (s ': ss) m (ScopedAsync s a)
- asyncBound :: forall m a s (ss :: [Type]). MonadUnliftIO m => m a -> Scoped (s ': ss) m (ScopedAsync s a)
- wait :: forall (m :: Type -> Type) s (ss :: [Type]) a. (MonadIO m, s :< ss) => ScopedAsync s a -> Scoped ss m a
- waitCatch :: forall (m :: Type -> Type) s (ss :: [Type]) a. (MonadIO m, s :< ss) => ScopedAsync s a -> Scoped ss m (Either SomeException a)
- waitScoped :: forall (m :: Type -> Type) s (ss :: [Type]) a. (MonadUnliftIO m, s :< ss) => ScopedAsync s a -> Scoped ss m ()
- waitCatchScoped :: forall (m :: Type -> Type) s (ss :: [Type]) a. (MonadUnliftIO m, s :< ss) => ScopedAsync s a -> Scoped ss m ()
- type ScopedHandle s = ScopedResource s Handle
- file :: forall (m :: Type -> Type) s (ss :: [Type]). MonadUnliftIO m => FilePath -> IOMode -> Scoped (s ': ss) m (ScopedHandle s)
- data IOMode
- hPutStrLn :: forall (m :: Type -> Type) s (ss :: [Type]). (MonadIO m, s :< ss) => ScopedHandle s -> Text -> Scoped ss m ()
- hPutStr :: forall (m :: Type -> Type) s (ss :: [Type]). (MonadIO m, s :< ss) => ScopedHandle s -> Text -> Scoped ss m ()
- hGetLine :: forall (m :: Type -> Type) s (ss :: [Type]). (MonadIO m, s :< ss) => ScopedHandle s -> Scoped ss m Text
- hGetContents :: forall (m :: Type -> Type) s (ss :: [Type]). (MonadIO m, s :< ss) => ScopedHandle s -> Scoped ss m Text
- tempFile :: forall (m :: Type -> Type) s (ss :: [Type]). MonadUnliftIO m => FilePath -> String -> Scoped (s ': ss) m (FilePath, ScopedHandle s)
- systemTempFile :: forall (m :: Type -> Type) s (ss :: [Type]). MonadUnliftIO m => String -> Scoped (s ': ss) m (FilePath, ScopedHandle s)
Scoped
computations and ScopedResource
s
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
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 Since: 0.1.0.0 |
Defined in Control.Monad.Scoped.Internal | |
(MonadIO m', m' ~~ m) => MonadIO (Scoped s m) Source # | You can perform Since: 0.1.0.0 |
Defined in Control.Monad.Scoped.Internal | |
(Alternative m', m' ~~ m) => Alternative (Scoped s m) Source # | Since: 0.1.0.0 |
Applicative (Scoped s m) Source # | Since: 0.1.0.0 |
Defined in Control.Monad.Scoped.Internal | |
Functor (Scoped s m) Source # | Since: 0.1.0.0 |
Monad (Scoped s m) Source # | Since: 0.1.0.0 |
(Alternative m', m' ~~ m) => MonadPlus (Scoped s m) Source # | Since: 0.1.0.0 |
(MonadFail m', m' ~~ m) => MonadFail (Scoped s m) Source # | You can Since: 0.1.0.0 |
Defined in Control.Monad.Scoped.Internal |
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
Show a => Show (ScopedResource s a) Source # | |
Defined in Control.Monad.Scoped.Internal Methods 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 Methods (==) :: 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 Methods 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 # |
Safely work with scopes
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
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 |
Safely work with Ptr
s
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 Async
s
type ScopedAsync s a = ScopedResource s (Async a) Source #
async :: forall m a s (ss :: [Type]). MonadUnliftIO m => m a -> Scoped (s ': ss) m (ScopedAsync s a) Source #
asyncBound :: forall m a s (ss :: [Type]). MonadUnliftIO m => m a -> Scoped (s ': ss) m (ScopedAsync s a) Source #
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
or Left
SomeException
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 #
waitCatchScoped :: forall (m :: Type -> Type) s (ss :: [Type]) a. (MonadUnliftIO m, s :< ss) => ScopedAsync s a -> Scoped ss m () Source #
Safely work with Handle
s
type ScopedHandle s = ScopedResource s Handle Source #
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
See openFile
Constructors
ReadMode | |
WriteMode | |
AppendMode | |
ReadWriteMode |
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