sifflet-2.3.0: Simple, visual, functional language for learning about recursion.

Safe HaskellSafe
LanguageHaskell2010

Language.Sifflet.Expr

Synopsis

Documentation

data ArgSpec Source

Constructors

ArgSpec 

Fields

argName :: String
 
argInlets :: Int
 

aspecsLookup :: String -> [ArgSpec] -> Maybe Int Source

Try to find the number of inlets for an argument from a list of ArgSpec

exprToValue :: Expr -> SuccFail Value Source

The value of an expression in the base environment.

data Expr Source

A more highly "parsed" type of expression

Function calls have two kinds: 1. ECall: restricted to the case where the function expression is just a symbol, since otherwise it will be hard to visualize. 2. EApp: allows any expression to be the function, but is applied to only one argument. For now, the type checker will convert ECall expressions to EApp expressions. Ultimately, the two variants ought to be unified.

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] 
ELambda Symbol Expr 
EApp Expr Expr

apply function to argument

ECall Symbol [Expr]

function name, arglist

EOp Operator Expr Expr

binary operator application

EGroup Expr

grouping parentheses

Instances

Eq Expr Source 
Show Expr Source 
Repr Expr Source 
HsPretty Expr Source

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

PyPretty Expr Source

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 Source

Expr

toLambdaExpr :: [String] -> Expr -> SuccFail Expr Source

Try to convert the arguments and body of a function to a lambda expression. Fails if there are no arguments, since a lambda expression requires one. If there are multiple arguments, then we get a nested lambda expression.

callToApp :: Expr -> Expr Source

Convert an ECall expression to an EApp expression

mapply :: Expr -> [Expr] -> Expr Source

Helper for callToApp, but may have other uses. Creates an EApp expression representing a function call with possibly many arguments.

appToCall :: Expr -> Expr Source

Convert an EApp expression to an ECall expression

mcall :: Expr -> [Expr] -> Expr Source

Helper for appToCall, but may have other uses. Creates an ECall expression.

exprIsAtomic :: Expr -> Bool Source

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 -> Bool Source

Compound = non-atomic

eIf :: Expr -> Expr -> Expr -> Expr Source

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

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

exprIsLiteral :: Expr -> Bool Source

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 in 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 = Int Source

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 

data Value Source

Instances

Eq Value Source 
Show Value Source 
Repr Value Source 
ToXml Value Source

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

newtype 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 Source

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 Source 
Repr Function Source 
ToXml Function Source

Functions

functionArgResultTypes :: Function -> ([Type], Type) Source

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

functionType :: Function -> Type Source

The type of a function, where (a -> b) is represented as TypeCons Function [a, b]

type TypeVarName = String Source

Type variable name

type TypeConsName = String Source

Type constructor name

data Type Source

A Type is either a type variable or a constructed type with a constructor and a list of type parameters

typeFunction :: [Type] -> Type -> Type Source

The type of a function, from its argument types and result type, where (a -> b) is represented as TypeCons Function [a, b]. Note that for n-ary functions, n > 2 implies nested function types: (a -> b -> c) is represented as TypeCons Function [a, TypeCons Function [b, c]], etc.

type Env = [EnvFrame] Source

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

Insert names and values from lists into an environment

envPop :: Env -> Env Source

Return to the environment prior to an extendEnv

envGet :: Env -> String -> Value Source

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 -> Functions Source

All the functions in the environment

apply :: Value -> [Value] -> Env -> Int -> EvalResult Source

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