express-0.1.16: Dynamically-typed expressions involving function application and variables.
Copyright(c) 2019-2021 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Express.Fold

Description

Defines utilities for folding and unfolding Exprs.

Synopsis

Documentation

fold :: [Expr] -> Expr Source #

O(n). Folds a list of Exprs into a single Expr. (cf. unfold)

This always generates an ill-typed expression.

fold [val False, val True, val (1::Int)]
[False,True,1] :: ill-typed # ExprList $ Bool #

This is useful when applying transformations on lists of Exprs, such as canonicalize, mapValues or canonicalVariations.

> let ii = var "i" (undefined::Int)
> let kk = var "k" (undefined::Int)
> let qq = var "q" (undefined::Bool)
> let notE = value "not" not
> unfold . canonicalize . fold $ [ii,kk,notE :$ qq, notE :$ val False]
[x :: Int,y :: Int,not p :: Bool,not False :: Bool]

unfold :: Expr -> [Expr] Source #

O(n). Unfolds an Expr representing a list into a list of Exprs. This reverses the effect of fold.

> expr [1,2,3::Int]
[1,2,3] :: [Int]
> unfold $ expr [1,2,3::Int]
[1 :: Int,2 :: Int,3 :: Int]

foldPair :: (Expr, Expr) -> Expr Source #

O(1). Folds a pair of Expr values into a single Expr. (cf. unfoldPair)

This always generates an ill-typed expression, as it uses a fake pair constructor.

> foldPair (val False, val (1::Int))
(False,1) :: ill-typed # ExprPair $ Bool #
> foldPair (val (0::Int), val True)
(0,True) :: ill-typed # ExprPair $ Int #

This is useful when applying transformations on pairs of Exprs, such as canonicalize, mapValues or canonicalVariations.

> let ii = var "i" (undefined::Int)
> let kk = var "k" (undefined::Int)
> unfoldPair $ canonicalize $ foldPair (ii,kk)
(x :: Int,y :: Int)

unfoldPair :: Expr -> (Expr, Expr) Source #

O(1). Unfolds an Expr representing a pair. This reverses the effect of foldPair.

> value "," ((,) :: Bool->Bool->(Bool,Bool)) :$ val True :$ val False
(True,False) :: (Bool,Bool)
> unfoldPair $ value "," ((,) :: Bool->Bool->(Bool,Bool)) :$ val True :$ val False
(True :: Bool,False :: Bool)

foldTrio :: (Expr, Expr, Expr) -> Expr Source #

O(1). Folds a trio/triple of Expr values into a single Expr. (cf. unfoldTrio)

This always generates an ill-typed expression as it uses a fake trio/triple constructor.

> foldTrio (val False, val (1::Int), val 'a')
(False,1,'a') :: ill-typed # ExprTrio $ Bool #
> foldTrio (val (0::Int), val True, val 'b')
(0,True,'b') :: ill-typed # ExprTrio $ Int #

This is useful when applying transformations on pairs of Exprs, such as canonicalize, mapValues or canonicalVariations.

> let ii = var "i" (undefined::Int)
> let kk = var "k" (undefined::Int)
> let zz = var "z" (undefined::Int)
> unfoldPair $ canonicalize $ foldPair (ii,kk,zz)
(x :: Int,y :: Int,z :: Int)

unfoldTrio :: Expr -> (Expr, Expr, Expr) Source #

O(1). Unfolds an Expr representing a trio/triple. This reverses the effect of foldTrio.

> value ",," ((,,) :: Bool->Bool->Bool->(Bool,Bool,Bool)) :$ val True :$ val False :$ val True
(True,False,True) :: (Bool,Bool,Bool)
> unfoldTrio $ value ",," ((,,) :: Bool->Bool->Bool->(Bool,Bool,Bool)) :$ val True :$ val False :$ val True
(True :: Bool,False :: Bool,True :: Bool)

(cf. unfoldPair)

foldApp :: [Expr] -> Expr Source #

O(n). Folds a list of Expr with function application (:$). This reverses the effect of unfoldApp.

foldApp [e0]           =  e0
foldApp [e0,e1]        =  e0 :$ e1
foldApp [e0,e1,e2]     =  e0 :$ e1 :$ e2
foldApp [e0,e1,e2,e3]  =  e0 :$ e1 :$ e2 :$ e3

Remember :$ is left-associative, so:

foldApp [e0]           =    e0
foldApp [e0,e1]        =   (e0 :$ e1)
foldApp [e0,e1,e2]     =  ((e0 :$ e1) :$ e2)
foldApp [e0,e1,e2,e3]  = (((e0 :$ e1) :$ e2) :$ e3)

This function may produce an ill-typed expression.

unfoldApp :: Expr -> [Expr] Source #

O(n). Unfold a function application Expr into a list of function and arguments.

unfoldApp $ e0                    =  [e0]
unfoldApp $ e0 :$ e1              =  [e0,e1]
unfoldApp $ e0 :$ e1 :$ e2        =  [e0,e1,e2]
unfoldApp $ e0 :$ e1 :$ e2 :$ e3  =  [e0,e1,e2,e3]

Remember :$ is left-associative, so:

unfoldApp e0                          =  [e0]
unfoldApp (e0 :$ e1)                  =  [e0,e1]
unfoldApp ((e0 :$ e1) :$ e2)          =  [e0,e1,e2]
unfoldApp (((e0 :$ e1) :$ e2) :$ e3)  =  [e0,e1,e2,e3]