Safe Haskell | None |
---|---|
Language | Haskell2010 |
Test.Speculate.Expr.Ground
- grounds :: Instances -> Expr -> [Expr]
- groundBinds :: Instances -> Expr -> [Binds]
- groundAndBinds :: Instances -> Expr -> [(Binds, Expr)]
- equal :: Instances -> Int -> Expr -> Expr -> Bool
- lessOrEqual :: Instances -> Int -> Expr -> Expr -> Bool
- less :: Instances -> Int -> Expr -> Expr -> Bool
- inequal :: Instances -> Int -> Expr -> Expr -> Bool
- true :: Instances -> Int -> Expr -> Bool
- false :: Instances -> Int -> Expr -> Bool
- condEqual :: Instances -> Int -> Expr -> Expr -> Expr -> Bool
- condEqualM :: Instances -> Int -> Int -> Expr -> Expr -> Expr -> Bool
- trueBinds :: Instances -> Int -> Expr -> [Binds]
- trueRatio :: Instances -> Int -> Expr -> Ratio Int
Documentation
grounds :: Instances -> Expr -> [Expr] Source #
List all possible valuations of an expression (potentially infinite). In pseudo-Haskell:
take 3 $ grounds preludeInstances ((x + x) + y) == [(0 + 0) + 0, (0 + 0) + 1, (1 + 1) + 0]
groundBinds :: Instances -> Expr -> [Binds] Source #
List all possible variable bindings to an expression
take 3 $ groundBinds preludeInstances ((x + x) + y) == [ [("x",0),("y",0)] , [("x",0),("y",1)] , [("x",1),("y",0)] ]
groundAndBinds :: Instances -> Expr -> [(Binds, Expr)] Source #
List all possible variable bindings and valuations to an expression
groundAndBinds ti e == zipWith (,) (grounds ti e) (groundBinds ti e)
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
.
true :: Instances -> Int -> Expr -> Bool Source #
Is a boolean expression true for all variable assignments?
false :: Instances -> Int -> 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