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

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

Language.Scheme.Core

Contents

Description

This module contains Core functionality, primarily Scheme expression evaluation.

Synopsis

Scheme code evaluation

evalLisp :: Env -> LispVal -> IOThrowsError LispVal Source

Evaluate a lisp data structure and return a value for use by husk

evalLisp' :: Env -> LispVal -> IO (ThrowsError LispVal) Source

Evaluate a lisp data structure and return the LispVal or LispError result directly

 result <- evalLisp' env $ List [Atom "/", Number 1, Number 0]
 case result of
   Left err -> putStrLn $ "Error: " ++ (show err)
   Right val -> putStrLn $ show val

evalString :: Env -> String -> IO String Source

Evaluate a string containing Scheme code

env <- primitiveBindings

evalString env "(+ x x x)"
"3"

evalString env "(+ x x x (* 3 9))"
"30"

evalString env "(* 3 9)"
"27"

evalAndPrint :: Env -> String -> IO () Source

Evaluate a string and print results to console

apply Source

Arguments

:: LispVal

Current continuation

-> LispVal

Function or continuation to execute

-> [LispVal]

Arguments

-> IOThrowsError LispVal

Final value of computation

Call into a Scheme function

continueEval Source

Arguments

:: Env

Current environment

-> LispVal

Current continuation

-> LispVal

Value of previous computation

-> Maybe [LispVal]

Extra arguments from previous computation

-> IOThrowsError LispVal

Final value of computation

A support function for eval; eval calls into this function instead of returning values directly. continueEval then uses the continuation argument to manage program control flow.

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

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

runIOThrowsREPL :: IOThrowsError String -> IO String Source

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.

Core data

nullEnvWithImport :: IO Env Source

An empty environment with the %import function. This is presently just intended for internal use by the compiler.

primitiveBindings :: IO Env Source

Environment containing the primitive forms that are built into the Scheme language. This function only includes forms that are implemented in Haskell; derived forms implemented in Scheme (such as let, list, etc) are available in the standard library which must be pulled into the environment using (load)

For the purposes of using husk as an extension language, r5rsEnv will probably be more useful.

r5rsEnv :: IO Env Source

Load the standard r5rs environment, including libraries

r5rsEnv' :: IO Env Source

Load the standard r5rs environment, including libraries, but do not create the (import) binding

r7rsEnv :: IO Env Source

Load the standard r7rs environment, including libraries

Note that the only difference between this and the r5rs equivalent is that slightly less Scheme code is loaded initially.

r7rsEnv' :: IO Env Source

Load the standard r7rs environment

r7rsTimeEnv :: IO Env Source

Load haskell bindings used for the r7rs time library

version :: String Source

Husk version number

Utility functions

findFileOrLib :: String -> ErrorT LispError IO String Source

Attempts to find the file both in the current directory and in the husk libraries. If the file is not found in the current directory but exists as a husk library, return the full path to the file in the library. Otherwise just return the given filename.

getDataFileFullPath :: String -> IO String Source

Get the full path to a data file installed for husk

replaceAtIndex :: forall a. Int -> a -> [a] -> [a] Source

registerExtensions :: Env -> (FilePath -> IO FilePath) -> IO () Source

Register optional SRFI extensions

showBanner :: IO () Source

A utility function to display the husk console banner

showLispError :: LispError -> IO String Source

This is the recommended function to use to display a lisp error, instead of just using show directly.

substr :: (LispVal, LispVal, LispVal) -> IOThrowsError LispVal Source

A helper function for the special form (string-set!)

updateList :: LispVal -> LispVal -> LispVal -> IOThrowsError LispVal Source

A helper function for (list-set!)

updateVector :: LispVal -> LispVal -> LispVal -> IOThrowsError LispVal Source

A helper function for the special form (vector-set!)

updateByteVector :: LispVal -> LispVal -> LispVal -> IOThrowsError LispVal Source

A helper function for the special form (bytevector-u8-set!)

Error handling

addToCallHistory :: LispVal -> [LispVal] -> [LispVal] Source

Add a function to the call history

throwErrorWithCallHistory :: LispVal -> LispError -> IOThrowsError LispVal Source

Rethrow given error with call history, if available

Internal use only

meval :: Env -> LispVal -> LispVal -> IOThrowsError LispVal Source

A wrapper for macroEval and eval