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

Avail.Derive

Description

This module contains mechanisms for deriving necessary instances for a new Effect typeclass to work with avail. If you only need functionalities from mtl, monad-control, unliftio and capability, you don't need to use this module.

You need these extensions when using the module:

DataKinds
DerivingStrategies
FlexibleContexts
FlexibleInstances
GeneralizedNewtypeDeriving
StandaloneDeriving
TemplateHaskell
TypeFamilies
UndecidableInstances
Synopsis

Deriving

avail :: Q Type -> Q [Dec] Source #

Derive necessary instances for an Effect typeclass to work with avail. Specifically, this only works with typeclasses without superclasses; see avail' for a version that takes care of superclasses.

avail' :: [Q Type] -> Q Type -> Q [Dec] Source #

Derive necessary instances for an Effect typeclass to work with avail. This is a generalized version of avail that allows you to pass in a list of superclasses.

For superclasses Sup :: [Effect] and current class Cls :: Effect, the code generated is:

instance IsEff Cls where
  type Superclasses Cls = Sup
deriving newtype instance (Cls m, Eff Cls) => Cls (M m)

Although this is very little code, it is still boilerplate and defining them by hand is error-prone. Therefore, please do not define instances for M by hand (except when doing dirty hacks); use this function instead.

Helpers for deriving instances for multi-param classes

with1 :: (Q Type -> Q a) -> Q a Source #

Introduce one type variable a.

with2 :: (Q Type -> Q Type -> Q a) -> Q a Source #

Introduce two type variables a, b.

with3 :: (Q Type -> Q Type -> Q Type -> Q a) -> Q a Source #

Introduce three type variables a, b, c.

with4 :: (Q Type -> Q Type -> Q Type -> Q Type -> Q a) -> Q a Source #

Introduce four type variables a, b, c, d.

with5 :: (Q Type -> Q Type -> Q Type -> Q Type -> Q Type -> Q a) -> Q a Source #

Introduce five type variables a, b, c, d, e.

withN :: Int -> ([Q Type] -> Q a) -> Q a Source #

Introduce arbitrarily many type variables a1, a2, a3, ....

with1' :: String -> (Q Type -> Q a) -> Q a Source #

Introduce one type variable with given name.

with2' :: String -> String -> (Q Type -> Q Type -> Q a) -> Q a Source #

Introduce two type variables with given names.

with3' :: String -> String -> String -> (Q Type -> Q Type -> Q Type -> Q a) -> Q a Source #

Introduce three type variables with given names.

with4' :: String -> String -> String -> String -> (Q Type -> Q Type -> Q Type -> Q Type -> Q a) -> Q a Source #

Introduce four type variables with given names.

with5' :: String -> String -> String -> String -> String -> (Q Type -> Q Type -> Q Type -> Q Type -> Q Type -> Q a) -> Q a Source #

Introduce five type variables with given names.

withN' :: [String] -> ([Q Type] -> Q a) -> Q a Source #

Introduce arbitrarily many type variables with given names.

Necessary reexports - do not use directly

newtype 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.

Constructors

UnsafeLift (m a)

Unsafely lift an m action into M m. This completely sidesteps the effect management mechanism; You should not use this.

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