Copyright | (c) 2021-2025 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | None |
Language | Haskell2010 |
Conjure
Description
A library for Conjuring function implementations from tests or partial definitions. (a.k.a.: functional inductive programming)
Step 1: declare your partial function
factorial :: Int -> Int factorial 2 = 2 factorial 3 = 6 factorial 4 = 24
Step 2: declare a list with the potential building blocks:
ingredients :: [Ingredient] ingredients = [ con (0::Int) , con (1::Int) , fun "+" ((+) :: Int -> Int -> Int) , fun "*" ((*) :: Int -> Int -> Int) , fun "-" ((-) :: Int -> Int -> Int) ]
Step 3: call conjure
and see your generated function:
> conjure "factorial" factorial ingredients factorial :: Int -> Int -- 0.1s, testing 4 combinations of argument values -- 0.8s, pruning with 27/65 rules -- 0.8s, 3 candidates of size 1 -- 0.9s, 3 candidates of size 2 -- 0.9s, 7 candidates of size 3 -- 0.9s, 8 candidates of size 4 -- 0.9s, 28 candidates of size 5 -- 0.9s, 35 candidates of size 6 -- 0.9s, 167 candidates of size 7 -- 0.9s, tested 95 candidates factorial 0 = 1 factorial x = x * factorial (x - 1)
The above example takes less than a second to run in a modern laptop.
Factorial is discovered from scratch through a search. We prune the search space using properties discovered from the results of testing.
Conjure is not limited to integers, it works for functions over algebraic data types too. See:
take' :: Int -> [a] -> [a] take' 0 [x] = [] take' 1 [x] = [x] take' 0 [x,y] = [] take' 1 [x,y] = [x] take' 2 [x,y] = [x,y] take' 3 [x,y] = [x,y]
> conjure "take" (take' :: Int -> [A] -> [A]) > [ con (0 :: Int) > , con (1 :: Int) > , con ([] :: [A]) > , fun ":" ((:) :: A -> [A] -> [A]) > , fun "-" ((-) :: Int -> Int -> Int) > ] take :: Int -> [A] -> [A] -- testing 153 combinations of argument values -- pruning with 4/7 rules -- ... ... ... ... ... ... -- 0.4s, 6 candidates of size 8 -- 0.4s, 5 candidates of size 9 -- 0.4s, tested 15 candidates take 0 xs = [] take x [] = [] take x (y:xs) = y:take (x - 1) xs
The above example also takes less than a second to run in a modern laptop. The selection of functions in the list of ingredients was minimized to what was absolutely needed here. With a larger collection as ingredients YMMV.
Conjure works for user-defined algebraic data types too,
given that they are made instances of the Conjurable
typeclass.
For types without data invariants,
it should be enough to call deriveConjurable
to create an instance using TH.
Synopsis
- conjure :: Conjurable f => String -> f -> [Ingredient] -> IO ()
- type Ingredient = (Expr, Reification)
- con :: (Conjurable a, Show a) => a -> Ingredient
- unfun :: (Conjurable a, Show a) => a -> Ingredient
- fun :: Conjurable a => String -> a -> Ingredient
- guard :: Ingredient
- iif :: Conjurable a => a -> Ingredient
- ordcase :: Conjurable a => a -> Ingredient
- maxTests :: Int -> Ingredient
- target :: Int -> Ingredient
- maxSize :: Int -> Ingredient
- conjureFromSpec :: Conjurable f => String -> (f -> Bool) -> [Ingredient] -> IO ()
- class (Typeable a, Name a) => Conjurable a where
- conjureEquality :: a -> Maybe Expr
- conjureTiers :: a -> Maybe [[Expr]]
- conjureSubTypes :: a -> Reification
- conjureCases :: a -> [Expr]
- conjureSize :: a -> Int
- conjureExpress :: a -> Expr -> Expr
- data Expr
- val :: (Typeable a, Show a) => a -> Expr
- value :: Typeable a => String -> a -> Expr
- reifyExpress :: (Express a, Show a) => a -> Expr -> Expr
- reifyEquality :: (Eq a, Typeable a) => a -> Maybe Expr
- reifyTiers :: (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
- conjureType :: Conjurable a => a -> Reification
- class Name a where
- class (Show a, Typeable a) => Express a where
- deriveConjurable :: Name -> DecsQ
- deriveConjurableIfNeeded :: Name -> DecsQ
- deriveConjurableCascading :: Name -> DecsQ
- data Results = Results {
- implementationss :: [[Defn]]
- candidatess :: [[Defn]]
- bindings :: Defn
- theory :: Thy
- patternss :: [[Defn]]
- deconstructions :: [Expr]
- conjpure :: Conjurable f => String -> f -> [Ingredient] -> Results
- data A
- data B
- data C
- data D
- data E
- data F
- maxRecursions :: Int -> Ingredient
- maxEquationSize :: Int -> Ingredient
- maxSearchTests :: Int -> Ingredient
- maxDeconstructionSize :: Int -> Ingredient
- maxConstantSize :: Int -> Ingredient
- maxPatternSize :: Int -> Ingredient
- maxPatternDepth :: Int -> Ingredient
- showCandidates :: Ingredient
- showTheory :: Ingredient
- singlePattern :: Ingredient
- showTests :: Ingredient
- showPatterns :: Ingredient
- showDeconstructions :: Ingredient
- carryOn :: Ingredient
- dontRewrite :: Ingredient
- dontRequireDescent :: Ingredient
- omitAssortedPruning :: Ingredient
- omitEarlyTests :: Ingredient
- dontCopyBindings :: Ingredient
- nonAtomicNumbers :: Ingredient
- uniqueCandidates :: Ingredient
- type Prim = Ingredient
- pr :: (Conjurable a, Show a) => a -> Ingredient
- prim :: Conjurable a => String -> a -> Ingredient
Basic use
conjure :: Conjurable f => String -> f -> [Ingredient] -> IO () Source #
Conjures an implementation of a partially defined function.
Takes a String
with the name of a function,
a partially-defined function from a conjurable type,
and a list of building blocks encoded as Expr
s.
For example, given:
factorial :: Int -> Int factorial 2 = 2 factorial 3 = 6 factorial 4 = 24 ingredients :: [Ingredient] ingredients = [ con (0::Int) , con (1::Int) , fun "+" ((+) :: Int -> Int -> Int) , fun "*" ((*) :: Int -> Int -> Int) , fun "-" ((-) :: Int -> Int -> Int) ]
The conjure
function does the following:
> conjure "factorial" factorial ingredients factorial :: Int -> Int -- 0.1s, testing 4 combinations of argument values -- 0.8s, pruning with 27/65 rules -- ... ... ... ... ... ... -- 0.9s, 35 candidates of size 6 -- 0.9s, 167 candidates of size 7 -- 0.9s, tested 95 candidates factorial 0 = 1 factorial x = x * factorial (x - 1)
type Ingredient = (Expr, Reification) Source #
A single functional ingredient in conjuring.
Specify conjure ingredients with con
and fun
:
conjure "foo" foo [ con False , con True , con (0 :: Int) , con (1 :: Int) , ... , fun "&&" (&&) , fun "||" (||) , fun "+" ((+) :: Int -> Int -> Int) , fun "*" ((*) :: Int -> Int -> Int) , fun "-" ((-) :: Int -> Int -> Int) , ... ]
Ingredients may include arbitrary
constants (con
),
constructors (con
)
or functions (fun
).
These may be built-in or user defined.
Use con
on Show
instances
and fun
otherwise.
This is internally
an arbitrary atomic Expr
ession
paired with
a Reification
of type information.
con :: (Conjurable a, Show a) => a -> Ingredient Source #
unfun :: (Conjurable a, Show a) => a -> Ingredient Source #
Provided a Show
-able non-functional value to Conjure.
(cf. fun
)
conjure "foo" foo [ unfun False , unfun True , unfun (0 :: Int) , unfun (1 :: Int) , ... ]
Argument types have to be monomorphized, so use type bindings when applicable.
TODO: Make unfun
the standard way to create encode Show
values.
This is a replacement to con
.
In hindsight, con
is not such a great name:
con
structors may be fun
ctional after all!
fun :: Conjurable a => String -> a -> Ingredient Source #
Provides a functional value as an ingredient to Conjure.
To be used on values that are not Show
instances
such as functions.
(cf. unfun
, con
)
conjure "foo" foo [ ... , fun "&&" (&&) , fun "||" (||) , fun "+" ((+) :: Int -> Int -> Int) , fun "*" ((*) :: Int -> Int -> Int) , fun "-" ((-) :: Int -> Int -> Int) , ... ]
Argument types have to be monomorphized, so use type bindings when applicable.
guard :: Ingredient Source #
Provides a guard bound to the conjured function's return type.
Guards are only alllowed at the root fo the RHS.
last' :: [Int] -> Int last' [x] = x last' [x,y] = y last' [x,y,z] = z
> conjure "last" last' > [ con ([] :: [Int]) > , fun ":" ((:) :: Int -> [Int] -> [Int]) > , fun "null" (null :: [Int] -> Bool) > , guard > , fun "undefined" (undefined :: Int) > ] last :: [Int] -> Int -- 0.0s, testing 360 combinations of argument values -- 0.0s, pruning with 5/5 rules -- 0.0s, 1 candidates of size 1 -- 0.0s, 0 candidates of size 2 -- 0.0s, 0 candidates of size 3 -- 0.0s, 0 candidates of size 4 -- 0.0s, 0 candidates of size 5 -- 0.0s, 0 candidates of size 6 -- 0.0s, 4 candidates of size 7 -- 0.0s, tested 2 candidates last [] = undefined last (x:xs) | null xs = x | otherwise = last xs
iif :: Conjurable a => a -> Ingredient Source #
Provides an if condition bound to the given return type as a Conjure ingredient.
This should be used when one wants Conjure to consider if-expressions at all:
last' :: [Int] -> Int last' [x] = x last' [x,y] = y last' [x,y,z] = z
> conjure "last" last' [ con ([] :: [Int]) > , fun ":" ((:) :: Int -> [Int] -> [Int]) > , fun "null" (null :: [Int] -> Bool) > , iif (undefined :: Int) > , fun "undefined" (undefined :: Int) > ] last :: [Int] -> Int -- 0.0s, testing 360 combinations of argument values -- 0.0s, pruning with 5/5 rules -- ... ... ... ... ... -- 0.0s, 4 candidates of size 7 -- 0.0s, tested 2 candidates last [] = undefined last (x:xs) = if null xs then x else last xs
ordcase :: Conjurable a => a -> Ingredient Source #
Provides a case condition bound to the given return type.
This should be used when one wants Conjure to consider ord-case expressions:
> conjure "mem" mem > [ con False > , con True > , fun "`compare`" (compare :: Int -> Int -> Ordering) > , ordcase (undefined :: Bool) > ] mem :: Int -> Tree -> Bool -- ... ... ... ... ... -- 0.0s, 384 candidates of size 12 -- 0.0s, tested 346 candidates mem x Leaf = False mem x (Node t1 y t2) = case x `compare` y of LT -> mem x t1 EQ -> True GT -> mem x t2
Basic configuration parameters
maxTests :: Int -> Ingredient Source #
By default,
conjure
tests candidates up to a maximum of 360 tests.
This configures the maximum number of tests to each candidate,
when provided in the list of ingredients:
conjure "..." ... [ ... , maxTests 1080 , ... ]
target :: Int -> Ingredient Source #
By default, conjure
targets testing 10080 candidates.
This configures a different target when
provided in the list of ingredients:
conjure "..." ... [ ... , target 5040 , ... ]
maxSize :: Int -> Ingredient Source #
Conjuring from a specification
conjureFromSpec :: Conjurable f => String -> (f -> Bool) -> [Ingredient] -> IO () Source #
Conjures an implementation from a function specification.
This function works like conjure
but instead of receiving a partial definition
it receives a boolean filter / property about the function.
For example, given:
squareSpec :: (Int -> Int) -> Bool squareSpec square = square 0 == 0 && square 1 == 1 && square 2 == 4
Then:
> conjureFromSpec "square" squareSpec [fun "*" ((*) :: Int -> Int -> Int)] square :: Int -> Int -- 0.1s, pruning with 2/6 rules -- 0.1s, 1 candidates of size 1 -- 0.1s, 0 candidates of size 2 -- 0.1s, 1 candidates of size 3 -- 0.1s, tested 2 candidates square x = x * x
This allows users to specify QuickCheck-style properties, here is an example using LeanCheck:
import Test.LeanCheck (holds, exists) squarePropertySpec :: (Int -> Int) -> Bool squarePropertySpec square = and [ holds n $ \x -> square x >= x , holds n $ \x -> square x >= 0 , exists n $ \x -> square x > x ] where n = 60
When using custom types
class (Typeable a, Name a) => Conjurable a where Source #
Class of Conjurable
types.
Functions are Conjurable
if all their arguments are Conjurable
, Listable
and Show
able.
For atomic types that are Listable
,
instances are defined as:
instance Conjurable Atomic where conjureTiers = reifyTiers
For atomic types that are both Listable
and Eq
,
instances are defined as:
instance Conjurable Atomic where conjureTiers = reifyTiers conjureEquality = reifyEquality
For types with subtypes, instances are defined as:
instance Conjurable Composite where conjureTiers = reifyTiers conjureEquality = reifyEquality conjureSubTypes x = conjureType y . conjureType z . conjureType w where (Composite ... y ... z ... w ...) = x
Above x
, y
, z
and w
are just proxies.
The Proxy
type was avoided for backwards compatibility.
Please see the source code of Conjure.Conjurable for more examples.
Conjurable
instances can be derived automatically using
deriveConjurable
.
(cf. reifyTiers
, reifyEquality
, conjureType
)
Minimal complete definition
Methods
conjureEquality :: a -> Maybe Expr Source #
Returns Just
the ==
function encoded as an Expr
when available
or Nothing
otherwise.
Use reifyEquality
when defining this.
conjureTiers :: a -> Maybe [[Expr]] Source #
Returns Just
tiers
of values encoded as Expr
s when possible
or Nothing
otherwise.
Use reifyTiers
when defining this.
conjureSubTypes :: a -> Reification Source #
conjureCases :: a -> [Expr] Source #
Returns a top-level case breakdown.
conjureSize :: a -> Int Source #
Returns the (recursive) size of the given value.
conjureExpress :: a -> Expr -> Expr Source #
Returns a function that deeply reencodes an expression when possible.
(id
when not available.)
Use reifyExpress
when defining this.
Instances
Values of type Expr
represent objects or applications between objects.
Each object is encapsulated together with its type and string representation.
Values encoded in Expr
s are always monomorphic.
An Expr
can be constructed using:
val
, for values that areShow
instances;value
, for values that are notShow
instances, like functions;:$
, for applications betweenExpr
s.
> val False False :: Bool
> value "not" not :$ val False not False :: Bool
An Expr
can be evaluated using evaluate
, eval
or evl
.
> evl $ val (1 :: Int) :: Int 1
> evaluate $ val (1 :: Int) :: Maybe Bool Nothing
> eval 'a' (val 'b') 'b'
Show
ing a value of type Expr
will return a pretty-printed representation
of the expression together with its type.
> show (value "not" not :$ val False) "not False :: Bool"
Expr
is like Dynamic
but has support for applications and variables
(:$
, var
).
The var
underscore convention:
Functions that manipulate Expr
s usually follow the convention
where a value
whose String
representation starts with '_'
represents a var
iable.
Instances
Show Expr | Shows > show (value "not" not :$ val False) "not False :: Bool" |
Eq Expr | O(n). Does not evaluate values when comparing, but rather uses their representation as strings and their types. This instance works for ill-typed expressions. |
Ord Expr | O(n). Does not evaluate values when comparing, but rather uses their representation as strings and their types. This instance works for ill-typed expressions. Expressions come first
when they have smaller complexity ( |
value :: Typeable a => String -> a -> Expr #
O(1).
It takes a string representation of a value and a value, returning an
Expr
with that terminal value.
For instances of Show
, it is preferable to use val
.
> value "0" (0 :: Integer) 0 :: Integer
> value "'a'" 'a' 'a' :: Char
> value "True" True True :: Bool
> value "id" (id :: Int -> Int) id :: Int -> Int
> value "(+)" ((+) :: Int -> Int -> Int) (+) :: Int -> Int -> Int
> value "sort" (sort :: [Bool] -> [Bool]) sort :: [Bool] -> [Bool]
reifyExpress :: (Express a, Show a) => a -> Expr -> Expr Source #
Reifies the expr
function in a Conjurable
type instance.
This is to be used
in the definition of conjureExpress
of Conjurable
typeclass instances.
instance ... => Conjurable <Type> where ... conjureExpress = reifyExpress ...
reifyEquality :: (Eq a, Typeable a) => a -> Maybe Expr Source #
Reifies equality ==
in a Conjurable
type instance.
This is to be used
in the definition of conjureEquality
of Conjurable
typeclass instances:
instance ... => Conjurable <Type> where ... conjureEquality = reifyEquality ...
reifyTiers :: (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]] Source #
Reifies equality to be used in a conjurable type.
This is to be used
in the definition of conjureTiers
of Conjurable
typeclass instances:
instance ... => Conjurable <Type> where ... conjureTiers = reifyTiers ...
conjureType :: Conjurable a => a -> Reification Source #
To be used in the implementation of conjureSubTypes
.
instance ... => Conjurable <Type> where ... conjureSubTypes x = conjureType (field1 x) . conjureType (field2 x) . ... . conjureType (fieldN x) ...
If we were to come up with a variable name for the given type
what name
would it be?
An instance for a given type Ty
is simply given by:
instance Name Ty where name _ = "x"
Examples:
> name (undefined :: Int) "x"
> name (undefined :: Bool) "p"
> name (undefined :: [Int]) "xs"
This is then used to generate an infinite list of variable names
:
> names (undefined :: Int) ["x", "y", "z", "x'", "y'", "z'", "x''", "y''", "z''", ...]
> names (undefined :: Bool) ["p", "q", "r", "p'", "q'", "r'", "p''", "q''", "r''", ...]
> names (undefined :: [Int]) ["xs", "ys", "zs", "xs'", "ys'", "zs'", "xs''", "ys''", ...]
Minimal complete definition
Nothing
Methods
O(1).
Returns a name for a variable of the given argument's type.
> name (undefined :: Int) "x"
> name (undefined :: [Bool]) "ps"
> name (undefined :: [Maybe Integer]) "mxs"
The default definition is:
name _ = "x"
Instances
Name Int16 | |
Defined in Data.Express.Name | |
Name Int32 | |
Defined in Data.Express.Name | |
Name Int64 | |
Defined in Data.Express.Name | |
Name Int8 | |
Defined in Data.Express.Name | |
Name GeneralCategory | |
Defined in Data.Express.Name Methods name :: GeneralCategory -> String # | |
Name Word16 | |
Defined in Data.Express.Name | |
Name Word32 | |
Defined in Data.Express.Name | |
Name Word64 | |
Defined in Data.Express.Name | |
Name Word8 | |
Defined in Data.Express.Name | |
Name Ordering | name (undefined :: Ordering) = "o" names (undefined :: Ordering) = ["o", "p", "q", "o'", ...] |
Defined in Data.Express.Name | |
Name A Source # | |
Defined in Conjure.Conjurable | |
Name B Source # | |
Defined in Conjure.Conjurable | |
Name C Source # | |
Defined in Conjure.Conjurable | |
Name D Source # | |
Defined in Conjure.Conjurable | |
Name E Source # | |
Defined in Conjure.Conjurable | |
Name F Source # | |
Defined in Conjure.Conjurable | |
Name Integer | name (undefined :: Integer) = "x" names (undefined :: Integer) = ["x", "y", "z", "x'", ...] |
Defined in Data.Express.Name | |
Name () | name (undefined :: ()) = "u" names (undefined :: ()) = ["u", "v", "w", "u'", "v'", ...] |
Defined in Data.Express.Name | |
Name Bool | name (undefined :: Bool) = "p" names (undefined :: Bool) = ["p", "q", "r", "p'", "q'", ...] |
Defined in Data.Express.Name | |
Name Char | name (undefined :: Char) = "c" names (undefined :: Char) = ["c", "d", "e", "c'", "d'", ...] |
Defined in Data.Express.Name | |
Name Double | name (undefined :: Double) = "x" names (undefined :: Double) = ["x", "y", "z", "x'", ...] |
Defined in Data.Express.Name | |
Name Float | name (undefined :: Float) = "x" names (undefined :: Float) = ["x", "y", "z", "x'", ...] |
Defined in Data.Express.Name | |
Name Int | name (undefined :: Int) = "x" names (undefined :: Int) = ["x", "y", "z", "x'", "y'", ...] |
Defined in Data.Express.Name | |
Name Word | |
Defined in Data.Express.Name | |
Name (Complex a) | name (undefined :: Complex) = "x" names (undefined :: Complex) = ["x", "y", "z", "x'", ...] |
Defined in Data.Express.Name | |
Name (Ratio a) | name (undefined :: Rational) = "q" names (undefined :: Rational) = ["q", "r", "s", "q'", ...] |
Defined in Data.Express.Name | |
Name a => Name (Maybe a) | names (undefined :: Maybe Int) = ["mx", "mx1", "mx2", ...] nemes (undefined :: Maybe Bool) = ["mp", "mp1", "mp2", ...] |
Defined in Data.Express.Name | |
Name a => Name [a] | names (undefined :: [Int]) = ["xs", "ys", "zs", "xs'", ...] names (undefined :: [Bool]) = ["ps", "qs", "rs", "ps'", ...] |
Defined in Data.Express.Name | |
(Name a, Name b) => Name (Either a b) | names (undefined :: Either Int Int) = ["exy", "exy1", ...] names (undefined :: Either Int Bool) = ["exp", "exp1", ...] |
Defined in Data.Express.Name | |
(Name a, Name b) => Name (a, b) | names (undefined :: (Int,Int)) = ["xy", "zw", "xy'", ...] names (undefined :: (Bool,Bool)) = ["pq", "rs", "pq'", ...] |
Defined in Data.Express.Name | |
Name (a -> b) | names (undefined :: ()->()) = ["f", "g", "h", "f'", ...] names (undefined :: Int->Int) = ["f", "g", "h", ...] |
Defined in Data.Express.Name | |
(Name a, Name b, Name c) => Name (a, b, c) | names (undefined :: (Int,Int,Int)) = ["xyz","uvw", ...] names (undefined :: (Int,Bool,Char)) = ["xpc", "xpc1", ...] |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d) => Name (a, b, c, d) | names (undefined :: ((),(),(),())) = ["uuuu", "uuuu1", ...] names (undefined :: (Int,Int,Int,Int)) = ["xxxx", ...] |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e) => Name (a, b, c, d, e) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f) => Name (a, b, c, d, e, f) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g) => Name (a, b, c, d, e, f, g) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h) => Name (a, b, c, d, e, f, g, h) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i) => Name (a, b, c, d, e, f, g, h, i) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j) => Name (a, b, c, d, e, f, g, h, i, j) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j, Name k) => Name (a, b, c, d, e, f, g, h, i, j, k) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j, Name k, Name l) => Name (a, b, c, d, e, f, g, h, i, j, k, l) | |
Defined in Data.Express.Name |
class (Show a, Typeable a) => Express a where #
Express
typeclass instances provide an expr
function
that allows values to be deeply encoded as applications of Expr
s.
expr False = val False expr (Just True) = value "Just" (Just :: Bool -> Maybe Bool) :$ val True
The function expr
can be contrasted with the function val
:
val
always encodes values as atomicValue
Expr
s -- shallow encoding.expr
ideally encodes expressions as applications (:$
) betweenValue
Expr
s -- deep encoding.
Depending on the situation, one or the other may be desirable.
Instances can be automatically derived using the TH function
deriveExpress
.
The following example shows a datatype and its instance:
data Stack a = Stack a (Stack a) | Empty
instance Express a => Express (Stack a) where expr s@(Stack x y) = value "Stack" (Stack ->>: s) :$ expr x :$ expr y expr s@Empty = value "Empty" (Empty -: s)
To declare expr
it may be useful to use auxiliary type binding operators:
-:
, ->:
, ->>:
, ->>>:
, ->>>>:
, ->>>>>:
, ...
For types with atomic values, just declare expr = val
Instances
deriveConjurable :: Name -> DecsQ Source #
Derives an Conjurable
instance for the given type Name
.
If not already present,
this also derives Listable
, Express
and Name
instances.
If the Data.Express' type binding operators
(-:
,
->:
or
->>:
)
are not in scope,
this derives them as well.
This function needs the TemplateHaskell
extension.
You can place the following at the top of the file:
{-# LANGUAGE TemplateHaskell #-} import Conjure import Test.LeanCheck
Then just call deriveConjurable
after your data type declaration:
data Peano = Z | S Peano deriving (Show, Eq) deriveConjurable ''Peano
deriveConjurable
expects the argument type to be
an instance of Show
and Eq
.
deriveConjurableIfNeeded :: Name -> DecsQ Source #
Same as deriveConjurable
but does not warn when instance already exists
(deriveConjurable
is preferable).
deriveConjurableCascading :: Name -> DecsQ Source #
Derives a Conjurable
instance for a given type Name
cascading derivation of type arguments as well.
Pure interfaces
Results to the conjpure
family of functions.
This is for advanced users.
One is probably better-off using the conjure
family.
Constructors
Results | |
Fields
|
conjpure :: Conjurable f => String -> f -> [Ingredient] -> Results Source #
Like conjure
but in the pure world.
The most important part of the result are the tiers of implementations however results also include candidates, tests and the underlying theory.
Helper test types
Generic type A
.
Can be used to test polymorphic functions with a type variable
such as take
or sort
:
take :: Int -> [a] -> [a] sort :: Ord a => [a] -> [a]
by binding them to the following types:
take :: Int -> [A] -> [A] sort :: [A] -> [A]
This type is homomorphic to Nat6
, B
, C
, D
, E
and F
.
It is instance to several typeclasses so that it can be used to test functions with type contexts.
Instances
Bounded A | |
Enum A | |
Ix A | |
Num A | |
Read A | |
Integral A | |
Real A | |
Defined in Test.LeanCheck.Utils.Types Methods toRational :: A -> Rational # | |
Show A | |
Conjurable A Source # | |
Defined in Conjure.Conjurable Methods conjureArgumentHoles :: A -> [Expr] Source # conjureEquality :: A -> Maybe Expr Source # conjureTiers :: A -> Maybe [[Expr]] Source # conjureSubTypes :: A -> Reification Source # conjureIf :: A -> Expr Source # conjureCases :: A -> [Expr] Source # conjureArgumentCases :: A -> [[Expr]] Source # conjureSize :: A -> Int Source # conjureExpress :: A -> Expr -> Expr Source # conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe A Source # | |
Express A Source # | |
Defined in Conjure.Expr | |
Name A Source # | |
Defined in Conjure.Conjurable | |
Eq A | |
Ord A | |
Listable A | |
Generic type B
.
Can be used to test polymorphic functions with two type variables
such as map
or foldr
:
map :: (a -> b) -> [a] -> [b] foldr :: (a -> b -> b) -> b -> [a] -> b
by binding them to the following types:
map :: (A -> B) -> [A] -> [B] foldr :: (A -> B -> B) -> B -> [A] -> B
Instances
Bounded B | |
Enum B | |
Ix B | |
Num B | |
Read B | |
Integral B | |
Real B | |
Defined in Test.LeanCheck.Utils.Types Methods toRational :: B -> Rational # | |
Show B | |
Conjurable B Source # | |
Defined in Conjure.Conjurable Methods conjureArgumentHoles :: B -> [Expr] Source # conjureEquality :: B -> Maybe Expr Source # conjureTiers :: B -> Maybe [[Expr]] Source # conjureSubTypes :: B -> Reification Source # conjureIf :: B -> Expr Source # conjureCases :: B -> [Expr] Source # conjureArgumentCases :: B -> [[Expr]] Source # conjureSize :: B -> Int Source # conjureExpress :: B -> Expr -> Expr Source # conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe B Source # | |
Express B Source # | |
Defined in Conjure.Expr | |
Name B Source # | |
Defined in Conjure.Conjurable | |
Eq B | |
Ord B | |
Listable B | |
Generic type C
.
Can be used to test polymorphic functions with three type variables
such as uncurry
or zipWith
:
uncurry :: (a -> b -> c) -> (a, b) -> c zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
by binding them to the following types:
uncurry :: (A -> B -> C) -> (A, B) -> C zipWith :: (A -> B -> C) -> [A] -> [B] -> [C]
Instances
Bounded C | |
Enum C | |
Ix C | |
Num C | |
Read C | |
Integral C | |
Real C | |
Defined in Test.LeanCheck.Utils.Types Methods toRational :: C -> Rational # | |
Show C | |
Conjurable C Source # | |
Defined in Conjure.Conjurable Methods conjureArgumentHoles :: C -> [Expr] Source # conjureEquality :: C -> Maybe Expr Source # conjureTiers :: C -> Maybe [[Expr]] Source # conjureSubTypes :: C -> Reification Source # conjureIf :: C -> Expr Source # conjureCases :: C -> [Expr] Source # conjureArgumentCases :: C -> [[Expr]] Source # conjureSize :: C -> Int Source # conjureExpress :: C -> Expr -> Expr Source # conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe C Source # | |
Express C Source # | |
Defined in Conjure.Expr | |
Name C Source # | |
Defined in Conjure.Conjurable | |
Eq C | |
Ord C | |
Listable C | |
Generic type D
.
Can be used to test polymorphic functions with four type variables.
Instances
Bounded D | |
Enum D | |
Ix D | |
Num D | |
Read D | |
Integral D | |
Real D | |
Defined in Test.LeanCheck.Utils.Types Methods toRational :: D -> Rational # | |
Show D | |
Conjurable D Source # | |
Defined in Conjure.Conjurable Methods conjureArgumentHoles :: D -> [Expr] Source # conjureEquality :: D -> Maybe Expr Source # conjureTiers :: D -> Maybe [[Expr]] Source # conjureSubTypes :: D -> Reification Source # conjureIf :: D -> Expr Source # conjureCases :: D -> [Expr] Source # conjureArgumentCases :: D -> [[Expr]] Source # conjureSize :: D -> Int Source # conjureExpress :: D -> Expr -> Expr Source # conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe D Source # | |
Express D Source # | |
Defined in Conjure.Expr | |
Name D Source # | |
Defined in Conjure.Conjurable | |
Eq D | |
Ord D | |
Listable D | |
Generic type E
.
Can be used to test polymorphic functions with five type variables.
Instances
Bounded E | |
Enum E | |
Ix E | |
Num E | |
Read E | |
Integral E | |
Real E | |
Defined in Test.LeanCheck.Utils.Types Methods toRational :: E -> Rational # | |
Show E | |
Conjurable E Source # | |
Defined in Conjure.Conjurable Methods conjureArgumentHoles :: E -> [Expr] Source # conjureEquality :: E -> Maybe Expr Source # conjureTiers :: E -> Maybe [[Expr]] Source # conjureSubTypes :: E -> Reification Source # conjureIf :: E -> Expr Source # conjureCases :: E -> [Expr] Source # conjureArgumentCases :: E -> [[Expr]] Source # conjureSize :: E -> Int Source # conjureExpress :: E -> Expr -> Expr Source # conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe E Source # | |
Express E Source # | |
Defined in Conjure.Expr | |
Name E Source # | |
Defined in Conjure.Conjurable | |
Eq E | |
Ord E | |
Listable E | |
Generic type F
.
Can be used to test polymorphic functions with five type variables.
Instances
Bounded F | |
Enum F | |
Ix F | |
Num F | |
Read F | |
Integral F | |
Real F | |
Defined in Test.LeanCheck.Utils.Types Methods toRational :: F -> Rational # | |
Show F | |
Conjurable F Source # | |
Defined in Conjure.Conjurable Methods conjureArgumentHoles :: F -> [Expr] Source # conjureEquality :: F -> Maybe Expr Source # conjureTiers :: F -> Maybe [[Expr]] Source # conjureSubTypes :: F -> Reification Source # conjureIf :: F -> Expr Source # conjureCases :: F -> [Expr] Source # conjureArgumentCases :: F -> [[Expr]] Source # conjureSize :: F -> Int Source # conjureExpress :: F -> Expr -> Expr Source # conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe F Source # | |
Express F Source # | |
Defined in Conjure.Expr | |
Name F Source # | |
Defined in Conjure.Conjurable | |
Eq F | |
Ord F | |
Listable F | |
Advanced options
maxRecursions :: Int -> Ingredient Source #
By default,
conjure
evaluates candidates for up to 60 recursive calls.
This allows overriding the default when provided in the ingredient list.
maxEquationSize :: Int -> Ingredient Source #
By default,
conjure
considers equations of up to 5 symbols
for pruning-through-rewriting.
This allows overriding the default: 6 or 7 are also good values for this depending on the number of ingredients.
conjure ... ... [ ... , maxEquationSize 6 , ... ]
Internally, this is the maximum size passed to the Speculate tool.
maxSearchTests :: Int -> Ingredient Source #
By default,
conjure
enumerates up to 110880 argument combinations
while reifying the partial definition passed by the user.
This allows configuring a higher default when provided in the ingredient list.
Increasing this setting is useful when the partial definition is not exercised enough.
maxDeconstructionSize :: Int -> Ingredient Source #
By default
conjure
allows deconstruction expressions
of up to 4 symbols.
This allows overriding the default when provided in the ingredient list.
maxConstantSize :: Int -> Ingredient Source #
Configures a maximum size of constant sub-expressions
when provided in the ingredient list
of conjure
or conjureFromSpec
.
maxPatternSize :: Int -> Ingredient Source #
By default,
conjure
places no limit in the LHS pattern sizes.
This allows configuring a limit when provided in the ingredient list
maxPatternDepth :: Int -> Ingredient Source #
By default,
conjure
enumerates pattern breakdowns of the outernmost constructor
of depth 1.
This allows overriding the default when provided in the ingredient list: a depth of 2 allows breakdowns of the two outernmost constructors; a depth of 3, three outernmost constructors; etc.
Debug options
showCandidates :: Ingredient Source #
(Debug option) When provided in the ingredients list, this enables showing enumerated candidates.
conjure ... ... [ ... , showCandidates , ... ]
Warning: activating this will likely produce a humongous wall-of-text.
showTheory :: Ingredient Source #
(Debug option). Shows the underlying theory used in pruning when this is provided in the ingredient list.
singlePattern :: Ingredient Source #
(Debug option) When provided in the ingredient list, this reverts to a legacy enumeration that contains candidates with a single LHS matching everything.
showTests :: Ingredient Source #
(Debug option)
When provided in the ingredients list,
conjure
will print the tests reified from the partial definition.
(cf. maxTests
, maxSearchTests
)
showPatterns :: Ingredient Source #
(Debug option)
When this option is provided in the ingredients list,
conjure
will print the enumrated LHS patterns.
(cf. maxPatternSize
, maxPatternDepth
)
showDeconstructions :: Ingredient Source #
(Debug option)
Makes conjure
print enumerated deconstructions
when provided in its ingredient list.
carryOn :: Ingredient Source #
Carry on after finding a suitable candidate. To be provided as a setting in the list of ingredients.
Advanced pruning options
dontRewrite :: Ingredient Source #
Disables rewriting-as-pruning
when provided in the ingredient list
of conjure
or conjureFromSpec
.
dontRequireDescent :: Ingredient Source #
Disables the recursive descent requirement
when provided in the ingredient list
of conjure
or conjureFromSpec
.
omitAssortedPruning :: Ingredient Source #
Disables assorted pruning rules
when provided in the ingredient list
of conjure
or conjureFromSpec
.
omitEarlyTests :: Ingredient Source #
Omits early tests
when provided in the ingredient list
of conjure
or conjureFromSpec
.
dontCopyBindings :: Ingredient Source #
Disables the copy-bindings rule
when provided in the ingredient list
of conjure
or conjureFromSpec
.
nonAtomicNumbers :: Ingredient Source #
Disables the requirement of atomic numeric expressions
when provided in the ingredient list
of conjure
or conjureFromSpec
.
(cf. maxConstantSize
)
uniqueCandidates :: Ingredient Source #
Enables expensive unique-modulo-testing candidates
when provided in the ingredient list
of conjure
or conjureFromSpec
.
Warning: this makes conjure
very slow,
it is only intended for approximating the theoretical
limits of pruning in toy examples.
Deprecated functions
type Prim = Ingredient Source #
Deprecated: Prim
is deprecated, please use Ingredient
instead
DEPRACATED. Please use Ingredient
instead
pr :: (Conjurable a, Show a) => a -> Ingredient Source #
prim :: Conjurable a => String -> a -> Ingredient Source #