express-0.1.1: Dynamically-typed expressions involving applications and variables.

Copyright(c) 2019 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellSafe
LanguageHaskell2010

Data.Express.Hole

Contents

Description

Utilities for manipulating variables and typed holes encoded as Exprs.

Synopsis

Creating variables

varAsTypeOf :: String -> Expr -> Expr Source #

O(1). Creates a variable with the same type as the given Expr.

> let one = val (1::Int)
> "x" `varAsTypeOf` one
x :: Int
> "p" `varAsTypeOf` val False
p :: Bool

listVars :: Typeable a => String -> a -> [Expr] Source #

Generate an infinite list of variables based on a template and a given type. (cf. listVarsAsTypeOf)

> putL 10 $ listVars "x" (undefined :: Int)
[ x :: Int
, y :: Int
, z :: Int
, x' :: Int
, y' :: Int
, z' :: Int
, x'' :: Int
, ...
]
> putL 10 $ listVars "p" (undefined :: Bool)
[ p :: Bool
, q :: Bool
, r :: Bool
, p' :: Bool
, q' :: Bool
, r' :: Bool
, p'' :: Bool
, ...
]

listVarsAsTypeOf :: String -> Expr -> [Expr] Source #

Generate an infinite list of variables based on a template and the type of a given Expr. (cf. listVars)

> let one = val (1::Int)
> putL 10 $ "x" `listVarsAsTypeOf` one
[ x :: Int
, y :: Int
, z :: Int
, x' :: Int
, ...
]
> let false = val False
> putL 10 $ "p" `listVarsAsTypeOf` false
[ p :: Bool
, q :: Bool
, r :: Bool
, p' :: Bool
, ...
]

Typed holes

hole :: Typeable a => a -> Expr Source #

O(1). Creates an Expr representing a typed hole of the given argument type.

> hole (undefined :: Int)
_ :: Int
> hole (undefined :: Maybe String)
_ :: Maybe [Char]

A hole is represented as a variable with no name or a value named "_":

hole x = var "" x
hole x = value "_" x

isHole :: Expr -> Bool Source #

O(1). Checks if an Expr represents a typed hole. (cf. hole)

> isHole $ hole (undefined :: Int)
True
> isHole $ value "not" not :$ val True
False
> isHole $ val 'a'
False

holes :: Expr -> [Expr] Source #

O(n). Lists all holes in an expression, in order and with repetitions. (cf. nubHoles)

> holes $ hole (undefined :: Bool)
[_ :: Bool]
> holes $ value "&&" (&&) :$ hole (undefined :: Bool) :$ hole (undefined :: Bool)
[_ :: Bool,_ :: Bool]
> holes $ hole (undefined :: Bool->Bool) :$ hole (undefined::Bool)
[_ :: Bool -> Bool,_ :: Bool]

nubHoles :: Expr -> [Expr] Source #

O(n log n). Lists all holes in an expression without repetitions. (cf. holes)

> nubHoles $ hole (undefined :: Bool)
[_ :: Bool]
> nubHoles $ value "&&" (&&) :$ hole (undefined :: Bool) :$ hole (undefined :: Bool)
[_ :: Bool]
> nubHoles $ hole (undefined :: Bool->Bool) :$ hole (undefined::Bool)
[_ :: Bool,_ :: Bool -> Bool]

holeAsTypeOf :: Expr -> Expr Source #

O(1). Creates an Expr representing a typed hole with the type of the given Expr. (cf. hole)

> val (1::Int)
1 :: Int
> holeAsTypeOf $ val (1::Int)
_ :: Int