quickspec-0.9.6: Equational laws for free!
Test.QuickSpec.Term
Description
Terms and evaluation.
data Symbol Source
Constructors
Fields
Instances
symbol :: Typeable a => String -> Int -> a -> SymbolSource
data Term Source
showOp :: String -> StringSource
isOp :: String -> BoolSource
isUndefined :: Term -> BoolSource
symbols :: Term -> [Symbol]Source
depth :: Term -> IntSource
size :: Int -> Term -> IntSource
holes :: Term -> [(Symbol, Int)]Source
functor :: Term -> SymbolSource
args :: Term -> [Term]Source
funs :: Term -> [Symbol]Source
vars :: Term -> [Symbol]Source
mapVars :: (Symbol -> Symbol) -> Term -> TermSource
mapConsts :: (Symbol -> Symbol) -> Term -> TermSource
data Expr a Source
data Atom a Source
data PGen a Source
pgen :: Gen a -> PGen aSource
type Strategy = forall a. Symbol -> PGen a -> Gen aSource
newtype Variable a Source
newtype Constant a Source
mapVariable :: (Symbol -> Symbol) -> Variable a -> Variable aSource
mapConstant :: (Symbol -> Symbol) -> Constant a -> Constant aSource
newtype Valuation Source
promoteVal :: (forall a. Variable a -> Gen a) -> Gen ValuationSource
valuation :: Strategy -> Gen ValuationSource
var :: Variable a -> Expr aSource
con :: Constant a -> Expr aSource
app :: Expr (a -> b) -> Expr a -> Expr bSource