husk-scheme-3.5.6: R5RS Scheme interpreter, compiler, and library.

Portabilityportable
Stabilityexperimental
Maintainergithub.com/justinethier
Safe HaskellSafe-Infered

Language.Scheme.Types

Description

This module contains top-level data type definitions, environments, error types, and associated functions.

Synopsis

Documentation

data Env Source

A Scheme environment containing variable bindings of form (namespaceName, variableName), variableValue

nullEnv :: IO EnvSource

An empty environment

data LispError 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

showError :: LispError -> StringSource

Create a textual description for a LispError

runIOThrowsREPL :: IOThrowsError String -> IO StringSource

Execute an IO action and return result or an error message. This is intended for use by a REPL, where a result is always needed regardless of type.

runIOThrows :: IOThrowsError String -> IO (Maybe String)Source

Execute an IO action and return error or Nothing if no error was thrown.

data LispVal Source

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.

Number Integer 
Float Double 
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

Fields

params :: [String]
 
vararg :: Maybe String
 
body :: [LispVal]
 
closure :: Env
 
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.

Opaque Dynamic

Opaque Haskell value.

Port Handle

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.

Fields

synClosure :: Maybe Env

Code env in effect at definition time, if applicable

synRenameClosure :: Maybe Env

Renames (from macro hygiene) in effect at def time; only applicable if this macro defined inside another macro.

synDefinedInMacro :: Bool
 
synIdentifiers :: [LispVal]

Literal identifiers from syntax-rules

synRules :: [LispVal]

Rules from syntax-rules

EOF 
Nil String

Internal use only; do not use this type directly.

Instances

Eq LispVal 
Ord LispVal 
Show LispVal

Allow conversion of lispval instances to strings

toOpaque :: Typeable a => a -> LispValSource

Convert a Haskell value to an opaque Lisp value.

fromOpaque :: forall a. Typeable a => LispVal -> ThrowsError aSource

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

Constructors

SchemeBody [LispVal]

A block of Scheme code

HaskellBody

A Haskell function

data DynamicWinders Source

Container to store information from a dynamic-wind

Constructors

DynamicWinders 

Fields

before :: LispVal

Function to execute when resuming continuation within extent of dynamic-wind

after :: LispVal

Function to execute when leaving extent of dynamic-wind

Instances

eqv :: [LispVal] -> ThrowsError LispValSource

Compare two LispVal instances

eqvList :: ([LispVal] -> ThrowsError LispVal) -> [LispVal] -> ThrowsError LispValSource

Compare two lists of haskell values, using the given comparison function

showVal :: LispVal -> StringSource

Create a textual description of a LispVal

unwordsList :: [LispVal] -> StringSource

Convert a list of Lisp objects into a space-separated string

makeFunc :: Monad m => Maybe String -> Env -> [LispVal] -> [LispVal] -> m LispValSource

Create a scheme function

makeNormalFunc :: Monad m => Env -> [LispVal] -> [LispVal] -> m LispValSource

Create a normal scheme function

makeVarargs :: Monad m => LispVal -> Env -> [LispVal] -> [LispVal] -> m LispValSource

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 LispValSource

Create a haskell function

makeNormalHFunc :: Monad m => Env -> [String] -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> m LispValSource

Create a normal haskell function

makeHVarargs :: Monad m => LispVal -> Env -> [String] -> (Env -> LispVal -> LispVal -> Maybe [LispVal] -> IOThrowsError LispVal) -> m LispValSource

Create a haskell function that can receive any number of arguments