bluefin-0.2.6.0: The Bluefin effect system
Safe HaskellNone
LanguageHaskell2010

Bluefin.Eff

Synopsis

Eff monad

data Eff (es :: Effects) a #

Instances

Instances details
e :> es => OneWayCoercible (Eff e r :: Type) (Eff es r :: Type) 
Instance details

Defined in Bluefin.Internal

Applicative (Eff es) 
Instance details

Defined in Bluefin.Internal

Methods

pure :: a -> Eff es a #

(<*>) :: Eff es (a -> b) -> Eff es a -> Eff es b #

liftA2 :: (a -> b -> c) -> Eff es a -> Eff es b -> Eff es c #

(*>) :: Eff es a -> Eff es b -> Eff es b #

(<*) :: Eff es a -> Eff es b -> Eff es a #

Functor (Eff es) 
Instance details

Defined in Bluefin.Internal

Methods

fmap :: (a -> b) -> Eff es a -> Eff es b #

(<$) :: a -> Eff es b -> Eff es a #

Monad (Eff es) 
Instance details

Defined in Bluefin.Internal

Methods

(>>=) :: Eff es a -> (a -> Eff es b) -> Eff es b #

(>>) :: Eff es a -> Eff es b -> Eff es b #

return :: a -> Eff es a #

e :> es => OneWayCoercible (Eff e :: Type -> Type) (Eff es :: Type -> Type) 
Instance details

Defined in Bluefin.Internal

Run an Eff

runPureEff :: (forall (es :: Effects). Eff es a) -> a #

Run an Eff that doesn't contain any unhandled effects.

runEff_ #

Arguments

:: (forall (e :: Effects). IOE e -> Eff e a) 
-> IO a

͘

Run an Eff whose only unhandled effect is IO.

>>> runEff_ $ \io -> do
      effIO io (putStrLn "Hello world!")
Hello, world!

This probably has better type inference properties than runEff and so will probably replace it in a later version.

runEff #

Arguments

:: (forall (e :: Effects) (es :: Effects). IOE e -> Eff (e :& es) a) 
-> IO a

͘

Run an Eff whose only unhandled effect is IO.

>>> runEff_ $ \io -> do
      effIO io (putStrLn "Hello world!")
Hello, world!

We suggest you use runEff_ instead, as it probably has better type inference properties.

Resource management

bracket #

Arguments

:: forall (es :: Effects) a b. Eff es a

Acquire the resource

-> (a -> Eff es ())

Release the resource

-> (a -> Eff es b)

Run the body with resource

-> 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.bracket, whose documentation you can inspect for further details.

bracket has a very general type that does not require es to contain an exception or IO effect. The reason that this is safe is:

  • While bracket does catch exceptions, this is unobservable, since the exception is re-thrown; the cleanup action happens unconditionally; and no part of it gets access to the thrown exception.
  • Eff itself is able to guarantee that any exceptions thrown in the body will be actually thrown before bracket exits. This is inherited from the fact that Eff is a wrapper around IO.

While it is usually the case that the cleanup action will in fact want to use IO effects, this is not universally true, see the polymorphicBracket example for an example.

finally #

Arguments

:: forall (es :: Effects) b. Eff es b

Body

-> Eff es ()

Final action to run after the body, regardless of whether the body terminated normally or via exception

-> Eff es b 

A simpler variant of bracket for use when you don't need to acquire a resource.

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.

withMonadIO #

Arguments

:: forall (e :: Effects) (es :: Effects) r. e :> es 
=> IOE e 
-> (forall (m :: Type -> Type). MonadIO m => m r)

MonadIO operation

-> Eff es r

MonadIO operation run in Eff

Run MonadIO operations in Eff.

>>> runEff_ $ \io -> withMonadIO io $ liftIO $ do
      putStrLn "Hello world!"
Hello, world!

withMonadFail #

Arguments

:: forall (e :: Effects) (es :: Effects) r. e :> es 
=> Exception String e

Exception to throw on fail

-> (forall (m :: Type -> Type). MonadFail m => m r)

MonadFail operation

-> Eff es r

MonadFail operation run in Eff

Run MonadFail operations in Eff.

>>> runPureEff $ try $ \e ->
      when (2 > 1) $
        withMonadFail e (fail "2 was bigger than 1")
Left "2 was bigger than 1"

Effect tracking

data Effects #

Instances

Instances details
Handle h => Handle (Rec1 h) 
Instance details

Defined in Bluefin.Internal

Methods

handleImpl :: HandleD (Rec1 h) #

mapHandle :: forall (e :: Effects) (es :: Effects). e :> es => Rec1 h e -> Rec1 h es #

(forall (e' :: Effects) (es' :: Effects). e' :> es' => OneWayCoercible (OneWayCoercibleHandle h e') (OneWayCoercibleHandle h es')) => Handle (OneWayCoercibleHandle h) 
Instance details

Defined in Bluefin.Internal

Handle h => Handle (GenericCloneableHandle h) 
Instance details

Defined in Bluefin.Internal.CloneableHandle

(Handle h, Generic1 h, GCloneableHandle (Rep1 h)) => CloneableHandle (GenericCloneableHandle h) 
Instance details

Defined in Bluefin.Internal.CloneableHandle

CloneableHandle h => GCloneableHandle (Rec1 h)

A cloneable handle is generically cloneable

Instance details

Defined in Bluefin.Internal.CloneableHandle

(Handle h1, Handle h2) => Handle (h1 :*: h2) 
Instance details

Defined in Bluefin.Internal

Methods

handleImpl :: HandleD (h1 :*: h2) #

mapHandle :: forall (e :: Effects) (es :: Effects). e :> es => (h1 :*: h2) e -> (h1 :*: h2) es #

(GCloneableHandle h1, GCloneableHandle h2) => GCloneableHandle (h1 :*: h2)

A pair of cloneable handles is generically cloneable

Instance details

Defined in Bluefin.Internal.CloneableHandle

Handle h => Handle (M1 i t h) 
Instance details

Defined in Bluefin.Internal

Methods

handleImpl :: HandleD (M1 i t h) #

mapHandle :: forall (e :: Effects) (es :: Effects). e :> es => M1 i t h e -> M1 i t h es #

GCloneableHandle h => GCloneableHandle (M1 i t h)

An annotated cloneable handle is generically cloneable

Instance details

Defined in Bluefin.Internal.CloneableHandle

class (es1 :: Effects) :> (es2 :: Effects) #

Effect subset constraint

Instances

Instances details
e :> e

A set of effects e is a subset of itself

Instance details

Defined in Bluefin.Internal

e :> (e :& es)

e is a subset of a larger set e :& es

Instance details

Defined in Bluefin.Internal

e :> es => e :> (x :& es)

If e is subset of es then e is a subset of a larger set, x :& es

Instance details

Defined in Bluefin.Internal

type (:&) = 'Union infixr 9 #

type (:&) :: Effects -> Effects -> Effects

Union of effects