| Copyright | (c) 2021 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)
This is currently an experimental tool in its early stages, don't expect much from its current version. It is just a piece of curiosity in its current state.
Step 1: declare your partial function
square :: Int -> Int square 0 = 0 square 1 = 1 square 2 = 4
Step 2: declare a list with the potential building blocks:
background :: [Expr] background = [ val (0::Int) , val (1::Int) , value "+" ((+) :: Int -> Int -> Int) , value "*" ((*) :: Int -> Int -> Int) ]
Step 3: call conjure and see your generated function:
> conjure "square" square background square :: Int -> Int -- looking through 815 candidates, 100% match, 3/3 assignments square x = x * x
Synopsis
- conjure :: Conjurable f => String -> f -> [Expr] -> IO ()
- val :: (Typeable a, Show a) => a -> Expr
- value :: Typeable a => String -> a -> Expr
- data Expr
- conjureWithMaxSize :: Conjurable f => Int -> String -> f -> [Expr] -> IO ()
- conjureWith :: Conjurable f => Args -> String -> f -> [Expr] -> IO ()
- data Args = Args {
- maxTests :: Int
- maxSize :: Int
- maxRecursiveCalls :: Int
- maxEquationSize :: Int
- maxRecursionSize :: Int
- args :: Args
- class Typeable a => Conjurable a where
- conjureEquality :: a -> Maybe Expr
- conjureTiers :: a -> Maybe [[Expr]]
- reifyEquality :: (Eq a, Typeable a) => a -> Maybe Expr
- reifyTiers :: (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
- conjpure :: Conjurable f => String -> f -> [Expr] -> (Int, Int, [(Int, Expr)])
- conjpureWith :: Conjurable f => Args -> String -> f -> [Expr] -> (Int, Int, [(Int, Expr)])
Basic use
conjure :: Conjurable f => String -> f -> [Expr] -> 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 Exprs.
For example, given:
square :: Int -> Int square 0 = 0 square 1 = 1 square 2 = 4 background :: [Expr] background = [ val (0::Int) , val (1::Int) , value "+" ((+) :: Int -> Int -> Int) , value "*" ((*) :: Int -> Int -> Int) ]
The conjure function does the following:
> conjure "square" square background square :: Int -> Int -- looking through 815 candidates, 100% match, 3/3 assignments square x = x * x
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]
Values of type Expr represent objects or applications between objects.
Each object is encapsulated together with its type and string representation.
Values encoded in Exprs are always monomorphic.
An Expr can be constructed using:
val, for values that areShowinstances;value, for values that are notShowinstances, like functions;:$, for applications betweenExprs.
> 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'
Showing 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 Exprs usually follow the convention
where a value whose String representation starts with '_'
represents a variable.
Instances
| 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 ( |
| Show Expr | Shows > show (value "not" not :$ val False) "not False :: Bool" |
Advanced use
conjureWithMaxSize :: Conjurable f => Int -> String -> f -> [Expr] -> IO () Source #
Like conjure but allows setting the maximum size of considered expressions
instead of the default value of 9.
conjureWithMaxSize 10 "function" function [...]
conjureWith :: Conjurable f => Args -> String -> f -> [Expr] -> IO () Source #
Arguments to be passed to conjureWith or conjpureWith.
See args for the defaults.
Constructors
| Args | |
Fields
| |
Default arguments to conjure.
- 60 tests
- functions of up to 9 symbols
- maximum of 1 recursive call
- pruning with equations up to size 5
- recursion up to 60 symbols.
When using custom types
class Typeable a => Conjurable a where Source #
Class of Conjurable types.
Functions are Conjurable
if all their arguments are Conjurable, Listable and Showable.
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 ...) = xAbove 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.
(cf. reifyTiers, reifyEquality, conjureType)
Minimal complete definition
Nothing
Instances
reifyEquality :: (Eq 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 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 ...