1.0.4.63: Don't zeroize dynamic-extent simple-unboxed-arrays on x86 and x86-64
[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 #19
166   (let ((dx (if (foo)
167                 (list x)
168                 (list y z))))
169     (declare (dynamic-extent dx))
170     ...)
171
172 DX is not allocated on stack.
173 --------------------------------------------------------------------------------
174 #20
175 (defun-with-dx foo (x)
176   (flet ((make (x)
177            (let ((l (list nil nil)))
178              (setf (first l) x)
179              (setf (second l) (1- x))
180              l)))
181     (let ((l (make x)))
182       (declare (dynamic-extent l))
183       (mapc #'print l))))
184
185 Result of MAKE is not stack allocated, which means that
186 stack-allocation of structures is impossible.
187 --------------------------------------------------------------------------------
188 #21
189 (defun-with-dx foo ()
190   (let ((dx (list (list 1 2) (list 3 4))))
191     (declare (dynamic-extent dx))
192     ...))
193
194 External list in DX is allocated on stack, but internal are not.
195 --------------------------------------------------------------------------------
196 #22
197 IR2 does not perform unused code flushing.
198 --------------------------------------------------------------------------------
199 #23
200 Python does not know that &REST lists are LISTs (and cannot derive it).
201 --------------------------------------------------------------------------------
202 #24
203 a. Iterations on &REST lists, returning them as VALUES could be
204    rewritten with &MORE vectors.
205 b. Implement local unknown-values mv-call (useful for fast type checking).
206 --------------------------------------------------------------------------------
207 #26
208 SBCL cannot derive upper bound for I and uses generic arithmetic here:
209
210 (defun foo (l)
211   (declare (vector l))
212   (dotimes (i (length l))
213     (if (block nil
214           (map-foo (lambda (x) (if x (return t)))
215                    l))
216         t
217         nil)))
218
219 (So the constraint propagator or a possible future SSA-convertor
220 should know the connection between an NLE and its CLEANUP.)
221 --------------------------------------------------------------------------------
222 #27
223 (We always zeroize stack-allocated arrays of boxed elements.  The
224 previous note here suggested that we could avoid that step on
225 platforms with conservative GC; it's not clear to me (NJF) that
226 doing so is a wise idea.)
227
228 x86 and x86-64 do not zeroize stack-allocated arrays of unboxed
229 elements; other platforms could copy what they do.
230 --------------------------------------------------------------------------------
231 #28
232 a. Accessing raw slots in structure instances is more inefficient than
233 it could be; if we placed raw slots before the header word, we would
234 not need to do arithmetic at runtime to access them.  (But beware:
235 this would complicate handling of the interior pointer).
236
237 b. (Also note that raw slots are currently disabled on HPPA)
238 --------------------------------------------------------------------------------
239 #29
240 Python is overly zealous when converting high-level CL functions, such
241 as MIN/MAX, LOGBITP, and LOGTEST, to low-level CL functions.  Reducing
242 Python's aggressiveness would make it easier to effect changes such as
243
244 x86-64:
245 * direct MIN/MAX on {SINGLE,DOUBLE}-FLOATs ({MIN,MAX}S{S,D})
246
247 x86-64:
248 * direct LOGBITP on word-sized integers and fixnums (BT + JC)
249
250 x86{,-64}/PPC:
251 * branch-free MIN/MAX on word-sized integers and fixnums (floats could
252   be handled too, modulo safety considerations on the PPC)
253
254 x86-64:
255 * efficient LOGTESTs on word-sized integers and fixnums (TEST)
256
257 etc., etc.
258
259 (The framework for this has been implemented as of 0.9.9.18; see the
260 vm-support-routine COMBINATION-IMPLEMENTATION-STYLE and its use in
261 src/compiler/ir1opt.lisp, IR1-OPTIMIZE-COMBINATION.  The above
262 optimizations are left as an exercise for the reader.)
263 --------------------------------------------------------------------------------
264 #30
265 (defun foo (x y)
266   (< x y))
267
268 FOO's IR1 representation is roughly:
269
270 (defun foo (x y)
271   (if (< x y)
272       T
273       NIL))
274
275 However, if a full call is generated for < (and similarly for other
276 predicate functions), then the IF is unnecessary, since the return value
277 of (< x y) is already T or NIL.
278 --------------------------------------------------------------------------------
279 #31
280 The typecheck generated for a declaration like (integer 0 45) on x86 looks
281 like:
282
283 ;      12B:       F6C203           TEST DL, 3
284 ;      12E:       753B             JNE L1
285 ;      130:       8BC2             MOV EAX, EDX
286 ;      132:       83F800           CMP EAX, 0
287 ;      135:       7C34             JL L1
288 ;      137:       8BC2             MOV EAX, EDX
289 ;      139:       3DB4000000       CMP EAX, 180
290 ;      13E:       7F2B             JNLE L1
291
292 A better code sequence for this would be:
293
294   TEST DL, 3
295   JNE L1
296   MOV EAX, EDX
297   CMP EAX, 180
298   JBE L1
299
300 Doing an unsigned comparison means that, similarly to %CHECK-BOUND, we can
301 combine the <0 and >=bound tests.  This sort of test is generated often
302 in SBCL and any array-based code that's serious about type-checking its
303 indices.
304 --------------------------------------------------------------------------------
305 #32
306 The code for a vector bounds check on x86 (similarly on x86-64) where
307 the vector is in EDX and the index in EAX looks like:
308
309 ;       49: L0:   8B5AFD           MOV EBX, [EDX-3]
310 ;       4C:       39C3             CMP EBX, EAX
311 ;       4E:       7632             JBE L2
312
313 because %CHECK-BOUND is used for bounds-checking any array dimension.
314 A more efficient specialization (%CHECK-BOUND/VECTOR) would produce:
315
316   CMP [EDX-3], EAX
317   JBE L2
318
319 Which is slightly shorter and avoids using a register.
320 --------------------------------------------------------------------------------
321 #33
322 Reports from the Java camp indicate that using an SSE2-based
323 floating-point backend on x86 when possible is highly preferable to
324 using the x86 FP stack.  It would be nice if SBCL included an SSE2-based
325 floating point backend with a compile-time option to switch between the
326 two.
327 --------------------------------------------------------------------------------
328 #34
329 Compiling
330
331 (defun foo (x y)
332   (declare (type (integer 0 45) x y))
333   (+ x y))
334
335 results in the following error trapping code for type-checking the
336 arguments:
337
338 ;      424: L0:   8B058CE31812     MOV EAX, [#x1218E38C]      ; '(MOD 46)
339 ;      42A:       0F0B0A           BREAK 10                   ; error trap
340 ;      42D:       05               BYTE #X05
341 ;      42E:       1F               BYTE #X1F                  ; OBJECT-NOT-TYPE-ERROR
342 ;      42F:       FECE01           BYTE #XFE, #XCE, #X01      ; EDI
343 ;      432:       0E               BYTE #X0E                  ; EAX
344 ;      433: L1:   8B0590E31812     MOV EAX, [#x1218E390]      ; '(MOD 46)
345 ;      439:       0F0B0A           BREAK 10                   ; error trap
346 ;      43C:       03               BYTE #X03
347 ;      43D:       1F               BYTE #X1F                  ; OBJECT-NOT-TYPE-ERROR
348 ;      43E:       8E               BYTE #X8E                  ; EDX
349 ;      43F:       0E               BYTE #X0E                  ; EAX
350
351 Notice that '(MOD 46) has two entries in the constant vector.  Having
352 one would be preferable.
353 --------------------------------------------------------------------------------
354 #35
355 Compiling
356
357 (defun foo (a i)
358   (declare (type simple-vector a))
359   (aref a i))
360
361 results in the following x86 code:
362
363 ; 115886E9:       F7C703000000     TEST EDI, 3                ; no-arg-parsing entry point
364 ;      6EF:       7510             JNE L0
365 ;      6F1:       8BC7             MOV EAX, EDI
366 ;      6F3:       83F800           CMP EAX, 0
367 ;      6F6:       7C09             JL L0
368 ;      6F8:       8BC7             MOV EAX, EDI
369 ;      6FA:       3DF8FFFF7F       CMP EAX, 2147483640
370 ;      6FF:       7E0F             JLE L1
371 ;      701: L0:   8B057C865811     MOV EAX, [#x1158867C]      ; '(MOD
372                                                               ;   536870911)
373 ;      707:       0F0B0A           BREAK 10                   ; error trap
374 ;      70A:       05               BYTE #X05
375 ;      70B:       1F               BYTE #X1F                  ; OBJECT-NOT-TYPE-ERROR
376 ;      70C:       FECE01           BYTE #XFE, #XCE, #X01      ; EDI
377 ;      70F:       0E               BYTE #X0E                  ; EAX
378 ;      710: L1:   8B42FD           MOV EAX, [EDX-3]
379 ;      713:       8BCF             MOV ECX, EDI
380 ;      715:       39C8             CMP EAX, ECX
381 ;      717:       7620             JBE L2
382 ;      719:       8B540A01         MOV EDX, [EDX+ECX+1]
383
384 ... plus the standard return sequence and some error blocks.  The
385 `TEST EDI, 3' and associated comparisons are to ensure that `I' is a
386 positive fixnum.  The associated comparisons are unnecessary, as the
387 %CHECK-BOUND VOP only requires its tested index to be a fixnum and takes
388 care of the negative fixnum case itself.
389
390 {HAIRY-,}DATA-VECTOR-REF are DEFKNOWN'd with EXPLICIT-CHECK, which would
391 seem to take care of this, but EXPLICIT-CHECK only seems to be used when
392 compiling calls to unknown functions or similar.  Furthermore,
393 EXPLICIT-CHECK, as NJF understands it, doesn't have the right
394 semantics--it suppresses all type checking of arguments, whereas what we
395 really want is to ensure that the argument is a fixnum, but not check
396 its positiveness.
397 --------------------------------------------------------------------------------
398 #36
399
400 In #35, the CMP EAX, $foo instructions are all preceded by a MOV.  They
401 appear to be unnecessary, but are necessary because in IR2, EDI is a
402 DESCRIPTOR-REG, whereas EAX is an ANY-REG--and the comparison VOPs only
403 accept ANY-REGs.  Therefore, the MOVs are "necessary" to ensure that the
404 comparison VOP receives an TN of the appropriate storage class.
405
406 Obviously, it would be better if a) we only performed one MOV prior to
407 all three comparisons or b) eliminated the necessity of the MOV(s)
408 altogether.  The former option is probably easier than the latter.
409
410 --------------------------------------------------------------------------------
411 #37
412
413 Dynamic extent allocation doesn't currently work for one-element lists,
414 since there's a source transform from (LIST X) to (CONS X NIL).
415