code-conjure-0.3.2: 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.Spec

Description

An internal module of Conjure, a library for Conjuring function implementations from tests or partial definitions. (a.k.a.: functional inductive programming)

Synopsis

Documentation

type Spec1 a b = [(a, b)] Source #

A partial specification of a function with one argument:

sumSpec :: Spec1 [Int] Int
sumSpec  =
  [ []      -= 0
  , [1,2]   -= 3
  , [3,4,5] -= 12
  ]

To be passed as one of the arguments to conjure1.

type Spec2 a b c = [((a, b), c)] Source #

A partial specification of a function with two arguments:

appSpec :: Spec2 [Int] [Int] [Int]
appSpec  =
  [ (,) []      [0,1]   -= [0,1]
  , (,) [2,3]   []      -= [2,3]
  , (,) [4,5,6] [7,8,9] -= [4,5,6,7,8,9]
  ]

To be passed as one of the arguments to conjure2.

type Spec3 a b c d = [((a, b, c), d)] Source #

A partial specification of a function with three arguments.

To be passed as one of the arguments to conjure3

(-=) :: a -> b -> (a, b) Source #

To be used when constructing specifications: Spec1, Spec2 and Spec3.

conjure1 :: (Eq a, Eq b, Show a, Conjurable a, Conjurable b) => String -> Spec1 a b -> [Expr] -> IO () Source #

Conjures a one argument function from a specification.

Given:

sumSpec :: Spec1 [Int] Int
sumSpec  =
  [ []      -= 0
  , [1,2]   -= 3
  , [3,4,5] -= 12
  ]
sumPrimitives :: [Expr]
sumPrimitives  =
  [ value "null" (null :: [Int] -> Bool)
  , val (0::Int)
  , value "+"    ((+) :: Int -> Int -> Int)
  , value "head" (head :: [Int] -> Int)
  , value "tail" (tail :: [Int] -> [Int])
  ]

Then:

> conjure1 "sum" sumSpec sumPrimitives
sum :: [Int] -> Int
-- testing 3 combinations of argument values
-- ...
-- looking through 189/465 candidates of size 10
xs ++ ys  =  if null xs then ys else head xs:(tail xs ++ ys)

(cf. Spec1, conjure1With)

conjure2 :: (Conjurable a, Eq a, Show a, Conjurable b, Eq b, Show b, Conjurable c, Eq c) => String -> Spec2 a b c -> [Expr] -> IO () Source #

Conjures a two argument function from a specification.

Given:

appSpec :: Spec2 [Int] [Int] [Int]
appSpec  =
  [ (,) []      [0,1]   -= [0,1]
  , (,) [2,3]   []      -= [2,3]
  , (,) [4,5,6] [7,8,9] -= [4,5,6,7,8,9]
  ]
appPrimitives :: [Expr]
appPrimitives =
  [ value "null" (null :: [Int] -> Bool)
  , value ":"    ((:) :: Int -> [Int] -> [Int])
  , value "head" (head :: [Int] -> Int)
  , value "tail" (tail :: [Int] -> [Int])
  ]

Then:

> conjure2 "++" appSpec appPrimitives
(++) :: [Int] -> [Int] -> [Int]
-- testing 3 combinations of argument values
-- ...
-- looking through 26166/57090 candidates of size 11
xs ++ ys  =  if null xs then ys else head xs:(tail xs ++ ys)

(cf. Spec2, conjure2With)

conjure3 :: (Conjurable a, Eq a, Show a, Conjurable b, Eq b, Show b, Conjurable c, Eq c, Show c, Conjurable d, Eq d) => String -> Spec3 a b c d -> [Expr] -> IO () Source #

Conjures a three argument function from a specification.

(cf. Spec3, conjure3With)

conjure1With :: (Eq a, Eq b, Show a, Conjurable a, Conjurable b) => Args -> String -> Spec1 a b -> [Expr] -> IO () Source #

Like conjure1 but allows setting options through Args/args.

conjure2With :: (Conjurable a, Eq a, Show a, Conjurable b, Eq b, Show b, Conjurable c, Eq c) => Args -> String -> Spec2 a b c -> [Expr] -> IO () Source #

Like conjure2 but allows setting options through Args/args.

conjure3With :: (Conjurable a, Eq a, Show a, Conjurable b, Eq b, Show b, Conjurable c, Eq c, Show c, Conjurable d, Eq d) => Args -> String -> Spec3 a b c d -> [Expr] -> IO () Source #

Like conjure3 but allows setting options through Args/args.