Safe Haskell | None |
---|---|
Language | Haskell2010 |
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]
- sigN :: String -> Type -> Dec
- funN :: String -> [Clause] -> Dec
- class Eq nm => NameLike nm where
- class Valcon a where
- app :: Exp -> [Exp] -> Exp
- class LitC a where
- 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
- true :: Valcon a => a
- false :: Valcon a => a
- nil :: Valcon a => a
- hNil' :: Type
- hZero' :: Type
- unit :: Exp
- id' :: Exp
- 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
Syntax elements
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
Pattern vs Value abstraction
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.
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.
Lift a TH Lit
Tupling
Listing
This class is used to overload literal construction based on the type of the literal.
Instances
LitC Char Source # | |
LitC Integer Source # | |
LitC () Source # | |
Defined in Language.Haskell.TH.Helper | |
LitC a => LitC [a] Source # | |
Defined in Language.Haskell.TH.Helper | |
(LitC a, LitC b) => LitC (a, b) Source # | |
Defined in Language.Haskell.TH.Helper | |
(LitC a, LitC b, LitC c) => LitC (a, b, c) Source # | |
Defined in Language.Haskell.TH.Helper |
Constructor abstraction
ctv :: Valcon a => CtorDef -> Char -> [a] Source #
Make a list of variables, one for each argument to a constructor
Lift a constructor over a fixed number of arguments.
Pre-lifted versions of common operations
(&&::) :: [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)