3 (declare (simple-string s))
4 (declare (optimize (speed 3) (safety 0) (debug 0)))
7 (dotimes (i (length s))
8 (when (eql (aref s i) #\1)
12 * On X86 I is represented as a tagged integer.
15 3: SLOT S!11[EDX] {SB-C::VECTOR-LENGTH 1 7} => t23[EAX]
16 4: MOVE t23[EAX] => t24[EBX]
18 --------------------------------------------------------------------------------
21 (declare (optimize (speed 3) (safety 0) (space 2) (debug 0)))
22 (declare (type (simple-array double-float 1) v))
24 (declare (type double-float s))
25 (dotimes (i (length v))
26 (setq s (+ s (aref v i))))
29 * Python does not combine + with AREF, so generates extra move and
32 * On X86 Python thinks that all FP registers are directly accessible
33 and emits costy MOVE ... => FR1.
35 --------------------------------------------------------------------------------
38 (declare (optimize (speed 3) (safety 0) (space 2))
40 (let ((v (make-list n)))
41 (setq v (make-array n))
44 * IR1 does not optimize away (MAKE-LIST N).
45 --------------------------------------------------------------------------------
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))))
53 VOP DATA-VECTOR-SET/SIMPLE-STRING V2!14[EDI] t32[EAX] t30[S2]>t33[CL]
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]>
60 * The value of DATA-VECTOR-SET is not used, so there is no need in the
64 --------------------------------------------------------------------------------
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)))
74 Without the marked declaration Python will use boxed representation for X1.
80 ;; use of X as DOUBLE-FLOAT
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"
89 (if (= (cond ((irgh x) 0)
96 This code could be optimized to
102 --------------------------------------------------------------------------------
104 (inverted variant of #9)
107 (let ((y (sap-alien x c-string)))
111 It could be optimized to
113 (lambda (x) (list x x))
115 (if Y were used only once, the current compiler would optimize it)
116 --------------------------------------------------------------------------------
118 (typep (truly-the (simple-array * (*)) x) 'simple-vector)
121 --------------------------------------------------------------------------------
123 FAST-+/FIXNUM and similar should accept unboxed arguments in interests
124 of representation selection. Problem: inter-TN dependencies.
125 --------------------------------------------------------------------------------
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 --------------------------------------------------------------------------------
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:
137 (DECLARE (OPTIMIZE (SAFETY 1) (SPEED 3) (DEBUG 1))
138 (TYPE (INTEGER -10000 10000) A)
141 ((89 125 16) (ASH A (MIN 18 -706)))
142 (T (DPB -3 (BYTE 30 30) -1))))
143 --------------------------------------------------------------------------------
146 ((= i (the (integer 0 100) n)))
149 It is commonly expected for Python to derive (FIXNUMP I). (If ``='' is
150 replaced with ``>='', Python will do.)
151 --------------------------------------------------------------------------------
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 --------------------------------------------------------------------------------
161 (lambda (x) (declare (null x)) (sxhash x)) goes through SYMBOL-HASH
162 rather than either constant-folding or manipulating NIL-VALUE or
164 --------------------------------------------------------------------------------
169 (declare (dynamic-extent dx))
172 DX is not allocated on stack.
173 --------------------------------------------------------------------------------
175 (defun-with-dx foo (x)
177 (let ((l (list nil nil)))
179 (setf (second l) (1- x))
182 (declare (dynamic-extent l))
185 Result of MAKE is not stack allocated, which means that
186 stack-allocation of structures is impossible.
187 --------------------------------------------------------------------------------
189 (defun-with-dx foo ()
190 (let ((dx (list (list 1 2) (list 3 4))))
191 (declare (dynamic-extent dx))
194 External list in DX is allocated on stack, but internal are not.
195 --------------------------------------------------------------------------------
197 IR2 does not perform unused code flushing.
198 --------------------------------------------------------------------------------
200 Python does not know that &REST lists are LISTs (and cannot derive it).
201 --------------------------------------------------------------------------------
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 --------------------------------------------------------------------------------
208 SBCL cannot derive upper bound for I and uses generic arithmetic here:
212 (dotimes (i (length l))
214 (map-foo (lambda (x) (if x (return t)))
219 (So the constraint propagator or a possible future SSA-convertor
220 should know the connection between an NLE and its CLEANUP.)
221 --------------------------------------------------------------------------------
223 Initialization of stack-allocated arrays is inefficient: we always
224 fill the vector with zeroes, even when it is not needed (as for
225 platforms with conservative GC or for arrays of unboxed objectes) and
226 is performed later explicitely.
227 --------------------------------------------------------------------------------
229 a. Accessing raw slots in structure instances is more inefficient than
230 it could be; if we placed raw slots before the header word, we would
231 not need to do arithmetic at runtime to access them. (But beware:
232 this would complicate handling of the interior pointer).
234 b. (Also note that raw slots are currently disabled on HPPA)
235 --------------------------------------------------------------------------------
237 Python is overly zealous when converting high-level CL functions, such
238 as MIN/MAX, LOGBITP, and LOGTEST, to low-level CL functions. Reducing
239 Python's aggressiveness would make it easier to effect changes such as
242 * direct MIN/MAX on {SINGLE,DOUBLE}-FLOATs ({MIN,MAX}S{S,D})
245 * direct LOGBITP on word-sized integers and fixnums (BT + JC)
248 * branch-free MIN/MAX on word-sized integers and fixnums (floats could
249 be handled too, modulo safety considerations on the PPC)
252 * efficient LOGTESTs on word-sized integers and fixnums (TEST)
256 (The framework for this has been implemented as of 0.9.9.18; see the
257 vm-support-routine COMBINATION-IMPLEMENTATION-STYLE and its use in
258 src/compiler/ir1opt.lisp, IR1-OPTIMIZE-COMBINATION. The above
259 optimizations are left as an exercise for the reader.)
260 --------------------------------------------------------------------------------
265 FOO's IR1 representation is roughly:
272 However, if a full call is generated for < (and similarly for other
273 predicate functions), then the IF is unnecessary, since the return value
274 of (< x y) is already T or NIL.
275 --------------------------------------------------------------------------------
277 The typecheck generated for a declaration like (integer 0 45) on x86 looks
280 ; 12B: F6C203 TEST DL, 3
282 ; 130: 8BC2 MOV EAX, EDX
283 ; 132: 83F800 CMP EAX, 0
285 ; 137: 8BC2 MOV EAX, EDX
286 ; 139: 3DB4000000 CMP EAX, 180
289 A better code sequence for this would be:
297 Doing an unsigned comparison means that, similarly to %CHECK-BOUND, we can
298 combine the <0 and >=bound tests. This sort of test is generated often
299 in SBCL and any array-based code that's serious about type-checking its
301 --------------------------------------------------------------------------------
303 The code for a vector bounds check on x86 (similarly on x86-64) where
304 the vector is in EDX and the index in EAX looks like:
306 ; 49: L0: 8B5AFD MOV EBX, [EDX-3]
307 ; 4C: 39C3 CMP EBX, EAX
310 because %CHECK-BOUND is used for bounds-checking any array dimension.
311 A more efficient specialization (%CHECK-BOUND/VECTOR) would produce:
316 Which is slightly shorter and avoids using a register.
317 --------------------------------------------------------------------------------
319 Reports from the Java camp indicate that using an SSE2-based
320 floating-point backend on x86 when possible is highly preferable to
321 using the x86 FP stack. It would be nice if SBCL included an SSE2-based
322 floating point backend with a compile-time option to switch between the
324 --------------------------------------------------------------------------------
329 (declare (type (integer 0 45) x y))
332 results in the following error trapping code for type-checking the
335 ; 424: L0: 8B058CE31812 MOV EAX, [#x1218E38C] ; '(MOD 46)
336 ; 42A: 0F0B0A BREAK 10 ; error trap
338 ; 42E: 1F BYTE #X1F ; OBJECT-NOT-TYPE-ERROR
339 ; 42F: FECE01 BYTE #XFE, #XCE, #X01 ; EDI
340 ; 432: 0E BYTE #X0E ; EAX
341 ; 433: L1: 8B0590E31812 MOV EAX, [#x1218E390] ; '(MOD 46)
342 ; 439: 0F0B0A BREAK 10 ; error trap
344 ; 43D: 1F BYTE #X1F ; OBJECT-NOT-TYPE-ERROR
345 ; 43E: 8E BYTE #X8E ; EDX
346 ; 43F: 0E BYTE #X0E ; EAX
348 Notice that '(MOD 46) has two entries in the constant vector. Having
349 one would be preferable.
350 --------------------------------------------------------------------------------
355 (declare (type simple-vector a))
358 results in the following x86 code:
360 ; 115886E9: F7C703000000 TEST EDI, 3 ; no-arg-parsing entry point
362 ; 6F1: 8BC7 MOV EAX, EDI
363 ; 6F3: 83F800 CMP EAX, 0
365 ; 6F8: 8BC7 MOV EAX, EDI
366 ; 6FA: 3DF8FFFF7F CMP EAX, 2147483640
368 ; 701: L0: 8B057C865811 MOV EAX, [#x1158867C] ; '(MOD
370 ; 707: 0F0B0A BREAK 10 ; error trap
372 ; 70B: 1F BYTE #X1F ; OBJECT-NOT-TYPE-ERROR
373 ; 70C: FECE01 BYTE #XFE, #XCE, #X01 ; EDI
374 ; 70F: 0E BYTE #X0E ; EAX
375 ; 710: L1: 8B42FD MOV EAX, [EDX-3]
376 ; 713: 8BCF MOV ECX, EDI
377 ; 715: 39C8 CMP EAX, ECX
379 ; 719: 8B540A01 MOV EDX, [EDX+ECX+1]
381 ... plus the standard return sequence and some error blocks. The
382 `TEST EDI, 3' and associated comparisons are to ensure that `I' is a
383 positive fixnum. The associated comparisons are unnecessary, as the
384 %CHECK-BOUND VOP only requires its tested index to be a fixnum and takes
385 care of the negative fixnum case itself.
387 {HAIRY-,}DATA-VECTOR-REF are DEFKNOWN'd with EXPLICIT-CHECK, which would
388 seem to take care of this, but EXPLICIT-CHECK only seems to be used when
389 compiling calls to unknown functions or similar. Furthermore,
390 EXPLICIT-CHECK, as NJF understands it, doesn't have the right
391 semantics--it suppresses all type checking of arguments, whereas what we
392 really want is to ensure that the argument is a fixnum, but not check
394 --------------------------------------------------------------------------------
397 In #35, the CMP EAX, $foo instructions are all preceded by a MOV. They
398 appear to be unnecessary, but are necessary because in IR2, EDI is a
399 DESCRIPTOR-REG, whereas EAX is an ANY-REG--and the comparison VOPs only
400 accept ANY-REGs. Therefore, the MOVs are "necessary" to ensure that the
401 comparison VOP receives an TN of the appropriate storage class.
403 Obviously, it would be better if a) we only performed one MOV prior to
404 all three comparisons or b) eliminated the necessity of the MOV(s)
405 altogether. The former option is probably easier than the latter.