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

Safe HaskellNone
LanguageHaskell2010

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 -> Clause Source #

A simple clause, without where or guards.

defclause :: Int -> Exp -> Clause Source #

A default clause with N arguments.

sval :: Pat -> Exp -> Dec Source #

A simple Val clause

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

instance_none :: String -> DataDef -> [Dec] -> Dec Source #

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 -> Dec Source #

Build a type signature declaration with a string name

funN :: String -> [Clause] -> Dec Source #

Build a fundecl with a string name

Pattern vs Value abstraction

class Eq nm => NameLike nm where Source #

Methods

toName :: nm -> Name Source #

Instances
NameLike Name Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

toName :: Name -> Name Source #

NameLike String Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

toName :: String -> Name Source #

class Valcon a where Source #

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] -> a Source #

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

vr :: NameLike nm => nm -> a Source #

Reference a named variable.

raw_lit :: Lit -> a Source #

Lift a TH Lit

tup :: [a] -> a Source #

Tupling

lst :: [a] -> a Source #

Listing

Instances
Valcon Exp Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

lK :: NameLike nm => nm -> [Exp] -> Exp Source #

vr :: NameLike nm => nm -> Exp Source #

raw_lit :: Lit -> Exp Source #

tup :: [Exp] -> Exp Source #

lst :: [Exp] -> Exp Source #

Valcon Pat Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

lK :: NameLike nm => nm -> [Pat] -> Pat Source #

vr :: NameLike nm => nm -> Pat Source #

raw_lit :: Lit -> Pat Source #

tup :: [Pat] -> Pat Source #

lst :: [Pat] -> Pat Source #

Valcon Type Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

lK :: NameLike nm => nm -> [Type] -> Type Source #

vr :: NameLike nm => nm -> Type Source #

raw_lit :: Lit -> Type Source #

tup :: [Type] -> Type Source #

lst :: [Type] -> Type Source #

app :: Exp -> [Exp] -> Exp Source #

Build an application node without a given head

class LitC a where Source #

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

Methods

lit :: Valcon p => a -> p Source #

Instances
LitC Char Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

lit :: Valcon p => Char -> p Source #

LitC Integer Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

lit :: Valcon p => Integer -> p Source #

LitC () Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

lit :: Valcon p => () -> p Source #

LitC a => LitC [a] Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

lit :: Valcon p => [a] -> p Source #

(LitC a, LitC b) => LitC (a, b) Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

lit :: Valcon p => (a, b) -> p Source #

(LitC a, LitC b, LitC c) => LitC (a, b, c) Source # 
Instance details

Defined in Language.Haskell.TH.Helper

Methods

lit :: Valcon p => (a, b, c) -> p Source #

Constructor abstraction

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

Common pattern: list of a familiy of variables

vrn :: Valcon a => Char -> Int -> a Source #

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 -> a Source #

Make a simple pattern to bind a constructor

ctc :: Valcon a => CtorDef -> a Source #

Reference the constructor itself

Lift a constructor over a fixed number of arguments.

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

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

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

Pre-lifted versions of common operations

true :: Valcon a => a Source #

false :: Valcon a => a Source #

nil :: Valcon a => a Source #

cons :: Valcon a => a -> a -> a Source #

box :: Valcon a => a -> a Source #

(==:) :: Exp -> Exp -> Exp Source #

(&&:) :: Exp -> Exp -> Exp Source #

(++:) :: Exp -> Exp -> Exp Source #

(>>:) :: Exp -> Exp -> Exp Source #

(.:) :: Exp -> Exp -> Exp Source #

ap' :: Exp -> Exp -> Exp Source #

(>:) :: Exp -> Exp -> Exp Source #

(&&::) :: [Exp] -> Exp Source #

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

(++::) :: [Exp] -> Exp Source #

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

(>>::) :: [Exp] -> Exp Source #

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] -> Exp Source #

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

(.::) :: [Exp] -> Exp Source #

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] -> Exp Source #

K-way liftM