Copyright | (c) 2016-2024 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module is part of Speculate.
Generate and evaluate ground values of expressions.
Synopsis
- grounds :: (Expr -> [[Expr]]) -> Expr -> [Expr]
- groundBinds :: (Expr -> [[Expr]]) -> Expr -> [Binds]
- equal :: Instances -> Int -> Expr -> Expr -> Bool
- lessOrEqual :: Instances -> Int -> Expr -> Expr -> Bool
- less :: Instances -> Int -> Expr -> Expr -> Bool
- inequal :: Instances -> Int -> Expr -> Expr -> Bool
- isTrue :: (Expr -> [Expr]) -> Expr -> Bool
- isFalse :: (Expr -> [Expr]) -> Expr -> Bool
- condEqual :: Instances -> Int -> Expr -> Expr -> Expr -> Bool
- condEqualM :: Instances -> Int -> Int -> Expr -> Expr -> Expr -> Bool
- trueRatio :: Instances -> Int -> Expr -> Ratio Int
- constify :: Expr -> Expr
- constifications :: Expr -> [Expr]
Documentation
groundBinds :: (Expr -> [[Expr]]) -> Expr -> [Binds] Source #
List all possible variable bindings to an expression
take 3 $ groundBinds (lookupTiers preludeInstances) ((x + x) + y) == [ [("x",0),("y",0)] , [("x",0),("y",1)] , [("x",1),("y",0)] ]
equal :: Instances -> Int -> Expr -> Expr -> Bool Source #
Are two expressions equal for a given number of tests?
lessOrEqual :: Instances -> Int -> Expr -> Expr -> Bool Source #
Are two expressions less-than-or-equal for a given number of tests?
less :: Instances -> Int -> Expr -> Expr -> Bool Source #
Are two expressions less-than for a given number of tests?
inequal :: Instances -> Int -> Expr -> Expr -> Bool Source #
Are two expressions inequal for *all* variable assignments?
Note this is different than not . equal
.
isTrue :: (Expr -> [Expr]) -> Expr -> Bool Source #
Is a boolean expression true for all variable assignments?
isFalse :: (Expr -> [Expr]) -> Expr -> Bool Source #
Is an expression ALWAYS false? This is *NOT* the same as not true.
condEqual :: Instances -> Int -> Expr -> Expr -> Expr -> Bool Source #
Are two expressions equal under a given condition for a given number of tests?
condEqualM :: Instances -> Int -> Int -> Expr -> Expr -> Expr -> Bool Source #
Are two expressions equal under a given condition for a given number of tests and a minimum amount of tests
trueRatio :: Instances -> Int -> Expr -> Ratio Int Source #
Under a maximum number of tests, returns the ratio for which an expression holds true.
constify :: Expr -> Expr Source #
O(n). Turn all variables in an expression into fake constants.
> vars (xx -+- yy) [x :: Int, y :: Int]
> constify (xx -+- yy) x + y :: Int
> vars (constify (xx -+- yy)) []
constifications :: Expr -> [Expr] Source #
O(n).
Returns a list with all possible permutations
of variables in the given expression,
all constify
ed into fake constants.
> constifications (xx -+- yy) [ x + y :: Int , y + x :: Int ]
> constifications (xx -:- xxs) [ x:xs :: [Int] ]
Types are respected.
This is useful for checking ground-joinability in term rewriting.