derive-lifted-instances-0.2.2: Derive class instances though various kinds of lifting
Copyright(c) Sjoerd Visscher 2020
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.DeriveLiftedInstances

Description

 
Synopsis

Deriving instances

deriveInstance :: Derivator -> Q Type -> Q [Dec] Source #

Derive the instance with the given Derivator and the given instance head.

The instance head can be passed as a template haskell type quotation, for example:

{-# LANGUAGE TemplateHaskell #-}
[t| Num ShowsPrec |]
[t| forall a. Num a => Num [a] |]
[t| forall a b. (Num a, Num b) => Num (a, b) |]

idDeriv :: Derivator Source #

The identity Derivator. Not useful on its own, but often used as input for other Derivators.

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 Show
deriveInstance (newtypeDeriv 'Ap 'getAp idDeriv) [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 } deriving Show
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]

biapDeriv :: Derivator -> Derivator -> Derivator Source #

Given how to derive an instance for a and b, biapDeriv creates a Derivator for f a b, when f is an instance of Biapplicative. Example:

deriveInstance (biapDeriv idDeriv idDeriv) [t| forall a b. (Num a, Num b) => Num (a, b) |]

> (2, 3) * (5, 10)
(10, 30)

monoidDeriv :: Derivator Source #

Create a Derivator for any Monoid m. This is a degenerate instance that only collects all values of type m, and ignores the rest.

monoidDerivBy :: Q Exp -> Q Exp -> Derivator Source #

Create a Derivator for a monoid, given TH expressions to replace (<>) and mempty respectively. Example:

monoidDerivBy [| (+) |] [| 0 |]

showDeriv :: Derivator Source #

Derive instances for ShowsPrec. Example:

deriveInstance showDeriv [t| Num ShowsPrec |]

> show ((6 * 7) ^ 2 :: ShowsPrec)
"fromInteger 6 * fromInteger 7 * (fromInteger 6 * fromInteger 7)"

data ShowsPrec Source #

Helper for showing infix expressions

Instances

Instances details
Bounded ShowsPrec Source # 
Instance details

Defined in Data.DeriveLiftedInstances

Floating ShowsPrec Source # 
Instance details

Defined in Data.DeriveLiftedInstances

Fractional ShowsPrec Source # 
Instance details

Defined in Data.DeriveLiftedInstances

Num ShowsPrec Source # 
Instance details

Defined in Data.DeriveLiftedInstances

Show ShowsPrec Source # 
Instance details

Defined in Data.DeriveLiftedInstances.Internal

Semigroup ShowsPrec Source # 
Instance details

Defined in Data.DeriveLiftedInstances

Monoid ShowsPrec Source # 
Instance details

Defined in Data.DeriveLiftedInstances

Creating derivators

data Derivator Source #

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))

Constructors

Derivator 

Fields

Orphan instances

Bounded ShowsPrec Source # 
Instance details

Floating ShowsPrec Source # 
Instance details

Fractional ShowsPrec Source # 
Instance details

Num ShowsPrec Source # 
Instance details

Semigroup ShowsPrec Source # 
Instance details

Monoid ShowsPrec Source # 
Instance details