Safe Haskell | None |
---|---|
Language | Haskell2010 |
Test.Speculate.Expr.Core
Contents
- data Expr
- constant :: Typeable a => String -> a -> Expr
- showConstant :: (Typeable a, Show a) => a -> Expr
- var :: (Listable a, Typeable a) => String -> a -> Expr
- hole :: (Listable a, Typeable a) => a -> Expr
- holeOfTy :: TypeRep -> Expr
- ($$) :: Expr -> Expr -> Maybe Expr
- evaluate :: Typeable a => Expr -> Maybe a
- eval :: Typeable a => a -> Expr -> a
- typ :: Expr -> TypeRep
- etyp :: Expr -> Either Expr TypeRep
- typeCorrect :: Expr -> Bool
- arity :: Expr -> Int
- holes :: Expr -> [TypeRep]
- vars :: Expr -> [(TypeRep, String)]
- consts :: Expr -> [Expr]
- atomicConstants :: Expr -> [Expr]
- subexprs :: Expr -> [Expr]
- subexprsV :: Expr -> [Expr]
- isSub :: Expr -> Expr -> Bool
- hasVar :: Expr -> Bool
- unfoldApp :: Expr -> [Expr]
- isConstantNamed :: Expr -> String -> Bool
- lengthE :: Expr -> Int
- depthE :: Expr -> Int
- countVar :: TypeRep -> String -> Expr -> Int
- countVars :: Expr -> [(TypeRep, String, Int)]
- unrepeatedVars :: Expr -> Bool
- isAssignment :: Expr -> Bool
- lexicompare :: Expr -> Expr -> Ordering
- lexicompareBy :: (Expr -> Expr -> Ordering) -> Expr -> Expr -> Ordering
- compareComplexity :: Expr -> Expr -> Ordering
- compareComplexityThen :: (Expr -> Expr -> Ordering) -> Expr -> Expr -> Ordering
- falseE :: Expr
- showExpr :: Expr -> String
- showPrecExpr :: Int -> Expr -> String
- showsPrecExpr :: Int -> Expr -> String -> String
- showOpExpr :: String -> Expr -> String
- showsOpExpr :: String -> Expr -> String -> String
- eqExprCommuting :: [Expr] -> Expr -> Expr -> Bool
Documentation
An encoded Haskell functional-application expression for use by Speculate.
Smart constructors
constant :: Typeable a => String -> a -> Expr Source #
Encode a constant Haskell expression for use by Speculate.
It takes a string representation of a value and a value, returning an
Expr
. Examples:
constant "0" 0 constant "'a'" 'a' constant "True" True constant "id" (id :: Int -> Int) constant "(+)" ((+) :: Int -> Int -> Int) constant "sort" (sort :: [Bool] -> [Bool])
var :: (Listable a, Typeable a) => String -> a -> Expr Source #
var "x" (undefined :: Ty)
returns a variable of type Ty
named "x"
hole :: (Listable a, Typeable a) => a -> Expr Source #
(intended for advanced users)
hole (undefined :: Ty)
returns a hole of type Ty
By convention, a Hole is a variable named with the empty string.
Smart destructors
eval :: Typeable a => a -> Expr -> a Source #
Evaluates an expression when possible (correct type, no holes). Returns a default value otherwise.
typ :: Expr -> TypeRep Source #
The type of an expression. This raises errors, but those should not happen if expressions are smart-constructed.
etyp :: Expr -> Either Expr TypeRep Source #
etyp returns either: the Right type a Left expression with holes with the structure of the I'll typed expression
Queries
typeCorrect :: Expr -> Bool Source #
consts :: Expr -> [Expr] Source #
List terminal constants in an expression. This does not repeat values.
atomicConstants :: Expr -> [Expr] Source #
subexprs :: Expr -> [Expr] Source #
Non-variable sub-expressions of an expression
This includes the expression itself
subexprsV :: Expr -> [Expr] Source #
Sub-expressions of an expression including variables and the expression itself.
unfoldApp :: Expr -> [Expr] Source #
Unfold function application:
(((f :$ e1) :$ e2) :$ e3) = [f,e1,e2,e3]
Properties of expressions
countVar :: TypeRep -> String -> Expr -> Int Source #
Number of occurrences of a given variable name. In term rewriting terms: |s|_x
unrepeatedVars :: Expr -> Bool Source #
isAssignment :: Expr -> Bool Source #
lexicompare :: Expr -> Expr -> Ordering Source #
Compare two expressiosn lexicographically
1st their type arity; 2nd their type; 3rd var < constants < apps 4th lexicographic order on names
compareComplexity :: Expr -> Expr -> Ordering Source #
Compares two expressions first by their complexity: 1st length; 2nd number of variables (more variables is less complex); 3nd sum of number of variable occurrences; 4th their depth; 5th lexicompare.
compareComplexityThen :: (Expr -> Expr -> Ordering) -> Expr -> Expr -> Ordering Source #
Compares two expressions first by their complexity:
1st length;
2nd number of variables (more variables is less complex);
3nd sum of number of variable occurrences;
4th their depth;
5th normal compare
.