derive-0.1: A program and library to derive instances for data typesContentsIndex
Language.Haskell.TH.Helper
Contents
Special folds for the guessing
Syntax elements
Pattern vs Value abstraction
Constructor abstraction
Lift a constructor over a fixed number of arguments.
Pre-lifted versions of common operations
Description
These small short-named functions are intended to make the construction of abstranct syntax trees less tedious.
Synopsis
applyWith :: Exp -> [Exp] -> Exp
foldl1With :: Exp -> [Exp] -> Exp
foldr1With :: Exp -> [Exp] -> Exp
sclause :: [Pat] -> Exp -> Clause
defclause :: Int -> Exp -> Clause
sval :: Pat -> Exp -> Dec
case' :: Exp -> [(Pat, Exp)] -> Exp
(->:) :: String -> Exp -> Exp
instance_none :: String -> DataDef -> [Dec] -> Dec
instance_default :: String -> DataDef -> [Dec] -> Dec
instance_context :: [String] -> String -> DataDef -> [Dec] -> Dec
simple_instance :: String -> DataDef -> [Dec] -> [Dec]
generic_instance :: String -> DataDef -> [Type] -> [Dec] -> [Dec]
funN :: String -> [Clause] -> Dec
class Valcon a where
lK :: String -> [a] -> a
vr :: String -> a
raw_lit :: Lit -> a
tup :: [a] -> a
lst :: [a] -> a
app :: Exp -> [Exp] -> Exp
class LitC a where
lit :: Valcon p => a -> p
dataVars :: DataDef -> [Type]
vars :: Valcon a => Char -> Int -> [a]
vrn :: Valcon a => Char -> Int -> a
ctv :: Valcon a => CtorDef -> Char -> [a]
ctp :: Valcon a => CtorDef -> Char -> a
ctc :: Valcon a => CtorDef -> a
l0 :: Valcon a => String -> a
l1 :: Valcon a => String -> a -> a
l2 :: Valcon a => String -> a -> a -> a
true :: Valcon a => a
false :: Valcon a => a
nil :: Valcon a => a
hNil' :: Type
hZero' :: Type
cons :: Valcon a => a -> a -> a
box :: Valcon a => a -> a
return' :: Exp -> Exp
const' :: Exp -> Exp
hSucc' :: Type -> Type
(==:) :: Exp -> Exp -> Exp
(&&:) :: Exp -> Exp -> Exp
(++:) :: Exp -> Exp -> Exp
(>>=:) :: Exp -> Exp -> Exp
(>>:) :: Exp -> Exp -> Exp
(.:) :: Exp -> Exp -> Exp
ap' :: Exp -> Exp -> Exp
(>:) :: Exp -> Exp -> Exp
hCons' :: Type -> Type -> Type
(&&::) :: [Exp] -> Exp
(++::) :: [Exp] -> Exp
(>>::) :: [Exp] -> Exp
sequence__ :: [Exp] -> Exp
(.::) :: [Exp] -> Exp
liftmk :: Exp -> [Exp] -> Exp
Special folds for the guessing
applyWith :: Exp -> [Exp] -> Exp
foldl1With :: Exp -> [Exp] -> Exp
foldr1With :: Exp -> [Exp] -> Exp
Syntax elements
sclause :: [Pat] -> Exp -> Clause
A simple clause, without where or guards.
defclause :: Int -> Exp -> Clause
A default clause with N arguments.
sval :: Pat -> Exp -> Dec
A simple Val clause
case' :: Exp -> [(Pat, Exp)] -> Exp
(->:) :: String -> Exp -> Exp
instance_none :: String -> DataDef -> [Dec] -> Dec
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
instance_default :: String -> DataDef -> [Dec] -> Dec
instance_context :: [String] -> String -> DataDef -> [Dec] -> Dec
simple_instance :: String -> DataDef -> [Dec] -> [Dec]
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]
Build an instance of a class for a data type, using the class at the given types
funN :: String -> [Clause] -> Dec
Build a fundecl with a string name
Pattern vs Value abstraction
class Valcon a where
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 :: String -> [a] -> a
Build an application node, with a name for a head and a provided list of arguments.
vr :: String -> a
Reference a named variable.
raw_lit :: Lit -> a
Lift a TH Lit
tup :: [a] -> a
Tupling
lst :: [a] -> a
Listing
show/hide Instances
app :: Exp -> [Exp] -> Exp
Build an application node without a given head
class LitC a where
This class is used to overload literal construction based on the type of the literal.
Methods
lit :: Valcon p => a -> p
show/hide Instances
LitC Char
LitC Integer
LitC ()
(LitC a, LitC b) => LitC (a, b)
(LitC a, LitC b, LitC c) => LitC (a, b, c)
LitC a => LitC [a]
Constructor abstraction
dataVars :: DataDef -> [Type]
vars :: Valcon a => Char -> Int -> [a]
Common pattern: list of a familiy of variables
vrn :: Valcon a => Char -> Int -> a
Variable based on a letter + number
ctv :: Valcon a => CtorDef -> Char -> [a]
Make a list of variables, one for each argument to a constructor
ctp :: Valcon a => CtorDef -> Char -> a
Make a simple pattern to bind a constructor
ctc :: Valcon a => CtorDef -> a
Reference the constructor itself
Lift a constructor over a fixed number of arguments.
l0 :: Valcon a => String -> a
l1 :: Valcon a => String -> a -> a
l2 :: Valcon a => String -> a -> a -> a
Pre-lifted versions of common operations
true :: Valcon a => a
false :: Valcon a => a
nil :: Valcon a => a
hNil' :: Type
hZero' :: Type
cons :: Valcon a => a -> a -> a
box :: Valcon a => a -> a
return' :: Exp -> Exp
const' :: Exp -> Exp
hSucc' :: Type -> Type
(==:) :: Exp -> Exp -> Exp
(&&:) :: Exp -> Exp -> Exp
(++:) :: Exp -> Exp -> Exp
(>>=:) :: Exp -> Exp -> Exp
(>>:) :: Exp -> Exp -> Exp
(.:) :: Exp -> Exp -> Exp
ap' :: Exp -> Exp -> Exp
(>:) :: Exp -> Exp -> Exp
hCons' :: Type -> Type -> Type
(&&::) :: [Exp] -> Exp
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
(>>::) :: [Exp] -> Exp
sequence__ :: [Exp] -> Exp
(.::) :: [Exp] -> Exp
liftmk :: Exp -> [Exp] -> Exp
K-way liftM
Produced by Haddock version 0.8