| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Bluefin.Eff
Synopsis
- data Eff (es :: Effects) a
- runPureEff :: (forall (es :: Effects). Eff es a) -> a
- runEff :: (forall (e :: Effects) (es :: Effects). IOE e -> Eff (e :& es) a) -> IO a
- bracket :: forall (es :: Effects) a b. Eff es a -> (a -> Eff es ()) -> (a -> Eff es b) -> Eff es b
- withMonadIO :: forall (e :: Effects) (es :: Effects) r. e :> es => IOE e -> (forall (m :: Type -> Type). MonadIO m => m r) -> Eff es r
- withMonadFail :: forall (e :: Effects) (es :: Effects) r. e :> es => Exception String e -> (forall (m :: Type -> Type). MonadFail m => m r) -> Eff es r
- data Effects
- class (es1 :: Effects) :> (es2 :: Effects)
- type (:&) = 'Union
Eff monad
Run an Eff
runPureEff :: (forall (es :: Effects). Eff es a) -> a #
Run an Eff that doesn't contain any unhandled effects.
Resource management
bracket :: forall (es :: Effects) a b. Eff es a -> (a -> Eff es ()) -> (a -> Eff es b) -> Eff es b #
bracket acquire release body: acquire a resource, perform the
body with it, and release the resource even if body threw an
exception. This is essentially the same as
Control.Exception., whose
documentation you can inspect for further details.bracket
Type classes
See Bluefin.Eff.IO for the most direct way of doing I/O in
Bluefin. If you really want to use MonadIO you can use
withMonadIO.
Effect tracking
class (es1 :: Effects) :> (es2 :: Effects) #
Effect subset constraint
Instances
| e :> e | A set of effects |
Defined in Bluefin.Internal | |
| e :> (e :& es) |
|
Defined in Bluefin.Internal | |
| e :> es => e :> (x :& es) | If |
Defined in Bluefin.Internal | |