-- | -- Module : Conjure -- Copyright : (c) 2021 Rudy Matela -- License : 3-Clause BSD (see the file LICENSE) -- Maintainer : Rudy Matela -- -- 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 {-# LANGUAGE CPP #-} module Conjure ( -- * Basic use conjure , val , value , Expr -- * Advanced use , conjureWithMaxSize , conjureWith , Args(..) , args -- * When using custom types , Conjurable (conjureEquality, conjureTiers) , reifyEquality, reifyTiers -- * Pure interfaces , conjpure , conjpureWith ) where import Conjure.Engine import Conjure.Conjurable