code-conjure-0.2.0: conjure Haskell functions out of partial definitions
Copyright(c) 2021 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellNone
LanguageHaskell2010

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:

primitives :: [Expr]
primitives =
  [ 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 primitives
square :: Int -> Int
-- testing 3 combinations of argument values
-- looking through 3 candidates of size 1
-- looking through 3 candidates of size 2
-- looking through 5 candidates of size 3
square x  =  x * x
Synopsis

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

primitives :: [Expr]
primitives =
  [ val (0::Int)
  , val (1::Int)
  , value "+" ((+) :: Int -> Int -> Int)
  , value "*" ((*) :: Int -> Int -> Int)
]

The conjure function does the following:

> conjure "square" square primitives
square :: Int -> Int
-- testing 3 combinations of argument values
-- looking through 3 candidates of size 1
-- looking through 3 candidates of size 2
-- looking through 5 candidates of size 3
square x  =  x * x

The primitives list is defined with val and value.

val :: (Typeable a, Show a) => a -> Expr #

O(1). A shorthand for value for values that are Show instances.

> val (0 :: Int)
0 :: Int
> val 'a'
'a' :: Char
> val True
True :: Bool

Example equivalences to value:

val 0     =  value "0" 0
val 'a'   =  value "'a'" 'a'
val True  =  value "True" True

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]

data Expr #

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 are Show instances;
  • value, for values that are not Show instances, like functions;
  • :$, for applications between Exprs.
> 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

Instances details
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.

Instance details

Defined in Data.Express.Core

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

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 (compareComplexity) or when they come first lexicographically (compareLexicographically).

Instance details

Defined in Data.Express.Core

Methods

compare :: Expr -> Expr -> Ordering #

(<) :: Expr -> Expr -> Bool #

(<=) :: Expr -> Expr -> Bool #

(>) :: Expr -> Expr -> Bool #

(>=) :: Expr -> Expr -> Bool #

max :: Expr -> Expr -> Expr #

min :: Expr -> Expr -> Expr #

Show Expr

Shows Exprs with their types.

> show (value "not" not :$ val False)
"not False :: Bool"
Instance details

Defined in Data.Express.Core

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

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 #

Like conjure but allows setting options through Args/args.

conjureWith args{maxSize = 11} "function" function [...]

data Args Source #

Arguments to be passed to conjureWith or conjpureWith. See args for the defaults.

Constructors

Args 

Fields

args :: Args Source #

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 ...)  =  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.

(cf. reifyTiers, reifyEquality, conjureType)

Minimal complete definition

Nothing

Methods

conjureEquality :: a -> Maybe Expr Source #

Returns Just the == function encoded as an Expr when available or Nothing otherwise.

conjureTiers :: a -> Maybe [[Expr]] Source #

Returns Just tiers of values encoded as Exprs when possible or Nothing otherwise.

Instances

Instances details
Conjurable Bool Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Char Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Double Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Float Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int8 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int16 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int32 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int64 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Integer Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Ordering Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word8 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word16 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word32 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word64 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable () Source # 
Instance details

Defined in Conjure.Conjurable

(Conjurable a, Listable a, Show a) => Conjurable [a] Source # 
Instance details

Defined in Conjure.Conjurable

(Conjurable a, Listable a, Show a) => Conjurable (Maybe a) Source # 
Instance details

Defined in Conjure.Conjurable

(Integral a, Conjurable a, Listable a, Show a, Eq a) => Conjurable (Ratio a) Source # 
Instance details

Defined in Conjure.Conjurable

(RealFloat a, Conjurable a, Listable a, Show a, Eq a) => Conjurable (Complex a) Source # 
Instance details

Defined in Conjure.Conjurable

(Listable a, Show a, Conjurable a, Conjurable b) => Conjurable (a -> b) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a -> b) -> [Expr] Source #

conjureEquality :: (a -> b) -> Maybe Expr Source #

conjureTiers :: (a -> b) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a -> b) -> Reification Source #

(Conjurable a, Listable a, Show a, Conjurable b, Listable b, Show b) => Conjurable (Either a b) Source # 
Instance details

Defined in Conjure.Conjurable

(Conjurable a, Listable a, Show a, Conjurable b, Listable b, Show b) => Conjurable (a, b) Source # 
Instance details

Defined in Conjure.Conjurable

(Conjurable a, Listable a, Show a, Conjurable b, Listable b, Show b, Conjurable c, Listable c, Show c) => Conjurable (a, b, c) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c) -> [Expr] Source #

conjureEquality :: (a, b, c) -> Maybe Expr Source #

conjureTiers :: (a, b, c) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c) -> Reification Source #

(Conjurable a, Listable a, Show a, Conjurable b, Listable b, Show b, Conjurable c, Listable c, Show c, Conjurable d, Listable d, Show d) => Conjurable (a, b, c, d) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c, d) -> [Expr] Source #

conjureEquality :: (a, b, c, d) -> Maybe Expr Source #

conjureTiers :: (a, b, c, d) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c, d) -> Reification Source #

(Conjurable a, Listable a, Show a, Conjurable b, Listable b, Show b, Conjurable c, Listable c, Show c, Conjurable d, Listable d, Show d, Conjurable e, Listable e, Show e) => Conjurable (a, b, c, d, e) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c, d, e) -> [Expr] Source #

conjureEquality :: (a, b, c, d, e) -> Maybe Expr Source #

conjureTiers :: (a, b, c, d, e) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c, d, e) -> Reification Source #

(Conjurable a, Listable a, Show a, Conjurable b, Listable b, Show b, Conjurable c, Listable c, Show c, Conjurable d, Listable d, Show d, Conjurable e, Listable e, Show e, Conjurable f, Listable f, Show f) => Conjurable (a, b, c, d, e, f) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c, d, e, f) -> [Expr] Source #

conjureEquality :: (a, b, c, d, e, f) -> Maybe Expr Source #

conjureTiers :: (a, b, c, d, e, f) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c, d, e, f) -> Reification Source #

(Conjurable a, Listable a, Show a, Conjurable b, Listable b, Show b, Conjurable c, Listable c, Show c, Conjurable d, Listable d, Show d, Conjurable e, Listable e, Show e, Conjurable f, Listable f, Show f, Conjurable g, Listable g, Show g) => Conjurable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c, d, e, f, g) -> [Expr] Source #

conjureEquality :: (a, b, c, d, e, f, g) -> Maybe Expr Source #

conjureTiers :: (a, b, c, d, e, f, g) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c, d, e, f, g) -> Reification Source #

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
  ...

Pure interfaces

conjpure :: Conjurable f => String -> f -> [Expr] -> ([[Expr]], [[Expr]], [Expr]) Source #

Like conjure but in the pure world.

Returns a triple with:

  1. tiers of implementations
  2. tiers of candidate bodies
  3. a list of tests

conjpureWith :: Conjurable f => Args -> String -> f -> [Expr] -> ([[Expr]], [[Expr]], [Expr]) Source #

Like conjpure but allows setting options through Args and args.