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

CopyrightJustin Ethier
LicenseMIT (see LICENSE in the distribution)
Maintainergithub.com/justinethier
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Language.Scheme.Types

Contents

Description

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

Synopsis

Environments

data Env Source #

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

Instances

Eq Env Source # 

Methods

(==) :: Env -> Env -> Bool #

(/=) :: Env -> Env -> Bool #

nullEnv :: IO Env Source #

An empty environment

Error Handling

data LispError Source #

Types of errors that may occur when evaluating Scheme code

Constructors

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 = ErrorT 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

showCallHistory :: String -> [LispVal] -> String Source #

Display call history for an error

Types and related functions

data LispVal Source #

Scheme data types

Constructors

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

Fields

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.

Fields

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.

Instances

Eq LispVal Source # 

Methods

(==) :: LispVal -> LispVal -> Bool #

(/=) :: LispVal -> LispVal -> Bool #

Ord LispVal Source # 
Show LispVal Source #

Allow conversion of lispval instances to strings

nullLisp :: LispVal Source #

Scheme null value

toOpaque :: Typeable a => a -> LispVal Source #

Convert a Haskell value to an opaque Lisp value.

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

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

makeNullContinuation :: Env -> LispVal Source #

Make an empty continuation that does not contain any code

makeCPS Source #

Arguments

:: 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)

makeCPSWArgs Source #

Arguments

:: 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

eqv Source #

Arguments

:: [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

eqVal :: LispVal -> LispVal -> Bool Source #

A more convenient way to call eqv

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.