Safe Haskell | Safe-Infered |
---|
These small short-named functions are intended to make the construction of abstranct syntax trees less tedious.
- applyWith, foldr1With, foldl1With :: 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, nil, false :: Valcon a => a
- hNil', hZero' :: Type
- unit :: Exp
- id' :: Exp
- cons :: Valcon a => a -> a -> a
- box :: Valcon a => a -> a
- return', const' :: Exp -> Exp
- hSucc' :: Type -> Type
- (==:), (>:), ap', (.:), (>>:), (>>=:), (++:), (&&:) :: Exp -> Exp -> Exp
- hCons' :: Type -> Type -> Type
- (&&::), (.::), sequence__, (>>::), (++::) :: [Exp] -> Exp
- liftmk :: Exp -> [Exp] -> Exp
Special folds for the guessing
applyWith, foldr1With, foldl1With :: Exp -> [Exp] -> ExpSource
Syntax elements
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
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.
This class is used to overload literal construction based on the type of the literal.
Constructor abstraction
ctv :: Valcon a => CtorDef -> Char -> [a]Source
Make a list of variables, one for each argument to a constructor