Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- data ArgSpec = ArgSpec {}
- aspecsLookup :: String -> [ArgSpec] -> Maybe Int
- type EvalResult = EvalRes Value
- data EvalRes e
- = EvalOk e
- | EvalError String
- | EvalUntried
- exprToValue :: Expr -> SuccFail Value
- valueToLiteral :: Value -> SuccFail Expr
- valueToLiteral' :: Value -> Expr
- newtype Symbol = Symbol String
- type OStr = String
- type OBool = Bool
- type OChar = Char
- data Expr
- eSymbol :: String -> Expr
- eSym :: String -> Expr
- eInt :: Integer -> Expr
- eString :: OStr -> Expr
- eChar :: OChar -> Expr
- eFloat :: Double -> Expr
- toLambdaExpr :: [String] -> Expr -> SuccFail Expr
- callToApp :: Expr -> Expr
- mapply :: Expr -> [Expr] -> Expr
- appToCall :: Expr -> Expr
- mcall :: Expr -> [Expr] -> Expr
- exprIsAtomic :: Expr -> Bool
- exprIsCompound :: Expr -> Bool
- eBool :: Bool -> Expr
- eFalse :: Expr
- eTrue :: Expr
- eIf :: Expr -> Expr -> Expr -> Expr
- eList :: [Expr] -> Expr
- eCall :: String -> [Expr] -> Expr
- exprIsLiteral :: Expr -> Bool
- exprSymbols :: Expr -> [Symbol]
- exprVarNames :: Expr -> [String]
- data Operator = Operator {}
- type Precedence = Int
- data OperatorGrouping
- data Value
- valueFunction :: Value -> Function
- newtype Functions = Functions [Function]
- data Function = Function (Maybe String) [Type] Type FunctionImpl
- functionName :: Function -> String
- functionNArgs :: Function -> Int
- functionArgSpecs :: Function -> [ArgSpec]
- functionArgTypes :: Function -> [Type]
- functionResultType :: Function -> Type
- functionArgResultTypes :: Function -> ([Type], Type)
- functionType :: Function -> Type
- functionArgNames :: Function -> [String]
- functionBody :: Function -> Expr
- functionImplementation :: Function -> FunctionImpl
- type FunctionDefTuple = (String, [String], [Type], Type, Expr)
- functionToDef :: Function -> FunctionDefTuple
- functionFromDef :: FunctionDefTuple -> Function
- data FunctionImpl
- type TypeVarName = String
- type TypeConsName = String
- data Type
- typeBool :: Type
- typeChar :: Type
- typeNum :: Type
- typeString :: Type
- typeList :: Type -> Type
- typeFunction :: [Type] -> Type -> Type
- 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
- evalWithLimit :: Expr -> Env -> Int -> EvalResult
- stackSize :: Int
- apply :: Value -> [Value] -> Env -> Int -> EvalResult
- newUndefinedFunction :: String -> [String] -> Function
- 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
aspecsLookup :: String -> [ArgSpec] -> Maybe Int Source
Try to find the number of inlets for an argument from a list of ArgSpec
type EvalResult = EvalRes Value Source
exprToValue :: Expr -> SuccFail Value Source
The value of an expression in the base environment.
valueToLiteral :: Value -> SuccFail Expr Source
valueToLiteral' :: Value -> 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.]
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 |
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.
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.
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
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.
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.
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
valueFunction :: Value -> Function Source
A collection of functions, typically to be saved or exported or read from a file
A function may have a name and always has an implementation
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 |
functionName :: Function -> String Source
functionNArgs :: Function -> Int Source
functionArgSpecs :: Function -> [ArgSpec] Source
functionArgTypes :: Function -> [Type] Source
functionResultType :: Function -> Type Source
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]
functionArgNames :: Function -> [String] Source
functionBody :: Function -> Expr Source
data FunctionImpl Source
type TypeVarName = String Source
Type variable name
type TypeConsName = String Source
Type constructor name
A Type is either a type variable or a constructed type with a constructor and a list of type parameters
typeString :: Type Source
typeFunction :: [Type] -> Type -> Type Source
envInsertL :: Env -> [String] -> [Value] -> Env Source
Insert names and values from lists into an environment
envGetFunction :: Env -> String -> Function Source
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
eval :: Expr -> Env -> EvalResult Source
evalWithLimit :: Expr -> Env -> Int -> EvalResult Source
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
newUndefinedFunction :: String -> [String] -> Function Source
ePositivep :: Expr -> Expr Source
eNegativep :: Expr -> Expr Source