(lispkit core)

Library (lispkit core) provides a foundational API for

Primitives

If expr is an expression, it is evaluated in the specified environment env and its values are returned. If it is a definition, the specified identifiers are defined in the specified environment, provided the environment is not immutable. Should env not be provided, the global interaction environment is used.

The apply procedure calls proc with the elements of the list (append (list arg1 ...) args) as the actual arguments.

The equal? procedure, when applied to pairs, vectors, strings and bytevectors, recursively compares them, returning #t when the unfoldings of its arguments into possibly infinite trees are equal (in the sense of equal?) as ordered trees, and #f otherwise. It returns the same as eqv? when applied to booleans, symbols, numbers, characters, ports, procedures, and the empty list. If two objects are eqv?, they must be equal? as well. In all other cases, equal? may return either #t or #f. Even if its arguments are circular data structures, equal? must always terminate. As a rule of thumb, objects are generally equal? if they print the same.

The eqv? procedure defines a useful equivalence relation on objects. It returns #t if obj1 and obj2 are regarded as the same object.

The eqv? procedure returns #t if:

  • obj1 and obj2 are both #t or both #f

  • obj1 and obj2 are both symbols and are the same symbol according to the symbol=? procedure

  • obj1 and obj2 are both exact numbers and are numerically equal in the sense of =

  • obj1 and obj2 are both inexact numbers such that they are numerically equal in the sense of =, and they yield the same results in the sense of eqv? when passed as arguments to any other procedure that can be defined as a finite composition of Scheme’s standard arithmetic procedures, provided it does not result in a NaN value

  • obj1 and obj2 are both characters and are the same character according to the char=? procedure

  • obj1 and obj2 are both the empty list

  • obj1 and obj2 are both a pair and car and cdr of both pairs are the same in the sense of eqv?

  • obj1 and obj2 are ports, vectors, hashtables, bytevectors, records, or strings that denote the same location in the store

  • obj1 and obj2 are procedures whose location tags are equal

The eqv? procedure returns #f if:

  • obj1 and obj2 are of different types

  • one of obj1 and obj2 is #t but the other is #f

  • obj1 and obj2 are symbols but are not the same symbol according to the symbol=? procedure

  • one of obj1 and obj2 is an exact number but the other is an inexact number

  • obj1 and obj2 are both exact numbers and are numerically unequal in the sense of =

  • obj1 and obj2 are both inexact numbers such that either they are numerically unequal in the sense of =, or they do not yield the same results in the sense of eqv? when passed as arguments to any other procedure that can be defined as a finite composition of Scheme’s standard arithmetic procedures, provided it does not result in a NaN value. As an exception, the behavior of eqv? is unspecified when both obj1 and obj2 are NaN.

  • obj1 and obj2 are characters for which the char=? procedure returns #f

  • one of obj1 and obj2 is the empty list but the other is not

  • obj1 and obj2 are both a pair but either car or cdr of both pairs are not the same in the sense of eqv?

  • obj1 and obj2 are ports, vectors, hashtables, bytevectors, records, or strings that denote distinct locations

  • obj1 and obj2 are procedures that would behave differently (i.e. return different values or have different side effects) for some arguments

The eq? procedure is similar to eqv? except that in some cases it is capable of discerning distinctions finer than those detectable by eqv?. It always returns #f when eqv? also would, but returns #f in some cases where eqv? would return #t. On symbols, booleans, the empty list, pairs, and records, and also on non-empty strings, vectors, and bytevectors, eq? and eqv? are guaranteed to have the same behavior.

(quote datum) evaluates to datum. datum can be any external representation of a LispKit object. This notation is used to include literal constants in LispKit code. (quote datum) can be abbreviated as ’datum. The two notations are equivalent in all respects. Numerical constants, string constants, character constants, vector constants, bytevector constants, and boolean constants evaluate to themselves. They need not be quoted.

Quasiquote expressions are useful for constructing a list or vector structure when some but not all of the desired structure is known in advance. If no commas appear within template, the result of evaluating (quasiquote template) is equivalent to the result of evaluating (quote template). If a comma appears within template, however, the expression following the comma is evaluated ("unquoted") and its result is inserted into the structure instead of the comma and the expression. If a comma appears followed without intervening whitespace by @, then it is an error if the following expression does not evaluate to a list; the opening and closing parentheses of the list are then "stripped away" and the elements of the list are inserted in place of the ,@ expression sequence. ,@ normally appears only within a list or vector.

Quasiquote expressions can be nested. Substitutions are made only for unquoted components appearing at the same nesting level as the outermost quasiquote. The nesting level increases by one inside each successive quasiquotation, and decreases by one inside each unquotation. Comma corresponds to form unquote, ,@ corresponds to form unquote-splicing.

Definitions

define is used to define variables. At the outermost level of a program, a definition (define var expr) has essentially the same effect as the assignment expression (set! var expr) if variable var is bound to a non-syntax value. However, if var is not bound, or is a syntactic keyword, then the definition will bind var to a new location before performing the assignment, whereas it would be an error to perform a set! on an unbound variable.

The form (define (f arg ...) expr) defines a function f with arguments arg ... and body expr. It is equivalent to (define f (lambda (arg ...) expr)).

The parameter doc is a string literal defining documentation for variable var. It can be accessed, for instance, by using the procedure environment-documentation on the environment in which the variable was bound.

(define pi 3.141 "documentation for `pi`")
(environment-documentation (interaction-environment) 'pi)
"documentation for `pi`"

define-values creates multiple definitions var ... from a single expression expr returning multiple values. It is allowed wherever define is allowed.

expr is evaluated, and the variables var ... are bound to the return values in the same way that the formal arguments in a lambda expression are matched to the actual arguments in a procedure call.

It is an error if a variable var appears more than once in var ....

(define-values (x y) (integer-sqrt 17))
(list x y)                              ⇒ (4 1)
(define-values vs (values 'a 'b 'c))
vs                                      ⇒ (a b c)

The parameter doc is an optional string literal defining documentation for variable var. It directly follows the identifier name.

Syntax definitions have the form (define-syntax keyword transformer). keyword is an identifier, and transformer is an instance of syntax-rules. Like variable definitions, syntax definitions can appear at the outermost level or nested within a body.

If the define-syntax occurs at the outermost level, then the global syntactic environment is extended by binding the keyword to the specified transformer, but previous expansions of any global binding for keyword remain unchanged. Otherwise, it is an internal syntax definition, and is local to the "body" in which it is defined. Any use of a syntax keyword before its corresponding definition is an error.

Macros can expand into definitions in any context that permits them. However, it is an error for a definition to define an identifier whose binding has to be known in order to determine the meaning of the definition itself, or of any preceding definition that belongs to the same group of internal definitions. Similarly, it is an error for an internal definition to define an identifier whose binding has to be known in order to determine the boundary between the internal definitions and the expressions of the body it belongs to.

Here is an example defining syntax for while loops. while evaluates the body of the loop as long as the predicate is true.

(define-syntax while
  (syntax-rules ()
    ((_ pred body ...)
      (let loop () (when pred body ... (loop))))))

The parameter doc is an optional string literal defining documentation for the keyword var:

(define-syntax kwote "alternative to quote"
  (syntax-rules ()
    ((kwote exp) (quote exp))))

A transformer spec has one of the two forms listed above. It is an error if any of the literal ..., or the ellipsis symbol in the second form, is not an identifier. It is also an error if syntax rules rule are not of the form

  • (pattern template).

The pattern in a rule is a list pattern whose first element is an identifier. In general, a pattern is either an identifier, a constant, or one of the following:

  • (pattern ...)

  • (pattern pattern ... . pattern)

  • (pattern ... pattern ellipsis pattern ...) (pattern ... pattern ellipsis pattern ... . pattern)

  • #(pattern ...)

  • #(pattern ... pattern ellipsis pattern ...)

A template is either an identifier, a constant, or one of the following:

  • (element ...)

  • (element element ... . template) (ellipsis template)

  • #(element ...)

where an element is a template optionally followed by an ellipsis. An ellipsis is the identifier specified in the second form of syntax-rules, or the default identifier ... (three consecutive periods) otherwise.

Here is an example showcasing how when can be defined in terms of if:

(define-syntax when
  (syntax-rules ()
    ((_ c e ...)
      (if c (begin e ...)))))

A library definition takes the following form: (define-library (name ...) declaration ...). (name ...) is a list whose members are identifiers and exact non-negative integers. It is used to identify the library uniquely when importing from other programs or libraries. It is inadvisable, but not an error, for identifiers in library names to contain any of the characters |, \, ?, *, <, ", :, >, +, [, ], /.

A declaration is any of:

  • (export exportspec ...)

  • (import importset ...)

  • (begin statement ...)

  • (include filename ...)

  • (include-ci filename ...)

  • (include-library-declarations filename ...)

  • (cond-expand clause ...)

An export declaration specifies a list of identifiers which can be made visible to other libraries or programs. An exportspec takes one of the following forms:

  • ident

  • (rename ident1 ident2)

In an exportspec, an identifier ident names a single binding defined within or imported into the library, where the external name for the export is the same as the name of the binding within the library. A rename spec exports the binding defined within or imported into the library and named by ident1 in each (ident1 ident2) pairing, using ident2 as the external name.

An import declaration provides a way to import the identifiers exported by another library. It has the same syntax and semantics as an import declaration used in a program or at the read-eval-print loop.

The begin, include, and include-ci declarations are used to specify the body of the library. They have the same syntax and semantics as the corresponding expression types.

The include-library-declarations declaration is similar to include except that the contents of the file are spliced directly into the current library definition. This can be used, for example, to share the same export declaration among multiple libraries as a simple form of library interface.

The cond-expand declaration has the same syntax and semantics as the cond-expand expression type, except that it expands to spliced-in library declarations rather than expressions enclosed in begin.

Procedure set! is used to assign values to variables. expr is evaluated, and the resulting value is stored in the location to which variable var is bound. It is an error if var is not bound either in some region enclosing the set! expression or else globally. The result of the set! expression is unspecified.

Importing definitions

An import declaration provides a way to import identifiers exported by a library. Each importset names a set of bindings from a library and possibly specifies local names for the imported bindings. It takes one of the following forms:

  • libraryname

  • (only importset identifier ...)

  • (except importset identifier ...)

  • (prefix importset identifier)

  • (rename importset (ifrom ito) ...)

In the first form, all of the identifiers in the named library’s export clauses are imported with the same names (or the exported names if exported with rename). The additional importset forms modify this set as follows:

  • only produces a subset of the given importset including only the listed identifiers (after any renaming). It is an error if any of the listed identifiers are not found in the original set.

  • except produces a subset of the given importset, excluding the listed identifiers (after any renaming). It is an error if any of the listed identifiers are not found in the original set.

  • rename modifies the given importset, replacing each instance of ifrom with ito. It is an error if any of the listed identifiers are not found in the original set.

  • prefix automatically renames all identifiers in the given importset, prefixing each with the specified identifier.

In a program or library declaration, it is an error to import the same identifier more than once with different bindings, or to redefine or mutate an imported binding with a definition or with set!, or to refer to an identifier before it is imported. However, a read-eval-print loop will permit these actions.

Procedures

Returns #t if obj is a procedure; otherwise, it returns #f.

Returns #t if obj is a procedure which accepts zero arguments; otherwise, it returns #f.

Returns #t if obj is a procedure that accepts n arguments; otherwise, it returns #f. This is equivalent to:

(and (procedure? obj)
     (procedure-arity-includes? obj n))

A lambda expression evaluates to a procedure. The environment in effect when the lambda expression was evaluated is remembered as part of the procedure. When the procedure is later called with some actual arguments, the environment in which the lambda expression was evaluated will be extended by binding the variables in the formal argument list arg1 ... to fresh locations, and the corresponding actual argument values will be stored in those locations. Next, the expressions in the body of the lambda expression will be evaluated sequentially in the extended environment. The results of the last expression in the body will be returned as the results of the procedure call.

A case-lambda expression evaluates to a procedure that accepts a variable number of arguments and is lexically scoped in the same manner as a procedure resulting from a lambda expression. When the procedure is called, the first clause for which the arguments agree with formals is selected, where agreement is specified as for formals of a lambda expression. The variables of formals are bound to fresh locations, the values of the arguments are stored in those locations, the expressions in the body are evaluated in the extended environment, and the results of the last expression in the body is returned as the results of the procedure call. It is an error for the arguments not to agree with formals of any clause.

Here is an example showing how to use case-lambda for defining a simple accumulator:

(define (make-accumulator n)
  (case-lambda
    (()  n)
    ((m) (set! n (+ n m)) n)))
(define a (make-accumulator 1))
(a)                              ⇒ 1
(a 5)                            ⇒ 6
(a)                              ⇒ 6

Returns a procedure accepting no arguments and evaluating expr ..., returning the result of the last expression being evaluated as the result of a procedure call. (thunk expr ...) is equivalent to (lambda () expr ...).

Returns a procedure accepting an arbitrary amount of arguments and evaluating expr ..., returning the result of the last expression being evaluated as the result of a procedure call. (thunk* expr ...) is equivalent to (lambda args expr ...).

Returns the name of procedure proc as a string, or #f if proc does not have a name.

Creates a copy of procedure proc with name as name. name is either a string or a symbol. If it is not possible to create a renamed procedure, procedure-rename returns #f.

Returns a value representing the arity of procedure proc, or returns #f if no arity information is available for proc.

If procedure-arity returns a fixnum k, then procedure proc accepts exactly k arguments and applying proc to some number of arguments other than k will result in an arity error.

If procedure-arity returns an "arity-at-least" object a, then procedure proc accepts (arity-at-least-value a) or more arguments and applying proc to some number of arguments less than (arity-at-least-value a) will result in an arity error.

If procedure-arity returns a list, then procedure proc accepts any of the arities described by the elements of the list. Applying proc to some number of arguments not described by an element of the list will result in an arity error.

Returns the smallest arity range in form of a pair (min . max) such that if proc is provided n arguments with n < min or n > max, an arity error gets raised.

(procedure-arity-range (lambda () 3))      ⇒  (0 . 0)
(procedure-arity-range (lambda (x) x))     ⇒  (1 . 1)
(procedure-arity-range (lambda x x))       ⇒  (0 . #f)
(procedure-arity-range (lambda (x . y) x)) ⇒  (1 . #f)

Returns #t if procedure proc can accept k arguments and #f otherwise. If this procedure returns #f, applying proc to k arguments will result in an arity error.

Returns #t if obj is an "arity-at-least" object and #f otherwise.

Returns a fixnum denoting the minimum number of arguments required by the given "arity-at-least" object obj.

Procedures with optional arguments

An opt-lambda expression evaluates to a procedure and is lexically scoped in the same manner as a procedure resulting from a lambda expression. When the procedure is later called with actual arguments, the variables are bound to fresh locations, the values of the corresponding arguments are stored in those locations, the body expr ... is evaluated in the extended environment, and the result of the last body expression is returned as the result of the procedure call.

Formal arguments argi are required arguments. Arguments bindi are optional. They are of the form (var init), with var being a symbol and init an initialization expression which gets evaluated and assigned to var if the argument is not provided when the procedure is called. It is a syntax violation if the same variable appears more than once among the variables.

A procedure created with the first syntax of opt-formals takes at least n arguments and at most n + m arguments. A procedure created with the second syntax of opt-formals takes n or more arguments. If the procedure is called with fewer than n + m (but at least n arguments), the missing actual arguments are substituted by the values resulting from evaluating the corresponding _init_s. The corresponding _init_s are evaluated in an unspecified order in the lexical environment of the opt-lambda expression when the procedure is called.

Similar to syntax opt-lambda except that the initializers of optional arguments bindi corresponding to missing actual arguments are evaluated sequentially from left to right. The region of the binding of a variable is that part of the opt*-lambda expression to the right of it or its binding.

define-optionals is operationally equivalent to (define f (opt-lambda (arg ... bind ...) expr ...)) or (define f (opt-lambda (arg ... bind ... . rest) expr ...)) if the second syntactical form is used.

define-optionals* is operationally equivalent to (define f (opt*-lambda (arg ... bind ...) expr ...)) or (define f (opt*-lambda (arg ... bind ... . rest) expr ...)) if the second syntactical form is used.

Tagged procedures

LispKit allows a data object to be associated with a procedure. Such data objects are called tags, procedures with an associated tag are called tagged procedures. The tag of a procedure is immutable. It is defined at procedure creation time and can later be retrieved without calling the procedure.

Returns #t if obj is a tagged procedure and #f otherwise. Procedures are tagged procedures if they were created either via lambda/tag or case-lambda/tag.

Returns the tag of the tagged procedure proc. It is an error if proc is not a tagged procedure.

A lambda/tag expression evaluates to a tagged procedure. First, tag is evaluated to obtain the tag value for the procedure. Then, the tagged procedure itself gets created for the given formal arguments. The procedure is lexically scoped in the same manner as a procedure resulting from a lambda expression. When the procedure is called, it behaves as if constructed by a lambda expression with the same formal arguments and body.

A case-lambda/tag expression evaluates to a tagged procedure. First, tag is evaluated to obtain the tag value for the procedure. Then, the tagged procedure itself gets created, accepting a variable number of arguments. It is lexically scoped in the same manner as a procedure resulting from a lambda expression. When the procedure is called, it behaves as if it was constructed by a case-lambda expression with the same formal arguments and bodies.

Delayed execution

LispKit provides promises to delay the execution of code. Built on top of promises are streams. Streams are similar to lists, except that the tail of a stream is not computed until it is de-referenced. This allows streams to be used to represent infinitely long lists. Library (lispkit core) only defines procedures for streams equivalent to promises. Library (lispkit stream) provides all the list-like functionality.

The promise? procedure returns #t if argument obj is a promise, and #f otherwise.

The make-promise procedure returns a promise which, when forced, will return obj. It is similar to delay, but does not delay its argument: it is a procedure rather than syntax. If obj is already a promise, it is returned. eager represents the same procedure like make-promise.

The delay construct is used together with the procedure force to implement lazy evaluation or "call by need". (delay expr) returns an object called a promise which, at some point in the future, can be asked (by the force procedure) to evaluate expr, and deliver the resulting value.

The expression (delay-force expr) is conceptually similar to (delay (force expr)), with the difference that forcing the result of delay-force will in effect result in a tail call to (force expr), while forcing the result of (delay (force expr)) might not. Thus iterative lazy algorithms that might result in a long series of chains of delay and force can be rewritten using delay-force to prevent consuming unbounded space during evaluation. lazy represents the same procedure like delay-force.

The force procedure forces the value of a promise created by delay, delay-force, or make-promise. If no value has been computed for the promise, then a value is computed and returned. The value of the promise must be cached (or "memoized") so that if it is forced a second time, the previously computed value is returned. Consequently, a delayed expression is evaluated using the parameter values and exception handler of the call to force which first requested its value. If promise is not a promise, it may be returned unchanged.

(force (delay (+ 1 2)))        ⇒  3
(let ((p (delay (+ 1 2))))
  (list (force p) (force p)))  ⇒ (3 3)
(define integers
  (letrec ((next (lambda (n)
                   (delay (cons n (next (+ n 1)))))))
    (next 0)))
(define head
  (lambda (stream) (car (force stream))))
(define tail
  (lambda (stream) (cdr (force stream))))
(head (tail (tail integers)))  ⇒  2

The following example is a mechanical transformation of a lazy stream-filtering algorithm into Scheme. Each call to a constructor is wrapped in delay, and each argument passed to a deconstructor is wrapped in force. The use of (delay-force ...) instead of (delay (force ...)) around the body of the procedure ensures that an ever-growing sequence of pending promises does not exhaust available storage, because force will, in effect, force such sequences iteratively.

(define (stream-filter p? s)
  (delay-force
    (if (null? (force s))
        (delay ’())
        (let ((h (car (force s)))
              (t (cdr (force s))))
          (if (p? h)
              (delay (cons h (stream-filter p? t)))
              (stream-filter p? t))))))

(head (tail (tail (stream-filter odd? integers))))  ⇒  5

The following examples are not intended to illustrate good programming style, as delay, force, and delay-force are mainly intended for programs written in the functional style. However, they do illustrate the property that only one value is computed for a promise, no matter how many times it is forced.

(define count 0)
(define p
  (delay (begin (set! count (+ count 1))
                (if (> count x) count (force p)))))
(define x 5)
p                              ⇒  a promise
(force p)                      ⇒  6
p                              ⇒  a promise
(begin (set! x 10) (force p))  ⇒  6

The stream? procedure returns #t if argument obj is a stream, and #f otherwise. If obj is a stream, stream? does not force its promise. If (stream? obj) is #t, then one of (stream-null? obj) and (stream-pair? obj) will be #t and the other will be #f; if (stream? obj) is #f, both (stream-null? obj) and (stream-pair? obj) will be #f.

The make-stream procedure returns a stream which, when forced, will return obj. It is similar to stream-delay, but does not delay its argument: it is a procedure rather than syntax. If obj is already a stream, it is returned. stream-eager represents the same procedure like make-stream.

The stream-delay syntax is used together with procedure stream-force to implement lazy evaluation or "call by need". (stream-delay expr) returns an object called a stream which, at some point in the future, can be asked (by the stream-force procedure) to evaluate expr, and deliver the resulting value.

The expression (stream-delay-force expr) is conceptually similar to (stream-delay (stream-force expr)), with the difference that forcing the result of stream-delay-force will in effect result in a tail call to (stream-force expr), while forcing the result of (stream-delay (stream-force expr)) might not. Thus iterative lazy algorithms that might result in a long series of chains of delay and force can be rewritten using stream-delay-force to prevent consuming unbounded space during evaluation. stream-lazy represents the same procedure like stream-delay-force.

Symbols

Returns #t if obj is a symbol, otherwise returns #f.

Returns #t if obj is an interned symbol, otherwise returns #f.

Returns a new (fresh) symbol whose name consists of prefix str followed by a number. If str is not provided, "g" is used as a prefix.

Returns #t if all the arguments are symbols and all have the same names in the sense of string=?.

Returns the symbol whose name is string str. This procedure can create symbols with names containing special characters that would require escaping when written, but does not interpret escapes in its input.

Returns a new uninterned symbol whose name is str. This procedure can create symbols with names containing special characters that would require escaping when written, but does not interpret escapes in its input.

Returns the name of symbol sym as a string, but without adding escapes.

Booleans

The standard boolean objects for true and false are written as #t and #f. Alternatively, they can be written #true and #false, respectively. What really matters, though, are the objects that the Scheme conditional expressions (if, cond, and, or, when, unless, do) treat as true or false. The phrase a "true value" (or sometimes just "true") means any object treated as true by the conditional expressions, and the phrase "a false value" (or "false") means any object treated as false by the conditional expressions.

Of all the Scheme values, only #f counts as false in conditional expressions. All other Scheme values, including #t, count as true. Boolean literals evaluate to themselves, so they do not need to be quoted in programs.

The boolean? predicate returns #t if obj is either #t or #f and returns #f otherwise.

(boolean? #f)    ⇒  #t
(boolean? 0)     ⇒  #f
(boolean? '())   ⇒  #f

Returns #t if all the arguments are booleans and all are #t or all are #f.

The test ... expressions are evaluated from left to right, and if any expression evaluates to #f, then #f is returned. Any remaining expressions are not evaluated. If all the expressions evaluate to true values, the values of the last expression are returned. If there are no expressions, then #t is returned.

(and (= 2 2) (> 2 1))  ⇒  #t
(and (= 2 2) (< 2 1))  ⇒  #f
(and 12 'c '(f g))     ⇒  (f g)
(and)                  ⇒  #t

The test ... expressions are evaluated from left to right, and the value of the first expression that evaluates to a true value is returned. Any remaining expressions are not evaluated. If all expressions evaluate to #f or if there are no expressions, then #f is returned.

(or (= 2 2) (> 2 1))            ⇒  #t
(or (= 2 2) (< 2 1))            ⇒  #t
(or #f #f #f)                   ⇒  #f
(or (memq 'b '(a b c)) (/ 3 0)) ⇒  (b c)

The not procedure returns #t if obj is false, and returns #f otherwise.

(not #t)        ⇒  #f
(not 3)         ⇒  #f
(not (list 3))  ⇒  #f
(not #f)        ⇒  #t
(not '())       ⇒  #f
(not (list))    ⇒  #f
(not 'nil)      ⇒  #f

The opt procedure returns failval if obj is #f. If obj is not #f, opt applies predicate pred to obj and returns the result of this function application. If failval is not provided, #t is used as a default. This function is useful to verify a given predicate pred for an optional value obj.

Conditional and inclusion compilation

The cond-expand expression type provides a way to statically expand different expressions depending on the implementation. A ce-clause takes the following form:

(featurerequirement expression ...)

The last clause can be an “else clause,” which has the form:

(else expression ...)

A featurerequirement takes one of the following forms:

  • featureidentifier

  • (library name)

  • (and featurerequirement ...)

  • (or featurerequirement ...)

  • (not featurerequirement)

LispKit maintains a list of feature identifiers which are present, as well as a list of libraries which can be imported. The value of a featurerequirement is determined by replacing each featureidentifier and (library name) with #t, and all other feature identifiers and library names with #f, then evaluating the resulting expression as a Scheme boolean expression under the normal interpretation of and, or, and not.

A cond-expand is then expanded by evaluating the featurerequirements of successive ce-clause in order until one of them returns #t. When a true clause is found, the corresponding expression ... are expanded to a begin, and the remaining clauses are ignored. If none of the listed featurerequirement evaluates to #t, then if there is an "else" clause, its expression ... are included. Otherwise, the behavior of the cond-expand is unspecified. Unlike cond, cond-expand does not depend on the value of any variables. The exact features provided are defined by the implementation, its environment and host platform.

LispKit supports the following featureidentifier:

  • lispkit

  • r7rs

  • ratios

  • complex

  • syntax-rules

  • little-endian

  • big-endian

  • dynamic-loading

  • modules

  • 32bit

  • 64bit

  • macos

  • macosx

  • ios

  • linux

  • i386

  • x86-64

  • arm64

  • arm

Both include and include-ci take one or more filenames expressed as string literals, apply an implementation-specific algorithm to find corresponding files, read the contents of the files in the specified order as if by repeated applications of read, and effectively replace the include or include-ci expression with a begin expression containing what was read from the files. The difference between the two is that include-ci reads each file as if it began with the #!fold-case directive, while include does not.

Multiple values

Delivers all of its arguments to its continuation. The values procedure might be defined as follows:

(define (values . things)
  (call-with-current-continuation
    (lambda (cont) (apply cont things))))

Calls its producer argument with no arguments and a continuation that, when passed some values, calls the consumer procedure with those values as arguments. The continuation for the call to consumer is the continuation of the call to call-with-values.

(call-with-values (lambda () (values 4 5))
                  (lambda (a b) b))
  ⇒  5
(call-with-values * -)
  ⇒  -1

apply-with-values calls procedure proc with vals as its arguments and returns the corresponding result. vals might refer to multiple values created via procedure values. This is a LispKit-specific procedure that relies on multiple return values being represented by a container object.

Environments

Environments are first-class objects which associate identifiers (symbols) with values. Environments are used implicitly by the LispKit compiler and runtime system, but library (lispkit core) also provides an API allowing systems to manipulate and use environments programmatically.

For instance, when a top-level variable gets created with define, the name/value association for that variable is added to the "top-level" environment. The LispKit compiler implicitly creates environments other than the top-level environment, for example, when compiling and executing libraries.

There are several types of bindings that can occur within an environment. A variable binding associates a value with an identifier. This is the most common type of binding. In addition to variable bindings, environments can have keyword bindings. A keyword binding associates an identifier with a macro transformer (usually via syntax-rules). There are also unassigned bindings referring to bindings without a known value.

Returns #t if obj is an environment. Otherwise, it returns #f.

Returns #t if obj is an interaction environment, i.e. a mutable environment in which expressions entered by the user into a read-eval-print loop are being evaluated. Otherwise, procedure interaction-environment? returns #f.

Returns #t if obj is a custom environment, i.e. an environment that was programmatically constructed. Otherwise, predicate custom-environment? returns #f.

Special form the-environment returns the current top-level environment. If there is none, the-environment returns #f.

Here is an example how one can print the names bound at compile-time:

(define-library (foo)
  (import (only (lispkit core) the-environment environment-bound-names)
          (only (lispkit port) display newline))
  (begin
    (display "bound = ")
    (display (environment-bound-names (the-environment)))
    (newline)))
(import (foo))

bound = (display the-environment newline environment-bound-names)

This procedure returns an environment that results by starting with an empty environment and then importing each list, considered as an import set, into it. The bindings of the environment represented by the specifier are immutable, as is the environment itself.

Returns a list of the symbols that are bound by environment env.

Returns a list of the bindings of environment env. Each element of this list takes one of two forms: the form (name) indicates that name is bound but unassigned, while (name obj) indicates that name is bound to value obj.

Returns #t if symbol ident is bound in environment env; otherwise returns #f.

Returns the value to which symbol ident is bound in environment env. This procedure throws an error if ident is not bound to a value in env.

Symbol ident must be bound in environment env. Procedure environment-assignable? returns #t if the binding of ident may be modified.

Symbol ident must be bound in environment env and must be assignable. Procedure environment-assign! modifies the binding to have obj as its value.

Predicate environment-definable? returns #t if symbol ident is definable in environment env, and #f otherwise. Currently, interaction environments and custom environments allow for identifiers to be defined. For all other types of environments, this predicate returns #f independent of ident.

Defines ident to be bound to obj in environment env. This procedure signals an error if ident is not definable in env.

Defines ident to be a keyword bound to macro transformer transf (typically expressed in terms of syntax-rules) in environment env. This procedure signals an error if ident is not definable in environment env.

Imports the identifiers exported by a library and specified via an import set importset into the environment env. The procedure fails if the type of environment does not allow identifiers to be defined programmatically.

Returns the documentation associated with the identifier ident in environment env as a string. This procedure returns #f if ident is not associated with any documentation.

Assigns the documentation string str to identifier ident in environment env.

If version is equal to 5, corresponding to R5RS, scheme-report-environment returns an environment that contains only the bindings defined in the R5RS library.

If version is equal to 5, corresponding to R5RS, the null-environment procedure returns an environment that contains only the bindings for all syntactic keywords defined in the R5RS library.

This procedure returns a mutable environment which is the environment in which expressions entered by the user into a read-eval-print loop are evaluated. This is typically a superset of bindings from (lispkit base).

Source files

load reads a source file specified by filename and executes it in the given environment. If no environment is specified, the current interaction environment is used, which can be accessed via (interaction-environment). Execution of the file consists of reading expressions and definitions from the file, compiling them, and evaluating them sequentially in the environment. load returns the result of evaluating the last expression or definition from the file. During compilation, the special form source-directory can be used to access the directory in which the executed file is located.

It is an error if filename is not a string. If filename is not an absolute file path, LispKit will try to find the file in a predefined set of directories, such as the default libraries search path. If no file name suffix, also called path extension, is provided, the system will try to determine the right suffix. For instance, (load "Prelude") will find the prelude file, determine its suffix and load and execute the file.

Syntax errors

syntax-error behaves similarly to error except that implementations with an expansion pass separate from evaluation should signal an error as soon as syntax-error is expanded. This can be used as a syntax-rules template for a pattern that is an invalid use of the macro, which can provide more descriptive error messages.

message is a string literal, and args ... are arbitrary expressions providing additional information. Applications cannot count on being able to catch syntax errors with exception handlers or guards.

(define-syntax simple-let
  (syntax-rules ()
    ((_ (head ... ((x . y) val) . tail) body1 body2 ...)
      (syntax-error "expected an identifier but got" (x . y)))
    ((_ ((name val) ...) body1 body2 ...)
      ((lambda (name ...) body1 body2 ...) val ...))))

Utilities

Performs no operation and returns nothing. This is often useful as a placeholder or whenever a no-op statement is needed.

Returns #t if obj is the "void" value (i.e. no value); returns #f otherwise.

The identity function is always returning its argument obj.

Last updated