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

Description

This module is part of Conjure.

This defines functions that deal with recursive descent and deconstructions

Synopsis

Documentation

conjureIsDeconstruction :: Conjurable f => f -> Int -> Expr -> Bool Source #

Returns whether an expression is a deconstruction based on the results of testing.

This function takes three arguments:

  1. a (conjurable) function from where type info is obtained
  2. the maximum number of tests
  3. an Expr of a possible deconstruction.

To facilitate use, this function is often used in curried form in the contest of a "conjuring" function. Given that the type of the function-to-be-conjured is '[Int] -> Int' and we would like to test for a maximum of 60 arguments, we would declare:

> isDeconstruction = conjureIsDeconstruction (undefined :: [Int] -> Int) 60

Deconstructions are expressions that decrease the size of all arguments that have a size greater than 0. Here are some examples:

> import Data.Express.Fixtures
> isDeconstruction  (minus :$ i_ :$ one)
True
> isDeconstruction (tail' is_)
True
> isDeconstruction (minus :$ i_ :$ two)
True
decandidates = [minus :$ i_ :$ one, tail' is_, head' is_, zero -*- i_]
> filter isDeconstruction decandidates
[ _ - 1 :: Int
, tail _ :: [Int]
]

Well formed deconstructions should have exactly one typed hole:

> isDeconstruction (i_ -+- i_)
False
> isDeconstruction (xx -+- one)
False

We can only deconstruct to the same type. Even though tail is a deconstruction, head is not.

> isDeconstruction (head' is_)
False

Deconstructions should always reduce the size of expressions:

> isDeconstruction (take' two is_)
False

Lastly we disallow deconstructions that always map to values of size 0. For the purposes of expression generation, in these cases we are better of not recursing at all and returning a constant value!

> isDeconstruction (zero -*- i_)
False

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

Returns whether a non-empty subset of arguments descends arguments by deconstruction.

> descends isDec (xxs -++- yys) (xxs -++- tail' yys)
True
> descends isDec (xxs -++- yys) (xxs -++- yys)
False
> descends isDec (xxs -++- yys) (head' xxs -:- tail xxs  -++-  head' yys -:- tail yys)
False

candidateDeconstructionsFrom :: Expr -> [Expr] Source #

Compute candidate deconstructions from an Expr.

This is used in the implementation of candidateDefnsC followed by conjureIsDeconstruction.

> candidateDeconstructionsFrom (xx `mod'` yy)
[ _ `mod` y
, x `mod` _
]

To be constrasted with candidateDeconstructionsFromHoled.

candidateDeconstructionsFromHoled :: Expr -> [Expr] Source #

Compute candidate deconstructions from an Expr.

This is used in the implementation of candidateExprs followed by conjureIsDeconstruction.

This is similar to canonicalVariations but always leaves a hole of the same return type as the given expression.

> candidateDeconstructionsFrom (i_ `mod'` i_)
[ _ `mod` x
, x `mod` _
]

To be contrasted with candidateDeconstructionsFrom