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

Portabilityportable
Stabilityexperimental
Maintainergithub.com/justinethier
Safe HaskellNone

Language.Scheme.Primitives

Contents

Description

This module contains primitive functions written in Haskell. Most of these map directly to an equivalent Scheme function.

Synopsis

Pure functions

List

car :: [LispVal] -> IOThrowsError LispValSource

Retrieve the first item from a list

Arguments:

  • List (or DottedList)

Returns: LispVal - First item in the list

cdr :: [LispVal] -> IOThrowsError LispValSource

Return the tail of a list, with the first element removed

Arguments:

  • List (or DottedList)

Returns: List (or DottedList)

cons :: [LispVal] -> IOThrowsError LispValSource

The LISP cons operation - create a list from two values

Arguments:

  • LispVal
  • LispVal

Returns: List (or DottedList) containing new value(s)

eq :: [LispVal] -> IOThrowsError LispValSource

Use pointer equality to compare two objects if possible, otherwise fall back to the normal equality comparison

equal :: [LispVal] -> ThrowsError LispValSource

Recursively compare two LispVals for equality

Arguments:

  • LispVal
  • LispVal

Returns: Bool - True if equal, false otherwise

Vector

buildVector :: [LispVal] -> ThrowsError LispValSource

Create a vector from the given lisp values

Arguments:

  • LispVal (s)

Returns: Vector

vectorLength :: [LispVal] -> ThrowsError LispValSource

Determine the length of the given vector

Arguments:

  • Vector

Returns: Number

vectorRef :: [LispVal] -> ThrowsError LispValSource

Retrieve the object at the given position of a vector

Arguments:

  • Vector
  • Number - Index of the vector to retrieve

Returns: Object at the given index

vectorToList :: [LispVal] -> ThrowsError LispValSource

Convert the given vector to a list

Arguments:

  • Vector

Returns: List

listToVector :: [LispVal] -> ThrowsError LispValSource

Convert the given list to a vector

Arguments:

  • List to convert

Returns: Vector

makeVector :: [LispVal] -> ThrowsError LispValSource

Create a new vector

Arguments:

  • Number - Length of the vector
  • LispVal - Value to fill the vector with

Returns: Vector

Bytevectors

makeByteVector :: [LispVal] -> ThrowsError LispValSource

Create a new bytevector

Arguments:

  • Number - Length of the new bytevector
  • Number (optional) - Byte value to fill the bytevector with

Returns: ByteVector - A new bytevector

byteVector :: [LispVal] -> ThrowsError LispValSource

Create new bytevector containing the given data

Arguments:

  • Objects - Objects to convert to bytes for the bytevector

Returns: ByteVector - A new bytevector

byteVectorLength :: [LispVal] -> IOThrowsError LispValSource

Find the length of a bytevector

Arguments:

  • ByteVector

Returns: Number - Length of the given bytevector

byteVectorRef :: [LispVal] -> IOThrowsError LispValSource

Return object at the given index of a bytevector

Arguments:

  • ByteVector
  • Number - Index of the bytevector to query

Returns: Object at the index

byteVectorCopy :: [LispVal] -> IOThrowsError LispValSource

Create a copy of the given bytevector

Arguments:

  • ByteVector - Bytevector to copy
  • Number (optional) - Start of the region to copy
  • Number (optional) - End of the region to copy

Returns: ByteVector - A new bytevector containing the copied region

byteVectorAppend :: [LispVal] -> IOThrowsError LispValSource

Append many bytevectors into a new bytevector

Arguments:

  • ByteVector (one or more) - Bytevectors to concatenate

Returns: ByteVector - A new bytevector containing the values

byteVectorUtf2Str :: [LispVal] -> IOThrowsError LispValSource

Convert a bytevector to a string

Arguments:

  • ByteVector

Returns: String

byteVectorStr2Utf :: [LispVal] -> IOThrowsError LispValSource

Convert a string to a bytevector

Arguments:

  • String

Returns: ByteVector

Hash Table

hashTblExists :: [LispVal] -> ThrowsError LispValSource

Determine if the given key is found in the hashtable

Arguments:

  • HashTable to search
  • Key to search for

Returns: Bool - True if found, False otherwise

hashTblRef :: [LispVal] -> ThrowsError LispValSource

Retrieve the value from the hashtable for the given key. An error is thrown if the key is not found.

Arguments:

  • HashTable to copy
  • Object that is the key to query the table for

Returns: Object containing the key's value

hashTblSize :: [LispVal] -> ThrowsError LispValSource

Return the number of key/value associations in the hashtable

Arguments:

  • HashTable

Returns: Number - number of associations

hashTbl2List :: [LispVal] -> ThrowsError LispValSource

Create a list containing all key/value pairs in the hashtable

Arguments:

  • HashTable

Returns: List of (key, value) pairs

hashTblKeys :: [LispVal] -> ThrowsError LispValSource

Create a list containing all keys in the hashtable

Arguments:

  • HashTable

Returns: List containing the keys

hashTblValues :: [LispVal] -> ThrowsError LispValSource

Create a list containing all values in the hashtable

Arguments:

  • HashTable

Returns: List containing the values

hashTblCopy :: [LispVal] -> ThrowsError LispValSource

Create a new copy of a hashtable

Arguments:

  • HashTable to copy

Returns: HashTable

hashTblMake :: [LispVal] -> ThrowsError LispValSource

Create a new hashtable

Arguments: (None)

Returns: HashTable

wrapHashTbl :: ([LispVal] -> ThrowsError LispVal) -> [LispVal] -> IOThrowsError LispValSource

A helper function to allow a pure function to work with pointers, by dereferencing the leading object in the argument list if it is a pointer. This is a special hash-table specific function that will also dereference a hash table key if it is included.

wrapLeadObj :: ([LispVal] -> ThrowsError LispVal) -> [LispVal] -> IOThrowsError LispValSource

A helper function to allow a pure function to work with pointers, by dereferencing the leading object in the argument list if it is a pointer.

String

buildString :: [LispVal] -> ThrowsError LispValSource

Convert a list of characters to a string

Arguments:

  • Character (one or more) - Character(s) to add to the string

Returns: String - new string built from given chars

makeString :: [LispVal] -> ThrowsError LispValSource

Make a new string

Arguments:

  • Number - number of characters in the string
  • Char (optional) - Character to fill in each position of string. Defaults to space

Returns: String - new string

doMakeString :: forall a. (Num a, Eq a) => a -> Char -> String -> LispValSource

Helper function

stringLength :: [LispVal] -> IOThrowsError LispValSource

Determine the length of the given string

Arguments:

  • String - String to examine

Returns: Number - Length of the given string

stringRef :: [LispVal] -> IOThrowsError LispValSource

Get character at the given position of a string

Arguments:

  • String - String to examine
  • Number - Get the character at this position

Returns: Char

substring :: [LispVal] -> IOThrowsError LispValSource

Get a part of the given string

Arguments:

  • String - Original string
  • Number - Starting position of the substring
  • Number - Ending position of the substring

Returns: String - substring of the original string

stringCIEquals :: [LispVal] -> IOThrowsError LispValSource

Perform a case insensitive comparison of the given strings

Arguments:

  • String - String to compare
  • String - String to compare

Returns: Bool - True if strings are equal, false otherwise

stringCIBoolBinop :: ([Char] -> [Char] -> Bool) -> [LispVal] -> IOThrowsError LispValSource

Helper function

stringAppend :: [LispVal] -> IOThrowsError LispValSource

Append all given strings together into a single string

Arguments:

  • String (one or more) - String(s) to concatenate

Returns: String - all given strings appended together as a single string

stringToNumber :: [LispVal] -> IOThrowsError LispValSource

Convert given string to a number

Arguments:

  • String - String to convert
  • Number (optional) - Number base to convert from, defaults to base 10 (decimal)

Returns: Numeric type, actual type will depend upon given string

stringToList :: [LispVal] -> IOThrowsError LispValSource

Convert the given string to a list of chars

Arguments:

  • String - string to deconstruct

Returns: List - list of characters

listToString :: [LispVal] -> IOThrowsError LispValSource

Convert the given list of characters to a string

Arguments:

  • List - list of chars to convert

Returns: String - Resulting string

stringCopy :: [LispVal] -> IOThrowsError LispValSource

Create a copy of the given string

Arguments:

  • String - String to copy

Returns: String - New copy of the given string

symbol2String :: [LispVal] -> ThrowsError LispValSource

Convert the given symbol to a string

Arguments:

  • Atom - Symbol to convert

Returns: String

string2Symbol :: [LispVal] -> IOThrowsError LispValSource

Convert a string to a symbol

Arguments:

  • String (or pointer) - String to convert

Returns: Atom

Character

charCIBoolBinop :: (Char -> Char -> Bool) -> [LispVal] -> ThrowsError LispValSource

Helper function

charPredicate :: (Char -> Bool) -> [LispVal] -> ThrowsError LispValSource

Determine if given character satisfies the given predicate

charUpper :: [LispVal] -> ThrowsError LispValSource

Convert a character to uppercase

Arguments:

  • Char

Returns: Char - Character in uppercase

charLower :: [LispVal] -> ThrowsError LispValSource

Convert a character to lowercase

Arguments:

  • Char

Returns: Char - Character in lowercase

char2Int :: [LispVal] -> ThrowsError LispValSource

Convert from a charater to an integer

Arguments:

  • Char

Returns: Number

int2Char :: [LispVal] -> ThrowsError LispValSource

Convert from an integer to a character

Arguments:

  • Number

Returns: Char

Predicate

isHashTbl :: [LispVal] -> ThrowsError LispValSource

Determine if a given object is a hashtable

Arguments:

  • Object to inspect

Returns: Bool - True if arg was a hashtable, false otherwise

isChar :: [LispVal] -> ThrowsError LispValSource

Determine if the given value is a character

Arguments:

  • LispVal to check

Returns: Bool - True if the argument is a character, False otherwise

isString :: [LispVal] -> IOThrowsError LispValSource

Determine if the given value is a string

Arguments:

  • LispVal to check

Returns: Bool - True if the argument is a string, False otherwise

isBoolean :: [LispVal] -> ThrowsError LispValSource

Determine if the given value is a boolean

Arguments:

  • LispVal to check

Returns: Bool - True if the argument is a boolean, False otherwise

isDottedList :: [LispVal] -> IOThrowsError LispValSource

Determine if given object is an improper list

Arguments:

  • Value to check

Returns: Bool - True if improper list, False otherwise

isProcedure :: [LispVal] -> ThrowsError LispValSource

Determine if given object is a procedure

Arguments:

  • Value to check

Returns: Bool - True if procedure, False otherwise

isList :: LispVal -> IOThrowsError LispValSource

Determine if given object is a list

Arguments:

  • Value to check

Returns: Bool - True if list, False otherwise

isVector :: LispVal -> IOThrowsError LispValSource

Determine if given object is a bytevector

Arguments:

  • Value to check

Returns: Bool - True if bytevector, False otherwise

isByteVector :: LispVal -> IOThrowsError LispValSource

Determine if given object is a bytevector

Arguments:

  • Value to check

Returns: Bool - True if bytevector, False otherwise

isNull :: [LispVal] -> IOThrowsError LispValSource

Determine if given object is the null list

Arguments:

  • Value to check

Returns: Bool - True if null list, False otherwise

isEOFObject :: [LispVal] -> ThrowsError LispValSource

Determine if given object is the EOF marker

Arguments:

  • Value to check

Returns: Bool - True if EOF, False otherwise

isSymbol :: [LispVal] -> ThrowsError LispValSource

Determine if given object is a symbol

Arguments:

  • Value to check

Returns: Bool - True if a symbol, False otherwise

Utility functions

unpackEquals :: LispVal -> LispVal -> Unpacker -> ThrowsError BoolSource

Determine if two lispval's are equal

boolBinop :: (LispVal -> ThrowsError a) -> (a -> a -> Bool) -> [LispVal] -> ThrowsError LispValSource

Helper function to perform a binary logic operation on two LispVal arguments.

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

Perform the given function against a single LispVal argument

unaryOp' :: (LispVal -> IOThrowsError LispVal) -> [LispVal] -> IOThrowsError LispValSource

Same as unaryOp but in the IO monad

strBoolBinop :: (String -> String -> Bool) -> [LispVal] -> IOThrowsError LispValSource

Perform boolBinop against two string arguments

charBoolBinop :: (Char -> Char -> Bool) -> [LispVal] -> ThrowsError LispValSource

Perform boolBinop against two char arguments

boolBoolBinop :: (Bool -> Bool -> Bool) -> [LispVal] -> ThrowsError LispValSource

Perform boolBinop against two boolean arguments

unpackStr :: LispVal -> ThrowsError StringSource

Unpack a LispVal String

Arguments:

  • String - String to unpack

unpackBool :: LispVal -> ThrowsError BoolSource

Unpack a LispVal boolean

Arguments:

  • Bool - Boolean to unpack

Impure functions

All of these functions must be executed within the IO monad.

Input / Output

makePort :: IOMode -> [LispVal] -> IOThrowsError LispValSource

Open the given file

LispVal Arguments:

  • String - filename

Returns: Port

closePort :: [LispVal] -> IOThrowsError LispValSource

Close the given port

Arguments:

  • Port

Returns: Bool - True if the port was closed, false otherwise

currentOutputPort :: [LispVal] -> IOThrowsError LispValSource

Return the current input port

LispVal Arguments: (None)

Returns: Port

currentInputPort :: [LispVal] -> IOThrowsError LispValSource

Return the current input port

LispVal Arguments: (None)

Returns: Port

isOutputPort :: [LispVal] -> IOThrowsError LispValSource

Determine if the given objects is an output port

LispVal Arguments:

  • Port

Returns: Bool - True if an output port, false otherwise

isInputPort :: [LispVal] -> IOThrowsError LispValSource

Determine if the given objects is an input port

LispVal Arguments:

  • Port

Returns: Bool - True if an input port, false otherwise

isCharReady :: [LispVal] -> IOThrowsError LispValSource

Determine if a character is ready on the port

LispVal Arguments:

  • Port

Returns: Bool

readProc :: [LispVal] -> IOThrowsError LispValSource

Read from the given port

LispVal Arguments:

  • Port

Returns: LispVal

readCharProc :: (Handle -> IO Char) -> [LispVal] -> IOThrowsError LispValSource

Read character from port

LispVal Arguments:

  • Port

Returns: Char

writeProc :: (Handle -> LispVal -> IO a) -> [LispVal] -> ErrorT LispError IO LispValSource

Write to the given port

LispVal Arguments:

  • LispVal
  • Port (optional)

Returns: (None)

writeCharProc :: [LispVal] -> IOThrowsError LispValSource

Write character to the given port

Arguments:

  • Char - Value to write
  • Port (optional) - Port to write to, defaults to standard output

Returns: (None)

readContents :: [LispVal] -> IOThrowsError LispValSource

Read the given file and return the raw string content

Arguments:

  • String - Filename to read

Returns: String - Actual text read from the file

load :: String -> IOThrowsError [LispVal]Source

Parse the given file and return a list of scheme expressions

Arguments:

  • String - Filename to read

Returns: [LispVal] - Raw contents of the file parsed as scheme code

readAll :: [LispVal] -> IOThrowsError LispValSource

Read the contents of the given scheme source file into a list

Arguments:

  • String - Filename to read

Returns: List - Raw contents of the file parsed as scheme code

fileExists :: [LispVal] -> IOThrowsError LispValSource

Determine if the given file exists

Arguments:

  • String - Filename to check

Returns: Bool - True if file exists, false otherwise

deleteFile :: [LispVal] -> IOThrowsError LispValSource

Delete the given file

Arguments:

  • String - Filename to delete

Returns: Bool - True if file was deleted, false if an error occurred

Symbol generation

gensym :: [LispVal] -> IOThrowsError LispValSource

Generate a (reasonably) unique symbol, given an optional prefix. This function is provided even though it is not part of R5RS.

Arguments:

  • String - Prefix of the unique symbol

Returns: Atom

_gensym :: String -> IOThrowsError LispValSource

Version of gensym that can be conveniently called from Haskell.

Time

currentTimestamp :: [LispVal] -> IOThrowsError LispValSource

Return the current time, in seconds

Arguments: (None)

Returns: Current UNIX timestamp in seconds

System

system :: [LispVal] -> IOThrowsError LispValSource

Execute a system command on the underlying OS.

Arguments:

  • String - Command to execute

Returns: Integer - program return status