Copyright | (c) 2021 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type Defn = [Bndn]
- type Bndn = (Expr, Expr)
- toDynamicWithDefn :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe Dynamic
- devaluate :: Typeable a => (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe a
- deval :: Typeable a => (Expr -> Expr) -> Int -> Defn -> a -> Expr -> a
- devl :: Typeable a => (Expr -> Expr) -> Int -> Defn -> Expr -> a
- devalFast :: Typeable a => (Expr -> Expr) -> Int -> Defn -> a -> Expr -> a
- showDefn :: Defn -> String
- defnApparentlyTerminates :: Defn -> Bool
- isRedundantDefn :: Defn -> Bool
- module Conjure.Expr
Documentation
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
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:
- a function that deeply reencodes an expression (cf.
expr
) - the maximum number of recursive evaluations
- a
Defn
to be used when evaluating the givenExpr
- 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 Bool
s, Int
s and their lists:
exprExpr :: Expr -> Expr exprExpr = conjureExpress (undefined :: Bool -> [Bool] -> Int -> [Int] -> ())
The maximum number of recursive evaluations counts in two ways:
- the maximum number of entries in the recursive-evaluation memo table;
- 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...
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')
defnApparentlyTerminates :: Defn -> Bool Source #
Returns whether the given definition apparentlyTerminates
.
isRedundantDefn :: Defn -> Bool Source #
Returns whether the given Defn
is redundant
with regards to its patterns.
Here is an example of a redundant Defn
:
0 ? 0 = 0 0 ? x = 0 x ? 0 = x x ? y = x
It is redundant because it is equivalent to:
0 ? _ = 0 x ? _ = x
If the given expression is incomplete (hasHole
)
this function returns True
as nothing can be said.
module Conjure.Expr