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 primitive functions written in Haskell. Most of these map directly to an equivalent Scheme function.
Synopsis
- car :: [LispVal] -> IOThrowsError LispVal
- cdr :: [LispVal] -> IOThrowsError LispVal
- cons :: [LispVal] -> IOThrowsError LispVal
- eq :: [LispVal] -> IOThrowsError LispVal
- equal :: [LispVal] -> ThrowsError LispVal
- makeList :: [LispVal] -> ThrowsError LispVal
- listCopy :: [LispVal] -> IOThrowsError LispVal
- buildVector :: [LispVal] -> ThrowsError LispVal
- vectorLength :: [LispVal] -> ThrowsError LispVal
- vectorRef :: [LispVal] -> ThrowsError LispVal
- vectorCopy :: [LispVal] -> IOThrowsError LispVal
- vectorToList :: [LispVal] -> ThrowsError LispVal
- listToVector :: [LispVal] -> ThrowsError LispVal
- makeVector :: [LispVal] -> ThrowsError LispVal
- makeByteVector :: [LispVal] -> ThrowsError LispVal
- byteVector :: [LispVal] -> ThrowsError LispVal
- byteVectorLength :: [LispVal] -> IOThrowsError LispVal
- byteVectorRef :: [LispVal] -> IOThrowsError LispVal
- byteVectorCopy :: [LispVal] -> IOThrowsError LispVal
- byteVectorAppend :: [LispVal] -> IOThrowsError LispVal
- byteVectorUtf2Str :: [LispVal] -> IOThrowsError LispVal
- byteVectorStr2Utf :: [LispVal] -> IOThrowsError LispVal
- hashTblExists :: [LispVal] -> ThrowsError LispVal
- hashTblSize :: [LispVal] -> ThrowsError LispVal
- hashTbl2List :: [LispVal] -> ThrowsError LispVal
- hashTblKeys :: [LispVal] -> ThrowsError LispVal
- hashTblValues :: [LispVal] -> ThrowsError LispVal
- hashTblCopy :: [LispVal] -> ThrowsError LispVal
- hashTblMake :: [LispVal] -> ThrowsError LispVal
- wrapHashTbl :: ([LispVal] -> ThrowsError LispVal) -> [LispVal] -> IOThrowsError LispVal
- wrapLeadObj :: ([LispVal] -> ThrowsError LispVal) -> [LispVal] -> IOThrowsError LispVal
- buildString :: [LispVal] -> ThrowsError LispVal
- makeString :: [LispVal] -> ThrowsError LispVal
- doMakeString :: forall a. (Num a, Eq a) => a -> Char -> String -> LispVal
- stringLength :: [LispVal] -> IOThrowsError LispVal
- stringRef :: [LispVal] -> IOThrowsError LispVal
- substring :: [LispVal] -> IOThrowsError LispVal
- stringCIEquals :: [LispVal] -> IOThrowsError LispVal
- stringCIBoolBinop :: (String -> String -> Bool) -> [LispVal] -> IOThrowsError LispVal
- stringAppend :: [LispVal] -> IOThrowsError LispVal
- stringToNumber :: [LispVal] -> IOThrowsError LispVal
- stringToList :: [LispVal] -> IOThrowsError LispVal
- listToString :: [LispVal] -> IOThrowsError LispVal
- stringToVector :: [LispVal] -> IOThrowsError LispVal
- vectorToString :: [LispVal] -> IOThrowsError LispVal
- stringCopy :: [LispVal] -> IOThrowsError LispVal
- symbol2String :: [LispVal] -> ThrowsError LispVal
- string2Symbol :: [LispVal] -> IOThrowsError LispVal
- charCIBoolBinop :: (Char -> Char -> Bool) -> [LispVal] -> ThrowsError LispVal
- charPredicate :: (Char -> Bool) -> [LispVal] -> ThrowsError LispVal
- charUpper :: [LispVal] -> ThrowsError LispVal
- charLower :: [LispVal] -> ThrowsError LispVal
- charDigitValue :: [LispVal] -> ThrowsError LispVal
- char2Int :: [LispVal] -> ThrowsError LispVal
- int2Char :: [LispVal] -> ThrowsError LispVal
- isHashTbl :: [LispVal] -> ThrowsError LispVal
- isChar :: [LispVal] -> ThrowsError LispVal
- isString :: [LispVal] -> IOThrowsError LispVal
- isBoolean :: [LispVal] -> ThrowsError LispVal
- isBooleanEq :: Monad m => [LispVal] -> m LispVal
- isSymbolEq :: Monad m => [LispVal] -> m LispVal
- isDottedList :: [LispVal] -> IOThrowsError LispVal
- isProcedure :: [LispVal] -> ThrowsError LispVal
- isList :: LispVal -> IOThrowsError LispVal
- isVector :: LispVal -> IOThrowsError LispVal
- isRecord :: LispVal -> IOThrowsError LispVal
- isByteVector :: LispVal -> IOThrowsError LispVal
- isNull :: [LispVal] -> IOThrowsError LispVal
- isEOFObject :: [LispVal] -> ThrowsError LispVal
- isSymbol :: [LispVal] -> ThrowsError LispVal
- data Unpacker
- unpackEquals :: LispVal -> LispVal -> Unpacker -> ThrowsError Bool
- boolBinop :: (LispVal -> ThrowsError a) -> (a -> a -> Bool) -> [LispVal] -> ThrowsError LispVal
- unaryOp :: (LispVal -> ThrowsError LispVal) -> [LispVal] -> ThrowsError LispVal
- unaryOp' :: (LispVal -> IOThrowsError LispVal) -> [LispVal] -> IOThrowsError LispVal
- strBoolBinop :: (String -> String -> Bool) -> [LispVal] -> IOThrowsError LispVal
- charBoolBinop :: (Char -> Char -> Bool) -> [LispVal] -> ThrowsError LispVal
- boolBoolBinop :: (Bool -> Bool -> Bool) -> [LispVal] -> ThrowsError LispVal
- unpackStr :: LispVal -> ThrowsError String
- unpackBool :: LispVal -> ThrowsError Bool
- makePort :: (FilePath -> IOMode -> IO Handle) -> IOMode -> [LispVal] -> IOThrowsError LispVal
- makeBufferPort :: Maybe LispVal -> IOThrowsError LispVal
- openInputString :: [LispVal] -> IOThrowsError LispVal
- openOutputString :: [LispVal] -> IOThrowsError LispVal
- getOutputString :: [LispVal] -> IOThrowsError LispVal
- openInputByteVector :: [LispVal] -> IOThrowsError LispVal
- openOutputByteVector :: [LispVal] -> IOThrowsError LispVal
- getOutputByteVector :: [LispVal] -> IOThrowsError LispVal
- closePort :: [LispVal] -> IOThrowsError LispVal
- flushOutputPort :: [LispVal] -> IOThrowsError LispVal
- currentOutputPort :: [LispVal] -> IOThrowsError LispVal
- currentInputPort :: [LispVal] -> IOThrowsError LispVal
- isTextPort :: [LispVal] -> IOThrowsError LispVal
- isBinaryPort :: [LispVal] -> IOThrowsError LispVal
- isOutputPort :: [LispVal] -> IOThrowsError LispVal
- isInputPort :: [LispVal] -> IOThrowsError LispVal
- isInputPortOpen :: [LispVal] -> IOThrowsError LispVal
- isOutputPortOpen :: [LispVal] -> IOThrowsError LispVal
- isCharReady :: [LispVal] -> IOThrowsError LispVal
- readProc :: Bool -> [LispVal] -> IOThrowsError LispVal
- readCharProc :: (Handle -> IO Char) -> [LispVal] -> IOThrowsError LispVal
- readByteVector :: [LispVal] -> IOThrowsError LispVal
- readString :: [LispVal] -> IOThrowsError LispVal
- writeProc :: (Handle -> LispVal -> IO a) -> [LispVal] -> ExceptT LispError IO LispVal
- writeCharProc :: [LispVal] -> IOThrowsError LispVal
- writeByteVector :: [LispVal] -> IOThrowsError LispVal
- writeString :: [LispVal] -> IOThrowsError LispVal
- readContents :: [LispVal] -> IOThrowsError LispVal
- load :: String -> IOThrowsError [LispVal]
- readAll :: [LispVal] -> IOThrowsError LispVal
- fileExists :: [LispVal] -> IOThrowsError LispVal
- deleteFile :: [LispVal] -> IOThrowsError LispVal
- eofObject :: [LispVal] -> ThrowsError LispVal
- gensym :: [LispVal] -> IOThrowsError LispVal
- _gensym :: String -> IOThrowsError LispVal
- currentTimestamp :: [LispVal] -> IOThrowsError LispVal
- system :: [LispVal] -> IOThrowsError LispVal
- getEnvVars :: [LispVal] -> IOThrowsError LispVal
Pure functions
List
car :: [LispVal] -> IOThrowsError LispVal Source #
Retrieve the first item from a list
Arguments:
- List (or DottedList)
Returns: LispVal - First item in the list
cdr :: [LispVal] -> IOThrowsError LispVal Source #
Return the tail of a list, with the first element removed
Arguments:
- List (or DottedList)
Returns: List (or DottedList)
cons :: [LispVal] -> IOThrowsError LispVal Source #
The LISP cons
operation - create a list from two values
Arguments:
- LispVal
- LispVal
Returns: List (or DottedList) containing new value(s)
eq :: [LispVal] -> IOThrowsError LispVal Source #
Use pointer equality to compare two objects if possible, otherwise fall back to the normal equality comparison
equal :: [LispVal] -> ThrowsError LispVal Source #
Recursively compare two LispVals for equality
Arguments:
- LispVal
- LispVal
Returns: Bool - True if equal, false otherwise
makeList :: [LispVal] -> ThrowsError LispVal Source #
Create a new list
Arguments
- Number - Length of the list
- LispVal - Object to fill the list with (optional)
Returns: List
listCopy :: [LispVal] -> IOThrowsError LispVal Source #
Create a copy of a list
Arguments
- List
Returns: List
Vector
buildVector :: [LispVal] -> ThrowsError LispVal Source #
Create a vector from the given lisp values
Arguments:
- LispVal (s)
Returns: Vector
vectorLength :: [LispVal] -> ThrowsError LispVal Source #
Determine the length of the given vector
Arguments:
- Vector
Returns: Number
vectorRef :: [LispVal] -> ThrowsError LispVal Source #
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
vectorCopy :: [LispVal] -> IOThrowsError LispVal Source #
Create a copy of a vector
Arguments
- Vector
- Number - Start copying the vector from this element (optional)
- Number - Stop copying the vector at this element (optional)
Returns: Vector
vectorToList :: [LispVal] -> ThrowsError LispVal Source #
Convert the given vector to a list
Arguments:
- Vector
Returns: List
listToVector :: [LispVal] -> ThrowsError LispVal Source #
Convert the given list to a vector
Arguments:
- List to convert
Returns: Vector
makeVector :: [LispVal] -> ThrowsError LispVal Source #
Create a new vector
Arguments:
- Number - Length of the vector
- LispVal - Value to fill the vector with
Returns: Vector
Bytevectors
makeByteVector :: [LispVal] -> ThrowsError LispVal Source #
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 LispVal Source #
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 LispVal Source #
Find the length of a bytevector
Arguments:
- ByteVector
Returns: Number - Length of the given bytevector
byteVectorRef :: [LispVal] -> IOThrowsError LispVal Source #
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 LispVal Source #
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 LispVal Source #
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 LispVal Source #
Convert a bytevector to a string
Arguments:
- ByteVector
Returns: String
byteVectorStr2Utf :: [LispVal] -> IOThrowsError LispVal Source #
Convert a string to a bytevector
Arguments:
- String
Returns: ByteVector
Hash Table
hashTblExists :: [LispVal] -> ThrowsError LispVal Source #
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
hashTblSize :: [LispVal] -> ThrowsError LispVal Source #
Return the number of key/value associations in the hashtable
Arguments:
- HashTable
Returns: Number - number of associations
hashTbl2List :: [LispVal] -> ThrowsError LispVal Source #
Create a list containing all key/value pairs in the hashtable
Arguments:
- HashTable
Returns: List of (key, value) pairs
hashTblKeys :: [LispVal] -> ThrowsError LispVal Source #
Create a list containing all keys in the hashtable
Arguments:
- HashTable
Returns: List containing the keys
hashTblValues :: [LispVal] -> ThrowsError LispVal Source #
Create a list containing all values in the hashtable
Arguments:
- HashTable
Returns: List containing the values
hashTblCopy :: [LispVal] -> ThrowsError LispVal Source #
Create a new copy of a hashtable
Arguments:
- HashTable to copy
Returns: HashTable
hashTblMake :: [LispVal] -> ThrowsError LispVal Source #
Create a new hashtable
Arguments: (None)
Returns: HashTable
wrapHashTbl :: ([LispVal] -> ThrowsError LispVal) -> [LispVal] -> IOThrowsError LispVal Source #
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 LispVal Source #
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 LispVal Source #
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 LispVal Source #
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
stringLength :: [LispVal] -> IOThrowsError LispVal Source #
Determine the length of the given string
Arguments:
- String - String to examine
Returns: Number - Length of the given string
stringRef :: [LispVal] -> IOThrowsError LispVal Source #
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 LispVal Source #
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 LispVal Source #
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 :: (String -> String -> Bool) -> [LispVal] -> IOThrowsError LispVal Source #
Helper function
stringAppend :: [LispVal] -> IOThrowsError LispVal Source #
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 LispVal Source #
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 LispVal Source #
Convert the given string to a list of chars
Arguments:
- String - string to deconstruct
Returns: List - list of characters
listToString :: [LispVal] -> IOThrowsError LispVal Source #
Convert the given list of characters to a string
Arguments:
- List - list of chars to convert
Returns: String - Resulting string
stringToVector :: [LispVal] -> IOThrowsError LispVal Source #
Convert a string to a vector
Arguments
- String
Returns: Vector
vectorToString :: [LispVal] -> IOThrowsError LispVal Source #
Convert a vector to a string
Arguments
- Vector
Returns: String
stringCopy :: [LispVal] -> IOThrowsError LispVal Source #
Create a copy of the given string
Arguments:
- String - String to copy
Returns: String - New copy of the given string
symbol2String :: [LispVal] -> ThrowsError LispVal Source #
Convert the given symbol to a string
Arguments:
- Atom - Symbol to convert
Returns: String
string2Symbol :: [LispVal] -> IOThrowsError LispVal Source #
Convert a string to a symbol
Arguments:
- String (or pointer) - String to convert
Returns: Atom
Character
charCIBoolBinop :: (Char -> Char -> Bool) -> [LispVal] -> ThrowsError LispVal Source #
Helper function
charPredicate :: (Char -> Bool) -> [LispVal] -> ThrowsError LispVal Source #
Determine if given character satisfies the given predicate
charUpper :: [LispVal] -> ThrowsError LispVal Source #
Convert a character to uppercase
Arguments:
- Char
Returns: Char - Character in uppercase
charLower :: [LispVal] -> ThrowsError LispVal Source #
Convert a character to lowercase
Arguments:
- Char
Returns: Char - Character in lowercase
charDigitValue :: [LispVal] -> ThrowsError LispVal Source #
Return integer value of a char digit
Arguments
- Char
Returns: Number, or False
char2Int :: [LispVal] -> ThrowsError LispVal Source #
Convert from a charater to an integer
Arguments:
- Char
Returns: Number
int2Char :: [LispVal] -> ThrowsError LispVal Source #
Convert from an integer to a character
Arguments:
- Number
Returns: Char
Predicate
isHashTbl :: [LispVal] -> ThrowsError LispVal Source #
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 LispVal Source #
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 LispVal Source #
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 LispVal Source #
Determine if the given value is a boolean
Arguments:
- LispVal to check
Returns: Bool - True if the argument is a boolean, False otherwise
isBooleanEq :: Monad m => [LispVal] -> m LispVal Source #
Determine if multiple boolean values are the same
Arguments
- A list of Bool values
Returns: True if the list contains booleans that are the same, False otherwise
isSymbolEq :: Monad m => [LispVal] -> m LispVal Source #
Determine if multiple symbols values are the same
Arguments
- A list of Atom values
Returns: True if all of the symbols are the same, False otherwise
isDottedList :: [LispVal] -> IOThrowsError LispVal Source #
Determine if given object is an improper list
Arguments:
- Value to check
Returns: Bool - True if improper list, False otherwise
isProcedure :: [LispVal] -> ThrowsError LispVal Source #
Determine if given object is a procedure
Arguments:
- Value to check
Returns: Bool - True if procedure, False otherwise
isList :: LispVal -> IOThrowsError LispVal Source #
Determine if given object is a list
Arguments:
- Value to check
Returns: Bool - True if list, False otherwise
isVector :: LispVal -> IOThrowsError LispVal Source #
Determine if given object is a vector
Arguments:
- Value to check
Returns: Bool - True if vector, False otherwise
isRecord :: LispVal -> IOThrowsError LispVal Source #
Determine if given object is a record
Arguments:
- Value to check
Returns: Bool - True if record, False otherwise
isByteVector :: LispVal -> IOThrowsError LispVal Source #
Determine if given object is a bytevector
Arguments:
- Value to check
Returns: Bool - True if bytevector, False otherwise
isNull :: [LispVal] -> IOThrowsError LispVal Source #
Determine if given object is the null list
Arguments:
- Value to check
Returns: Bool - True if null list, False otherwise
isEOFObject :: [LispVal] -> ThrowsError LispVal Source #
Determine if given object is the EOF marker
Arguments:
- Value to check
Returns: Bool - True if EOF, False otherwise
isSymbol :: [LispVal] -> ThrowsError LispVal Source #
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 Bool Source #
Determine if two lispval's are equal
boolBinop :: (LispVal -> ThrowsError a) -> (a -> a -> Bool) -> [LispVal] -> ThrowsError LispVal Source #
Helper function to perform a binary logic operation on two LispVal arguments.
unaryOp :: (LispVal -> ThrowsError LispVal) -> [LispVal] -> ThrowsError LispVal Source #
Perform the given function against a single LispVal argument
unaryOp' :: (LispVal -> IOThrowsError LispVal) -> [LispVal] -> IOThrowsError LispVal Source #
Same as unaryOp but in the IO monad
strBoolBinop :: (String -> String -> Bool) -> [LispVal] -> IOThrowsError LispVal Source #
Perform boolBinop against two string arguments
charBoolBinop :: (Char -> Char -> Bool) -> [LispVal] -> ThrowsError LispVal Source #
Perform boolBinop against two char arguments
boolBoolBinop :: (Bool -> Bool -> Bool) -> [LispVal] -> ThrowsError LispVal Source #
Perform boolBinop against two boolean arguments
unpackStr :: LispVal -> ThrowsError String Source #
Unpack a LispVal String
Arguments:
- String - String to unpack
unpackBool :: LispVal -> ThrowsError Bool Source #
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 :: (FilePath -> IOMode -> IO Handle) -> IOMode -> [LispVal] -> IOThrowsError LispVal Source #
Open the given file
LispVal Arguments:
- String - filename
Returns: Port
makeBufferPort :: Maybe LispVal -> IOThrowsError LispVal Source #
Create an memory-backed port
openInputString :: [LispVal] -> IOThrowsError LispVal Source #
Create a new input string buffer
openOutputString :: [LispVal] -> IOThrowsError LispVal Source #
Create a new output string buffer
getOutputString :: [LispVal] -> IOThrowsError LispVal Source #
Get string written to string-output-port
openInputByteVector :: [LispVal] -> IOThrowsError LispVal Source #
Create a new input bytevector buffer
openOutputByteVector :: [LispVal] -> IOThrowsError LispVal Source #
Create a new output bytevector buffer
getOutputByteVector :: [LispVal] -> IOThrowsError LispVal Source #
Get bytevector written to bytevector-output-port
closePort :: [LispVal] -> IOThrowsError LispVal Source #
Close the given port
Arguments:
- Port
Returns: Bool - True if the port was closed, false otherwise
flushOutputPort :: [LispVal] -> IOThrowsError LispVal Source #
Flush the given output port
currentOutputPort :: [LispVal] -> IOThrowsError LispVal Source #
Return the current input port
LispVal Arguments: (None)
Returns: Port
currentInputPort :: [LispVal] -> IOThrowsError LispVal Source #
Return the current input port
LispVal Arguments: (None)
Returns: Port
isTextPort :: [LispVal] -> IOThrowsError LispVal Source #
Determine if the given port is a text port.
Arguments
- Port
Returns: Bool
isBinaryPort :: [LispVal] -> IOThrowsError LispVal Source #
Determine if the given port is a binary port.
Arguments
- Port
Returns: Bool
isOutputPort :: [LispVal] -> IOThrowsError LispVal Source #
Determine if the given objects is an output port
LispVal Arguments:
- Port
Returns: Bool - True if an output port, false otherwise
isInputPort :: [LispVal] -> IOThrowsError LispVal Source #
Determine if the given objects is an input port
LispVal Arguments:
- Port
Returns: Bool - True if an input port, false otherwise
isInputPortOpen :: [LispVal] -> IOThrowsError LispVal Source #
Determine if the given port is open
Arguments
- Port
Returns: Bool
isOutputPortOpen :: [LispVal] -> IOThrowsError LispVal Source #
Determine if the given port is open
Arguments
- Port
Returns: Bool
isCharReady :: [LispVal] -> IOThrowsError LispVal Source #
Determine if a character is ready on the port
LispVal Arguments:
- Port
Returns: Bool
readProc :: Bool -> [LispVal] -> IOThrowsError LispVal Source #
Read from the given port
LispVal Arguments:
- Port
Returns: LispVal
readCharProc :: (Handle -> IO Char) -> [LispVal] -> IOThrowsError LispVal Source #
Read character from port
LispVal Arguments:
- Port
Returns: Char
readByteVector :: [LispVal] -> IOThrowsError LispVal Source #
Read a byte vector from the given port
Arguments
- Number - Number of bytes to read
- Port - Port to read from
Returns: ByteVector
readString :: [LispVal] -> IOThrowsError LispVal Source #
Read a string from the given port
Arguments
- Number - Number of bytes to read
- Port - Port to read from
Returns: String
writeProc :: (Handle -> LispVal -> IO a) -> [LispVal] -> ExceptT LispError IO LispVal Source #
Write to the given port
LispVal Arguments:
- LispVal
- Port (optional)
Returns: (None)
writeCharProc :: [LispVal] -> IOThrowsError LispVal Source #
Write character to the given port
Arguments:
- Char - Value to write
- Port (optional) - Port to write to, defaults to standard output
Returns: (None)
writeByteVector :: [LispVal] -> IOThrowsError LispVal Source #
Write a byte vector to the given port
Arguments
- ByteVector
- Port
Returns: (unspecified)
writeString :: [LispVal] -> IOThrowsError LispVal Source #
Write a string to the given port
Arguments
- String
- Port
Returns: (unspecified)
readContents :: [LispVal] -> IOThrowsError LispVal Source #
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 LispVal Source #
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 LispVal Source #
Determine if the given file exists
Arguments:
- String - Filename to check
Returns: Bool - True if file exists, false otherwise
deleteFile :: [LispVal] -> IOThrowsError LispVal Source #
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 LispVal Source #
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 LispVal Source #
Version of gensym that can be conveniently called from Haskell.
Time
currentTimestamp :: [LispVal] -> IOThrowsError LispVal Source #
Return the current time, in seconds
Arguments: (None)
Returns: Current UNIX timestamp in seconds
System
system :: [LispVal] -> IOThrowsError LispVal Source #
Execute a system command on the underlying OS.
Arguments:
- String - Command to execute
Returns: Integer - program return status
getEnvVars :: [LispVal] -> IOThrowsError LispVal Source #
Retrieve all environment variables
Arguments: (none)
Returns: List - list of key/value alists