sifflet-lib-1.0: Library of modules shared by sifflet and its tests and its exporters.Source codeContentsIndex
Sifflet.Language.Expr
Synopsis
stringToExpr :: String -> SuccFail Expr
exprToValue :: Expr -> SuccFail Value
stringToValue :: String -> SuccFail Value
stringToLiteral :: String -> SuccFail Expr
data Symbol = Symbol String
type OInt = Integer
type OStr = String
type OBool = Bool
type OChar = Char
type OFloat = Double
data Expr
= EUndefined
| ESymbol Symbol
| ELit Value
| EIf Expr Expr Expr
| EList [Expr]
| ECall Symbol [Expr]
eSymbol :: String -> Expr
eInt :: OInt -> Expr
eString :: OStr -> Expr
eChar :: OChar -> Expr
eFloat :: OFloat -> Expr
eBool :: Bool -> Expr
eFalse :: Expr
eTrue :: Expr
eIf :: Expr -> Expr -> Expr -> Expr
eList :: [Expr] -> Expr
eCall :: String -> [Expr] -> Expr
exprSymbols :: Expr -> [Symbol]
exprVarNames :: Expr -> [String]
type ExprTree = Tree ExprNode
data ExprNode = ENode ExprNodeLabel EvalResult
data ExprNodeLabel
= NUndefined
| NSymbol Symbol
| NLit Value
exprNodeIoletCounter :: Env -> ExprNode -> (Int, Int)
exprToTree :: Expr -> ExprTree
treeToExpr :: ExprTree -> Expr
exprToReprTree :: Expr -> Tree String
type EvalResult = EvalRes Value
data EvalRes e
= EvalOk e
| EvalError String
| EvalUntried
evalTree :: ExprTree -> Env -> ExprTree
unevalTree :: ExprTree -> ExprTree
data Value
= VBool OBool
| VChar OChar
| VInt OInt
| VFloat OFloat
| VStr OStr
| VFun Function
| VList [Value]
valueFunction :: Value -> Function
data Functions = Functions [Function]
data Function = Function (Maybe String) [VpType] VpType FunctionImpl
functionName :: Function -> String
functionNArgs :: Function -> Int
functionArgTypes :: Function -> [VpType]
functionResultType :: Function -> VpType
functionType :: Function -> ([VpType], VpType)
functionArgNames :: Function -> [String]
functionBody :: Function -> Expr
functionImplementation :: Function -> FunctionImpl
type FunctionDefTuple = (String, [String], [VpType], VpType, Expr)
functionToDef :: Function -> FunctionDefTuple
functionFromDef :: FunctionDefTuple -> Function
data FunctionImpl
= Primitive ([Value] -> EvalResult)
| Compound [String] Expr
data VpType
= VpTypeBool
| VpTypeChar
| VpTypeNum
| VpTypeString
| VpTypeList VpType
| VpTypeFunction [VpType] VpType
| VpTypeVar String
typeMatch :: VpType -> Value -> TypeEnv -> SuccFail TypeEnv
typeCheck :: [String] -> [VpType] -> [Value] -> SuccFail [Value]
vpTypeOf :: Value -> SuccFail VpType
type TypeEnv = Map String VpType
emptyTypeEnv :: TypeEnv
type Env = [EnvFrame]
emptyEnv :: Env
makeEnv :: [String] -> [Value] -> Env
extendEnv :: [String] -> [Value] -> Env -> Env
envInsertL :: Env -> [String] -> [Value] -> Env
envPop :: Env -> Env
envIns :: Env -> String -> Value -> Env
envSet :: Env -> String -> Value -> Env
envGet :: Env -> String -> Value
envGetFunction :: Env -> String -> Function
envLookup :: Env -> String -> Maybe Value
envLookupFunction :: Env -> String -> Maybe Function
envSymbols :: Env -> [String]
envFunctionSymbols :: Env -> [String]
envFunctions :: Env -> Functions
eval :: Expr -> Env -> EvalResult
apply :: Value -> [Value] -> Env -> Int -> EvalResult
decideTypes :: Expr -> [String] -> Env -> Either String ([VpType], VpType)
newUndefinedFunction :: String -> [String] -> Function
undefinedTypes :: [String] -> ([VpType], VpType)
ePlus :: Expr -> Expr -> Expr
eTimes :: Expr -> Expr -> Expr
eMinus :: Expr -> Expr -> Expr
eDiv :: Expr -> Expr -> Expr
eMod :: Expr -> Expr -> Expr
eAdd1 :: Expr -> Expr
eSub1 :: Expr -> Expr
eEq :: Expr -> Expr -> Expr
eNe :: Expr -> Expr -> Expr
eGt :: Expr -> Expr -> Expr
eGe :: Expr -> Expr -> Expr
eLt :: Expr -> Expr -> Expr
eLe :: Expr -> Expr -> Expr
eZerop :: Expr -> Expr
ePositivep :: Expr -> Expr
eNegativep :: Expr -> Expr
baseEnv :: Env
Documentation
stringToExpr :: String -> SuccFail ExprSource
exprToValue :: Expr -> SuccFail ValueSource
The value of an expression in the base environment.
stringToValue :: String -> SuccFail ValueSource
stringToLiteral :: String -> SuccFail ExprSource
data Symbol Source
Constructors
Symbol String
show/hide Instances
type OInt = IntegerSource
type OStr = StringSource
type OBool = BoolSource
type OChar = CharSource
type OFloat = DoubleSource
data Expr Source

A more highly parsed type of expression

ELit (literals) are primitive (self-evaluating) expressions, in the sense that if x is a literal, then eval x env = EvalOk x for any environment env. 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)

Constructors
EUndefined
ESymbol Symbol
ELit Value
EIf Expr Expr Expr
EList [Expr]
ECall Symbol [Expr]
show/hide Instances
eSymbol :: String -> ExprSource
eInt :: OInt -> ExprSource
eString :: OStr -> ExprSource
eChar :: OChar -> ExprSource
eFloat :: OFloat -> ExprSource
eBool :: Bool -> ExprSource
eFalse :: ExprSource
eTrue :: ExprSource
eIf :: Expr -> Expr -> Expr -> ExprSource
eList :: [Expr] -> ExprSource
eCall :: String -> [Expr] -> ExprSource
Example: ePlus_2_3 = eCall + [eInt 2, eInt 3]
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.
type ExprTree = Tree ExprNodeSource
data ExprNode Source
Constructors
ENode ExprNodeLabel EvalResult
show/hide Instances
data ExprNodeLabel Source
Constructors
NUndefined
NSymbol Symbol
NLit Value
show/hide Instances
exprNodeIoletCounter :: Env -> ExprNode -> (Int, Int)Source
exprToTree :: Expr -> ExprTreeSource
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.
exprToReprTree :: Expr -> Tree StringSource
type EvalResult = EvalRes ValueSource
data EvalRes e Source
Constructors
EvalOk e
EvalError String
EvalUntried
show/hide Instances
evalTree :: ExprTree -> Env -> ExprTreeSource
unevalTree :: ExprTree -> ExprTreeSource
data Value Source
Constructors
VBool OBool
VChar OChar
VInt OInt
VFloat OFloat
VStr OStr
VFun Function
VList [Value]
show/hide Instances
valueFunction :: Value -> FunctionSource
data Functions Source
A collection of functions, typically to be saved or exported or read from a file
Constructors
Functions [Function]
show/hide Instances
data Function Source
A function may have a name and always has an implementation
Constructors
Function (Maybe String) [VpType] VpType FunctionImpl
show/hide Instances
functionName :: Function -> StringSource
functionNArgs :: Function -> IntSource
functionArgTypes :: Function -> [VpType]Source
functionResultType :: Function -> VpTypeSource
functionType :: Function -> ([VpType], VpType)Source
Type type of a function, a tuple of (arg types, result type)
functionArgNames :: Function -> [String]Source
functionBody :: Function -> ExprSource
functionImplementation :: Function -> FunctionImplSource
type FunctionDefTuple = (String, [String], [VpType], VpType, Expr)Source
functionToDef :: Function -> FunctionDefTupleSource
functionFromDef :: FunctionDefTuple -> FunctionSource
data FunctionImpl Source
Constructors
Primitive ([Value] -> EvalResult)
Compound [String] Expr
show/hide Instances
data VpType Source
Constructors
VpTypeBool
VpTypeChar
VpTypeNum
VpTypeString
VpTypeList VpType
VpTypeFunction [VpType] VpType
VpTypeVar String
show/hide Instances
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 TypeEnv = Map String VpTypeSource
emptyTypeEnv :: TypeEnvSource
type Env = [EnvFrame]Source
emptyEnv :: EnvSource
makeEnv :: [String] -> [Value] -> EnvSource
extendEnv :: [String] -> [Value] -> Env -> EnvSource
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
envIns :: Env -> String -> Value -> EnvSource
envSet :: Env -> String -> Value -> EnvSource
envGet :: Env -> String -> ValueSource
Get the value of a variable from an environment
envGetFunction :: Env -> String -> FunctionSource
envLookup :: Env -> String -> Maybe ValueSource
envLookupFunction :: Env -> String -> Maybe FunctionSource
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
eval :: Expr -> Env -> EvalResultSource
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.
newUndefinedFunction :: String -> [String] -> FunctionSource
undefinedTypes :: [String] -> ([VpType], VpType)Source
ePlus :: Expr -> Expr -> ExprSource
eTimes :: Expr -> Expr -> ExprSource
eMinus :: Expr -> Expr -> ExprSource
eDiv :: Expr -> Expr -> ExprSource
eMod :: Expr -> Expr -> ExprSource
eAdd1 :: Expr -> ExprSource
eSub1 :: Expr -> ExprSource
eEq :: Expr -> Expr -> ExprSource
eNe :: Expr -> Expr -> ExprSource
eGt :: Expr -> Expr -> ExprSource
eGe :: Expr -> Expr -> ExprSource
eLt :: Expr -> Expr -> ExprSource
eLe :: Expr -> Expr -> ExprSource
eZerop :: Expr -> ExprSource
ePositivep :: Expr -> ExprSource
eNegativep :: Expr -> ExprSource
baseEnv :: EnvSource
Produced by Haddock version 2.6.1