home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Garbo
/
Garbo.cdr
/
mac
/
science
/
xlspstrd.sit
/
xlisp.help
< prev
next >
Wrap
Text File
|
1991-02-09
|
107KB
|
2,949 lines
;; system variables
(*OBARRAY* VARIABLE) "The object hash table"
(*STANDARD-INPUT* VARIABLE) "Default input stream."
(*STANDARD-OUTPUT* VARIABLE) "Default output stream."
(*ERROR-OUTPUT* VARIABLE) "Default error output stream."
(*DEBUG-IO* VARIABLE) "Default break input/output stream."
(*TRACE-OUTPUT* VARIABLE) "Default trace output stream."
(*EVALHOOK* VARIABLE)
"If *EVALHOOK* is not NIL, its value must be a function of arguments:
a form to evaluate and an environment. This function does the evaluation
instead of EVAL."
(*APPLYHOOK* VARIABLE) "(Not yet implemented)"
(*TRACELIST* VARIABLE) "List of names of functions and macros to be traced"
(*TRACENABLE* VARIABLE) "Enable backtrace on errors"
(*TRACELIMIT* VARIABLE) "Number of levels of trace back information"
(*BREAKENABLE* VARIABLE) "Flag that controls entering the break loop on errors"
(*READTABLE* VARIABLE) "The current readtable."
(*GC-FLAG* VARIABLE) "Controls printing of GC messages"
(*GC-HOOK* VARIABLE) "If not nil, function of two arguments to be called after GC"
(*PRINT-CASE* VARIABLE) "symbol output case (:upcase or :downcase)"
(*RANDOM-STATE* VARIABLE) "Current state of the random number generator"
(*INPUT-STREAM* VARIABLE) "Stream used for buffering between listener and reader."
(PI VARIABLE)
"The floating-point number that is approximately equal to the ratio of the
circumference of a circle to its diameter."
(- VARIABLE) "The current input expression"
(+ VARIABLE) "The last expression read"
(++ VARIABLE) "The previous value of +"
(+++ VARIABLE) "The previous value of ++"
(* VARIABLE) "The result of the last evaluation"
(** VARIABLE) "The previous value of *"
(*** VARIABLE) "The previous value of **"
;; Built in types
(SUBR TYPE) "Built in function"
(FSUBR TYPE) "Built in special form or macro"
(CONS TYPE) "A list cell"
(SYMBOL TYPE) "A symbol"
(FIXNUM TYPE) "An integer"
(FLONUM TYPE) "A floating point number"
(STRING TYPE) "A string"
(OBJECT TYPE) "An xlisp object"
(FILE-STREAM TYPE) "A file stream"
(VECTOR TYPE) "A vector"
(CLOSURE TYPE) "A function closure or macro"
(CHARACTER TYPE) "A character"
(UNNAMED-STREAM TYPE) "An unnamed stream (string input stream, e. g.)"
(COMPLEX TYPE) "A complex number"
(ARRAY TYPE) "A displaced multidimensional array"
;; built in object prototypes
(*OBJECT* VARIABLE) "The top of the object hierarchy."
(HARDWARE-OBJECT-PROTO VARIABLE) "Internally allocatable object prototype"
(WINDOW-PROTO VARIABLE) "Window prototype"
(EDIT-WINDOW-PROTO VARIABLE) "Edit window prototype"
(LISTENER-PROTO VARIABLE) "Listener window prototype"
(MENU-PROTO VARIABLE) "Menu prototype"
(APPLE-MENU-PROTO VARIABLE) "Apple menu prototype"
(MENU-ITEM-PROTO VARIABLE) "Menu item prototype"
(DIALOG-PROTO VARIABLE) "Dialog prototype"
(DIALOG-ITEM-PROTO VARIABLE) "Dialog item prototype"
(BUTTON-ITEM-PROTO VARIABLE) "Dialog button prototype"
(TOGGLE-ITEM-PROTO VARIABLE) "Dialog toggle item (check box) prototype"
(TEXT-ITEM-PROTO VARIABLE) "Dialog text item prototype (editable or static)"
(CHOICE-ITEM-PROTO VARIABLE) "Dialog choice item (radio button cluster) prototype"
(SCROLL-ITEM-PROTO VARIABLE) "Dialog scroll bar prototype"
(LIST-ITEM-PROTO VARIABLE) "Dialog list item prototype"
(GRAPH-WINDOW-PROTO VARIABLE) "Graphics window prototype"
(GRAPH-PROTO VARIABLE) "Dynamic plot prototype"
(SPIN-PROTO VARIABLE) "Rotating plot prototype"
(SCATMAT-PROTO VARIABLE) "Scatterplot matrix prototype"
(NAME-LIST-PROTO VARIABLE) "Name list prototype"
(HISTOGRAM-PROTO VARIABLE) "Histogram prototype"
(SCATTERPLOT-PROTO VARIABLE) "Scatterplot prototype"
(COMPOUND-DATA-PROTO VARIABLE) "Compound data object prototype"
;; evaluator functions
EVAL
"Args: (expr)
Evaluates EXPR in a NULL environment and returns the result."
APPLY
"Args: (function &rest args)
Conses all arguments but the last onto the last and applies FUNCTION to
the resulting argument list. Last argument must be a list."
FUNCALL
"Args: (function &rest arguments)
Applies FUNCTION to the ARGUMENTs"
QUOTE
"Syntax: (quote x)
Returns X without evaluating it. ALso 'x."
FUNCTION
"Syntax: (function x)
If X is a lambda expression, creates and returns a lexical closure of X in
the current lexical environment. If X is a symbol that names a function,
returns that function. ALso #'x."
BACKQUOTE
"Syntax: (backquote template) or `template.
Fills in TEMPLATE by expanding COMMA and COMMA-AT expressions."
LAMBDA
"Syntax: (lambda args {forms}*)
Makes a function closure."
;; symbol functions
SET
"Args: (symbol value)
Assigns the value of VALUE to the dynamic variable named by SYMBOL (i. e.
it changes the global definition of SYMBOL), and returns the value assigned."
SETQ
"Syntax: (setq {var form}*)
VARs are not evaluated and must be symbols. Assigns the value of the first
FORM to the first VAR, then assigns the value of the second FORM to the second
VAR, and so on. Returns the last value assigned."
SETF
"Syntax: (setf {place newvalue}*)
Replaces the value in PLACE with the value of NEWVALUE, from left to right.
Returns the value of the last NEWVALUE. Each PLACE may be any one of the
following:
* A symbol that names a variable.
* A function call form whose first element is the name of the following
functions:
nth
aref subarray sublist select elt
get
symbol-value
symbol-plist
documentation
slot-value
c?r c??r c???r c????r
where '?' stands for either 'a' or 'd'."
DEFUN
"Syntax: (defun name lambda-list [doc] {form}*)
Defines a function as the global definition of the symbol NAME. The
complete syntax of a lambda-list is:
({var}*
[&optional {var}*]
[&rest var]
[&aux {var}*])
The doc-string DOC, if supplied, is saved as a FUNCTION doc and can be
retrieved by (documentation 'NAME 'function)."
DEFMACRO
"Syntax: (defmacro name defmacro-lambda-list [doc] {form}*)
Defines a macro as the global definition of the symbol NAME. The complete
syntax of a lambda-list is:
({var}*
[&optional {var}*]
[&rest var]
[&aux {var}*])
The doc-string DOC, if supplied, is saved as a FUNCTION doc and can be
retrieved by (documentation 'NAME 'function)."
GENSYM
"Args: (&optional (x nil))
Creates and returns a new uninterned symbol whose name is a prefix string
(defaults to \"G\"), followed by a decimal number. The number is incremented
by each call to GENSYM. X, if an integer, resets the counter. If X is a
string, it becomes the new prefix."
MAKE-SYMBOL
"Args: (string)
Create and return new uninterned symbol with print name STRING."
INTERN
"Args: (name)
Returns a symbol having the specified name, creating it if necessary."
SYMBOL-NAME
"Args: (symbol)
Returns the print name of the symbol SYMBOL."
SYMBOL-VALUE
"Args: (symbol)
Returns the current global value of the variable named by SYMBOL."
SYMBOL-FUNCTION
"Args: (symbol)
Returns the current global function definition of the function named by SYMBOL."
SYMBOL-PLIST
"Args: (symbol)
Returns the property list of SYMBOL."
GET
"Args: (symbol indicator)
Looks on the property list of SYMBOL for the specified INDICATOR. If this
is found, returns the associated value. Otherwise, returns nil."
PUTPROP
"Args: (symbol value indicator)
Puts property INDICATOR with value VALUE on the property list of SYMBOL.
Returns VALUE."
REMPROP
"Args: (symbol indicator)
Look on property list of SYMBOL for property with specified
INDICATOR. If found, splice this indicator and its value out of
the plist, and return the tail of the original list starting with
INDICATOR. If not found, returns NIL with no side effects.
(This is what it should return. Actually always returns nil. ***BUG***)"
HASH
" Args (sym n)
Computes the hash index for symbol SYM in a table of size N."
;; list functions
CAR
"Args: (list)
Returns the car of LIST. Returns NIL if LIST is NIL."
CDR
"Args: (list)
Returns the cdr of LIST. Returns NIL if LIST is NIL."
CAAAAR
"Args: (x)
Equivalent to (CAR (CAR (CAR (CAR X))))."
CAAADR
"Args: (x)
Equivalent to (CAR (CAR (CAR (CDR X))))."
CAAAR
"Args: (x)
Equivalent to (CAR (CAR (CAR X)))."
CAADAR
"Args: (x)
Equivalent to (CAR (CAR (CDR (CAR X))))."
CAADDR
"Args: (x)
Equivalent to (CAR (CAR (CDR (CDR X))))."
CAADR
"Args: (x)
Equivalent to (CAR (CAR (CDR X)))."
CAAR
"Args: (x)
Equivalent to (CAR (CAR X))."
CADAAR
"Args: (x)
Equivalent to (CAR (CDR (CAR (CAR X))))."
CADADR
"Args: (x)
Equivalent to (CAR (CDR (CAR (CDR X))))."
CADAR
"Args: (x)
Equivalent to (CAR (CDR (CAR X)))."
CADDAR
"Args: (x)
Equivalent to (CAR (CDR (CDR (CAR X))))."
CADDDR
"Args: (x)
Equivalent to (CAR (CDR (CDR (CDR X))))."
CADDR
"Args: (x)
Equivalent to (CAR (CDR (CDR X)))."
CADR
"Args: (x)
Equivalent to (CAR (CDR X))."
CDAADR
"Args: (x)
Equivalent to (CDR (CAR (CAR (CDR X))))."
CDAAR
"Args: (x)
Equivalent to (CDR (CAR (CAR X)))."
CDADAR
"Args: (x)
Equivalent to (CDR (CAR (CDR (CAR X))))."
CDADDR
"Args: (x)
Equivalent to (CDR (CAR (CDR (CDR X))))."
CDADR
"Args: (x)
Equivalent to (CDR (CAR (CDR X)))."
CDAR
"Args: (x)
Equivalent to (CDR (CAR X))."
CDDAAR
"Args: (x)
Equivalent to (CDR (CDR (CAR (CAR X))))."
CDDADR
"Args: (x)
Equivalent to (CDR (CDR (CAR (CDR X))))."
CDDAR
"Args: (x)
Equivalent to (CDR (CDR (CAR X)))."
CDDDAR
"Args: (x)
Equivalent to (CDR (CDR (CDR (CAR X))))."
CDDDDR
"Args: (x)
Equivalent to (CDR (CDR (CDR (CDR X))))."
CDDDR
"Args: (x)
Equivalent to (CDR (CDR (CDR X)))."
CDDR
"Args: (x)
Equivalent to (CDR (CDR X))."
CDAAAR
"Args: (x)
Equivalent to (CDR (CAR (CAR (CAR X))))."
FIRST
"Args: (x)
Equivalent to (CAR X)."
SECOND
"Args: (x)
Equivalent to (CAR (CDR X))."
THIRD
"Args: (x)
Equivalent to (CADDR X)."
FOURTH
"Args: (x)
Equivalent to (CADDDR X)."
REST
"Args: (x)
Equivalent to (CDR X)."
CONS
"Args: (x y)
Returns a new cons (list node) whose car and cdr are X and Y, respectively."
LIST
"Args: (&rest args)
Returns a list of its arguments"
APPEND
"Args: (&rest lists)
Constructs a new list by concatenating its arguments."
REVERSE
"Args: (list)
Returns a new list containing the same elements as LIST but in
reverse order."
LAST
"Args: (list)
Returns the last cons in LIST"
NTH
"Args: (n list)
Returns the N-th element of LIST, where the car of LIST is the zero-th
element."
NTHCDR
"Args: (n list)
Returns the result of performing the CDR operation N times on LIST."
MEMBER
"Args: (item list &key (test #'eql) test-not)
Returns the tail of LIST beginning with the first ITEM."
ASSOC
"Args: (item alist &key (test #'eql) test-not)
Returns the first pair in ALIST whose car is equal (in the sense of TEST) to
ITEM."
SUBST
"Args: (new old tree &key (test #'eql) test-not)
Substitutes NEW for subtrees of TREE that match OLD."
SUBLIS
"Args: (alist tree &key (test #'eql) test-not)
Substitutes from ALIST for subtrees of TREE nondestructively."
REMOVE
"Args: (item list &key (test #'eql) test-not)
Returns a copy of LIST with ITEM removed."
LENGTH
"Args: (sequence)
Returns the length of SEQUENCE."
MAPC
"Args: (fun list &rest more-lists)
Applies FUN to successive cars of LISTs. Returns the first LIST."
MAPCAR
"Args: (fun list &rest more-lists)
Applies FUN to successive cars of LISTs and returns the results as a list."
MAPL
"Args: (fun list &rest more-lists)
Applies FUN to successive cdrs of LISTs. Returns the first LIST."
MAPLIST
"Args: (fun list &rest more-lists)
Applies FUN to successive cdrs of LISTs and returns the results as a list."
;; destructive list functions
RPLACA
"Args: (x y)
Replaces the car of X with Y, and returns the modified X."
RPLACD
"Args: (x y)
Replaces the cdr of X with Y, and returns the modified X."
NCONC
"Args: (&rest lists)
Concatenates LISTs by destructively modifying them."
DELETE
"Args: (item list &key (test #'eql) test-not)
Returns a list formed by removing the specified ITEM destructively from
LIST."
;; predicate functions
ATOM
"Args: (x)
Returns T if X is not a cons; NIL otherwise."
SYMBOLP
"Args: (x)
Returns T if X is a symbol; NIL otherwise."
NUMBERP
"Args: (x)
Returns T if X is any kind of number; NIL otherwise."
BOUNDP
"Args: (symbol)
Returns T if the global variable named by SYMBOL has a value; NIL otherwise."
NULL
"Args: (x)
Returns T if X is NIL; NIL otherwise."
LISTP
"Args: (x)
Returns T if X is either a cons or NIL; NIL otherwise."
CONSP
"Args: (x)
Returns T if X is a cons; NIL otherwise."
EQ
"Args: (x y)
Returns T if X and Y are the same identical object; NIL otherwise."
EQL
"Args: (x y)
Returns T if X and Y are EQ, or if they are numbers of the same type with
the same value, or if they are identical strings. Returns NIL otherwise."
EQUAL
"Args: (x y)
Returns T if X and Y are EQL or if they are of the same type and corresponding
components are EQUAL. Returns NIL otherwise. Arrays must be EQ to be EQUAL."
NOT
"Args: (x)
Returns T if X is NIL; NIL otherwise."
;; special forms
COND
"Syntax: (cond {(test {form}*)}*)
Evaluates each TEST in order until one evaluates to a non-NIL value. Then
evaluates the associated FORMs in order and returns the value of the last
FORM. If no forms follow the TEST, then returns the value of the TEST.
Returns NIL, if all TESTs evaluate to NIL."
CASE
"Syntax: (case keyform {({key | ({key}*)} {form}*)}*)
Evaluates KEYFORM and tries to find the KEY that is EQL to the value of
KEYFORM. If one is found, then evaluates FORMs that follow the KEY and
returns the value of the last FORM. If not, simply returns NIL."
AND
"Syntax: (and {form}*)
Evaluates FORMs in order from left to right. If any FORM evaluates to NIL,
returns immediately with the value NIL. Else, returns the value of the
last FORM."
OR
"Syntax: (or {form}*)
Evaluates FORMs in order from left to right. If any FORM evaluates to
non-NIL, quits and returns that value. If the last FORM is reached,
returns whatever value it returns."
LET
"Syntax: (let ({var | (var [value])}*) {form}*)
Initializes VARs, binding them to the values of VALUEs (which defaults to NIL)
all at once, then evaluates FORMs as a PROGN."
LET*
"Syntax: (let* ({var | (var [value])}*) {form}*)
Initializes VARs, binding them to the values of VALUEs (which defaults to NIL)
from left to right, then evaluates FORMs as a PROGN."
IF
"Syntax: (if test then [else])
If TEST evaluates to non-NIL, then evaluates THEN and returns the result.
If not, evaluates ELSE (which defaults to NIL) and returns the result."
PROG
"Syntax: (prog ({var | (var [init])}*) {tag | statement}*)
Binds VARs in parallel, and then executes STATEMENTs."
PROG*
"Syntax: (prog* ({var | (var [init])}*) {tag | statement}*)
Binds VARs sequentially, and then executes STATEMENTs."
PROG1
"Syntax: (prog1 first {form}*)
Evaluates FIRST and FORMs in order, and returns the value of FIRST."
PROG2
"Syntax: (prog2 first second {forms}*)
Evaluates FIRST, SECOND, and FORMs in order, and returns the value
of SECOND."
PROGN
"Syntax: (progn {form}*)
Evaluates FORMs in order, and returns whatever the last FORM returns."
PROGV
"Syntax: (progv symbols values {form}*)
Evaluates FORMs in order, with SYMBOLS dynamically bound to VALUES, and
returns whatever the last FORM returns."
GO
"Syntax: (go tag)
Jumps to the specified TAG established by a lexically surrounding PROG
construct."
RETURN
"Syntax: (return [result])
Returns from the lexically surrounding PROG construct. The value of RESULT,
which defaults to NIL, is returned as the value of the PROG construct."
DO
"Syntax: (do ({(var [init [step]])}*) (endtest {result}*) {tag | statement}*)
Creates a NIL block, binds each VAR to the value of the corresponding INIT,
and then executes STATEMENTs repeatedly until ENDTEST is satisfied. After
each iteration, assigns to each VAR the value of the corresponding STEP. When
ENDTEST is satisfied, evaluates RESULTs as a PROGN and returns the value of
the last RESULT (or NIL if no RESULTs are supplied). Performs variable
bindings and assignments all at once, just like LET does."
DO*
"Syntax: (do* ({(var [init [step]])}*) (endtest {result}*) {tag | statement}*)
Just like DO, but performs variable bindings and assignments in serial, just
like LET* and SETQ do."
DOLIST
"Syntax: (dolist (var listform [result]) {tag | statement}*)
Executes STATEMENTs, with VAR bound to each member of the list value of
LISTFORM. Then returns the value of RESULT (which defaults to NIL)."
DOTIMES
"Syntax: (dotimes (var countform [result]) {tag | statement}*)
Executes STATEMENTs, with VAR bound to each number between 0 (inclusive) and
the value of COUNTFORM (exclusive). Then returns the value of RESULT
(which defaults to NIL)."
CATCH
"Syntax: (catch tag {form}*)
Sets up a catcher with that value TAG. Then evaluates FORMs as a PROGN, but
may possibly abort the evaluation by a THROW form that specifies the value
EQ to the catcher tag."
THROW
"Syntax: (throw tag result)
Evaluates TAG and aborts the execution of the most recent CATCH form that sets
up a catcher with the same tag value. The CATCH form returns whatever RESULT
returned."
;; debugging and error handling functions
ERROR
"Args: (message-string arg)
Signals a fatal error. ARG is printed after the MESSAGE-STRING."
CERROR
"Args: (continue-message-string error-message-string args)
Signals a correctable error. Returns NIL when continued from the break loop."
BREAK
CLEAN-UP
"Args: ()
Cleans up after an error and moves to next lower break loop level."
TOP-LEVEL
"Args: ()
Returns to the top level."
CONTINUE
"Args: ()
Continues after a correctable error"
ERRSET
"Args: (expr [pflag])
Traps errors occurring during the evaluation of EXPR. PFLAG controls printing
of the error message. Returns the value of the last expression consed with
NIL or NIL. "
"Args: (number)
Prints NUMBER levels of trace back information. Returns NIL."
BAKTRACE
"Args: (&optional number)
Prints NUMBER levels of trace back information. Returns NIL."
EVALHOOK
"Args: (form evalhookfn applyhookfn &optional (env nil))
Evaluates FORM with *EVALHOOK* bound to EVALHOOKFN and *APPLYHOOK* bound
to APPLYHOOKFN. Ignores these hooks once, for the top-level evaluation
of FORM.(Note: *APPPLYHOOK* is not yet implemented, and is thus ignored.)"
;; string functions
STRCAT
" Args: ({string}*)
Concatenates the STRINGs and returns the result."
SUBSEQ
"Args: (string start &optional end)
Extracts and returns the substring of STRING starting at START and ending at
END, if supplied, or the end of STRING."
STRING
"
Args: (sym)
Returns print-name of SYM if SYM is a symbol, or SYM if SYM is a."
CHAR
"Args: (string index)
Returns the INDEX-th character in STRING."
;; I/O functions
READ
"Args: (&optional (stream *standard-input*) (eof-error-p t) (eof-value nil) (recursivep nil))
Reads and returns the next object from STREAM."
PRINT
"Args: (object &optional (stream *standard-output*))
Outputs a newline character, and then prints OBJECT in the most readable
representation. Returns OBJECT."
PRIN1
"Args: (object &optional (stream *standard-output*))
Prints OBJECT in the most readable representation. Returns OBJECT."
PRINC
"Args: (object &optional (stream *standard-output*))
Prints OBJECT without escape characters. Returns OBJECT."
TERPRI
"Args: (&optional (stream *standard-output*))
Outputs a newline character."
FLATSIZE
"Args: (object)
Returns length of printed representation of OBJECT using PRIN1"
FLATC
"Args: (object)
Returns length of printed representation of OBJECT using PRINC"
;; file I/O functions
OPEN
"Args: (fname &key (direction :input))
Opens file named by string or symbol FNAME. DIRECTION is :INPUT or :OUTPUT."
CLOSE
"Args: (stream)
Close file stream STREAM."
READ-CHAR
"Args: (&optional (stream *standard-input*) (eof-value nil) (recursive-p nil))
Reads a character from STREAM."
PEEK-CHAR
"Args: (&optional (peek-type nil) (stream *standard-input*) (eof-value nil) (recursive-p nil))
Peeks at the next character in the input stream STREAM."
WRITE-CHAR
"Args: (char &optional (stream *standard-output*))
Outputs CHAR and returns it."
READ-LINE
"Args: (&optional (stream *standard-input*) (eof-value nil) (recursive-p nil))
Returns line of text read from STREAM as a string without the newline character."
;; system functions
LOAD
"Args: (filename &key (verbose t) (print nil))
Loads the file named by FILENAME into XLISP. Returns T if load succeeds,
NIL if file does not exist."
DRIBBLE
"Args: (&optional file)
If string or symbol FILE is supplied creates a transcript file with this name.
If FILE is missing closes the transcript file."
SYSTEM
"Args: (string)
Runs the operating system command specified by string. Not available on
all implementations."
DYN-LOAD
"Args: (file &key verbose libflags fortran)
Links the object file FILE with standard C libraries and loads into
the running XLISP-STAT process. If FORTRAN is not NIL also searches
standard FORTRAN libraries. LIBFLAGS can be a string used to specify
additional libraries, for example "-lcmlib". Not available on all
implementations."
CALL-CFUN
"Args: (cfun &rest args)
CFUN is a string naming a C function. The remaining arguments must be
integers, sequences of integers, reals or sequences of reals. CFUN is
called with the remaining arguments and a list of the lists of the
values of the arguments after the call is returned. Arguments in the
call will be pointers to ints or pointers to doubles. Not available
on all implementations."
CALL-FSUB
"Args: (fsub &rest args)
FSUB is a string naming a FORTRAN subroutine. The remaining arguments
must be integers, sequences of integers, reals or sequences of reals.
FSUB is called with the remaining arguments and a list of the lists of
the values of the arguments after the call is returned. Arguments in
the call will be (arrays of) integers or double precision numbers. Not
available on all implementations."
CALL-LFUN
"Args: (lfun &rest args)
LFUN is a C function written to conform to internal XLISP argument
reading and value returning conventions. Applies LFUN to ARGS and
returns the result."
GC
"Args: ()
Forces garbage collection. Returns nil."
EXPAND
"Args: (number)
Expand memory by adding NUMBER segments. Returns the number of segments."
ALLOC
"Args: (number)
Changes number of nodes to allocate in each segment to NUMBER. Returns
old number of nodes to allocate."
ROOM
"Args: ()
Shows memory allocation statistics. Returns nil."
SAVE
"Args: (file)
Saves current memory image in FILE.wks. Does not work right with allocated objects."
RESTORE
"Args: (file)
Restores memory image from FILE.wks. Does not work right with allocated objects."
TYPE-OF
"Args: (x)
Returns the type of X."
EXIT
"Args: ()
Exits from XLISP."
PEEK
"Args (address)
Peek at an ADDRESS in memory."
POKE
"Args: (address value)
Poke VALUE into ADDRESS in memory."
ADDRESS-OF
"Args (x)
Get the address of an XLISP node."
X11-OPTIONS
"Args: (&key (fast-lines t) (fast-symbols t) (motion-sync t)
Sets performance options for X11 window system."
;; new functions and special forms
VECTOR
"Args: (&rest items)
Returns a vector with ITEMS as elements."
BLOCK
"Syntax: (block name {form}*)
The FORMs are evaluated in order, but it is possible to exit the block
using (RETURN-FROM name value). The RETURN-FROM must be lexically contained
within the block."
RETURN-FROM
"Syntax: (return-from name [result])
Returns from the lexically surrounding block whose name is NAME. The value
of RESULT, which defaults to NIL, is returned as the value of the block."
TAGBODY
"Syntax: (tagbody {tag | statement}*)
Executes STATEMENTs and returns NIL if it falls off the end."
PSETQ
"Syntax: (psetq {var form}*)
Similar to SETQ, but evaluates all FORMs first, and then assigns each value to
the corresponding VAR. Returns NIL always."
FLET
"Syntax: (flet ({(name lambda-list {decl | doc}* {form}*)}*) . body)
Evaluates BODY as a PROGN, with local function definitions in effect. BODY is
the scope of each local function definition. Since the scope does not include
the function definitions themselves, the local function can reference
externally defined functions of the same name. See the doc of DEFUN for the
complete syntax of a lambda-list. Doc-strings for local functions are simply
ignored."
LABELS
"Syntax: (labels ({(name lambda-list {decl | doc}* {form}*)}*) . body)
Evaluates BODY as a PROGN, with the local function definitions in effect.
The scope of the locally defined functions include the function definitions
themselves, so they can reference externally defined functions of the same
name. See the doc of DEFUN for the complete syntax of a lambda-list.
Doc-strings for local functions are simply ignored."
MACROLET
"Syntax: (macrolet ({(name defmacro-lambda-list {decl | doc}* . body)}*)
{form}*)
Evaluates FORMs as a PROGN, with the local macro definitions in effect.
See the doc of DEFMACRO for the complete syntax of a defmacro-lambda-list.
Doc-strings for local macros are simply ignored."
UNWIND-PROTECT
"Syntax: (unwind-protect protected-form {cleanup-form}*)
Evaluates PROTECTED-FORM and returns whatever it returned. Guarantees that
CLEANUP-FORMs be always evaluated before exiting from the UNWIND-PROTECT
form."
PPRINT
"Args: (object &optional (stream *standard-output*))
Pretty-prints OBJECT. Returns OBJECT."
STRING<
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
If STRING1 is lexicographically less than STRING2, then returns the longest
common prefix of the strings. Otherwise, returns NIL."
STRING<=
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
If STRING1 is lexicographically less than or equal to STRING2, then returns
the longest common prefix of the two strings. Otherwise, returns NIL."
STRING=
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
Returns T if the two strings are character-wise CHAR=; NIL otherwise."
STRING/=
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
Returns NIL if STRING1 and STRING2 are character-wise CHAR=. Otherwise,
returns the index to the longest common prefix of the strings."
STRING>=
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
If STRING1 is lexicographically greater than or equal to STRING2, then returns
the longest common prefix of the strings. Otherwise, returns NIL."
STRING>
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
If STRING1 is lexicographically greater than STRING2, then returns the
longest common prefix of the strings. Otherwise, returns NIL."
STRING-LESSP
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
Similar to STRING<, but ignores cases."
STRING-NOT-GREATERP
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
Similar to STRING<=, but ignores cases."
STRING-EQUAL
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
Given two strings (string1 and string2), and optional integers start1,
start2, end1 and end2, compares characters in string1 to characters in
string2 (using char-equal)."
STRING-NOT-EQUAL
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
Similar to STRING=, but ignores cases."
STRING-NOT-LESSP
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
Similar to STRING>=, but ignores cases."
STRING-GREATERP
"Args: (string1 string2
&key (start1 0) (end1 (length string1))
(start2 0) (end2 (length string2)))
Similar to STRING>, but ignores cases."
INTEGERP
"Args: (x)
Returns T if X is an integer (fixnum or bignum); NIL otherwise."
FLOATP
"Args: (x)
Returns T if X is a floating-point number; NIL otherwise."
STRINGP
"Args: (x)
Returns T if X is a string; NIL otherwise."
ARRAYP
"Args: (x)
Returns T if X is an array; NIL otherwise."
STREAMP
"Args: (x)
Returns T if X is a stream object; NIL otherwise."
OBJECTP
"Args: (x)
Returns T if X is an object, NIL otherwise."
STRING-UPCASE
"Args: (string &key (start 0) (end (length string)))
Returns a copy of STRING with all lower case characters converted to
uppercase."
STRING-DOWNCASE
"Args: (string &key (start 0) (end (length string)))
Returns a copy of STRING with all upper case characters converted to
lowercase."
NSTRING-UPCASE
"Args: (string &key (start 0) (end (length string)))
Returns STRING with all lower case characters converted to uppercase."
NSTRING-DOWNCASE
"Args: (string &key (start 0) (end (length string)))
Returns STRING with all upper case characters converted to lowercase."
STRING-TRIM
"Args: (char-bag string)
Returns a copy of STRING with the characters in CHAR-BAG removed from both
ends."
STRING-LEFT-TRIM
"Args: (char-bag string)
Returns a copy of STRING with the characters in CHAR-BAG removed from the
left end."
STRING-RIGHT-TRIM
"Args: (char-bag string)
Returns a copy of STRING with the characters in CHAR-BAG removed from the
right end."
WHEN
"Syntax: (when test {form}*)
If TEST evaluates to non-NIL evaluates FORMs as a PROGN. If not, returns NIL."
UNLESS
"Syntax: (unless test {form}*)
If TEST evaluates to NIL evaluates FORMs as a PROGN. If not, returns NIL."
LOOP
"Syntax: (loop {form}*)
Executes FORMs repeatedly until exited by a THROW or RETURN. The FORMs are
surrounded by an implicit NIL block."
FBOUNDP
"Args: (symbol)
Returns T if SYMBOL has a global function definition or if SYMBOL names a
special form or a macro; NIL otherwise."
PROGV
"Syntax: (progv symbols values {form}*)
SYMBOLS must evaluate to a list of symbols. VALUES must evaluate to a list
of initial values. Evaluates FORMs as a PROGN, with each variable bound
dynamically to the corresponding value."
CHARACTERP
"Args: (x)
Returns T if X is a character; NIL otherwise."
CHAR-INT
"Args: (char)
Returns the ASCII code of CHAR. Equivalent to CHAR-CODE in XLISP."
INT-CHAR
"Args: (integer)
Performs the inverse of CHAR-INT. Equivalent to CODE-CHAR in XLISP."
READ-BYTE
"Args: (&optional stream)
Reads the next byte from STREAM."
WRITE-BYTE
"Args: (integer &optional stream)
Outputs INTEGER to the binary stream STREAM. Returns INTEGER."
MAKE-STRING-INPUT-STREAM
"Args: (string &optional (start 0) (end (length string)))
Returns an input stream which will supply the characters of String between
Start and End in order."
MAKE-STRING-OUTPUT-STREAM
"Args: ()
Returns an output stream which will accumulate all output given it for
the benefit of the function GET-OUTPUT-STREAM-STRING."
GET-OUTPUT-STREAM-STRING
"Args: (stream)
Returns a string of all the characters sent to STREAM made by
MAKE-STRING-OUTPUT-STREAM since the last call to this function."
GET-OUTPUT-STREAM-LIST
"Args: (stream)
Returns list of elements in stream."
GCD
"Args: (&rest integers)
Returns the greatest common divisor of INTEGERs."
GET-LAMBDA-EXPRESSION
"Args (closure)
Extracts lambda expression from CLOSURE."
MACROEXPAND
"Args: (form)
If FORM is a macro form expands it repeatedly until it is not a macro."
MACROEXPAND-1
"Args: (form)
If FORM is a macro form, then expands it once."
CHAR<
"Args: (char &rest more-chars)
Returns T if the codes of CHARs are in strictly increasing order; NIL
otherwise."
CHAR<=
"Args: (char &rest more-chars)
Returns T if the codes of CHARs are in strictly non-decreasing order; NIL
otherwise."
CHAR=
"Args: (char &rest more-chars)
Returns T if all CHARs are the same character; NIL otherwise."
CHAR/=
"Args: (char &rest more-chars)
Returns T if no two of CHARs are the same character; NIL otherwise."
CHAR>=
"Args: (char &rest more-chars)
Returns T if the codes of CHARs are in strictly non-increasing order; NIL
otherwise."
CHAR>
"Args: (char &rest more-chars)
Returns T if the codes of CHARs are in strictly decreasing order; NIL
otherwise."
CHAR-LESSP
"Args: (char &rest more-chars)
Returns T if the codes of CHARs are in strictly increasing order; NIL
otherwise. For a lower-case character, the code of its upper-case equivalent
is used."
CHAR-NOT-GREATERP
"Args: (char &rest more-chars)
Returns T if the codes of CHARs are in strictly non-decreasing order; NIL
otherwise. For a lower-case character, the code of its upper-case equivalent
is used."
CHAR-EQUAL
"Args: (char &rest more-chars)
Returns T if all of its arguments are the same character; NIL otherwise.
Upper case character and its lower case equivalent are regarded the same."
CHAR-NOT-EQUAL
"Args: (char &rest more-chars)
Returns T if no two of CHARs are the same character; NIL otherwise.
Upper case character and its lower case equivalent are regarded the same."
CHAR-NOT-LESSP
"Args: (char &rest more-chars)
Returns T if the codes of CHARs are in strictly non-increasing order; NIL
otherwise. For a lower-case character, the code of its upper-case equivalent
is used."
CHAR-GREATERP
"Args: (char &rest more-chars)
Returns T if the codes of CHARs are in strictly decreasing order; NIL
otherwise. For a lower-case character, the code of its upper-case equivalent
is used."
UPPER-CASE-P
"Args: (char)
Returns T if CHAR is an upper-case character; NIL otherwise."
LOWER-CASE-P
"Args: (char)
Returns T if CHAR is a lower-case character; NIL otherwise."
BOTH-CASE-P
"Args: (char)
Returns T if CHAR is an alphabetic character; NIL otherwise."
DIGIT-CHAR-P
"Args: (char &optional (radix 10))
If CHAR represents a digit returns the weight as an integer.
Otherwise, returns nil."
ALPHANUMERICP
"Args: (char)
Returns T if CHAR is either numeric or alphabetic; NIL otherwise."
CHAR-UPCASE
"Args: (char)
Returns the upper-case equivalent of CHAR, if any, or CHAR."
CHAR-DOWNCASE
"Args: (char)
Returns the lower-case equivalent of CHAR, if any, or CHAR."
DIGIT-CHAR
"Args: (digit)
Returns a character object that represents the DIGIT, or NIL."
CHAR-CODE
"Args: (char)
Returns ASCII code of CHAR."
CODE-CHAR
"Args: (code)
Returns character object with the specified ASCII code, or NIL."
ENDP
"Args: (x)
Returns T if X is NIL. Returns NIL if X is a cons. Otherwise, signals an
error."
REMOVE-IF
"Args: (test list)
Returns a copy of LIST with elements satisfying TEST removed."
REMOVE-IF-NOT
"Args: (test list)
Returns a copy of LIST with elements not satisfying TEST removed."
DELETE-IF
"Args: (test list)
Returns result of destructively removing the elements satisfying TEST from LIST."
DELETE-IF-NOT
"Args: (test list)
Returns result of destructively removing the elements not satisfying TEST from LIST."
TRACE
"Syntax: (trace {function-name}*)
Traces the specified functions. With no FUNCTION-NAMEs, returns a list of
functions currently being traced."
UNTRACE
"Syntax: (untrace {function-name}*)
Removes tracing from the specified functions. With no FUNCTION-NAMEs,
untraces all functions."
SORT
"Args: (list predicate)
Destructively sorts LIST. PREDICATE should return non-NIL if its first
argument is to precede its second argument."
;; *OBJECT*
(*OBJECT* OBJECT PROTO) "The root object."
(*OBJECT* OBJECT :GET-METHOD)
"Method args: (selector)
Returns method for SELECTOR symbol from object's precedence list."
(*OBJECT* OBJECT :HAS-SLOT)
"Method args: (slot &optional own)
Returns T if slot SLOT exists, NIL if not. If OWN is not NIL
only checks the object; otherwise check the entire precedence list."
(*OBJECT* OBJECT :HAS-METHOD)
"Method args: (selector &optional own)
Returns T if method for SELECTOR exists, NIL if not. If OWN is not NIL
only checks the object; otherwise check the entire precedence list."
(*OBJECT* OBJECT :ADD-SLOT)
"Method args: (slot &optional value)
Installs slot SLOT in object, if it does not already exist, and
sets its value to VLAUE."
(*OBJECT* OBJECT :ADD-METHOD)
"Method args: (selector method)
Installs METHOD for SELECTOR in object."
(*OBJECT* OBJECT :DELETE-SLOT)
"Method args: (slot)
Deletes slot SLOT from object if it exists."
(*OBJECT* OBJECT :DELETE-METHOD)
"Method args: (selector)
Deletes method for SELECTOR in object if it exists."
(*OBJECT* OBJECT :SHOW)
"Method Args: ()
Prints object's internal data."
(*OBJECT* OBJECT :ISNEW)
"Method args: (&rest args)
Checks ARGS for keyword arguments matching slots and uses them to
initialize slots."
(*OBJECT* OBJECT :PARENTS)
"Method args: ()
Returns copy of parents list."
(*OBJECT* OBJECT :PRECEDENCE-LIST)
"Method args: ()
Returns copy of the precedence list."
(*OBJECT* OBJECT :OWN-SLOTS)
"Method args: ()
Returns list of names of slots owned by object."
(*OBJECT* OBJECT :OWN-METHODS)
"Method args ()
Returns copy of selectors for methods owned by object."
(*OBJECT* OBJECT :INTERNAL-DOC)
"Method args (topic &optional value)
Retrieves or installs documentation for topic."
(*OBJECT* OBJECT :REPARENT)
"Method args: (&rest parents)
Changes precedence list to correspond to PARENTS. Does not change descendants."
;; compound data objects
(COMPOUND-DATA-PROTO OBJECT :SELECT-DATA)
"Sets or retrieves subset of data. Arguments depend on the object."
(COMPOUND-DATA-PROTO OBJECT :MAKE-DATA)
"Methos args: (data)
Make object like self with new data."
(COMPOUND-DATA-PROTO OBJECT :DATA-SEQ)
"Methos args: ()
Return sequence of object's data."
(COMPOUND-DATA-PROTO OBJECT :DATA-LENGTH)
"Methos args: ()
Return length of object's data."
;; WINDOW-PROTO
(WINDOW-PROTO OBJECT PROTO)
"Instance variables: (title location size go-away)
Basic window prototype. Instance variables used at allocation; can set with
keywords to :ISNEW."
(WINDOW-PROTO OBJECT :SHOW-WINDOW)
"Method args: ()
Makes window visible and moves it to the front. Returns NIL."
(WINDOW-PROTO OBJECT :HIDE-WINDOW)
"Method args: ()
Hides the window without deallocating it. Returns NIL."
(WINDOW-PROTO OBJECT :CLOSE)
"Method args: ()
Closes the window without deallocating it. Returns NIL."
(WINDOW-PROTO OBJECT :TITLE)
"Method args: (&optional title)
Sets window title to TITLE if supplied. Returns current title."
(WINDOW-PROTO OBJECT :LOCATION)
"Method args: (&optional left top)
Moves window content to (LEFT TOP) if supplied. Returns list of
current left, top. Adjusts for the menu bar."
(WINDOW-PROTO OBJECT :SIZE)
"Method args: (&optional width height)
Sets window content width and size to WIDTH and SIZE if supplied.
Returns list of current WIDTH HEIGHT. Adjusts for the menu bar."
(WINDOW-PROTO OBJECT :FRAME-LOCATION)
"Method args: (&optional left top)
Moves window frame to (LEFT TOP) if supplied. Returns list of
current left, top. Adjusts for the menu bar."
(WINDOW-PROTO OBJECT :FRAME-SIZE)
"Method args: (&optional width height)
Sets window frame width and size to WIDTH and SIZE if supplied.
Returns list of current WIDTH and HEIGHT. Adjusts for the menu bar."
(WINDOW-PROTO OBJECT :UNDO)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :CUT-TO-CLIP)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :COPY-TO-CLIP)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :PASTE-FROM-CLIP)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :CLEAR)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :PASTE-STREAM)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :PASTE-STRING)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :SELECTION-STREAM)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :ACTIVATE)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :UPDATE)
"Method args: ()
Does nothing."
(WINDOW-PROTO OBJECT :FIND)
"Method args: ()
Does nothing."
;; EDIT-WINDOW-PROTO
(EDIT-WINDOW-PROTO OBJECT PROTO)
"Instance variables: (input-enabled output-stream bind-to-file)
Edit window prototype. Instance variables used at allocation; can set with
:SINEW keywords. Inherits from WINDOW-PROTO"
(EDIT-WINDOW-PROTO OBJECT :ISNEW)
"Method args: (&key title location size go-away input-enabled
output-stream bind-to-file)
Initializes instance variables and sends itself the :ALLOCATE message.
Instance variables are used on allocation. GO-AWAY says whether window has a
close box, OUTPUT-STREAM can be used to write to the window, and BIND-TO-FILE
will cause a get-file-dialog to appear when the window is allocated."
(EDIT-WINDOW-PROTO OBJECT :ALLOCATE)
"Method args: ()
Allocates and opens the window. Obtains file with get-file-dialog if slot
BIND-TO-FILE is true."
(EDIT-WINDOW-PROTO OBJECT :CUT-TO-CLIP)
"Method args: ()
Cut selection to clip board."
(EDIT-WINDOW-PROTO OBJECT :COPY-TO-CLIP)
"Method args: ()
Copy selection to clip board."
(EDIT-WINDOW-PROTO OBJECT :PASTE-FROM-CLIP)
"Method args: ()
Paste selection to clip board."
(EDIT-WINDOW-PROTO OBJECT :REVERT)
"Method args: ()
Reverts to file on disk; opens dialog to check first."
(EDIT-WINDOW-PROTO OBJECT :SAVE)
"Method args: ()
Save file. Use save-file dialog to get a name if not bound to file."
(EDIT-WINDOW-PROTO OBJECT :SAVE-AS)
"Method args: ()
Save file under name obtained by save-file-dialog and bind window to the file."
(EDIT-WINDOW-PROTO OBJECT :SAVE-COPY)
"Method args: ()
Save copy of file under name obtained by save-file-dialog; don't change file binding."
(EDIT-WINDOW-PROTO OBJECT :PASTE-STREAM)
"Method args: (string)
Inserts the characters in STRING at the current insertion point, replacing any
current selection."
(EDIT-WINDOW-PROTO OBJECT :PASTE-STRING)
"Method args: (stream)
Inserts the characters in STREAM at the current insertion point, replacing any
current selection."
(EDIT-WINDOW-PROTO OBJECT :FLUSH-WINDOW)
"Method args: (&optional count)
Flushes the first COUNT characters from the window. Flushes all characters if
COUNT is not supplied."
(EDIT-WINDOW-PROTO OBJECT :SELECTION-STREAM)
"Method args: ()
Returns a stream containing the characters of the current selection."
(EDIT-WINDOW-PROTO OBJECT :CLOSE)
"Method args: ()
Closes and deallocates the window. Asks about saving the file if necessary."
(EDIT-WINDOW-PROTO OBJECT :REMOVE)
"Method args: ()
Closes and deallocates the window. Asks about saving the file if necessary."
(EDIT-WINDOW-PROTO OBJECT :DISPOSE)
"Method args: ()
Closes and deallocates the window. Asks about saving the file if necessary."
(EDIT-WINDOW-PROTO OBJECT :ACTIVATE)
"Method args: ()
Does nothing."
(EDIT-WINDOW-PROTO OBJECT :UPDATE)
"Method args: ()
Does nothing."
(EDIT-WINDOW-PROTO OBJECT :FIND-STRING)
"Method args: (string)
Finds and selects STRING if it is in the file. Returns T if found, NIL if not.
Search is case insensitive."
;; LISTENER-PROTO
(LISTENER-PROTO OBJECT :ISNEW)
"Method args: ()
Initializes new listener object."
(LISTENER-PROTO OBJECT :ALLOCATE)
"Method args: ()
Connects object to internal listener window."
;; MENU-PROTO
(MENU-PROTO OBJECT PROTO)
"Instance variables: (title items enabled id)
Basic menu prototype. Instance variables used internally."
(MENU-PROTO OBJECT :ISNEW)
"Method args: (title)
Sets menu title to TITLE and sends it the itself :ALLOCATE message."
(MENU-PROTO OBJECT :ALLOCATE)
"Method args: ()
Allocates an internal menu for the object."
(MENU-PROTO OBJECT :DISPOSE)
"Method args: ()
Disposes of the internal menu."
(MENU-PROTO OBJECT :INSTALL)
"Method args ()
Installs the menu in the menu bar (Macintosh only)."
(MENU-PROTO OBJECT :REMOVE)
"Method args: ()
Removes the menu from the menu bar (Macintosh only)."
(MENU-PROTO OBJECT :ENABLED)
"Method args: (&optional enabled)
If ENABLED is supplied enables or disables the menu if ENABLED is true or
NIL. Returns T if menu is enabled, NIL otherwise."
(MENU-PROTO OBJECT :UPDATE)
"Method args: ()
Sends each menu item the :UPTADE message."
(MENU-PROTO OBJECT :ALLOCATED-P)
"Method args: ()
Returns true if menu is allocated, NIL otherwise."
(MENU-PROTO OBJECT :TITLE)
"Method args: (&optional TITLE)
If TITLE is supplied sets menu title to TITLE. Returns menu title."
(MENU-PROTO OBJECT :ITEMS)
"Method args: ()
Returns list of menu items."
(MENU-PROTO OBJECT :INSTALLED-P)
"Method args: ()
Returns true if menu is in the menu bar, NIL otherwise."
(MENU-PROTO OBJECT :APPEND-ITEMS)
"Method args: (&rest items)
adds ITEMS to the menu and Returns NIL."
(MENU-PROTO OBJECT :DELETE-ITEMS)
"Method args: (&rest items)
Removes ITEMS from menu and returns NIL. Signals an error if an
item is not in the menu"
(MENU-PROTO OBJECT :SELECT)
"Method args: (index)
Sends item (elt items (- INDEX 1)) the :DO-ACTION message."
(MENU-PROTO OBJECT :POPUP)
"Method args: (x y)
Waits for a mouse click if mouse is not already down at call time, then
pops up menu at screen coordinates (X Y)."
;; APPLE-MENU-PROTO
(APPLE-MENU-PROTO OBJECT :ISNEW)
"Method args: (title)
Sets menu title to TITLE and sends it the itself :ALLOCATE message."
(APPLE-MENU-PROTO OBJECT :SELECT)
"Method args: (index)
Sends item (elt items (- INDEX 1)) the :DO-ACTION message or opens the
desk accessory."
;; MENU-ITEM-PROTO
(MENU-ITEM-PROTO OBJECT PROTO)
"Instance variables: (title key mark style action enabled menu)
Menu item. Instance variables used on installation; can set using
keywords to :ISNEW."
(MENU-ITEM-PROTO OBJECT :ISNEW)
"Method args: (title &key key mark style action (enabled t))
Initializes a new menu item object."
(MENU-ITEM-PROTO OBJECT :TITLE)
"Method args: (&optional title)
Sets item title to TITLE if supplied and returns title."
(MENU-ITEM-PROTO OBJECT :KEY)
"Method args: (&optional char)
Sets item keyboard equivalent to CHAR, if supplied, and returns current key
(Macintosh only)."
(MENU-ITEM-PROTO OBJECT :MARK)
"Method args: (&optional MARK)
Sets item mark to MARK if MARK is a character, to a check if MARK is T
and to no mark if MARK is NIL. Returns current mark (Macintosh only)."
(MENU-ITEM-PROTO OBJECT :STYLE)
"Method args: (&optional style)
Sets and returns item style. STYLE can be a symbol or list of symbols from
BOLD, ITALIC, UNDERLINE, SHADOW, CONDENSE, EXTEND (Macintosh only)."
(MENU-ITEM-PROTO OBJECT :ACTION)
"Method args: (&optional FCN)
Sets ACTION slot to FCN if supplied; returns current ACTION value."
(MENU-ITEM-PROTO OBJECT :ENABLED)
"Method args: (&optional enable)
Enables or disables item if ENABLED is supplied; returns T if enabled,
NIL if not."
(MENU-ITEM-PROTO OBJECT :INSTALLED-P)
"Method args: ()
Returns T if item is installed in a menu, NIL if not."
(MENU-ITEM-PROTO OBJECT :UPDATE)
"Method args: ()
Does nothing."
(MENU-ITEM-PROTO OBJECT :DO-ACTION)
"Method args: ()
Funcalls the value of the ACTION slot."
;; DIALOG-PROTO
(DIALOG-PROTO OBJECT PROTO)
"Dialog window prototype."
(DIALOG-PROTO OBJECT :ISNEW)
"Method args: (items &key title location size go-away type default-button)
Initializes and allocates a dialog. ITEMS is a list of dialog items; type
should be MODAL or MODELESS. Default is MODAL. Type only affect window
appearance, not the dialog's behavior."
(DIALOG-PROTO OBJECT :ALLOCATE)
"Method args: ()
Allocates and opens a dialog window."
(DIALOG-PROTO OBJECT :REMOVE)
"Method args: ()
Closes and deallocates the dialog window."
(DIALOG-PROTO OBJECT :DISPOSE)
"Method args: ()
Closes and deallocates the dialog window."
(DIALOG-PROTO OBJECT :CLOSE)
"Method args: ()
Closes and deallocates the dialog window."
(DIALOG-PROTO OBJECT :ALLOCATED-P)
"Method args: ()
Returns T if dialog is allocated, NIL if not."
(DIALOG-PROTO OBJECT :DEFAULT-BUTTON)
"Message args: (button)
Makes BUTTON the default button."
(DIALOG-PROTO OBJECT :MODAL-DIALOG)
"Method args: ()
Puts dialog into modal mode, waits for a dialog event, and returns the item
in which the event occurred."
(DIALOG-PROTO :ITEMS)
"Method args: ()
Returns list of dialog items."
;; DIALOG-ITEM-PROTO
(DIALOG-ITEM-PROTO OBJECT PROTO)
"Dialog item prototype."
(DIALOG-ITEM-PROTO OBJECT :DO-ACTION)
"Method args: ()
Funcalls value of ACTION slot if it is not NIL."
(DIALOG-ITEM-PROTO OBJECT :ACTION)
"Method args (&optional fcn)
Sets or returns value of ACTION slot."
;; BUTTON-ITEM-PROTO
(BUTTON-ITEM-PROTO OBJECT :ISNEW)
"Method args: (text &key location size action)
Initializes a button item."
;; TOGGLE-ITEM-PROTO
(TOGGLE-ITEM-PROTO OBJECT PROTO)
"Toggle item prototype."
(TOGGLE-ITEM-PROTO OBJECT :ISNEW)
"Method args: (text &key location size action value)
Initializes a toggle (check box) item."
(TOGGLE-ITEM-PROTO OBJECT :VALUE)
"Method args: (value)
Sets or gets toggle item value. Value is T or NIL."
;; TEXT-ITEM-PROTO
(TEXT-ITEM-PROTO OBJECT PROTO)
"Text item prototype."
(TEXT-ITEM-PROTO OBJECT :ISNEW)
"Method args: (text &key location size action (editable nil))
Initializes a text item (editable or static)."
(TEXT-ITEM-PROTO OBJECT :TEXT)
"Method args: (string)
Sets or gets text item's text."
;; CHOICE-ITEM-PROTO
(CHOICE-ITEM-PROTO OBJECT PROTO)
"Choice (radio button cluster) item prototype."
(CHOICE-ITEM-PROTO OBJECT :ISNEW)
"Method args: (strings &key location size action value)
Initializes a choice (radio button cluster) item. STRINGS is a list of strings."
(CHOICE-ITEM-PROTO OBJECT :VALUE)
"Method args: (value)
Sets or gets choice item value. Value is the zero-based index of the selected item."
;; SCROLL-ITEM-PROTO
(SCROLL-ITEM-PROTO OBJECT PROTO)
"Scroll bar item."
(SCROLL-ITEM-PROTO OBJECT :ISNEW)
"Method args: (&key location size action (min-value 0) (max-value 100) (page-increment 5)
value)
Initializes a scroll bar item. Orientation is determined by SIZE; default is horizontal."
(SCROLL-ITEM-PROTO OBJECT :VALUE)
"Method args: (value)
Sets or gets scroll item value. Value is truncated to [min-value, max-value]."
(SCROLL-ITEM-PROTO OBJECT :MAX-VALUE)
"Method args: (value)
Sets or gets scroll item minimum value."
(SCROLL-ITEM-PROTO OBJECT :MIN-VALUE)
"Method args: (value)
Sets or gets scroll item maximum value."
(SCROLL-ITEM-PROTO OBJECT :SCROLL-ACTION)
"Method args: ()
Funcalls ACTION slot value if it is not NIL."
;; LIST-ITEM-PROTO
(LIST-ITEM-PROTO OBJECT PROTO)
"List item."
(LIST-ITEM-PROTO OBJECT :ISNEW)
"Method args: (strings &key location size action (columns 1))
Initializes a list item. STRINGS should be a sequence of two dimensional array
of strings. COLUMNS is the number of columns visible in the display."
(LIST-ITEM-PROTO OBJECT :DO-ACTION)
"Method args: (&optional (double nil))
Funcalls value of ACTION slot, if it is not NIL, with argument DOUBLE."
(LIST-ITEM-PROTO OBJECT :SET-TEXT)
"Method args: (index string)
Sets text at INDEX to STRING. INDEX should be a number or a list of two numbers,
depending on whether the list cas constructed with a sequence or an array."
(LIST-ITEM-PROTO OBJECT :SELECTION)
"Method args: (&optional index)
Sets or returns index of selected cell. INDEX should be a number for a sequence
and a list of two numbers for an array, or NIL to turn off selection."
;; GRAPH-WINDOW-PROTO
(GRAPH-WINDOW-PROTO OBJECT PROTO)
"Basic graphics window prototype."
(GRAPH-WINDOW-PROTO OBJECT :ISNEW)
" Method args: (&key (title \"Graph Window\") location size
(go-away t) menu (black-on-white t)
has-h-scroll has-v-scroll menu-title)
Initializes and send :allocate message to basic plot window."
(GRAPH-WINDOW-PROTO OBJECT :ALLOCATE)
"Method args: ()
Allocates new graph window based on content of slots."
(GRAPH-WINDOW-PROTO OBJECT :IDLE-ON)
"
Method args: (&optional on)
Sets or returns idling state. On means :do-idle method is sent each pass through
the event loop."
(GRAPH-WINDOW-PROTO OBJECT :MENU)
"Method args: (&optional menu)
Sets or retrieves window's menu."
(GRAPH-WINDOW-PROTO OBJECT :UPDATE)
"Method args: (resized)
Sends self the :RESIZED method if RESIZED is true, redraws the frame and
controls, and sends self the :REDRAW message."
(GRAPH-WINDOW-PROTO OBJECT :ACTIVATE)
"Method args: (active)
Installs menu if ACTIVE is true; removes it otherwise. (Macintosh only.)"
(GRAPH-WINDOW-PROTO OBJECT :REMOVE)
"Method args: ()
Closes and deallocates the graph window."
(GRAPH-WINDOW-PROTO OBJECT :DISPOSE)
"Method args: ()
Closes and deallocates the graph window."
(GRAPH-WINDOW-PROTO OBJECT :CLOSE)
"Method args: ()
Closes and deallocates the graph window."
(GRAPH-WINDOW-PROTO OBJECT :WHILE-BUTTON-DOWN)
"Method args: (fcn &optional (motion-only t))
Calls fcn repeatedly while mouse button is down. FCN should take two arguments,
the current x and y coordinates of the mouse. Returns NIL. Should be called
when button is already down."
(GRAPH-WINDOW-PROTO OBJECT :TITLE)
"Method args: (&optional string)
Sets or retrieves window title."
(GRAPH-WINDOW-PROTO OBJECT :DO-IDLE)
"Method args: ()
Message received from system in idle state when idling is on."
(GRAPH-WINDOW-PROTO OBJECT :REDRAW)
"Method args: ()
Message received from system when window needs redrawing."
(GRAPH-WINDOW-PROTO OBJECT :RESIZE)
"Method args: ()
Message received from system when window is resized."
(GRAPH-WINDOW-PROTO OBJECT :CANVAS-WIDTH)
"Method args: ()
Returns current canvas width."
(GRAPH-WINDOW-PROTO OBJECT :CANVAS-HEIGHT)
"Method args: ()
Returns current canvas height."
(GRAPH-WINDOW-PROTO OBJECT :LINE-TYPE)
"Method args: (&optional type)
Sets or returns current line type. Choices are SOLID and DASHED."
(GRAPH-WINDOW-PROTO OBJECT :DRAW-MODE)
"Method args: (&optional mode)
Sets or returns current drawing mode. Choices are NORMAL and XOR."
(GRAPH-WINDOW-PROTO OBJECT :DRAW-COLOR)
"Method args: (&optional color)
Sets or retrieves current drawing color. Choices are in the list *COLORS*."
(GRAPH-WINDOW-PROTO OBJECT :BACK-COLOR)
"Method args: (&optional color)
Sets or retrieves current background color. Choices are in the list *COLORS*."
(GRAPH-WINDOW-PROTO OBJECT :USE-COLOR)
"Method args: (&optional use)
Sets or retrieves current color use state. Has no effect on B/W systems."
(GRAPH-WINDOW-PROTO OBJECT :REVERSE-COLORS)
"Method args: ()
Reverses drawing and background colors and sends self the :REDRAW message."
(GRAPH-WINDOW-PROTO OBJECT :VIEW-RECT)
"Method args: ()
Returns the current view rectangle as list of the form
(LEFT TOP WIDTH HEIGHT)"
(GRAPH-WINDOW-PROTO OBJECT :LINE-WIDTH)
"Method args: (&optional width)
Sets or retrieves current line width."
(GRAPH-WINDOW-PROTO OBJECT :CLIP-RECT)
"Method args: (&optional left top width height)
Sets or retrieves current clip rectangle. If NIL is supplied clipping is turned off.
A result of NIL means clipping is disabled."
(GRAPH-WINDOW-PROTO OBJECT :CURSOR)
"Method args: (&optional cursor)
Sets or retrieves the current window cursor. Choices are in the list *cursors*."
(GRAPH-WINDOW-PROTO OBJECT :HAS-H-SCROLL)
"Method args: (&optional x)
Determines or sets whether window has a horizontal scrollbar. If X is
supplied and is NIL the scroll bar is removed. If X is a number a scroll
bar is added and the canvas width is set to the number (between 0 and 3200).
If X is T a scroll bar is added and the canvas width is set to the maximum
of the screen's width and height."
(GRAPH-WINDOW-PROTO OBJECT :HAS-V-SCROLL)
"Method args: (&optional x)
Determines or sets whether window has a vertical scrollbar. If X is
supplied and is NIL the scroll bar is removed. If X is a number a scroll
bar is added and the canvas height is set to the number (between 0 and 3200).
If X is T a scroll bar is added and the canvas height is set to the maximum
of the screen's width and height."
(GRAPH-WINDOW-PROTO OBJECT :SCROLL)
"Method args: (x y)
Sets or returns current position of left top corner of view rectangle.
X or Y are ignored if no horizontal or vertical scroll bar is present."
(GRAPH-WINDOW-PROTO OBJECT :H-SCROLL-INCS)
"Method args: (inc page-inc)
Sets or retrieves the increments scrolled by the buttons and page areas
of the horizontal scroll bar."
(GRAPH-WINDOW-PROTO OBJECT :V-SCROLL-INCS)
"Method args: (inc page-inc)
Sets or retrieves the increments scrolled by the buttons and page areas
of the vertical scroll bar."
(GRAPH-WINDOW-PROTO OBJECT :DRAW-LINE)
"Method args: (x1 y1 x2 y2)
Draws line from (x1 y1) to (x2 y2)."
(GRAPH-WINDOW-PROTO OBJECT :ERASE-RECT)
"Method args: (left top width height)
Frames the rectangle (LEFT TOP WIDTH HEIGHT)."
(GRAPH-WINDOW-PROTO OBJECT :FRAME-RECT)
"Method args: (left top width height)
Fills the rectangle (LEFT TOP WIDTH HEIGHT) with the background color."
(GRAPH-WINDOW-PROTO OBJECT :PAINT-RECT)
"Method args: (left top width height)
Fills the rectangle (LEFT TOP WIDTH HEIGHT) with the drawing color."
(GRAPH-WINDOW-PROTO OBJECT :ERASE-OVAL)
"Method args: (left top width height)
Fills the oval in (LEFT TOP WIDTH HEIGHT) with the background color."
(GRAPH-WINDOW-PROTO OBJECT :FRAME-OVAL)
"Method args: (left top width height)
Frames the oval in (LEFT TOP WIDTH HEIGHT)."
(GRAPH-WINDOW-PROTO OBJECT :PAINT-OVAL)
"Method args: (left top width height)
Fills the oval in (LEFT TOP WIDTH HEIGHT) with the drawing color."
(GRAPH-WINDOW-PROTO OBJECT :FRAME-POLY)
"Method args: (poly &optional (from-origin t))
Outlines polygon. POLY is a list of lists of two numbers. If FROM-ORIGIN is
true coordinates are relative to the origin; otherwise they are relative to
the previous point."
(GRAPH-WINDOW-PROTO OBJECT :PAINT-POLY)
"Method args: (poly &optional (from-origin t))
Paints content of polygon in current draw color. POLY is a list of lists of two
numbers. If FROM-ORIGIN is true coordinates are relative to the origin;
otherwise they are relative to the previous point."
(GRAPH-WINDOW-PROTO OBJECT :ERASE-POLY)
"Method args: (poly &optional (from-origin t))
Erases content of polygon. POLY is a list of lists of two numbers. If
FROM-ORIGIN is true coordinates are relative to the origin; otherwise
they are relative to the previous point."
(GRAPH-WINDOW-PROTO OBJECT :ERASE-ARC)
"Method args: (left top width height start delta)
Fills the arc in (LEFT TOP WIDTH HEIGHT) from START by DELTA with the
background color. Angles are in degrees."
(GRAPH-WINDOW-PROTO OBJECT :FRAME-ARC)
"Method args: (left top width height start delta)
Frames the arc in (LEFT TOP WIDTH HEIGHT) from START by DELTA. Angles are in
degrees."
(GRAPH-WINDOW-PROTO OBJECT :PAINT-ARC)
"Method args: (left top width height start delta)
Fills the oval in (LEFT TOP WIDTH HEIGHT) from START by DELTA with the
drawing color. Angles are in degrees."
(GRAPH-WINDOW-PROTO OBJECT :TEXT-ASCENT)
"Method args: ()
Returns ascent in pixels for the window's text font."
(GRAPH-WINDOW-PROTO OBJECT :TEXT-DESCENT)
"Method args: ()
Returns descent in pixels for the window's text font."
(GRAPH-WINDOW-PROTO OBJECT :TEXT-WIDTH)
"Method args: (string)
Returns widh in pixels of STRING in the window's font."
(GRAPH-WINDOW-PROTO OBJECT :DRAW-STRING)
"Method args: (string x y)
Draws STRING horizontally starting at (x y)."
(GRAPH-WINDOW-PROTO OBJECT :DRAW-STRING-UP)
"Method args: (string x y)
Draws STRING vertically starting at (x y)."
(GRAPH-WINDOW-PROTO OBJECT :DRAW-TEXT)
"Method args: (string x y h v)
Draws STRING horizontally positioned relative to (x y). H controls horizontal
justification. 0 = left justified, 1 = centered, 2 = right justified. V controls
vertical positioning. 0 = above (x y), 1 = below (x y)."
(GRAPH-WINDOW-PROTO OBJECT :DRAW-TEXT-UP)
"Method args: (string x y h v)
Same as :DRAW-TEXT but rotated by 90 degrees."
(GRAPH-WINDOW-PROTO OBJECT :DRAW-SYMBOL)
"Method args: (symbol hilited x y)
Draws SYMBOL at (x y). Choices are in list *PLOT-SYMBOLS*"
(GRAPH-WINDOW-PROTO OBJECT :REPLACE-SYMBOL)
"Method args: (oldsym oldh newsym newh x y)
Replaces OLDSYM at (x y) by NEWSYM. Hilighting states are set by OLDH and NEWH.
Available symbols are in the list *PLOT-SYMBOLS*"
(GRAPH-WINDOW-PROTO OBJECT :DRAW-BITMAP)
"Method args: (image left top)
Draws IMAGE, a matrix of 0's and 1's, with top left corner at (LEFT TOP)"
(GRAPH-WINDOW-PROTO OBJECT :DRAW-POINT)
"Method args: (x y)
Draws a single pixel at (X Y)"
(GRAPH-WINDOW-PROTO OBJECT :START-BUFFERING)
"Method args: ()
Starts sending drawing result so buffer or increases buffering level if already
buffering."
(GRAPH-WINDOW-PROTO OBJECT :BUFFER-TO-SCREEN)
"Method args: (&optional left top width height)
Reduces buffering level. If level reaches zero copies content of rectangle
(LEFT TOP WIDTH HEIGHT to window. Default rectangle is the window's view rectangle."
(GRAPH-WINDOW-PROTO OBJECT :COPY-TO-CLIP)
"Method args: ()
Sends the plot the :REDRAW message, surrounded by open and close picture commands.
Then puts the picture on the clip board."
(GRAPH-WINDOW-PROTO OBJECT :DRAG-GREY-RECT)
"Method args: (x y width height)
Drags grey rectangle starting at (LIST (- X WIDTH) (- Y HEIGHT) WIDTH HEIGHT)
while mouse button is down. Returns the final rectangle. Should be called when
the mouse is down."
;; GRAPH-PROTO
(GRAPH-PROTO OBJECT PROTO)
"Basic graphics window prototype."
(GRAPH-PROTO OBJECT :ISNEW)
" Method args: (vars &key (title \"Graph\") location size
(go-away t) menu (black-on-white t)
has-h-scroll has-v-scroll menu-title
variable-labels scale)
Initializes and send :allocate message to basic plot window."
(GRAPH-PROTO OBJECT :ALLOCATE)
"Method args: ()
Allocates a new graph."
(GRAPH-PROTO OBJECT :RESIZE)
"
Method args: ()
Adjusts internal layout after resizing."
(GRAPH-PROTO OBJECT :REDRAW)
"Method args: ()
Redraws entire plot."
(GRAPH-PROTO OBJECT :REDRAW-CONTENT)
"Method args: ()
Redraws plot's content."
(GRAPH-PROTO OBJECT :ADJUST-SCREEN)
"Method args: ()
Checks all points and adjusts their screen states to match internal state."
(GRAPH-PROTO OBJECT :ADJUST-POINTS-IN-RECT)
"Method args: (left top width height state)
Adjusts points in rectangle to have specified state. STATE should be HILITED or SELECTED.
If it is HILITED, highlighted points outside the rectangle are unhighlighted."
(GRAPH-PROTO OBJECT :ADJUST-SCREEN-POINT)
"Method args: (i)
Adjusts the screen highlight state of point I to match internal state. Internal state
should not be INVISIBLE."
(GRAPH-PROTO OBJECT :CONTENT-RECT)
"Method args: (&optional left top width height)
Sets or retrieves current content rectangle."
(GRAPH-PROTO OBJECT :CONTENT-ORIGIN)
"Method args: (&optional x y)
Sets or retrieves the current content origin."
(GRAPH-PROTO OBJECT :CONTENT-VARIABLES)
"Method args: (&optional xvar yvar)
Sets or retrieves the indices of the current content variables."
(GRAPH-PROTO OBJECT :CLICK-RANGE)
"Method args: (&optional width height)
Sets or retrieves the size of the current mouse click range."
(GRAPH-PROTO OBJECT :MOUSE-MODE)
"Method args (&optional mode)
Sets or retrieves current mouse mode."
(GRAPH-PROTO OBJECT :SHOWING-LABELS)
"Method args: (&optional showing)
Sets or retrieves current labeling state (true or NIL)."
(GRAPH-PROTO OBJECT :MARGIN)
"Method args: (&optional left top right bottom &key (draw t))
Sets or retrieves current list of margin sizes."
(GRAPH-PROTO OBJECT :FIXED-ASPECT)
"Method args: (&optional fixed)
Sets or retrieves current size adjustment option (true or NIL)."
(GRAPH-PROTO OBJECT :X-AXIS)
"Method args: (&optional showing labeled ticks)
Sets or retrieves current acis label state. SHOWING and LABELED should be
true or NIL; TICKS should be a number. All three should be supplied for setting
a new state. A list of the three properties is returned."
(GRAPH-PROTO OBJECT :Y-AXIS)
"Method args: (&optional showing labeled ticks)
Sets or retrieves current acis label state. SHOWING and LABELED should be
true or NIL; TICKS should be a number. All three should be supplied for setting
a new state. A list of the three properties is returned."
(GRAPH-PROTO OBJECT :BRUSH)
"Method args: (x y width height)
Sets or retrieves current brush. Brush is specified in terms of the lower lefthand
corner and its width and height."
(GRAPH-PROTO OBJECT :ERASE-BRUSH)
"Method args: ()
Removes brush from the screen."
(GRAPH-PROTO OBJECT :DRAW-BRUSH)
"Method args: ()
Draws brush at its current position."
(GRAPH-PROTO OBJECT :MOVE-BRUSH)
"Method args: (x y)
Moves the brush's lower left hand corner to (X, Y)."
(GRAPH-PROTO OBJECT :RESIZE-BRUSH)
"Method args: ()
Opens the brush resizing dialog and resets the brush if the OK button is clicked."
(GRAPH-PROTO OBJECT :DO-CLICK)
"Method args: (x y extend option)
Sends appropriate action message for mouse mode to plot."
(GRAPH-PROTO OBJECT :DO-MOTION)
"Method args: (x y)
Sends appropriate action message for mouse mode to plot."
(GRAPH-PROTO OBJECT :DO-KEY)
"Method args: (char shift option)
Message received when user hits a key."
(GRAPH-PROTO OBJECT :UNSELECT-ALL-POINTS)
"Method args: ()
Unselects all points."
(GRAPH-PROTO OBJECT :ERASE-SELECTION)
"Method args: ()
Sets selected points states to invisible and sends :ADJUST-SCREEN message."
(GRAPH-PROTO OBJECT :MASK-SELECTION)
"Method args: ()
Masks selected points and sends :ADJUST-SCREEN message "
(GRAPH-PROTO OBJECT :UNMASK-ALL-POINTS)
"Method args: ()
Unmasks all points and sends :ADJUST-SCREEN message "
(GRAPH-PROTO OBJECT :SHOW-ALL-POINTS)
"Method args: ()
Sets all point states to normal and sends :ADJUST-SCREEN message "
(GRAPH-PROTO OBJECT :ALL-POINTS-SHOWING-P)
"Method ars: ()"
(GRAPH-PROTO OBJECT :ALL-POINTS-UNMASKED-P)
"Method ars: ()"
(GRAPH-PROTO OBJECT :ANY-POINTS-SELECTED-P)
"Method ars: ()"
(GRAPH-PROTO OBJECT :LINKED)
"Method ars: (&optional on)
Sets or retrieves plot's linking state."
(GRAPH-PROTO OBJECT :NUM-VARIABLES)
"Method args: ()
Returns the number of variables in the plot."
(GRAPH-PROTO OBJECT :VARIABLE-LABEL)
"Method args: (var &optional label)
Sets or returns label for variable with index VAR. Vectorized."
(GRAPH-PROTO OBJECT :RANGE)
"Method args: (index &optional low high)
Sets or retrieves variable's original coordinate range. Vectorized."
(GRAPH-PROTO OBJECT :SCALED-RANGE)
"Method args: (index &optional low high)
Sets or retrieves variable's transformed coordinate range. Vectorized."
(GRAPH-PROTO OBJECT :SCREEN-RANGE)
"Method args: (index &optional low high)
Sets or retrieves variable's screen coordinate range. Vectorized."
(GRAPH-PROTO OBJECT :TRANSFORMATION)
"Method args: (&optional a &key (draw t))
Sets or retrieves transformation. A should be a matrix or NIL. If draw is true
the :REDRAW-CONTENT message is sent."
(GRAPH-PROTO OBJECT :APPLY-TRANSFORMATION)
"Method args: (a &key draw basis)
Applies matrix A to current transformation. If draw is true the :REDRAW-CONTENT
message is sent."
(GRAPH-PROTO OBJECT :ADD-POINTS)
"Method args: (points &key point-labels (draw t))
Adds points to plot. POINTS is a list of sequences, POINT-LABELS a list of
strings. If DRAW is true the new points are added to the screen."
(GRAPH-PROTO OBJECT :CLEAR-POINTS)
"Method args: (&key (draw t))
Removes all points from the plot. If DRAW is true the :REDRAW-CONTENT
message is sent."
(GRAPH-PROTO OBJECT :NUM-POINTS)
"Method args: ()
Returns the number of points in the plot."
(GRAPH-PROTO OBJECT :POINT-COORDINATE)
"Method args: (var point &optional value)
Sets or retrieves coordinate for variable VAR and point POINT in the original
coordinate system. Vectorized."
(GRAPH-PROTO OBJECT :POINT-SCREEN-COORDINATE)
"Method args: (var point)
Returns rounded coordinate for variable VAR and point POINT in the screen
coordinate system. Vectorized."
(GRAPH-PROTO OBJECT :POINT-TRANSFORMED-COORDINATE)
"Method args: (var point)
Returns coordinate for variable VAR and point POINT in the transformed
coordinate system. Vectorized."
(GRAPH-PROTO OBJECT :POINT-MASKED)
"Method args: (point &optional masked)
Sets or retrieves masked state (true or NIL) of point POINT. Vectorized."
(GRAPH-PROTO OBJECT :POINT-COLOR)
"Method args: (point &optional color)
Sets or retrieves color of point POINT. Vectorized."
(GRAPH-PROTO OBJECT :POINT-STATE)
"Method args: (point &optional state)
Sets or retrieves state (invisible, normal, hilited or selected) of point
POINT. Vectorized."
(GRAPH-PROTO OBJECT :POINT-SCREEN-STATE)
"Method args: (point &optional state)
Sets or retrieves internal screen state of point POINT. Does no
drawing. Vectorized."
(GRAPH-PROTO OBJECT :POINT-LABEL)
"Method args: (point &optional label)
Sets or retrieves label of point POINT. Vectorized."
(GRAPH-PROTO OBJECT :POINT-SYMBOL)
"Method args: (point &optional symbol)
Sets or retrieves symbol of point POINT. Vectorized."
(GRAPH-PROTO OBJECT :POINT-SELECTED)
"Method args: (point &optional selected)
Sets or returns selection status (true or NIL) of POINT. Sends
:ADJUST-SCREEN message if states are set. Vectorized."
(GRAPH-PROTO OBJECT :POINT-HILITED)
"Method args: (point &optional hilited)
Sets or returns highlighting status (true or NIL) of POINT. Sends
:ADJUST-SCREEN message if states are set. Vectorized."
(GRAPH-PROTO OBJECT :POINT-SHOWING)
"Method args: (point &optional selected)
Sets or returns visibility status (true or NIL) of POINT. Sends
:ADJUST-SCREEN message if states are set. Vectorized."
(GRAPH-PROTO OBJECT :UNSHOW-ALL-POINTS)
"Method args: ()
Makes all points invisible."
(GRAPH-PROTO OBJECT :SELECTION)
"Method args: (&optional list)
Sets or Return indices of current selection."
(GRAPH-PROTO OBJECT :POINTS-HILITED)
"Method args: (&optional list)
Sets or Return indices of currently highlighted points."
(GRAPH-PROTO OBJECT :POINTS-SHOWING)
"Method args: (&optional list)
Sets or Return indices of currently visible points."
(GRAPH-PROTO OBJECT :POINTS-SELECTED)
"Method args: (&optional list)
Sets or Return indices of current selection."
(GRAPH-PROTO OBJECT :ADD-LINES)
"Method args: (lines &key type (draw t))
Adds lines to plot. LINES is a list of sequences, the coordinates of the line starts.
TYPE is normal or dashed. If DRAW is true the new lines are added to the screen."
(GRAPH-PROTO OBJECT :CLEAR-LINES)
"Method args: (&key (draw t))
Removes all lines from the plot. If DRAW is true the :REDRAW-CONTENT
message is sent."
(GRAPH-PROTO OBJECT :NUM-LINES)
"Method args: ()
Returns the number of line starts in the plot."
(GRAPH-PROTO OBJECT :LINESTART-COORDINATE)
"Method args: (var line &optional value)
Sets or retrieves coordinate for variable VAR and line start LINE in the original
coordinate system. Vectorized."
(GRAPH-PROTO OBJECT :LINESTART-SCREEN-COORDINATE)
"Method args: (var line)
Returns rounded coordinate for variable VAR and line start LINE in the screen
coordinate system. Vectorized."
(GRAPH-PROTO OBJECT :LINESTART-TRANSFORMED-COORDINATE)
"Method args: (var line)
Returns coordinate for variable VAR and line start LINE in the transformed
coordinate system. Vectorized."
(GRAPH-PROTO OBJECT :LINESTART-MASKED)
"Method args: (line &optional masked)
Sets or retrieves masked state (true or NIL) of line start LINE. Vectorized."
(GRAPH-PROTO OBJECT :LINESTART-COLOR)
"Method args: (line &optional color)
Sets or retrieves color of line start LINE. Vectorized."
(GRAPH-PROTO OBJECT :LINESTART-NEXT)
"Method args: (line &optional next)
Sets or returns index of line start to which line is to be drawn. Negative values
mean no line. Vectorized."
(GRAPH-PROTO OBJECT :LINESTART-TYPE)
"Method args: (line &optional type)
Sets or retrieves line type. Vectorized."
(GRAPH-PROTO OBJECT :LINESTART-WIDTH)
"Method args: (line &optional width)
Sets or retrieves the line width for the line start. Vectorized."
(GRAPH-PROTO OBJECT :DRAW-DATA-POINTS)
"Method args: (var1 var2 m n)
Draws points with indices between m (inclusive) and n (exclusive) using VAR1 and VAR2
coordinates."
(GRAPH-PROTO OBJECT :DRAW-DATA-LINES)
"Method args: (var1 var2 m n)
Draws lines with indices between m (inclusive) and n (exclusive) using VAR1 and VAR2
coordinates."
(GRAPH-PROTO OBJECT :ROTATE-2)
"Method args: (var1 var2 angle &key (draw t))
Rotates int the plane of variables with indices VAR1 and VAR2 by ANGLE, in
radians. sends the :REDRAW-CONTENT message if DRWA is true."
(GRAPH-PROTO OBJECT :ADJUST-TO-DATA)
"Method args: (&key (draw t))
Sets ranges to the actual range of variables in the original coordinate
system. If DRAW is true sends :RESIZE and :REDRAW messages."
(GRAPH-PROTO OBJECT :VISIBLE-RANGE)
"Method args: (var)
Returns list of min and max of variable VAR over visible, unmasked points,
lines and strings. Vectorized."
(GRAPH-PROTO OBJECT :SCALE-TO-RANGE)
"Method args: (var low high &key (draw t))
Scales and shifts data to map visible range into specified range. Sends
:RESIZE and :REDRAW messages if DRAW is true."
(GRAPH-PROTO OBJECT :SCALE)
"Method args: (var &optional scale &key (draw t))
Sets or retrieves current scale for variable VAR. Sends :RESIZE and :REDRAW
messages if DRAW is true."
(GRAPH-PROTO OBJECT :SHIFT)
"Method args: (var &optional shift &key (draw t))
Sets or retrieves current shift for variable VAR. Sends :RESIZE and :REDRAW
messages if DRAW is true."
(GRAPH-PROTO OBJECT :CLEAR-MASKS)
"Method args: ()
Unmasks all points, lines and strings."
(GRAPH-PROTO OBJECT :SLICE-VARIABLE)
"Method args: (var low high)
Masks points lines and strings with variable VAR original coordinates outside
of (LOW, HIGH)."
(GRAPH-PROTO OBJECT :REAL-TO-CANVAS)
"Method args: (x y)
Returns list of canvas coordinates of point (X, Y), in the original coordinate system,
based on current content variables."
(GRAPH-PROTO OBJECT :SCALED-TO-CANVAS)
"Method args: (x y)
Returns list of canvas coordinates of point (X, Y), in the scaled coordinate system,
based on current content variables."
(GRAPH-PROTO OBJECT :CANVAS-TO-REAL)
"Method args: (x y)
Returns list of real coordinates, in the original coordinate system, of
canvas point (X, Y), based on current content variables."
(GRAPH-PROTO OBJECT :CANVAS-TO-SCALED)
"Method args: (x y)
Returns list of scaled coordinates, in the scaled coordinate system, of
canvas point (X, Y), based on current content variables."
(GRAPH-PROTO OBJECT :POINTS-IN-RECT)
"
Method args: (left top width height)
Returns list of indices of points in screen rectangle."
;; SPIN-PROTO
(SPIN-PROTO OBJECT PROTO) "Rotating plot"
(SPIN-PROTO OBJECT :ALLOCATE) "documentation not yet available"
(SPIN-PROTO OBJECT :SHOWING-AXES)
"Method args: (&optional showing)
Sets or retrieves axis showing status (true or NIL)."
(SPIN-PROTO OBJECT :DEPTH-CUING)
"Method args: (&optional cuing)
Sets or retrieves cuing status (true or NIL)."
(SPIN-PROTO OBJECT :DO-IDLE)
"Method args: ()
Sends :ROTATE message."
(SPIN-PROTO OBJECT :ANGLE)
"Method args: (&optional angle)
Sets or retrieves current rotation angle, in radians."
(SPIN-PROTO OBJECT :ROTATE)
"Method args: ()
Rotates once in the current plane by the current angle."
;; SCATMAT-PROTO
(SCATMAT-PROTO OBJECT PROTO) "Scatterplot matrix"
;; NAME-LIST-PROTO
(NAME-LIST-PROTO OBJECT PROTO) "Name list"
(NAME-LIST-PROTO OBJECT :ADD-POINTS)
"Method args: (points &key point-labels (draw t))
Adds points to plot. POINTS is a number or a list of sequences, POINT-LABELS a list of
strings. If DRAW is true the new points are added to the screen."
;; HISTOGRAM-PROTO
(HISTOGRAM-PROTO OBJECT PROTO) "Histogram"
(HISTOGRAM-PROTO OBJECT :ADD-POINTS)
"Method args: (points (draw t))
Adds points to plot. POINTS is a sequence or a list of sequences. If DRAW is
true the new points are added to the screen."
(HISTOGRAM-PROTO OBJECT :NUM-BINS)
"Method args: (&optional bins &key (draw t))
Sets or retrieves number of bins in the histogram. Sends :REDRAW-CONTENT message
if DRAW is true."
(HISTOGRAM-PROTO OBJECT :BIN-COUNTS)
"Args: ()
Returns list of the bin counts for the histogram."
;; SCATTERPLOT-PROTO
(SCATTERPLOT-PROTO OBJECT Proto) "Scatterplot"
(SCATTERPLOT-PROTO OBJECT :ADD-POINTS)
"Method args: (points &key point-labels (draw t))
or: (x y &key point-labels (draw t))
Adds points to plot. POINTS is a list of sequences,
POINT-LABELS a list of strings. If DRAW is true the new points
are added to the screen. For a 2D plot POINTS can be replaced
by two sequences X and Y."
(SCATTERPLOT-PROTO OBJECT :ADD-LINES)
"Method args: (lines &key type (draw t))
or: (x y &key point-labels (draw t))
Adds lines to plot. LINES is a list of sequences, the
coordinates of the line starts. TYPE is normal or dashed. If
DRAW is true the new lines are added to the screen. For a 2D
plot LINES can be replaced by two sequences X and Y."
;; Regular Functions
;; dialog
SYSBEEP
"Args (&optional (n 10))
Beep for 10 units."
NUM-TO-STRING
"Args (num)
Return string representation of NUM."
ABOUT-XLISP-STAT
"Args: ()
Show \About XLISP-STAT dialog on Macintosh, return NIL"
;; edit.c
OPEN-FILE-DIALOG
"Args ()
Present standard Macintosh Open File dialog; return file name string or NIL."
FRONT-WINDOW
"Args: ()
Macintosh. Return front window object, if it is an XLISP-STAT window, NIL otherwise."
HIDE-FRONT-WINDOW
"Args: ()
Hide the front window."
SYSTEM-EDIT
"
Args (item)
Check if edit selection is handled by a desk accessory. If so return T,
otherwise return NIL."
;; common
APROPOS
"Args: (string)
Prints symbols whose print-names contain STRING as substring.
If STRING is a symbol its print name is used."
APROPOS-LIST
"Args: (string)
Returns, as a list, all symbols whose print-names contain STRING as substring.
If STRING is a symbol its print name is used."
IDENTITY
"Args: (x)
Simply returns X."
MAKE-LIST
"Args: (size &key (initial-element nil))
Creates and returns a list containing SIZE elements, each of which is
initialized to INITIAL-ELEMENT."
ADJOIN
"Args: (item list &key (test #'eql) test-not (key #'identity))
Adds ITEM to LIST unless ITEM is already a member of LIST."
FILE-POSITION
"Args (stream &optional position)
Returns current position of file pointer in file stream STREAM. Sets
pointer to POSITION if supplied."
FORMAT
"Args: (destination control &rest args)
Very basic implementation of Common Lisp format function. Only A, S, D, F, E,
G, %, and ~ directives are supported. D, % and ~ can take one argument, R, E
and G can take two."
FORCE-OUTPUT
"Args: (&optional (stream *standard-output*))
Attempts to force any buffered output to be sent."
COPY-LIST
"Args: (list)
Returns a new copy of LIST."
COPY-SEQ
"Args: (sequence)
Returns a copy of SEQUENCE."
REDUCE
"Args: (function sequence &key initial-value)
Combines all the elements of SEQUENCE using a binary operation FUNCTION. If
INITIAL-VALUE is supplied it is logically placed before SEQUENCE."
MAP
"Args: (result-type function sequence &rest more-sequences)
FUNCTION must take as many arguments as there are sequences provided. RESULT-TYPE
must be the either the symbol VECTOR or the symbol LIST. The result is a
sequence of the specified type such that the i-th element of the result is the
result of applying FUNCTION to the i-th elements of the SEQUENCEs."
ELT
"Args: (a i)
Returns element I of sequence A. ELT can be used in setf."
COERCE
"Args: (x type)
Coerces X to an object of the type TYPE."
COMPLEXP
"Args: (x)
Returns T if X is a complex number; NIL otherwise."
COMPLEX
"Args: (realpart &optional (imagpart 0))
Returns a complex number with the given real and imaginary parts."
CONJUGATE
"Args: (number)
Returns the complex conjugate of NUMBER."
REALPART
"Args: (number)
Extracts the real part of NUMBER."
IMAGPART
"Args: (number)
Extracts the imaginary part of NUMBER."
DEFCONSTANT
"Syntax: (defconstant name initial-value [doc])
Declares that the variable NAME is a constant whose value is the value of
INITIAL-VALUE. If DOC is supplied it is saved as a VARIABLE doc."
DEFPARAMETER
"Syntax: (defparameter name initial-value [doc])
Sets variable NAME to INITIAL-VALUE. If DOC is supplied it is saved as a VARIABLE doc."
DEFVAR
"Syntax: (defvar name [initial-value [doc]])
Initializes variable NAME if it does not yet have a value. If DOC is supplied
it is saved as a VARIABLE doc."
MAKUNBOUND
"Args: (symbol)
Sets the function slot of SYMBOL to *UNBOUND*. Returns SYMBOL."
FMAKUNBOUND
"Args: (symbol)
Sets the value slot of SYMBOL to *UNBOUND*. Returns SYMBOL."
TIME
"Syntax: (time form)
Form is evaluated and its result returned. In addition the time required
for the evaluation is printed."
GETENV
"Args: ()
Returns current lexical environment."
GET-INTERNAL-REAL-TIME
"Args: ()
Returns the real time in the internal time format."
GET-INTERNAL-RUN-TIME
"Args: ()
Returns the run time in the internal time format."
CONCATENATE
"Args: (type &rest sequences)
Returns new sequence containing all elements of SEQUENCES in order."
SOME
"Args (pred &rest sequences)
Returns true if some elements of SEQUENCES satisfy PRED."
EVERY
"Args (pred &rest sequences)
Returns true if every element of SEQUENCES satisfy PRED."
NOTANY
"Args (pred &rest sequences)
Returns true if no element of SEQUENCES satisfies PRED."
NOTEVERY
"Args (pred &rest sequences)
Returns true if some element of SEQUENCES does not satisfy PRED."
UNION
"Args: (list1 list2 &key :test :test-not)
Returns list of all elements in either LIST1 or LIST2 or both."
INTERSECTION
"Args: (list1 list2 &key :test :test-not)
Returns list of all elements in both LIST1 and LIST2."
SET-DIFFERENCE
"Args: (list1 list2 &key :test :test-not)
Returns list of all elements in LIST1 but not in LIST2."
SUBSETP
"Args: (list1 list2 &key :test :test-not)
Returns T if all elements of LIST2 are in LIST1."
REMOVE-DUPLICATES
"Args: (list &key :test :test-not)
Returns copy of LIST without duplicate elements."
BUTLAST
"Args: (list &optional (n 1))
Returns copy of LIST with last N elements removed."
MAKE-STRING
"Args n &key initial-element)
Returns string of length N. Default INITIAL-ELEMENT is a blank."
FIND
"Args: (item list &key (test #'eql) test-not)
Returns the entry for item if there is one, or NIL."
POSITION
"Args: (item list &key (test #'eql) test-not)
Returns the position of item in LIST or NIL if it is not present."
;; commonarrays
ARRAYP
"Args: (x)
Returns T if X is an array; NIL otherwise."
ARRAY-IN-BOUNDS-P
"Args: (array &rest subscripts)
Returns T if SUBSCRIPTS are valid subscripts for ARRAY; NIL otherwise."
ARRAY-DIMENSIONS
"Args: (array)
Returns a list whose elements are the dimensions of ARRAY"
ARRAY-RANK
"Args: (array)
Returns the number of dimensions of ARRAY."
ARRAY-TOTAL-SIZE
"Args: (array)
Returns the total number of elements of ARRAY."
ARRAY-DIMENSION
"Args: (array)
Returns a list whose elements are the dimensions of ARRAY"
ARRAY-ROW-MAJOR-INDEX
"Args: (array &rest subscripts)
Returns the index into the data vector of ARRAY for the element of ARRAY
specified by SUBSCRIPTS."
AREF
"Args: (array &rest subscripts)
Returns the element of ARRAY specified by SUBSCRIPTS."
MAKE-ARRAY
"Args: (dimensions
&key initial-element (initial-contents nil)
(displaced-to nil))
Creates an array of the specified DIMENSIONS. The default for INITIAL-
ELEMENT depends on ELEMENT-TYPE."
;; distributions
BIVNORM-CDF
"Args: (x y r)
Returns the value of the standard bivariate normal distribution function
with correlation R at (X, Y). Vectorized."
NORMAL-CDF
"Args: (x)
Returns the value of the standard normal distribution function at X.
Vectorized."
BETA-CDF
"Args: (x alpha beta)
Returns the value of the Beta(ALPHA, BETA) distribution function at X.
Vectorized."
GAMMA-CDF
"Args: (x alpha)
Returns the value of the Gamma(alpha, 1) distribution function at X.
Vectorized."
CHISQ-CDF
"Args: (x df)
Returns the value of the Chi-Square(DF) distribution function at X. Vectorized."
T-CDF
"Args: (x df)
Returns the value of the T(DF) distribution function at X. Vectorized."
F-CDF
"Args: (x ndf ddf)
Returns the value of the F(NDF, DDF) distribution function at X. Vectorized."
CAUCHY-CDF
"Args: (x)
Returns the value of the standard Cauchy distribution function at X.
Vectorized."
LOG-GAMMA
"Args: (x)
Returns the log gamma function of X. Vectorized."
NORMAL-QUANT
"Args (p)
Returns the P-th quantile of the standard normal distribution. Vectorized."
CAUCHY-QUANT
"Args (p)
Returns the P-th quantile(s) of the standard Cauchy distribution. Vectorized."
BETA-QUANT
"Args: (p alpha beta)
Returns the P-th quantile of the Beta(ALPHA, BETA) distribution. Vectorized."
GAMMA-QUANT
"Args: (p alpha)
Returns the P-th quantile of the Gamma(ALPHA, 1) distribution. Vectorized."
CHISQ-QUANT
"Args: (p df)
Returns the P-th quantile of the Chi-Square(DF) distribution. Vectorized."
T-QUANT
"Args: (p df)
Returns the P-th quantile of the T(DF) distribution. Vectorized."
F-QUANT
"Args: (p ndf ddf)
Returns the P-th quantile of the F(NDF, DDF) distribution. Vectorized."
NORMAL-DENS
"Args: (x)
Returns the density at X of the standard normal distribution. Vectorized."
CAUCHY-DENS
"Args: (x)
Returns the density at X of the standard Cauchy distribution. Vectorized."
BETA-DENS
"Args: (x alpha beta)
Returns the density at X of the Beta(ALPHA, BETA) distribution. Vectorized."
GAMMA-DENS
"Args: (x alpha)
Returns the density at X of the Gamma(ALPHA, 1) distribution. Vectorized."
CHISQ-DENS
"Args: (x alpha)
Returns the density at X of the Chi-Square(DF) distribution. Vectorized."
T-DENS
"Args: (x alpha)
Returns the density at X of the T(DF) distribution. Vectorized."
F-DENS
"Args: (x ndf ddf)
Returns the density at X of the F(NDF, DDF) distribution. Vectorized."
UNIFORM-RAND
"Args: (n)
Returns a list of N uniform random variables from the range (0, 1).
Vectorized."
NORMAL-RAND
"Args: (n)
Returns a list of N standard normal random numbers. Vectorized."
CAUCHY-RAND
"Args: (n)
Returns a list of N standard Cauchy random numbers. Vectorized."
T-RAND
"Args: (n df)
Returns a list of N T(DF) random variables. Vectorized."
F-RAND
"Args: (n ndf ddf)
Returns a list of N F(NDF, DDF) random variables. Vectorized."
GAMMA-RAND
"Args: (n a)
Returns a list of N Gamma(A, 1) random variables. Vectorized."
CHISQ-RAND
"Args: (n df)
Returns a list of N Chi-Square(DF) random variables. Vectorized."
BETA-RAND
"Args: (n a b)
Returns a list of N beta(A, B) random variables. Vectorized."
;; ddistributions.c
BINOMIAL-CDF
"Args (x n p)
Returns value of the Binomial(N, P) distribution function at X. Vectorized."
POISSON-CDF
"Args (x mu)
Returns value of the Poisson(MU) distribution function at X. Vectorized."
BINOMIAL-PMF
"Args (k n p)
Returns value of the Binomial(N, P) pmf function at integer K. Vectorized."
POISSON-PMF
"Args (k mu)
Returns value of the Poisson(MU) pmf function at integer K. Vectorized."
BINOMIAL-QUANT
"Args: (x n p)
Returns x-th quantile (left continuous inverse) of Binomial(N, P) cdf.
Vectorized."
POISSON-QUANT
"Args: (x mu)
Returns x-th quantile (left continuous inverse) of Poisson(MU) cdf.
Vectorized."
BINOMIAL-RAND
"Args: (k n p)
Returns list of K draws from the Binomial(N, P) distribution. Vectorized."
POISSON-RAND
"Args: (k mu)
Returns list of K draws from the Poisson(MU) distribution. Vectorized."
;; linalg.c
LU-DECOMP
"Args: (a)
A is a square matrix of numbers (real or complex). Computes the LU
decomposition of A and returns a list of the form (LU IV D FLAG), where
LU is a matrix with the L part in the lower triangle, the U part in the
upper triangle (the diagonal entries of L are taken to be 1), IV is a vector
describing the row permutation used, D is 1 if the number of permutations
is odd, -1 if even, and FLAG is T if A is numerically singular, NIL otherwise.
Used bu LU-SOLVE."
LU-SOLVE
"Args: (lu b)
LU is the result of (LU-DECOMP A) for a square matrix A, B is a sequence.
Returns the solution to the equation Ax = B. Signals an error if A is singular."
DETERMINANT
"Args: (m)
Returns the determinant of the square matrix M."
INVERSE
"Args: (m)
Returns the inverse of the the square matrix M; signals an error if M is ill
conditioned or singular"
SV-DECOMP
"Args: (a)
A is a matrix of real numbers with at least as many rows as columns.
Computes the singular value decomposition of A and returns a list of the form
(U W V FLAG) where U and V are matrices whose columns are the left and right
singular vectors of A and W is the sequence of singular values of A. FLAG is T
if the algorithm converged, NIL otherwise."
QR-DECOMP
"Args: (a &optional pivot)
A is a matrix of real numbers with at least as many rows as columns. Computes
the QR factorization of A and returns the result in a list of the form (Q R).
If PIVOT is true the columns of X are first permuted to place insure the
absolute values of the diagonal elements of R are nonincreasing. In this case
the result includes a third element, a list of the indices of the columns in
the order in which they were used."
CHOL-DECOMP
"Args: (a)
Modified Cholesky decomposition. A should be a square, symmetric matrix.
Computes lower triangular matrix L such that L L^T = A + D where D is a diagonal
matrix. If A is strictly positive definite D will be zero. Otherwise D is as
small as possible to make A + D numerically strictly positive definite. Returns
a list (L (max D))."
RCONDEST
"Args: (a)
Returns an estimate of the reciprocal of the L1 condition number of an upper
triangular matrix a."
MAKE-ROTATION
"Args: (x y &optional alpha)
Returns a rotation matrix for rotating from X to Y, or from X toward Y
by angle ALPHA, in radians. X and Y are sequences of the same length."
SPLINE
"Args: (x y &key xvals)
Returns list of x and y values of natural cubic spline interpolation of (X,Y).
X must be strictly increasing. XVALS can be an integer, the number of equally
spaced points to use in the range of X, or it can be a sequence of points at
which to interpolate."
KERNEL-SMOOTH
"Args: (x y &key xvals width type)
Returns list of x and y values of kernel smooth of (X,Y). XVALS can be an
integer, the number of equally spaced points to use in the range of X, or it
can be a sequence of points at which to interpolate. WIDTH specifies the
window width. TYPE specifies the lernel and should be one of the symbols G, T,
U or B for Gaussian, triangular, uniform or bisquare. The default is B."
KERNEL-DENS
"Args: (x &key xvals width type)
Returns list of x and y values of kernel density estimate of X. XVALS can be an
integer, the number of equally spaced points to use in the range of X, or it
can be a sequence of points at which to interpolate. WIDTH specifies the
window width. TYPE specifies the lernel and should be one of the symbols G, T,
U or B for gaussian, triangular, uniform or bisquare. The default is B."
FFT
"Args: (x &optional inverse)
Returns unnormalized Fourier transform of X, or inverse transform if INVERSE
is true."
;; matrices1
MATMULT
"Args: (a b)
Returns the matrix product of matrices a and b. If a is a vector it is treated
as a row vector; if b is a vector it is treated as a column vector."
%*
"Args: (a b)
Returns the matrix product of matrices a and b. If a is a vector it is treated
as a row vector; if b is a vector it is treated as a column vector."
INNER-PRODUCT
"Args: (x y)
Returns inner product of sequences X and Y."
CROSS-PRODUCT
"Args: (x)
If X is a matrix returns (matmult (transpose X) X). If X is a vector returns
(inner-product X X)."
DIAGONAL
"Args: (x)
If X is a matrix, returns the diagonal of X. If X is a sequence, returns a
diagonal matrix of rank (length X) with diagonal elements eq to the elements
of X."
IDENTITY-MATRIX
"Args: (n)
Returns the identity matrix of rank N."
OUTER-PRODUCT
"Args: (x y &optional (fcn #'*))
Returns the generalized outer product of x and y, using fcn. Tat is, the result
is a matrix of dimension ((length x) (length y)) and the (i j) element of the
result is computed as (apply fcn (aref x i) (aref y j))."
ROW-LIST
"Args: (m)
Returns a list of the rows of M as vectors"
COLUMN-LIST
"Args: (m)
Returns a list of the columns of M as vectors"
BIND-ROWS
"Args (&rest args)
The ARGS can be matrices, vectors, or lists. Arguments are bound into a matrix
along their rows.
Example: (bind-rows #2a((1 2)(3 4)) #(5 6)) returns #2a((1 2)(3 4)(5 6))"
BIND-COLUMNS
"Args (&rest args)
The ARGS can be matrices, vectors, or lists. Arguments are bound into a matrix
along their columns.
Example: (bind-columns #2a((1 2)(3 4)) #(5 6)) returns #2a((1 2 5)(3 4 6))"
TRANSPOSE
"Args: (m)
Returns the transpose of the matrix M."
;; matrices2
MAKE-SWEEP-MATRIX
"Args: (x y &optional weights)
X is a matrix, Y and WEIGHTS are sequences. Returns the sweep matrix for the
(possibly weighted) regression of Y on X."
SWEEP-OPERATOR
"Args: (a indices &optional tolerances)
A is a matrix, INDICES a sequence of the column indices to be swept. Returns
a list of the swept result and the list of the columns actually swept. (See
MULTREG documentation.) If supplied, TOLERANCES should be a list of real
numbers the same length as INDICES. An index will only be swept if its pivot
element is larger than the corresponding element of TOLERANCES."
;; basics
SEQUENCEP
"Args: (x)
Returns T if X is a sequence, NIL otherwise."
COPY-VECTOR
"Args: (VECTOR)
Returns a copy of VECTOR with elements eq to the elements of VECTOR"
COPY-ARRAY
"Args: (array)
Returns a copy of ARRAY with elements eq to the elements of ARRAY."
SPLIT-LIST
"Args: (list cols)
Returns a list of COLS lists of equal length of the elements of LIST.
Example: (split-list '(1 2 3 4 5 6) 2) returns ((1 2 3) (4 5 6))"
WHICH
"Args: (x)
X is an array or a list. Returns a list of the indices where X is not NIL."
ISEQ
"Args: (n &optional m)
With one argumant returns a list of consecutive integers from 0 to N - 1.
With two returns a list of consecutive integers from N to M.
Examples: (iseq 4) returns (0 1 2 3)
(iseq 3 7) returns (3 4 5 6 7)
(iseq 3 -3) returns (3 2 1 0 -1 -2 -3)"
REPEAT
"Args: (vals times)
Repeats VALS. If TIMES is a number and VALS is a non-null, non-array atom, a list
of length TIMES with all elements eq to VALS is returned. If VALS is a list and
TIMES is a number then VALS is appended TIMES times. If TIMES is a list of numbers
then VALS must be a list of equal length and the simpler version of repeat is
mapped down the two lists.
Examples: (repeat 2 5) returns (2 2 2 2 2)
(repeat '(1 2) 3) returns (1 2 1 2 1 2)
(repeat '(4 5 6) '(1 2 3)) returns (4 5 5 6 6 6)
(repeat '((4) (5 6)) '(2 3)) returns (4 4 5 6 5 6 5 6)"
SAMPLE
"Args: (x n &optional (replace nil))
Returns a list of a random sample of size N from sequence X drawn with or
without replacement."
SELECT
"Args: (a &rest indices)
A can be a list or an array. If A is a list and INDICES is a single number
then the appropriate element of A is returned. If is a list and INDICES is
a list of numbers then the sublist of the corresponding elements is returned.
If A in an array then the number of INDICES must match the ARRAY-RANK of A.
If each index is a number then the appropriate array element is returned.
Otherwise the INDICES must all be lists of numbers and the corresponding
submatrix of A is returned. SELECT can be used in setf."
PERMUTE-ARRAY
"Args: (a p)
Returns a copy of the array A permuted according to the permutation P."
;; compound
COMPOUND-DATA-P
"Args: (x)
Returns T if X is a compound data item, NIL otherwise."
MAP-ELEMENTS
"Args: (function data &rest more-data)
FUNCTION must take as many arguments as there are DATA arguments supplied.
DATA arguments must either all be sequences or all be arrays of the same
shape. The result is of the same type and shape as the first DATA argument,
with elements the result of applying FUNCTION elementwise to the DATA
arguments"
COMPOUND-DATA-SEQ
"Args (x)
Returns data sequence in X."
COMPOUND-DATA-LENGTH
"Args (x)
Returns length of data sequence in X."
;; math.c
+
"Args: (&rest numbers)
Returns the sum of its arguments. With no args, returns 0. Vectorized."
-
"Args: (number &rest more-numbers)
Subtracts the second and all subsequent NUMBERs from the first. With one arg,
negates it. Vectorized."
*
"Args: (&rest numbers)
Returns the product of its arguments. With no args, returns 1. Vectorized."
/
"Args: (number &rest more-numbers)
Divides the first NUMBER (element-wise) by each of the subsequent NUMBERS.
With one arg, returns its reciprocal. Vectorized."
REM
"Args: (x y)
Returns the remainder of dividing x by y. Vectorized."
MOD
"Args: (x y)
Returns x mod y. Vectorized."
PMIN
"Args: (&rest items)
Parallel minimum of ITEMS. Vectorized."
PMAX
"Args: (&rest items)
Parallel maximum of ITEMS. Vectorized."
^
"Args: (base-number power-number)
Returns BASE-NUMBER raised to the power POWER-NUMBER. Vectorized."
**
"Args: (base-number power-number)
Returns BASE-NUMBER raised to the power POWER-NUMBER. Vectorized."
EXPT
"Args: (base-number power-number)
Returns BASE-NUMBER raised to the power POWER-NUMBER. Vectorized."
LOG
"Args: (number)
Returns the natural logarithm(s) of NUMBER. Vectorized."
ABS
"Args: (number)
Returns the absolute value or modulus of NUMBER. Vectorized."
1+
"Args: (number)
Returns NUMBER + 1. Vectorized."
1-
"Args: (number)
Returns NUMBER - 1. Vectorized."
SIN
"Args: (radians)
Returns the sine of RADIANS. Vectorized."
COS
"Args: (radians)
Returns the cosine of RADIANS. Vectorized."
TAN
"Args: (radians)
Returns the tangent of RADIANS. Vectorized."
EXP
"Args: (x)
Calculates e raised to the power x, where e is the base of natural
logarithms. Vectorized."
SQRT
"Args: (number)
Returns the square root of NUMBER. Vectorized."
TRUNCATE
"Args: (number)
Returns real NUMBER as an integer, rounded toward 0. Vectorized."
FLOAT
"Args: (number)
Converts real number to a floating-point number. If NUMBER is
already a float, FLOAT simply returns NUMBER. Vectorized."
RANDOM
"Args: (number)
Generates a uniformly distributed pseudo-random number between zero (inclusive)
and NUMBER (exclusive). Vectorized."
FLOOR
"Args: (number)
Returns the largest integer( not larger than the NUMBER. Vectorized."
CEILING
"Args: (number)
Returns the smallest integer(s) not less than or NUMBER. Vectorized."
ROUND
"Args: (number)
Rounds NUMBER to nearest integer. Vectorized."
ASIN
"Args: (number)
Returns the arc sine of NUMBER. Vectorized."
ACOS
"Args: (number)
Returns the arc cosine of NUMBER. Vectorized."
ATAN
"Args: (number)
Returns the arc tangent of NUMBER. Vectorized."
PHASE
"Args: (number)
Returns the angle part of the polar representation of a complex number.
For non-complex numbers, this is 0."
MINUSP
"Args: (number)
Returns T if NUMBER < 0; NIL otherwise. Vectorized."
ZEROP
"Args: (number)
Returns T if NUMBER = 0; NIL otherwise. Vectorized."
PLUSP
"Args: (number)
Returns T if NUMBER > 0; NIL otherwise. Vectorized."
EVENP
"Args: (integer)
Returns T if INTEGER is even. Returns NIL if INTEGER is odd. Vectorized."
ODDP
"Args: (integer)
Returns T if INTEGER is odd; NIL otherwise. Vectorized."
LOGAND
" Args: ({number}*)
Bit-wise logical AND of NUMBERs. Vectorized."
LOGIOR
" Args: ({number}*)
Bit-wise logical OR of NUMBERs. Vectorized."
" Args: ({number}*)
Bit-wise logical XOR of NUMBERs. Vectorized."
LOGNOT
"Args: (number)
Bit-wise logical NOT of NUMBER. Vectorized."
LOGXOR
"Args: (&rest integers)
Returns the bit-wise EXCLUSIVE OR of its arguments."
<
"Args: (&rest numbers)
Returns T if NUMBERS are in strictly increasing order; NIL otherwise.
Vectorized."
<=
"Args: (&rest numbers)
Returns T if NUMBERS are in nondecreasing order; NIL otherwise. Vectorized."
=
"Args: (&rest numbers)
Returns T if NUMBERS are all equal; NIL otherwise. Vectorized."
/=
"Args: (&rest numbers)
Returns T if NUMBERS no two adjacent numbers are equal; NIL otherwise. Vectorized."
>=
"Args: (&rest numbers)
Returns T if NUMBERS are in nonincreasing order; NIL otherwise. Vectorized."
>
"Args: (&rest numbers)
Returns T if NUMBERS are in strictly decreasing order; NIL otherwise. Vectorized."
;; objects
KIND-OF-P
"Args: (x y)
Returns T is X and Y are objects and X inherits from Y, NIL otherwise."
SLOT-VALUE
"Args: (slot &optional value)
Must be used in a method. Returns the value of current objects slot named SLOT.
If Value is supplied SLOT is set to VALUE. Can be used in setf."
MAKE-OBJECT
"Args: (&rest parents)
Returns a new object with parents PARENTS. If PARENTS is NIL (list *OBJECT*)
is used."
SEND
"Args: (object selector &rest args)
Applies first method for SELECTOR found in OBJECT's precedence list to
OBJECT and ARGS."
SEND-SUPER
"Args: (selector &rest args)
Apply inherited method. Must be used within a method. Specifically, Applies
first method for SELECTOR found in the cdr of the precedence list of the owner
of the current method to the current object and args."
CALL-METHOD
"Args (object selector &rest args)
Funcalls method for SELECTOR found in OBJECT to SELF. Can only be used in a method."
CALL-NEXT-METHOD
"Args (&rest args)
Funcalls next method for current selector and precedence list. Can only be used in a method."
DEFMETH
"Syntax: (defmeth object name lambda-list [doc] {form}*)
OBJECT must evaluate to an existing object. Installs a method for NAME in
the value of OBJECT and installs DOC in OBJECTS's documentation."
DEFPROTO
"Syntax (defproto name &optional ivars cvars (parent *object*) doc)
Makes a new object prototype with instance variables IVARS, 'class'
variables CVARS and parents PARENT. PARENT can be a single object or
a list of objects. IVARS and CVARS must be lists."
;; optimize
BRACKET-SEARCH
"Args: (f a b &key (max-iters 50) (verbose nil))
F is a real valued function of one argument, A and B are real numbers.
Tries to bracket a local minimum of f. Returns a list of the form
((A C B) (FA FC FB)), with A <= C <= B and FA = (f A) , etc. If the search
was successful then FC < min(FA, FB). Prints iteration information if
VERBOSE is not NIL."
GOLDEN-SEARCH
"Args: (f a b &key start (tolerance .000001) (verbose nil))
F is a real valued function of one argument, A and B are real numbers.
Uses a golden section search to locate the minimum of F. Convergence
occurs roughly when the change in X is less than tolerance * (1 + x).
Returns list of the form (X FX), with FX = (F X). Prints iteration
information if VERBOSE is not NIL."
PARABOLIC-SEARCH
"Args: (f a b &key start (tolerance .00001) (max-iters 100) (verbose nil))
F is a real valued function of one argument, A and B are real numbers.
Uses a hybrid parabolic approximation/golden section search to locate
the minimum of F. Convergence occurs roughly when the change in X is
less than tolerance * (1 + x). Returns list of the form (X FX N),
with FX = (F X) and N is the number of iterations. Prints iteration information
if VERBOSE is not NIL."
;; sortdata.c
SORT-DATA
"Args: (sequence)
Returns a sequence with the numbers or strings in the sequence X in order."
ORDER
"Args (x)
Returns a sequence of the indices of elements in the sequence of numbers
or strings X in order."
RANK
"Args (x)
Returns a sequence with the elements of the list or array of numbers or
strings X replaced by their ranks."
;; statistics.c
QUANTILE
"Args: (x p)
Returns the P-th quantile(s) of X. Vectorized on P."
SUM
"Args: (&rest number-data)
Returns the sum of all the elements of its arguments. Returns 0 if there
are no arguments. Vector reducing."
PROD
"Args: (&rest number-data)
Returns the product of all the elements of its arguments. Returns 1 if there
are no arguments. Vector reducing."
MIN
"Args: (number &rest more-numbers)
Returns the least of its arguments. Vector reducing"
MAX
"Args: (number &rest more-numbers)
Returns the greatest of its arguments. Vector reducing"
COUNT-ELEMENTS
"Args: (number &rest more-numbers)
Returns the number of its arguments. Vector reducing"
ELEMENT-SEQ
"Args: (x)
Returns sequence of the elements of compound item X."
IF-ELSE
"Args: (first x y)
Takes simple or compound data items FIRST, X and Y and returns result of
elementswise selecting from X if FIRST is not NIL and from Y otherwise."
MEAN
"Args: (x)
Returns the mean of the elements x. Vector reducing."
NUMGRAD
"Args: (f x &optional scale derivstep)
Computes the numerical gradient of F at X."
NUMHESS
"Args: (f x &optional scale derivstep)
Computes the numerical Hessian matrix of F at X."
;; uni
MAKE-RANDOM-STATE
"Args (&optional state)
If STATE is NIL or omitted returns a copy of the current value of
*random-state*. If STATE is a state object a copy of STATE is returned.
If STATE is T a new, \"randomly\" initialized state object is returned."
RANDOM-STATE-P
"Args (x)
Returns T if X can be used as a RANDOM-STATE."
;; windows
SCREEN-SIZE
"Args: ()
Returns list (WIDTH HEIGHT) of screen dimensions."
SCREEN-HAS-COLOR
"Args: ()
Returns T is system supports color, NIL otherwise."
;; xsiviewwindow.c
RESET-GRAPHICS-BUFFER
"Args: ()
Resets the graphics buffer."
;; xsiviewinternal
UNLINK-ALL-WINDOWS
"Args: ()
Unlinks all plots."
;; xsiview
GET-NICE-RANGE
"Args: (low high ticks)
Returns list of the form (LOW HIGH TICKS) that makes for nice tick marks."
;; xsgraphics
HISTOGRAM
"Args: (data &key (title \"Histogram\"))
Opens a window with a histogram of DATA. TITLE is the window title. The number
of bins used can be adjusted using the histogram menu. The histogram can be
linked to other plots with the link-views command. Returns a plot object."
PLOT-POINTS
"Args: (x y &key (title \"Scatter Plot\") variable-labels point-labels symbol color)
Opens a window with a scatter plot of X vs Y, where X and Y are compound
number-data. VARIABLE-LABELS and POINT-LABELS, if supplied, should be lists of
character strings. TITLE is the window title. The plot can be linked to
other plots with the link-views command. Returns a plot object."
PLOT-LINES
"Args: (x y &key (title \"Line Plot\") variable-labels type width color)
Opens a window with a connected line plot of X vs Y, where X and Y are
compound number-data. VARIABLE-LABELS, if supplied, should be lists of
character strings. TITLE is the window title. The plot can be linked to
other plots with the link-views command. Returns a plot object."
SPIN-PLOT
"Args: (data &key (title \"Spinning Plot\") variable-labels point-labels
(scale t))
DATA is a list of three compound number-data objects of equal length. Opens
a window with a rotating plot of the three elements of DATA. VARIABLE-LABELS
and POINT-LABELS, if supplied, should be lists of character strings. TITLE
is the window title. If scale is NIL data are assumed to be between -1 and 1.
The plot can be linked to other plots with the link-views command. Returns
a plot object."
SCATTERPLOT-MATRIX
"Args: (data &key (title \"Spinning Plot\") variable-labels point-labels
(scale t))
DATA is a list of two or more compound number-data objects of equal length.
Opens a window with a brushable scatter plot matrix of the elements of DATA.
VARIABLE-LABELS and POINT-LABELS, if supplied, should be lists of character strings.
TITLE is the window title. If scale is NIL data are assumed to be between -1
and 1.The plot can be linked to other plots with the link-views command.
Returns a plot object."
NAME-LIST
"Args: (names &key (title \"Name List\"))
NAMES is a number or a list of character strings. Opens a window with a list
of the supplied character strings or entries numbered from 0 to NAMES - 1.
This display can be linked to plots with the link-views function. Returns a
plot object."
BEST-CURSOR-SIZE
"Args: (&optional width height)
Returns list of best cursor width and height close to WIDTH and HEIGHT
to use on the active display. Only available under X11 windows."
PARSE-COLOR
"Args: (string)
Returns list of RGB values for STRING, an X11 color specification.
Only available under X11 windows."
FREE-COLOR
"Args: (symbol)
Frees the color associated with SYMBOL."
FREE-CURSOR
"Args: (symbol)
Frees the cursor associated with SYMBOL."
MAKE-COLOR
"Args: (symbol red green blue)
Allocates color specified by real fractinal RGB values and associates
it with SYMBOL."
MAKE-CURSOR
"Args: (symbol image &optional mask x-hot y-hot)
Allocates cursor and associates it with SYMBOL. IMAGE and MASK are matrices of
0's and 1's, x-hot and y-hot are integers representing the hot spot."