derive-2.5.13: A program and library to derive instances for data types

Safe HaskellNone

Language.Haskell.TH.Helper

Contents

Description

These small short-named functions are intended to make the construction of abstranct syntax trees less tedious.

Synopsis

Special folds for the guessing

Syntax elements

sclause :: [Pat] -> Exp -> ClauseSource

A simple clause, without where or guards.

defclause :: Int -> Exp -> ClauseSource

A default clause with N arguments.

sval :: Pat -> Exp -> DecSource

A simple Val clause

case' :: Exp -> [(Pat, Exp)] -> ExpSource

instance_none :: String -> DataDef -> [Dec] -> DecSource

We provide 3 standard instance constructors instance_default requires C for each free type variable instance_none requires no context instance_context requires a given context

simple_instance :: String -> DataDef -> [Dec] -> [Dec]Source

Build an instance of a class for a data type, using the heuristic that the type is itself required on all type arguments.

generic_instance :: String -> DataDef -> [Type] -> [Dec] -> [Dec]Source

Build an instance of a class for a data type, using the class at the given types

sigN :: String -> Type -> DecSource

Build a type signature declaration with a string name

funN :: String -> [Clause] -> DecSource

Build a fundecl with a string name

Pattern vs Value abstraction

class Eq nm => NameLike nm whereSource

Methods

toName :: nm -> NameSource

class Valcon a whereSource

The class used to overload lifting operations. To reduce code duplication, we overload the wrapped constructors (and everything else, but that's irrelevant) to work in patterns, expressions, and types.

Methods

lK :: NameLike nm => nm -> [a] -> aSource

Build an application node, with a name for a head and a provided list of arguments.

vr :: NameLike nm => nm -> aSource

Reference a named variable.

raw_lit :: Lit -> aSource

Lift a TH Lit

tup :: [a] -> aSource

Tupling

lst :: [a] -> aSource

Listing

app :: Exp -> [Exp] -> ExpSource

Build an application node without a given head

class LitC a whereSource

This class is used to overload literal construction based on the type of the literal.

Methods

lit :: Valcon p => a -> pSource

Instances

LitC Char 
LitC Integer 
LitC () 
LitC a => LitC [a] 
(LitC a, LitC b) => LitC (a, b) 
(LitC a, LitC b, LitC c) => LitC (a, b, c) 

Constructor abstraction

vars :: Valcon a => Char -> Int -> [a]Source

Common pattern: list of a familiy of variables

vrn :: Valcon a => Char -> Int -> aSource

Variable based on a letter + number

ctv :: Valcon a => CtorDef -> Char -> [a]Source

Make a list of variables, one for each argument to a constructor

ctp :: Valcon a => CtorDef -> Char -> aSource

Make a simple pattern to bind a constructor

ctc :: Valcon a => CtorDef -> aSource

Reference the constructor itself

Lift a constructor over a fixed number of arguments.

l0 :: (NameLike nm, Valcon a) => nm -> aSource

l1 :: (NameLike nm, Valcon a) => nm -> a -> aSource

l2 :: (NameLike nm, Valcon a) => nm -> a -> a -> aSource

Pre-lifted versions of common operations

true :: Valcon a => aSource

nil :: Valcon a => aSource

cons :: Valcon a => a -> a -> aSource

box :: Valcon a => a -> aSource

ap' :: Exp -> Exp -> ExpSource

(&&::) :: [Exp] -> ExpSource

Build a chain of expressions, with an appropriate terminal sequence__ does not require a unit at the end (all others are optimised automatically)

(.::) :: [Exp] -> ExpSource

Build a chain of expressions, with an appropriate terminal sequence__ does not require a unit at the end (all others are optimised automatically)

sequence__ :: [Exp] -> ExpSource

Build a chain of expressions, with an appropriate terminal sequence__ does not require a unit at the end (all others are optimised automatically)

(>>::) :: [Exp] -> ExpSource

Build a chain of expressions, with an appropriate terminal sequence__ does not require a unit at the end (all others are optimised automatically)

(++::) :: [Exp] -> ExpSource

Build a chain of expressions, with an appropriate terminal sequence__ does not require a unit at the end (all others are optimised automatically)

liftmk :: Exp -> [Exp] -> ExpSource

K-way liftM