0.pre7.3:
[sbcl.git] / contrib / compiler-extras.lisp
1 ;;;; The files
2 ;;;;   compiler-extras.lisp
3 ;;;;   code-extras.lisp
4 ;;;; hold things that I (WHN) am working on which are sufficiently
5 ;;;; closely tied to the system that they want to be under the same
6 ;;;; revision control, but which aren't yet ready for prime time.
7 ;;;;
8 ;;;; As of around sbcl-0.6.10, these are mostly performance fixes.
9 ;;;; Fixes for logical bugs tend to go straight into the system, but
10 ;;;; fixes for performance problems can easily introduce logical bugs,
11 ;;;; and no one's going to thank me for replacing old slow correct
12 ;;;; code with new fast wrong code.
13 ;;;;
14 ;;;; Unless you want to live *very* dangerously, you don't want to be
15 ;;;; running these. There might be some small value to looking at
16 ;;;; these files to see whether I'm working on optimizing something
17 ;;;; whose performance you care about, so that you can patch it, or
18 ;;;; write test cases for it, or pester me to release it, or whatever.
19
20 (in-package "SB-KERNEL")
21 (eval-when (:compile-toplevel :load-toplevel :execute)
22   (export '(index-or-minus-1
23             %find-position %find-position-vector-macro
24             %find-position-if %find-position-if-vector-macro)))
25
26 (in-package "SB-C")
27
28 (declaim (optimize (speed 1) (space 2)))
29
30 ;;; TO DO for DEFTRANSFORM FILL:
31 ;;;   ?? This DEFTRANSFORM, and the old DEFTRANSFORMs, should only
32 ;;;      apply when SPEED > SPACE.
33 ;;;   ?? Add test cases.
34
35 #+nil ; not tested yet..
36 (deftransform replace ((seq1 seq2 &key (start1 0) end1 (start2 0) end2)
37                        (vector vector &key
38                                (:start1 index) (:end1 (or index null))
39                                (:start2 index) (:end2 (or index null)))
40                        *
41                        ;; This is potentially an awfully big transform
42                        ;; (if things like (EQ SEQ1 SEQ2) aren't known
43                        ;; at runtime). We need to make it available
44                        ;; inline, since otherwise there's no way to do
45                        ;; it efficiently on all array types, but it
46                        ;; probably doesn't belong inline all the time.
47                        :policy (> speed (1+ space)))
48   "open code"
49   (let ((et1 (upgraded-element-type-specifier-or-give-up seq1))
50         (et2 (upgraded-element-type-specifier-or-give-up seq2)))
51     `(let* ((n-copied (min (- end1 start1) (- end2 start2)))
52             (effective-end1 (+ start1 n-copied)))
53        (if (eq seq1 seq2)
54            (with-array-data ((seq seq1)
55                              (start (min start1 start2))
56                              (end (max end1 end2)))
57              (declare (type (simple-array ,et1 1) seq))
58              (if (<= start1 start2)
59                  (let ((index2 start2))
60                    (declare (type index index2))
61                    (loop for index1 of-type index
62                          from start1 below effective-end1 do
63                          (setf (aref seq index1)
64                                (aref seq index2))
65                          (incf index2)))
66                  (let ((index2 (1- end2)))
67                    (declare (type (integer -2 #.most-positive-fixnum) index2))
68                    (loop for index1 of-type index-or-minus-1
69                          from (1- effective-end1) downto start1 do
70                          (setf (aref seq index1)
71                                (aref seq index2))
72                          (decf index2)))))
73            (with-array-data ((seq1 seq1) (start1 start1) (end1 end1))
74              (declare (type (simple-array ,et1 1) seq1))
75              (with-array-data ((seq2 seq2) (start2 start2) (end2 end2))
76                (declare (type (simple-array ,et2 1) seq2))
77                (let ((index2 start2))
78                  (declare (type index index2))
79                  (loop for index1 of-type index
80                        from start1 below effective-end1 do
81                        (setf (aref seq index1)
82                              (aref seq index2))
83                        (incf index2))))))
84        seq1)))
85
86 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
87 ;;;; setting up for POSITION/FIND stuff
88
89 (defknown %find-position
90   (t sequence t index sequence-end function function)
91   (values t (or index null))
92   (flushable call))
93 (defknown %find-position-if 
94   (function sequence t index sequence-end function)
95   (values t (or index null))
96   (call))
97
98 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
99 ;;;; POSITION, POSITION-IF, FIND, and FIND-IF proper
100
101 ;;; FIXME: Blow away old CMU CL implementation:
102 ;;;  * the section of seq.lisp with VECTOR-LOCATER-MACRO and LOCATER-TEST-NOT
103 ;;;  * matches to 'find' and 'position' in seq.lisp
104
105 ;;; We want to make sure that %FIND-POSITION is inline-expanded into
106 ;;; %FIND-POSITION-IF only when %FIND-POSITION-IF has an inline
107 ;;; expansion, so we factor out the condition into this function.
108 (defun check-inlineability-of-find-position-if (sequence from-end)
109   (let ((ctype (continuation-type sequence)))
110     (cond ((csubtypep ctype (specifier-type 'vector))
111            ;; It's not worth trying to inline vector code unless we know
112            ;; a fair amount about it at compile time.
113            (upgraded-element-type-specifier-or-give-up sequence)
114            (unless (constant-continuation-p from-end)
115              (give-up-ir1-transform
116               "FROM-END argument value not known at compile time")))
117           ((csubtypep ctype (specifier-type 'list))
118            ;; Inlining on lists is generally worthwhile.
119            ) 
120           (t
121            (give-up-ir1-transform
122             "sequence type not known at compile time")))))
123
124 ;;; %FIND-POSITION-IF for LIST data
125 (deftransform %find-position-if ((predicate sequence from-end start end key)
126                                  (function list t t t function)
127                                  *
128                                  :policy (> speed space)
129                                  :important t)
130   "expand inline"
131   '(let ((index 0)
132          (find nil)
133          (position nil))
134      (declare (type index index))
135      (dolist (i sequence (values find position))
136        (let ((key-i (funcall key i)))
137          (when (and end (>= index end))
138            (return (values find position)))
139          (when (>= index start)
140            (when (funcall predicate key-i)
141              ;; This hack of dealing with non-NIL FROM-END for list data
142              ;; by iterating forward through the list and keeping track of
143              ;; the last time we found a match might be more screwy than
144              ;; what the user expects, but it seems to be allowed by the
145              ;; ANSI standard. (And if the user is screwy enough to ask
146              ;; for FROM-END behavior on list data, turnabout is fair play.)
147              ;;
148              ;; It's also not enormously efficient, calling PREDICATE and
149              ;; KEY more often than necessary; but all the alternatives
150              ;; seem to have their own efficiency problems.
151              (if from-end
152                  (setf find i
153                        position index)
154                  (return (values i index))))))
155        (incf index))))
156
157 ;;; %FIND-POSITION for LIST data can be expanded into %FIND-POSITION-IF
158 ;;; without loss of efficiency. (I.e., the optimizer should be able
159 ;;; to straighten everything out.)
160 (deftransform %find-position ((item sequence from-end start end key test)
161                               (t list t t t t t)
162                               *
163                               :policy (> speed space)
164                               :important t)
165   "expand inline"
166   '(%find-position-if (let ((test-fun (%coerce-callable-to-function test)))
167                         (lambda (i)
168                           (funcall test-fun i item)))
169                       sequence
170                       from-end
171                       start
172                       end
173                       (%coerce-callable-to-function key)))
174
175 ;;; The inline expansions for the VECTOR case are saved as macros so
176 ;;; that we can share them between the DEFTRANSFORMs and the default
177 ;;; cases in the DEFUNs. (This isn't needed for the LIST case, because
178 ;;; the DEFTRANSFORMs for LIST are less choosy about when to expand.)
179 (defun %find-position-or-find-position-if-vector-expansion (sequence-arg
180                                                             from-end
181                                                             start
182                                                             end-arg
183                                                             element
184                                                             done-p-expr)
185   (let ((offset (gensym "OFFSET"))
186         (block (gensym "BLOCK"))
187         (index (gensym "INDEX"))
188         (n-sequence (gensym "N-SEQUENCE-"))
189         (sequence (gensym "SEQUENCE"))
190         (n-end (gensym "N-END-"))
191         (end (gensym "END-")))
192     `(let ((,n-sequence ,sequence-arg)
193            (,n-end ,end-arg))
194        (with-array-data ((,sequence ,n-sequence :offset-var ,offset)
195                          (,start ,start)
196                          (,end (or ,n-end (length ,n-sequence))))
197          (block ,block
198            (macrolet ((maybe-return ()
199                         '(let ((,element (aref ,sequence ,index)))
200                            (when ,done-p-expr
201                              (return-from ,block
202                                (values ,element
203                                        (- ,index ,offset)))))))
204              (if ,from-end
205                  (loop for ,index
206                        ;; (If we aren't fastidious about declaring that 
207                        ;; INDEX might be -1, then (FIND 1 #() :FROM-END T)
208                        ;; can send us off into never-never land, since
209                        ;; INDEX is initialized to -1.)
210                        of-type index-or-minus-1
211                        from (1- ,end) downto ,start do
212                        (maybe-return))
213                  (loop for ,index of-type index from ,start below ,end do
214                        (maybe-return))))
215            (values nil nil))))))
216 (defmacro %find-position-vector-macro (item sequence
217                                             from-end start end key test)
218   (let ((element (gensym "ELEMENT")))
219     (%find-position-or-find-position-if-vector-expansion
220      sequence
221      from-end
222      start
223      end
224      element
225      `(funcall ,test ,item (funcall ,key ,element)))))
226 (defmacro %find-position-if-vector-macro (predicate sequence
227                                                     from-end start end key)
228   (let ((element (gensym "ELEMENT")))
229     (%find-position-or-find-position-if-vector-expansion
230      sequence
231      from-end
232      start
233      end
234      element
235      `(funcall ,predicate (funcall ,key ,element)))))
236
237 ;;; %FIND-POSITION and %FIND-POSITION-IF for VECTOR data
238 (deftransform %find-position-if ((predicate sequence from-end start end key)
239                                  (function vector t t t function)
240                                  *
241                                  :policy (> speed space)
242                                  :important t)
243   "expand inline"
244   (check-inlineability-of-find-position-if sequence from-end)
245   '(%find-position-if-vector-macro predicate sequence
246                                    from-end start end key))
247 (deftransform %find-position ((item sequence from-end start end key test)
248                               (t vector t t t function function)
249                               *
250                               :policy (> speed space)
251                               :important t)
252   "expand inline"
253   (check-inlineability-of-find-position-if sequence from-end)
254   '(%find-position-vector-macro item sequence
255                                 from-end start end key test))
256 \f
257 ;;;; optimizations for floating point FLOOR, CEILING, TRUNCATE, and
258 ;;;; ROUND, lifted from CMU CL 18c
259 ;;;;
260 ;;;; (Without these optimizations, these functions cons!)
261
262 ;;; Convert (TRUNCATE x y) to the obvious implementation.  We only want
263 ;;; this when under certain conditions and let the generic TRUNCATE
264 ;;; handle the rest.  (Note: if Y = 1, the divide and multiply by Y
265 ;;; should be removed by other DEFTRANSFORMs.)
266 (deftransform truncate ((x &optional y)
267                         (float &optional (or float integer)))
268   '(let ((res (%unary-truncate (/ x y))))
269      (values res (- x (* y res)))))
270
271 (deftransform floor ((number &optional divisor)
272                      (float &optional (or integer float)))
273   '(multiple-value-bind (tru rem) (truncate number divisor)
274     (if (and (not (zerop rem))
275              (if (minusp divisor)
276                  (plusp number)
277                  (minusp number)))
278         (values (1- tru) (+ rem divisor))
279         (values tru rem))))
280
281 (deftransform ceiling ((number &optional divisor)
282                        (float &optional (or integer float)))
283   '(multiple-value-bind (tru rem) (truncate number divisor)
284     (if (and (not (zerop rem))
285              (if (minusp divisor)
286                  (minusp number)
287                  (plusp number)))
288         (values (1+ tru) (- rem divisor))
289         (values tru rem))))