c1dd7f6125d8e637148149bda2fa772be8769e82
[sbcl.git] / src / compiler / fndb.lisp
1 ;;;; This file defines all the standard functions to be known
2 ;;;; functions. Each function has type and side-effect information,
3 ;;;; and may also have IR1 optimizers.
4
5 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; more information.
7 ;;;;
8 ;;;; This software is derived from the CMU CL system, which was
9 ;;;; written at Carnegie Mellon University and released into the
10 ;;;; public domain. The software is in the public domain and is
11 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
12 ;;;; files for more information.
13
14 (in-package "SB!C")
15 \f
16 ;;;; information for known functions:
17
18 (defknown coerce (t type-specifier) t
19   ;; Note:
20   ;; (1) This is not FLUSHABLE because it's defined to signal errors.
21   ;; (2) It's not worth trying to make this FOLDABLE in the
22   ;;     cross-compiler,because
23   ;;       (a) it would probably be really hard to make all the 
24   ;;           tricky issues (e.g. which specialized array types are
25   ;;           supported) match between cross-compiler and target
26   ;;           compiler, and besides
27   ;;       (b) leaving it not FOLDABLE lets us use the idiom
28   ;;               (COERCE FOO 'SOME-SPECIALIZED-ARRAY-TYPE-OR-ANOTHER)
29   ;;           as a way of delaying the generation of specialized
30   ;;           array types until runtime, which helps us keep the
31   ;;           cross-compiler's dumper relatively simple and which
32   ;;           lets us preserve distinctions which might not even exist
33   ;;           on the cross-compilation host (because ANSI doesn't
34   ;;           guarantee that specialized array types exist there).
35   (movable #-sb-xc-host foldable)
36   :derive-type (result-type-specifier-nth-arg 2))
37 (defknown list-to-simple-string* (list) simple-string)
38 (defknown list-to-bit-vector* (list) bit-vector)
39 (defknown list-to-vector* (list type) vector)
40 (defknown list-to-simple-vector* (list) simple-vector)
41 (defknown vector-to-vector* (vector type) vector)
42 (defknown vector-to-simple-string* (vector) vector)
43
44 (defknown type-of (t) t (foldable flushable))
45
46 ;;; These can be affected by type definitions, so they're not FOLDABLE.
47 (defknown (upgraded-complex-part-type upgraded-array-element-type)
48           (type-specifier) type-specifier
49   (flushable))
50 \f
51 ;;;; from the "Predicates" chapter:
52
53 ;;; FIXME: Is it right to have TYPEP (and TYPE-OF, elsewhere; and
54 ;;; perhaps SPECIAL-OPERATOR-P and others) be FOLDABLE in the
55 ;;; cross-compilation host? After all, some type relationships (e.g.
56 ;;; FIXNUMness) might be different between host and target. Perhaps
57 ;;; this property should be protected by #-SB-XC-HOST? Perhaps we need
58 ;;; 3-stage bootstrapping after all? (Ugh! It's *so* slow already!)
59 (defknown typep (t type-specifier) boolean
60   (flushable
61    ;; Unlike SUBTYPEP or UPGRADED-ARRAY-ELEMENT-TYPE and friends, this
62    ;; seems to be FOLDABLE. Like SUBTYPEP, it's affected by type
63    ;; definitions, but unlike SUBTYPEP, there should be no way to make
64    ;; a TYPEP expression with constant arguments which doesn't return
65    ;; an error before the type declaration (because of undefined
66    ;; type). E.g. you can do
67    ;;   (SUBTYPEP 'INTEGER 'FOO) => NIL, NIL
68    ;;   (DEFTYPE FOO () T)
69    ;;   (SUBTYPEP 'INTEGER 'FOO) => T, T
70    ;; but the analogous
71    ;;   (TYPEP 12 'FOO)
72    ;;   (DEFTYPE FOO () T)
73    ;;   (TYPEP 12 'FOO)
74    ;; doesn't work because the first call is an error.
75    ;;
76    ;; (UPGRADED-ARRAY-ELEMENT-TYPE and UPGRADED-COMPLEX-PART-TYPE have
77    ;; behavior like SUBTYPEP in this respect, not like TYPEP.)
78    foldable))
79 (defknown subtypep (type-specifier type-specifier) (values boolean boolean) 
80   ;; This is not FOLDABLE because its value is affected by type
81   ;; definitions.
82   ;;
83   ;; FIXME: Is it OK to fold this when the types have already been
84   ;; defined? Does the code inherited from CMU CL already do this?
85   (flushable)) 
86
87 (defknown (null symbolp atom consp listp numberp integerp rationalp floatp
88                 complexp characterp stringp bit-vector-p vectorp
89                 simple-vector-p simple-string-p simple-bit-vector-p arrayp
90                 sb!xc:packagep functionp compiled-function-p not)
91   (t) boolean (movable foldable flushable))
92
93 (defknown (eq eql) (t t) boolean (movable foldable flushable))
94 (defknown (equal equalp) (t t) boolean (foldable flushable recursive))
95 \f
96 ;;;; classes
97
98 (sb!xc:deftype name-for-class () 't)
99 (defknown class-name (sb!xc:class) name-for-class (flushable))
100 (defknown find-class (name-for-class &optional t lexenv)
101   (or sb!xc:class null) ())
102 (defknown class-of (t) sb!xc:class (flushable))
103 (defknown layout-of (t) layout (flushable))
104 (defknown copy-structure (structure-object) structure-object
105   (flushable unsafe))
106 \f
107 ;;;; from the "Control Structure" chapter:
108
109 ;;; This is not FLUSHABLE, since it's required to signal an error if
110 ;;; unbound.
111 (defknown (symbol-value symbol-function) (symbol) t ())
112
113 (defknown boundp (symbol) boolean (flushable))
114 (defknown fboundp ((or symbol cons)) boolean (flushable explicit-check))
115 (defknown special-operator-p (symbol) t
116   ;; The set of special operators never changes.
117   (movable foldable flushable)) 
118 (defknown set (symbol t) t (unsafe)
119   :derive-type #'result-type-last-arg)
120 (defknown fdefinition ((or symbol cons)) function (unsafe explicit-check))
121 (defknown %set-fdefinition ((or symbol cons) function) function
122   (unsafe explicit-check))
123 (defknown makunbound (symbol) symbol)
124 (defknown fmakunbound ((or symbol cons)) (or symbol cons)
125   (unsafe explicit-check))
126 (defknown (get-setf-method get-setf-method-multiple-value)
127   ((or list symbol) &optional lexenv)
128   (values list list list form form)
129   (flushable))
130 (defknown apply (callable t &rest t) *) ; ### Last arg must be List...
131 (defknown funcall (callable &rest t) *)
132
133 (defknown (mapcar maplist mapcan mapcon) (callable list &rest list) list
134   (call))
135
136 (defknown (mapc mapl) (callable list &rest list) list (foldable call))
137
138 ;;; We let VALUES-LIST be foldable, since constant-folding will turn
139 ;;; it into VALUES. VALUES is not foldable, since MV constants are
140 ;;; represented by a call to VALUES.
141 (defknown values (&rest t) * (movable flushable unsafe))
142 (defknown values-list (list) * (movable foldable flushable))
143 \f
144 ;;;; from the "Macros" chapter:
145
146 (defknown macro-function (symbol &optional lexenv)
147   (or function null)
148   (flushable))
149 (defknown (macroexpand macroexpand-1) (t &optional lexenv)
150   (values form &optional boolean))
151
152 (defknown compiler-macro-function (t &optional lexenv)
153   (or function null)
154   (flushable))
155 \f
156 ;;;; from the "Declarations" chapter:
157
158 (defknown proclaim (list) (values) (recursive))
159
160 ;;;; from the "Symbols" chapter:
161
162 (defknown get (symbol t &optional t) t (flushable))
163 (defknown remprop (symbol t) t)
164 (defknown symbol-plist (symbol) list (flushable))
165 (defknown getf (list t &optional t) t (foldable flushable))
166 (defknown get-properties (list list) (values t t list) (foldable flushable))
167 (defknown symbol-name (symbol) simple-string (movable foldable flushable))
168 (defknown make-symbol (string) symbol (flushable))
169 (defknown copy-symbol (symbol &optional t) symbol (flushable))
170 (defknown gensym (&optional (or string unsigned-byte)) symbol ())
171 (defknown symbol-package (symbol) (or sb!xc:package null) (flushable))
172 (defknown keywordp (t) boolean (flushable))       ; If someone uninterns it...
173 \f
174 ;;;; from the "Packages" chapter:
175
176 (sb!xc:deftype package-designator () '(or stringable sb!xc:package))
177 (sb!xc:deftype symbols () '(or list symbol))
178
179 ;;; Should allow a package name, I think, tho CLtL II doesn't say so...
180 (defknown gentemp (&optional string package-designator) symbol)
181
182 (defknown make-package (stringable &key
183                                    (:use list)
184                                    (:nicknames list)
185                                    ;; ### Extensions...
186                                    (:internal-symbols index)
187                                    (:external-symbols index))
188   sb!xc:package)
189 (defknown find-package (package-designator) (or sb!xc:package null)
190   (flushable))
191 (defknown package-name (package-designator) (or simple-string null)
192   (flushable))
193 (defknown package-nicknames (package-designator) list (flushable))
194 (defknown rename-package (package-designator package-designator &optional list)
195   sb!xc:package)
196 (defknown package-use-list (package-designator) list (flushable))
197 (defknown package-used-by-list (package-designator) list (flushable))
198 (defknown package-shadowing-symbols (package-designator) list (flushable))
199 (defknown list-all-packages () list (flushable))
200 (defknown intern (string &optional package-designator)
201   (values symbol (member :internal :external :inherited nil))
202   ())
203 (defknown find-symbol (string &optional package-designator)
204   (values symbol (member :internal :external :inherited nil))
205   (flushable))
206 (defknown (export import) (symbols &optional package-designator) (eql t))
207 (defknown unintern (symbol &optional package-designator) boolean)
208 (defknown unexport (symbols &optional package-designator) (eql t))
209 (defknown shadowing-import (symbols &optional package-designator) (eql t))
210 (defknown shadow ((or symbol string list) &optional package-designator) (eql t))
211 (defknown (use-package unuse-package) ((or list package-designator) &optional package-designator) (eql t))
212 (defknown find-all-symbols (stringable) list (flushable))
213 \f
214 ;;;; from the "Numbers" chapter:
215
216 (defknown zerop (number) boolean (movable foldable flushable explicit-check))
217 (defknown (plusp minusp) (real) boolean
218   (movable foldable flushable explicit-check))
219 (defknown (oddp evenp) (integer) boolean
220   (movable foldable flushable explicit-check))
221 (defknown (= /=) (number &rest number) boolean
222   (movable foldable flushable explicit-check))
223 (defknown (< > <= >=) (real &rest real) boolean
224   (movable foldable flushable explicit-check))
225 (defknown (max min) (real &rest real) real
226   (movable foldable flushable explicit-check))
227
228 (defknown + (&rest number) number
229   (movable foldable flushable explicit-check))
230 (defknown - (number &rest number) number
231   (movable foldable flushable explicit-check))
232 (defknown * (&rest number) number
233   (movable foldable flushable explicit-check))
234 (defknown / (number &rest number) number
235   (movable foldable flushable explicit-check))
236 (defknown (1+ 1-) (number) number
237   (movable foldable flushable explicit-check))
238
239 (defknown conjugate (number) number
240   (movable foldable flushable explicit-check))
241
242 (defknown gcd (&rest integer) unsigned-byte
243   (movable foldable flushable explicit-check)
244   #|:derive-type 'boolean-result-type|#)
245 (defknown lcm (&rest integer) unsigned-byte
246   (movable foldable flushable explicit-check))
247
248 #!-propagate-fun-type
249 (defknown exp (number) irrational
250   (movable foldable flushable explicit-check recursive)
251   :derive-type #'result-type-float-contagion)
252
253 #!+propagate-fun-type
254 (defknown exp (number) irrational
255   (movable foldable flushable explicit-check recursive))
256
257 (defknown expt (number number) number
258   (movable foldable flushable explicit-check recursive))
259 (defknown log (number &optional real) irrational
260   (movable foldable flushable explicit-check))
261 (defknown sqrt (number) irrational
262   (movable foldable flushable explicit-check))
263 (defknown isqrt (unsigned-byte) unsigned-byte
264   (movable foldable flushable explicit-check recursive))
265
266 (defknown (abs phase signum) (number) number
267   (movable foldable flushable explicit-check))
268 (defknown cis (real) (complex float)
269   (movable foldable flushable explicit-check))
270
271 #!-propagate-fun-type
272 (progn
273 (defknown (sin cos) (number)
274   (or (float -1.0 1.0) (complex float))
275   (movable foldable flushable explicit-check recursive)
276   :derive-type #'result-type-float-contagion)
277
278 (defknown atan
279   (number &optional real) irrational
280   (movable foldable flushable explicit-check recursive)
281   :derive-type #'result-type-float-contagion)
282
283 (defknown (tan sinh cosh tanh asinh)
284   (number) irrational (movable foldable flushable explicit-check recursive)
285   :derive-type #'result-type-float-contagion)
286 ) ; PROGN
287
288 #!+propagate-fun-type
289 (progn
290 (defknown (sin cos) (number)
291   (or (float -1.0 1.0) (complex float))
292   (movable foldable flushable explicit-check recursive))
293
294 (defknown atan
295   (number &optional real) irrational
296   (movable foldable flushable explicit-check recursive))
297
298 (defknown (tan sinh cosh tanh asinh)
299   (number) irrational (movable foldable flushable explicit-check recursive))
300 ) ; PROGN
301
302 (defknown (asin acos acosh atanh)
303   (number) irrational
304   (movable foldable flushable explicit-check recursive))
305
306 (defknown float (real &optional float) float
307   (movable foldable flushable explicit-check))
308
309 (defknown (rational) (real) rational
310   (movable foldable flushable explicit-check))
311
312 (defknown (rationalize) (real) rational
313   (movable foldable flushable explicit-check recursive))
314
315 (defknown (numerator denominator) (rational) integer
316   (movable foldable flushable))
317
318 (defknown (floor ceiling truncate round)
319   (real &optional real) (values integer real)
320   (movable foldable flushable explicit-check))
321
322 (defknown (mod rem) (real real) real
323   (movable foldable flushable explicit-check))
324
325 (defknown (ffloor fceiling fround ftruncate)
326   (real &optional real) (values float float)
327   (movable foldable flushable explicit-check))
328
329 (defknown decode-float (float) (values float float-exponent float)
330   (movable foldable flushable explicit-check))
331 (defknown scale-float (float float-exponent) float
332   (movable foldable flushable explicit-check))
333 (defknown float-radix (float) float-radix
334   (movable foldable flushable explicit-check))
335 (defknown float-sign (float &optional float) float
336   (movable foldable flushable explicit-check))
337 (defknown (float-digits float-precision) (float) float-digits
338   (movable foldable flushable explicit-check))
339 (defknown integer-decode-float (float)
340           (values integer float-exponent (member -1 1))
341           (movable foldable flushable explicit-check))
342
343 (defknown complex (real &optional real) number
344   (movable foldable flushable explicit-check))
345
346 (defknown (realpart imagpart) (number) real (movable foldable flushable))
347
348 (defknown (logior logxor logand logeqv) (&rest integer) integer
349   (movable foldable flushable explicit-check))
350
351 (defknown (lognand lognor logandc1 logandc2 logorc1 logorc2)
352           (integer integer) integer
353   (movable foldable flushable explicit-check))
354
355 (defknown boole (boole-code integer integer) integer
356   (movable foldable flushable))
357
358 (defknown lognot (integer) integer (movable foldable flushable explicit-check))
359 (defknown logtest (integer integer) boolean (movable foldable flushable))
360 (defknown logbitp (bit-index integer) boolean (movable foldable flushable))
361 (defknown ash (integer integer) integer (movable foldable flushable explicit-check))
362 (defknown (logcount integer-length) (integer) bit-index
363   (movable foldable flushable explicit-check))
364 ;;; FIXME: According to the ANSI spec, it's legal to use any
365 ;;; nonnegative indices for BYTE arguments, not just BIT-INDEX. It's
366 ;;; hard to come up with useful ways to do this, but it is possible to
367 ;;; come up with *legal* ways to do this, so it would be nice
368 ;;; to fix this so we comply with the spec.
369 (defknown byte (bit-index bit-index) byte-specifier
370   (movable foldable flushable))
371 (defknown (byte-size byte-position) (byte-specifier) bit-index
372   (movable foldable flushable))
373 (defknown ldb (byte-specifier integer) integer (movable foldable flushable))
374 (defknown ldb-test (byte-specifier integer) boolean
375   (movable foldable flushable))
376 (defknown mask-field (byte-specifier integer) integer
377   (movable foldable flushable))
378 (defknown dpb (integer byte-specifier integer) integer
379   (movable foldable flushable))
380 (defknown deposit-field (integer byte-specifier integer) integer
381   (movable foldable flushable))
382 (defknown random ((real (0)) &optional random-state) (real 0) ())
383 (defknown make-random-state (&optional (or (member nil t) random-state))
384   random-state (flushable))
385 (defknown random-state-p (t) boolean (movable foldable flushable))
386 \f
387 ;;;; from the "Characters" chapter:
388 (defknown (standard-char-p graphic-char-p alpha-char-p
389                            upper-case-p lower-case-p both-case-p alphanumericp)
390   (character) boolean (movable foldable flushable))
391
392 (defknown digit-char-p (character &optional unsigned-byte)
393   (or (integer 0 35) null) (movable foldable flushable))
394
395 (defknown (char= char/= char< char> char<= char>= char-equal char-not-equal
396                  char-lessp char-greaterp char-not-greaterp char-not-lessp)
397   (character &rest character) boolean (movable foldable flushable))
398
399 (defknown character (t) character (movable foldable flushable))
400 (defknown char-code (character) char-code (movable foldable flushable))
401 (defknown (char-upcase char-downcase) (character) character
402   (movable foldable flushable))
403 (defknown digit-char (integer &optional integer)
404   (or character null) (movable foldable flushable))
405 (defknown char-int (character) char-code (movable foldable flushable))
406 (defknown char-name (character) (or simple-string null)
407   (movable foldable flushable))
408 (defknown name-char (stringable) (or character null)
409   (movable foldable flushable))
410 (defknown code-char (char-code) base-char
411   ;; By suppressing constant folding on CODE-CHAR when the
412   ;; cross-compiler is running in the cross-compilation host vanilla
413   ;; ANSI Common Lisp, we can use CODE-CHAR expressions to delay until
414   ;; target Lisp run time the generation of CHARACTERs which aren't
415   ;; STANDARD-CHARACTERs. That way, we don't need to rely on the host
416   ;; Common Lisp being able to handle any characters other than those
417   ;; guaranteed by the ANSI spec.
418   (movable #-sb-xc-host foldable flushable))
419 \f
420 ;;;; from the "Sequences" chapter:
421
422 (defknown elt (sequence index) t (foldable flushable))
423
424 (defknown subseq (sequence index &optional sequence-end) consed-sequence
425   (flushable)
426   :derive-type (sequence-result-nth-arg 1))
427
428 (defknown copy-seq (sequence) consed-sequence (flushable)
429   :derive-type #'result-type-first-arg)
430
431 (defknown length (sequence) index (foldable flushable))
432
433 (defknown reverse (sequence) consed-sequence (flushable)
434   :derive-type #'result-type-first-arg)
435
436 (defknown nreverse (sequence) sequence ()
437   :derive-type #'result-type-first-arg)
438
439 (defknown make-sequence (type-specifier index
440                                         &key
441                                         (:initial-element t))
442   consed-sequence
443   (movable flushable unsafe)
444   :derive-type (result-type-specifier-nth-arg 1))
445
446 (defknown concatenate (type-specifier &rest sequence) consed-sequence
447   (flushable)
448   :derive-type (result-type-specifier-nth-arg 1))
449
450 (defknown (map %map) (type-specifier callable sequence &rest sequence) consed-sequence
451   (flushable call)
452 ; :DERIVE-TYPE 'TYPE-SPEC-ARG1 ? Nope... (MAP NIL ...) returns NULL, not NIL.
453   )
454 (defknown %map-to-list-arity-1 (callable sequence) list (flushable call))
455 (defknown %map-to-simple-vector-arity-1 (callable sequence) simple-vector
456   (flushable call))
457 (defknown %map-to-nil-on-simple-vector (callable simple-vector) null
458   (flushable call))
459 (defknown %map-to-nil-on-vector (callable vector) null (flushable call))
460 (defknown %map-to-nil-on-sequence (callable sequence) null (flushable call))
461
462 ;;; returns the result from the predicate...
463 (defknown some (callable sequence &rest sequence) t
464   (foldable flushable call))
465
466 (defknown (every notany notevery) (callable sequence &rest sequence) boolean
467   (foldable flushable call))
468
469 ;;; unsafe for :INITIAL-VALUE...
470 (defknown reduce (callable
471                   sequence
472                   &key
473                   (:from-end t)
474                   (:start index)
475                   (:end sequence-end)
476                   (:initial-value t)
477                   (:key callable))
478   t
479   (foldable flushable call unsafe))
480
481 (defknown fill (sequence t &key (:start index) (:end sequence-end)) sequence
482   (unsafe)
483   :derive-type #'result-type-first-arg)
484
485 (defknown replace (sequence
486                    sequence
487                    &key
488                    (:start1 index)
489                    (:end1 sequence-end)
490                    (:start2 index)
491                    (:end2 sequence-end))
492   sequence ()
493   :derive-type #'result-type-first-arg)
494
495 (defknown remove
496   (t sequence &key (:from-end t) (:test callable)
497      (:test-not callable) (:start index) (:end sequence-end)
498      (:count sequence-end) (:key callable))
499   consed-sequence
500   (flushable call)
501   :derive-type (sequence-result-nth-arg 2))
502
503 (defknown substitute
504   (t t sequence &key (:from-end t) (:test callable)
505      (:test-not callable) (:start index) (:end sequence-end)
506      (:count sequence-end) (:key callable))
507   consed-sequence
508   (flushable call)
509   :derive-type (sequence-result-nth-arg 3))
510
511 (defknown (remove-if remove-if-not)
512   (callable sequence &key (:from-end t) (:start index) (:end sequence-end)
513             (:count sequence-end) (:key callable))
514   consed-sequence
515   (flushable call)
516   :derive-type (sequence-result-nth-arg 2))
517
518 (defknown (substitute-if substitute-if-not)
519   (t callable sequence &key (:from-end t) (:start index) (:end sequence-end)
520      (:count sequence-end) (:key callable))
521   consed-sequence
522   (flushable call)
523   :derive-type (sequence-result-nth-arg 3))
524
525 (defknown delete
526   (t sequence &key (:from-end t) (:test callable)
527      (:test-not callable) (:start index) (:end sequence-end)
528      (:count sequence-end) (:key callable))
529   sequence
530   (flushable call)
531   :derive-type (sequence-result-nth-arg 2))
532
533 (defknown nsubstitute
534   (t t sequence &key (:from-end t) (:test callable)
535      (:test-not callable) (:start index) (:end sequence-end)
536      (:count sequence-end) (:key callable))
537   sequence
538   (flushable call)
539   :derive-type (sequence-result-nth-arg 3))
540
541 (defknown (delete-if delete-if-not)
542   (callable sequence &key (:from-end t) (:start index) (:end sequence-end)
543             (:count sequence-end) (:key callable))
544   sequence
545   (flushable call)
546   :derive-type (sequence-result-nth-arg 2))
547
548 (defknown (nsubstitute-if nsubstitute-if-not)
549   (t callable sequence &key (:from-end t) (:start index) (:end sequence-end)
550      (:count sequence-end) (:key callable))
551   sequence
552   (flushable call)
553   :derive-type (sequence-result-nth-arg 3))
554
555 (defknown remove-duplicates
556   (sequence &key (:test callable) (:test-not callable) (:start index) (:from-end t)
557             (:end sequence-end) (:key callable))
558   consed-sequence
559   (flushable call)
560   :derive-type (sequence-result-nth-arg 1))
561
562 (defknown delete-duplicates
563   (sequence &key (:test callable) (:test-not callable) (:start index) (:from-end t)
564             (:end sequence-end) (:key callable))
565   sequence
566   (flushable call)
567   :derive-type (sequence-result-nth-arg 1))
568
569 (defknown find (t sequence &key (:test callable) (:test-not callable)
570                   (:start index) (:from-end t) (:end sequence-end) (:key callable))
571   t
572   (foldable flushable call))
573
574 (defknown (find-if find-if-not)
575   (callable sequence &key (:from-end t) (:start index) (:end sequence-end)
576             (:key callable))
577   t
578   (foldable flushable call))
579
580 (defknown position (t sequence &key (:test callable) (:test-not callable)
581                       (:start index) (:from-end t) (:end sequence-end)
582                       (:key callable))
583   (or index null)
584   (foldable flushable call))
585
586 (defknown (position-if position-if-not)
587   (callable sequence &key (:from-end t) (:start index) (:end sequence-end)
588             (:key callable))
589   (or index null)
590   (foldable flushable call))
591
592 (defknown count (t sequence &key (:test callable) (:test-not callable)
593                       (:start index) (:from-end t) (:end sequence-end)
594                       (:key callable))
595   index
596   (foldable flushable call))
597
598 (defknown (count-if count-if-not)
599   (callable sequence &key (:from-end t) (:start index) (:end sequence-end)
600             (:key callable))
601   index
602   (foldable flushable call))
603
604 (defknown (mismatch search)
605   (sequence sequence &key (:from-end t) (:test callable) (:test-not callable)
606             (:start1 index) (:end1 sequence-end) (:start2 index) (:end2 sequence-end)
607             (:key callable))
608   (or index null)
609   (foldable flushable call))
610
611 ;;; not FLUSHABLE, since vector sort guaranteed in-place...
612 (defknown (stable-sort sort) (sequence callable &key (:key callable)) sequence
613   (call)
614   :derive-type (sequence-result-nth-arg 1))
615
616 (defknown merge (type-specifier sequence sequence callable
617                                 &key (:key callable))
618   sequence
619   (flushable call)
620   :derive-type (result-type-specifier-nth-arg 1))
621
622 ;;; not FLUSHABLE, despite what CMU CL's DEFKNOWN said..
623 (defknown read-sequence (sequence stream
624                                   &key
625                                   (:start index)
626                                   (:end sequence-end))
627   (index)
628   ())
629
630 (defknown write-sequence (sequence stream
631                                    &key
632                                    (:start index)
633                                    (:end sequence-end))
634   sequence
635   ()
636   :derive-type (sequence-result-nth-arg 1))
637 \f
638 ;;;; from the "Manipulating List Structure" chapter:
639 (defknown (car cdr caar cadr cdar cddr
640                caaar caadr cadar caddr cdaar cdadr cddar cdddr
641                caaaar caaadr caadar caaddr cadaar cadadr caddar cadddr
642                cdaaar cdaadr cdadar cdaddr cddaar cddadr cdddar cddddr
643                first second third fourth fifth sixth seventh eighth ninth tenth
644                rest)
645   (list)
646   t
647   (foldable flushable))
648
649 (defknown cons (t t) cons (movable flushable unsafe))
650
651 (defknown tree-equal (t t &key (:test callable) (:test-not callable)) boolean
652   (foldable flushable call))
653 (defknown endp (t) boolean (foldable flushable movable))
654 (defknown list-length (list) (or index null) (foldable flushable))
655 (defknown (nth nthcdr) (index list) t (foldable flushable))
656 (defknown last (list &optional index) list (foldable flushable))
657 (defknown list (&rest t) list (movable flushable unsafe))
658 (defknown list* (t &rest t) t (movable flushable unsafe))
659 (defknown make-list (index &key (:initial-element t)) list
660   (movable flushable unsafe))
661
662 ;;; All but last must be list...
663 (defknown append (&rest t) t (flushable))
664
665 (defknown copy-list (list) list (flushable))
666 (defknown copy-alist (list) list (flushable))
667 (defknown copy-tree (t) t (flushable recursive))
668 (defknown revappend (list t) t (flushable))
669 (defknown nconc (&rest list) list ())
670 (defknown nreconc (list t) list ())
671 (defknown butlast (list &optional index) list (flushable))
672 (defknown nbutlast (list &optional index) list ())
673 (defknown ldiff (list t) list (flushable))
674 (defknown (rplaca rplacd) (cons t) list (unsafe))
675
676 (defknown (nsubst subst) (t t t &key (:key callable) (:test callable)
677                             (:test-not callable))
678   list (flushable unsafe call))
679
680 (defknown (subst-if subst-if-not nsubst-if nsubst-if-not)
681           (t t t &key (:key callable))
682   list (flushable unsafe call))
683
684 (defknown (sublis nsublis) (list t &key (:key callable) (:test callable)
685                                  (:test-not callable))
686   list (flushable unsafe call))
687
688 (defknown member (t list &key (:key callable) (:test callable)
689                     (:test-not callable))
690   list (foldable flushable call))
691 (defknown (member-if member-if-not) (callable list &key (:key callable))
692   list (foldable flushable call))
693
694 (defknown tailp (t list) boolean (foldable flushable))
695
696 (defknown adjoin (t list &key (:key callable) (:test callable)
697                     (:test-not callable))
698   list (foldable flushable unsafe call))
699
700 (defknown (union intersection set-difference set-exclusive-or)
701           (list list &key (:key callable) (:test callable) (:test-not callable))
702   list
703   (foldable flushable call))
704
705 (defknown (nunion nintersection nset-difference nset-exclusive-or)
706           (list list &key (:key callable) (:test callable) (:test-not callable))
707   list
708   (foldable flushable call))
709
710 (defknown subsetp
711           (list list &key (:key callable) (:test callable) (:test-not callable))
712   boolean
713   (foldable flushable call))
714
715 (defknown acons (t t t) list (movable flushable unsafe))
716 (defknown pairlis (t t &optional t) list (flushable unsafe))
717
718 (defknown (rassoc assoc)
719           (t list &key (:key callable) (:test callable) (:test-not callable))
720   list (foldable flushable call))
721 (defknown (assoc-if-not assoc-if rassoc-if rassoc-if-not)
722           (callable list &key (:key callable)) list (foldable flushable call))
723
724 (defknown (memq assq) (t list) list (foldable flushable unsafe))
725 (defknown delq (t list) list (flushable unsafe))
726 \f
727 ;;;; from the "Hash Tables" chapter:
728
729 (defknown make-hash-table
730   (&key (:test callable) (:size unsigned-byte)
731         (:rehash-size (or (integer 1) (float (1.0))))
732         (:rehash-threshold (real 0 1))
733         (:weak-p t))
734   hash-table
735   (flushable unsafe))
736 (defknown hash-table-p (t) boolean (movable foldable flushable))
737 (defknown gethash (t hash-table &optional t) (values t boolean)
738   (flushable unsafe)) ; not FOLDABLE, since hash table contents can change
739 (defknown %puthash (t hash-table t) t (unsafe))
740 (defknown remhash (t hash-table) boolean ())
741 (defknown maphash (callable hash-table) null (flushable call))
742 (defknown clrhash (hash-table) hash-table ())
743 (defknown hash-table-count (hash-table) index (flushable))
744 (defknown hash-table-rehash-size (hash-table) (or (integer 1) (float (1.0)))
745   (foldable flushable))
746 (defknown hash-table-rehash-threshold (hash-table) (real 0 1)
747   (foldable flushable))
748 (defknown hash-table-size (hash-table) index (flushable))
749 (defknown hash-table-test (hash-table) symbol (foldable flushable))
750 (defknown sxhash (t) (integer 0 #.sb!vm:*target-most-positive-fixnum*)
751   (foldable flushable))
752 \f
753 ;;;; from the "Arrays" chapter
754
755 (defknown make-array ((or index list)
756                       &key
757                       (:element-type type-specifier)
758                       (:initial-element t)
759                       (:initial-contents t)
760                       (:adjustable t)
761                       (:fill-pointer t)
762                       (:displaced-to (or array null))
763                       (:displaced-index-offset index))
764   array (flushable unsafe))
765
766 (defknown vector (&rest t) simple-vector (flushable unsafe))
767
768 (defknown aref (array &rest index) t (foldable flushable))
769 (defknown row-major-aref (array index) t (foldable flushable))
770
771 (defknown array-element-type (array)
772   type-specifier
773   (foldable flushable recursive))
774 (defknown array-rank (array) array-rank (foldable flushable))
775 (defknown array-dimension (array array-rank) index (foldable flushable))
776 (defknown array-dimensions (array) list (foldable flushable))
777 (defknown array-in-bounds-p (array &rest index) boolean (foldable flushable))
778 (defknown array-row-major-index (array &rest index) array-total-size
779   (foldable flushable))
780 (defknown array-total-size (array) array-total-size (foldable flushable))
781 (defknown adjustable-array-p (array) boolean (movable foldable flushable))
782
783 (defknown svref (simple-vector index) t (foldable flushable))
784 (defknown bit ((array bit) &rest index) bit (foldable flushable))
785 (defknown sbit ((simple-array bit) &rest index) bit (foldable flushable))
786
787 (defknown (bit-and bit-ior bit-xor bit-eqv bit-nand bit-nor bit-andc1 bit-andc2
788                    bit-orc1 bit-orc2)
789   ((array bit) (array bit) &optional (or (array bit) (member t)))
790   (array bit)
791   (foldable)
792   #|:derive-type #'result-type-last-arg|#)
793
794 (defknown bit-not ((array bit) &optional (or (array bit) (member t)))
795   (array bit)
796   (foldable)
797   #|:derive-type #'result-type-last-arg|#)
798
799 (defknown array-has-fill-pointer-p (array) boolean (movable foldable flushable))
800 (defknown fill-pointer (vector) index (foldable flushable))
801 (defknown vector-push (t vector) (or index null) ())
802 (defknown vector-push-extend (t vector &optional index) index ())
803 (defknown vector-pop (vector) t ())
804
805 (defknown adjust-array
806   (array (or index list) &key (:element-type type-specifier)
807          (:initial-element t) (:initial-contents list)
808          (:fill-pointer t) (:displaced-to (or array null))
809          (:displaced-index-offset index))
810   array (unsafe))
811 ;  :derive-type 'result-type-arg1) Not even close...
812 \f
813 ;;;; from the "Strings" chapter:
814
815 (defknown char (string index) character (foldable flushable))
816 (defknown schar (simple-string index) character (foldable flushable))
817
818 (sb!xc:deftype stringable () '(or character string symbol))
819
820 (defknown (string= string-equal)
821   (stringable stringable &key (:start1 index) (:end1 sequence-end)
822               (:start2 index) (:end2 sequence-end))
823   boolean
824   (foldable flushable))
825
826 (defknown (string< string> string<= string>= string/= string-lessp
827                    string-greaterp string-not-lessp string-not-greaterp
828                    string-not-equal)
829   (stringable stringable &key (:start1 index) (:end1 sequence-end)
830               (:start2 index) (:end2 sequence-end))
831   (or index null)
832   (foldable flushable))
833
834 (defknown make-string (index &key (:element-type type-specifier)
835                        (:initial-element character))
836   simple-string (flushable))
837
838 (defknown (string-trim string-left-trim string-right-trim)
839   (sequence stringable) simple-string (flushable))
840
841 (defknown (string-upcase string-downcase string-capitalize)
842   (stringable &key (:start index) (:end sequence-end))
843   simple-string (flushable))
844
845 (defknown (nstring-upcase nstring-downcase nstring-capitalize)
846   (string &key (:start index) (:end sequence-end))
847   string ())
848
849 (defknown string (stringable) string
850   (flushable explicit-check))
851 \f
852 ;;;; internal non-keyword versions of string predicates:
853
854 (defknown (string<* string>* string<=* string>=* string/=*)
855   (stringable stringable index sequence-end index sequence-end)
856   (or index null)
857   (foldable flushable))
858
859 (defknown string=*
860   (stringable stringable index sequence-end index sequence-end)
861   boolean
862   (foldable flushable))
863 \f
864 ;;;; from the "Eval" chapter:
865
866 (defknown eval (t) * (recursive))
867 (defknown constantp (t &optional lexenv) boolean
868   (foldable flushable))
869 \f
870 ;;;; from the "Streams" chapter:
871
872 (defknown make-synonym-stream (symbol) stream (flushable))
873 (defknown make-broadcast-stream (&rest stream) stream (flushable))
874 (defknown make-concatenated-stream (&rest stream) stream (flushable))
875 (defknown make-two-way-stream (stream stream) stream (flushable))
876 (defknown make-echo-stream (stream stream) stream (flushable))
877 (defknown make-string-input-stream (string &optional index index) stream (flushable unsafe))
878 (defknown make-string-output-stream () stream (flushable))
879 (defknown get-output-stream-string (stream) simple-string ())
880 (defknown streamp (t) boolean (movable foldable flushable))
881 (defknown stream-element-type (stream) type-specifier (movable foldable flushable))
882 (defknown (output-stream-p input-stream-p) (stream) boolean (movable foldable
883                                                                      flushable))
884 (defknown close (stream &key (:abort t)) stream ())
885 \f
886 ;;;; from the "Input/Output" chapter:
887
888 ;;; The I/O functions are currently given effects ANY under the theory
889 ;;; that code motion over I/O operations is particularly confusing and
890 ;;; not very important for efficency.
891
892 (defknown copy-readtable (&optional (or readtable null) readtable) readtable
893   ())
894 (defknown readtablep (t) boolean (movable foldable flushable))
895
896 (defknown set-syntax-from-char
897   (character character &optional (or readtable null) readtable) (eql t)
898   ())
899
900 (defknown set-macro-character (character callable &optional t readtable) (eql t)
901   (unsafe))
902 (defknown get-macro-character (character &optional readtable)
903   (values callable boolean) (flushable))
904
905 (defknown make-dispatch-macro-character (character &optional t readtable)
906   (eql t) ())
907 (defknown set-dispatch-macro-character
908   (character character callable &optional readtable) (eql t)
909   (unsafe))
910 (defknown get-dispatch-macro-character
911   (character character &optional readtable) callable
912   (flushable))
913
914 ;;; may return any type due to eof-value...
915 (defknown (read read-preserving-whitespace read-char-no-hang read-char)
916   (&optional streamlike t t t) t  (explicit-check))
917
918 (defknown read-delimited-list (character &optional streamlike t) t
919   (explicit-check))
920 (defknown read-line (&optional streamlike t t t) (values t boolean)
921   (explicit-check))
922 (defknown unread-char (character &optional streamlike) t
923   (explicit-check))
924 (defknown peek-char (&optional (or character (member nil t)) streamlike t t t)
925   t
926   (explicit-check))
927 (defknown listen (&optional streamlike) boolean (flushable explicit-check))
928
929 (defknown clear-input (&optional stream) null (explicit-check))
930
931 (defknown read-from-string
932   (string &optional t t
933           &key
934           (:start index)
935           (:end sequence-end)
936           (:preserve-whitespace t))
937   (values t index))
938 (defknown parse-integer
939   (string &key
940           (:start index)
941           (:end sequence-end)
942           (:radix (integer 2 36))
943           (:junk-allowed t))
944   (values (or integer null ()) index))
945
946 (defknown read-byte (stream &optional t t) t (explicit-check))
947
948 (defknown write
949   (t &key
950      (:stream streamlike)
951      (:escape t)
952      (:radix t)
953      (:base (integer 2 36))
954      (:circle t)
955      (:pretty t)
956      (:level (or unsigned-byte null))
957      (:readably t)
958      (:length (or unsigned-byte null))
959      (:case t)
960      (:array t)
961      (:gensym t)
962      (:lines (or unsigned-byte null))
963      (:right-margin (or unsigned-byte null))
964      (:miser-width (or unsigned-byte null))
965      (:pprint-dispatch t))
966   t
967   (any explicit-check)
968   :derive-type #'result-type-first-arg)
969
970 (defknown (prin1 print princ) (t &optional streamlike) t (any explicit-check)
971   :derive-type #'result-type-first-arg)
972
973 ;;; xxx-TO-STRING functions are not foldable because they depend on
974 ;;; the dynamic environment.
975 (defknown write-to-string
976   (t &key (:escape t) (:radix t) (:base (integer 2 36)) (:readably t)
977      (:circle t) (:pretty t) (:level (or unsigned-byte null))
978      (:length (or unsigned-byte null)) (:case t) (:array t) (:gensym t)
979      (:lines (or unsigned-byte null)) (:right-margin (or unsigned-byte null))
980      (:miser-width (or unsigned-byte null)) (:pprint-dispatch t))
981   simple-string
982   (foldable flushable explicit-check))
983
984 (defknown (prin1-to-string princ-to-string) (t) simple-string (flushable))
985
986 (defknown write-char (character &optional streamlike) character
987   (explicit-check))
988 (defknown (write-string write-line)
989   (string &optional streamlike &key (:start index) (:end sequence-end))
990   string
991   (explicit-check))
992
993 (defknown (terpri finish-output force-output clear-output)
994   (&optional streamlike) null
995   (explicit-check))
996
997 (defknown fresh-line (&optional streamlike) boolean
998   (explicit-check))
999
1000 (defknown write-byte (integer stream) integer
1001   (explicit-check))
1002
1003 (defknown format ((or streamlike string) (or string function) &rest t)
1004   (or string null)
1005   (explicit-check))
1006
1007 (defknown (y-or-n-p yes-or-no-p) (&optional string &rest t) boolean
1008   (explicit-check))
1009 \f
1010 ;;;; from the "File System Interface" chapter:
1011
1012 ;;; (No pathname functions are FOLDABLE because they all potentially
1013 ;;; depend on *DEFAULT-PATHNAME-DEFAULTS*, e.g. to provide a default
1014 ;;; host when parsing a namestring.)
1015
1016 (defknown wild-pathname-p (pathname-designator
1017                            &optional
1018                            (member nil :host :device
1019                                    :directory :name
1020                                    :type :version))
1021   boolean
1022   (flushable))
1023 (defknown pathname-match-p (pathname-designator pathname-designator) boolean
1024   (flushable))
1025 (defknown translate-pathname (pathname-designator
1026                               pathname-designator
1027                               pathname-designator &key)
1028   pathname
1029   (flushable))
1030
1031 (defknown logical-pathname (pathname-designator) logical-pathname ())
1032 (defknown translate-logical-pathname (pathname-designator &key) pathname ())
1033 (defknown load-logical-pathname-translations (string) t ())
1034 (defknown logical-pathname-translations (logical-host-designator) list ())
1035
1036 (defknown pathname (pathname-designator) pathname (flushable))
1037 (defknown truename (pathname-designator) pathname ())
1038
1039 (defknown parse-namestring
1040   (pathname-designator &optional
1041                        (or list host string (member :unspecific))
1042                        pathname-designator
1043                        &key
1044                        (:start index)
1045                        (:end sequence-end)
1046                        (:junk-allowed t))
1047   (values (or pathname null) index)
1048   ())
1049
1050 (defknown merge-pathnames
1051   (pathname-designator &optional pathname-designator pathname-version)
1052   pathname
1053   (flushable))
1054
1055 (defknown make-pathname
1056  (&key (:defaults pathname-designator)
1057        (:host (or string pathname-host))
1058        (:device (or string pathname-device))
1059        (:directory (or pathname-directory string (member :wild)))
1060        (:name (or pathname-name string (member :wild)))
1061        (:type (or pathname-type string (member :wild)))
1062        (:version pathname-version) (:case (member :local :common)))
1063   pathname (flushable))
1064
1065 (defknown pathnamep (t) boolean (movable flushable))
1066
1067 (defknown pathname-host (pathname-designator
1068                          &key (:case (member :local :common)))
1069   pathname-host (flushable))
1070 (defknown pathname-device (pathname-designator
1071                            &key (:case (member :local :common)))
1072   pathname-device (flushable))
1073 (defknown pathname-directory (pathname-designator
1074                               &key (:case (member :local :common)))
1075   pathname-directory (flushable))
1076 (defknown pathname-name (pathname-designator
1077                          &key (:case (member :local :common)))
1078   pathname-name (flushable))
1079 (defknown pathname-type (pathname-designator
1080                          &key (:case (member :local :common)))
1081   pathname-type (flushable))
1082 (defknown pathname-version (pathname-designator)
1083   pathname-version (flushable))
1084
1085 (defknown (namestring file-namestring directory-namestring host-namestring)
1086   (pathname-designator) simple-string
1087   (flushable))
1088
1089 (defknown enough-namestring (pathname-designator &optional pathname-designator)
1090   simple-string
1091   (flushable))
1092
1093 (defknown user-homedir-pathname (&optional t) pathname (flushable))
1094
1095 (defknown open
1096   (pathname-designator &key
1097                        (:direction (member :input :output :io :probe))
1098                        (:element-type type-specifier)
1099                        (:if-exists (member :error :new-version :rename
1100                                            :rename-and-delete :overwrite
1101                                            :append :supersede nil))
1102                        (:if-does-not-exist (member :error :create nil))
1103                        (:external-format (member :default)))
1104   (or stream null))
1105
1106 (defknown rename-file (pathname-designator filename)
1107   (values pathname pathname pathname))
1108 (defknown delete-file (pathname-designator) t)
1109 (defknown probe-file (pathname-designator) (or pathname null) (flushable))
1110 (defknown file-write-date (pathname-designator) (or unsigned-byte null)
1111   (flushable))
1112 (defknown file-author (pathname-designator) (or simple-string null)
1113   (flushable))
1114
1115 (defknown file-position (stream &optional
1116                                 (or unsigned-byte (member :start :end)))
1117   (or unsigned-byte (member t nil)))
1118 (defknown file-length (stream) (or unsigned-byte null) (flushable))
1119
1120 (defknown load
1121   ((or filename stream)
1122    &key
1123    (:verbose t)
1124    (:print t)
1125    (:if-does-not-exist (member :error :create nil))
1126    ;; FIXME: ANSI specifies an :EXTERNAL-FORMAT keyword too.
1127    )
1128   t)
1129
1130 (defknown directory (pathname-designator &key
1131                                          (:check-for-subdirs t)
1132                                          (:all t)
1133                                          (:follow-links t))
1134   list (flushable))
1135 \f
1136 ;;;; from the "Errors" chapter:
1137
1138 (defknown error (t &rest t) nil) ; never returns...
1139 (defknown cerror (string t &rest t) null)
1140 (defknown warn (t &rest t) null)
1141 (defknown break (&optional t &rest t) null)
1142 \f
1143 ;;;; from the "Miscellaneous" Chapter:
1144
1145 (defknown compile ((or symbol cons) &optional (or list function null))
1146   (values (or function symbol cons) boolean boolean))
1147
1148 (defknown compile-file
1149   (filename
1150    &key
1151    (:output-file (or filename
1152                      null
1153                      ;; FIXME: This last case is a non-ANSI hack.
1154                      (member t)))
1155    (:verbose t)
1156    (:print t)
1157    (:external-format t)
1158    (:block-compile t)
1159    (:entry-points list)
1160    (:byte-compile (member t nil :maybe)))
1161   (values (or pathname null) boolean boolean))
1162
1163 (defknown disassemble (callable &key
1164                                 (:stream stream)
1165                                 (:use-labels t))
1166   null)
1167
1168 (defknown fdocumentation (t symbol)
1169   (or string null)
1170   (flushable))
1171
1172 (defknown describe (t &optional (or stream (member t nil))) (values))
1173 (defknown inspect (t) (values))
1174
1175 (defknown room (&optional (member t nil :default)) (values))
1176 (defknown ed (&optional (or symbol cons filename) &key (:init t) (:display t))
1177   t)
1178 (defknown dribble (&optional filename &key (:if-exists t)) t)
1179
1180 (defknown apropos      (stringable &optional package-designator t) (values))
1181 (defknown apropos-list (stringable &optional package-designator t) list
1182   (flushable))
1183
1184 (defknown get-decoded-time ()
1185   (values (integer 0 59) (integer 0 59) (integer 0 23) (integer 1 31)
1186           (integer 1 12) unsigned-byte (integer 0 6) boolean (rational -24 24))
1187   (flushable))
1188
1189 (defknown get-universal-time () unsigned-byte (flushable))
1190
1191 (defknown decode-universal-time
1192           (unsigned-byte &optional (or null (rational -24 24)))
1193   (values (integer 0 59) (integer 0 59) (integer 0 23) (integer 1 31)
1194           (integer 1 12) unsigned-byte (integer 0 6) boolean (rational -24 24))
1195   (flushable))
1196
1197 (defknown encode-universal-time
1198   ((integer 0 59) (integer 0 59) (integer 0 23) (integer 1 31)
1199    (integer 1 12) unsigned-byte &optional (or null (rational -24 24)))
1200   unsigned-byte
1201   (flushable))
1202
1203 (defknown (get-internal-run-time get-internal-real-time)
1204   () internal-time (flushable))
1205
1206 (defknown sleep ((or (rational 0) (float 0.0))) null)
1207
1208 ;;; Even though ANSI defines LISP-IMPLEMENTATION-TYPE and
1209 ;;; LISP-IMPLEMENTATION-VERSION to possibly punt and return NIL, we
1210 ;;; know that there's no valid reason for our implementations to ever
1211 ;;; do so, so we can safely guarantee that they'll return strings.
1212 (defknown (lisp-implementation-type lisp-implementation-version)
1213   () simple-string (flushable))
1214
1215 ;;; For any of these functions, meaningful information might not be
1216 ;;; available, so -- unlike the related LISP-IMPLEMENTATION-FOO
1217 ;;; functions -- these really can return NIL.
1218 (defknown (machine-type machine-version machine-instance
1219            software-type software-version
1220            short-site-name long-site-name)
1221   () (or simple-string null) (flushable))
1222
1223 (defknown identity (t) t (movable foldable flushable unsafe)
1224   :derive-type #'result-type-first-arg)
1225
1226 ;;; &OPTIONAL is to agree with the optimization in the interpreter stub.
1227 (defknown constantly (t &optional t t &rest t) function (movable flushable))
1228 (defknown complement (function) function (movable flushable))
1229 \f
1230 ;;;; magical compiler frobs
1231
1232 ;;; We can't fold this in general because of SATISFIES. There is a
1233 ;;; special optimizer anyway.
1234 (defknown %typep (t (or type-specifier ctype)) boolean
1235   (movable flushable explicit-check))
1236 (defknown %instance-typep (t (or type-specifier ctype)) boolean
1237   (movable flushable explicit-check))
1238
1239 (defknown %cleanup-point () t)
1240 (defknown %special-bind (t t) t)
1241 (defknown %special-unbind (t) t)
1242 (defknown %listify-rest-args (t index) list (flushable))
1243 (defknown %more-arg-context (t t) (values t index) (flushable))
1244 (defknown %more-arg (t index) t)
1245 (defknown %more-arg-values (t index index) * (flushable))
1246 (defknown %verify-argument-count (index index) (values))
1247 (defknown %argument-count-error (t) nil)
1248 (defknown %unknown-values () *)
1249 (defknown %catch (t t) t)
1250 (defknown %unwind-protect (t t) t)
1251 (defknown (%catch-breakup %unwind-protect-breakup) () t)
1252 (defknown %lexical-exit-breakup (t) t)
1253 (defknown %continue-unwind (t t t) nil)
1254 (defknown %throw (t &rest t) nil) ; This is MV-called.
1255 (defknown %nlx-entry (t) *)
1256 (defknown %%primitive (t t &rest t) *)
1257 (defknown %pop-values (t) t)
1258 (defknown %type-check-error (t t) nil)
1259 (defknown %odd-keyword-arguments-error () nil)
1260 (defknown %unknown-keyword-argument-error (t) nil)
1261 (defknown (%ldb %mask-field) (bit-index bit-index integer) unsigned-byte
1262   (movable foldable flushable explicit-check))
1263 (defknown (%dpb %deposit-field) (integer bit-index bit-index integer) integer
1264   (movable foldable flushable explicit-check))
1265 (defknown %negate (number) number (movable foldable flushable explicit-check))
1266 (defknown %check-bound (array index fixnum) index (movable foldable flushable))
1267 (defknown data-vector-ref (simple-array index) t (foldable flushable explicit-check))
1268 (defknown data-vector-set (array index t) t (unsafe explicit-check))
1269 (defknown hairy-data-vector-ref (array index) t (foldable flushable explicit-check))
1270 (defknown hairy-data-vector-set (array index t) t (unsafe explicit-check))
1271 (defknown sb!kernel:%caller-frame-and-pc () (values t t) (flushable))
1272 (defknown sb!kernel:%with-array-data (array index (or index null))
1273   (values (simple-array * (*)) index index index)
1274   (foldable flushable))
1275 (defknown %set-symbol-package (symbol t) t (unsafe))
1276 (defknown %coerce-name-to-function ((or symbol cons)) function (flushable))
1277 (defknown %coerce-callable-to-function (callable) function (flushable))
1278
1279 ;;; Structure slot accessors or setters are magically "known" to be
1280 ;;; these functions, although the var remains the Slot-Accessor
1281 ;;; describing the actual function called.
1282 ;;;
1283 ;;; FIXME: It would be nice to make structure slot accessors be
1284 ;;; ordinary functions (proclaimed as SB-EXT:CONSTANT-FUNCTION, but
1285 ;;; otherwise ordinary).
1286 (defknown %slot-accessor (t) t (flushable))
1287 (defknown %slot-setter (t t) t (unsafe))
1288 \f
1289 ;;;; SETF inverses
1290
1291 (defknown %aset (array &rest t) t (unsafe))
1292 (defknown %set-row-major-aref (array index t) t (unsafe))
1293 (defknown %rplaca (cons t) t (unsafe))
1294 (defknown %rplacd (cons t) t (unsafe))
1295 (defknown %put (symbol t t) t (unsafe))
1296 (defknown %setelt (sequence index t) t (unsafe))
1297 (defknown %svset (simple-vector index t) t (unsafe))
1298 (defknown %bitset (bit-vector &rest index) bit (unsafe))
1299 (defknown %sbitset (simple-bit-vector &rest index) bit (unsafe))
1300 (defknown %charset (string index character) character (unsafe))
1301 (defknown %scharset (simple-string index character) character (unsafe))
1302 (defknown %set-symbol-value (symbol t) t (unsafe))
1303 (defknown fset (symbol function) function (unsafe))
1304 (defknown %set-symbol-plist (symbol t) t (unsafe))
1305 (defknown (setf fdocumentation) ((or string null) t symbol)
1306   (or string null)
1307   ())
1308 (defknown %setnth (index list t) t (unsafe))
1309 (defknown %set-fill-pointer (vector index) index (unsafe))
1310 \f
1311 ;;;; internal type predicates
1312
1313 ;;; Simple TYPEP uses that don't have any standard predicate are
1314 ;;; translated into non-standard unary predicates.
1315 (defknown (fixnump bignump ratiop short-float-p single-float-p double-float-p
1316            long-float-p base-char-p %standard-char-p %instancep
1317            array-header-p)
1318   (t) boolean (movable foldable flushable))
1319 \f
1320 ;;;; miscellaneous "sub-primitives"
1321
1322 (defknown %sp-string-compare
1323   (simple-string index index simple-string index index)
1324   (or index null)
1325   (foldable flushable))