code-conjure-0.5.2: synthesize 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.Defn

Description

This module is part of Conjure.

This module exports the Defn type synonym and utilities involving it.

You are probably better off importing Conjure.

Synopsis

Documentation

type Defn = [Bndn] Source #

A function definition as a list of top-level case bindings (Bndn).

Here is an example using the notation from Data.Express.Fixtures:

sumV :: Expr
sumV  =  var "sum" (undefined :: [Int] -> Int)

(=-) = (,)
infixr 0 =-

sumDefn :: Defn
sumDefn  =  [ sum' nil           =-  zero
            , sum' (xx -:- xxs)  =-  xx -+- (sumV :$ xxs)
            ]  where  sum' e  =  sumV :$ e

type Bndn = (Expr, Expr) Source #

A single binding in a definition (Defn).

toDynamicWithDefn :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe Dynamic Source #

Evaluates an Expr to a Dynamic value using the given Defn as definition when a recursive call is found.

Arguments:

  1. a function that deeply reencodes an expression (cf. expr)
  2. the maximum number of recursive evaluations
  3. a Defn to be used when evaluating the given Expr
  4. an Expr to be evaluated

This function cannot be used to evaluate a functional value for the given Defn and can only be used when occurrences of the given Defn are fully applied.

The function the deeply reencodes an Expr can be defined using functionality present in Conjure.Conjurable. Here's a quick-and-dirty version that is able to reencode Bools, Ints and their lists:

exprExpr :: Expr -> Expr
exprExpr  =  conjureExpress (undefined :: Bool -> [Bool] -> Int -> [Int] -> ())

The maximum number of recursive evaluations counts in two ways:

  1. the maximum number of entries in the recursive-evaluation memo table;
  2. the maximum number of terminal values considered (but in this case the limit is multiplied by the _size_ of the given Defn.

These could be divided into two separate parameters but then there would be an extra _dial_ to care about...

(cf. devaluate, deval, devl)

devaluate :: Typeable a => (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe a Source #

Evaluates an Expr expression into Just a regular Haskell value using a Defn definition when it is found. If there's a type-mismatch, this function returns Nothing.

This function requires a Expr-deep-reencoding function and a limit to the number of recursive evaluations.

(cf. toDynamicWithDefn, deval, devl)

deval :: Typeable a => (Expr -> Expr) -> Int -> Defn -> a -> Expr -> a Source #

Evaluates an Expr expression into a regular Haskell value using a Defn definition when it is found in the given expression. If there's a type-mismatch, this function return a default value.

This function requires a Expr-deep-reencoding function and a limit to the number of recursive evaluations.

(cf. toDynamicWithDefn, devaluate, devl')

devl :: Typeable a => (Expr -> Expr) -> Int -> Defn -> Expr -> a Source #

Evaluates an Expr expression into a regular Haskell value using a Defn definition when it is found in the given expression. If there's a type-mismatch, this raises an error.

This function requires a Expr-deep-reencoding function and a limit to the number of recursive evaluations.

(cf. toDynamicWithDefn, devaluate, deval')

devalFast :: Typeable a => (Expr -> Expr) -> Int -> Defn -> a -> Expr -> a Source #

Like deval but only works for when the given Defn definition has no case breakdowns.

In other words, this only works when the given Defn is a singleton list whose first value of the only element is a simple application without constructors.

showDefn :: Defn -> String Source #

Pretty-prints a Defn as a String:

> putStr $ showDefn sumDefn
sum []  =  0
sum (x:xs)  =  x + sum xs

defnApparentlyTerminates :: Defn -> Bool Source #

Returns whether the given definition apparentlyTerminates.