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

Data.DeriveLiftedInstances.Internal

Description

 
Synopsis

Documentation

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 -> Int
meth3 :: Maybe [a] -> 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 v0 v1 = (($op "meth2" meth2) `$ap` ($var fold0 v0)) `$ap` ($var fold1 v1)
  where
    fold0 _ f = f
    fold1 map f = [| $map $f |]
meth3 v2 = $res (($op "meth2" meth2) `$ap` ($var fold2 v2))
  where
    fold2 map f = [| $map ($map $f) |]

Constructors

Derivator 

Fields

idDeriv :: Derivator Source #

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

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

contains :: Data d => Name -> d -> Bool Source #

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

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

Orphan instances

Lift Fixity Source # 
Instance details

Methods

lift :: Fixity -> Q Exp #

liftTyped :: Fixity -> Q (TExp Fixity) #

Lift FixityDirection Source # 
Instance details