Copyright | Justin Ethier |
---|---|
License | MIT (see LICENSE in the distribution) |
Maintainer | github.com/justinethier |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This module contains top-level data type definitions, environments, error types, and associated functions.
Synopsis
- data Env = Environment {}
- nullEnv :: IO Env
- data LispError
- type ThrowsError = Either LispError
- type IOThrowsError = ExceptT LispError IO
- liftThrows :: ThrowsError a -> IOThrowsError a
- showCallHistory :: String -> [LispVal] -> String
- data LispVal
- = Atom String
- | List [LispVal]
- | DottedList [LispVal] LispVal
- | Vector (Array Int LispVal)
- | ByteVector ByteString
- | HashTable (Map LispVal LispVal)
- | Number Integer
- | Float Double
- | Complex (Complex Double)
- | Rational Rational
- | String String
- | Char Char
- | Bool Bool
- | PrimitiveFunc ([LispVal] -> ThrowsError LispVal)
- | Func { }
- | HFunc { }
- | IOFunc ([LispVal] -> IOThrowsError LispVal)
- | EvalFunc ([LispVal] -> IOThrowsError LispVal)
- | CustFunc ([LispVal] -> IOThrowsError LispVal)
- | Pointer {
- pointerVar :: String
- pointerEnv :: Env
- | Opaque Dynamic
- | Port Handle (Maybe Knob)
- | Continuation { }
- | Syntax {
- synClosure :: Maybe Env
- synRenameClosure :: Maybe Env
- synDefinedInMacro :: Bool
- synEllipsis :: String
- synIdentifiers :: [LispVal]
- synRules :: [LispVal]
- | SyntaxExplicitRenaming LispVal
- | LispEnv Env
- | EOF
- | Nil String
- nullLisp :: LispVal
- toOpaque :: Typeable a => a -> LispVal
- fromOpaque :: forall a. Typeable a => LispVal -> ThrowsError a
- data DeferredCode
- = SchemeBody [LispVal]
- | HaskellBody {
- contFunction :: Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal
- contFunctionArgs :: Maybe [LispVal]
- data DynamicWinders = DynamicWinders {}
- 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
- box :: LispVal -> IOThrowsError [LispVal]
- makeFunc :: Monad m => Maybe String -> Env -> [LispVal] -> [LispVal] -> m LispVal
- makeNormalFunc :: Monad m => Env -> [LispVal] -> [LispVal] -> m LispVal
- makeVarargs :: Monad m => LispVal -> Env -> [LispVal] -> [LispVal] -> m LispVal
- makeHFunc :: Monad m => Maybe String -> Env -> [String] -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> m LispVal
- makeNormalHFunc :: Monad m => Env -> [String] -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> m LispVal
- makeHVarargs :: Monad m => LispVal -> Env -> [String] -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> m LispVal
- validateFuncParams :: [LispVal] -> Maybe Integer -> IOThrowsError Bool
Environments
A Scheme environment containing variable bindings of form (namespaceName, variableName), variableValue
Error Handling
Types of errors that may occur when evaluating Scheme code
NumArgs (Maybe Integer) [LispVal] | Invalid number of function arguments |
TypeMismatch String LispVal | Type error |
Parser ParseError | Parsing error |
BadSpecialForm String LispVal | Invalid special (built-in) form |
UnboundVar String String | A referenced variable has not been declared |
DivideByZero | Divide by Zero error |
NotImplemented String | Feature is not implemented |
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 |
ErrorWithCallHist LispError [LispVal] | Wraps an error to also include the current call history |
type ThrowsError = Either LispError Source #
Container used by operations that could throw an error
type IOThrowsError = ExceptT LispError IO Source #
Container used to provide error handling in the IO monad
liftThrows :: ThrowsError a -> IOThrowsError a Source #
Lift a ThrowsError into the IO monad
Types and related functions
Scheme data types
Atom String | Symbol |
List [LispVal] | List |
DottedList [LispVal] LispVal | Pair |
Vector (Array Int LispVal) | Vector |
ByteVector ByteString | ByteVector from R7RS |
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. |
Number Integer | Integer number |
Float Double | Double-precision floating point number |
Complex (Complex Double) | Complex number |
Rational Rational | Rational number |
String String | String |
Char Char | Character |
Bool Bool | Boolean |
PrimitiveFunc ([LispVal] -> ThrowsError LispVal) | Primitive function |
Func | Function written in Scheme |
HFunc | Function formed from a Haskell function |
IOFunc ([LispVal] -> IOThrowsError LispVal) | Primitive function within the IO monad |
EvalFunc ([LispVal] -> IOThrowsError LispVal) | Function within the IO monad with access to the current environment and continuation. |
CustFunc ([LispVal] -> IOThrowsError LispVal) | A custom function written by code outside of husk. Any code that uses the Haskell API should define custom functions using this data type. |
Pointer | Pointer to an environment variable. |
| |
Opaque Dynamic | Opaque Haskell value. |
Port Handle (Maybe Knob) | I/O port |
Continuation | Continuation |
| |
Syntax | Type to hold a syntax object that is created by a macro definition. Syntax objects are not used like regular types in that they are not passed around within variables. In other words, you cannot use set! to assign a variable to a syntax object. But they are used during function application. In any case, it is convenient to define the type here because syntax objects are stored in the same environments and manipulated by the same functions as regular variables. |
| |
SyntaxExplicitRenaming LispVal | Syntax for an explicit-renaming macro |
LispEnv Env | Wrapper for a scheme environment |
EOF | End of file indicator |
Nil String | Internal use only; do not use this type directly. |
fromOpaque :: forall a. Typeable a => LispVal -> ThrowsError a Source #
Convert an opaque Lisp value back into a Haskell value of the appropriate type, or produce a TypeMismatch error.
data DeferredCode Source #
Container to hold code that is passed to a continuation for deferred execution
SchemeBody [LispVal] | A block of Scheme code |
HaskellBody | A Haskell function |
|
data DynamicWinders Source #
Container to store information from a dynamic-wind
Instances
Show DynamicWinders Source # | |
Defined in Language.Scheme.Types showsPrec :: Int -> DynamicWinders -> ShowS # show :: DynamicWinders -> String # showList :: [DynamicWinders] -> ShowS # |
makeNullContinuation :: Env -> LispVal Source #
Make an empty continuation that does not contain any code
:: Env | Environment |
-> LispVal | Current continuation |
-> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) | Haskell function |
-> LispVal | The Haskell function packaged as a LispVal |
Make a continuation that takes a higher-order function (written in Haskell)
:: Env | Environment |
-> LispVal | Current continuation |
-> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) | Haskell function |
-> [LispVal] | Arguments to the function |
-> LispVal | The Haskell function packaged as a LispVal |
Make a continuation that stores a higher-order function and arguments to that function
:: [LispVal] | A list containing two values to compare |
-> ThrowsError LispVal | Result wrapped as a Bool |
Compare two LispVal
instances
eqvList :: ([LispVal] -> ThrowsError LispVal) -> [LispVal] -> ThrowsError LispVal Source #
Compare two lists of haskell values, using the given comparison function
box :: LispVal -> IOThrowsError [LispVal] Source #
A helper function to make pointer deref code more concise
makeFunc :: Monad m => Maybe String -> Env -> [LispVal] -> [LispVal] -> m LispVal Source #
Create a scheme function
makeNormalFunc :: Monad m => Env -> [LispVal] -> [LispVal] -> m LispVal Source #
Create a normal scheme function
makeVarargs :: Monad m => LispVal -> Env -> [LispVal] -> [LispVal] -> m LispVal Source #
Create a scheme function that can receive any number of arguments
makeHFunc :: Monad m => Maybe String -> Env -> [String] -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> m LispVal Source #
Create a haskell function
makeNormalHFunc :: Monad m => Env -> [String] -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> m LispVal Source #
Create a normal haskell function
makeHVarargs :: Monad m => LispVal -> Env -> [String] -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> m LispVal Source #
Create a haskell function that can receive any number of arguments
validateFuncParams :: [LispVal] -> Maybe Integer -> IOThrowsError Bool Source #
Validate formal function parameters.