Safe Haskell | None |
---|---|
Language | Haskell2010 |
Efficient size-based search for values satisfying/falsifying a lazy boolean predicate.
Predicates are typically of type a -> Bool
, although an alternative boolean type called Cool
is provided and using it may give faster searches.
See Control.Enumerable for defining default enumerations of data types (required for searching).
Synopsis
- search :: (Enumerable a, Coolean cool) => Int -> (a -> cool) -> IO [a]
- sat :: (Enumerable a, Coolean cool) => Int -> (a -> cool) -> Bool
- ctrex :: (Coolean cool, Enumerable a) => Int -> (a -> cool) -> IO (Either Integer a)
- searchRaw :: (Enumerable a, Coolean cool) => Int -> (a -> cool) -> IO [(Bool, a)]
- usearch :: Enumerable a => Int -> (a -> Bool) -> [a]
- test :: (Coolean cool, Enumerable a, Show a) => (a -> cool) -> IO ()
- testTime :: (Coolean cool, Enumerable a, Show a) => Int -> (a -> cool) -> IO ()
- data Options
- sat' :: (Enumerable a, Coolean cool) => Options -> Int -> (a -> cool) -> Bool
- search' :: (Enumerable a, Coolean cool) => Options -> Int -> (a -> cool) -> IO [a]
- ctrex' :: (Coolean cool, Enumerable a) => Options -> Int -> (a -> cool) -> IO (Either Integer a)
- searchRaw' :: (Enumerable a, Coolean cool) => Options -> Int -> (a -> cool) -> IO [(Bool, a)]
- test' :: (Coolean cool, Enumerable a, Show a) => Options -> (a -> cool) -> IO ()
- testTime' :: (Coolean cool, Enumerable a, Show a) => Options -> Int -> (a -> cool) -> IO ()
- (&&&) :: (Coolean a, Coolean b) => a -> b -> Cool
- (|||) :: (Coolean a, Coolean b) => a -> b -> Cool
- (==>) :: (Coolean a, Coolean b) => a -> b -> Cool
- nott :: Coolean a => a -> Cool
- true :: Cool
- false :: Cool
- data Cool
- class Coolean b
- module Control.Enumerable
Searching
search :: (Enumerable a, Coolean cool) => Int -> (a -> cool) -> IO [a] Source #
Lazily finds all (non-isomorphic) values of or below a given size that satisfy a predicate.
sat :: (Enumerable a, Coolean cool) => Int -> (a -> cool) -> Bool Source #
Is there a value of or below a given size that satisfies this predicate?
ctrex :: (Coolean cool, Enumerable a) => Int -> (a -> cool) -> IO (Either Integer a) Source #
Find a counterexample to the given predicate, of or below a given size. If no counterexample is found, the number of performed executions of the predicate is returned.
searchRaw :: (Enumerable a, Coolean cool) => Int -> (a -> cool) -> IO [(Bool, a)] Source #
Lazily finds all non-isomorphic (w.r.t. laziness) inputs to a predicate and returns them along with the result of the predicate.
usearch :: Enumerable a => Int -> (a -> Bool) -> [a] Source #
Unsafe version of search. Non-deterministic for some predicates.
Testing properties
test :: (Coolean cool, Enumerable a, Show a) => (a -> cool) -> IO () Source #
SmallCheck-like test driver. Tests a property with gradually increasing sizes until a conunterexample is found. For each size, it shows the worst case number of tests required (if the predicate is fully eager).
testTime :: (Coolean cool, Enumerable a, Show a) => Int -> (a -> cool) -> IO () Source #
Stop testing after a given number of seconds
Options for parallel conjunction
Options for parallel conjunction strategies. Only matters for
predicates using the Cool
data type instead of Bool.
D | Sequential |
O | Optimal Short-circuiting |
F | Parallel (fair) |
OF | Optimal Short-circuiting and fairness |
OS | Optimal Short-circuiting and choice-subset detection |
OSF | Subset choice short-circuiting |
Instances
Enum Options Source # | |
Eq Options Source # | |
Read Options Source # | |
Show Options Source # | |
ctrex' :: (Coolean cool, Enumerable a) => Options -> Int -> (a -> cool) -> IO (Either Integer a) Source #
searchRaw' :: (Enumerable a, Coolean cool) => Options -> Int -> (a -> cool) -> IO [(Bool, a)] Source #
testTime' :: (Coolean cool, Enumerable a, Show a) => Options -> Int -> (a -> cool) -> IO () Source #
Deep embedded boolean type
Concurrent booleans. Writing properties with the Cool data type often yields faster searches compared to Bool.
Provides better interoperability between Bool and Cool by overloading operators.
Re-exported
module Control.Enumerable