Initial Commit
[packages] / xemacs-packages / ilisp / extra / hyperspec.el
1 ;;; hyperspec.el --- Browse documentation from the Common Lisp HyperSpec
2
3 ;; Copyright 1997 Naggum Software
4
5 ;; Author: Erik Naggum <erik@naggum.no>
6 ;; Keywords: lisp
7
8 ;; This file is not part of GNU Emacs, but distributed under the same
9 ;; conditions as GNU Emacs, and is useless without GNU Emacs.
10
11 ;; GNU Emacs is free software; you can redistribute it and/or modify
12 ;; it under the terms of the GNU General Public License as published by
13 ;; the Free Software Foundation; either version 2, or (at your option)
14 ;; any later version.
15
16 ;; GNU Emacs is distributed in the hope that it will be useful,
17 ;; but WITHOUT ANY WARRANTY; without even the implied warranty of
18 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
19 ;; GNU General Public License for more details.
20
21 ;; You should have received a copy of the GNU General Public License
22 ;; along with GNU Emacs; see the file COPYING.  If not, write to
23 ;; the Free Software Foundation, Inc., 59 Temple Place - Suite 330,
24 ;; Boston, MA 02111-1307, USA.
25
26 ;;; Commentary:
27
28 ;; Kent Pitman and Xanalys Inc. have made the text of American National
29 ;; Standard for Information Technology -- Programming Language -- Common
30 ;; Lisp, ANSI X3.226-1994 available on the WWW, in the form of the Common
31 ;; Lisp HyperSpec.  This package makes it convenient to peruse this
32 ;; documentation from within Emacs.
33
34 ;;; Code:
35
36 (require 'cl)
37 (require 'browse-url)                   ;you need the Emacs 20 version
38 (require 'thingatpt)
39
40 (defvar common-lisp-hyperspec-root
41   "http://www.xanalys.com/software_tools/reference/HyperSpec/"
42   "The root of the Common Lisp HyperSpec URL.
43 If you copy the HyperSpec to your local system, set this variable to
44 something like \"file:/usr/local/doc/HyperSpec/\".")
45
46 ;;; Added variable for CLHS symbol table. See details below.
47 ;;;
48 ;;; 20011201 Edi Weitz
49
50 (defvar common-lisp-hyperspec-symbol-table nil
51   "The HyperSpec symbol table file.
52 If you copy the HyperSpec to your local system, set this variable to
53 the location of the symbol table which is usually \"Map_Sym.txt\"
54 or \"Symbol-Table.text\".")
55
56 (defvar common-lisp-hyperspec-history nil
57   "History of symbols looked up in the Common Lisp HyperSpec.")
58
59 ;;if only we had had packages or hash tables..., but let's fake it.
60
61 (defvar common-lisp-hyperspec-symbols (make-vector 67 0))
62
63 (defun common-lisp-hyperspec (symbol-name)
64   "View the documentation on SYMBOL-NAME from the Common Lisp HyperSpec.
65 If SYMBOL-NAME has more than one definition, all of them are displayed with
66 your favorite browser in sequence.  The browser should have a \"back\"
67 function to view the separate definitions.
68
69 The Common Lisp HyperSpec is the full ANSI Standard Common Lisp, provided
70 by Kent Pitman and Xanalys Inc.  By default, the Xanalys Web site is
71 visited to retrieve the information.  Xanalys Inc. allows you to transfer
72 the entire Common Lisp HyperSpec to your own site under certain conditions.
73 Visit http://www.xanalys.com/software_tools/reference/HyperSpec/ for more
74 information.  If you copy the HyperSpec to another location, customize the
75 variable `common-lisp-hyperspec-root' to point to that location."
76   (interactive (list (let ((symbol-at-point (thing-at-point 'symbol)))
77                        (if (and symbol-at-point
78                                 (intern-soft (downcase symbol-at-point)
79                                              common-lisp-hyperspec-symbols))
80                            symbol-at-point
81                          (completing-read
82                           "Look up symbol in Common Lisp HyperSpec: "
83                           common-lisp-hyperspec-symbols #'boundp
84                           t symbol-at-point
85                           'common-lisp-hyperspec-history)))))
86   (maplist (lambda (entry)
87              (browse-url (concat common-lisp-hyperspec-root "Body/" (car entry)))
88              (if (cdr entry)
89                  (sleep-for 1.5)))
90            (let ((symbol (intern-soft (downcase symbol-name)
91                                       common-lisp-hyperspec-symbols)))
92              (if (and symbol (boundp symbol))
93                  (symbol-value symbol)
94                (error "The symbol `%s' is not defined in Common Lisp"
95                       symbol-name)))))
96
97 ;;; Added the following just to provide a common entry point according
98 ;;; to the various 'hyperspec' implementations.
99 ;;;
100 ;;; 19990820 Marco Antoniotti
101
102 (eval-when (load eval)
103   (defalias 'hyperspec-lookup 'common-lisp-hyperspec))
104
105
106 ;;; Added dynamic lookup of symbol in CLHS symbol table
107 ;;;
108 ;;; 20011202 Edi Weitz
109
110 ;;; Replaced symbol table for v 4.0 with the one for v 6.0
111 ;;; (which is now online at Xanalys' site)
112 ;;;
113 ;;; 20020213 Edi Weitz
114
115 (if common-lisp-hyperspec-symbol-table
116     (let ((index-buffer (find-file-noselect common-lisp-hyperspec-symbol-table)))
117       (labels ((get-one-line ()
118                  (prog1 
119                      (delete* ?\n (thing-at-point 'line))
120                    (forward-line))))
121         (save-excursion
122           (set-buffer index-buffer)
123           (goto-char (point-min))
124           (while (< (point) (point-max))
125             (let* ((symbol (intern (downcase (get-one-line))
126                                    common-lisp-hyperspec-symbols))
127                    (relative-url (get-one-line)))
128               (set symbol (list (subseq relative-url
129                                         (1+ (position ?\/ relative-url :from-end t))))))))))
130   (mapcar (lambda (entry)
131             (let ((symbol (intern (car entry) common-lisp-hyperspec-symbols)))
132               (if (boundp symbol)
133                   (push (cadr entry) (symbol-value symbol))
134                 (set symbol (cdr entry)))))
135           '(("&allow-other-keys" "03_da.htm")
136             ("&aux" "03_da.htm")
137             ("&body" "03_dd.htm")
138             ("&environment" "03_dd.htm")
139             ("&key" "03_da.htm")
140             ("&optional" "03_da.htm")
141             ("&rest" "03_da.htm")
142             ("&whole" "03_dd.htm")
143             ("*" "a_st.htm")
144             ("**" "v__stst_.htm")
145             ("***" "v__stst_.htm")
146             ("*break-on-signals*" "v_break_.htm")
147             ("*compile-file-pathname*" "v_cmp_fi.htm")
148             ("*compile-file-truename*" "v_cmp_fi.htm")
149             ("*compile-print*" "v_cmp_pr.htm")
150             ("*compile-verbose*" "v_cmp_pr.htm")
151             ("*debug-io*" "v_debug_.htm")
152             ("*debugger-hook*" "v_debugg.htm")
153             ("*default-pathname-defaults*" "v_defaul.htm")
154             ("*error-output*" "v_debug_.htm")
155             ("*features*" "v_featur.htm")
156             ("*gensym-counter*" "v_gensym.htm")
157             ("*load-pathname*" "v_ld_pns.htm")
158             ("*load-print*" "v_ld_prs.htm")
159             ("*load-truename*" "v_ld_pns.htm")
160             ("*load-verbose*" "v_ld_prs.htm")
161             ("*macroexpand-hook*" "v_mexp_h.htm")
162             ("*modules*" "v_module.htm")
163             ("*package*" "v_pkg.htm")
164             ("*print-array*" "v_pr_ar.htm")
165             ("*print-base*" "v_pr_bas.htm")
166             ("*print-case*" "v_pr_cas.htm")
167             ("*print-circle*" "v_pr_cir.htm")
168             ("*print-escape*" "v_pr_esc.htm")
169             ("*print-gensym*" "v_pr_gen.htm")
170             ("*print-length*" "v_pr_lev.htm")
171             ("*print-level*" "v_pr_lev.htm")
172             ("*print-lines*" "v_pr_lin.htm")
173             ("*print-miser-width*" "v_pr_mis.htm")
174             ("*print-pprint-dispatch*" "v_pr_ppr.htm")
175             ("*print-pretty*" "v_pr_pre.htm")
176             ("*print-radix*" "v_pr_bas.htm")
177             ("*print-readably*" "v_pr_rda.htm")
178             ("*print-right-margin*" "v_pr_rig.htm")
179             ("*query-io*" "v_debug_.htm")
180             ("*random-state*" "v_rnd_st.htm")
181             ("*read-base*" "v_rd_bas.htm")
182             ("*read-default-float-format*" "v_rd_def.htm")
183             ("*read-eval*" "v_rd_eva.htm")
184             ("*read-suppress*" "v_rd_sup.htm")
185             ("*readtable*" "v_rdtabl.htm")
186             ("*standard-input*" "v_debug_.htm")
187             ("*standard-output*" "v_debug_.htm")
188             ("*terminal-io*" "v_termin.htm")
189             ("*trace-output*" "v_debug_.htm")
190             ("+" "a_pl.htm")
191             ("++" "v_pl_plp.htm")
192             ("+++" "v_pl_plp.htm")
193             ("-" "a__.htm")
194             ("/" "a_sl.htm")
195             ("//" "v_sl_sls.htm")
196             ("///" "v_sl_sls.htm")
197             ("/=" "f_eq_sle.htm")
198             ("1+" "f_1pl_1_.htm")
199             ("1-" "f_1pl_1_.htm")
200             ("<" "f_eq_sle.htm")
201             ("<=" "f_eq_sle.htm")
202             ("=" "f_eq_sle.htm")
203             (">" "f_eq_sle.htm")
204             (">=" "f_eq_sle.htm")
205             ("abort" "a_abort.htm")
206             ("abs" "f_abs.htm")
207             ("acons" "f_acons.htm")
208             ("acos" "f_asin_.htm")
209             ("acosh" "f_sinh_.htm")
210             ("add-method" "f_add_me.htm")
211             ("adjoin" "f_adjoin.htm")
212             ("adjust-array" "f_adjust.htm")
213             ("adjustable-array-p" "f_adju_1.htm")
214             ("allocate-instance" "f_alloca.htm")
215             ("alpha-char-p" "f_alpha_.htm")
216             ("alphanumericp" "f_alphan.htm")
217             ("and" "a_and.htm")
218             ("append" "f_append.htm")
219             ("apply" "f_apply.htm")
220             ("apropos" "f_apropo.htm")
221             ("apropos-list" "f_apropo.htm")
222             ("aref" "f_aref.htm")
223             ("arithmetic-error" "e_arithm.htm")
224             ("arithmetic-error-operands" "f_arithm.htm")
225             ("arithmetic-error-operation" "f_arithm.htm")
226             ("array" "t_array.htm")
227             ("array-dimension" "f_ar_dim.htm")
228             ("array-dimension-limit" "v_ar_dim.htm")
229             ("array-dimensions" "f_ar_d_1.htm")
230             ("array-displacement" "f_ar_dis.htm")
231             ("array-element-type" "f_ar_ele.htm")
232             ("array-has-fill-pointer-p" "f_ar_has.htm")
233             ("array-in-bounds-p" "f_ar_in_.htm")
234             ("array-rank" "f_ar_ran.htm")
235             ("array-rank-limit" "v_ar_ran.htm")
236             ("array-row-major-index" "f_ar_row.htm")
237             ("array-total-size" "f_ar_tot.htm")
238             ("array-total-size-limit" "v_ar_tot.htm")
239             ("arrayp" "f_arrayp.htm")
240             ("ash" "f_ash.htm")
241             ("asin" "f_asin_.htm")
242             ("asinh" "f_sinh_.htm")
243             ("assert" "m_assert.htm")
244             ("assoc" "f_assocc.htm")
245             ("assoc-if" "f_assocc.htm")
246             ("assoc-if-not" "f_assocc.htm")
247             ("atan" "f_asin_.htm")
248             ("atanh" "f_sinh_.htm")
249             ("atom" "a_atom.htm")
250             ("base-char" "t_base_c.htm")
251             ("base-string" "t_base_s.htm")
252             ("bignum" "t_bignum.htm")
253             ("bit" "a_bit.htm")
254             ("bit-and" "f_bt_and.htm")
255             ("bit-andc1" "f_bt_and.htm")
256             ("bit-andc2" "f_bt_and.htm")
257             ("bit-eqv" "f_bt_and.htm")
258             ("bit-ior" "f_bt_and.htm")
259             ("bit-nand" "f_bt_and.htm")
260             ("bit-nor" "f_bt_and.htm")
261             ("bit-not" "f_bt_and.htm")
262             ("bit-orc1" "f_bt_and.htm")
263             ("bit-orc2" "f_bt_and.htm")
264             ("bit-vector" "t_bt_vec.htm")
265             ("bit-vector-p" "f_bt_vec.htm")
266             ("bit-xor" "f_bt_and.htm")
267             ("block" "s_block.htm")
268             ("boole" "f_boole.htm")
269             ("boole-1" "v_b_1_b.htm")
270             ("boole-2" "v_b_1_b.htm")
271             ("boole-and" "v_b_1_b.htm")
272             ("boole-andc1" "v_b_1_b.htm")
273             ("boole-andc2" "v_b_1_b.htm")
274             ("boole-c1" "v_b_1_b.htm")
275             ("boole-c2" "v_b_1_b.htm")
276             ("boole-clr" "v_b_1_b.htm")
277             ("boole-eqv" "v_b_1_b.htm")
278             ("boole-ior" "v_b_1_b.htm")
279             ("boole-nand" "v_b_1_b.htm")
280             ("boole-nor" "v_b_1_b.htm")
281             ("boole-orc1" "v_b_1_b.htm")
282             ("boole-orc2" "v_b_1_b.htm")
283             ("boole-set" "v_b_1_b.htm")
284             ("boole-xor" "v_b_1_b.htm")
285             ("boolean" "t_ban.htm")
286             ("both-case-p" "f_upper_.htm")
287             ("boundp" "f_boundp.htm")
288             ("break" "f_break.htm")
289             ("broadcast-stream" "t_broadc.htm")
290             ("broadcast-stream-streams" "f_broadc.htm")
291             ("built-in-class" "t_built_.htm")
292             ("butlast" "f_butlas.htm")
293             ("byte" "f_by_by.htm")
294             ("byte-position" "f_by_by.htm")
295             ("byte-size" "f_by_by.htm")
296             ("caaaar" "f_car_c.htm")
297             ("caaadr" "f_car_c.htm")
298             ("caaar" "f_car_c.htm")
299             ("caadar" "f_car_c.htm")
300             ("caaddr" "f_car_c.htm")
301             ("caadr" "f_car_c.htm")
302             ("caar" "f_car_c.htm")
303             ("cadaar" "f_car_c.htm")
304             ("cadadr" "f_car_c.htm")
305             ("cadar" "f_car_c.htm")
306             ("caddar" "f_car_c.htm")
307             ("cadddr" "f_car_c.htm")
308             ("caddr" "f_car_c.htm")
309             ("cadr" "f_car_c.htm")
310             ("call-arguments-limit" "v_call_a.htm")
311             ("call-method" "m_call_m.htm")
312             ("call-next-method" "f_call_n.htm")
313             ("car" "f_car_c.htm")
314             ("case" "m_case_.htm")
315             ("catch" "s_catch.htm")
316             ("ccase" "m_case_.htm")
317             ("cdaaar" "f_car_c.htm")
318             ("cdaadr" "f_car_c.htm")
319             ("cdaar" "f_car_c.htm")
320             ("cdadar" "f_car_c.htm")
321             ("cdaddr" "f_car_c.htm")
322             ("cdadr" "f_car_c.htm")
323             ("cdar" "f_car_c.htm")
324             ("cddaar" "f_car_c.htm")
325             ("cddadr" "f_car_c.htm")
326             ("cddar" "f_car_c.htm")
327             ("cdddar" "f_car_c.htm")
328             ("cddddr" "f_car_c.htm")
329             ("cdddr" "f_car_c.htm")
330             ("cddr" "f_car_c.htm")
331             ("cdr" "f_car_c.htm")
332             ("ceiling" "f_floorc.htm")
333             ("cell-error" "e_cell_e.htm")
334             ("cell-error-name" "f_cell_e.htm")
335             ("cerror" "f_cerror.htm")
336             ("change-class" "f_chg_cl.htm")
337             ("char" "f_char_.htm")
338             ("char-code" "f_char_c.htm")
339             ("char-code-limit" "v_char_c.htm")
340             ("char-downcase" "f_char_u.htm")
341             ("char-equal" "f_chareq.htm")
342             ("char-greaterp" "f_chareq.htm")
343             ("char-int" "f_char_i.htm")
344             ("char-lessp" "f_chareq.htm")
345             ("char-name" "f_char_n.htm")
346             ("char-not-equal" "f_chareq.htm")
347             ("char-not-greaterp" "f_chareq.htm")
348             ("char-not-lessp" "f_chareq.htm")
349             ("char-upcase" "f_char_u.htm")
350             ("char/=" "f_chareq.htm")
351             ("char<" "f_chareq.htm")
352             ("char<=" "f_chareq.htm")
353             ("char=" "f_chareq.htm")
354             ("char>" "f_chareq.htm")
355             ("char>=" "f_chareq.htm")
356             ("character" "a_ch.htm")
357             ("characterp" "f_chp.htm")
358             ("check-type" "m_check_.htm")
359             ("cis" "f_cis.htm")
360             ("class" "t_class.htm")
361             ("class-name" "f_class_.htm")
362             ("class-of" "f_clas_1.htm")
363             ("clear-input" "f_clear_.htm")
364             ("clear-output" "f_finish.htm")
365             ("close" "f_close.htm")
366             ("clrhash" "f_clrhas.htm")
367             ("code-char" "f_code_c.htm")
368             ("coerce" "f_coerce.htm")
369             ("compilation-speed" "d_optimi.htm")
370             ("compile" "f_cmp.htm")
371             ("compile-file" "f_cmp_fi.htm")
372             ("compile-file-pathname" "f_cmp__1.htm")
373             ("compiled-function" "t_cmpd_f.htm")
374             ("compiled-function-p" "f_cmpd_f.htm")
375             ("compiler-macro" "f_docume.htm")
376             ("compiler-macro-function" "f_cmp_ma.htm")
377             ("complement" "f_comple.htm")
378             ("complex" "a_comple.htm")
379             ("complexp" "f_comp_3.htm")
380             ("compute-applicable-methods" "f_comput.htm")
381             ("compute-restarts" "f_comp_1.htm")
382             ("concatenate" "f_concat.htm")
383             ("concatenated-stream" "t_concat.htm")
384             ("concatenated-stream-streams" "f_conc_1.htm")
385             ("cond" "m_cond.htm")
386             ("condition" "e_cnd.htm")
387             ("conjugate" "f_conjug.htm")
388             ("cons" "a_cons.htm")
389             ("consp" "f_consp.htm")
390             ("constantly" "f_cons_1.htm")
391             ("constantp" "f_consta.htm")
392             ("continue" "a_contin.htm")
393             ("control-error" "e_contro.htm")
394             ("copy-alist" "f_cp_ali.htm")
395             ("copy-list" "f_cp_lis.htm")
396             ("copy-pprint-dispatch" "f_cp_ppr.htm")
397             ("copy-readtable" "f_cp_rdt.htm")
398             ("copy-seq" "f_cp_seq.htm")
399             ("copy-structure" "f_cp_stu.htm")
400             ("copy-symbol" "f_cp_sym.htm")
401             ("copy-tree" "f_cp_tre.htm")
402             ("cos" "f_sin_c.htm")
403             ("cosh" "f_sinh_.htm")
404             ("count" "f_countc.htm")
405             ("count-if" "f_countc.htm")
406             ("count-if-not" "f_countc.htm")
407             ("ctypecase" "m_tpcase.htm")
408             ("debug" "d_optimi.htm")
409             ("decf" "m_incf_.htm")
410             ("declaim" "m_declai.htm")
411             ("declaration" "d_declar.htm")
412             ("declare" "s_declar.htm")
413             ("decode-float" "f_dec_fl.htm")
414             ("decode-universal-time" "f_dec_un.htm")
415             ("defclass" "m_defcla.htm")
416             ("defconstant" "m_defcon.htm")
417             ("defgeneric" "m_defgen.htm")
418             ("define-compiler-macro" "m_define.htm")
419             ("define-condition" "m_defi_5.htm")
420             ("define-method-combination" "m_defi_4.htm")
421             ("define-modify-macro" "m_defi_2.htm")
422             ("define-setf-expander" "m_defi_3.htm")
423             ("define-symbol-macro" "m_defi_1.htm")
424             ("defmacro" "m_defmac.htm")
425             ("defmethod" "m_defmet.htm")
426             ("defpackage" "m_defpkg.htm")
427             ("defparameter" "m_defpar.htm")
428             ("defsetf" "m_defset.htm")
429             ("defstruct" "m_defstr.htm")
430             ("deftype" "m_deftp.htm")
431             ("defun" "m_defun.htm")
432             ("defvar" "m_defpar.htm")
433             ("delete" "f_rm_rm.htm")
434             ("delete-duplicates" "f_rm_dup.htm")
435             ("delete-file" "f_del_fi.htm")
436             ("delete-if" "f_rm_rm.htm")
437             ("delete-if-not" "f_rm_rm.htm")
438             ("delete-package" "f_del_pk.htm")
439             ("denominator" "f_numera.htm")
440             ("deposit-field" "f_deposi.htm")
441             ("describe" "f_descri.htm")
442             ("describe-object" "f_desc_1.htm")
443             ("destructuring-bind" "m_destru.htm")
444             ("digit-char" "f_digit_.htm")
445             ("digit-char-p" "f_digi_1.htm")
446             ("directory" "f_dir.htm")
447             ("directory-namestring" "f_namest.htm")
448             ("disassemble" "f_disass.htm")
449             ("division-by-zero" "e_divisi.htm")
450             ("do" "m_do_do.htm")
451             ("do*" "m_do_do.htm")
452             ("do-all-symbols" "m_do_sym.htm")
453             ("do-external-symbols" "m_do_sym.htm")
454             ("do-symbols" "m_do_sym.htm")
455             ("documentation" "f_docume.htm")
456             ("dolist" "m_dolist.htm")
457             ("dotimes" "m_dotime.htm")
458             ("double-float" "t_short_.htm")
459             ("double-float-epsilon" "v_short_.htm")
460             ("double-float-negative-epsilon" "v_short_.htm")
461             ("dpb" "f_dpb.htm")
462             ("dribble" "f_dribbl.htm")
463             ("dynamic-extent" "d_dynami.htm")
464             ("ecase" "m_case_.htm")
465             ("echo-stream" "t_echo_s.htm")
466             ("echo-stream-input-stream" "f_echo_s.htm")
467             ("echo-stream-output-stream" "f_echo_s.htm")
468             ("ed" "f_ed.htm")
469             ("eighth" "f_firstc.htm")
470             ("elt" "f_elt.htm")
471             ("encode-universal-time" "f_encode.htm")
472             ("end-of-file" "e_end_of.htm")
473             ("endp" "f_endp.htm")
474             ("enough-namestring" "f_namest.htm")
475             ("ensure-directories-exist" "f_ensu_1.htm")
476             ("ensure-generic-function" "f_ensure.htm")
477             ("eq" "f_eq.htm")
478             ("eql" "a_eql.htm")
479             ("equal" "f_equal.htm")
480             ("equalp" "f_equalp.htm")
481             ("error" "a_error.htm")
482             ("etypecase" "m_tpcase.htm")
483             ("eval" "f_eval.htm")
484             ("eval-when" "s_eval_w.htm")
485             ("evenp" "f_evenpc.htm")
486             ("every" "f_everyc.htm")
487             ("exp" "f_exp_e.htm")
488             ("export" "f_export.htm")
489             ("expt" "f_exp_e.htm")
490             ("extended-char" "t_extend.htm")
491             ("fboundp" "f_fbound.htm")
492             ("fceiling" "f_floorc.htm")
493             ("fdefinition" "f_fdefin.htm")
494             ("ffloor" "f_floorc.htm")
495             ("fifth" "f_firstc.htm")
496             ("file-author" "f_file_a.htm")
497             ("file-error" "e_file_e.htm")
498             ("file-error-pathname" "f_file_e.htm")
499             ("file-length" "f_file_l.htm")
500             ("file-namestring" "f_namest.htm")
501             ("file-position" "f_file_p.htm")
502             ("file-stream" "t_file_s.htm")
503             ("file-string-length" "f_file_s.htm")
504             ("file-write-date" "f_file_w.htm")
505             ("fill" "f_fill.htm")
506             ("fill-pointer" "f_fill_p.htm")
507             ("find" "f_find_.htm")
508             ("find-all-symbols" "f_find_a.htm")
509             ("find-class" "f_find_c.htm")
510             ("find-if" "f_find_.htm")
511             ("find-if-not" "f_find_.htm")
512             ("find-method" "f_find_m.htm")
513             ("find-package" "f_find_p.htm")
514             ("find-restart" "f_find_r.htm")
515             ("find-symbol" "f_find_s.htm")
516             ("finish-output" "f_finish.htm")
517             ("first" "f_firstc.htm")
518             ("fixnum" "t_fixnum.htm")
519             ("flet" "s_flet_.htm")
520             ("float" "a_float.htm")
521             ("float-digits" "f_dec_fl.htm")
522             ("float-precision" "f_dec_fl.htm")
523             ("float-radix" "f_dec_fl.htm")
524             ("float-sign" "f_dec_fl.htm")
525             ("floating-point-inexact" "e_floa_1.htm")
526             ("floating-point-invalid-operation" "e_floati.htm")
527             ("floating-point-overflow" "e_floa_2.htm")
528             ("floating-point-underflow" "e_floa_3.htm")
529             ("floatp" "f_floatp.htm")
530             ("floor" "f_floorc.htm")
531             ("fmakunbound" "f_fmakun.htm")
532             ("force-output" "f_finish.htm")
533             ("format" "f_format.htm")
534             ("formatter" "m_format.htm")
535             ("fourth" "f_firstc.htm")
536             ("fresh-line" "f_terpri.htm")
537             ("fround" "f_floorc.htm")
538             ("ftruncate" "f_floorc.htm")
539             ("ftype" "d_ftype.htm")
540             ("funcall" "f_funcal.htm")
541             ("function" "a_fn.htm")
542             ("function-keywords" "f_fn_kwd.htm")
543             ("function-lambda-expression" "f_fn_lam.htm")
544             ("functionp" "f_fnp.htm")
545             ("gcd" "f_gcd.htm")
546             ("generic-function" "t_generi.htm")
547             ("gensym" "f_gensym.htm")
548             ("gentemp" "f_gentem.htm")
549             ("get" "f_get.htm")
550             ("get-decoded-time" "f_get_un.htm")
551             ("get-dispatch-macro-character" "f_set__1.htm")
552             ("get-internal-real-time" "f_get_in.htm")
553             ("get-internal-run-time" "f_get__1.htm")
554             ("get-macro-character" "f_set_ma.htm")
555             ("get-output-stream-string" "f_get_ou.htm")
556             ("get-properties" "f_get_pr.htm")
557             ("get-setf-expansion" "f_get_se.htm")
558             ("get-universal-time" "f_get_un.htm")
559             ("getf" "f_getf.htm")
560             ("gethash" "f_gethas.htm")
561             ("go" "s_go.htm")
562             ("graphic-char-p" "f_graphi.htm")
563             ("handler-bind" "m_handle.htm")
564             ("handler-case" "m_hand_1.htm")
565             ("hash-table" "t_hash_t.htm")
566             ("hash-table-count" "f_hash_1.htm")
567             ("hash-table-p" "f_hash_t.htm")
568             ("hash-table-rehash-size" "f_hash_2.htm")
569             ("hash-table-rehash-threshold" "f_hash_3.htm")
570             ("hash-table-size" "f_hash_4.htm")
571             ("hash-table-test" "f_hash_5.htm")
572             ("host-namestring" "f_namest.htm")
573             ("identity" "f_identi.htm")
574             ("if" "s_if.htm")
575             ("ignorable" "d_ignore.htm")
576             ("ignore" "d_ignore.htm")
577             ("ignore-errors" "m_ignore.htm")
578             ("imagpart" "f_realpa.htm")
579             ("import" "f_import.htm")
580             ("in-package" "m_in_pkg.htm")
581             ("incf" "m_incf_.htm")
582             ("initialize-instance" "f_init_i.htm")
583             ("inline" "d_inline.htm")
584             ("input-stream-p" "f_in_stm.htm")
585             ("inspect" "f_inspec.htm")
586             ("integer" "t_intege.htm")
587             ("integer-decode-float" "f_dec_fl.htm")
588             ("integer-length" "f_intege.htm")
589             ("integerp" "f_inte_1.htm")
590             ("interactive-stream-p" "f_intera.htm")
591             ("intern" "f_intern.htm")
592             ("internal-time-units-per-second" "v_intern.htm")
593             ("intersection" "f_isec_.htm")
594             ("invalid-method-error" "f_invali.htm")
595             ("invoke-debugger" "f_invoke.htm")
596             ("invoke-restart" "f_invo_1.htm")
597             ("invoke-restart-interactively" "f_invo_2.htm")
598             ("isqrt" "f_sqrt_.htm")
599             ("keyword" "t_kwd.htm")
600             ("keywordp" "f_kwdp.htm")
601             ("labels" "s_flet_.htm")
602             ("lambda" "a_lambda.htm")
603             ("lambda-list-keywords" "v_lambda.htm")
604             ("lambda-parameters-limit" "v_lamb_1.htm")
605             ("last" "f_last.htm")
606             ("lcm" "f_lcm.htm")
607             ("ldb" "f_ldb.htm")
608             ("ldb-test" "f_ldb_te.htm")
609             ("ldiff" "f_ldiffc.htm")
610             ("least-negative-double-float" "v_most_1.htm")
611             ("least-negative-long-float" "v_most_1.htm")
612             ("least-negative-normalized-double-float" "v_most_1.htm")
613             ("least-negative-normalized-long-float" "v_most_1.htm")
614             ("least-negative-normalized-short-float" "v_most_1.htm")
615             ("least-negative-normalized-single-float" "v_most_1.htm")
616             ("least-negative-short-float" "v_most_1.htm")
617             ("least-negative-single-float" "v_most_1.htm")
618             ("least-positive-double-float" "v_most_1.htm")
619             ("least-positive-long-float" "v_most_1.htm")
620             ("least-positive-normalized-double-float" "v_most_1.htm")
621             ("least-positive-normalized-long-float" "v_most_1.htm")
622             ("least-positive-normalized-short-float" "v_most_1.htm")
623             ("least-positive-normalized-single-float" "v_most_1.htm")
624             ("least-positive-short-float" "v_most_1.htm")
625             ("least-positive-single-float" "v_most_1.htm")
626             ("length" "f_length.htm")
627             ("let" "s_let_l.htm")
628             ("let*" "s_let_l.htm")
629             ("lisp-implementation-type" "f_lisp_i.htm")
630             ("lisp-implementation-version" "f_lisp_i.htm")
631             ("list" "a_list.htm")
632             ("list*" "f_list_.htm")
633             ("list-all-packages" "f_list_a.htm")
634             ("list-length" "f_list_l.htm")
635             ("listen" "f_listen.htm")
636             ("listp" "f_listp.htm")
637             ("load" "f_load.htm")
638             ("load-logical-pathname-translations" "f_ld_log.htm")
639             ("load-time-value" "s_ld_tim.htm")
640             ("locally" "s_locall.htm")
641             ("log" "f_log.htm")
642             ("logand" "f_logand.htm")
643             ("logandc1" "f_logand.htm")
644             ("logandc2" "f_logand.htm")
645             ("logbitp" "f_logbtp.htm")
646             ("logcount" "f_logcou.htm")
647             ("logeqv" "f_logand.htm")
648             ("logical-pathname" "a_logica.htm")
649             ("logical-pathname-translations" "f_logica.htm")
650             ("logior" "f_logand.htm")
651             ("lognand" "f_logand.htm")
652             ("lognor" "f_logand.htm")
653             ("lognot" "f_logand.htm")
654             ("logorc1" "f_logand.htm")
655             ("logorc2" "f_logand.htm")
656             ("logtest" "f_logtes.htm")
657             ("logxor" "f_logand.htm")
658             ("long-float" "t_short_.htm")
659             ("long-float-epsilon" "v_short_.htm")
660             ("long-float-negative-epsilon" "v_short_.htm")
661             ("long-site-name" "f_short_.htm")
662             ("loop" "m_loop.htm")
663             ("loop-finish" "m_loop_f.htm")
664             ("lower-case-p" "f_upper_.htm")
665             ("machine-instance" "f_mach_i.htm")
666             ("machine-type" "f_mach_t.htm")
667             ("machine-version" "f_mach_v.htm")
668             ("macro-function" "f_macro_.htm")
669             ("macroexpand" "f_mexp_.htm")
670             ("macroexpand-1" "f_mexp_.htm")
671             ("macrolet" "s_flet_.htm")
672             ("make-array" "f_mk_ar.htm")
673             ("make-broadcast-stream" "f_mk_bro.htm")
674             ("make-concatenated-stream" "f_mk_con.htm")
675             ("make-condition" "f_mk_cnd.htm")
676             ("make-dispatch-macro-character" "f_mk_dis.htm")
677             ("make-echo-stream" "f_mk_ech.htm")
678             ("make-hash-table" "f_mk_has.htm")
679             ("make-instance" "f_mk_ins.htm")
680             ("make-instances-obsolete" "f_mk_i_1.htm")
681             ("make-list" "f_mk_lis.htm")
682             ("make-load-form" "f_mk_ld_.htm")
683             ("make-load-form-saving-slots" "f_mk_l_1.htm")
684             ("make-method" "m_call_m.htm")
685             ("make-package" "f_mk_pkg.htm")
686             ("make-pathname" "f_mk_pn.htm")
687             ("make-random-state" "f_mk_rnd.htm")
688             ("make-sequence" "f_mk_seq.htm")
689             ("make-string" "f_mk_stg.htm")
690             ("make-string-input-stream" "f_mk_s_1.htm")
691             ("make-string-output-stream" "f_mk_s_2.htm")
692             ("make-symbol" "f_mk_sym.htm")
693             ("make-synonym-stream" "f_mk_syn.htm")
694             ("make-two-way-stream" "f_mk_two.htm")
695             ("makunbound" "f_makunb.htm")
696             ("map" "f_map.htm")
697             ("map-into" "f_map_in.htm")
698             ("mapc" "f_mapc_.htm")
699             ("mapcan" "f_mapc_.htm")
700             ("mapcar" "f_mapc_.htm")
701             ("mapcon" "f_mapc_.htm")
702             ("maphash" "f_maphas.htm")
703             ("mapl" "f_mapc_.htm")
704             ("maplist" "f_mapc_.htm")
705             ("mask-field" "f_mask_f.htm")
706             ("max" "f_max_m.htm")
707             ("member" "a_member.htm")
708             ("member-if" "f_mem_m.htm")
709             ("member-if-not" "f_mem_m.htm")
710             ("merge" "f_merge.htm")
711             ("merge-pathnames" "f_merge_.htm")
712             ("method" "t_method.htm")
713             ("method-combination" "a_method.htm")
714             ("method-combination-error" "f_meth_1.htm")
715             ("method-qualifiers" "f_method.htm")
716             ("min" "f_max_m.htm")
717             ("minusp" "f_minusp.htm")
718             ("mismatch" "f_mismat.htm")
719             ("mod" "a_mod.htm")
720             ("most-negative-double-float" "v_most_1.htm")
721             ("most-negative-fixnum" "v_most_p.htm")
722             ("most-negative-long-float" "v_most_1.htm")
723             ("most-negative-short-float" "v_most_1.htm")
724             ("most-negative-single-float" "v_most_1.htm")
725             ("most-positive-double-float" "v_most_1.htm")
726             ("most-positive-fixnum" "v_most_p.htm")
727             ("most-positive-long-float" "v_most_1.htm")
728             ("most-positive-short-float" "v_most_1.htm")
729             ("most-positive-single-float" "v_most_1.htm")
730             ("muffle-warning" "a_muffle.htm")
731             ("multiple-value-bind" "m_multip.htm")
732             ("multiple-value-call" "s_multip.htm")
733             ("multiple-value-list" "m_mult_1.htm")
734             ("multiple-value-prog1" "s_mult_1.htm")
735             ("multiple-value-setq" "m_mult_2.htm")
736             ("multiple-values-limit" "v_multip.htm")
737             ("name-char" "f_name_c.htm")
738             ("namestring" "f_namest.htm")
739             ("nbutlast" "f_butlas.htm")
740             ("nconc" "f_nconc.htm")
741             ("next-method-p" "f_next_m.htm")
742             ("nil" "a_nil.htm")
743             ("nintersection" "f_isec_.htm")
744             ("ninth" "f_firstc.htm")
745             ("no-applicable-method" "f_no_app.htm")
746             ("no-next-method" "f_no_nex.htm")
747             ("not" "a_not.htm")
748             ("notany" "f_everyc.htm")
749             ("notevery" "f_everyc.htm")
750             ("notinline" "d_inline.htm")
751             ("nreconc" "f_revapp.htm")
752             ("nreverse" "f_revers.htm")
753             ("nset-difference" "f_set_di.htm")
754             ("nset-exclusive-or" "f_set_ex.htm")
755             ("nstring-capitalize" "f_stg_up.htm")
756             ("nstring-downcase" "f_stg_up.htm")
757             ("nstring-upcase" "f_stg_up.htm")
758             ("nsublis" "f_sublis.htm")
759             ("nsubst" "f_substc.htm")
760             ("nsubst-if" "f_substc.htm")
761             ("nsubst-if-not" "f_substc.htm")
762             ("nsubstitute" "f_sbs_s.htm")
763             ("nsubstitute-if" "f_sbs_s.htm")
764             ("nsubstitute-if-not" "f_sbs_s.htm")
765             ("nth" "f_nth.htm")
766             ("nth-value" "m_nth_va.htm")
767             ("nthcdr" "f_nthcdr.htm")
768             ("null" "a_null.htm")
769             ("number" "t_number.htm")
770             ("numberp" "f_nump.htm")
771             ("numerator" "f_numera.htm")
772             ("nunion" "f_unionc.htm")
773             ("oddp" "f_evenpc.htm")
774             ("open" "f_open.htm")
775             ("open-stream-p" "f_open_s.htm")
776             ("optimize" "d_optimi.htm")
777             ("or" "a_or.htm")
778             ("otherwise" "m_case_.htm")
779             ("output-stream-p" "f_in_stm.htm")
780             ("package" "t_pkg.htm")
781             ("package-error" "e_pkg_er.htm")
782             ("package-error-package" "f_pkg_er.htm")
783             ("package-name" "f_pkg_na.htm")
784             ("package-nicknames" "f_pkg_ni.htm")
785             ("package-shadowing-symbols" "f_pkg_sh.htm")
786             ("package-use-list" "f_pkg_us.htm")
787             ("package-used-by-list" "f_pkg__1.htm")
788             ("packagep" "f_pkgp.htm")
789             ("pairlis" "f_pairli.htm")
790             ("parse-error" "e_parse_.htm")
791             ("parse-integer" "f_parse_.htm")
792             ("parse-namestring" "f_pars_1.htm")
793             ("pathname" "a_pn.htm")
794             ("pathname-device" "f_pn_hos.htm")
795             ("pathname-directory" "f_pn_hos.htm")
796             ("pathname-host" "f_pn_hos.htm")
797             ("pathname-match-p" "f_pn_mat.htm")
798             ("pathname-name" "f_pn_hos.htm")
799             ("pathname-type" "f_pn_hos.htm")
800             ("pathname-version" "f_pn_hos.htm")
801             ("pathnamep" "f_pnp.htm")
802             ("peek-char" "f_peek_c.htm")
803             ("phase" "f_phase.htm")
804             ("pi" "v_pi.htm")
805             ("plusp" "f_minusp.htm")
806             ("pop" "m_pop.htm")
807             ("position" "f_pos_p.htm")
808             ("position-if" "f_pos_p.htm")
809             ("position-if-not" "f_pos_p.htm")
810             ("pprint" "f_wr_pr.htm")
811             ("pprint-dispatch" "f_ppr_di.htm")
812             ("pprint-exit-if-list-exhausted" "m_ppr_ex.htm")
813             ("pprint-fill" "f_ppr_fi.htm")
814             ("pprint-indent" "f_ppr_in.htm")
815             ("pprint-linear" "f_ppr_fi.htm")
816             ("pprint-logical-block" "m_ppr_lo.htm")
817             ("pprint-newline" "f_ppr_nl.htm")
818             ("pprint-pop" "m_ppr_po.htm")
819             ("pprint-tab" "f_ppr_ta.htm")
820             ("pprint-tabular" "f_ppr_fi.htm")
821             ("prin1" "f_wr_pr.htm")
822             ("prin1-to-string" "f_wr_to_.htm")
823             ("princ" "f_wr_pr.htm")
824             ("princ-to-string" "f_wr_to_.htm")
825             ("print" "f_wr_pr.htm")
826             ("print-not-readable" "e_pr_not.htm")
827             ("print-not-readable-object" "f_pr_not.htm")
828             ("print-object" "f_pr_obj.htm")
829             ("print-unreadable-object" "m_pr_unr.htm")
830             ("probe-file" "f_probe_.htm")
831             ("proclaim" "f_procla.htm")
832             ("prog" "m_prog_.htm")
833             ("prog*" "m_prog_.htm")
834             ("prog1" "m_prog1c.htm")
835             ("prog2" "m_prog1c.htm")
836             ("progn" "s_progn.htm")
837             ("program-error" "e_progra.htm")
838             ("progv" "s_progv.htm")
839             ("provide" "f_provid.htm")
840             ("psetf" "m_setf_.htm")
841             ("psetq" "m_psetq.htm")
842             ("push" "m_push.htm")
843             ("pushnew" "m_pshnew.htm")
844             ("quote" "s_quote.htm")
845             ("random" "f_random.htm")
846             ("random-state" "t_rnd_st.htm")
847             ("random-state-p" "f_rnd_st.htm")
848             ("rassoc" "f_rassoc.htm")
849             ("rassoc-if" "f_rassoc.htm")
850             ("rassoc-if-not" "f_rassoc.htm")
851             ("ratio" "t_ratio.htm")
852             ("rational" "a_ration.htm")
853             ("rationalize" "f_ration.htm")
854             ("rationalp" "f_rati_1.htm")
855             ("read" "f_rd_rd.htm")
856             ("read-byte" "f_rd_by.htm")
857             ("read-char" "f_rd_cha.htm")
858             ("read-char-no-hang" "f_rd_c_1.htm")
859             ("read-delimited-list" "f_rd_del.htm")
860             ("read-from-string" "f_rd_fro.htm")
861             ("read-line" "f_rd_lin.htm")
862             ("read-preserving-whitespace" "f_rd_rd.htm")
863             ("read-sequence" "f_rd_seq.htm")
864             ("reader-error" "e_rder_e.htm")
865             ("readtable" "t_rdtabl.htm")
866             ("readtable-case" "f_rdtabl.htm")
867             ("readtablep" "f_rdta_1.htm")
868             ("real" "t_real.htm")
869             ("realp" "f_realp.htm")
870             ("realpart" "f_realpa.htm")
871             ("reduce" "f_reduce.htm")
872             ("reinitialize-instance" "f_reinit.htm")
873             ("rem" "f_mod_r.htm")
874             ("remf" "m_remf.htm")
875             ("remhash" "f_remhas.htm")
876             ("remove" "f_rm_rm.htm")
877             ("remove-duplicates" "f_rm_dup.htm")
878             ("remove-if" "f_rm_rm.htm")
879             ("remove-if-not" "f_rm_rm.htm")
880             ("remove-method" "f_rm_met.htm")
881             ("remprop" "f_rempro.htm")
882             ("rename-file" "f_rn_fil.htm")
883             ("rename-package" "f_rn_pkg.htm")
884             ("replace" "f_replac.htm")
885             ("require" "f_provid.htm")
886             ("rest" "f_rest.htm")
887             ("restart" "t_rst.htm")
888             ("restart-bind" "m_rst_bi.htm")
889             ("restart-case" "m_rst_ca.htm")
890             ("restart-name" "f_rst_na.htm")
891             ("return" "m_return.htm")
892             ("return-from" "s_ret_fr.htm")
893             ("revappend" "f_revapp.htm")
894             ("reverse" "f_revers.htm")
895             ("room" "f_room.htm")
896             ("rotatef" "m_rotate.htm")
897             ("round" "f_floorc.htm")
898             ("row-major-aref" "f_row_ma.htm")
899             ("rplaca" "f_rplaca.htm")
900             ("rplacd" "f_rplaca.htm")
901             ("safety" "d_optimi.htm")
902             ("satisfies" "t_satisf.htm")
903             ("sbit" "f_bt_sb.htm")
904             ("scale-float" "f_dec_fl.htm")
905             ("schar" "f_char_.htm")
906             ("search" "f_search.htm")
907             ("second" "f_firstc.htm")
908             ("sequence" "t_seq.htm")
909             ("serious-condition" "e_seriou.htm")
910             ("set" "f_set.htm")
911             ("set-difference" "f_set_di.htm")
912             ("set-dispatch-macro-character" "f_set__1.htm")
913             ("set-exclusive-or" "f_set_ex.htm")
914             ("set-macro-character" "f_set_ma.htm")
915             ("set-pprint-dispatch" "f_set_pp.htm")
916             ("set-syntax-from-char" "f_set_sy.htm")
917             ("setf" "a_setf.htm")
918             ("setq" "s_setq.htm")
919             ("seventh" "f_firstc.htm")
920             ("shadow" "f_shadow.htm")
921             ("shadowing-import" "f_shdw_i.htm")
922             ("shared-initialize" "f_shared.htm")
923             ("shiftf" "m_shiftf.htm")
924             ("short-float" "t_short_.htm")
925             ("short-float-epsilon" "v_short_.htm")
926             ("short-float-negative-epsilon" "v_short_.htm")
927             ("short-site-name" "f_short_.htm")
928             ("signal" "f_signal.htm")
929             ("signed-byte" "t_sgn_by.htm")
930             ("signum" "f_signum.htm")
931             ("simple-array" "t_smp_ar.htm")
932             ("simple-base-string" "t_smp_ba.htm")
933             ("simple-bit-vector" "t_smp_bt.htm")
934             ("simple-bit-vector-p" "f_smp_bt.htm")
935             ("simple-condition" "e_smp_cn.htm")
936             ("simple-condition-format-arguments" "f_smp_cn.htm")
937             ("simple-condition-format-control" "f_smp_cn.htm")
938             ("simple-error" "e_smp_er.htm")
939             ("simple-string" "t_smp_st.htm")
940             ("simple-string-p" "f_smp_st.htm")
941             ("simple-type-error" "e_smp_tp.htm")
942             ("simple-vector" "t_smp_ve.htm")
943             ("simple-vector-p" "f_smp_ve.htm")
944             ("simple-warning" "e_smp_wa.htm")
945             ("sin" "f_sin_c.htm")
946             ("single-float" "t_short_.htm")
947             ("single-float-epsilon" "v_short_.htm")
948             ("single-float-negative-epsilon" "v_short_.htm")
949             ("sinh" "f_sinh_.htm")
950             ("sixth" "f_firstc.htm")
951             ("sleep" "f_sleep.htm")
952             ("slot-boundp" "f_slt_bo.htm")
953             ("slot-exists-p" "f_slt_ex.htm")
954             ("slot-makunbound" "f_slt_ma.htm")
955             ("slot-missing" "f_slt_mi.htm")
956             ("slot-unbound" "f_slt_un.htm")
957             ("slot-value" "f_slt_va.htm")
958             ("software-type" "f_sw_tpc.htm")
959             ("software-version" "f_sw_tpc.htm")
960             ("some" "f_everyc.htm")
961             ("sort" "f_sort_.htm")
962             ("space" "d_optimi.htm")
963             ("special" "d_specia.htm")
964             ("special-operator-p" "f_specia.htm")
965             ("speed" "d_optimi.htm")
966             ("sqrt" "f_sqrt_.htm")
967             ("stable-sort" "f_sort_.htm")
968             ("standard" "07_ffb.htm")
969             ("standard-char" "t_std_ch.htm")
970             ("standard-char-p" "f_std_ch.htm")
971             ("standard-class" "t_std_cl.htm")
972             ("standard-generic-function" "t_std_ge.htm")
973             ("standard-method" "t_std_me.htm")
974             ("standard-object" "t_std_ob.htm")
975             ("step" "m_step.htm")
976             ("storage-condition" "e_storag.htm")
977             ("store-value" "a_store_.htm")
978             ("stream" "t_stream.htm")
979             ("stream-element-type" "f_stm_el.htm")
980             ("stream-error" "e_stm_er.htm")
981             ("stream-error-stream" "f_stm_er.htm")
982             ("stream-external-format" "f_stm_ex.htm")
983             ("streamp" "f_stmp.htm")
984             ("string" "a_string.htm")
985             ("string-capitalize" "f_stg_up.htm")
986             ("string-downcase" "f_stg_up.htm")
987             ("string-equal" "f_stgeq_.htm")
988             ("string-greaterp" "f_stgeq_.htm")
989             ("string-left-trim" "f_stg_tr.htm")
990             ("string-lessp" "f_stgeq_.htm")
991             ("string-not-equal" "f_stgeq_.htm")
992             ("string-not-greaterp" "f_stgeq_.htm")
993             ("string-not-lessp" "f_stgeq_.htm")
994             ("string-right-trim" "f_stg_tr.htm")
995             ("string-stream" "t_stg_st.htm")
996             ("string-trim" "f_stg_tr.htm")
997             ("string-upcase" "f_stg_up.htm")
998             ("string/=" "f_stgeq_.htm")
999             ("string<" "f_stgeq_.htm")
1000             ("string<=" "f_stgeq_.htm")
1001             ("string=" "f_stgeq_.htm")
1002             ("string>" "f_stgeq_.htm")
1003             ("string>=" "f_stgeq_.htm")
1004             ("stringp" "f_stgp.htm")
1005             ("structure" "f_docume.htm")
1006             ("structure-class" "t_stu_cl.htm")
1007             ("structure-object" "t_stu_ob.htm")
1008             ("style-warning" "e_style_.htm")
1009             ("sublis" "f_sublis.htm")
1010             ("subseq" "f_subseq.htm")
1011             ("subsetp" "f_subset.htm")
1012             ("subst" "f_substc.htm")
1013             ("subst-if" "f_substc.htm")
1014             ("subst-if-not" "f_substc.htm")
1015             ("substitute" "f_sbs_s.htm")
1016             ("substitute-if" "f_sbs_s.htm")
1017             ("substitute-if-not" "f_sbs_s.htm")
1018             ("subtypep" "f_subtpp.htm")
1019             ("svref" "f_svref.htm")
1020             ("sxhash" "f_sxhash.htm")
1021             ("symbol" "t_symbol.htm")
1022             ("symbol-function" "f_symb_1.htm")
1023             ("symbol-macrolet" "s_symbol.htm")
1024             ("symbol-name" "f_symb_2.htm")
1025             ("symbol-package" "f_symb_3.htm")
1026             ("symbol-plist" "f_symb_4.htm")
1027             ("symbol-value" "f_symb_5.htm")
1028             ("symbolp" "f_symbol.htm")
1029             ("synonym-stream" "t_syn_st.htm")
1030             ("synonym-stream-symbol" "f_syn_st.htm")
1031             ("t" "a_t.htm")
1032             ("tagbody" "s_tagbod.htm")
1033             ("tailp" "f_ldiffc.htm")
1034             ("tan" "f_sin_c.htm")
1035             ("tanh" "f_sinh_.htm")
1036             ("tenth" "f_firstc.htm")
1037             ("terpri" "f_terpri.htm")
1038             ("the" "s_the.htm")
1039             ("third" "f_firstc.htm")
1040             ("throw" "s_throw.htm")
1041             ("time" "m_time.htm")
1042             ("trace" "m_tracec.htm")
1043             ("translate-logical-pathname" "f_tr_log.htm")
1044             ("translate-pathname" "f_tr_pn.htm")
1045             ("tree-equal" "f_tree_e.htm")
1046             ("truename" "f_tn.htm")
1047             ("truncate" "f_floorc.htm")
1048             ("two-way-stream" "t_two_wa.htm")
1049             ("two-way-stream-input-stream" "f_two_wa.htm")
1050             ("two-way-stream-output-stream" "f_two_wa.htm")
1051             ("type" "a_type.htm")
1052             ("type-error" "e_tp_err.htm")
1053             ("type-error-datum" "f_tp_err.htm")
1054             ("type-error-expected-type" "f_tp_err.htm")
1055             ("type-of" "f_tp_of.htm")
1056             ("typecase" "m_tpcase.htm")
1057             ("typep" "f_typep.htm")
1058             ("unbound-slot" "e_unboun.htm")
1059             ("unbound-slot-instance" "f_unboun.htm")
1060             ("unbound-variable" "e_unbo_1.htm")
1061             ("undefined-function" "e_undefi.htm")
1062             ("unexport" "f_unexpo.htm")
1063             ("unintern" "f_uninte.htm")
1064             ("union" "f_unionc.htm")
1065             ("unless" "m_when_.htm")
1066             ("unread-char" "f_unrd_c.htm")
1067             ("unsigned-byte" "t_unsgn_.htm")
1068             ("untrace" "m_tracec.htm")
1069             ("unuse-package" "f_unuse_.htm")
1070             ("unwind-protect" "s_unwind.htm")
1071             ("update-instance-for-different-class" "f_update.htm")
1072             ("update-instance-for-redefined-class" "f_upda_1.htm")
1073             ("upgraded-array-element-type" "f_upgr_1.htm")
1074             ("upgraded-complex-part-type" "f_upgrad.htm")
1075             ("upper-case-p" "f_upper_.htm")
1076             ("use-package" "f_use_pk.htm")
1077             ("use-value" "a_use_va.htm")
1078             ("user-homedir-pathname" "f_user_h.htm")
1079             ("values" "a_values.htm")
1080             ("values-list" "f_vals_l.htm")
1081             ("variable" "f_docume.htm")
1082             ("vector" "a_vector.htm")
1083             ("vector-pop" "f_vec_po.htm")
1084             ("vector-push" "f_vec_ps.htm")
1085             ("vector-push-extend" "f_vec_ps.htm")
1086             ("vectorp" "f_vecp.htm")
1087             ("warn" "f_warn.htm")
1088             ("warning" "e_warnin.htm")
1089             ("when" "m_when_.htm")
1090             ("wild-pathname-p" "f_wild_p.htm")
1091             ("with-accessors" "m_w_acce.htm")
1092             ("with-compilation-unit" "m_w_comp.htm")
1093             ("with-condition-restarts" "m_w_cnd_.htm")
1094             ("with-hash-table-iterator" "m_w_hash.htm")
1095             ("with-input-from-string" "m_w_in_f.htm")
1096             ("with-open-file" "m_w_open.htm")
1097             ("with-open-stream" "m_w_op_1.htm")
1098             ("with-output-to-string" "m_w_out_.htm")
1099             ("with-package-iterator" "m_w_pkg_.htm")
1100             ("with-simple-restart" "m_w_smp_.htm")
1101             ("with-slots" "m_w_slts.htm")
1102             ("with-standard-io-syntax" "m_w_std_.htm")
1103             ("write" "f_wr_pr.htm")
1104             ("write-byte" "f_wr_by.htm")
1105             ("write-char" "f_wr_cha.htm")
1106             ("write-line" "f_wr_stg.htm")
1107             ("write-sequence" "f_wr_seq.htm")
1108             ("write-string" "f_wr_stg.htm")
1109             ("write-to-string" "f_wr_to_.htm")
1110             ("y-or-n-p" "f_y_or_n.htm")
1111             ("yes-or-no-p" "f_y_or_n.htm")
1112             ("zerop" "f_zerop.htm"))))
1113                 
1114 (provide 'hyperspec)
1115
1116 ;;; hyperspec.el ends here