derive-2.0.0: A program and library to derive instances for data typesSource codeContentsIndex
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
foldl1With :: Exp -> [Exp] -> Exp
foldr1With :: Exp -> [Exp] -> Exp
applyWith :: 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]
sigN :: String -> Type -> Dec
funN :: String -> [Clause] -> Dec
class Eq nm => NameLike nm where
toName :: nm -> Name
class Valcon a where
lK :: NameLike nm => nm -> [a] -> a
vr :: NameLike nm => nm -> 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 :: (NameLike nm, Valcon a) => nm -> a
l1 :: (NameLike nm, Valcon a) => nm -> a -> a
l2 :: (NameLike nm, Valcon a) => nm -> a -> a -> a
false :: Valcon a => a
nil :: Valcon a => a
true :: Valcon a => a
hZero' :: Type
hNil' :: Type
cons :: Valcon a => a -> a -> a
box :: Valcon a => a -> a
const' :: Exp -> Exp
return' :: Exp -> Exp
hSucc' :: Type -> Type
(&&:) :: Exp -> Exp -> Exp
(++:) :: Exp -> Exp -> Exp
(>>=:) :: Exp -> Exp -> Exp
(>>:) :: Exp -> Exp -> Exp
(.:) :: Exp -> Exp -> Exp
ap' :: Exp -> Exp -> Exp
(>:) :: Exp -> Exp -> Exp
(==:) :: Exp -> Exp -> Exp
hCons' :: Type -> Type -> Type
(++::) :: [Exp] -> Exp
(>>::) :: [Exp] -> Exp
sequence__ :: [Exp] -> Exp
(.::) :: [Exp] -> Exp
(&&::) :: [Exp] -> Exp
liftmk :: Exp -> [Exp] -> Exp
Special folds for the guessing
foldl1With :: Exp -> [Exp] -> ExpSource
foldr1With :: Exp -> [Exp] -> ExpSource
applyWith :: Exp -> [Exp] -> ExpSource
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
(->:) :: String -> 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
instance_default :: String -> DataDef -> [Dec] -> DecSource
instance_context :: [String] -> String -> DataDef -> [Dec] -> DecSource
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
show/hide Instances
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
show/hide Instances
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
show/hide 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
dataVars :: DataDef -> [Type]Source
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
false :: Valcon a => aSource
nil :: Valcon a => aSource
true :: Valcon a => aSource
hZero' :: TypeSource
hNil' :: TypeSource
cons :: Valcon a => a -> a -> aSource
box :: Valcon a => a -> aSource
const' :: Exp -> ExpSource
return' :: Exp -> ExpSource
hSucc' :: Type -> TypeSource
(&&:) :: Exp -> Exp -> ExpSource
(++:) :: Exp -> Exp -> ExpSource
(>>=:) :: Exp -> Exp -> ExpSource
(>>:) :: Exp -> Exp -> ExpSource
(.:) :: Exp -> Exp -> ExpSource
ap' :: Exp -> Exp -> ExpSource
(>:) :: Exp -> Exp -> ExpSource
(==:) :: Exp -> Exp -> ExpSource
hCons' :: Type -> Type -> TypeSource
(++::) :: [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
sequence__ :: [Exp] -> ExpSource
(.::) :: [Exp] -> ExpSource
(&&::) :: [Exp] -> ExpSource
liftmk :: Exp -> [Exp] -> ExpSource
K-way liftM
Produced by Haddock version 2.4.2