| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Bluefin.Exception.GeneralBracket
Contents
Synopsis
- generalBracket :: forall r b h a (es :: Effects). Handle h => Eff es r -> MakeExceptions r a h es -> (r -> b -> Eff es a) -> (r -> Eff es ()) -> (forall (e :: Effects). h e -> r -> Eff (e :& es) b) -> Eff es a
- data MakeExceptions r a (h :: Effects -> Type) (es :: Effects)
- catchWithResource :: forall ex r a (es :: Effects). (r -> ex -> Eff es a) -> MakeExceptions r a (Exception ex) es
- pureMakeExceptions :: forall h (e :: Effects) r a. h e -> MakeExceptions r a h e
- apMakeExceptions :: forall (h1 :: Effects -> Type) (h2 :: Effects -> Type) r a (e :: Effects). (Handle h1, Handle h2) => MakeExceptions r a (h1 :~> h2) e -> MakeExceptions r a h1 e -> MakeExceptions r a h2 e
- fmapMakeExceptions :: forall (h1 :: Effects -> Type) (h2 :: Effects -> Type) (e :: Effects) r a. (Handle h1, Handle h2) => (h1 :~> h2) e -> MakeExceptions r a h1 e -> MakeExceptions r a h2 e
- data ((h1 :: Effects -> Type) :~> (h2 :: Effects -> Type)) (es :: Effects)
- abstract :: forall h2 h1 (es :: Effects). Handle h2 => (forall (e :: Effects). h1 e -> h2 (e :& es)) -> (h1 :~> h2) es
Effectful functions
Arguments
| :: forall r b h a (es :: Effects). Handle h | |
| => Eff es r | Acquire the resource |
| -> MakeExceptions r a h es | Construct the handle |
| -> (r -> b -> Eff es a) | To run on normal termination |
| -> (r -> Eff es ()) | To run on unknown exception |
| -> (forall (e :: Effects). h e -> r -> Eff (e :& es) b) | Body |
| -> Eff es a |
A generalization of bracket that enables distinguishing
exceptional from normal exit.
r- The type of the resource
b- The result type of the body
a- The type of the overall result
h- The handle of exceptions available in the body
Handle
data MakeExceptions r a (h :: Effects -> Type) (es :: Effects) #
To create a MakeExceptions use catchWithResource and the
Applicative-like functions that produce and combine them.
Instances
| (Handle h, e :> es) => OneWayCoercible (MakeExceptions r a h e :: Type) (MakeExceptions r a h es :: Type) | |
Defined in Bluefin.Internal.Exception Methods oneWayCoercibleImpl :: OneWayCoercibleD (MakeExceptions r a h e) (MakeExceptions r a h es) # | |
| Handle h => Handle (MakeExceptions r a h) | |
Defined in Bluefin.Internal.Exception Methods handleImpl :: HandleD (MakeExceptions r a h) # mapHandle :: forall (e :: Effects) (es :: Effects). e :> es => MakeExceptions r a h e -> MakeExceptions r a h es # | |
Arguments
| :: forall ex r a (es :: Effects). (r -> ex -> Eff es a) | |
| -> MakeExceptions r a (Exception ex) es | ͘ |
Arguments
| :: forall h (e :: Effects) r a. h e | |
| -> MakeExceptions r a h e | ͘ |
Analogous to pure
Arguments
| :: forall (h1 :: Effects -> Type) (h2 :: Effects -> Type) r a (e :: Effects). (Handle h1, Handle h2) | |
| => MakeExceptions r a (h1 :~> h2) e | |
| -> MakeExceptions r a h1 e | |
| -> MakeExceptions r a h2 e | ͘ |
Arguments
| :: forall (h1 :: Effects -> Type) (h2 :: Effects -> Type) (e :: Effects) r a. (Handle h1, Handle h2) | |
| => (h1 :~> h2) e | |
| -> MakeExceptions r a h1 e | |
| -> MakeExceptions r a h2 e | ͘ |
:~>
data ((h1 :: Effects -> Type) :~> (h2 :: Effects -> Type)) (es :: Effects) infixr 9 #
Instances
| (Handle h1, Handle h2) => OneWayCoercible ((h1 :~> h2) e :: Type) ((h1 :~> h2) es :: Type) | |
Defined in Bluefin.Internal.CloneableHandle Methods oneWayCoercibleImpl :: OneWayCoercibleD ((h1 :~> h2) e) ((h1 :~> h2) es) # | |
| (Handle h1, Handle h2) => Handle (h1 :~> h2) | |