sifflet-lib-1.2.4: Library of modules shared by sifflet and its tests and its exporters.

Sifflet.Language.Expr

Synopsis

Documentation

exprToValue :: Expr -> SuccFail ValueSource

The value of an expression in the base environment.

data Expr Source

A more highly parsed type of expression

I've restricted function calls to the case where the function expression is just a symbol, since otherwise it will be hard to visualize. But with some thought, it may be possible to generalize this to ECall [Expr] -- (function:args) The constructors EOp and EGroup are not used in Sifflet itself, but they are needed for export to Python, Haskell, and similar languages; they allow a distinction between operators and functions, and wrapping expressions in parentheses. EGroup e represents parentheses used for grouping: (e); it is not used for other cases of parentheses, e.g., around the argument list in a function call.]

Constructors

EUndefined 
ESymbol Symbol 
EBool Bool 
EChar Char 
ENumber Number 
EString String 
EIf Expr Expr Expr

if test branch1 branch2

EList [Expr] 
ECall Symbol [Expr]

function name, arglist

EOp Operator Expr Expr

binary operator application

EGroup Expr

grouping parentheses

Instances

Eq Expr 
Show Expr 
Repr Expr 
HsPretty Expr

HsPretty expressions. This is going to be like in Python.hs.

PyPretty Expr

Expr as an instance of PyPretty. This instance is only for Exprs as Python exprs, for export to Python! It will conflict with the one in ToHaskell.hs (or Haskell.hs).

The EOp case needs work to deal with precedences and avoid unnecessary parens. Note that this instance declaration is for *Python* Exprs. Haskell Exprs of course should not be pretty-printed the same way!

ToXml Expr

Expr

exprIsAtomic :: Expr -> BoolSource

Is an expression atomic? Atomic expressions do not need parentheses in any reasonable language, because there is nothing to be grouped (symbols, literals) or in the case of lists, they already have brackets which separate them from their neighbors.

All lists are atomic, even if they are not literals, because (for example) we can remove parentheses from ([a + b, 7])

exprIsCompound :: Expr -> BoolSource

Compound = non-atomic

eCall :: String -> [Expr] -> ExprSource

Example: ePlus_2_3 = eCall + [eInt 2, eInt 3]

exprIsLiteral :: Expr -> BoolSource

Is an Expr a literal? A literal is a boolean, character, number, string, or list of literals. We (should) only allow user input expressions to be literal expressions.

exprSymbols :: Expr -> [Symbol]Source

Given an expression, return the list of names of variables occurring n the expression

exprVarNames :: Expr -> [String]Source

exprVarNames expr returns the names of variables in expr that are UNBOUND in the base environment. This may not be ideal, but it's a start.

data Operator Source

An operator, such as * or + An operator is associative, like +, if (a + b) + c == a + (b + c). Its grouping is left to right if (a op b op c) means (a op b) op c; right to left if (a op b op c) means a op (b op c). Most operators group left to right.

Constructors

Operator 

type Precedence = IntSource

Operator priority, normally is > 0 or >= 0, but does that really matter? I think not.

data OperatorGrouping Source

Operator grouping: left to right or right to left, or perhaps not at all

Constructors

GroupLtoR 
GroupRtoL 
GroupNone 

type ExprTree = Tree ExprNodeSource

EXPRESSION TREES For pure Sifflet, so not defined for extended expressions.

treeToExpr :: ExprTree -> ExprSource

Convert an expression tree (back) to an expression It will not give back the *same* expression in the case of an EList.

data EvalRes e Source

Instances

Monad EvalRes 
Eq e => Eq (EvalRes e) 
Show e => Show (EvalRes e) 

data Value Source

Instances

Eq Value 
Show Value 
Repr Value 
ToXml Value

Values Still used in exprToXml in the EList case :-(

data Functions Source

A collection of functions, typically to be saved or exported or read from a file

Constructors

Functions [Function] 

data Function Source

A function may have a name and always has an implementation

Instances

Eq Function

We need to be able to say functions are equal (or not) in order to tell if environments are equal or not, in order to know whether there are unsaved changes. This is tricky since the primitive function implementations do not instantiate Eq, so if it's primitive == primitive? we go by the names alone (there's nothing else to go by). Otherwise all the parts must be equal.

Show Function 
Repr Function 
ToXml Function

Functions

functionType :: Function -> ([VpType], VpType)Source

Type type of a function, a tuple of (arg types, result type)

typeMatch :: VpType -> Value -> TypeEnv -> SuccFail TypeEnvSource

Try to match a single type and value, may result in binding a type variable in a new environment or just the old environment

typeCheck :: [String] -> [VpType] -> [Value] -> SuccFail [Value]Source

Check whether the values agree with the types (which may be abstract)

This is *probably* too lenient in the case of type variables: it can pass a mixed-type list.

vpTypeOf :: Value -> SuccFail VpTypeSource

Determine the type of a value. May result in a type variable.

type Env = [EnvFrame]Source

envInsertL :: Env -> [String] -> [Value] -> EnvSource

Insert names and values from lists into an environment

envPop :: Env -> EnvSource

Return to the environment prior to an extendEnv

envGet :: Env -> String -> ValueSource

Get the value of a variable from an environment

envSymbols :: Env -> [String]Source

List of all symbols bound in the environment

envFunctionSymbols :: Env -> [String]Source

List of all symbols bound to functions in the environment

envFunctions :: Env -> FunctionsSource

All the functions in the environment

apply :: Value -> [Value] -> Env -> Int -> EvalResultSource

Apply a function fvalue to a list of actual arguments args in an environment env and with a limited stack size stacksize

decideTypes :: Expr -> [String] -> Env -> Either String ([VpType], VpType)Source

decideTypes tries to find the argument types and return type of an expression considered as the body of a function, at the same time checking for consistency of inputs and outputs between the parts of the expression. It returns Right (argtypes, returntype) if successful; Left errormessage otherwise.