======================================================================== _Swindle_ ======================================================================== This is Swindle, written by Eli Barzilay (eli@barzilay.org) Swindle is a collection of modules that extend PLT Scheme (www.plt-scheme.org) with many additional features. The main feature which started this project is a CLOS-like object system based on Tiny-CLOS from Xerox, but there is a lot more -- see the feature list below for a rough picture. The latest version of Swindle is available at http://www.barzilay.org/Swindle/. There is also a low volume mailing list, mail me to register. Comments, bugs, or whatever are welcome. ------------------------------------------------------------------------ _base_ _base.ss_ ------------------------------------------------------------------------ The `base' module defines some basic low-level syntactic extensions to MzScheme. It can be used by itself to get these extensions. This module is intended to be used as a language module (as an initial-import for other modules). > (#%module-begin ...) [syntax] `base' is a language module -- it redefines `#%module-begin' to load itself for syntax definitions. > (#%top . id) [syntax] This special syntax is redefined to make keywords (symbols whose names begin with a ":") evaluate to themselves. Note that this does not interfere with using such symbols for local bindings. > (#%app ...) [syntax] Redefined so it is possible to apply using dot notation: `(foo x . y)' is the same as `(apply foo x y)'. This is possible only when the last (dotted) element is an identifier. > (define id-or-list ...) [syntax] The standard `define' form is modified so instead of an identifier name for a function, a list can be used -- resulting in a curried function. => (define (((plus x) y) z) (+ x y z)) => plus # => (plus 5) # => ((plus 5) 6) # => (((plus 5) 6) 7) 18 Note the names of intermediate functions. In addition, the following form can be used to define multiple values: => (define (values a b) (values 1 2)) > (let ([id-or-list ...] ...) ...) [syntax] > (let* ([id-or-list ...] ...) ...) [syntax] > (letrec ([id-or-list ...] ...) ...) [syntax] All standard forms of `let' are redefined so they can generate functions using the same shortcut that `define' allows. This includes the above extension to the standard `define'. For example: => (let ([((f x) y) (+ x y)]) ((f 1) 2)) 3 It also includes the `values' keyword in a similar way to `define'. For example: => (let ([(values i o) (make-pipe)]) i) # > (lambda formals body ...) [syntax] The standard `lambda' is extended with Lisp-like &-keywords in its argument list. This extension is available using the above short syntax. There is one important difference between these keywords and Lisp: some &-keywords are used to access arguments that follow the keyword part of the arguments. This makes it possible to write procedures that can be invoked as follows: (f ) (Note: do not use more keywords after the !) Available &-keywords are: * &optional, &opt, &opts: denote an optional argument, possibly with a default value (if the variable is specified as `(var val)'). => ((lambda (x &optional y [z 3]) (list x y z)) 1) (1 #f 3) => ((lambda (x &optional y [z 3]) (list x y z)) 1 2 #f) (1 2 #f) * &keys, &key: a keyword argument -- the variable should be specified as `x' or `(x)' to be initialized by an `:x' keyword, `(x v)' to specify a default value `v', and `(x k v)' to further specify an arbitrary keyword `k'. => ((lambda (&key x [y 2] [z :zz 3]) (list x y z)) :x 'x :zz 'z) (x 2 z) Note that keyword values take precedence on the left, and that keywords are not verified: => ((lambda (&key y) y) :y 1 :z 3 :y 2) 1 * &rest: a `rest' argument which behaves exactly like the Scheme dot formal parameter (actually a synonym for it: can't use both). Note that in case of optional arguments, the rest variable holds any arguments that were not used for defaults, but using keys doesn't change its value. For example: => ((lambda (x &rest r) r) 1 2 3) (2 3) => ((lambda (x &optional y &rest r) r) 1) () => ((lambda (x &optional y &rest r) r) 1 2 3) (3) => ((lambda (x &optional y . r) r) 1 2 3) (3) => ((lambda (x &key y &rest r) (list y r)) 1 :y 2 3 4) (2 (:y 2 3 4)) => ((lambda (x &key y &rest r) (list y r)) 1 :y 2 3 4 5) (2 (:y 2 3 4 5)) Note that the last two examples indicate that there is no error if the given argument list is not balanced. * &rest-keys: similar to `&rest', but all specified keys are removed with their values. => ((lambda (x &key y &rest r) r) 1 :x 2 :y 3) (:x 2 :y 3) => ((lambda (x &key y &rest-keys r) r) 1 :x 2 :y 3) (:x 2) * &body: similar to `&rest-keys', but all key/values are removed one by one until a non-key is encountered. (Warning: this is *not* the same as in Common Lisp!) => ((lambda (x &key y &body r) r) 1 :x 2 :y 3) () => ((lambda (x &key y &body r) r) 1 :x 2 :y 3 5 6) (5 6) * &all-keys: the list of all keys+vals, without a trailing body. => ((lambda (&keys x y &all-keys r) r) :x 1 :z 2 3 4) (:x 1 :z 2) * &other-keys: the list of unprocessed keys+vals, without a trailing body. => ((lambda (&keys x y &other-keys r) r) :x 1 :z 2 3 4) (:z 2) Finally, here is an example where all &rest-like arguments are different: => ((lambda (&keys x y &rest r &rest-keys rk &body b &all-keys ak &other-keys ok) (list r rk b ak ok)) :z 1 :x 2 2 3 4) ((:z 1 :x 2 2 3 4) (:z 1 2 3 4) (2 3 4) (:z 1 :x 2) (:z 1)) Note that the following invariants hold: * rest = (append all-keys body) * rest-keys = (append other-keys body) > (keyword? x) [procedure] A predicate for keyword symbols (symbols that begin with a ":"). > (syntax-keyword? x) [procedure] Similar to `keyword?' but also works for an identifier (a syntax object) that contains a keyword. > (getarg args keyword [not-found]) [procedure] Searches the given list of arguments for a value matched with the given keyword. Similar to CL's `getf', except no error checking is done for an unbalanced list. In case no value is found, the optional default value can be used -- this can be either a thunk, a promise, or any other value that will be used as is. For a repeated keyword the leftmost occurrence is used. > (syntax-getarg syntax-args keyword [not-found]) [procedure] Similar to `getarg' above, but the input is a syntax object of a keyword-value list. > (getargs initargs keyword) [procedure] The same as `getarg' but return the list of all key values matched -- no need for a default value. The result is in the same order as in the input. > (keys/args args) [procedure] The given argument list is scanned and split at the point where there are no more keyword-values, and the two parts are returned as two values. => (keys/args '(:a 1 :b 2 3 4 5)) (:a 1 :b 2) (3 4 5) > (filter-out-keys outs args) [procedure] The keywords specified in the outs argument, with their matching values are filtered out of the second arguments. ------------------------------------------------------------------------ _setf_ _setf.ss_ ------------------------------------------------------------------------ This module provides the forms `setf!', `psetf!', and `setf!-values' for generic setters, much like CL's `setf', and `psetf', and a form similar to MzScheme's `set!-values'. Note that when these are later re-exported (by `turbo'), they are renamed as `set!', `pset!', and `set!-values' (overriding the built-in `set!' and `set!-values'). Also, note that this just defines the basic functionality, the `misc' module defines many common setters. > (setf! place value ...) [syntax] Expand `(setf! (foo ...) v)' to `(set-foo! ... v)'. The generated `set-foo!' identifier has the same syntax context as `foo', which means that to use this for some `foo' you need to define `set-foo!' either as a function or a syntax in the same definition context of `foo'. The nice feature that comes out of this and the syntax system is that examples like the following work as expected: (let ([foo car] [set-foo! set-car!]) (setf! (foo a) 11)) `place' gets expanded before this processing is done so macros work properly. If the place is not a form, then this will just use the standard `set!'. Another extension of the original `set!' is that it allows changing several places in sequence -- `(setf! x a y b)' will set `x' to `a' and then set `y' to `b'. > (psetf! place value ...) [syntax] This is very similar to `setf!' above, except that the change to the places is done *simultaneously*. For example, `(setf! x y y x)' switches the values of the two variables. > (setf!-values (place ...) expr) [syntax] This is a version of `setf!', that works with multiple values. `expr' is expected to evaluate to the correct number of values, and these are then put into the specified places which can be an place suited to `setf!'. Note that no duplication of identifiers is checked, if an identifier appears more than once then it will have the last assigned value. > (set-values! places ... values-expr) [syntax] > (set-list! places ... list-expr) [syntax] > (set-vector! places ... vector-expr) [syntax] These are defined as special forms that use `setf!-values' to set the given places to the appropriate components of the third form. This allows foing the following: => (define (values a b c) (values 1 2 3)) => (setf! (values a b c) (values 11 22 33)) => (list a b c) (11 22 33) => (setf! (list a b c) (list 111 222 333)) => (list a b c) (111 222 333) => (setf! (list a b c) (list 1111 2222 3333)) => (list a b c) (1111 2222 3333) Furthermore, since the individual setting of each place is eventually done with `setf!', then this can be used recursively: => (set! (list a (vector b) (vector c c)) '(2 #(3) #(4 5))) => (list a b c) (2 3 5) > (shift! place ... newvalue) [syntax] This is similar to CL's `shiftf' -- it is roughly equivalent to (begin0 place1 (psetf! place1 place2 place2 place3 ... placen newvalue)) except that it avoids evaluating index subforms twice, for example: => (let ([foo (lambda (x) (printf ">>> ~s\n" x) x)] [a '(1)] [b '(2)]) (list (shift! (car (foo a)) (car (foo b)) 3) a b)) >>> (1) >>> (2) (1 (2) (3)) > (rotate! place ...) [syntax] This is similar to CL's `rotatef' -- it is roughly equivalent to (psetf! place1 place2 place2 place3 ... placen place1) except that it avoids evaluating index subforms twice. > (inc! place [delta]) [syntax] > (dec! place [delta]) [syntax] > (push! x place) [syntax] > (pop! place) [syntax] These are some simple usages of `setf!'. Note that they also avoid evaluating any indexes twice. ------------------------------------------------------------------------ _misc_ _misc.ss_ ------------------------------------------------------------------------ A lot of miscellaneous functionality that is needed for Swindle, or useful by itself. This module exports bindings from: `mzlib/string', `mzlib/list', `mzlib/etc'. _Convenient syntax definitions_ ------------------------------- > (define* ...) [syntax] Just like `define', except that the defined identifier is automatically `provide'd. Doesn't work for defining values. > (make-provide-syntax orig-def-syntax provide-def-syntax) [syntax] Creates `provide-def-syntax' as a syntax that is the same as `orig-def-syntax' together with an automatic `provide' form for the defined symbol, which should be either the first argument or the first identifier in a list (it does not work for recursive nesting). The convention when this is used is to use a "*" suffix for the second identifier. > (define-syntax* ...) [syntax] Defined as the auto-provide form of `define-syntax'. > (defsyntax ...) [syntax] > (defsyntax* ...) [syntax] > (letsyntax (local-syntaxes ...) ...) [syntax] These are just shorthands for `define-syntax', `define-syntax*', and `let-syntax'. This naming scheme is consistent with other definitions in this module (and the rest of Swindle). > (defsubst name body) [syntax] > (defsubst* name body) [syntax] > (letsubst ([name body] ...) letbody ...) [syntax] These are convenient ways of defining simple pattern transformer syntaxes (simple meaning they're much like inlined functions). In each of these forms, the `name' can be either a `(name arg ...)' which will define a simple macro or an identifier which will define a symbol-macro. For example: => (defsubst (my-if cond then else) (if (and cond (not (eq? 0 cond))) then else)) => (my-if 1 (echo 2) (echo 3)) 2 => (my-if 0 (echo 2) (echo 3)) 3 => (define x (list 1 2 3)) => (defsubst car-x (car x)) => car-x 1 => (set! car-x 11) => x (11 2 3) Actually, if a `(name arg ...)' is used, then the body can have more pattern/expansions following -- but since this form translates to a usage of `syntax-rules', the `name' identifier should normally be `_' in subsequent patterns. For example: => (defsubst (my-if cond then else) (if (and cond (not (eq? 0 cond))) then else) (_ cond then) (and cond (not (eq? 0 cond)) then)) => (my-if 0 1) #f Finally, note that since these are just patterns that get handled by syntax-rules, all the usual pattern stuff applies, like using `...'. > (defmacro name body) [syntax] > (defmacro* name body) [syntax] > (letmacro ([name body] ...) letbody ...) [syntax] These are just like MzScheme's define-macro (from mzlib/defmacro) with two major extensions: * If `name' is a simple identifier then a symbol-macro is defined (as with `defsubst' above). * A `letmacro' form for local macros is provided. _Controlling syntax_ -------------------- > (define-syntax-parameter name default) [syntax] > (define-syntax-parameter* name default) [syntax] Creates a `syntax parameter'. Syntax parameters are things that you can use just like normal parameters, but they are syntax transformers, and the information they store can be used by other syntax transformers. The purpose of having them around is to parameterize the way syntax transformation is used -- so they should be used as global option changes, not for frequent side effect: they change their value at syntax expansion time. Note that using it stores the literal syntax that is passed to them -- there is no way to evaluate the given argument, for example, if some parameter expects a boolean -- then `(not #t)' will not work! The syntax parameter itself is invoked wither with no arguments to retrieve its value, or with an argument to set it. Retrieving or setting the value in this way is meaningful only in an interactive context since using it in a function just expands to the current value: => (define-syntax-parameter -foo- 1) => (-foo-) 1 => (define (foo) (-foo-)) => (-foo- 2) => (-foo-) 2 => (foo) 1 _Setters and more list accessors_ --------------------------------- > (set-caar! place x) [procedure] > (set-cadr! place x) [procedure] > (set-cdar! place x) [procedure] > (set-cddr! place x) [procedure] > (set-caaar! place x) [procedure] > (set-caadr! place x) [procedure] > (set-cadar! place x) [procedure] > (set-caddr! place x) [procedure] > (set-cdaar! place x) [procedure] > (set-cdadr! place x) [procedure] > (set-cddar! place x) [procedure] > (set-cdddr! place x) [procedure] > (set-caaaar! place x) [procedure] > (set-caaadr! place x) [procedure] > (set-caadar! place x) [procedure] > (set-caaddr! place x) [procedure] > (set-cadaar! place x) [procedure] > (set-cadadr! place x) [procedure] > (set-caddar! place x) [procedure] > (set-cadddr! place x) [procedure] > (set-cdaaar! place x) [procedure] > (set-cdaadr! place x) [procedure] > (set-cdadar! place x) [procedure] > (set-cdaddr! place x) [procedure] > (set-cddaar! place x) [procedure] > (set-cddadr! place x) [procedure] > (set-cdddar! place x) [procedure] > (set-cddddr! place x) [procedure] These are all defined so it is possible to use `setf!' from "setf.ss" with these standard and library-provided functions. > (1st list) [procedure] > (2nd list) [procedure] > (3rd list) [procedure] > (4th list) [procedure] > (5th list) [procedure] > (6th list) [procedure] > (7th list) [procedure] > (8th list) [procedure] Quick list accessors -- no checking is done, which makes these slightly faster than the bindings provided by mzlib/list. > (set-1st! list x) [procedure] > (set-2nd! list x) [procedure] > (set-3rd! list x) [procedure] > (set-4th! list x) [procedure] > (set-5th! list x) [procedure] > (set-6th! list x) [procedure] > (set-7th! list x) [procedure] > (set-8th! list x) [procedure] Setter functions for the above. > (head pair) [procedure] > (tail pair) [procedure] > (set-head! pair x) [procedure] > (set-tail! pair x) [procedure] Synonyms for `first', `rest', `set-first!', `set-rest!'. > (set-second! list x) [procedure] > (set-third! list x) [procedure] > (set-fourth! list x) [procedure] > (set-fifth! list x) [procedure] > (set-sixth! list x) [procedure] > (set-seventh! list x) [procedure] > (set-eighth! list x) [procedure] Defined to allow `setf!' with these mzlib/list functions. Note that there is no error checking (unlike the accessor functions which are provided by mzlib/list). > (nth list n) [procedure] > (nthcdr list n) [procedure] Functions for pulling out the nth element and the nth tail of a list. Note the argument order which is unlike the one in CL. > (list-set! list n x) [procedure] > (set-nth! list n x) [procedure] A function to set the nth element of a list, also provided as `set-nth!' to allow using `setf!' with `nth'. > (set-list-ref! list n x) [procedure] > (set-vector-ref! vector n x) [procedure] > (set-string-ref! string n x) [procedure] These are defined as `list-set!', `vector-set!', and `string-set!', so the accessors can be used with `setf!'. > (last list) [procedure] > (set-last! list x) [procedure] Accessing a list's last element, and modifying it. > (set-unbox! box x) [procedure] Allow using `setf!' with `unbox'. Note: this is an alias for `set-box!' which is an inconsistent name with other Scheme `set-foo!' functions -- the result is that you can also do `(setf! (box foo) x)' and bogusly get the same effect. > (set-hash-table-get! table key [default] value) [syntax] This is defined to be able to `setf!' into a `hash-table-get' accessor. The form that `setf!' assembles always puts the new value last, but it is still useful to have a default thunk which results in an optional argument in an unusual place (and this argument is ignored by this, which is why it is defined as a macro). For example: => (define t (make-hash-table)) => (inc! (hash-table-get t 'foo)) hash-table-get: no value found for key: foo => (inc! (hash-table-get t 'foo (thunk 0))) => (hash-table-get t 'foo) 1 _Utilities_ ----------- > (eprintf fmt-string args ...) [procedure] Same as `printf' but it uses the current-error-port. > concat [procedure] A shorter alias for `string-append'. > (symbol-append sym ...) [procedure] Self explanatory. > (maptree func tree) [procedure] Applies given function to a tree made of cons cells, and return the results tree with the same shape. > (map! func list ...) [procedure] Same as `map' -- but destructively modifies the first list to hold the results of applying the function. Assumes all lists have the same length. > (maptree! func tree) [procedure] Same as `maptree' -- but destructively modifies the list to hold the results of applying the function. > (mappend func list ...) [procedure] > (mappend! func list ...) [procedure] Common idiom for doing a `(map func list ...)' and appending the results. `mappend!' uses `append!'. > (mapply func list-of-lists) [procedure] Apply the given `func' on every list in `list-of-lists' and return the results list. > (negate predicate?) [procedure] Returns a negated predicate function. > (position-of x list) [procedure] Finds `x' in `list' and returns its index. > (find-if predicate? list) [procedure] Find and return an element of `list' which satisfies `predicate?', or #f if none found. > (some predicate? list ...) [procedure] > (every predicate? list ...) [procedure] Similar to MzScheme's `ormap' and `andmap', except that when multiple lists are given, the check stops as soon as the shortest list ends. > (regexp-quote string) [procedure] The same as `regexp-quote' from mzlib/string, but faster. > (with-output-to-string thunk) [procedure] Run `thunk' collecting generated output into a string. > (1+ x) [procedure] > (1- x) [procedure] Synonyms for `add1' and `sub1'. _Multi-dimensional hash-tables_ ------------------------------- > (make-l-hash-table) [procedure] > (l-hash-table-get table keys [failure-thunk]) [procedure] > (l-hash-table-put! table keys value) [procedure] > (set-l-hash-table-get! table key [default] value) [syntax] These functions are similar to MzScheme's hash-table functions, except that they work with a list of keys (compared with `eq?'). If it was possible to use a custom equality hash-table, then then would use something like (lambda (x y) (and (= (length x) (length y)) (andmap eq? x y))). The implementation uses a hash-table of hash-tables, all of them weak, since it is supposed to be used for memoization. `set-l-hash-table-get!' is defined to work with `setf!'. > (memoize func) [procedure] Return a memoized version of `func'. Note that if `func' is recursive, it should be arranged for it to call the memoized version rather then call itself directly. > (memoize! func-name) [syntax] Changes the given function binding to a memoized version. _Generic iteration and list comprehension_ ------------------------------------------ > (collect [dir] (var base expr) clause ...) [syntax] Sophisticated iteration syntax. The iteration is specified by the given clauses, where `var' serves as an accumulator variable that collects a value beginning with `base' and continuing with `expr' -- similar to a single binding in a `do' form with a variable, an initial value and an update expression. But there are much more iteration options than a `do' form: this form supports a generic list-comprehension and related constructs. Forms that use this construct are: > (loop-for clause ...) [syntax] Use when no value collection is needed, and the default for expressions is to do them instead of using them as a filter. Implemented as: (collect => (acc (void) acc) do clause ...) > (list-of expr clause ...) [syntax] Implemented as: (reverse! (collect (acc '() (cons expr acc)) clause ...)) > (sum-of expr clause ...) [syntax] Implemented as: (collect (acc 0 (+ expr acc)) clause ...) > (product-of expr clause ...) [syntax] Implemented as: (collect (acc 1 (* expr acc)) clause ...) > (count-of clause ...) [syntax] Only count matching cases, implemented as: (sum-of 1 clause ...) Each clause is either: * (v <- ...): a binding generator clause; * (v <- ... and v <- ...): parallel generator clauses; * (v is is-expr): bind `v' to the result of `is-expr'; * while expr: a `while' keyword followed by an expression will abort the whole loop if that expression evaluates to #f; * until expr: an `until' keyword followed by an expression will abort the whole loop if that expression evaluates to a non-#f value; * when ...: filter by the following expressions -- if an expression evaluates to #f, stop processing this iteration (default for all macros except for `loop-for'); * unless ...: filter by the negation of the following expressions; * do ...: execute the following expressions, used for side effects (default for the `loop-for' macro); * expr: expression is used according to the current mode set by a `when', `unless', or `do', keyword that precedes it. The effect of this form is to iterate each generator variable according to generating `<-' clauses (see below for these) and parallel clauses, and evaluate the `expr' with each combination, which composes a result out of iteration-bound values and an accumulated result. Generation is done in a nested fashion, where the rightmost generator spin fastest. Parallel generators (specified with an infix `and') make all iterations happen simultaneously, ending as soon as the first one ends. An `is' clause is used for binding arbitrary variables, a `do' clause is used to execute code for general side-effects, and other clauses are used to filter results before continuing down the clause list. Each clause can use variables bound by previous clauses, and the `expr' can use all bound variables as well as the given accumulator variable. An optional first token can be used to specify the direction which is used to accumulate the result. It can be one of these two tokens: `<=': A "backward" collection, the default (similar to `foldl'); `=>': A "forward" collection (similar to `foldr'). The default "backward" direction works by generating an accumulator carrying loop, as in this code (this code is for demonstration, not what `collect' creates): (let loop ([x foo] [acc '()]) (if (done? x) acc (loop (next x) (cons (value x) acc)))) which is a common Scheme idiom for such operations. The problem is that this accumulation happens in reverse -- requiring reversing the final result (which is done by the `list-of' macro). A "forward" direction does a naive recursive loop: (let loop ([x foo]) (if (done? x) '() (cons (value x) (loop (next x))))) collecting values in the correct order, but the problem is that it keeps a computation context which makes memory consumption inefficient. The default style is usually preferred, since reversing a list is a cheap operation, but it is not possible when infinite lists (streams) are used since it is impossible to reverse them. In these cases, the "forward" style should be used, but the `expr' must take care not to evaluate the iteration "variable" immediately, using `delay' or a similar mechanism (this "variable" is not bound to a value but substituted with an expression (a symbol macro)). For example, here's a quick lazy list usage: => (defsubst (lcons x y) (delay (cons x y))) => (define (lcar s) (car (force s))) => (define (lcdr s) (cdr (force s))) => (define x (collect (_ '() (lcons x _)) (x <- 0 ..))) ; loops indefinitely => (define x (collect => (_ '() (lcons x _)) (x <- 0 ..))) => (lcar (lcdr (lcdr x))) 2 Note that the `loop-for' macro uses a "forward" direction, but this is only because it is slightly faster since it doesn't require an extra binding. [The direction can be changed for a single part by using a "<-!" keyword instead of "<-", but this is an experimental feature since I don't know if it's actually useful for anything. Do not try to mix this with the `while' and `until' keywords which are implemented differently based on the direction.] Generator forms are one of the following ("..", "then", "until", "while" are literal tokens), see below for what values are generated: * (v <- sequence): iterate `v' on values from `sequence'; * (v <- 1st [2nd] .. [last]): iterate on an enumerated range, including last element of range; * (v <- 1st [2nd] ..< last): iterate on an enumerated range, excluding last element of range; * (v <- 1st [2nd] .. while last): iterate on an enumerated range, excluding last element of range; * (v <- 1st [2nd] .. until last): iterate on an enumerated range, excluding last element of range; * (v <- x then next-e [{while|until} cond-e]): start with the `x' expression, continue with the `next-e' expression (which can use `v'), do this while/until `cond-e' is true if a condition is given; * (v <- x {while|until} cond-e): repeat using the `x' expression while/until `cond-e' is true; * (v <- func arg ...): applies `func' to `arg ...', the result is expected to be some "iterator value" which is used to do the iteration -- iteration values are created by `collect-iterator' and `collect-numerator', see below for their description and return values. * (v <- gen1 <- gen2 <- ...): generator clauses can have multiple parts specified by more `<-'s, all of them will run sequentially; * (v1 <- gen1 ... and v2 <- gen2 ...): finally, an infix `and' specifies parallel generators, binding several variables. Iteration is possible on one of the following sequence values: * list: iterate over the list's element; * vector: iterate over the vector's elements; * string: iterate over characters in the string; * integer n: iterate on values from 0 to n-1; * procedure f: - if f accepts zero arguments, begin with (f) and iterate by re-applying (f) over and over, so the only way to end this iteration is by returning `collect-final' (see below); - otherwise, if f accepts one argument, it is taken as a generator function: it is passed a one-argument procedure `yield' which can be used to suspend its execution returning the given value, and it will be continued when more values are required (see `function-iterator' below); * hash-table: iterate over key-value pairs -- this is done with a generator function: (lambda (yield) (hash-table-for-each seq (lambda (k v) (yield (cons k v))))) * other values: repeated infinitely. Note that iteration over non-lists is done efficiently, iterating over a vector `v' is better than iterating over `(vector->list v)'. Enumeration is used whenever a ".." token is used to specify a range. There are different enumeration types based on different input types, and all are modified by the token used: * "..": a normal inclusive range; * "..<": a range that does not include the last element; * ".. while": a range that continues while a predicate is true; * ".. until": a range that continues until a predicate is true. The "..<" token extends to predicates in the expected way: the element that satisfies the predicate is the last one and it is not included in the enumeration -- unlike "..". These are the possible types that can be used with an enumeration: * num1 [num2] .. [num3]: go from num1 to num3 in num3 in num2-num1 steps, if num2 is not given then use +1/-1 steps, if num3 is not given don't stop; * num1 [num2] .. pred: go from num1 by num2-num1 steps (defaults to 1), up to the number that satisfies the given predicate; * char1 [char2] .. [char3/pred]: the same as with numbers, but on character ranges; * func .. [pred/x]: use `func' the same way as in an iterator above, use `pred' to identify the last element, if `pred' is omitted repeat indefinitely; * fst [next] .. [pred]: start with `fst', continue by repeated applications of the `next' function on it, and use `pred' to identify the last element, if `pred' is omitted repeat indefinitely, if `next' is omitted repeat `fst', and if both `fst' and `next' are numbers or characters then use their difference for stepping. (Note that to repeat a function value you should use `identity' as for `next' or the function will be used as described above.) Here is a long list of examples for clarification, all using `list-of', but the generalization should be obvious: => (list-of x [x <- '(1 2 3)]) (1 2 3) => (list-of (list x y) [x <- '(1 2 3)] [y <- 1 .. 2]) ((1 1) (1 2) (2 1) (2 2) (3 1) (3 2)) => (list-of (format "~a~a~a" x y z) [x <- '(1 2)] [y <- #(a b)] [z <- "xy"]) ("1ax" "1ay" "1bx" "1by" "2ax" "2ay" "2bx" "2by") => (list-of (+ x y) [x <- '(1 2 3)] [y <- 20 40 .. 100]) (21 41 61 81 101 22 42 62 82 102 23 43 63 83 103) => (list-of (+ x y) [x <- '(1 2 3) and y <- 20 40 .. 100]) (21 42 63) => (list-of y [x <- 0 .. and y <- '(a b c d e f g h i)] (even? x)) (a c e g i) => (list-of y [x <- 0 .. and y <- '(a b c d e f g h i)] when (even? x) do (echo y)) a c e g i (a c e g i) => (list-of (list x y) [x <- 3 and y <- 'x]) ((0 x) (1 x) (2 x)) => (list-of (list x y) [x <- 3 and y <- 'x ..]) ((0 x) (1 x) (2 x)) => (list-of (list x y) [x <- #\0 .. and y <- '(a b c d)]) ((#\0 a) (#\1 b) (#\2 c) (#\3 d)) => (list-of x [x <- '(1 2 3) then (cdr x) until (null? x)]) ((1 2 3) (2 3) (3)) => (list-of (list x y) [x <- '(1 2 3) then (cdr y) until (null? x) and y <- '(10 20 30) then (cdr x) until (null? y)]) (((1 2 3) (10 20 30)) ((20 30) (2 3)) ((3) (30))) => (list-of x [x <- (lambda (yield) 42)]) () => (list-of x [x <- (lambda (yield) (yield 42))]) (42) => (list-of x [x <- (lambda (yield) (yield (yield 42)))]) (42 42) => (list-of x [x <- (lambda (yield) (for-each (lambda (x) (echo x) (yield x)) '(3 2 1 0)))]) 3 2 1 0 (3 2 1 0) => (list-of x [x <- (lambda (yield) (for-each (lambda (x) (echo x) (yield (/ x))) '(3 2 1 0)))]) 3 2 1 0 /: division by zero => (list-of x [c <- 3 and x <- (lambda (yield) (for-each (lambda (x) (echo x) (yield (/ x))) '(3 2 1 0)))]) 3 2 1 (1/3 1/2 1) => (define h (make-hash-table)) => (set! (hash-table-get h 'x) 1 (hash-table-get h 'y) 2 (hash-table-get h 'z) 3) => (list-of x [x <- h]) ((y . 2) (z . 3) (x . 1)) => (list-of x [x <- 4 <- 4 .. 0 <- '(1 2 3)]) (0 1 2 3 4 3 2 1 0 1 2 3) => (list-of (list x y) [x <- 1 .. 3 <- '(a b c) and y <- (lambda (y) (y 'x) (y 'y)) <- "abcd"]) ((1 x) (2 y) (3 #\a) (a #\b) (b #\c) (c #\d)) Note that parallel iteration is useful both for enumerating results, and for walking over a finite prefix of an infinite iteration. The following is an extensive list of various ranges: => (list-of x [x <- 0 .. 6]) (0 1 2 3 4 5 6) => (list-of x [x <- 0 ..< 6]) (0 1 2 3 4 5) => (list-of x [x <- 0 .. -6]) (0 -1 -2 -3 -4 -5 -6) => (list-of x [x <- 0 ..< -6]) (0 -1 -2 -3 -4 -5) => (list-of x [x <- 0 2 .. 6]) (0 2 4 6) => (list-of x [x <- 0 2 ..< 6]) (0 2 4) => (list-of x [x <- 0 -2 ..< -6]) (0 -2 -4) => (list-of x [x <- #\a .. #\g]) (#\a #\b #\c #\d #\e #\f #\g) => (list-of x [x <- #\a ..< #\g]) (#\a #\b #\c #\d #\e #\f) => (list-of x [x <- #\a #\c .. #\g]) (#\a #\c #\e #\g) => (list-of x [x <- #\a #\c ..< #\g]) (#\a #\c #\e) => (list-of x [x <- #\g #\e ..< #\a]) (#\g #\e #\c) => (list-of x [x <- 6 5 .. zero?]) (6 5 4 3 2 1 0) => (list-of x [x <- 6 5 ..< zero?]) (6 5 4 3 2 1) => (list-of x [x <- 6 5 .. until zero?]) (6 5 4 3 2 1) => (list-of x [x <- 6 5 .. while positive?]) (6 5 4 3 2 1) => (list-of x [x <- '(1 2 3) cdr .. null?]) ((1 2 3) (2 3) (3) ()) => (list-of x [x <- '(1 2 3) cdr ..< null?]) ((1 2 3) (2 3) (3)) => (list-of x [x <- '(1 2 3) cdr .. until null?]) ((1 2 3) (2 3) (3)) => (list-of x [x <- '(1 2 3) cdr .. while pair?]) ((1 2 3) (2 3) (3)) => (list-of x [x <- #\a #\d .. while char-alphabetic?]) (#\a #\d #\g #\j #\m #\p #\s #\v #\y) => (list-of x [x <- #\a #\d .. char-alphabetic?]) (#\a) => (list-of x [x <- #\a #\d ..< char-alphabetic?]) () => (list-of x [x <- 0 1 .. positive?]) (0 1) => (list-of x [x <- 1 2 .. positive?]) (1) => (list-of x [x <- 1 2 ..< positive?]) () => (list-of x [x <- '(a b c) ..< pair?]) () => (list-of x [x <- '(a b c) .. pair?]) ((a b c)) => (list-of x [x <- '(a b c) cdr .. pair?]) ((a b c)) => (list-of x [x <- read-line .. eof-object?]) ...list of remaining input lines, including #... => (list-of x [x <- read-line ..< eof-object?]) ...list of remaining input lines, excluding #... => (list-of x [x <- read-line ..< eof]) ...the same... > collect-final [value] This value can be used to terminate iterations: when it is returned as the iteration value (not the state), the iteration will terminate without using it. > (function-iterator f [final-value]) [procedure] `f' is expected to be a function that can accept a single input value. It is applied on a `yield' function that can be used to return a value at any point. The return value is a function of no argument, which returns on every application values that were passed to `yield'. When `f' terminates, the final result of the iterated return value depends on the optional argument -- if none was supplied, the actual return value is returned, if a thunk was supplied it is applied for a return value, and if any other value was given it is returned. After termination, calling the iterated function again results in an error. (The supplied `yield' function returns its supplied value to the calling context when resumed.) => (define (foo yield) (yield 1) (yield 2) (yield 3)) => (define bar (function-iterator foo)) => (list (bar) (bar) (bar)) (1 2 3) => (bar) 3 => (bar) function-iterator: iterated function # exhausted. => (define bar (function-iterator foo 'done)) => (list (bar) (bar) (bar) (bar)) (1 2 3 done) => (bar) function-iterator: iterated function # exhausted. => (define bar (function-iterator foo (thunk (error 'foo "done")))) => (list (bar) (bar) (bar)) (1 2 3) => (bar) foo: done > (collect-iterator sequence) [procedure] > (collect-numerator from second to [flag]) [procedure] These functions are used to construct iterations. `collect-iterator' is the function used to create iteration over a sequence object and it is used by `(x <- sequence)' forms of `collect'. `collect-numerator' create range iterations specified with `(x <- from second to)' forms, where unspecified values are passed as `#f', and the flag argument is a `<', `while', or `until' symbol for ranges specified with "..<", ".. while" and ".. until". These functions are available for implementing new iteration constructs, for example: => (define (in-values producer) (collect-iterator (call-with-values producer list))) => (list-of x [x <- in-values (thunk (values 1 2 3))]) (1 2 3) The return value that specifies an iteration is a list of four items: 1. the initial state value; 2. a `step' function that gets a state and returns the next one; 3. a predicate for the end state (#f for none); 4. a function that computes a value from the state variable. But usually the functions are more convenient. Finally, remember that you can return `collect-final' as the value to terminate any iteration. _Convenient printing_ --------------------- > (echo arg ...) [syntax] This is a handy printout utility that offers an alternative approach to `printf'-like output (it's a syntax, but it can be used as a regular function too, see below). When applied, it simply prints its arguments one by one, using certain keywords to control its behavior: * :>e - output on the current-error-port; * :>o - output on the current-output-port (default); * :>s - accumulate output in a string which is the return value (string output sets `:n-' as default (unless pre-specified)); * :> p - output on the given port `p', or a string if `#f'; * :>> o - use `o', a procedure that gets a value and a port, as the output handler (the procedure can take one value and display it on the current output port); * :d - use `display' output (default); * :w - use `write' output; * :d1 :w1 - change to a `display' or `write' output just for the next argument; * :s- - no spaces between arguments; * :s+ - add spaces between arguments (default); * :n- - do not print a final newline; * :n+ - terminate the output with a newline (default); * :n - output a newline now; * : or :: - avoid a space at this point; * :\{ - begin a list construct (see below). Keywords that require additional argument are ignored if no argument is given. Recursive processing of a list begins with a `:\{' and ends with a `:\}' (which can be simpler if `read-curly-brace-as-paren' is off). Inside a list context, values are inspected and any lists cause iteration for all elements. In each iteration, all non-list arguments are treated normally, but lists are dissected and a single element is printed in each step, terminating when the shortest list ends (and repeating a last `dotted' element of a list): => (define abc '(a b c)) => (echo :\{ "X" abc :\}) X a X b X c => (echo :\{ "X" abc '(1 2 3 4) :\}) X a 1 X b 2 X c 3 => (echo :\{ "X" abc '(1 . 2) :\}) X a 1 X b 2 X c 2 Inside a list context, the `:^' keyword can be used to stop this iteration if it is the last: => (echo :s- :\{ abc :^ ", " :\}) a, b, c Nesting of lists is also simple, following these simple rules, by nesting the `:\{' ... `:\}' construct: => (echo :s- :\{ "<" :\{ '((1 2) (3 4 5) 6 ()) :^ "," :\} ">" :^ "-" :\}) <1,2>-<3,4,5>-<6>-<> Note that this example is similar to the CL `format': (format t "~{<~{~a~^,~}>~^-~}" '((1 2) (3 4 5) 6 ())) except that `echo' treats a dotted element (a non-list in this case) as repeating as needed. There are two additional special keywords that are needed only in uncommon situations: * :k- - turn off keyword processing * :k+ - turn keyword processing on Usually, when `echo' is used, it is processed by a macro that detects all keywords, even if there is a locally bound variable with a keyword name. This means that keywords are only ones that are syntactically so, not expressions that evaluate to keywords. The two cases where this matters are -- when `echo' is used for its value (using it as a value, not in a head position) no processing is done so all keywords will just get printed; and when `echo' is used in a context where a variable has a keyword name and you want to use its value (which not a great idea anyway, so there is no way around it). The first case is probably more common, so the variable `echo:' is bound to a special value that will force treating the next value as a keyword (if it evaluates to one) -- it can also be used to turn keyword processing on (which means that all keyword values will have an effect). Here is a likely examples where `echo:' should be used: => (define (echo-values vals) (apply echo "The given values are:" echo: :w vals)) => (echo-values '("a" "b" "c")) The given values are: "a" "b" "c" => (echo-values '(:a :b :c)) The given values are: :a :b :c And here are some tricky examples: => (echo :>s 2) "2" => (define e echo) ; `e' is the real `echo' function => (e :>s 2) ; no processing done here :>s 2 => (e echo: :>s 2) ; explicit key "2" => (e echo: :k+ :>s 2) ; turn on keywords "2" => (let ([:>s 1]) (echo :>s 2)) ; `:>s' was processed by `echo' "2" => (let ([:>s 1]) (e :>s 2)) ; `:>s' was not processed 1 2 => (let ([:>s 1]) (e echo: :>s 2)) ; `:>s' is not a keyword here! 1 2 => (let ([:>s 1]) (echo echo: :>s 2)) ; `echo:' not needed "2" Finally, it is possible to introduce new keywords to `echo'. This is done by calling it with the `:set-user' keyword, which expects a keyword to attach a handler to, and the handler itself. The handler can be a simple value or a keyword that will be used instead: => (echo :set-user :foo "foo") => (echo 1 :foo 2) 1 foo 2 => (echo :set-user :foo :n) => (echo 1 :foo 2) 1 2 The `:set-user' keyword can appear with other arguments, it has a global effect in any case: => (echo 1 :foo :set-user :foo "FOO" 2 :foo 3 :set-user :foo "bar" :foo 4) 1 2 FOO 3 bar 4 => (echo 1 :foo 2) 1 bar 2 If the handler is a function, then when this keyword is used, the function is applied on arguments pulled from the remaining `echo' arguments that follow (if the function can get any number of arguments, then all remaining arguments are taken). The function can work in two ways: (1) when it is called, the `current-output-port' will be the one that `echo' currently prints to, so it can just print stuff; (2) if the function returns a list (or a single value which is not `#f' or `void'), then these values will be used instead of the taken arguments. Some examples: => (echo :set-user :foo (thunk "FOO") 1 :foo 2) 1 FOO 2 => (echo :set-user :add1 add1 1 :add1 2) 1 3 => (echo :set-user :+1 (lambda (n) (list n '+1= (add1 n))) :+1 2) 2 +1= 3 => (echo :set-user :<> (lambda args (append '("<") args '(">"))) :<> 1 2 3) < 1 2 3 > Care should be taken when user keywords are supposed to handle other keywords -- the `echo:' tag will usually be among the arguments except when `:k+' was used and an argument value was received. This exposes the keyword treatment hack and might change in the future. To allow user handlers to change settings temporarily, there are `:push' and `:pop' keywords that will save and restore the current state (space and newline flags, output type and port etc). For example: => (echo :set-user :@ (lambda (l) (echo-quote list :push :s- :\{ "\"" l "\"" :^ ", " :\} :pop))) => (echo 1 :@ '(2 3 4) 5) 1 "2", "3", "4" 5 The above example shows another helper tool -- the `echo-quote' syntax: `(echo-quote head arg ...)' will transform into `(head ...)', where keyword arguments are prefix with the `echo:' tag. Without it, things would look much worse. In addition to `:set-user' there is an `:unset-user' keyword which cancels a keyword handler. Note that built-in keywords cannot be overridden or unset. > (echos arg ...) [syntax] Just uses `echo' with `:>s'. > echo: [value] See the `echo' description for usage of this value. > (named-lambda name args body ...) [syntax] Like `lambda', but the name is bound to itself in the body. > (thunk body ...) [syntax] Returns a procedure of no arguments that will have the given body. > (while condition body ...) [syntax] > (until condition body ...) [syntax] Simple looping constructs. > (dotimes (i n) body ...) [syntax] Loop `n' times, evaluating the body when `i' is bound to 0,1,...,n-1. > (dolist (x list) body ...) [syntax] Loop with `x' bound to elements of `list'. > (no-errors body ...) [syntax] Execute body, catching all errors and returning `#f' if one occurred. > (no-errors* body ...) [syntax] Execute body, catching all errors and returnsthe exception if one occured. > (regexp-case string clause ...) [syntax] Try to match the given `string' against several regexps. Each clause has one of the following forms: * (re => function): if `string' matches `re', apply `function' on the result list. * ((re args ...) body ...): if `string' matches `re', bind the tail of results (i.e, excluding the whole match result) to the given arguments and evaluate the body. The whole match result (the first element of `regexp-match') is bound to `match'. * (re body ...): if `string' matches `re', evaluate the body -- no match results are available. * (else body ...): should be the last clause which is evaluated if all previous cases failed. _Sorting_ --------- The following section defines functions for sorting. They are taken directly from slib since they are more convenient and faster than the functions in mzlib/list. See the source for more details. > (sorted? sequence less?) [procedure] True when `sequence' is a list (x0 x1 ... xm) or a vector #(x0 ... xm) such that its elements are sorted according to `less?': (not (less? (list-ref list i) (list-ref list (- i 1)))). > (merge a b less?) [procedure] Takes two lists `a' and `b' such that both (sorted? a less?) and (sorted? b less?) are true, and returns a new list in which the elements of `a' and `b' have been stably interleaved so that (sorted? (merge a b less?) less?) is true. Note: this does not accept vectors. > (merge! a b less?) [procedure] Takes two sorted lists `a' and `b' and smashes their cdr fields to form a single sorted list including the elements of both. Note: this does not accept vectors. > (sort! sequence less?) [procedure] Sorts the list or vector `sequence' destructively. > (sort sequence less?) [procedure] Sorts a vector or list non-destructively. It does this by sorting a copy of the sequence. ------------------------------------------------------------------------ _turbo_ _turbo.ss_ ------------------------------------------------------------------------ This module combines the `base', `setf', and `misc', modules to create a new language module. Use this module to get most of Swindle's functionality which is unrelated to the object system. This module exports bindings from: `mzlib/setf', `mzlib/base', `mzlib/misc'. It is intended to be used as a language module (as an initial-import for other modules). > (set! place value ...) [syntax] > (pset! place value ...) [syntax] > (set!-values (place ...) expr) [syntax] This module renames `setf!', `psetf!', and `setf!-values' from the `setf' module as `set!', `pset!' and `set!-values' so the built-in `set!' and `set!-values' syntaxes are overridden. > #%module-begin [syntax] `turbo' is a language module -- it redefines `#%module-begin' to load itself for syntax definitions. ------------------------------------------------------------------------ _tiny-clos_ _tiny-clos.ss_ ------------------------------------------------------------------------ This module is the core object system. It is a heavily hacked version of the original Tiny-CLOS code from Xerox, but it has been fitted to MzScheme, optimized and extended. See the source file for a lot of details about how the CLOS magic is created. [There is one difference between Swindle and Tiny-CLOS: the meta object hierarchy is assumed to be using only single inheritance, or if there is multiple inheritance then the built in meta objects should come first to make the slots allocated in the same place. This should not be a problem in realistic situations.] > ??? [value] This is MzScheme's `unspecified' value which is used as the default value for unbound slots. It is provided so you can check if a slot is unbound. *** Low level functionality (These functions should be used with caution, since they make shooting legs in exotic ways extremely easy.) > (change-class! object new-class initargs ...) [procedure] This operation changes the class of the given `object' to the given `new-class'. The way this is done is by creating a fresh instance of `new-class', then copying all slot values from `object' to the new instance for all shared slot names. Finally, the new instance's set of slots is used for the original object with the new class, so it preserves its identity. > (set-instance-proc! object proc) [syntax] This function sets the procedure of an entity object. It is useful only for making new entity classes. *** Basic functionality > (instance? x) [procedure] > (object? x) [procedure] These two are synonyms: a predicate that returns #t for objects that are allocated and managed by Swindle. > (class-of x) [procedure] Return the class object of `x'. This will either be a Swindle class for objects, or a built-in class for other Scheme values. > (slot-ref obj slot) [procedure] Pull out the contents of the slot named `slot' in the given `obj'. Note that slot names are usually symbols, but can be other values as well. > (slot-set! obj slot new) [procedure] Change the contents of the `slot' slot of `obj' to the given `new' value. > (set-slot-ref! obj slot new) [procedure] An alias for `slot-set!', to enable using `setf!' on it. > (slot-bound? object slot) [procedure] Checks if the given `slot' is bound in `object'. See also `???' above. _Singleton and Struct Specifiers_ --------------------------------- > (singleton x) [procedure] Returns a singleton specification. Singletons can be used as type specifications that have only one element in them so you can specialize methods on unique objects. This is actually just a list with the symbol `singleton' in its head and the value, but this function uses a hash table to always return the same object for the same value. For example: => (singleton 1) (singleton 1) => (eq? (singleton 1) (singleton 1)) #t but if the input objects are not `eq?', the result isn't either: => (eq? (singleton "1") (singleton "1")) #f Only `eq?' is used to compare objects. > (singleton? x) [procedure] Determines if something is a singleton specification (which is any list with a head containing the symbol `singleton'). > (singleton-value x) [procedure] Pulls out the value of a singleton specification. Also note that MzScheme struct types are converted to appropriate Swindle classes. This way, it is possible to have Swindle generic functions that work with struct type specializers. > (struct-type->class struct-type) [procedure] This function is used to convert a struct-type to a corresponding Swindle subclass of `'. See the MzScheme manual for details on struct types. *** Common accessors > (class-direct-slots class) [procedure] > (class-direct-supers class) [procedure] > (class-slots class) [procedure] > (class-cpl class) [procedure] > (class-name class) [procedure] > (class-initializers class) [procedure] Accessors for class objects (look better than using `slot-ref'). > (generic-methods generic) [procedure] > (generic-arity generic) [procedure] > (generic-name generic) [procedure] > (generic-combination generic) [procedure] Accessors for generic function objects. > (method-specializers method) [procedure] > (method-procedure method) [procedure] > (method-qualifier method) [procedure] > (method-name method) [procedure] > (method-arity method) [procedure] Accessors for method objects. `method-arity' is not really an accessor, it is deduced from the arity of the procedure (minus one for the `call-next-method' argument). *** Basic classes > [class] This is the "mother of all classes": every Swindle class is an instance of `'. Slots: * direct-supers: direct superclasses * direct-slots: direct slots, each a list of a name and options * cpl: class precedence list (classes list this to ) * slots: all slots (like direct slots) * nfields: number of fields * field-initializers: a list of functions to initialize slots * getters-n-setters: an alist of slot-names, getters, and setters * name: class name (usually the defined identifier) * initializers: procedure list that perform additional initializing See the `clos' documentation for available class and slot keyword arguments and their effect. Instance of `', subclass of `'. > [class] This is the "mother of all values": every value is an instance of `' (including standard Scheme values). Instance of `'. > [class] This is the "mother of all objects": every Swindle object is an instance of `'. Instance of `', subclass of `'. > [class] The class of all procedures classes, both standard Scheme procedures classes and entity (Swindle procedure objects) classes. (Note that this is a class of *classes*). Instance of `', subclass of `'. > [class] The class of entity classes -- generic functions and methods. An entity is a procedural Swindle object, something that you can apply as a function but it is still a Swindle object. Note that this is the class of entity *classes* not of entities themselves. Instance of `', subclass of `'. > [class] The class of all applicable values: methods, generic functions, and standard closures. Instance of `', subclass of `'. > [class] The class of generic functions: objects that contain method objects and calls the appropriate ones when applied. Slots: * methods: a list of objects * arity: the generic arity (same for all of its methods) * name: generic name * combination: a method combination function or #f, see `make-generic-combination' below for details Instance of `', subclass of `', `'. > [class] The class of methods: objects that are similar to Scheme closures, except that they have type specifiers attached. Note that in contrast to Tiny CLOS, methods are applicable objects in Swindle -- they check supplied argument types when applied. Slots: * specializers: a list of class (and singleton) specializers * procedure: the function (never call directly!) * qualifier: some qualifier tag, used when applying a generic * name: method name Instance of `', subclass of `', `'. *** Convenience functions These are some convenience functions -- no new syntax, just function wrappers for `make' with some class and some slot values. See `clos' for a more sophisticated (and convenient) approach. > (make-class direct-supers direct slots) [procedure] Creates a class object -- an instance of . > (make-generic-function [name/arity]) [procedure] Creates a generic function object -- an instance of . The argument can specify name and/or arguments number. > (make-method specializers procedure) [procedure] Creates a method object -- an instance of , using the given specializer list and procedure. The procedure should have a first argument which is being used to access a `call-next-method' call. > (no-next-method generic method [args ...]) [generic] > (no-applicable-method generic [args ...]) [generic] These two generic functions are equivalents to the ones in CL. The first one is applied on a generic and a method in case there was no next method and `call-next-method' was used. The second is used when a generic was called but no matching primary methods were found. The only difference is that in Swindle methods can be applied directly, and if `call-next-method' is used, then `no-next-method' gets `#f' for the generic argument. _Generics in the instance initialization protocol_ -------------------------------------------------- The following generic functions are used as part of the protocol of instantiating an instance, and some are used specifically to instantiate class objects. > (allocate-instance class) [generic] This generic function is called to allocate an instance of a class. It is applied on the class object, and is expected to return the new instance object of that class. > (initialize instance initargs) [generic] This generic is called to initialize an instance. It is applied on the newly allocated object and the given initargs, and is not expected to return any meaningful value -- only do some side effects on the instance to initialize it. When overriding this for a some class, it is not a good idea to skip `call-next-method' since it is responsible for initializing slot values. > (compute-getter-and-setter class slot allocator) [generic] This generic is used to get a getter and setter functions for a given slot. It is passed the class object, the slot information (a list of a slot name and options), and an allocator function. The allocator is a function that gets an initializer function and returns an index position for the new slot. The return value should be a list of two elements -- a getter and a setter functions. > (compute-cpl class) [generic] This generic is used to get the class-precedence-list for a class object. The standard object uses the `compute-std-cpl' (see in the code) which flattens the class ancestors using a topological sort that resolve ambiguities left-to-right. > (compute-slots class) [generic] This generic is used to compute all slot information for a given class, after its precedence list has been computed. The standard collects information from all preceding classes. > (compute-apply-method method) [generic] This generic is used to compute the procedure that will get executed when a method is applied directly. _Generics in the generic invocation protocol_ --------------------------------------------- These generics are used for invocation of generic functions. See the code to see how this circularity is achieved. > ((compute-apply-generic generic) args ...) [generic] This generic is used to compute the object (a closure) that is actually applied to execute the generic call. The standard version uses `compute-method' and `compute-apply-methods' below, and caches the result. > (compute-methods generic args) [generic] Computes the methods that should be applied for this generic invocation with args. The standard code filters applicable methods and sorts them according to their specificness. The return value is expected to depend only on the types of the arguments (and values if there are singleton specializers). > ((compute-method-more-specific? generic) mthd1 mthd2 args) [generic] Get a generic and return a function that gets two methods and a list of arguments and decide which of the two methods is more specific. This decision should only be based on the argument types, or values only in case of singletons. > ((compute-apply-methods generic methods) args ...) [generic] Gets a generic and returns a function that gets the given arguments for this call. This function which it returns is the combination of all given methods. The standard one arranges them by default using the `call-next-method' argument that methods have. Swindle extends this with qualified methods and applies `before', `after', and `around' methods in a similar way to CLOS: first the `around' methods are applied (and they usually call their `call-next-method' to continue but can return a different value), then all the `before' methods are applied (with no `call-next-method'), then all `primary' methods as usual (remembering the return value), and finally the `after' methods (similar to the `before', but in reverse specificness order). If the generic has a `combination' slot value, then it is a procedure that is used to combine the primary methods, but the auxiliary ones are still applied in the same way. This is unlike CLOS where the standard combinations run only `around' methods, and there is generally more control with method combinations, but in Swindle `compute-apply-methods' should be overridden for this. See `make-generic-combination' for details about method combinations. > (add-method generic method) [generic] This generic function is called to add a method to a generic function object. This is an other change from the original Tiny CLOS where it was a normal function. > (((make-generic-combination keys...) generic) tail args) [procedure] This function can be used to construct simple method combinations that can be used with the `combination' slot of generic functions. The combination itself is a function that gets a generic and returns a function that gets a list of method/procedure pairs (for optimization the method-procedures are pre taken) and the arguments and performs the call -- but this is only interesting if there's any need to implement a method combination directly, otherwise, the `make-generic-combination' interface should allow enough freedom. Note that when a method combination is used, `around', `before', and `after' are called around the primary call as usual, but the primaries are never called with a valid `call-next-method' argument. The keyword arguments that can be taken determine the behavior of this combination. Overall, it is roughly like a customizable version of a fold operation on the method calls. * :init - The initial value for this computation. Defaults to null. * :combine - A function to be called on a method call result and the old value, and produces a new value. The default is `cons', which with an initial null value will collect the results into a reversed list. * :process-methods - A function that can be called on the initial list of method/procedure pairs to change it -- for example, it can be reversed to apply the methods from the least specific to the most specific. No default. * :process-result - A function that can be called on the final resulting value to produce the actual return value. For example, it can reverse back a list of accumulated values. No default. * :control - If this parameter is specified, then the `:combine' argument is ignored. The value given to `:control' should be a function of four arguments: 1. a `loop' function that should be called on some new value and some new tail; 2. a `val' argument that gets the current accumulated value; 3. a `this' thunk that can be called to apply the current method and return its result; 4. a `tail' value that holds the rest of the method/procedure list which can be sent to `loop'. It should be clear now, that a `:control' argument can have a lot of control on the computation, it can abort, change arbitrary values and skip calling methods. Note that if it won't call `loop' with an empty list, then a `:process-result' function will not be used as well. See the pre-defined combinations in the source code to see examples of using this function. > generic-+-combination [procedure] > generic-list-combination [procedure] > generic-min-combination [procedure] > generic-max-combination [procedure] > generic-append-combination [procedure] > generic-append!-combination [procedure] > generic-begin-combination [procedure] > generic-and-combination [procedure] > generic-or-combination [procedure] These are all functions that can be used as a `combination' value for a generic function. They work in the same way as the standard method combinations of CL. Most of them do the obvious thing based on some function to combine the result. The `begin' combination simply executes all methods one by one and returns the last value, the `and' and `or' combinations will call them one by one until a false or true result is returned. The source of these can be used as templates for defining more combinations. *** More class functionality (In the following, a `class' can be a class, a singleton specifier, or a struct type.) > (subclass? class1 class2) [procedure] Is `class1' a subclass of `class2'? > (instance-of? x class) [procedure] Checks if `x' is an instance of `class' (or one of its subclasses). > (class? x) [procedure] Determines whether `x' is a class. > (specializer? x) [procedure] Determines whether `x' is a class, a singleton, or a struct-type. > (more-specific? class1 class2 x) [procedure] Is `class1' more specific than `class2' for the given value? _Swindle Customization Parameters_ ---------------------------------- > *default-method-class* [parameter] > *default-generic-class* [parameter] > *default-class-class* [parameter] > *default-entityclass-class* [parameter] These parameters specify default classes for the many constructor macros in `clos'. > *default-object-class* [parameter] This parameter contains a value which is automatically made a superclass for all classes. Defaults to `'. > *make-safely* [parameter] Setting this parameter to #t will make Swindle perform sanity checks on given initargs for creating an object. This will make things easier for debugging, but also slower. Defaults to `#f'. Note that the sanity checks are done in `initialize'. _Creating Instances_ -------------------- > (make class initargs ...) [generic] Create an instance of `class', which can be any Swindle class (except for some special top-level classes and built-in classes). See the `Object Initialization Protocol' below for a description of generic functions that are involved in creating a Swindle object. > (rec-make (name class arg ...) ...) [syntax] This is similar to: (letrec ([name (make class arg ...)] ...) (values name ...)) except that the names are first bound to allocated instances with no initargs, and then they are initialized with all these bindings. This is useful for situations where creating some instances needs other instances as values. One sample usage is the way `defclass' makes the class binding available for slot specifications like `:type'. Note that this is a special form, which invokes `allocate-instance' and `initialize' directly, so specializing `make' on some input will not change the way `rec-make' works. _Built-in Classes_ ------------------ > [class] The class of all built-on classes. Instance of `', subclass of `'. > [class] The superclass of all built-in classes. Instance of `', subclass of `'. > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] > [class] These classes represent built-in objects. See the class hierarchy below for a complete description of the relations between these classes. > [class] > [class] These are also classes for built-in objects, but they are classes for MzScheme structs -- which can be used like Swindle classes since they will get converted to appropriate Swindle subclasses of `'. `' is a class of structs that are hidden -- see the documentation for `struct-info' and the `skipped?' result. Note that structs can be used as long as they can be inspected -- otherwise, we can't even know that they are structs with `struct?' (this means that can only appear in the cpl of a struct class that inherits from a struct which is not under the current inspector). > [class] The class of all Scheme procedures. Instance of `', subclass of `', `'. > [class] The class of all primitive MzScheme procedures. Instance of `', subclass of `'. > (builtin? x) [procedure] > (function? x) [procedure] > (generic? x) [procedure] > (method? x) [procedure] Predicates for instances of , , , and . _Class Hierarchy_ ----------------- In the following, every class's class is specified after a colon. Also, some classes appear in more than once place due to multiple-inheritance. : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : : ... struct type classes ... _Object Initialization Protocol_ -------------------------------- This is the initialization protocol. All of these are generic functions (unlike the original Tiny CLOS). See the individual descriptions above for more details. make allocate-instance initialize class initialization only: compute-cpl compute-slots compute-getter-and-setter method initialization only: compute-apply-method add-method compute-apply-generic compute-methods compute-method-more-specific? compute-apply-methods ------------------------------------------------------------------------ _clos_ _clos.ss_ ------------------------------------------------------------------------ This module contains only syntax definitions, which makes Swindle closer to CLOS -- making the object system much more convenient to use. This module exports bindings from: `mzlib/tiny-clos'. _Generic macros_ ---------------- > (generic) [syntax] | (generic name initargs ...) | (generic name (arg ...) initargs ...) Create a generic function object (an instance of the `*default-generic-class*' parameter). The first form uses the default name given by the syntactical context, the second one gets an explicit name and the third also gets a list of arguments which is used to count the required number of arguments. If there is no argument list to count, the first method that gets added will set this number. The two last forms allow initargs to be passed to the instance creation, for example, to specify a `:combination' argument. (The first form does not allow keywords, since a keyword would be taken as the name.) > (defgeneric name (arg ...) initargs ...) [syntax] | (defgeneric (name arg ...) initargs ...) | (defgeneric name initargs ...) This form defines a generic function using the `generic' syntax given above. The last form doesn't specify a number of arguments. Some extra `initargs' can be specified too but they are needed mainly for a `:combination' argument. _Method macros_ --------------- > (call-next-method [args ...]) [local] > (next-method?) [local] These are bindings which are available only in method bodies. `call-next-method' will invoke the next method in a generic invocation sequence if any. If arguments are given to `call-next-method', it will change the arguments for the next method -- but this is done when the methods are already filtered and sorted, so the new arguments should always be consistent with the old types. If there are no methods left, or when calling a method directly, or when a before or after method is used, the `no-next-method' generic will be used -- normally resulting in an error. `next-method?' returns `#t' if there is another method ready to be called. > (method (arg ...) body ...) [syntax] > (named-method name (arg ...) body ...) [syntax] > (qualified-method qualifier (arg ...) body ...) [syntax] These forms are all similar variants to create a method object (and instance of the `*default-method-class*' parameter). A method looks very similar to a lambda expression, except that the an argument can be a of the form `[arg spec]' where `spec' is a specializer -- either a class or a singleton specifier (the square brackets are equivalent to round parens, just make the code more readable). Also, an argument can have the form of `[arg = val]' which is shorthand for specifying `[arg (singleton val)]'. In case of a simple argument, is always used as a specializer, but this processing stops as soon as a &-keyword is encountered. The `named-method' form is used to provide an explicit name (which can be used to call itself recursively) , and `qualified-method' is used to provide an explicit qualifier (which should be one of the standard qualifiers (:primary, :around, :before, or :after) when using the standard and classes). The resulting method can be added to a generic and these specializers will be used when filtering applicable methods, or it can be used by itself and the specializers will be used to check the arguments. This makes it easy to use `method' instead of `lambda' to get some type information, but note that the result is going to run slower since the type check only takes time but cannot be used by MzScheme to optimize the code. Note that the specializer argument are evaluated normally, which means that anything can be used, even something like: (let ([x (list )]) (method ([x (2nd x)] [y = (+ 2 3)]) (+ x y))) > (-defmethod-create-generics- [#t/#f]) [syntax-parameter] This is a syntax parameter (see above) holding a boolean. When this is set to `#t' (the default), then the `defmethod' form below will try to detect when the first definition happens and automatic add a `defgeneric' form to define the object as a generic. A safer but less convenient approach would be to set this to `#f' and always do an explicit `defgeneric'. > (defmethod name [qualifier] (arg ...) body ...) [syntax] | (defmethod [qualifier] (name arg ...) body ...) This form is used to define a method object using `method' and its variants above. A qualifier (a :keyword) can be specified anywhere before the argument list, and the name can be either specified before the arguments (Lisp style) or with the arguments (Scheme style). Depending on `-defmethod-create-generics-' (see above), this form might add a `defgeneric' form to define the given `name' as a generic object, and then add the created method. The created method is attached to the generic in any case, which makes the name of this form a little misleading since it is not always defining a variable value. In a local definition context, this should do the right thing as long as `defmethod' or `defgeneric' is used to define the method (but note that using a local generic function, is very inefficient) -- for example, both of these work (defining a local generic): (define (f) (defgeneric foo) (defmethod (foo [x ]) 1) (defmethod (foo [x ]) 2) 3) (define (f) (defmethod (foo [x ]) 1) (defmethod (foo [x ]) 2) 3) but this fails because the first `defmethod' doesn't know that it is already defined: (define (f) (define foo (generic foo)) (defmethod (foo [x c1]) 1) (defmethod (foo [x c1]) 2) 3) second "but" -- this: (define (f) (define foo (generic foo)) blah (defmethod (foo [x ]) 1) (defmethod (foo [x ]) 2) 3) works because a `defmethod' in an expression context is always the same as `add-method'. > (beforemethod ...) [syntax] > (aftermethod ...) [syntax] > (aroundmethod ...) [syntax] > (defbeforemethod ...) [syntax] > (defaftermethod ...) [syntax] > (defaroundmethod ...) [syntax] These forms are shorthands that will generate a qualified method using one of the standard qualifiers. _Class macros_ -------------- > (class [name] (super ...) slot ... class-initarg ...) [syntax] Create a class object (an instance of the `*default-class-class*' parameter). An explicit name can optionally be specified explicitly. The list of superclasses are evaluated normally, so they can be any expression (as with the `method' forms). Each slot can be either a symbol, which will be used as the slot name, or a list that begins with a symbol and continues with a keyword-argument option list. Finally, more initargs for the class generation can be provided. See the `defclass' forms below for an explanation on the available slot option and class initargs. If a name is given, then `rec-make' is used, see that for a description. > (entityclass [name] (super) slot ... class-initarg ...) [syntax] Same as the `class' form, but creates an entity class object (an instance of the `*default-entityclass-class*' parameter). > (-defclass-auto-initargs- [#f/initargs]) [syntax-parameter] This is a syntax parameter (see above) holding either `#f' or an initargs list . If it is not `#f', `defclass' below will add its contents to the end of the given initargs (so user supplied arguments can override them). The default is `#f'. > (-defclass-autoaccessors-naming- [naming-keyword]) [syntax-parameter] This syntax parameter holds a keyword symbol that is used in the `defclass' for the `:autoaccessors' if it is specified as `#t' or if it used due to `:auto'. See the description of the `:autoaccessors' option below for possible values. The default is `:class-slot'. > (-defclass-accessor-mode- [mode-keyword]) [syntax-parameter] This syntax parameter holds a keyword symbol that is used in the `defclass' for the way accessors, readers, and writers are generated. It can be `:defmethod' for using `defmethod', `:defgeneric' for using `defgeneric' and then `add-method', `:add-method' for using `add-method', `:method' for defining an independent method, or `:procedure' for defining a simple Scheme procedure. The default is `:defmethod. This default is usually fine, but a situation where this is important is if the syntax parameter `-defmethod-create-generics-' is set to `#f' so a `defmethod' requires a prior `defgeneric' so a defclass will not work unless the generic functions are defined in advance. > (defclass name (super ...) slot ... class-initarg ...) [syntax] This form uses the `class' form above to define a new class. See the `class' form for the syntax. Note that slot-options that are not compile-time ones (method names) are accumulated according to the class precedence list. Available slot options are: * :initarg keyword Use `keyword' in `make' to provide a value for this slot. * :initializer func Use the given function to initialize the slot -- either a thunk or a function that will be applied on the initargs given to `make'. * :initvalue value Use `value' as the default for this slot. * :reader name Define `name' (an unquoted symbol) as a reader method for this slot. * :writer name Define `name' (an unquoted symbol) as a writer method for this slot. * :accessor name Define `name' (an unquoted symbol) as an accessor method for this slot -- this means that two methods are defined: `name' and `set-name!'. * :type type Restrict this slot value to objects of the given `type'. * :lock { #t | #f | value } If specified and non-`#f', then this slot is locked. `#t' locks it permanently, but a diffrent value works as a key: they allow setting the slot by using cons of the key and the value to set. * :allocation { :class | :instance } Specify that this slot is a normal one (`:instance', the default), or allocated per class (`:class'). The specific way of creating helper methods (for readers, writers, and accessors) is determined by `-defclass-accessor-mode-' (see above). Available class options (in addition to normal ones that initialize the class slots like `:name', `:direct-slots', `:direct-supers') are: * :metaclass class create a class object which is an instance of the `class' meta-class (this means that an instance of the given meta-class should be used for creating the new class). * :autoinitargs { #t | #f } if set to `#t', make the class definition automatically generate initarg keywords from the slot names. * :autoaccessors { #f | #t | :class-slot | :slot } if set to non-`#f', generate accessor methods automatically -- either using the classname "-" slotname convention (`:class-slot') or just the slotname (`:slot'). If it is `#t' (or turned on by `:auto') then the default naming style is taken from the `-defclass-autoaccessors-naming-' syntax parameter. Note that for this, and other external object definitions (`:automaker' and `:autopred'), the class name is stripped of a surrounding "<>"s if any. * :automaker { #f | #t } automatically creates a `maker' function using the "make-" classname naming convention. The maker function is applied on arguments and keyword-values -- if there are n slots, then arguments after the first n are passed to `make' to create the instance, then the first n are `slot-set!'ed into the n slots. This means that it can get any number of arguments, and usually there is no point in additional keyword values (since if they initialize slots, their values will get overridden anyway). It also means that the order of the arguments depend on the *complete* list of the class's slots (as given by `class-slots'), so use caution when doing multiple inheritance (actually, in that case it is probably better to avoid these makers anyway). * :autopred { #f | #t } automatically create a predicate function using the `classname "?"' naming convention. * :default-slot-options { #f | '(keyword ...) } if specified as a quoted list, then slot descriptions are modified so the first arguments are taken as values to the specified keywords. For example, if it is `'(:type :initvalue)' then a slot description can have a single argument for `:type' after the slot name, a second argument for `:initvalue', and the rest can be more standard keyword-values. This is best set with `-defclass-auto-initargs-' * :auto { #f | #t } if specified as `#t', then all automatic behavior available above is turned on. * :printer { #f | #t | procedure } if given, install a printer function. `#t' means install the `print-object-with-slots' function from "clos.ss", otherwise, it is expected to be a function that gets an object, an escape boolean flag an an optional port (i.e, 2 or more arguments), and prints the object on the class using the escape flag to select `display'-style (`#f') or `write'-style (#t). Note that the class object is made by `class' with a name, so it is possible to use the class itself as the value of `:type' properties for a recursive class. Whenever the classname is used, it is taken from the defined name, without a surrounding "<>"s if any. Note that some of these options are processed at compile time (all method names and auto-generation of methods). > (defentityclass name (super ...) slot ... class-initarg ...) [syntax] The same as `defclass', but for entity classes. *** Auto provide forms > (defgeneric* ...) [syntax] > (defclass* ...) [syntax] > (defentityclass* ...) [syntax] These forms are defined as the original version, except that the defined variable is automatically provided (made using `make-provide-syntax' above). Note that there is no version for `defmethod' since it should not be used where a single definition place is needed -- and it wouldn't make sense to have multiple `provide' forms for every `defmethod*' occurrence. Note that `defclass*' provides only the class identifier and not any automatically generated ones (accessors etc). ------------------------------------------------------------------------ _extra_ _extra.ss_ ------------------------------------------------------------------------ This module defines some additional useful functionality which requires Swindle. > (defstruct ([super]) slot ...) [syntax] This is just a Swindle-style syntax for one of (define-struct struct-name (slot ...) (make-inspector)) (define-struct (struct-name super) (slot ...) (make-inspector)) with an additional binding of to the Swindle class that is computed by `struct-type->class'. The `(make-inspector)' is needed to make this a struct that we can access information on. Note that in method specifiers, the `struct:foo' which is defined by `define-struct' can be used just like `'. What all this means is that you can use MzScheme structs if you just want Swindle's generic functions, but use built in structs that are more efficient since they are part of the implementation. For example: => (defstruct () x y) => # => (defmethod (bar [x ]) (foo-x x)) => (bar (make-foo 1 2)) 1 => (defmethod (bar [x struct:foo]) (foo-x x)) => (bar (make-foo 3 4)) 3 => (generic-methods bar) (#) => (defstruct (foo) z) => (bar (make-foo2 10 11 12)) 10 To make things even easier, the super-struct can be written using a "<...>" syntax which will be stripped, and appropriate methods are added to `allocate-instance' and `initialize' so structs can be built using keywords: => (defstruct () z) => (foo-x (make :z 3 :y 2 :x 1)) 1 => (foo3-z (make :z 3 :y 2 :x 2)) 3 The `' identifier *must* be of this form -- enclosed in "<>"s. This restriction is due to the fact that defining an MzScheme struct `foo', makes `foo' bound as a syntax object to something that cannot be used in any other way. > (with-slots obj (slot ...) body ...) [syntax] Evaluate the body in an environment where each `slot' is defined as a symbol-macro that accesses the corresponding slot value of `obj'. Each `slot' is either an identifier `id' which makes it stand for `(slot-ref obj 'id)', or `(id slot)' which makes `id' stand for `(slot-ref obj 'slot)'. > (with-accessors obj (accessor ...) body ...) [syntax] Evaluate the body in an environment where each `accessor' is defined as a symbol-macro that accesses `obj'. Each `accessor' is either an identifier `id' which makes it stand for `(id obj)', or `(id accessor)' which makes `id' stand for `(accessor obj);. > (as class obj) [generic] Converts `obj' to an instance of `class'. This is a convenient generic wrapper around Scheme conversion functions (functions that look like `foo->bar'), but can be used for other classes too. > (add-as-method from-class to-class op ...) [procedure] Adds a method to `as' that will use the function `op' to convert instances of `from-class' to instances of `to-class'. More operators can be used which will make this use their composition. This is used to initialize `as' with the standard Scheme conversion functions. > (equals? x y) [generic] A generic that compares `x' and `y'. It has an around method that will stop and return `#t' if the two arguments are `equal?'. It is intended for user-defined comparison between any instances. > (add-equals?-method class pred?) [procedure] Adds a method to `equals?' that will use the given `pred?' predicate to compare instances of `class'. > (class+slots-equals? x y) [procedure] This is a predicate function (not a generic function) that will succeed if `x' and `y' are instances of the same class, and all of their corresponding slots are `equals?'. This is useful as a quick default for comparing simple classes (but be careful and avoid circularity problems). > (make-equals?-compare-class+slots class) [procedure] Make `class' use `class+slots-equals?' for comparison with `equals?'. > (add x ...) [generic] A generic addition operation, initialized for some Scheme types (numbers (+), lists (append), strings (string-append), symbols (symbol-append), procedures (compose), and vectors). It dispatches only on the first argument. > (add-add-method class op) [procedure] Add a method to `add' that will use `op' to add objects of class `class'. > (len x) [generic] A generic length operation, initialized for some Scheme types (lists (length), strings (string-length), vectors (vector-length)). > (add-len-method class op) [procedure] Add a method to `len' that will use `op' to measure objects length for instances of `class'. > (ref x indexes...) [generic] A generic reference operation, initialized for some Scheme types and instances. Methods are predefined for lists, vectors, strings, objects, hash-tables, boxes, promises, parameters, and namespaces. > (add-ref-method class op) [procedure] Add a method to `ref' that will use `op' to reference objects of class `class'. > (put! x v indexes) [generic] A generic setter operation, initialized for some Scheme types and instances. The new value comes first so it is possible to add methods to specialize on it. Methods are predefined for lists, vectors, strings, objects, hash-tables, boxes, parameters, and namespaces. > (add-put!-method class op) [procedure] Add a method to `put!' that will use `op' to change objects of class `class'. > (set-ref! x indexes... v) [syntax] This syntax will just translate to `(put! x v indexes...)'. It makes it possible to make `(set! (ref ...) ...)' work with `put!'. _Generic-based printing mechanism_ ---------------------------------- > *print-level* [parameter] > *print-length* [parameter] These parameters control how many levels deep a nested data object will print, and how many elements are printed at each level. `#f' means no limit. The effect is similar to the corresponding globals in Lisp. Only affects printing of container objects (like lists, vectors and structures). > (print-object obj esc? port) [generic] Prints `obj' on `port' using the above parameters -- the effect of `esc?' being true is to use a `write'-like printout rather than a `display'-like printout when it is false. Primitive Scheme values are printed normally, Swindle objects are printed using the un-`read'-able "#<...>" sequence unless a method that handles them is defined. For this printout, objects with a `name' slot are printed using that name (and their class's name). Warning: this is the method used for user-interaction output, errors etc. Make sure you only define reliable methods for it. > (print-object-with-slots obj esc? port) [procedure] This is a printer function that can be used for classes where the desired output shows slot values. Note that it is a simple function, which should be embedded in a method that is to be added to `print-object'. > (display-object obj [port]) [procedure] > (write-object obj [port]) [procedure] Used to display and write an object using `print-object'. Used as the corresponding output handler functions. > (object->string obj [esc? = #t]) [procedure] Convert the given `obj' to a string using its printed form. > (install-swindle-printer) [procedure] In MzScheme, output is configurable on a per-port basis. Use this function to install Swindle's `display-object' and `write-object' on the current output and error ports whenever they are changed (`swindle' does that on startup). This makes it possible to see Swindle values in errors, when using `printf' etc. _Simple matching_ ----------------- > match-failure [value] The result for a matcher function application that failed. You can return this value from a matcher function in a so the next matching one will get invoked. > (matching? matcher value) [procedure] The `matcher' argument is a value of any type, which is matched against the given `value'. For most values matching means being equal (using `equals?') to, but there are some exceptions: class objects are tested with `instance-of?', functions are used as predicates, literals are used with equals?, pairs are compared recursively and regexps are used with regexp-match. > (let/match pattern value body ...) [syntax] Match the `value' against the given `pattern', and evaluate the body on a success. It is an error for the match to fail. Variables that get bound in the matching process can be used in the body. The pattern specification has a complex syntax as follows: - simple values (not symbols) are compared with `matching?' above; - :x keywords are also used as literal values; - * is a wildcard that always succeeds; - ??? matches the `???' value; - (lambda ...) use the resulting closure value (for predicates); - (quote ...) use the contents as a simple value; - (quasiquote ...) same; - (V := P) assign the variable V to the value matched by P; - V for a variable name V that was not part of the pattern so far, this matches anything and binds V to the value -- the same as (V := *); - (! E) evaluate E, use the result as a literal value; - (!! E) evaluate E, continue matching only if it is true; - (V when E) same as (and V (!! E)); - (and P ...) combine the matchers with and, can bind any variables in all parts; - (or P ...) combine the matchers with or, bound variables are only from the successful form; - (if A B C) same as (or (and A B) C); - (F => P) continue matching P with (F x) (where is x is the current matched object); - (V :: P ...) same as (and (! V) P...), useful for class forms like ( :: (foo => f) ...); - (make ...) if the value is an instance of , then continue by the `...' part which is a list of slot names and patterns -- a slot name is either :foo or 'foo, and the pattern will be matched against the contents of that slot in the original instance; - ??? matches the unspecified value (`???' in tiny-clos) - (regexp R) convert R to a regexp and use that to match strings; - (regexp R P ...) like the above, but continue matching the result with `(P ...)' so it can bind variables to the result (something like `(regexp "a(x?)b" x y)' will bind `x' to the `regexp-match' result, and `y' to a match of the sub-regexp part); - (...) other lists - match the elements of a list recursively (can use a dot suffix for a "rest" arguments). Note that variable names match anything and bind the name to the result, except when the name was already seen -- where the previously bound value is used, allowing patterns where some parts should match the same value. (A name was `seen' if it was previously used in the pattern except on different branches of an `or' pattern.) > (matcher pattern body ...) [syntax] This creates a matcher function, using the given `pattern' which will be matched with the list of given arguments on usage. If the given arguments fail to match on an application, an error will be raised. > (match x (pattern expr ...) ...) [syntax] This is similar to a `cond' statement but each clause starts with a pattern, possibly binding variables for its body. It also handles `else' as a last clause. > [class] A class similar to a generic function, that holds matcher functions such as the ones created by the `matcher' macro. It has three slots: `name', `default' (either a default value or a function that is applied to the arguments to produce the default value), and `matchers' (a list of matcher functions). Instance of `', subclass of `'. > (defmatcher (name pattern) body ...) [syntax] > (defmatcher0 (name pattern) body ...) [syntax] These macros define a matcher (if not defined yet), create a matcher function and add it to the matcher (either at the end (defmatcher) or at the beginning (defmatcher0)). _An amb macro_ -------------- This is added just because it is too much fun to miss. To learn about `amb', look for it in the Help Desk, in the "Teach Yourself Scheme in Fixnum Days" on-line manual. > (amb expr ...) [syntax] Execute forms in a nondeterministic way: each form is tried in sequence, and if one fails then evaluation continues with the next. `(amb)' fails immediately. > (amb-assert cond) [procedure] Asserts that `cond' is true, fails otherwise. > (amb-collect expr) [syntax] Evaluate expr, using amb-fail repeatedly until all options are exhausted and returns the list of all results. _Very basic UI - works also in console mode_ -------------------------------------------- The following defines some hacked UI functions that works using MrEd GUI if it is available, or the standard error and input ports otherwise. The check is done by looking for a GUI global binding. > *dialog-title* [parameter] This parameter defines the title used for the hacked UI interface. > (message fmt-string arg ...) [procedure] Like `printf' with a prefix title, or using a message dialog box. > (ok/cancel? fmt-string arg ...) [procedure] > (yes/no? fmt-string arg ...) [procedure] These functions are similar to `message', but they are used to ask an "ok/cancel" or a "yes/no" question. They return a boolean. ------------------------------------------------------------------------ _swindle_ _swindle.ss_ ------------------------------------------------------------------------ This module combines all modules to form the Swindle language module. Note that it does not re-define `#%module-begin', so the language used for transformers is still the one defined by `turbo'. This module exports bindings from: `mzlib/turbo', `mzlib/clos', `mzlib/extra'. It is intended to be used as a language module (as an initial-import for other modules).