bluefin-internal-0.3.4.0: The Bluefin effect system, internals
Safe HaskellNone
LanguageHaskell2010

Bluefin.Internal.Exception

Synopsis

Documentation

data HandledKey ret Source #

Constructors

MkHandledKey !(Exception ex) (ex -> ret) 

Instances

Instances details
Functor HandledKey Source # 
Instance details

Defined in Bluefin.Internal.Exception

Methods

fmap :: (a -> b) -> HandledKey a -> HandledKey b #

(<$) :: a -> HandledKey b -> HandledKey a #

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

Instances details
(Handle h, e :> es) => OneWayCoercible (MakeExceptions r a h e :: Type) (MakeExceptions r a h es :: Type) Source # 
Instance details

Defined in Bluefin.Internal.Exception

Handle h => Handle (MakeExceptions r a h) Source # 
Instance details

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

Instances details
(Handle h, e :> es) => OneWayCoercible (HandlerUnwrapped r a h e :: Type) (HandlerUnwrapped r a h es :: Type) Source # 
Instance details

Defined in Bluefin.Internal.Exception

Handle h => Handle (HandlerUnwrapped r a h) Source # 
Instance details

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 #

pureMakeExceptions 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 #

apMakeExceptions 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

͘

Analogous to ap and <*>

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 #

fmapMakeExceptions 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

͘

Analogous to fmap and <$>

catchWithResource Source #

Arguments

:: forall ex r a (es :: Effects). (r -> ex -> Eff es a) 
-> MakeExceptions r a (Exception ex) es

͘

generalBracket Source #

Arguments

:: forall r b h a (es :: Effects). Handle h 
=> Eff es r

Acquire the resource

-> MakeExceptions r a h es

Construct the handle h of exceptions to pass into the body, and determine what to run when the body terminates via one of those exceptions.

-> (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

  • acquire :: !(Eff es r)

    Acquire the resource

    This is run inside an asynchronous exception mask.

  • normalRelease :: !(r -> bodyRes -> Eff es a)

    Release the resource after normal exit

    This is run inside an asynchronous exception mask.

  • unknownExceptionRelease :: !(r -> Eff es ())

    Release the resource after exit due to an unknown exception.

    The exception will continue to be raised after this.

    This is run inside an asynchronous exception mask.

  • body :: !(r -> Eff es bodyRes)

    Use the resource

Instances

Instances details
e :> es => OneWayCoercible (BracketBase bodyRes r a e :: Type) (BracketBase bodyRes r a es :: Type) Source # 
Instance details

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 # 
Instance details

Defined in Bluefin.Internal.Exception

Associated Types

type Rep (BracketBase bodyRes r a es) 
Instance details

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)))))

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 # 
Instance details

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 #