|
DataMuseum.dkPresents historical artifacts from the history of: DKUUG/EUUG Conference tapes |
This is an automatic "excavation" of a thematic subset of
See our Wiki for more about DKUUG/EUUG Conference tapes Excavated with: AutoArchaeologist - Free & Open Source Software. |
top - metrics - downloadIndex: T l
Length: 51486 (0xc91e) Types: TextFile Names: »lispref-4«
└─⟦a05ed705a⟧ Bits:30007078 DKUUG GNU 2/12/89 └─⟦c06c473ab⟧ »./UNRELEASED/lispref.tar.Z« └─⟦1b57a2ffe⟧ └─⟦this⟧ »lispref-4«
Info file: lispref, -*-Text-*- produced by texinfo-format-buffer from file: lispref.texinfo This file documents GNU Emacs Lisp. This is Edition 0.1 Beta of the GNU Emacs Lisp Reference Manual, for Emacs Version 18, with some references to Emacs Version 19. Please read this document for review purposes. Published by the Free Software Foundation, 675 Massachusetts Avenue, Cambridge, MA 02139 USA Copyright (C) 1989 Free Software Foundation, Inc. Permission is granted to make and distribute verbatim copies of this manual provided the copyright notice and this permission notice are preserved on all copies. Permission is granted to copy and distribute modified versions of this manual under the conditions for verbatim copying, provided that the entire resulting derived work is distributed under the terms of a permission notice identical to this one. Permission is granted to copy and distribute translations of this manual into another language, under the above conditions for modified versions, except that this permission notice may be stated in a translation approved by the Foundation. ▶1f◀ File: lispref Node: Sequences Arrays Vectors, Prev: Lists, Up: Top, Next: Symbols Sequences, Arrays, and Vectors ****************************** Two supertypes are described in this chapter, sequences and arrays. The primitive type, vector, is also described here. Recall that the "sequence" type is a supertype of three other Lisp types: lists, vectors, and strings. In other words, any list is a sequence, any vector is a sequence, and any string is a sequence. The common property that all sequences have is that each is an ordered collection of elements. An "array" is a sequence in which all element is accessible in constant time, and whose length cannot be changed. Both strings and vectors are arrays. A list is not an array because the elements of a list are not all accessible in constant time; in fact, the access time of an element of a list is proportional to its position in the list. The following diagram shows the relationship between all these types. ___________________________________ | | | Sequence | | ______ ______________________ | | | | | | | | | List | | Array | | | | | | ________ _______ | | | |______| | | | | | | | | | | String | | Vector| | | | | |________| |_______| | | | |______________________| | |___________________________________| The Relationship between Sequences, Arrays, and Vectors The elements of vectors and lists may be any Lisp objects. The elements of strings are all characters. * Menu: * Sequence Functions:: * Arrays:: * Vectors:: ▶1f◀ File: lispref Node: Sequence Functions, Prev: Sequences Arrays Vectors, Up: Sequences Arrays Vectors, Next: Arrays Sequences ========= In Emacs Lisp, a "sequence" is either a list, a vector or a string. The common property that all sequences have is that each is an ordered collection of elements. This section describes functions that accept any kind of sequence. * Function: sequencep OBJECT Returns `t' if OBJECT is a list, vector, or string, `nil' otherwise. * Function: copy-sequence SEQUENCE Returns a copy of SEQUENCE. The copy is the same type of object as the original sequence, and it has the same elements in the same order. Storing a new element into the copy does not affect the original SEQUENCE, and vice versa. However, the elements of the new sequence are not copies; they are identical (`eq') to the elements of the original. Therefore, changes made within these elements, as found via the copied sequence, are also visible in the original sequence. See also `append' in *Note Building Cons Cells and Lists::, and `concat' in *Note Creating Strings::, for others ways to copy sequences. (setq bar '(1 2)) => (1 2) (setq x (vector 'foo bar)) => [foo (1 2)] (setq y (copy-sequence x)) => [foo (1 2)] (eq x y) => nil (equal x y) => t (eq (elt x 1) (elt y 1)) => t ;; Replacing an element of one sequence. (aset x 0 'quux) x => [quux (1 2)] y => [foo (1 2)] ;; Modifying the inside of a shared element. (setcar (aref x 1) 69) x => [quux (69 2)] y => [foo (69 2)] * Function: length SEQUENCE Returns the number of elements in SEQUENCE. If SEQUENCE is a cons that is not a list (the final CDR is not `nil'), a `wrong-type-argument' error results. (length '(1 2 3)) => 3 (length nil) => 0 (length "foobar") => 6 (length [1 2 3]) => 3 * Function: elt SEQUENCE INTEGER This function returns the element of SEQUENCE indexed by INTEGER. Legitimate values of INTEGER range from 0 up to one less than the length of SEQUENCE; other values produce an `args-out-of-range' error. (elt [1 2 3 4] 2) => 3 (elt '(1 2 3 4) 2) => 3 (char-to-string (elt "1234" 2)) => "3" (elt [1 2 3 4] 4) error-->Args out of range: [1 2 3 4], 4 (elt [1 2 3 4] -1) error-->Args out of range: [1 2 3 4], -1 This function duplicates `aref' (*Note Arrays::) and `nth' (*Note Accessing Elements of Lists: List Elements.), except that it works for any kind of sequence. ▶1f◀ File: lispref Node: Arrays, Prev: Sequence Functions, Up: Sequences Arrays Vectors, Next: Vectors Arrays ====== Arrays in Lisp, like arrays in most languages, are blocks of memory whose elements can be accessed in equal time. All Emacs Lisp arrays are single dimensional and zero-based (their first element is indexed with zero). Emacs Lisp provides two kinds of arrays, distinguished by what kinds of element they can contain. A "vector" is a general array; its elements can be any Lisp objects. A "string" is a specialized array; its elements must be characters (i.e., integers between 0 and 255). In principle, if you wish to have an array of characters, you could use either a string or a vector. In practice, we always choose strings for such applications, for three reasons: * They occupy one fourth the space of a vector. * Strings are printed in a way that shows the contents more clearly as characters. * Many of the specialized editing and I/O facilities of Emacs accept only strings. For example, you cannot insert a vector of characters into a buffer the way you can insert a string. *Note Strings and Characters::. In this section, we describe the functions that accept both strings and vectors. * Function: arrayp OBJECT This function returns `t' if the object is an array (i.e., either a vector or a string). (arrayp [a]) => t (arrayp "asdf") => t * Function: aref ARRAY INTEGER This function returns the INTEGER'th element of the ARRAY The first element is indexed with zero. In the example, the character `b' is ASCII code 98. (setq primes [2 3 5 7 11 13]) => [2 3 5 7 11 13] (aref primes 4) => 11 (aref "abcdefg" 1) => 98 (elt primes 4) => 11 See also the function `elt', in *Note Sequence Functions::. * Function: aset ARRAY INTEGER OBJECT This function sets the INTEGER'th element of ARRAY to be OBJECT. It returns OBJECT. (setq w [foo bar baz]) => [foo bar baz] (aset w 0 'fu) => fu w => [fu bar baz] (setq x "asdfasfd") => "asdfasfd" (aset x 3 ?Z) => 90 x => "asdZasfd" If ARRAY is a string and OBJECT is not a character, a `wrong-type-argument' error results. * Function: fillarray ARRAY OBJECT This function fills the array with pointers to OBJECT, replacing any previous values. It returns ARRAY. (setq a [a b c d e f g]) => [a b c d e f g] (fillarray a 0) => [0 0 0 0 0 0 0] a => [0 0 0 0 0 0 0] (setq s "When in the course") => "When in the course" (fillarray s ?-) => "------------------" If ARRAY is a string and OBJECT is not a character, a `wrong-type-argument' error results. The general sequence functions `copy-sequence' and `length' are often useful for objects known to be arrays. *Note Sequence Functions::. ▶1f◀ File: lispref Node: Vectors, Prev: Arrays, Up: Sequences Arrays Vectors Vectors ======= Arrays in Lisp, like arrays in most languages, are blocks of memory whose elements can be accessed in constant time. A "vector" is a general-purpose array; its elements can be any Lisp objects. (The other kind of array provided in Emacs Lisp is the "string", whose elements must be characters.) The main uses of vectors in Emacs are as syntax tables (vectors of integers), keymaps (vectors of commands), and inside of compiled functions. The elements of a vector are numbered starting with zero in Emacs Lisp. Vectors are printed with square brackets surrounding the elements in their order. Thus, a vector containing the symbols `a', `b' and `c' is printed as `[a b c]'. You can write vectors in the same way in Lisp input. A vector, like a string or a number, is considered a constant: the result of evaluating it is the same vector. The elements of the vector are not evaluated. Here are examples of these principles: (setq avector [1 two '(three) "four" [five]]) => [1 two (quote (three)) "four" [five]] (eval avector) => [1 two (quote (three)) "four" [five]] (eq avector (eval avector)) => t Here are some functions that relate specifically to vectors: * Function: vectorp OBJECT This function returns `t' if the object is a vector. (vectorp [a]) => t (vectorp "asdf") => nil * Function: vector &rest OBJECTS This function returns a vector whose elements are the arguments, OBJECTS. (vector 'foo 23 [bar baz] "rats") => [foo 23 [bar baz] "rats"] (vector) => [] * Function: make-vector INTEGER OBJECT This function returns a new vector consisting of INTEGER elements, all initialized to OBJECT. (setq sleepy (make-vector 9 'Z)) => [Z Z Z Z Z Z Z Z Z] * Function: vconcat &rest SEQUENCES This function returns a new vector containing all the elements of the arguments, SEQUENCES. These arguments may be lists, vectors, or strings; they may also be integers. If no SEQUENCES are given, an empty vector is returned. The value is a newly constructed vector which is not `eq' to any existing vector. (setq a (vconcat '(A B C) '(D E F))) => [A B C D E F] (eq a (vconcat a)) => nil (vconcat) => [] As a special feature, if one of the SEQUENCES is an integer (not a sequence of integers), it is first converted to the string of digits making up the decimal print representation of the integer. In the second example below, the number 123 is divided into three digits. Note that the ASCII code of the character `1' is 49, and that of `a' is 97. (vconcat [A B C] 123 "aa" '(foo (6 7))) => [A B C 49 50 51 97 97 foo (6 7)] For other concatenation functions, `mapconcat' in *Note Mapping Functions::, `concat' in *Note Creating Strings::, and `append' in *Note Building Cons Cells and Lists::. The `append' function may be used to convert a vector into a list with the same elements (*Note Building Cons Cells and Lists::): (append avector nil) => (1 two (quote (three)) "four" [five]) ▶1f◀ File: lispref Node: Symbols, Prev: Sequences Arrays Vectors, Up: Top, Next: Variables Symbols ******* This chapter describes how symbols may be used, what the components of symbols are, and how symbols are created and interned. Property lists are also described here. A "symbol" is a unique name which may be used in several ways simultaneously. These are listed below with references to were these uses are described. * A symbol can be used simply as a unique entity. *Note Creating and Interning Symbols:: * A symbol can be used as a global variable. *Note Global Variables:: * A symbol can be used as a local variable. *Note Local Variables:: * A symbol can be used to reference a function or macro. *Note Functions::, and *Note Macros::. * A symbol can be used to reference a property list of global information. *Note Property Lists:: You may test whether an arbitrary Lisp object is a symbol with `symbolp'. * Function: symbolp OBJECT This function returns `t' if OBJECT is a symbol, `nil' otherwise. * Menu: * Symbol Components:: * Definitions and Declarations:: * Creating and Interning Symbols:: * Property Lists:: * Lisp Symbol Completion:: ▶1f◀ File: lispref Node: Symbol Components, Prev: Symbols, Up: Symbols, Next: Definitions and Declarations Symbol Components ================= To support the above mentioned uses, each symbol has four components (or attributes or cells), each of which references another object. The print name cell is described elsewhere (*Note Symbol Type::). One essential aspect of symbols is that a symbol with a given print name is unique: no other symbol can have the same print name. The Lisp reader ensures that every time it reads a name, it looks for an existing symbol with that name before it creates a new one. (In GNU Emacs Lisp, this is done with a hashing algorithm that uses an obarray; *Note Creating and Interning Symbols::.) The other three cells of a symbol *may* reference any Lisp object whatsoever. In normal usage, if the symbol is used as the name of a function, the function cell usually contains a reference to a function as that is what the Lisp interpreter expects to see there. (*Note Evaluation::.) Keyboard macros (*Note Keyboard Macros::) and keymaps (*Note Keymaps::) may also be stored in the function cell of symbols. Likewise, the property list cell normally references a correctly formatted property list (*Note Property Lists::), as a number of functions will expect to see a property list there. The value cell contains the symbol's global value, if any, and that may be any Lisp object (*Note Global Variables::). Quite often, we will refer to the function `foo' when we really mean the function referenced by the function cell of the symbol `foo'. Similarly for the value cell and property list cell. The distinction will only be made when necessary. Here is a summary of the components of a symbol. Name The string of characters used to identify the symbol when reading or printing. See `symbol-name' in *Note Creating and Interning Symbols::. Value The global value of a symbol. See `symbol-value' in *Note Accessing Variables::. Function The function that is called when the symbol appears in the function position of a form being evaluated, or as the first argument to `funcall', `apply', etc. This cell is also used by keymaps and keyboard macros. See `symbol-function' in *Note Function Cells::. Property List The property list is used by several functions to look up values that are associated with the symbol and a property symbol. See `symbol-plist' in *Note Property Lists::. ▶1f◀ File: lispref Node: Definitions and Declarations, Prev: Symbol Components, Up: Symbols, Next: Creating and Interning Symbols Definitions and Declarations ============================ A "definition" or "declaration" is a special form that establishes a relationship between a symbol and some object. There are four definition constructs in GNU Emacs Lisp. `defvar' and `defconst' as definitions both establish a symbol as a global variable. As "declarations", they serve only to inform the person reading the code of the intended use of a symbol, and do not in any way affect whether the global value may be changed. `defvar' and `defconst' are documented in *Note Variables::. `defun' and `defmacro' definitions create `lambda' and `macro' expressions respectively and bind them to the function cell value of the symbol being defined. `defun' and `defmacro' are documented in separate chapters (*Note Functions:: and *Note Macros::). In GNU Emacs Lisp, definitions serve several purposes. First, they inform the user who reads the code that certain constructs (typically variables or functions) are *intended* to be used in the specified ways. Utilities such as `etags' and `make-docfile' can recognize these declarations also, and add the appropriate information to tag tables and the `etc/DOC' file. Second, they inform Lisp of the same thing, allowing it to ensure that the desired uses are made possible. Common Lisp Note: In most Lisp systems, declarations supply information to the compiler, allowing it to output more optimal code than would otherwise be possible. The GNU Emacs Lisp compiler does not presently make use of any declarations to optimize code. ▶1f◀ File: lispref Node: Creating and Interning Symbols, Prev: Definitions and Declarations, Up: Symbols, Next: Property Lists Creating and Interning Symbols ============================== To understand how symbols are created in GNU Emacs Lisp, it is necessary to know how Lisp reads them. It is essential to ensure that every time Lisp reads the same set of characters, it finds the same symbol. Failure to do so would be disastrous. When the Lisp reader encounters a symbol, it reads in all the characters in a name. Then it ``hashes'' those characters into a vector called an "obarray". Hashing is just an efficient method of looking something up. Instead of searching a telephone book cover to cover when looking up Jan Jones, you start with the `J's and go from there. That is a simple version of hashing. A number of symbols might all hash to the same element in that obarray, that is, they hash to the same "bucket", and Lisp just looks through the bucket to see if one of the symbols has the name in question. If such a symbol is found, then it is returned. If no such symbol is found, then a new symbol is created and added to the obarray. Adding a symbol to an obarray is called "interning" it, and the symbol may then be called an "interned symbol". A symbol may be interned in only one obarray. If a symbol is not in an obarray, then there is no way for Lisp ever to find it when its name is read. Such a symbol is called an "uninterned symbol" relative to the obarray. An uninterned symbol has all the other properties of symbols. It is possible, though uncommon, for two different symbols to have the same name in different obarrays; they are not `eq' or `equal'. The functions below all take a name and sometimes an obarray as arguments. It is a `wrong-type-argument' error if the name is not a string, or if the obarray is not a vector. * Function: symbol-name SYMBOL This function returns the string that is SYMBOL's name. Changing the name cell of a symbol will change the name of the symbol. Changing the string by substituting characters, etc, will also change the name of the symbol. Don't do either of these things. Rather, create a new symbol with the desired name. (symbol-name 'foo) => "foo" * Function: make-symbol NAME Return a newly allocated uninterned symbol whose name is NAME (which must be a string). Its value and function definition are void, and its property list is `nil'. In the example below, the value of `sym' is not `eq' to `foo' because the string was not interned. (setq sym (make-symbol "foo")) => foo (eq sym 'foo) => nil * Function: intern NAME &optional OBARRAY This function returns the symbol whose name is NAME. If the symbol is not in the obarray, it is added. If OBARRAY is supplied, it specifies the obarray to use; otherwise the value of the global variable `obarray' is used. (setq sym (intern "foo")) => foo (eq sym 'foo) => t * Function: intern-soft NAME &optional OBARRAY This function returns the symbol whose name is NAME, or `nil' if a symbol with that name is not found in the obarray. Therefore, you can use `intern-soft' to test whether a symbol with a given name is interned. If OBARRAY is supplied, it specifies the obarray to use; otherwise the value of the global variable `obarray' is used. (intern-soft "frazzle") ; No such symbol exists. => nil (make-symbol "frazzle") ; Create an uninterned one. => frazzle (intern-soft "frazzle") ; That one cannot be found. => nil (setq sym (intern "frazzle")) ; Create an interned one. => frazzle (intern-soft "frazzle") ; That one can be found! => frazzle (eq sym 'frazzle) ; And it is the same one. => t * Variable: obarray This global variable is the standard obarray for use by `intern' and `read'. It is a vector whose length ought to be prime for best results (presently 511). Each element is an interned symbol whose name hashes to that bucket. That symbol (if any) has an internal link (invisible to the user) to the next symbol that hashes to that bucket. The order of symbols in a bucket is unimportant. * Function: mapatoms FUNCTION &optional OBARRAY This function applies FUNCTION to every symbol in OBARRAY. It returns `nil'. If OBARRAY is not supplied, it defaults to the value of `obarray'; the normal obarray of all symbols. See `documentation' in *Note Documentation Strings::, for another example using `mapatoms'. (setq count 0) => 0 (defun count-syms (s) (setq count (1+ count))) => count-syms (mapatoms 'count-syms) => nil count => 1871 ▶1f◀ File: lispref Node: Property Lists, Prev: Creating and Interning Symbols, Up: Symbols, Next: Lisp Symbol Completion Property Lists ============== A "property list" ("plist" for short) is a list of paired elements stored in the property list cell of a symbol. Each of the pairs associate a property name (usually a symbol) with some property or value. Property lists are generally used to record information about a symbol, such as the name of the file in which it received a function definition in, or the grammatical class the name of the symbol belongs in a language understanding system. The property names (or keys) and property values may be any Lisp objects. The property names are compared using `eq'. Association lists (*Note Association Lists::) are very similar to property lists. But unlike association lists, the order in which the pairs of elements occur is not important since each property name can appear only once in the property list (as a key). Thus a property list is usually more space efficient than an association list. Another factor in favor of using a property list is that it is quickly accessable through the global symbol while an association list may be stored as a variable value which is accessed by a search up the run-time stack. There are several reasons for using an association list over a property list. Depending on your application, it may be faster to add a pair to the front of an association list than to update a property. All properties for a symbol are stored in the same property list, so there is a possibility of a conflict between different uses of a property name. (For this reason, it is best to name properties in some unique fashion such as including the name of your extension package in the property name.) An association list may be used like a stack where pairs are pushed on the top of the stack and later popped off; this is not possible with a property list. * Function: symbol-plist SYMBOL Returns the property list of the SYMBOL. A property list is a list in which the odd numbered elements are the property names and the even numbered elements are the properties or associated values. You should *not* use this function to get access to the property list for the purpose of altering it. (See the example for `setplist'). * Function: setplist SYMBOL PLIST This function sets SYMBOL's property list to PLIST. PLIST should be a well-formed property list, although this condition is not checked for. (setplist 'foo '(a 1 b (2 3) c nil)) => (a 1 b (2 3) c nil) (symbol-plist 'foo) => (a 1 b (2 3) c nil) * Function: get SYMBOL KEY This function gets KEY from SYMBOL's property list. If SYMBOL has such a key, the associated value is returned. If there is no such key, `nil' is returned. Thus, there is no distinction between an associated value of `nil' and the absence of the key. KEY is compared with the property names using `eq', so any object is legitimate. See `put' for example. * Function: put SYMBOL KEY VALUE This function puts VALUE onto SYMBOL's property list under the property name KEY, replacing any previous value. (Emacs oriented example needed here!!) (put 'fly 'verb 'transitive) =>'transitive (put 'fly 'noun '(a buzzing little bug)) => (a buzzing little bug) (get 'fly 'verb) => transitive (symbol-plist 'fly) => (verb transitive noun (a buzzing little bug)) ▶1f◀ File: lispref Node: Lisp Symbol Completion, Prev: Property Lists, Up: Symbols Lisp Symbol Completion ====================== If you type a part of a symbol, and then type `M-TAB' (`lisp-complete-symbol', Emacs will attempt to return as much of the name of the symbol that it can. Not only does this save typing, but it can help you with the name of a symbol that you partially forgot. For more on completion, *Note Completion::. * Command: lisp-complete-symbol This function performs completion on the symbol preceding point. That symbol is completed against the symbols in the global variable `obarray', inserting characters from the completion into the buffer. If there is more than one completion, a list of all possible completions is placed in the `*Help*' buffer. It is an error if there is no possible completion in `obarray'. If the symbol starts just after the character `(', only symbols with function definitions will be considered. Otherwise, symbols with any of a function definition, value, or property will be considered. `lisp-complete-symbol' returns `t' if the symbol had an exact, and unique, match; otherwise, it returns `nil'. In the example, the user already inserted `(forwa' into the buffer `foo.el'. `lisp-complete-symbol' is then invoked, and completes the function call to `(forward-'. ---------- Buffer: foo.el ---------- (forwa-!- ---------- Buffer: foo.el ---------- (lisp-complete-symbol) => nil ---------- Buffer: foo.el ---------- (forward--!- ---------- Buffer: foo.el ---------- ▶1f◀ File: lispref Node: Variables, Prev: Symbols, Up: Top, Next: Functions Variables ********* A "variable" is a name used in a program to stand for a value. Nearly all programming languages have variables of some sort in the textual representation of the program. In a Lisp program in textual form, variables are written like symbols. In Lisp, unlike most programming languages, programs are not merely text; they have a textual form, and a form as clusters of Lisp objects. When a Lisp program is in the form of Lisp objects, the object that represents a variable is a symbol (*Note Symbols::). Therefore, when a Lisp program is written as text, the variables are written just as symbols are written. The current value of a variable always resides in the symbol's value cell (*Note Symbol Components::). * Menu: * Global Variables:: * Void Variables:: * Defining Variables:: * Accessing Variables:: * Setting Variables:: * Local Variables:: * Variable Resolution:: * Buffer Local Variables:: * Default Value:: ▶1f◀ File: lispref Node: Global Variables, Prev: Variables, Up: Variables, Next: Constant Variables Global Variables ================ The simplest way to use a variable is "globally". This means that the variable has just one value at a time, and this value is in effect (until replaced with another value) throughout the Lisp system. After a new value replaces the old one, no memory of the old value remains. You give the symbol its value with `setq'. For example, (setq x '(a b)) gives the variable `x' the value `(a b)'. Note that the first argument of `setq', the name of the variable, is not evaluated; but the second argument, the desired value, is evaluated normally. Once you have done this, you can refer to the variable by using the symbol by itself as an expression. Thus, x => (a b) assuming the `setq' form shown above has already been executed. If you do another `setq', the new value replaces the old one. x => (a b) (setq x 4) => 4 x => 4 ▶1f◀ File: lispref Node: Constant Variables, Prev: Global Variables, Up: Variables, Next: Local Variables Variables that Never Change =========================== Emacs Lisp has two special symbols, `nil' and `t', that always evaluate to themselves. These symbols cannot be rebound, nor can their value cells be changed. An attempt to change the value results in a `setting-constant' error. nil == 'nil => nil (setq nil 500) error--> Attempt to set constant symbol: nil ▶1f◀ File: lispref Node: Local Variables, Prev: Constant Variables, Up: Variables, Next: Void Variables Local Variables =============== Global variables are given values that last until explicitly superseded with new values. Sometimes it is useful to create variable values that exist temporarily---only until exit from a certain part of the program. These values are called "local", and the variables so used are called "local variables". For example, when a function is called, its argument variables receive new local variables which last until the function exits. The `let' special form explicitly establishes new local values for specified variables; these last until exit from the `let' form. If you set the variable with `setq' or `set' while a local value is in effect, this replaces the local value; it does not alter the global value, or previous local values which are not currently visible. To model this behavior, we speak of a "local binding" of the variable as well as a local value. The local binding is a place that holds a local value. Function calling, or `let', creates the local binding; exit from the function or from the `let' removes the local binding. As long as the local binding lasts, the variable's value is stored within it. Use of `setq' or `set' while there is a local binding stores a different value into the local binding; it does not create a new binding. We also speak of the global binding, which is where (conceptually) the global value is kept. A variable can have more than one local binding at a time (for example, if there are nested `let' forms that bind it). In such a case, the most recently created local binding that still exists is the "current binding" of the variable. If there are no local bindings, the variable's current binding is its global binding. Ordinary evaluation of a symbol always returns the value of its current binding. Sometimes we call the current binding the "most-local existing binding", for emphasis. The special forms `let' and `let*' exist specifically to create local bindings. * Special form: let (BINDINGS...) FORMS... This function binds variables according to BINDINGS and then evaluates all of the FORMS in textual order. The `let'-form returns the value of the last form in FORMS. Each of the BINDINGS is either (i) a symbol, in which case that symbol is bound to `nil'; or (ii) a list of the form `(SYMBOL FORM)', in which case SYMBOL is bound to the result of evaluating FORM (FORM may be omitted, in which case `nil' is used). All of the FORMs in BINDINGS are evaluated in the order they appear and *before* any of the symbols are bound. The example illustrates this: `Z' is bound to the old value of `Y', which is 2, not the new value, 1. (setq Y 2) => 2 (let ((Y 1) (Z Y)) (list Y Z)) => (1 2) * Special form: let* (BINDINGS...) FORMS... This special form is like `let', except that the symbols in BINDINGS are bound as they are encountered before the remaining forms are evaluated. Therefore, an expression in the BINDINGS may reasonably refer to symbols already bound by this BINDINGS. Compare the following example with the example above for `let'. (setq Y 2) => 2 (let* ((Y 1) (Z Y)) ; Use the just-established value of `Y'. (list Y Z)) => (1 1) Here is a complete list of the other situations which create local bindings: * Function calls (*Note Functions::). * Macro calls (*Note Macros::). * `condition-case' (*Note Errors::). The number of local variable bindings at any given time, of all variables combined, is limited to the value of `max-specpdl-size' (*Note Eval::). This limit is designed to catch infinite recursions. If it gets in your way, you can set it as large as you like. ▶1f◀ File: lispref Node: Void Variables, Prev: Local Variables, Up: Variables, Next: Defining Variables When a Variable is ``Void'' =========================== If you have never given a symbol any value as a global variable, we say that that symbol's value is "void". In other words, the symbol's value cell does not have any Lisp object in it. If you try to evaluate this symbol, the result is a `void-variable' error. Note that a value of `nil' is not the same as void. The symbol `nil' is a Lisp object and can be the value of a variable just as any other object can be; but it is *a value*. A void variable does not have any value. After you have given a variable a value, you can make it void once more using `makunbound'. * Function: makunbound SYMBOL This function makes the current binding of SYMBOL void. This causes a future attempt to use this symbol as a variable to signal the error `void-variable', unless or until you set it again. `makunbound' returns SYMBOL. (makunbound 'x) ; Make the global value of `x' void. => x x error--> Symbol's value as variable is void: x If SYMBOL is locally bound, `makunbound' affects the most local existing binding. This is the only way a symbol can have a void local binding, since all the constructs that create local bindings create them with values. In this case, the voidness lasts at most as long as that binding does; when the binding is removed due to exit from the construct that made it, the previous or global binding is reexposed as usual, and the variable is no longer void unless the newly reexposed binding was void all along. (setq x 1) ; Put a value in the global binding. => 1 (let ((x 2)) ; Locally bind it. (makunbound 'x) ; Void the local binding. x) error--> Symbol's value as variable is void: x x ; The global binding is unchanged. => 1 (let ((x 2)) ; Locally bind it. (let ((x 3)) ; And again. (makunbound 'x) ; Void the innermost-local binding. x)) ; And refer: it's void. error--> Symbol's value as variable is void: x (let ((x 2)) (let ((x 3)) (makunbound 'x)) ; Void inner binding, then remove it. x) ; Now outer `let' binding is visible. => 2 A symbol that has been made void with `makunbound' is indistinguishable as a variable from one that has never received a value and has always been void. You can use the function `boundp' to test whether a symbol is currently void. * Function: boundp SYMBOL `boundp' returns `t' if SYMBOL is not void; to be more precise, if its current binding is not void. It returns `nil' otherwise. (boundp 'abracadabra) ; Starts out void. => nil (let ((abracadabra 5)) ; Locally bind it. (boundp 'abracadabra)) => t (boundp 'abracadabra) ; Still globally void. => nil (setq abracadabra 5) ; Make it globally nonvoid. => 5 (boundp 'abracadabra) => t ▶1f◀ File: lispref Node: Defining Variables, Prev: Void Variables, Up: Variables, Next: Accessing Variables Defining Global Variables ========================= You may declare your intention to use a symbol as a global variable with `defconst' or `defvar'. In GNU Emacs Lisp, definitions serve three purposes. First, they inform the user who reads the code that certain symbols are *intended* to be used as variables. Second, they inform the Lisp system of these things, supplying a value and documentation. Third, they provide information to utilities such as `etags' and `make-docfile', which create data bases of the functions and variables in a program. The difference between `defconst' and `defvar' is primarily a matter intent, of interest to human readers, but it also makes a difference for initialization. Emacs Lisp does not restrict the ways in which a variable can be used based on `defconst' or `defvar' declarations. A user-option defined in a library that is not loaded into Emacs by default should be defined with `defvar', so that the user can give his own value to the variable before loading the library. If `defconst' were used to define the user option, loading the library would always override any previous value of the variable. * Special form: defvar SYMBOL [VALUE [DOC-STRING]] This special form informs a person reading your code that SYMBOL will be used as a variable that the programs are likely to set or change. It is also used for all user-option variables except in the preloaded parts of Emacs. Note that SYMBOL is not evaluated; the symbol to be defined must appear explicitly in the `defconst'. If SYMBOL already has a value (i.e. it is not void), VALUE is not even evaluated, and SYMBOL's value remains unchanged. If SYMBOL is void and VALUE is specified, it is evaluated and SYMBOL is set to the result. (If VALUE is not specified, the value of SYMBOL is never changed.) The `defvar' form returns SYMBOL, but it is normally used at top level in a file where its value does not matter. If the DOC-STRING argument appears, it specifies the documentation for the variable. (This opportunity to specify documentation is one of the main benefits of defining the variable.) The documentation is stored on the symbol under the property `variable-documentation'. The Emacs help functions (*Note Documentation::) look for this property. If the first character of DOC-STRING is `*', it says this variable is considered to be a user option. For example, the form below defines `foo' but does not set the value cell of `foo'. (defvar foo) => foo The second example sets the value of `bar' to `23', and gives it a documentation string. (defvar bar 23 "The normal weight of a bar.") => bar The following form changes the documentation string for `bar', making it a user option, but does not change the value (the addition `(1+ 23)' is not even performed, since `bar' is already nonvoid). (defvar bar (1+ 23) "*The normal weight of a bar.") => bar bar => 23 Here is an equivalent expression for the `defvar' special form: (defvar SYMBOL VALUE DOC-STRING) == (progn (if (not (boundp 'SYMBOL)) (setq SYMBOL VALUE)) (put 'SYMBOL 'variable-documentation 'DOC-STRING) 'SYMBOL) * Special form: defconst SYMBOL [VALUE [DOC-STRING]] This special form informs a person reading your code that SYMBOL has a global value, established here, that will not normally be locally bound, or changed by the execution of the program. The user, however, may be welcome to change it. Note that SYMBOL is not evaluated; the symbol to be defined must appear explicitly in the `defconst'. `defconst' always evaluates VALUE and sets the global value of SYMBOL to the result, provided VALUE is given. Note: don't use `defconst' for user-option variables in libraries that are not normally loaded. The user should be able to specify a value for such a variable in the `.emacs' file, so that it will be in effect if/when the library is loaded later. Here, `pi' is a constant which presumably ought not to be changed by anyone (attempts by the U.S. Congress notwithstanding). However, as the second form illustrates, this is only advisory. (defconst pi 3 "Pi to one place.") => pi (setq pi 4) => pi pi => 4 * Function: user-variable-p VARIABLE This function returns `t' if VARIABLE is intended to be set by the user for customization, as opposed to by programs. (Other variables exist for the internal purposes of Lisp programs, and users need not know about them.) The decision is based on the first character of the property `variable-documentation' of VARIABLE. If the property exists and is a string, and its first character is `*', then the result is `t'; otherwise, the result is `nil'. Note that if the `defconst' and `defvar' special forms are used while the variable has a local binding, the local binding's value is set; the global binding is therefore not changed. But the canonical way to use these special forms is at top level in a file, where normally there are no local bindings in effect. ▶1f◀ File: lispref Node: Accessing Variables, Prev: Defining Variables, Up: Variables, Next: Setting Variables Accessing Variable Values ========================= The usual way to reference a variable is just to write the symbol which names it (*Note Symbol Forms::). However, this requires you to choose the variable to reference when you write the program. Usually that is exactly what you want to do, but occasionally you need to choose at run time which variable to reference. Then you can use `symbol-value'. * Function: symbol-value SYMBOL This function returns the value of SYMBOL. This is the value in the innermost local binding of the symbol, or its global value if it has no local bindings. (setq abracadabra 5) => 5 (let ((abracadabra 'foo)) (symbol-value 'abracadabra)) => foo (symbol-value 'abracadabra) => 5 A `void-variable' error is signaled if SYMBOL has neither a local binding nor a global value. ▶1f◀ File: lispref Node: Setting Variables, Prev: Accessing Variables, Up: Variables, Next: Variable Resolution How to Alter a Variable Value ============================= * Special form: setq [SYMBOL FORM]... This special form is the most common method of changing a variable's value. Each SYMBOL is given a new value, which is the result of evaluating the corresponding FORM. Naturally it is the most-local existing binding of each symbol that is changed. The value of the `setq' form is the value of the last FORM. (setq x (1+ 2)) => 3 x ; `x' now has a global value. => 3 (let ((x 5)) (setq x 6) ; The local binding of `x' is set. x) => 6 x ; The global value is unchanged. => 3 Note that the first FORM is evaluated, then the first SYMBOL is set, then the second FORM is evaluated, then the second SYMBOL is set, and so on: (setq x 10 ; Notice that `x' is set y (1+ x)) ; before the value of `y' is computed. => 11 * Function: set SYMBOL VALUE This function sets SYMBOL's value to VALUE, then returns VALUE. Since `set' is a function, the expression written for SYMBOL is evaluated to obtain the symbol to be set. As usual, it is the most-local existing binding of the variable that is set. If SYMBOL is not actually a symbol, a `wrong-type-argument' error is signaled. (set one 1) error--> Symbol's value as variable is void: one (set 'one 1) => 1 (set 'two 'one) => one (set two 2) ; `two' evaluates to symbol `one'. => 2 one ; So it is `one' that was set. => 2 (let ((one 1)) ; This binding of `one' is set, (set 'one 3) ; not the global value. one) => 3 one => 2 Logically speaking, `set' is a more fundamental primitive that `setq'. Any use of `setq' can be trivially rewritten to use `set'; `setq' could even be defined as a macro, given the availability of `set'. However, `set' itself is rarely used; beginners hardly need to know about it. It is needed only when the choice of variable to be set is made at run time. For example, the command `set-variable', which reads a variable name from the user and then sets it, needs to use `set'. Common Lisp Note: In Common Lisp, `set' always changes the symbol's special value, ignoring any lexical bindings. In Emacs Lisp, all variables and all bindings are special, so `set' always affects the most local existing binding. ▶1f◀ File: lispref Node: Variable Resolution, Prev: Setting Variables, Up: Variables, Next: Buffer Local Variables Local Variable Resolution ========================= There is only one canonical symbol `foo', but various variable values may be in effect for it, from different places in the Lisp programs. Therefore, when the variable is evaluated, Emacs Lisp must decide which of these values is currently in effect. The process by which this is done is called "variable resolution". Local bindings in Emacs Lisp have "indefinite scope" and "dynamic extent". "Scope" refers to *where* textually in the source code the binding can be accessed. "Extent" refers to *when*, as the program is executing, the binding exists. The combination of dynamic extent and indefinite scope is called "dynamic scoping". By contrast, most programming languages use "lexical scoping", in which references to a local variable must be textually within the function or block that binds the variable. *Common Lisp note:* variables declared ``special'' in Common Lisp behave exactly this way. * Menu: * Impl of Scope Rules:: * Scope:: * Extent:: ▶1f◀ File: lispref Node: Impl of Scope Rules, Prev: Variable Resolution, Up: Variable Resolution, Next: Scope Sample Implementation of Dynamic Scoping ---------------------------------------- A simple sample implementation (which is not how Emacs Lisp is actually implemented) might help you understand dynamic binding. Suppose there is a stack of bindings: variable-value pairs. To find the value of a variable, search the stack from top to bottom for a binding for that variable; the value from that binding is the value of the variable. To set the variable, search for a binding, then store the new value into that binding. At entry to a function or to a `let' form, we can push bindings on the stack for the arguments or local variables created there. At exit, we can remove those bindings. As you can see, a function's argument bindings remain in effect as long as it continues execution, even during its calls to other functions. That is why we say the extent of the binding is dynamic. And these other functions can refer to the bindings, if they use these variables. That is why we say the scope is indefinite. Binding a variable in one function and using it in another is a powerful technique, but if used without restraint, it can make programs hard to understand. There are two clean ways to use this technique: * Only a few related functions, written close together in one file, use or bind the variable. Its purpose is communication within one program. You should write comments to inform other programmers that they can see all uses of the variable before them, and to advise them not to add uses elsewhere. * The variable has a well-defined, documented meaning, and various functions refer to it (but do not bind it or set it) wherever that meaning is relevant. For example, the variable `case-fold-search' is defined as ``non-`nil' means ignore case when searching''; various search and replace functions refer to it directly or through their subroutines, but do not bind or set it. Now you can bind the variable in other programs, knowing reliably what the effect will be. ▶1f◀