1.0.24.6: OPTIMIZATION #23 is there already
[sbcl.git] / OPTIMIZATIONS
1 #1
2 (defun mysl (s)
3     (declare (simple-string s))
4     (declare (optimize (speed 3) (safety 0) (debug 0)))
5     (let ((c 0))
6       (declare (fixnum c))
7       (dotimes (i (length s))
8         (when (eql (aref s i) #\1)
9           (incf c)))
10       c))
11
12 * On X86 I is represented as a tagged integer.
13
14 * Unnecessary move:
15   3: SLOT S!11[EDX] {SB-C::VECTOR-LENGTH 1 7} => t23[EAX]
16   4: MOVE t23[EAX] => t24[EBX]
17
18 --------------------------------------------------------------------------------
19 #2
20 (defun quux (v)
21   (declare (optimize (speed 3) (safety 0) (space 2) (debug 0)))
22   (declare (type (simple-array double-float 1) v))
23   (let ((s 0d0))
24     (declare (type double-float s))
25     (dotimes (i (length v))
26       (setq s (+ s (aref v i))))
27     s))
28
29 * Python does not combine + with AREF, so generates extra move and
30   allocates a register.
31
32 * On X86 Python thinks that all FP registers are directly accessible
33   and emits costy MOVE ... => FR1.
34
35 --------------------------------------------------------------------------------
36 #3
37 (defun bar (n)
38   (declare (optimize (speed 3) (safety 0) (space 2))
39            (type fixnum n))
40   (let ((v (make-list n)))
41     (setq v (make-array n))
42     (length v)))
43
44 * IR1 does not optimize away (MAKE-LIST N).
45 --------------------------------------------------------------------------------
46 #4
47 (defun bar (v1 v2)
48   (declare (optimize (speed 3) (safety 0) (space 2))
49            (type (simple-array base-char 1) v1 v2))
50   (dotimes (i (length v1))
51     (setf (aref v2 i) (aref v1 i))))
52
53 VOP DATA-VECTOR-SET/SIMPLE-STRING V2!14[EDI] t32[EAX] t30[S2]>t33[CL]
54                                   => t34[S2]<t35[AL] 
55         MOV     #<TN t33[CL]>, #<TN t30[S2]>
56         MOV     BYTE PTR [EDI+EAX+1], #<TN t33[CL]>
57         MOV     #<TN t35[AL]>, #<TN t33[CL]>
58         MOV     #<TN t34[S2]>, #<TN t35[AL]>
59
60 * The value of DATA-VECTOR-SET is not used, so there is no need in the
61   last two moves.
62
63 * And why two moves?
64 --------------------------------------------------------------------------------
65 #8
66 (defun foo (d)
67   (declare (optimize (speed 3) (safety 0) (debug 0)))
68   (declare (type (double-float 0d0 1d0) d))
69   (loop for i fixnum from 1 to 5
70         for x1 double-float = (sin d) ;;; !!!
71         do (loop for j fixnum from 1 to 4
72                  sum x1 double-float)))
73
74 Without the marked declaration Python will use boxed representation for X1.
75
76 This is equivalent to
77
78 (let ((x nil))
79   (setq x 0d0)
80   ;; use of X as DOUBLE-FLOAT
81 )
82
83 The initial binding is effectless, and without it X is of type
84 DOUBLE-FLOAT. Unhopefully, IR1 does not optimize away effectless
85 SETs/bindings, and IR2 does not perform type inference.
86 --------------------------------------------------------------------------------
87 #9 "Multi-path constant folding"
88 (defun foo (x)
89   (if (= (cond ((irgh x) 0)
90                ((buh x) 1)
91                (t 2))
92          0)
93       :yes
94       :no))
95
96 This code could be optimized to
97
98 (defun foo (x)
99   (cond ((irgh x) :yes)
100         ((buh x) :no)
101         (t :no)))
102 --------------------------------------------------------------------------------
103 #11
104 (inverted variant of #9)
105
106 (lambda (x)
107   (let ((y (sap-alien x c-string)))
108     (list (alien-sap y)
109           (alien-sap y))))
110
111 It could be optimized to
112
113 (lambda (x) (list x x))
114
115 (if Y were used only once, the current compiler would optimize it)
116 --------------------------------------------------------------------------------
117 #12
118 (typep (truly-the (simple-array * (*)) x) 'simple-vector)
119
120 tests lowtag.
121 --------------------------------------------------------------------------------
122 #13
123 FAST-+/FIXNUM and similar should accept unboxed arguments in interests
124 of representation selection. Problem: inter-TN dependencies.
125 --------------------------------------------------------------------------------
126 #14
127 The derived type of (/ (THE (DOUBLE-FLOAT (0D0)) X) (THE (DOUBLE-FLOAT
128 1D0) Y)) is (DOUBLE-FLOAT 0.0d0). While it might be reasonable, it is
129 better to derive (OR (MEMBER 0.0d0) (DOUBLE-FLOAT (0.0d0))).
130 --------------------------------------------------------------------------------
131 #15
132 On the alpha, the system is reluctant to refer directly to a constant bignum,
133 preferring to load a large constant through a slow sequence of instructions,
134 then cons up a bignum for it:
135
136 (LAMBDA (A)
137   (DECLARE (OPTIMIZE (SAFETY 1) (SPEED 3) (DEBUG 1))
138            (TYPE (INTEGER -10000 10000) A)
139            (IGNORABLE A))
140   (CASE A
141     ((89 125 16) (ASH A (MIN 18 -706)))
142     (T (DPB -3 (BYTE 30 30) -1))))
143 --------------------------------------------------------------------------------
144 #16
145 (do ((i 0 (1+ i)))
146     ((= i (the (integer 0 100) n)))
147   ...)
148
149 It is commonly expected for Python to derive (FIXNUMP I). (If ``='' is
150 replaced with ``>='', Python will do.)
151 --------------------------------------------------------------------------------
152 #17 
153 Type tests for (ARRAY BIT), (ARRAY T) and similar go through full
154 %TYPEP, even though it is relatively simple to establish the arrayness
155 of an object and also to obtain the element type of an array.  As of
156 sbcl-0.8.12.30, this affects at least DUMP-OBJECT through
157 COMPOUND-OBJECT-P, and (LABELS MAYBE-EMIT-MAKE-LOAD-FORMS GROVEL)
158 through TYPEP UNBOXED-ARRAY, within the compiler itself.
159 --------------------------------------------------------------------------------
160 #18
161 (lambda (x) (declare (null x)) (sxhash x)) goes through SYMBOL-HASH
162 rather than either constant-folding or manipulating NIL-VALUE or
163 NULL-TN directly.
164 --------------------------------------------------------------------------------
165 #20
166 (defun-with-dx foo (x)
167   (flet ((make (x)
168            (let ((l (list nil nil)))
169              (setf (first l) x)
170              (setf (second l) (1- x))
171              l)))
172     (let ((l (make x)))
173       (declare (dynamic-extent l))
174       (mapc #'print l))))
175
176 Result of MAKE is not stack allocated, which means that
177 stack-allocation of structures is impossible.
178 --------------------------------------------------------------------------------
179 #22
180 IR2 does not perform unused code flushing.
181 --------------------------------------------------------------------------------
182 #24
183 a. Iterations on &REST lists, returning them as VALUES could be
184    rewritten with &MORE vectors.
185 b. Implement local unknown-values mv-call (useful for fast type checking).
186 --------------------------------------------------------------------------------
187 #26
188 SBCL cannot derive upper bound for I and uses generic arithmetic here:
189
190 (defun foo (l)
191   (declare (vector l))
192   (dotimes (i (length l))
193     (if (block nil
194           (map-foo (lambda (x) (if x (return t)))
195                    l))
196         t
197         nil)))
198
199 (So the constraint propagator or a possible future SSA-convertor
200 should know the connection between an NLE and its CLEANUP.)
201 --------------------------------------------------------------------------------
202 #27
203 Initialization of stack-allocated arrays is inefficient: we always
204 fill the vector with zeroes, even when it is not needed (as for
205 platforms with conservative GC or for arrays of unboxed objectes) and
206 is performed later explicitely.
207
208 (This is harder than it might look at first glance, as MAKE-ARRAY is smart
209 enough to eliminate something like ':initial-element 0'.  Such an optimization
210 is valid if the vector is being allocated in the heap, but not if it is being
211 allocated on the stack.  You could remove this optimization, but that makes
212 the heap-allocated case somewhat slower...)
213 --------------------------------------------------------------------------------
214 #28
215 a. Accessing raw slots in structure instances is more inefficient than
216 it could be; if we placed raw slots before the header word, we would
217 not need to do arithmetic at runtime to access them.  (But beware:
218 this would complicate handling of the interior pointer).
219
220 b. (Also note that raw slots are currently disabled on HPPA)
221 --------------------------------------------------------------------------------
222 #29
223 Python is overly zealous when converting high-level CL functions, such
224 as MIN/MAX, LOGBITP, and LOGTEST, to low-level CL functions.  Reducing
225 Python's aggressiveness would make it easier to effect changes such as
226
227 x86-64:
228 * direct MIN/MAX on {SINGLE,DOUBLE}-FLOATs ({MIN,MAX}S{S,D})
229
230 x86-64:
231 * direct LOGBITP on word-sized integers and fixnums (BT + JC)
232
233 x86{,-64}/PPC:
234 * branch-free MIN/MAX on word-sized integers and fixnums (floats could
235   be handled too, modulo safety considerations on the PPC)
236
237 x86-64:
238 * efficient LOGTESTs on word-sized integers and fixnums (TEST)
239
240 etc., etc.
241
242 (The framework for this has been implemented as of 0.9.9.18; see the
243 vm-support-routine COMBINATION-IMPLEMENTATION-STYLE and its use in
244 src/compiler/ir1opt.lisp, IR1-OPTIMIZE-COMBINATION.  The above
245 optimizations are left as an exercise for the reader.)
246 --------------------------------------------------------------------------------
247 #30
248 (defun foo (x y)
249   (< x y))
250
251 FOO's IR1 representation is roughly:
252
253 (defun foo (x y)
254   (if (< x y)
255       T
256       NIL))
257
258 However, if a full call is generated for < (and similarly for other
259 predicate functions), then the IF is unnecessary, since the return value
260 of (< x y) is already T or NIL.
261 --------------------------------------------------------------------------------
262 #31
263 The typecheck generated for a declaration like (integer 0 45) on x86 looks
264 like:
265
266 ;      12B:       F6C203           TEST DL, 3
267 ;      12E:       753B             JNE L1
268 ;      130:       8BC2             MOV EAX, EDX
269 ;      132:       83F800           CMP EAX, 0
270 ;      135:       7C34             JL L1
271 ;      137:       8BC2             MOV EAX, EDX
272 ;      139:       3DB4000000       CMP EAX, 180
273 ;      13E:       7F2B             JNLE L1
274
275 A better code sequence for this would be:
276
277   TEST DL, 3
278   JNE L1
279   MOV EAX, EDX
280   CMP EAX, 180
281   JBE L1
282
283 Doing an unsigned comparison means that, similarly to %CHECK-BOUND, we can
284 combine the <0 and >=bound tests.  This sort of test is generated often
285 in SBCL and any array-based code that's serious about type-checking its
286 indices.
287 --------------------------------------------------------------------------------
288 #32
289 The code for a vector bounds check on x86 (similarly on x86-64) where
290 the vector is in EDX and the index in EAX looks like:
291
292 ;       49: L0:   8B5AFD           MOV EBX, [EDX-3]
293 ;       4C:       39C3             CMP EBX, EAX
294 ;       4E:       7632             JBE L2
295
296 because %CHECK-BOUND is used for bounds-checking any array dimension.
297 A more efficient specialization (%CHECK-BOUND/VECTOR) would produce:
298
299   CMP [EDX-3], EAX
300   JBE L2
301
302 Which is slightly shorter and avoids using a register.
303 --------------------------------------------------------------------------------
304 #33
305 Reports from the Java camp indicate that using an SSE2-based
306 floating-point backend on x86 when possible is highly preferable to
307 using the x86 FP stack.  It would be nice if SBCL included an SSE2-based
308 floating point backend with a compile-time option to switch between the
309 two.
310 --------------------------------------------------------------------------------
311 #35
312 Compiling
313
314 (defun foo (a i)
315   (declare (type simple-vector a))
316   (aref a i))
317
318 results in the following x86 code:
319
320 ; 115886E9:       F7C703000000     TEST EDI, 3                ; no-arg-parsing entry point
321 ;      6EF:       7510             JNE L0
322 ;      6F1:       8BC7             MOV EAX, EDI
323 ;      6F3:       83F800           CMP EAX, 0
324 ;      6F6:       7C09             JL L0
325 ;      6F8:       8BC7             MOV EAX, EDI
326 ;      6FA:       3DF8FFFF7F       CMP EAX, 2147483640
327 ;      6FF:       7E0F             JLE L1
328 ;      701: L0:   8B057C865811     MOV EAX, [#x1158867C]      ; '(MOD
329                                                               ;   536870911)
330 ;      707:       0F0B0A           BREAK 10                   ; error trap
331 ;      70A:       05               BYTE #X05
332 ;      70B:       1F               BYTE #X1F                  ; OBJECT-NOT-TYPE-ERROR
333 ;      70C:       FECE01           BYTE #XFE, #XCE, #X01      ; EDI
334 ;      70F:       0E               BYTE #X0E                  ; EAX
335 ;      710: L1:   8B42FD           MOV EAX, [EDX-3]
336 ;      713:       8BCF             MOV ECX, EDI
337 ;      715:       39C8             CMP EAX, ECX
338 ;      717:       7620             JBE L2
339 ;      719:       8B540A01         MOV EDX, [EDX+ECX+1]
340
341 ... plus the standard return sequence and some error blocks.  The
342 `TEST EDI, 3' and associated comparisons are to ensure that `I' is a
343 positive fixnum.  The associated comparisons are unnecessary, as the
344 %CHECK-BOUND VOP only requires its tested index to be a fixnum and takes
345 care of the negative fixnum case itself.
346
347 {HAIRY-,}DATA-VECTOR-REF are DEFKNOWN'd with EXPLICIT-CHECK, which would
348 seem to take care of this, but EXPLICIT-CHECK only seems to be used when
349 compiling calls to unknown functions or similar.  Furthermore,
350 EXPLICIT-CHECK, as NJF understands it, doesn't have the right
351 semantics--it suppresses all type checking of arguments, whereas what we
352 really want is to ensure that the argument is a fixnum, but not check
353 its positiveness.
354 --------------------------------------------------------------------------------
355 #36
356
357 In #35, the CMP EAX, $foo instructions are all preceded by a MOV.  They
358 appear to be unnecessary, but are necessary because in IR2, EDI is a
359 DESCRIPTOR-REG, whereas EAX is an ANY-REG--and the comparison VOPs only
360 accept ANY-REGs.  Therefore, the MOVs are "necessary" to ensure that the
361 comparison VOP receives an TN of the appropriate storage class.
362
363 Obviously, it would be better if a) we only performed one MOV prior to
364 all three comparisons or b) eliminated the necessity of the MOV(s)
365 altogether.  The former option is probably easier than the latter.
366
367 --------------------------------------------------------------------------------
368 #38
369
370 (setf (subseq s1 start1 end1) (subseq s2 start2 end1))
371
372 could be transformed into
373
374 (let ((#:s2 s2)
375       (#:start2 start2)
376       (#:end2 end2))
377  (replace s1 #:s2 :start1 start1 :end1 end1 :start2 #:start2 :end2 #:end2))
378
379 when the return value is unused, avoiding the need to cons up the new sequence.
380
381 --------------------------------------------------------------------------------
382 #39
383
384 (let ((*foo* 42)) ...)
385
386 currently compiles to code that ensures the TLS index at runtime, which
387 is both a decently large chunk of code and unnecessary, as we could ensure
388 the TLS index at load-time as well.
389
390 --------------------------------------------------------------------------------
391 #40
392
393 When FTYPE is declared -- to say (function (t t t t t) t), and
394 function has a compiler-macro,
395
396   (apply #'foo 'x1 x2 'x3 more)
397
398 can be transformed into
399
400   (apply (lambda (x2 x4 x5) (foo 'x1 x2 'x3 x4 x5)) x2 more)
401
402 which allows compiler-macro-expansion for FOO. (Only constant
403 arguments can be moved inside the new lambda -- otherwise evaluation
404 order is altered.)