yael-0.1.0.0

Safe HaskellNone
LanguageHaskell2010

Yael.Eff

Description

Yael is an effect system that models effects as records. This module contains the core functionality needed to define and use effects.

In Yael, each effect is a record, paremeterized by a Monad, m. For example

data MyEffect m = MyEffect
  { _myMethod1 :: String -> m Bool
  , _myMethod2 :: m Int -> m [Int]
  }

Each field in an effect record is a "method" of that effect. Methods after often functions, but they don't have to be. They can be of the form `m a` for some a, or they can simply not refer to m at all. As seen in MyEffect, methods can be first-order, meaning that m only appears in the result of a functional method, or they can be higher order, meaning that m appears in the arguments of a functional method. Most methods are first-order, but higher-order methods are useful to represent effects that can wrap other effectful code, for example when working with transactional data

Synopsis

Documentation

data EffT (f :: (* -> *) -> *) (m :: * -> *) (a :: *) Source #

EffT is a monad transformer which adds an effect (or collection of effects) f to an underlying Monad m.

Instances
MonadBase s m => MonadBase s (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

liftBase :: s α -> EffT f m α #

MonadBaseControl s m => MonadBaseControl s (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Associated Types

type StM (EffT f m) a :: Type #

Methods

liftBaseWith :: (RunInBase (EffT f m) s -> s a) -> EffT f m a #

restoreM :: StM (EffT f m) a -> EffT f m a #

MonadTrans (EffT f) Source # 
Instance details

Defined in Yael.Eff

Methods

lift :: Monad m => m a -> EffT f m a #

Monad m => Monad (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

(>>=) :: EffT f m a -> (a -> EffT f m b) -> EffT f m b #

(>>) :: EffT f m a -> EffT f m b -> EffT f m b #

return :: a -> EffT f m a #

fail :: String -> EffT f m a #

Functor m => Functor (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

fmap :: (a -> b) -> EffT f m a -> EffT f m b #

(<$) :: a -> EffT f m b -> EffT f m a #

Applicative m => Applicative (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

pure :: a -> EffT f m a #

(<*>) :: EffT f m (a -> b) -> EffT f m a -> EffT f m b #

liftA2 :: (a -> b -> c) -> EffT f m a -> EffT f m b -> EffT f m c #

(*>) :: EffT f m a -> EffT f m b -> EffT f m b #

(<*) :: EffT f m a -> EffT f m b -> EffT f m a #

Alternative m => Alternative (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

empty :: EffT f m a #

(<|>) :: EffT f m a -> EffT f m a -> EffT f m a #

some :: EffT f m a -> EffT f m [a] #

many :: EffT f m a -> EffT f m [a] #

MonadIO m => MonadIO (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

liftIO :: IO a -> EffT f m a #

MonadPlus m => MonadPlus (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

mzero :: EffT f m a #

mplus :: EffT f m a -> EffT f m a -> EffT f m a #

MonadThrow m => MonadThrow (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

throwM :: Exception e => e -> EffT f m a #

MonadCatch m => MonadCatch (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

catch :: Exception e => EffT f m a -> (e -> EffT f m a) -> EffT f m a #

MonadMask m => MonadMask (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

mask :: ((forall a. EffT f m a -> EffT f m a) -> EffT f m b) -> EffT f m b #

uninterruptibleMask :: ((forall a. EffT f m a -> EffT f m a) -> EffT f m b) -> EffT f m b #

generalBracket :: EffT f m a -> (a -> ExitCase b -> EffT f m c) -> (a -> EffT f m b) -> EffT f m (b, c) #

MonadUnliftIO m => MonadUnliftIO (EffT f m) Source # 
Instance details

Defined in Yael.Eff

Methods

askUnliftIO :: EffT f m (UnliftIO (EffT f m)) #

withRunInIO :: ((forall a. EffT f m a -> IO a) -> IO b) -> EffT f m b #

type StM (EffT f m) a Source # 
Instance details

Defined in Yael.Eff

type StM (EffT f m) a = StM (ReaderT (f m) m) a

pattern EffT :: (f m -> m a) -> EffT f m a Source #

runEffT :: forall f m a. EffT f m a -> f m -> m a Source #

Run an effectful computation of f in m by providing a particular instantiation of that effect.

liftEffT :: (f m -> m a) -> EffT f m a Source #

Synonym for the EffT constructor. Lift a computation in m with access to the effect f into EffT f m

shareEffT :: f m -> (Lower f m m -> EffT f m a) -> m a Source #

withEffT :: HasEff g f m => (forall n. Monad n => g n -> n a) -> EffT f m a Source #

Lift a first-order computation that is expressible wholly through g into EffT. This is most commonly used to define convient method accessors generically in EffT.

Returning to the MyEffect example above, we'll see that _myMethod1 has type MyEffect m -> String -> m Bool. The MyEffect m paremeter is cumbersome to work with, so we can use withEffT:

myMethod1 :: (HasEff MyEffect f m) => String -> EffT f m Bool
myMethod1 s = withEffT $ myEffect -> _myMethod1 myEffect s

withEffT' :: HasEff g f m => (forall n. Monad n => Lower f m n -> g n -> n a) -> EffT f m a Source #

Lift a higher-order computation in g into EffT.

withEffT' is similar to withEffT, but it provides an additional "lowering" function that is useful for working with higher order computations. For example

myMethod2 :: (HasEff MyEffect f m) => EffT f m Int -> EffT f m [Int]
myMethod2 m = withEffT' $ lower myEffect -> _myMethod2 myEffect (lower m)

withEffT'' :: HasEff g f m => (forall n. Monad n => Lower f m n -> Raise f m n -> g n -> n a) -> EffT f m a Source #

type Lower f m n = EffT f m ~> n Source #

type Raise f m n = n ~> EffT f m Source #

type (~>) f g = forall x. f x -> g x Source #

localEffT :: Project f g => (g m -> g m) -> EffT f m a -> EffT f m a Source #

Modify a computational context. Useful for attaching behavior to a specific scope. Compare to local in Control.Monad.Reader

mapEffT :: Monad m => (f m -> g m) -> EffT g m a -> EffT f m a Source #

Transform an entire effect context into a new context. Useful for resolving one effect in a context without resolving every effect.

type HasEff g f m = (Project f g, Monad m) Source #

Type synonym expressing that an g is available for use within the wider context f

type family HasEffs xs f m where ... Source #

Type synonym expressing that a set of effects xs are all available within the wider context f. xs is expressed as a type level list, however order does not matter.

Equations

HasEffs '[x] f m = HasEff x f m 
HasEffs (x ': xs) f m = (HasEff x f m, HasEffs xs f m) 

type (:+) v effs = forall m f. HasEffs effs f m => EffT f m v infix 7 Source #

Syntactic sugar for first order computations with no additional constraints on the effectful context f or computational context m.

Example:

myFunction :: String -> [Int] :+ '[MyEffect]
myFunction s = do
  r1 <- myMethod1 s
  case r1 of
    True -> myMethod2 $ return 17
    False -> return [17]

data (a :<> b) (m :: * -> *) infixr 9 Source #

Combinator for composing effects.

Constructors

(a m) :<> (b m) infixr 9 
Instances
Project b c => Project (a :<> b) c Source # 
Instance details

Defined in Yael.Eff

Methods

prj :: Lens' ((a :<> b) m) (c m) Source #

Project (a :<> b) a Source # 
Instance details

Defined in Yael.Eff

Methods

prj :: Lens' ((a :<> b) m) (a m) Source #

(Show (a m), Show (b m)) => Show ((a :<> b) m) Source # 
Instance details

Defined in Yael.Eff

Methods

showsPrec :: Int -> (a :<> b) m -> ShowS #

show :: (a :<> b) m -> String #

showList :: [(a :<> b) m] -> ShowS #

Generic ((a :<> b) m) Source # 
Instance details

Defined in Yael.Eff

Associated Types

type Rep ((a :<> b) m) :: Type -> Type #

Methods

from :: (a :<> b) m -> Rep ((a :<> b) m) x #

to :: Rep ((a :<> b) m) x -> (a :<> b) m #

Field1 ((a :<> b) m) ((a' :<> b) m) (a m) (a' m) Source # 
Instance details

Defined in Yael.Eff

Methods

_1 :: Lens ((a :<> b) m) ((a' :<> b) m) (a m) (a' m) #

Field2 ((a :<> b) m) ((a :<> b') m) (b m) (b' m) Source # 
Instance details

Defined in Yael.Eff

Methods

_2 :: Lens ((a :<> b) m) ((a :<> b') m) (b m) (b' m) #

type Rep ((a :<> b) m) Source # 
Instance details

Defined in Yael.Eff

class Project (f :: (* -> *) -> *) g where Source #

Typeclass for extracting a specific effect from a larger context. It should generally not be necessary to implement your own instances of this class.

Methods

prj :: Lens' (f m) (g m) Source #

Instances
(TypeError (MissingError x y) :: Constraint) => Project x y Source # 
Instance details

Defined in Yael.Eff

Methods

prj :: Lens' (x m) (y m) Source #

Project x x Source # 
Instance details

Defined in Yael.Eff

Methods

prj :: Lens' (x m) (x m) Source #

Project b c => Project (a :<> b) c Source # 
Instance details

Defined in Yael.Eff

Methods

prj :: Lens' ((a :<> b) m) (c m) Source #

Project (a :<> b) a Source # 
Instance details

Defined in Yael.Eff

Methods

prj :: Lens' ((a :<> b) m) (a m) Source #

Project (EffList fs) f => Project (EffList (g ': fs)) f Source # 
Instance details

Defined in Yael.Eff.Builder

Methods

prj :: Lens' (EffList (g ': fs) m) (f m) Source #

Project (EffList (f ': fs)) f Source # 
Instance details

Defined in Yael.Eff.Builder

Methods

prj :: Lens' (EffList (f ': fs) m) (f m) Source #

newtype HigherOrder n (m :: * -> *) Source #

Helper for deriving Generic on effects with polymorphic methods

Constructors

HigherOrder 

Fields