Copyright | (c) Sjoerd Visscher 2020 |
---|---|
Maintainer | sjoerd@w3future.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- deriveInstance :: Derivator -> Q Type -> Q [Dec]
- idDeriv :: Derivator
- newtypeDeriv :: Name -> Name -> Derivator -> Derivator
- isoDeriv :: Q Exp -> Q Exp -> Derivator -> Derivator
- recordDeriv :: Q Exp -> [(Q Exp, Derivator)] -> Derivator
- apDeriv :: Derivator -> Derivator
- biapDeriv :: Derivator -> Derivator -> Derivator
- monoidDeriv :: Derivator
- monoidDerivBy :: Q Exp -> Q Exp -> Derivator
- showDeriv :: Derivator
- data ShowsPrec
- data Derivator = Derivator {}
Deriving instances
newtypeDeriv :: Name -> Name -> Derivator -> Derivator Source #
Given how to derive an instance for a
, and the names of a newtype wrapper around a
,
newtypeDeriv
creates a Derivator
for that newtype. Example:
newtype Ap f a = Ap { getAp :: f a } deriving ShowderiveInstance
(newtypeDeriv
'Ap 'getApidDeriv
) [t| forall f.Functor
f =>Functor
(Ap f) |] >fmap
(+1) (Ap [1,2,3]) Ap {getAp = [2,3,4]}
isoDeriv :: Q Exp -> Q Exp -> Derivator -> Derivator Source #
Given how to derive an instance for a
, and two functions of type a `->` b
and b `->` a
,
isoDeriv
creates a Derivator
for b
. (Note that the 2 functions don't have to form
an isomorphism, but if they don't, the new instance can break the class laws.) Example:
newtype X = X { unX ::Int
} derivingShow
mkX ::Int
-> X mkX i = X (mod
i 10)deriveInstance
(isoDeriv [| mkX |] [| unX |]idDeriv
) [t|Num
X |] > mkX 4^
2 X {unX = 6}
recordDeriv :: Q Exp -> [(Q Exp, Derivator)] -> Derivator Source #
Given an n-ary function to a
, and a list of pairs, consisting of a function from a
and a
Derivator
for the codomain of that function, create a Derivator
for a
. Examples:
data Rec f = Rec { getUnit :: f (), getInt :: f Int } deriveInstance (recordDeriv [| Rec |] [ ([| getUnit |], apDeriv monoidDeriv) , ([| getInt |], apDeriv idDeriv) ]) [t| forall f. Applicative f => Num (Rec f) |]
tripleDeriv deriv1 deriv2 deriv3 = recordDeriv [| (,,) |] [ ([| fst3 |], deriv1) , ([| snd3 |], deriv2) , ([| thd3 |], deriv3) ]
apDeriv :: Derivator -> Derivator Source #
Given how to derive an instance for a
, apDeriv
creates a Derivator
for f a
,
when f
is an instance of Applicative
. Example:
deriveInstance
(apDeriv
idDeriv
) [t| forall a.Num
a =>Num
[a] |] > [2, 3]*
[5, 10] [10, 20, 15, 30]
Helper for showing infix expressions
ShowsPrec (Int -> String -> String) | |
ShowOp2 Fixity (Int -> String -> String) | |
ShowOp1 Fixity (Int -> String -> String) |
Instances
Bounded ShowsPrec Source # | |
Floating ShowsPrec Source # | |
Defined in Data.DeriveLiftedInstances exp :: ShowsPrec -> ShowsPrec # log :: ShowsPrec -> ShowsPrec # sqrt :: ShowsPrec -> ShowsPrec # (**) :: ShowsPrec -> ShowsPrec -> ShowsPrec # logBase :: ShowsPrec -> ShowsPrec -> ShowsPrec # sin :: ShowsPrec -> ShowsPrec # cos :: ShowsPrec -> ShowsPrec # tan :: ShowsPrec -> ShowsPrec # asin :: ShowsPrec -> ShowsPrec # acos :: ShowsPrec -> ShowsPrec # atan :: ShowsPrec -> ShowsPrec # sinh :: ShowsPrec -> ShowsPrec # cosh :: ShowsPrec -> ShowsPrec # tanh :: ShowsPrec -> ShowsPrec # asinh :: ShowsPrec -> ShowsPrec # acosh :: ShowsPrec -> ShowsPrec # atanh :: ShowsPrec -> ShowsPrec # log1p :: ShowsPrec -> ShowsPrec # expm1 :: ShowsPrec -> ShowsPrec # | |
Fractional ShowsPrec Source # | |
Num ShowsPrec Source # | |
Defined in Data.DeriveLiftedInstances | |
Show ShowsPrec Source # | |
Semigroup ShowsPrec Source # | |
Monoid ShowsPrec Source # | |
Creating derivators
To write your own Derivator
you need to show how each part of a method gets lifted.
For example, when deriving an instance for type a
of the following methods:
meth0 :: a meth1 :: Int -> a meth2 :: a -> Either Bool a -> Sum Int meth3 :: Maybe [a] -> IO a
the resulting template haskell declarations are (pseudo code):
meth0 = $res ($op "meth0" meth0) meth1 a = $res (($op "meth1" meth1) `$ap` ($arg Int a)) meth2 ($inp v0) ($inp v1) = $cst (($op "meth2" meth2) `$ap` ($var (iterate
0) v0)) `$ap` ($var (iterate
1) v1) meth3 ($inp v2) = $eff (($op "meth2" meth2) `$ap` ($var (iterate
2) v2))
Derivator | |
|
Orphan instances
Bounded ShowsPrec Source # | |
Floating ShowsPrec Source # | |
exp :: ShowsPrec -> ShowsPrec # log :: ShowsPrec -> ShowsPrec # sqrt :: ShowsPrec -> ShowsPrec # (**) :: ShowsPrec -> ShowsPrec -> ShowsPrec # logBase :: ShowsPrec -> ShowsPrec -> ShowsPrec # sin :: ShowsPrec -> ShowsPrec # cos :: ShowsPrec -> ShowsPrec # tan :: ShowsPrec -> ShowsPrec # asin :: ShowsPrec -> ShowsPrec # acos :: ShowsPrec -> ShowsPrec # atan :: ShowsPrec -> ShowsPrec # sinh :: ShowsPrec -> ShowsPrec # cosh :: ShowsPrec -> ShowsPrec # tanh :: ShowsPrec -> ShowsPrec # asinh :: ShowsPrec -> ShowsPrec # acosh :: ShowsPrec -> ShowsPrec # atanh :: ShowsPrec -> ShowsPrec # log1p :: ShowsPrec -> ShowsPrec # expm1 :: ShowsPrec -> ShowsPrec # | |
Fractional ShowsPrec Source # | |
Num ShowsPrec Source # | |
Semigroup ShowsPrec Source # | |
Monoid ShowsPrec Source # | |