avail-0.1.0.0: Low-overhead effect management for concrete monads
Safe HaskellNone
LanguageHaskell2010

Avail

Description

avail is a companion to monad transformers that allows you to add effect management to concrete monads, i.e. specify what effects a piece of code can perform.

Traditionally, in order to manage effects, the effect typeclasses are placed on a polymorphic monad type m so that other details of the monad type is not known at that point, effectively limiting what a function can do:

(MonadWriter Log m, MonadState Store m, MonadReader Env m) => m ()

While this works well, it has inevitable performance drawback because of the polymorphic m. GHC doesn't know the implementation of m, hence cannot perform much optimization. On the other hand, if we use a concrete monad stack that supports all the effects we need, we will not be able to restrict the effects that can be performed.

avail addresses this by a monad transformer M. For any monad m, the monad type M m adds effect management on top of it. Specifically, for an effect typeclass c (such as MonadIO or MonadReader r), its methods can be used on M m only if:

  • The monad m actually supports the effect, i.e. has an instance c m of the effect typeclass;
  • The effect is available in current context, i.e. a phantom constraint Eff c (which doesn't contain any information) is added to the function signature.

This pattern was first outlined in the blog post Effect is a phantom. In avail, it allows you to manage effects via the phantom Eff constraint while still using a concrete monad stack; the Eff constarint is not tied to the stack anyhow. Finally, Eff has no instances, and can only be removed all at once via the runM function, obtaining the underlying monad.

avail supports libraries including mtl, unliftio, monad-control and capability out of the box, so there should be near-zero boilerplate to get started with avail. For other effect typeclasses, the avail support of them can be easily derived via the TH functions in Avail.Derive.

You need these language extensions when using this module:

DataKinds
FlexibleContexts
FlexibleInstances
RankNTypes
TypeApplications

You need more extensions when using Avail.Derive; see documentation in that module.

Synopsis

Documentation

data M m a Source #

The M monad transformer acts as a barrier of effects. For example, for a monad type App and any effect typeclass MonadOvO that App has an instance of, the constraint Eff MonadOvO is required to perform the methods of MonadOvO in the monad M App as defined for the App monad.

In particular, M is expected to be used on a concrete monad instead of a polymorphic one. This is particularly good in terms of program performance, and generally means instead of writing this:

f :: MonadState Int m => m ()

You should write

f :: Eff (MonadState Int) => M App ()

where App is a monad stack of your choice that has support of MonadState Int. This also means there is no MonadTrans instance for M.

Note: you should not define instances of M for effect typeclasses directly by hand as that is error-prone and may create holes in effect management. For defining instances of effect typeclasses for M, check out the Avail.Derive module and specifically the avail and avail' TH functions.

Also keep in mind that typeclasses inside mtl, exceptions, unliftio, monad-control and capability work with M out-of-the-box so no instance for them is needed to be defined on M by you.

Instances

Instances details
(MonadRWS r w s m, Eff (MonadRWS r w s)) => MonadRWS r w s (M m) Source # 
Instance details

Defined in Avail.Instances

(MonadWriter w m, Eff (MonadWriter w)) => MonadWriter w (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

writer :: (a, w) -> M m a #

tell :: w -> M m () #

listen :: M m a -> M m (a, w) #

pass :: M m (a, w -> w) -> M m a #

(MonadState s m, Eff (MonadState s)) => MonadState s (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

get :: M m s #

put :: s -> M m () #

state :: (s -> (a, s)) -> M m a #

(MonadReader r m, Eff (MonadReader r)) => MonadReader r (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

ask :: M m r #

local :: (r -> r) -> M m a -> M m a #

reader :: (r -> a) -> M m a #

(MonadError e m, Eff (MonadError e)) => MonadError e (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

throwError :: e -> M m a #

catchError :: M m a -> (e -> M m a) -> M m a #

Monad m => Monad (M m) Source # 
Instance details

Defined in Avail.Internal

Methods

(>>=) :: M m a -> (a -> M m b) -> M m b #

(>>) :: M m a -> M m b -> M m b #

return :: a -> M m a #

Functor m => Functor (M m) Source # 
Instance details

Defined in Avail.Internal

Methods

fmap :: (a -> b) -> M m a -> M m b #

(<$) :: a -> M m b -> M m a #

MonadFix m => MonadFix (M m) Source # 
Instance details

Defined in Avail.Internal

Methods

mfix :: (a -> M m a) -> M m a #

(MonadFail m, Eff MonadFail) => MonadFail (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

fail :: String -> M m a #

Applicative m => Applicative (M m) Source # 
Instance details

Defined in Avail.Internal

Methods

pure :: a -> M m a #

(<*>) :: M m (a -> b) -> M m a -> M m b #

liftA2 :: (a -> b -> c) -> M m a -> M m b -> M m c #

(*>) :: M m a -> M m b -> M m b #

(<*) :: M m a -> M m b -> M m a #

MonadZip m => MonadZip (M m) Source # 
Instance details

Defined in Avail.Internal

Methods

mzip :: M m a -> M m b -> M m (a, b) #

mzipWith :: (a -> b -> c) -> M m a -> M m b -> M m c #

munzip :: M m (a, b) -> (M m a, M m b) #

(MonadIO m, Eff MonadIO) => MonadIO (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

liftIO :: IO a -> M m a #

(Alternative m, Eff Alternative) => Alternative (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

empty :: M m a #

(<|>) :: M m a -> M m a -> M m a #

some :: M m a -> M m [a] #

many :: M m a -> M m [a] #

(MonadPlus m, Eff MonadPlus) => MonadPlus (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

mzero :: M m a #

mplus :: M m a -> M m a -> M m a #

(MonadThrow m, Eff MonadThrow) => MonadThrow (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

throwM :: Exception e => e -> M m a #

(MonadCatch m, Eff MonadCatch) => MonadCatch (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

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

(MonadMask m, Eff MonadMask) => MonadMask (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

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

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

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

(MonadCont m, Eff MonadCont) => MonadCont (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

callCC :: ((a -> M m b) -> M m a) -> M m a #

(PrimMonad m, Eff PrimMonad) => PrimMonad (M m) Source # 
Instance details

Defined in Avail.Instances

Associated Types

type PrimState (M m) #

Methods

primitive :: (State# (PrimState (M m)) -> (# State# (PrimState (M m)), a #)) -> M m a #

(MonadUnliftIO m, Eff MonadUnliftIO) => MonadUnliftIO (M m) Source # 
Instance details

Defined in Avail.Instances

Methods

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

type PrimState (M m) Source # 
Instance details

Defined in Avail.Instances

type PrimState (M m) = PrimState m

type Effect = (Type -> Type) -> Constraint Source #

The kind of effect typeclasses, i.e. those that define a set of operations on a monad. Examples include MonadIO and MonadReader.

This type is the same as the Capability type in capability.

class KnownList (Superclasses e) => IsEff (e :: Effect) Source #

Any Effect being used with avail should have an instance of this class. Specifically, this class stores the superclasses of effect typeclasses. For example, MonadUnliftIO has a superclass MonadIO.

You won't need to define instances of this by hand; instead, use the avail' Template Haskell function.

Associated Types

type Superclasses e :: [Effect] Source #

The superclasses of this typeclass.

Instances

Instances details
IsEff MonadFail Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses MonadFail :: [Effect] Source #

IsEff MonadIO Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses MonadIO :: [Effect] Source #

IsEff Alternative Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses Alternative :: [Effect] Source #

IsEff MonadPlus Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses MonadPlus :: [Effect] Source #

IsEff MonadThrow Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses MonadThrow :: [Effect] Source #

IsEff MonadCatch Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses MonadCatch :: [Effect] Source #

IsEff MonadMask Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses MonadMask :: [Effect] Source #

IsEff MonadCont Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses MonadCont :: [Effect] Source #

IsEff PrimMonad Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses PrimMonad :: [Effect] Source #

IsEff MonadUnliftIO Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses MonadUnliftIO :: [Effect] Source #

IsEff (MonadWriter w) Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses (MonadWriter w) :: [Effect] Source #

IsEff (MonadState s) Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses (MonadState s) :: [Effect] Source #

IsEff (MonadReader r) Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses (MonadReader r) :: [Effect] Source #

IsEff (MonadError e) Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses (MonadError e) :: [Effect] Source #

IsEff (MonadRWS r w s) Source # 
Instance details

Defined in Avail.Instances

Associated Types

type Superclasses (MonadRWS r w s) :: [Effect] Source #

type Eff (e :: Effect) = (Eff' e, Effs (Superclasses e)) Source #

The constraint that indicates an effect is available for use, i.e. you can perform methods defined by instances of the effect typeclass e in a M monad.

type family Effs (es :: [Effect]) :: Constraint where ... Source #

Convenient alias for (Eff e1, Eff e2, ..., Eff en).

Equations

Effs '[] = () 
Effs (e ': es) = (Eff e, Effs es) 

class KnownList (es :: [Effect]) Source #

The list of effect typeclasses es is known at compile time. This is required for functions like runM.

Instances

Instances details
KnownList ('[] :: [Effect]) Source # 
Instance details

Defined in Avail.Internal

Methods

rips :: (Effs '[] => a) -> a Source #

(IsEff e, KnownList es) => KnownList (e ': es) Source # 
Instance details

Defined in Avail.Internal

Methods

rips :: (Effs (e ': es) => a) -> a Source #

unM :: M m a -> m a Source #

Unwrap the M monad into the underlying concrete monad. This is rarely needed as most of the time you would also want to eliminate Eff constraints at the same time; for that see runM.

runM :: forall es m a. KnownList es => (Effs es => M m a) -> m a Source #

Unwrap the M monad into the underlying concrete monad and also eliminating Eff constraints. You need TypeApplications in order to specify the list of Effects you want to eliminate Eff constraints for:

runM @'[MonadReader Env, MonadState Store, MonadError MyErr] app

Note that functions like (&) generally does not work with this function; either apply directly or use ($) only.