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

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:

primitives :: [Prim]
primitives =
  [ pr (0::Int)
  , pr (1::Int)
  , prim "+" ((+) :: Int -> Int -> Int)
  , prim "*" ((*) :: Int -> Int -> Int)
  , prim "-" ((-) :: Int -> Int -> Int)
  ]

Step 3: call conjure and see your generated function:

> conjure "factorial" factorial primitives
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])
>   [ pr (0 :: Int)
>   , pr (1 :: Int)
>   , pr ([] :: [A])
>   , prim ":" ((:) :: A -> [A] -> [A])
>   , prim "-" ((-) :: 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 primitives was minimized to what was absolutely needed here. With a larger collection as primitives 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

Basic use

conjure :: Conjurable f => String -> f -> [Prim] -> 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:

factorial :: Int -> Int
factorial 2  =  2
factorial 3  =  6
factorial 4  =  24

primitives :: [Prim]
primitives =
  [ pr (0::Int)
  , pr (1::Int)
  , prim "+" ((+) :: Int -> Int -> Int)
  , prim "*" ((*) :: Int -> Int -> Int)
  , prim "-" ((-) :: Int -> Int -> Int)
  ]

The conjure function does the following:

> conjure "factorial" factorial primitives
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)

The primitives list is defined with pr and prim.

type Prim = (Expr, Reification) Source #

A primitive expression (paired with instance reification). Create Prims with pr and prim.

pr :: (Conjurable a, Show a) => a -> Prim Source #

Provides a primitive value to Conjure. To be used on Show instances. (cf. prim)

conjure "fun" fun [ pr False
                  , pr True
                  , pr (0 :: Int)
                  , pr (1 :: Int)
                  , ...
                  ]

Argument types have to be monomorphized, so use type bindings when applicable.

prim :: Conjurable a => String -> a -> Prim Source #

Provides a primitive value to Conjure. To be used on values that are not Show instances such as functions. (cf. pr)

conjure "fun" fun [ ...
                  , prim "&&" (&&)
                  , prim "||" (||)
                  , prim "+" ((+) :: Int -> Int -> Int)
                  , prim "*" ((*) :: Int -> Int -> Int)
                  , prim "-" ((-) :: Int -> Int -> Int)
                  , ...
                  ]

Argument types have to be monomorphized, so use type bindings when applicable.

guard :: Prim Source #

Provides an if condition 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'
>   [ pr ([] :: [Int])
>   , prim ":" ((:) :: Int -> [Int] -> [Int])
>   , prim "null" (null :: [Int] -> Bool)
>   , guard
>   , prim "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

prif :: Conjurable a => a -> Prim Source #

Provides an if condition bound to the given return type.

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' [ pr ([] :: [Int])
>                      , prim ":" ((:) :: Int -> [Int] -> [Int])
>                      , prim "null" (null :: [Int] -> Bool)
>                      , prif (undefined :: Int)
>                      , prim "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

primOrdCaseFor :: Conjurable a => a -> Prim 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
>   [ pr False
>   , pr True
>   , prim "`compare`" (compare :: Int -> Int -> Ordering)
>   , primOrdCaseFor (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

Advanced use

conjureWithMaxSize :: Conjurable f => Int -> String -> f -> [Prim] -> IO () Source #

Like conjure but allows setting the maximum size of considered expressions instead of the default value of 24.

conjureWithMaxSize 12 "function" function [...]

This function is a candidate for going away. Please set maxSize in Args instead.

conjureWith :: Conjurable f => Args -> String -> f -> [Prim] -> IO () Source #

Like conjure but allows setting options through Args/args.

conjureWith args{maxSize = 18} "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 24 symbols
  • target testing over 50400 candidates
  • maximum of one recursive call allowed in candidate bodies
  • maximum evaluation of up to 60 recursions
  • pruning with equations up to size 5
  • search for defined applications for up to 100000 combinations
  • require recursive calls to deconstruct arguments
  • don't show the theory used in pruning
  • do not show tested candidates
  • do not make candidates unique module testing

Conjuring from a specification

conjureFromSpec :: Conjurable f => String -> (f -> Bool) -> [Prim] -> 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 [prim "*" ((*) :: 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

conjureFromSpecWith :: Conjurable f => Args -> String -> (f -> Bool) -> [Prim] -> IO () Source #

Like conjureFromSpec but allows setting options through Args/args.

conjureFromSpecWith args{maxSize = 18} "function" spec [...]

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

Conjurable instances can be derived automatically using deriveConjurable.

(cf. reifyTiers, reifyEquality, conjureType)

Minimal complete definition

conjureExpress

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

Instances details
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 Int8 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 Word8 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Ordering Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable A Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable B Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable C Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable D Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable E Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable F Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Integer Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable () Source # 
Instance details

Defined in Conjure.Conjurable

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 Word Source # 
Instance details

Defined in Conjure.Conjurable

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

Defined in Conjure.Conjurable

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

Defined in Conjure.Conjurable

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

Defined in Conjure.Conjurable

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

Defined in Conjure.Conjurable

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

Defined in Conjure.Conjurable

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express 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 #

conjureIf :: (a, b) -> Expr Source #

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

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

conjureSize :: (a, b) -> Int Source #

conjureExpress :: (a, b) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b) Source #

(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 #

conjureIf :: (a -> b) -> Expr Source #

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

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

conjureSize :: (a -> b) -> Int Source #

conjureExpress :: (a -> b) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a -> b) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express 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 #

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

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

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

conjureSize :: (a, b, c) -> Int Source #

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

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express 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 #

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

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

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

conjureSize :: (a, b, c, d) -> Int Source #

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

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express d, Conjurable e, Listable e, Show e, Express 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 #

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

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

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

conjureSize :: (a, b, c, d, e) -> Int Source #

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

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d, e) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express d, Conjurable e, Listable e, Show e, Express e, Conjurable f, Listable f, Show f, Express 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 #

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

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

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

conjureSize :: (a, b, c, d, e, f) -> Int Source #

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

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

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express d, Conjurable e, Listable e, Show e, Express e, Conjurable f, Listable f, Show f, Express f, Conjurable g, Listable g, Show g, Express 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 #

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

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

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

conjureSize :: (a, b, c, d, e, f, g) -> Int Source #

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

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

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

Defined in Conjure.Conjurable

Methods

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

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

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

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

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

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

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

conjureSize :: (a, b, c, d, e, f, g, h) -> Int Source #

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

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d, e, f, g, h) Source #

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

Defined in Conjure.Conjurable

Methods

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

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

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

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

conjureIf :: (a, b, c, d, e, f, g, h, i) -> Expr Source #

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

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

conjureSize :: (a, b, c, d, e, f, g, h, i) -> Int Source #

conjureExpress :: (a, b, c, d, e, f, g, h, i) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d, e, f, g, h, i) Source #

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

Defined in Conjure.Conjurable

Methods

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

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

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

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

conjureIf :: (a, b, c, d, e, f, g, h, i, j) -> Expr Source #

conjureCases :: (a, b, c, d, e, f, g, h, i, j) -> [Expr] Source #

conjureArgumentCases :: (a, b, c, d, e, f, g, h, i, j) -> [[Expr]] Source #

conjureSize :: (a, b, c, d, e, f, g, h, i, j) -> Int Source #

conjureExpress :: (a, b, c, d, e, f, g, h, i, j) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d, e, f, g, h, i, j) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express d, Conjurable e, Listable e, Show e, Express e, Conjurable f, Listable f, Show f, Express f, Conjurable g, Listable g, Show g, Express g, Conjurable h, Listable h, Show h, Express h, Conjurable i, Listable i, Show i, Express i, Conjurable j, Listable j, Show j, Express j, Conjurable k, Listable k, Show k, Express k) => Conjurable (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

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

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

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

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

conjureIf :: (a, b, c, d, e, f, g, h, i, j, k) -> Expr Source #

conjureCases :: (a, b, c, d, e, f, g, h, i, j, k) -> [Expr] Source #

conjureArgumentCases :: (a, b, c, d, e, f, g, h, i, j, k) -> [[Expr]] Source #

conjureSize :: (a, b, c, d, e, f, g, h, i, j, k) -> Int Source #

conjureExpress :: (a, b, c, d, e, f, g, h, i, j, k) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d, e, f, g, h, i, j, k) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express d, Conjurable e, Listable e, Show e, Express e, Conjurable f, Listable f, Show f, Express f, Conjurable g, Listable g, Show g, Express g, Conjurable h, Listable h, Show h, Express h, Conjurable i, Listable i, Show i, Express i, Conjurable j, Listable j, Show j, Express j, Conjurable k, Listable k, Show k, Express k, Conjurable l, Listable l, Show l, Express l) => Conjurable (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c, d, e, f, g, h, i, j, k, l) -> [Expr] Source #

conjureEquality :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Maybe Expr Source #

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

conjureSubTypes :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Reification Source #

conjureIf :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Expr Source #

conjureCases :: (a, b, c, d, e, f, g, h, i, j, k, l) -> [Expr] Source #

conjureArgumentCases :: (a, b, c, d, e, f, g, h, i, j, k, l) -> [[Expr]] Source #

conjureSize :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Int Source #

conjureExpress :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l) Source #

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

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 #

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]

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

class Name a where #

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

name :: a -> String #

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

Instances details
Name Int16 
Instance details

Defined in Data.Express.Name

Methods

name :: Int16 -> String #

Name Int32 
Instance details

Defined in Data.Express.Name

Methods

name :: Int32 -> String #

Name Int64 
Instance details

Defined in Data.Express.Name

Methods

name :: Int64 -> String #

Name Int8 
Instance details

Defined in Data.Express.Name

Methods

name :: Int8 -> String #

Name GeneralCategory 
Instance details

Defined in Data.Express.Name

Name Word16 
Instance details

Defined in Data.Express.Name

Methods

name :: Word16 -> String #

Name Word32 
Instance details

Defined in Data.Express.Name

Methods

name :: Word32 -> String #

Name Word64 
Instance details

Defined in Data.Express.Name

Methods

name :: Word64 -> String #

Name Word8 
Instance details

Defined in Data.Express.Name

Methods

name :: Word8 -> String #

Name Ordering
name (undefined :: Ordering) = "o"
names (undefined :: Ordering) = ["o", "p", "q", "o'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Ordering -> String #

Name A Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: A -> String #

Name B Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: B -> String #

Name C Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: C -> String #

Name D Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: D -> String #

Name E Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: E -> String #

Name F Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: F -> String #

Name Integer
name (undefined :: Integer) = "x"
names (undefined :: Integer) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Integer -> String #

Name ()
name (undefined :: ()) = "u"
names (undefined :: ()) = ["u", "v", "w", "u'", "v'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: () -> String #

Name Bool
name (undefined :: Bool) = "p"
names (undefined :: Bool) = ["p", "q", "r", "p'", "q'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Bool -> String #

Name Char
name (undefined :: Char) = "c"
names (undefined :: Char) = ["c", "d", "e", "c'", "d'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Char -> String #

Name Double
name (undefined :: Double) = "x"
names (undefined :: Double) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Double -> String #

Name Float
name (undefined :: Float) = "x"
names (undefined :: Float) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Float -> String #

Name Int
name (undefined :: Int) = "x"
names (undefined :: Int) = ["x", "y", "z", "x'", "y'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Int -> String #

Name Word 
Instance details

Defined in Data.Express.Name

Methods

name :: Word -> String #

Name (Complex a)
name (undefined :: Complex) = "x"
names (undefined :: Complex) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Complex a -> String #

Name (Ratio a)
name (undefined :: Rational) = "q"
names (undefined :: Rational) = ["q", "r", "s", "q'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Ratio a -> String #

Name a => Name (Maybe a)
names (undefined :: Maybe Int) = ["mx", "mx1", "mx2", ...]
nemes (undefined :: Maybe Bool) = ["mp", "mp1", "mp2", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Maybe a -> String #

Name a => Name [a]
names (undefined :: [Int]) = ["xs", "ys", "zs", "xs'", ...]
names (undefined :: [Bool]) = ["ps", "qs", "rs", "ps'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: [a] -> String #

(Name a, Name b) => Name (Either a b)
names (undefined :: Either Int Int) = ["exy", "exy1", ...]
names (undefined :: Either Int Bool) = ["exp", "exp1", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Either a b -> String #

(Name a, Name b) => Name (a, b)
names (undefined :: (Int,Int)) = ["xy", "zw", "xy'", ...]
names (undefined :: (Bool,Bool)) = ["pq", "rs", "pq'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b) -> String #

Name (a -> b)
names (undefined :: ()->()) = ["f", "g", "h", "f'", ...]
names (undefined :: Int->Int) = ["f", "g", "h", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a -> b) -> String #

(Name a, Name b, Name c) => Name (a, b, c)
names (undefined :: (Int,Int,Int)) = ["xyz","uvw", ...]
names (undefined :: (Int,Bool,Char)) = ["xpc", "xpc1", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c) -> String #

(Name a, Name b, Name c, Name d) => Name (a, b, c, d)
names (undefined :: ((),(),(),())) = ["uuuu", "uuuu1", ...]
names (undefined :: (Int,Int,Int,Int)) = ["xxxx", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d) -> String #

(Name a, Name b, Name c, Name d, Name e) => Name (a, b, c, d, e) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e) -> String #

(Name a, Name b, Name c, Name d, Name e, Name f) => Name (a, b, c, d, e, f) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f) -> String #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g) => Name (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g) -> String #

(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) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h) -> String #

(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) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i) -> String #

(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) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i, j) -> String #

(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) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i, j, k) -> String #

(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) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String #

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

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 atomic Value Exprs -- shallow encoding.
  • expr ideally encodes expressions as applications (:$) between Value Exprs -- 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

Methods

expr :: a -> Expr #

Instances

Instances details
Express Int16 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int16 -> Expr #

Express Int32 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int32 -> Expr #

Express Int64 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int64 -> Expr #

Express Int8 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int8 -> Expr #

Express GeneralCategory 
Instance details

Defined in Data.Express.Express

Methods

expr :: GeneralCategory -> Expr #

Express Word16 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word16 -> Expr #

Express Word32 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word32 -> Expr #

Express Word64 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word64 -> Expr #

Express Word8 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word8 -> Expr #

Express Ordering 
Instance details

Defined in Data.Express.Express

Methods

expr :: Ordering -> Expr #

Express A Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: A -> Expr #

Express B Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: B -> Expr #

Express C Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: C -> Expr #

Express D Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: D -> Expr #

Express E Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: E -> Expr #

Express F Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: F -> Expr #

Express Integer 
Instance details

Defined in Data.Express.Express

Methods

expr :: Integer -> Expr #

Express () 
Instance details

Defined in Data.Express.Express

Methods

expr :: () -> Expr #

Express Bool 
Instance details

Defined in Data.Express.Express

Methods

expr :: Bool -> Expr #

Express Char 
Instance details

Defined in Data.Express.Express

Methods

expr :: Char -> Expr #

Express Double 
Instance details

Defined in Data.Express.Express

Methods

expr :: Double -> Expr #

Express Float 
Instance details

Defined in Data.Express.Express

Methods

expr :: Float -> Expr #

Express Int 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int -> Expr #

Express Word 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word -> Expr #

(RealFloat a, Express a) => Express (Complex a) 
Instance details

Defined in Data.Express.Express

Methods

expr :: Complex a -> Expr #

(Integral a, Express a) => Express (Ratio a) 
Instance details

Defined in Data.Express.Express

Methods

expr :: Ratio a -> Expr #

Express a => Express (Maybe a) 
Instance details

Defined in Data.Express.Express

Methods

expr :: Maybe a -> Expr #

Express a => Express [a] 
Instance details

Defined in Data.Express.Express

Methods

expr :: [a] -> Expr #

(Express a, Express b) => Express (Either a b) 
Instance details

Defined in Data.Express.Express

Methods

expr :: Either a b -> Expr #

(Express a, Express b) => Express (a, b) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b) -> Expr #

(Express a, Express b, Express c) => Express (a, b, c) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c) -> Expr #

(Express a, Express b, Express c, Express d) => Express (a, b, c, d) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d) -> Expr #

(Express a, Express b, Express c, Express d, Express e) => Express (a, b, c, d, e) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f) => Express (a, b, c, d, e, f) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g) => Express (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h) => Express (a, b, c, d, e, f, g, h) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i) => Express (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i, Express j) => Express (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i, j) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i, Express j, Express k) => Express (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i, j, k) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i, Express j, Express k, Express l) => Express (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Expr #

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

data Results Source #

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 -> [Prim] -> 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.

conjpureWith :: Conjurable f => Args -> String -> f -> [Prim] -> Results Source #

Like conjpure but allows setting options through Args and args.

Helper test types

data A #

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

Instances details
Bounded A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: A #

maxBound :: A #

Enum A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: A -> A #

pred :: A -> A #

toEnum :: Int -> A #

fromEnum :: A -> Int #

enumFrom :: A -> [A] #

enumFromThen :: A -> A -> [A] #

enumFromTo :: A -> A -> [A] #

enumFromThenTo :: A -> A -> A -> [A] #

Ix A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (A, A) -> [A] #

index :: (A, A) -> A -> Int #

unsafeIndex :: (A, A) -> A -> Int #

inRange :: (A, A) -> A -> Bool #

rangeSize :: (A, A) -> Int #

unsafeRangeSize :: (A, A) -> Int #

Num A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: A -> A -> A #

(-) :: A -> A -> A #

(*) :: A -> A -> A #

negate :: A -> A #

abs :: A -> A #

signum :: A -> A #

fromInteger :: Integer -> A #

Read A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Integral A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: A -> A -> A #

rem :: A -> A -> A #

div :: A -> A -> A #

mod :: A -> A -> A #

quotRem :: A -> A -> (A, A) #

divMod :: A -> A -> (A, A) #

toInteger :: A -> Integer #

Real A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: A -> Rational #

Show A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> A -> ShowS #

show :: A -> String #

showList :: [A] -> ShowS #

Conjurable A Source # 
Instance details

Defined in Conjure.Conjurable

Express A Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: A -> Expr #

Name A Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: A -> String #

Eq A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: A -> A -> Ordering #

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

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

(>) :: A -> A -> Bool #

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

max :: A -> A -> A #

min :: A -> A -> A #

Listable A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[A]] #

list :: [A] #

data B #

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

This type is homomorphic to A, Nat6, C, D, E and F.

Instances

Instances details
Bounded B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: B #

maxBound :: B #

Enum B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: B -> B #

pred :: B -> B #

toEnum :: Int -> B #

fromEnum :: B -> Int #

enumFrom :: B -> [B] #

enumFromThen :: B -> B -> [B] #

enumFromTo :: B -> B -> [B] #

enumFromThenTo :: B -> B -> B -> [B] #

Ix B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (B, B) -> [B] #

index :: (B, B) -> B -> Int #

unsafeIndex :: (B, B) -> B -> Int #

inRange :: (B, B) -> B -> Bool #

rangeSize :: (B, B) -> Int #

unsafeRangeSize :: (B, B) -> Int #

Num B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: B -> B -> B #

(-) :: B -> B -> B #

(*) :: B -> B -> B #

negate :: B -> B #

abs :: B -> B #

signum :: B -> B #

fromInteger :: Integer -> B #

Read B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Integral B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: B -> B -> B #

rem :: B -> B -> B #

div :: B -> B -> B #

mod :: B -> B -> B #

quotRem :: B -> B -> (B, B) #

divMod :: B -> B -> (B, B) #

toInteger :: B -> Integer #

Real B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: B -> Rational #

Show B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> B -> ShowS #

show :: B -> String #

showList :: [B] -> ShowS #

Conjurable B Source # 
Instance details

Defined in Conjure.Conjurable

Express B Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: B -> Expr #

Name B Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: B -> String #

Eq B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: B -> B -> Ordering #

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

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

(>) :: B -> B -> Bool #

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

max :: B -> B -> B #

min :: B -> B -> B #

Listable B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[B]] #

list :: [B] #

data C #

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]

This type is homomorphic to A, B, Nat6, D, E and F.

Instances

Instances details
Bounded C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: C #

maxBound :: C #

Enum C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: C -> C #

pred :: C -> C #

toEnum :: Int -> C #

fromEnum :: C -> Int #

enumFrom :: C -> [C] #

enumFromThen :: C -> C -> [C] #

enumFromTo :: C -> C -> [C] #

enumFromThenTo :: C -> C -> C -> [C] #

Ix C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (C, C) -> [C] #

index :: (C, C) -> C -> Int #

unsafeIndex :: (C, C) -> C -> Int #

inRange :: (C, C) -> C -> Bool #

rangeSize :: (C, C) -> Int #

unsafeRangeSize :: (C, C) -> Int #

Num C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: C -> C -> C #

(-) :: C -> C -> C #

(*) :: C -> C -> C #

negate :: C -> C #

abs :: C -> C #

signum :: C -> C #

fromInteger :: Integer -> C #

Read C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Integral C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: C -> C -> C #

rem :: C -> C -> C #

div :: C -> C -> C #

mod :: C -> C -> C #

quotRem :: C -> C -> (C, C) #

divMod :: C -> C -> (C, C) #

toInteger :: C -> Integer #

Real C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: C -> Rational #

Show C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> C -> ShowS #

show :: C -> String #

showList :: [C] -> ShowS #

Conjurable C Source # 
Instance details

Defined in Conjure.Conjurable

Express C Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: C -> Expr #

Name C Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: C -> String #

Eq C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: C -> C -> Ordering #

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

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

(>) :: C -> C -> Bool #

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

max :: C -> C -> C #

min :: C -> C -> C #

Listable C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[C]] #

list :: [C] #

data D #

Generic type D.

Can be used to test polymorphic functions with four type variables.

This type is homomorphic to A, B, C, Nat6, E and F.

Instances

Instances details
Bounded D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: D #

maxBound :: D #

Enum D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: D -> D #

pred :: D -> D #

toEnum :: Int -> D #

fromEnum :: D -> Int #

enumFrom :: D -> [D] #

enumFromThen :: D -> D -> [D] #

enumFromTo :: D -> D -> [D] #

enumFromThenTo :: D -> D -> D -> [D] #

Ix D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (D, D) -> [D] #

index :: (D, D) -> D -> Int #

unsafeIndex :: (D, D) -> D -> Int #

inRange :: (D, D) -> D -> Bool #

rangeSize :: (D, D) -> Int #

unsafeRangeSize :: (D, D) -> Int #

Num D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: D -> D -> D #

(-) :: D -> D -> D #

(*) :: D -> D -> D #

negate :: D -> D #

abs :: D -> D #

signum :: D -> D #

fromInteger :: Integer -> D #

Read D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Integral D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: D -> D -> D #

rem :: D -> D -> D #

div :: D -> D -> D #

mod :: D -> D -> D #

quotRem :: D -> D -> (D, D) #

divMod :: D -> D -> (D, D) #

toInteger :: D -> Integer #

Real D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: D -> Rational #

Show D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> D -> ShowS #

show :: D -> String #

showList :: [D] -> ShowS #

Conjurable D Source # 
Instance details

Defined in Conjure.Conjurable

Express D Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: D -> Expr #

Name D Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: D -> String #

Eq D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: D -> D -> Ordering #

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

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

(>) :: D -> D -> Bool #

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

max :: D -> D -> D #

min :: D -> D -> D #

Listable D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[D]] #

list :: [D] #

data E #

Generic type E.

Can be used to test polymorphic functions with five type variables.

This type is homomorphic to A, B, C, D, Nat6 and F.

Instances

Instances details
Bounded E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: E #

maxBound :: E #

Enum E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: E -> E #

pred :: E -> E #

toEnum :: Int -> E #

fromEnum :: E -> Int #

enumFrom :: E -> [E] #

enumFromThen :: E -> E -> [E] #

enumFromTo :: E -> E -> [E] #

enumFromThenTo :: E -> E -> E -> [E] #

Ix E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (E, E) -> [E] #

index :: (E, E) -> E -> Int #

unsafeIndex :: (E, E) -> E -> Int #

inRange :: (E, E) -> E -> Bool #

rangeSize :: (E, E) -> Int #

unsafeRangeSize :: (E, E) -> Int #

Num E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: E -> E -> E #

(-) :: E -> E -> E #

(*) :: E -> E -> E #

negate :: E -> E #

abs :: E -> E #

signum :: E -> E #

fromInteger :: Integer -> E #

Read E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Integral E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: E -> E -> E #

rem :: E -> E -> E #

div :: E -> E -> E #

mod :: E -> E -> E #

quotRem :: E -> E -> (E, E) #

divMod :: E -> E -> (E, E) #

toInteger :: E -> Integer #

Real E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: E -> Rational #

Show E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> E -> ShowS #

show :: E -> String #

showList :: [E] -> ShowS #

Conjurable E Source # 
Instance details

Defined in Conjure.Conjurable

Express E Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: E -> Expr #

Name E Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: E -> String #

Eq E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: E -> E -> Ordering #

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

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

(>) :: E -> E -> Bool #

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

max :: E -> E -> E #

min :: E -> E -> E #

Listable E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[E]] #

list :: [E] #

data F #

Generic type F.

Can be used to test polymorphic functions with five type variables.

This type is homomorphic to A, B, C, D, E and Nat6.

Instances

Instances details
Bounded F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: F #

maxBound :: F #

Enum F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: F -> F #

pred :: F -> F #

toEnum :: Int -> F #

fromEnum :: F -> Int #

enumFrom :: F -> [F] #

enumFromThen :: F -> F -> [F] #

enumFromTo :: F -> F -> [F] #

enumFromThenTo :: F -> F -> F -> [F] #

Ix F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (F, F) -> [F] #

index :: (F, F) -> F -> Int #

unsafeIndex :: (F, F) -> F -> Int #

inRange :: (F, F) -> F -> Bool #

rangeSize :: (F, F) -> Int #

unsafeRangeSize :: (F, F) -> Int #

Num F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: F -> F -> F #

(-) :: F -> F -> F #

(*) :: F -> F -> F #

negate :: F -> F #

abs :: F -> F #

signum :: F -> F #

fromInteger :: Integer -> F #

Read F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Integral F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: F -> F -> F #

rem :: F -> F -> F #

div :: F -> F -> F #

mod :: F -> F -> F #

quotRem :: F -> F -> (F, F) #

divMod :: F -> F -> (F, F) #

toInteger :: F -> Integer #

Real F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: F -> Rational #

Show F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> F -> ShowS #

show :: F -> String #

showList :: [F] -> ShowS #

Conjurable F Source # 
Instance details

Defined in Conjure.Conjurable

Express F Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: F -> Expr #

Name F Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: F -> String #

Eq F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: F -> F -> Ordering #

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

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

(>) :: F -> F -> Bool #

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

max :: F -> F -> F #

min :: F -> F -> F #

Listable F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[F]] #

list :: [F] #