Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- avail :: Q Type -> Q [Dec]
- avail' :: [Q Type] -> Q Type -> Q [Dec]
- with1 :: (Q Type -> Q a) -> Q a
- with2 :: (Q Type -> Q Type -> Q a) -> Q a
- with3 :: (Q Type -> Q Type -> Q Type -> Q a) -> Q a
- with4 :: (Q Type -> Q Type -> Q Type -> Q Type -> Q a) -> Q a
- with5 :: (Q Type -> Q Type -> Q Type -> Q Type -> Q Type -> Q a) -> Q a
- withN :: Int -> ([Q Type] -> Q a) -> Q a
- with1' :: String -> (Q Type -> Q a) -> Q a
- with2' :: String -> String -> (Q Type -> Q Type -> Q a) -> Q a
- with3' :: String -> String -> String -> (Q Type -> Q Type -> Q Type -> Q a) -> Q a
- with4' :: String -> String -> String -> String -> (Q Type -> Q Type -> Q Type -> Q Type -> Q a) -> Q a
- with5' :: String -> String -> String -> String -> String -> (Q Type -> Q Type -> Q Type -> Q Type -> Q Type -> Q a) -> Q a
- withN' :: [String] -> ([Q Type] -> Q a) -> Q a
- newtype M m a = UnsafeLift (m a)
Deriving
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 :: [
and current class Effect
]Cls ::
, the code generated is:Effect
instanceIsEff
Cls where typeSuperclasses
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
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, ...
.
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
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
as defined for the M
AppApp
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
. This also
means there is no MonadState
Int
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.
UnsafeLift (m a) | Unsafely lift an |