More incorrect next_free_page usage.
[sbcl.git] / doc / manual / efficiency.texinfo
blob434d53a1f7f1638556c4725a68c1f370cb77de3e
1 @node Efficiency
2 @comment  node-name,  next,  previous,  up
3 @chapter Efficiency
4 @cindex Efficiency
6 @menu
7 * Slot access::
8 * Stack allocation::
9 * Modular arithmetic::
10 * Global and Always-Bound variables::
11 * Miscellaneous Efficiency Issues::
12 @end menu
14 @node  Slot access
15 @comment  node-name,  next,  previous,  up
16 @section Slot access
17 @cindex Slot access
19 @subsection Structure object slot access
21 Structure slot accessors are efficient only if the compiler is able to
22 open code them: compiling a call to a structure slot accessor before
23 the structure is defined, declaring one @code{notinline}, or passing
24 it as a functional argument to another function causes severe
25 performance degradation.
27 @subsection Standard object slot access
29 The most efficient way to access a slot of a @code{standard-object} is
30 by using @code{slot-value} with a constant slot name argument inside a
31 @code{defmethod} body, where the variable holding the instance is a
32 specializer parameter of the method and is never assigned to. The cost
33 is roughly 1.6 times that of an open coded structure slot accessor.
35 Second most efficient way is to use a CLOS slot accessor, or
36 @code{slot-value} with a constant slot name argument, but in
37 circumstances other than specified above. This may be up to 3 times as
38 slow as the method described above.
40 Example:
42 @lisp
43 (defclass foo () ((bar)))
45 ;; Fast: specializer and never assigned to
46 (defmethod quux ((foo foo) new)
47   (let ((old (slot-value foo 'bar)))
48     (setf (slot-value foo 'bar) new)
49     old))
51 ;; Slow: not a specializer
52 (defmethod quux ((foo foo) new)
53   (let* ((temp foo)
54          (old (slot-value temp 'bar)))
55     (setf (slot-value temp 'bar) new)
56     old))
58 ;; Slow: assignment to FOO
59 (defmethod quux ((foo foo) new)
60   (let ((old (slot-value foo 'bar)))
61     (setf (slot-value foo 'bar) new)
62     (setf foo new)
63     old))
64 @end lisp
66 Note that when profiling code such as this, the first few calls to the
67 generic function are not representative, as the dispatch mechanism is
68 lazily set up during those calls.
70 @node  Stack allocation
71 @comment  node-name,  next,  previous,  up
72 @section Stack allocation
73 @cindex @code{dynamic-extent} declaration
74 @cindex declaration, @code{dynamic-extent}
76 SBCL has fairly extensive support for performing allocations on the
77 stack when a variable or function is declared @code{dynamic-extent}. The
78 @code{dynamic-extent} declarations are not verified, but are simply
79 trusted as long as @code{sb-ext:*stack-allocate-dynamic-extent*} is
80 true.
82 @include var-sb-ext-star-stack-allocate-dynamic-extent-star.texinfo
84 SBCL recognizes any value which a variable declared
85 @code{dynamic-extent} can take on as having dynamic extent. This means
86 that, in addition to the value a variable is bound to initially, a value
87 assigned to a variable by @code{setq} is also recognized as having
88 dynamic extent when the variable is declared
89 @code{dynamic-extent}. Users can thus build complex structures on the
90 stack using iteration and @code{setq}.
92 At present, SBCL implements stack allocation for the following kinds of
93 values when they are recognized as having dynamic extent:
95 @itemize
97 @item
98 @code{&rest} lists
100 @item
101 @findex @cl{cons}
102 @findex @cl{list}
103 @findex @cl{list*}
104 @findex @cl{vector}
105 the results of @code{cons}, @code{list}, @code{list*}, and @code{vector}
107 @item
108 @findex @cl{make-array}
109 the result of simple forms of @code{make-array}: stack allocation is
110 possible only if the resulting array is known to be both simple and
111 one-dimensional, and has a constant @code{:element-type}.
113 @cindex Safety optimization quality
114 @strong{Note}: stack space is limited, so allocation of a large vector
115 may cause stack overflow. Stack overflow checks are done except in zero
116 @code{safety} policies.
118 @item
119 @findex @cl{flet}
120 @findex @cl{labels}
121 @cindex @code{safety} optimization quality
122 @cindex optimization quality, @code{safety}
123 closures defined with @code{flet} or @code{labels} with a bound
124 @code{dynamic-extent} declaration.
126 @item
127 anonymous closures defined with @code{lambda}
129 @item
130 user-defined structures when the structure constructor defined using
131 @code{defstruct} has been declared @code{inline}
133 @strong{Note}: structures with ``raw'' slots can currently be
134 stack-allocated only on x86 and x86-64. A ``raw'' slot is one whose
135 declared type is a subtype of exactly one of: @code{double-float},
136 @code{single-float}, @code{(complex double-float)}, @code{(complex single-float)},
137 or @code{sb-ext:word}; but as an exception to the preceding, any subtype
138 of @code{fixnum} is not stored as raw despite also being a subtype
139 of @code{sb-ext:word}.
141 @item
142 otherwise-inaccessible parts of objects recognized to be dynamic
143 extent. The support for detecting when this applies is very
144 sophisticated. The compiler can do this detection when any value form
145 for a variable contains conditional allocations, function calls, inlined
146 functions, anonymous closures, or even other variables. This allows
147 stack allocation of complex structures.
149 @end itemize
151 Examples:
153 @lisp
154 ;;; Declaiming a structure constructor inline before definition makes
155 ;;; stack allocation possible.
156 (declaim (inline make-thing))
157 (defstruct thing obj next)
159 ;;; Stack allocation of various objects bound to DYNAMIC-EXTENT
160 ;;; variables.
161 (let* ((list (list 1 2 3))
162        (nested (cons (list 1 2) (list* 3 4 (list 5))))
163        (vector (make-array 3 :element-type 'single-float))
164        (thing (make-thing :obj list
165                           :next (make-thing :obj (make-array 3))))
166        (closure (let ((y ...)) (lambda () y))))
167   (declare (dynamic-extent list nested vector thing closure))
168   ...)
170 ;;; Stack allocation of objects assigned to DYNAMIC-EXTENT variables.
171 (let ((x nil))
172   (declare (dynamic-extent x))
173   (setq x (list 1 2 3))
174   (dotimes (i 10)
175     (setq x (cons i x)))
176   ...)
178 ;;; Stack allocation of arguments to a local function is equivalent
179 ;;; to stack allocation of local variable values.
180 (flet ((f (x)
181          (declare (dynamic-extent x))
182          ...))
183   ...
184   (f (list 1 2 3))
185   (f (cons (cons 1 2) (cons 3 4)))
186   ...)
188 ;;; Stack allocation of &REST lists
189 (defun foo (&rest args)
190   (declare (dynamic-extent args))
191   ...)
192 @end lisp
194 As a notable exception to recognizing otherwise inaccessible parts of
195 other recognized dynamic extent values, SBCL does not as of 1.0.48.21
196 propagate dynamic-extentness through @code{&rest} arguments -- but
197 another conforming implementation might, so portable code should not
198 rely on this.
200 @lisp
201 (declaim (inline foo))
202 (defun foo (fun &rest arguments)
203   (declare (dynamic-extent arguments))
204   (apply fun arguments))
206 (defun bar (a)
207   ;; SBCL will heap allocate the result of (LIST A), and stack allocate
208   ;; only the spine of the &rest list -- so this is safe, but unportable.
209   ;;
210   ;; Another implementation, including earlier versions of SBCL might consider
211   ;; (LIST A) to be otherwise inaccessible and stack-allocate it as well!
212   (foo #'car (list a)))
213 @end lisp
215 If dynamic extent constraints specified in the Common Lisp standard
216 are violated, the best that can happen is for the program to have
217 garbage in variables and return values; more commonly, the system will
218 crash.
220 In particular, it is important to realize that this can interact in
221 suprising ways with the otherwise inaccessible parts criterion:
223 @lisp
224 (let* ((a (list 1 2 3))
225        (b (cons a a)))
226    (declare (dynamic-extent b))
227    ;; Unless A is accessed elsewhere as well, SBCL will consider
228    ;; it to be otherwise inaccessible -- it can only be accessed
229    ;; through B, after all -- and stack allocate it as well.
230    ;;
231    ;; Hence returning (CAR B) here is unsafe.
232    ...)
233 @end lisp
235 @node  Modular arithmetic
236 @comment  node-name,  next,  previous,  up
237 @section Modular arithmetic
238 @cindex Modular arithmetic
239 @cindex Arithmetic, modular
240 @cindex Arithmetic, hardware
241 @findex @cl{logand}
242 Some numeric functions have a property: @var{N} lower bits of the
243 result depend only on @var{N} lower bits of (all or some)
244 arguments. If the compiler sees an expression of form @code{(logand
245 @var{exp} @var{mask})}, where @var{exp} is a tree of such ``good''
246 functions and @var{mask} is known to be of type @code{(unsigned-byte
247 @var{w})}, where @var{w} is a ``good'' width, all intermediate results
248 will be cut to @var{w} bits (but it is not done for variables and
249 constants!). This often results in an ability to use simple machine
250 instructions for the functions.
252 Consider an example.
254 @lisp
255 (defun i (x y)
256   (declare (type (unsigned-byte 32) x y))
257   (ldb (byte 32 0) (logxor x (lognot y))))
258 @end lisp
260 The result of @code{(lognot y)} will be negative and of type
261 @code{(signed-byte 33)}, so a naive implementation on a 32-bit
262 platform is unable to use 32-bit arithmetic here. But modular
263 arithmetic optimizer is able to do it: because the result is cut down
264 to 32 bits, the compiler will replace @code{logxor} and @code{lognot}
265 with versions cutting results to 32 bits, and because terminals
266 (here---expressions @code{x} and @code{y}) are also of type
267 @code{(unsigned-byte 32)}, 32-bit machine arithmetic can be used.
269 As of SBCL 0.8.5 ``good'' functions are @code{+}, @code{-};
270 @code{logand}, @code{logior}, @code{logxor}, @code{lognot} and their
271 combinations; and @code{ash} with the positive second
272 argument. ``Good'' widths are 32 on 32-bit CPUs and 64 on 64-bit CPUs.
273 While it is possible to support smaller widths as well,
274 currently this is not implemented.
276 @node  Global and Always-Bound variables
277 @comment  node-name,  next,  previous,  up
278 @section Global and Always-Bound variables
280 @include macro-sb-ext-defglobal.texinfo
282 @deffn {Declaration} @sbext{global}
284 Syntax: @code{(sb-ext:global symbol*)}
286 Only valid as a global proclamation.
288 Specifies that the named symbols cannot be proclaimed or locally
289 declared @code{special}. Proclaiming an already special or constant
290 variable name as @code{global} signal an error. Allows more efficient
291 value lookup in threaded environments in addition to expressing
292 programmer intention.
293 @end deffn
295 @deffn {Declaration} @sbext{always-bound}
297 Syntax: @code{(sb-ext:always-bound symbol*)}
299 Only valid as a global proclamation.
301 Specifies that the named symbols are always bound. Inhibits
302 @code{makunbound} of the named symbols. Proclaiming an unbound symbol
303 as @code{always-bound} signals an error. Allows the compiler to elide
304 boundness checks from value lookups.
305 @end deffn
307 @node  Miscellaneous Efficiency Issues
308 @comment  node-name,  next,  previous,  up
309 @section Miscellaneous Efficiency Issues
311 FIXME: The material in the CMUCL manual about getting good
312 performance from the compiler should be reviewed, reformatted in
313 Texinfo, lightly edited for SBCL, and substituted into this
314 manual. In the meantime, the original CMUCL manual is still 95+%
315 correct for the SBCL version of the Python compiler. See the
316 sections
318 @itemize
319 @item Advanced Compiler Use and Efficiency Hints
320 @item Advanced Compiler Introduction
321 @item More About Types in Python
322 @item Type Inference
323 @item Source Optimization
324 @item Tail Recursion
325 @item Local Call
326 @item Block Compilation
327 @item Inline Expansion
328 @item Object Representation
329 @item Numbers
330 @item General Efficiency Hints
331 @item Efficiency Notes
332 @end itemize
334 Besides this information from the CMUCL manual, there are a few other
335 points to keep in mind.
337 @itemize
339 @item
340 @findex @cl{let}
341 @findex @cl{let*}
342 @findex @cl{setq}
343 @findex @cl{setf}
344 The CMUCL manual doesn't seem to state it explicitly, but Python has a
345 mental block about type inference when assignment is involved. Python
346 is very aggressive and clever about inferring the types of values
347 bound with @code{let}, @code{let*}, inline function call, and so
348 forth. However, it's much more passive and dumb about inferring the
349 types of values assigned with @code{setq}, @code{setf}, and
350 friends. It would be nice to fix this, but in the meantime don't
351 expect that just because it's very smart about types in most respects
352 it will be smart about types involved in assignments.  (This doesn't
353 affect its ability to benefit from explicit type declarations
354 involving the assigned variables, only its ability to get by without
355 explicit type declarations.)
357 @c <!-- FIXME: Python dislikes assignments, but not in type
358 @c     inference. The real problems are loop induction, closed over
359 @c     variables and aliases. -->
361 @item
362 Since the time the CMUCL manual was written, CMUCL (and thus SBCL) has
363 gotten a generational garbage collector. This means that there are
364 some efficiency implications of various patterns of memory usage which
365 aren't discussed in the CMUCL manual. (Some new material should be
366 written about this.)
368 @item
369 SBCL has some important known efficiency problems.  Perhaps the most
370 important are
372 @itemize @minus
374 @item
375 The garbage collector is not particularly efficient, at least on
376 platforms without the generational collector (as of SBCL 0.8.9, all
377 except x86).
379 @item
380 Various aspects of the PCL implementation of CLOS are more inefficient
381 than necessary.
383 @end itemize
385 @end itemize
387 Finally, note that Common Lisp defines many constructs which, in
388 the infamous phrase, ``could be compiled efficiently by a
389 sufficiently smart compiler''. The phrase is infamous because
390 making a compiler which actually is sufficiently smart to find all
391 these optimizations systematically is well beyond the state of the art
392 of current compiler technology. Instead, they're optimized on a
393 case-by-case basis by hand-written code, or not optimized at all if
394 the appropriate case hasn't been hand-coded. Some cases where no such
395 hand-coding has been done as of SBCL version 0.6.3 include
397 @itemize
399 @item
400 @code{(reduce #'f x)} where the type of @code{x} is known at compile
401 time
403 @item
404 various bit vector operations, e.g.  @code{(position 0
405 some-bit-vector)}
407 @item
408 specialized sequence idioms, e.g.  @code{(remove item list :count 1)}
410 @item
411 cases where local compilation policy does not require excessive type
412 checking, e.g.  @code{(locally (declare (safety 1)) (assoc item
413 list))} (which currently performs safe @code{endp} checking internal
414 to assoc).
416 @end itemize
418 If your system's performance is suffering because of some construct
419 which could in principle be compiled efficiently, but which the SBCL
420 compiler can't in practice compile efficiently, consider writing a
421 patch to the compiler and submitting it for inclusion in the main
422 sources. Such code is often reasonably straightforward to write;
423 search the sources for the string ``@code{deftransform}'' to find many
424 examples (some straightforward, some less so).