Language.Scheme.Types
- data Env = Environment {}
- nullEnv :: IO Env
- macroNamespace :: [Char]
- varNamespace :: [Char]
- data LispError
- showError :: LispError -> String
- type ThrowsError = Either LispError
- trapError :: (MonadError e m, Show e) => m String -> m String
- extractValue :: ThrowsError a -> a
- type IOThrowsError = ErrorT LispError IO
- liftThrows :: ThrowsError a -> IOThrowsError a
- runIOThrows :: IOThrowsError String -> IO String
- data LispVal
- = Atom String
- | List [LispVal]
- | DottedList [LispVal] LispVal
- | Vector (Array Int LispVal)
- | HashTable (Map LispVal LispVal)
- | Number Integer
- | Float Double
- | Complex (Complex Double)
- | Rational Rational
- | String String
- | Char Char
- | Bool Bool
- | PrimitiveFunc ([LispVal] -> ThrowsError LispVal)
- | Func { }
- | IOFunc ([LispVal] -> IOThrowsError LispVal)
- | Port Handle
- | Continuation {
- closure :: Env
- body :: [LispVal]
- continuation :: LispVal
- contFunctionArgs :: Maybe [LispVal]
- continuationFunction :: Maybe (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal)
- | Nil String
- makeNullContinuation :: Env -> LispVal
- makeCPS :: Env -> LispVal -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> LispVal
- makeCPSWArgs :: Env -> LispVal -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> [LispVal] -> LispVal
- eqv :: [LispVal] -> ThrowsError LispVal
- eqvList :: ([LispVal] -> ThrowsError LispVal) -> [LispVal] -> ThrowsError LispVal
- eqVal :: LispVal -> LispVal -> Bool
- showVal :: LispVal -> String
- unwordsList :: [LispVal] -> String
Documentation
A Scheme environment containing variable bindings of form (namespaceName, variableName), variableValue
macroNamespace :: [Char]Source
varNamespace :: [Char]Source
Types of errors that may occur when evaluating Scheme code
Constructors
| NumArgs Integer [LispVal] | Invalid number of function arguments |
| TypeMismatch String LispVal | Type error |
| Parser ParseError | Parsing error |
| BadSpecialForm String LispVal | Invalid special (built-in) form |
| NotFunction String String | |
| UnboundVar String String | |
| DivideByZero | Divide by Zero error |
| NotImplemented String | |
| InternalError String | An internal error within husk; in theory user (Scheme) code should never allow one of these errors to be triggered. |
| Default String | Default error |
type ThrowsError = Either LispErrorSource
extractValue :: ThrowsError a -> aSource
type IOThrowsError = ErrorT LispError IOSource
liftThrows :: ThrowsError a -> IOThrowsError aSource
Scheme data types
Constructors
| Atom String | Symbol |
| List [LispVal] | List |
| DottedList [LispVal] LispVal | Pair |
| Vector (Array Int LispVal) | Vector |
| HashTable (Map LispVal LispVal) | Hash table. Technically this could be a derived data type instead of being built-in to the interpreter. And perhaps in the future it will be. But for now, a hash table is too important of a data type to not be included. Map is technically the wrong structure to use for a hash table since it is based on a binary tree and hence operations tend to be O(log n) instead of O(1). However, according to http://www.opensubscriber.com/message/haskell-cafe@haskell.org/10779624.html Map has good performance characteristics compared to the alternatives. So it stays for the moment... |
| Number Integer | Integer |
| Float Double | Floating point |
| Complex (Complex Double) | Complex number |
| Rational Rational | Rational number |
| String String | String |
| Char Char | Character |
| Bool Bool | Boolean |
| PrimitiveFunc ([LispVal] -> ThrowsError LispVal) | |
| Func | Function |
| IOFunc ([LispVal] -> IOThrowsError LispVal) | |
| Port Handle | I/O port |
| Continuation | Continuation |
Fields
| |
| Nil String | Internal use only; do not use this type directly. |
makeCPS :: Env -> LispVal -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> LispValSource
makeCPSWArgs :: Env -> LispVal -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> [LispVal] -> LispValSource
eqvList :: ([LispVal] -> ThrowsError LispVal) -> [LispVal] -> ThrowsError LispValSource
unwordsList :: [LispVal] -> StringSource