Copyright | (c) 2019-2024 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Documentation
match :: Expr -> Expr -> Maybe [(Expr, Expr)] Source #
Given two expressions, returns a Just
list of matches
of subexpressions of the first expressions
to variables in the second expression.
Returns Nothing
when there is no match.
> let zero = val (0::Int) > let one = val (1::Int) > let xx = var "x" (undefined :: Int) > let yy = var "y" (undefined :: Int) > let e1 -+- e2 = value "+" ((+)::Int->Int->Int) :$ e1 :$ e2
> (zero -+- one) `match` (xx -+- yy) Just [(y :: Int,1 :: Int),(x :: Int,0 :: Int)]
> (zero -+- (one -+- two)) `match` (xx -+- yy) Just [(y :: Int,1 + 2 :: Int),(x :: Int,0 :: Int)]
> (zero -+- (one -+- two)) `match` (xx -+- (yy -+- yy)) Nothing
In short:
(zero -+- one) `match` (xx -+- yy) = Just [(xx,zero), (yy,one)] (zero -+- (one -+- two)) `match` (xx -+- yy) = Just [(xx,zero), (yy,one-+-two)] (zero -+- (one -+- two)) `match` (xx -+- (yy -+- yy)) = Nothing
matchWith :: [(Expr, Expr)] -> Expr -> Expr -> Maybe [(Expr, Expr)] Source #
Like match
but allowing predefined bindings.
matchWith [(xx,zero)] (zero -+- one) (xx -+- yy) = Just [(xx,zero), (yy,one)] matchWith [(xx,one)] (zero -+- one) (xx -+- yy) = Nothing
isInstanceOf :: Expr -> Expr -> Bool Source #
Given two Expr
s,
checks if the first expression
is an instance of the second
in terms of variables.
(cf. encompasses
, hasInstanceOf
)
> let zero = val (0::Int) > let one = val (1::Int) > let xx = var "x" (undefined :: Int) > let yy = var "y" (undefined :: Int) > let e1 -+- e2 = value "+" ((+)::Int->Int->Int) :$ e1 :$ e2
one `isInstanceOf` one = True xx `isInstanceOf` xx = True yy `isInstanceOf` xx = True zero `isInstanceOf` xx = True xx `isInstanceOf` zero = False one `isInstanceOf` zero = False (xx -+- (yy -+- xx)) `isInstanceOf` (xx -+- yy) = True (yy -+- (yy -+- xx)) `isInstanceOf` (xx -+- yy) = True (zero -+- (yy -+- xx)) `isInstanceOf` (zero -+- yy) = True (one -+- (yy -+- xx)) `isInstanceOf` (zero -+- yy) = False
isSubexprOf :: Expr -> Expr -> Bool Source #
O(n^2).
Checks if an Expr
is a subexpression of another.
> (xx -+- yy) `isSubexprOf` (zz -+- (xx -+- yy)) True
> (xx -+- yy) `isSubexprOf` abs' (yy -+- xx) False
> xx `isSubexprOf` yy False
encompasses :: Expr -> Expr -> Bool Source #
Given two Expr
s,
checks if the first expression
encompasses the second expression
in terms of variables.
This is equivalent to flipping the arguments of isInstanceOf
.
zero `encompasses` xx = False xx `encompasses` zero = True