| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Bluefin.Internal.Exception
Synopsis
- data HandledKey ret = MkHandledKey !(Exception ex) (ex -> ret)
- checkHandledKey :: HandledKey ret -> InFlight -> Maybe ret
- runBodyWithHandlers :: forall r (es :: Effects) a b. ([HandledKey (r -> Eff es a)], BracketBase b r a es) -> Eff es a
- newtype MakeExceptions r a (h :: Effects -> Type) (es :: Effects) = MkMakeExceptions (Eff es (HandlerUnwrapped r a h es))
- data HandlerUnwrapped r a (h :: Effects -> Type) (es :: Effects) = MkHandlerUnwrapped [HandledKey (r -> Eff es a)] (forall b. (forall (e :: Effects). h e -> Eff (e :& es) b) -> Eff es b)
- pureHandlerUnwrapped :: forall h (e :: Effects) r a. h e -> HandlerUnwrapped r a h e
- pureMakeExceptions :: forall h (e :: Effects) r a. h e -> MakeExceptions r a h e
- apHandlerUnwrapped :: forall (h1 :: Effects -> Type) (h2 :: Effects -> Type) r a (e :: Effects). (Handle h1, Handle h2) => HandlerUnwrapped r a (h1 :~> h2) e -> HandlerUnwrapped r a h1 e -> HandlerUnwrapped r a h2 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
- fmapHandlerUnwrapped :: forall (h1 :: Effects -> Type) (h2 :: Effects -> Type) (e :: Effects) r a. (Handle h1, Handle h2) => (h1 :~> h2) e -> HandlerUnwrapped r a h1 e -> HandlerUnwrapped 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
- catchWithResource :: forall ex r a (es :: Effects). (r -> ex -> Eff es a) -> MakeExceptions r a (Exception ex) es
- 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 BracketBase bodyRes r a (es :: Effects) = MkBracketBase {
- acquire :: !(Eff es r)
- normalRelease :: !(r -> bodyRes -> Eff es a)
- unknownExceptionRelease :: !(r -> Eff es ())
- body :: !(r -> Eff es bodyRes)
- useImplBracketBase :: forall (e :: Effects) (es :: Effects) b r a. e :> es => BracketBase b r a e -> BracketBase b r a es
Documentation
data HandledKey ret Source #
Constructors
| MkHandledKey !(Exception ex) (ex -> ret) |
Instances
| Functor HandledKey Source # | |
Defined in Bluefin.Internal.Exception Methods fmap :: (a -> b) -> HandledKey a -> HandledKey b # (<$) :: a -> HandledKey b -> HandledKey a # | |
checkHandledKey :: HandledKey ret -> InFlight -> Maybe ret Source #
runBodyWithHandlers :: forall r (es :: Effects) a b. ([HandledKey (r -> Eff es a)], BracketBase b r a es) -> Eff es a Source #
newtype MakeExceptions r a (h :: Effects -> Type) (es :: Effects) Source #
To create a MakeExceptions use catchWithResource and the
Applicative-like functions that produce and combine them.
Constructors
| MkMakeExceptions (Eff es (HandlerUnwrapped r a h es)) |
Instances
| (Handle h, e :> es) => OneWayCoercible (MakeExceptions r a h e :: Type) (MakeExceptions r a h es :: Type) Source # | |
Defined in Bluefin.Internal.Exception Methods oneWayCoercibleImpl :: OneWayCoercibleD (MakeExceptions r a h e) (MakeExceptions r a h es) Source # | |
| Handle h => Handle (MakeExceptions r a h) Source # | |
Defined in Bluefin.Internal.Exception Methods handleImpl :: HandleD (MakeExceptions r a h) Source # mapHandle :: forall (e :: Effects) (es :: Effects). e :> es => MakeExceptions r a h e -> MakeExceptions r a h es Source # | |
data HandlerUnwrapped r a (h :: Effects -> Type) (es :: Effects) Source #
Constructors
| MkHandlerUnwrapped [HandledKey (r -> Eff es a)] (forall b. (forall (e :: Effects). h e -> Eff (e :& es) b) -> Eff es b) |
Instances
| (Handle h, e :> es) => OneWayCoercible (HandlerUnwrapped r a h e :: Type) (HandlerUnwrapped r a h es :: Type) Source # | |
Defined in Bluefin.Internal.Exception Methods oneWayCoercibleImpl :: OneWayCoercibleD (HandlerUnwrapped r a h e) (HandlerUnwrapped r a h es) Source # | |
| Handle h => Handle (HandlerUnwrapped r a h) Source # | |
Defined in Bluefin.Internal.Exception Methods handleImpl :: HandleD (HandlerUnwrapped r a h) Source # mapHandle :: forall (e :: Effects) (es :: Effects). e :> es => HandlerUnwrapped r a h e -> HandlerUnwrapped r a h es Source # | |
pureHandlerUnwrapped :: forall h (e :: Effects) r a. h e -> HandlerUnwrapped r a h e Source #
Arguments
| :: forall h (e :: Effects) r a. h e | |
| -> MakeExceptions r a h e | ͘ |
Analogous to pure
apHandlerUnwrapped :: forall (h1 :: Effects -> Type) (h2 :: Effects -> Type) r a (e :: Effects). (Handle h1, Handle h2) => HandlerUnwrapped r a (h1 :~> h2) e -> HandlerUnwrapped r a h1 e -> HandlerUnwrapped r a h2 e Source #
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 | ͘ |
fmapHandlerUnwrapped :: forall (h1 :: Effects -> Type) (h2 :: Effects -> Type) (e :: Effects) r a. (Handle h1, Handle h2) => (h1 :~> h2) e -> HandlerUnwrapped r a h1 e -> HandlerUnwrapped r a h2 e Source #
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 | ͘ |
Arguments
| :: forall ex r a (es :: Effects). (r -> ex -> Eff es a) | |
| -> MakeExceptions r a (Exception ex) es | ͘ |
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
data BracketBase bodyRes r a (es :: Effects) Source #
Constructors
| MkBracketBase | |
Fields
| |
Instances
| e :> es => OneWayCoercible (BracketBase bodyRes r a e :: Type) (BracketBase bodyRes r a es :: Type) Source # | |||||
Defined in Bluefin.Internal.Exception Methods oneWayCoercibleImpl :: OneWayCoercibleD (BracketBase bodyRes r a e) (BracketBase bodyRes r a es) Source # | |||||
| Generic (BracketBase bodyRes r a es) Source # | |||||
Defined in Bluefin.Internal.Exception Associated Types
Methods from :: BracketBase bodyRes r a es -> Rep (BracketBase bodyRes r a es) x # to :: Rep (BracketBase bodyRes r a es) x -> BracketBase bodyRes r a es # | |||||
| type Rep (BracketBase bodyRes r a es) Source # | |||||
Defined in Bluefin.Internal.Exception type Rep (BracketBase bodyRes r a es) = D1 ('MetaData "BracketBase" "Bluefin.Internal.Exception" "bluefin-internal-0.3.4.0-9GrTj2GQiLd7ycEThQMiPM" 'False) (C1 ('MetaCons "MkBracketBase" 'PrefixI 'True) ((S1 ('MetaSel ('Just "acquire") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Eff es r)) :*: S1 ('MetaSel ('Just "normalRelease") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (r -> bodyRes -> Eff es a))) :*: (S1 ('MetaSel ('Just "unknownExceptionRelease") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (r -> Eff es ())) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (r -> Eff es bodyRes))))) | |||||
useImplBracketBase :: forall (e :: Effects) (es :: Effects) b r a. e :> es => BracketBase b r a e -> BracketBase b r a es Source #