bluefin-0.0.15.0: The Bluefin effect system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Bluefin.Exception

Synopsis

Handle

data Exception exn (e :: Effects) #

Handle to an exception of type exn

Instances

Instances details
Handle (Exception s) 
Instance details

Defined in Bluefin.Internal

Methods

mapHandle :: forall (e :: Effects) (es :: Effects). e :> es => Exception s e -> Exception s es #

e :> es => MonadFail (EffReader (Exception String e) es) 
Instance details

Defined in Bluefin.Internal

Methods

fail :: String -> EffReader (Exception String e) es a #

Handlers

try #

Arguments

:: forall exn (es :: Effects) a. (forall (e :: Effects). Exception exn e -> Eff (e :& es) a) 
-> Eff es (Either exn a)

Left if the exception was thrown, Right otherwise

>>> runPureEff $ try $ \e -> do
      throw e 42
      pure "No exception thrown"
Left 42

handle #

Arguments

:: forall exn (es :: Effects) a. (exn -> Eff es a)

If the exception is thrown, apply this handler

-> (forall (e :: Effects). Exception exn e -> Eff (e :& es) a) 
-> Eff es a 

handle, but with the argument order swapped

>>> runPureEff $ handle (pure . show) $ \e -> do
      throw e 42
      pure "No exception thrown"
"42"

catch #

Arguments

:: forall exn (es :: Effects) a. (forall (e :: Effects). Exception exn e -> Eff (e :& es) a) 
-> (exn -> Eff es a)

If the exception is thrown, apply this handler

-> Eff es a 

Effectful operations

throw #

Arguments

:: forall (e :: Effects) (es :: Effects) ex a. e :> es 
=> Exception ex e 
-> ex

Value to throw

-> Eff es a 
>>> runPureEff $ try $ \e -> do
      throw e 42
      pure "No exception thrown"
Left 42
>>> runPureEff $ try $ \e -> do
      pure "No exception thrown"
Right "No exception thrown"

rethrowIO #

Arguments

:: forall ex (es :: Effects) (e1 :: Effects) (e2 :: Effects) r. (e1 :> es, e2 :> es, Exception ex) 
=> IOE e1 
-> Exception ex e2 
-> Eff es r 
-> Eff es r

͘

Rethrow an exception raised by an IO action as a Bluefin exception.

runEff $ \io -> do
  r <- try $ \ex -> do
    rethrowIO @IOException io ex $ do
      effIO io (readFile "/tmp/doesnt-exist")

  effIO io $ putStrLn $ case r of
    Left e -> "Caught IOException:\n" ++ show e
    Right contents -> contents
Caught IOException:
/tmp/doesnt-exist: openFile: does not exist (No such file or directory)