Style improvements and minor bugfix from sb-fasteval integration.
[sbcl.git] / src / compiler / target-main.lisp
blob60fe652b2ad86b7d4e99c8045318dbe7f71b80c6
1 ;;;; functions from classic CMU CL src/compiler/main.lisp which are
2 ;;;; needed only (and which may make sense only) on the
3 ;;;; cross-compilation target, not the cross-compilation host
5 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; more information.
7 ;;;;
8 ;;;; This software is derived from the CMU CL system, which was
9 ;;;; written at Carnegie Mellon University and released into the
10 ;;;; public domain. The software is in the public domain and is
11 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
12 ;;;; files for more information.
14 (in-package "SB!C")
16 ;;;; CL:COMPILE
18 (defun get-lambda-to-compile (definition-designator)
19 (if (consp definition-designator)
20 definition-designator
21 (multiple-value-bind (definition env-p)
22 (function-lambda-expression definition-designator)
23 (when env-p
24 (error "~S was defined in a non-null environment."
25 definition-designator))
26 (unless definition
27 (error "can't find a definition for ~S" definition-designator))
28 definition)))
30 ;;; Handle the nontrivial case of CL:COMPILE.
31 ;;;
32 ;;; If ERRORP is true signals an error immediately -- otherwise returns
33 ;;; a function that will signal the error.
34 (defun actually-compile (name definition *lexenv* source-info tlf errorp)
35 (let ((source-paths (when source-info *source-paths*)))
36 (with-compilation-values
37 (sb!xc:with-compilation-unit ()
38 ;; FIXME: These bindings were copied from SUB-COMPILE-FILE with
39 ;; few changes. Once things are stable, the shared bindings
40 ;; probably be merged back together into some shared utility
41 ;; macro, or perhaps both merged into one of the existing utility
42 ;; macros SB-C::WITH-COMPILATION-VALUES or
43 ;; CL:WITH-COMPILATION-UNIT.
44 (with-source-paths
45 (prog* ((tlf (or tlf 0))
46 ;; If we have a source-info from LOAD, we will
47 ;; also have a source-paths already set up -- so drop
48 ;; the ones from WITH-COMPILATION-VALUES.
49 (*source-paths* (or source-paths *source-paths*))
50 (form (get-lambda-to-compile definition))
51 (*source-info* (or source-info
52 (make-lisp-source-info
53 form :parent *source-info*)))
54 (*toplevel-lambdas* ())
55 (*block-compile* nil)
56 (*allow-instrumenting* nil)
57 (*code-coverage-records* nil)
58 (*code-coverage-blocks* nil)
59 (*current-path* nil)
60 (*last-source-context* nil)
61 (*last-original-source* nil)
62 (*last-source-form* nil)
63 (*last-format-string* nil)
64 (*last-format-args* nil)
65 (*last-message-count* 0)
66 (*last-error-context* nil)
67 (*gensym-counter* 0)
68 ;; KLUDGE: This rebinding of policy is necessary so that
69 ;; forms such as LOCALLY at the REPL actually extend the
70 ;; compilation policy correctly. However, there is an
71 ;; invariant that is potentially violated: future
72 ;; refactoring must not allow this to be done in the file
73 ;; compiler. At the moment we're clearly alright, as we
74 ;; call %COMPILE with a core-object, not a fasl-stream,
75 ;; but caveat future maintainers. -- CSR, 2002-10-27
76 (*policy* (lexenv-policy *lexenv*))
77 ;; see above
78 (*handled-conditions* (lexenv-handled-conditions *lexenv*))
79 ;; ditto
80 (*disabled-package-locks* (lexenv-disabled-package-locks *lexenv*))
81 ;; FIXME: ANSI doesn't say anything about CL:COMPILE
82 ;; interacting with these variables, so we shouldn't. As
83 ;; of SBCL 0.6.7, COMPILE-FILE controls its verbosity by
84 ;; binding these variables, so as a quick hack we do so
85 ;; too. But a proper implementation would have verbosity
86 ;; controlled by function arguments and lexical variables.
87 (*compile-verbose* nil)
88 (*compile-print* nil)
89 (oops nil))
90 (handler-bind (((satisfies handle-condition-p) #'handle-condition-handler))
91 (unless source-paths
92 (find-source-paths form tlf))
93 (let ((*compiler-error-bailout*
94 (lambda (e)
95 (setf oops e)
96 ;; Unwind the compiler frames: users want the know where
97 ;; the error came from, not how the compiler got there.
98 (go :error))))
99 (return
100 (with-world-lock ()
101 (%compile form (make-core-object)
102 :name name
103 :path `(original-source-start 0 ,tlf))))))
104 :error
105 ;; Either signal the error right away, or return a function that
106 ;; will signal the corresponding COMPILED-PROGRAM-ERROR. This is so
107 ;; that we retain our earlier behaviour when called with erronous
108 ;; lambdas via %SIMPLE-EVAL. We could legally do just either one
109 ;; always, but right now keeping the old behaviour seems like less
110 ;; painful option: compiler.pure.lisp is full of tests that make all
111 ;; sort of assumptions about when which things are signalled. FIXME,
112 ;; probably.
113 (if errorp
114 (error oops)
115 (let ((message (princ-to-string oops))
116 (source (source-to-string form)))
117 (return
118 (lambda (&rest arguments)
119 (declare (ignore arguments))
120 (error 'compiled-program-error
121 :message message
122 :source source)))))))))))
124 (defun compile-in-lexenv (name definition lexenv
125 &optional source-info tlf errorp)
126 (dx-flet ((really-compile (definition lexenv)
127 (actually-compile
128 name definition lexenv source-info tlf errorp)))
129 (multiple-value-bind (compiled-definition warnings-p failure-p)
130 (typecase definition
131 #!+sb-fasteval
132 (sb!interpreter:interpreted-function
133 (multiple-value-call #'really-compile
134 (sb!interpreter:prepare-for-compile definition)))
135 #!+sb-eval
136 (sb!eval:interpreted-function
137 (multiple-value-call #'really-compile
138 (sb!eval:prepare-for-compile definition)))
139 (function
140 (values definition nil nil))
142 (really-compile definition lexenv)))
143 (aver (typep compiled-definition 'compiled-function))
144 (let ((result (if (not name)
145 compiled-definition
146 (progn
147 (if (and (symbolp name) (macro-function name))
148 (setf (macro-function name) compiled-definition)
149 (setf (fdefinition name) compiled-definition))
150 name))))
151 (values result warnings-p failure-p)))))
153 (defun compile (name &optional (definition (or (and (symbolp name)
154 (macro-function name))
155 (fdefinition name))))
156 #!+sb-doc
157 "Produce a compiled function from DEFINITION. If DEFINITION is a
158 lambda-expression, it is coerced to a function. If DEFINITION is an
159 interpreted function, it is compiled. If DEFINITION is already a compiled
160 function, it is used as-is. (Future versions of SBCL might try to
161 recompile the existing definition, but this is not currently supported.)
163 If NAME is NIL, the compiled function is returned as the primary value.
164 Otherwise the resulting compiled function replaces existing function
165 definition of NAME, and NAME is returned as primary value; if NAME is a symbol
166 that names a macro, its macro function is replaced and NAME is returned as
167 primary value.
169 Also returns a secondary value which is true if any conditions of type
170 WARNING occur during the compilation, and NIL otherwise.
172 Tertiary value is true if any conditions of type ERROR, or WARNING that are
173 not STYLE-WARNINGs occur during compilation, and NIL otherwise.
175 (compile-in-lexenv name definition (make-null-lexenv)))
177 (defun make-form-tracking-stream-observer (file-info)
178 (lambda (arg1 arg2 arg3)
179 ;; Log some kind of reader event into FILE-INFO.
180 (case arg1
181 (:reset ; a char macro returned zero values - "virtual whitespace".
182 ;; I think this would be an ideal place at which to inquire and stash
183 ;; the FILE-POSITION in bytes so that DEBUG-SOURCE-START-POSITIONS
184 ;; are obtained _after_ having skipped virtual whitespace, not before.
185 (setf (fill-pointer (file-info-subforms file-info)) 0))
187 (let ((subforms (file-info-subforms file-info)))
188 ;; (ARG1 ARG2 ARG3) = (start-pos end-pos form)
189 (vector-push-extend arg1 subforms)
190 (vector-push-extend arg2 subforms)
191 (vector-push-extend arg3 subforms))))))
193 ;;; COMPILE-FILE-POSITION macro
195 ;; Macros and inline functions report the original-source position. e.g.:
196 ;; 01: (declaim (inline foo))
197 ;; 02: (defun foo (x) (if x (warn "fail @line ~d" (compile-file-position))))
198 ;; 03: (defun bar (y) (foo y))
199 ;; 04: (defun baz (y) (foo y))
200 ;; will cause BAR to print 3 and BAZ to print 4 in the warning message.
202 ;; For macros this seems fair enough, but for inline functions it could
203 ;; be considered undesirable on the grounds that enabling/disabling inlining
204 ;; should not change visible behavior. Other then working harder to figure
205 ;; out where we are in inlined code (which may not even be feasible),
206 ;; a viable remedy is that all inlineable functions should have their stored
207 ;; representation not contain any macros, i.e. macros could be pre-expanded,
208 ;; which in this case means stuffing in the literal integers.
209 ;; I feel that that would be a general improvement to semantics, because
210 ;; as things are, an inline function's macros are expanded at least as many
211 ;; times as there are calls to the function - not very defensible
212 ;; as a design choice, but just an accident of the particular implementation.
214 (defmacro compile-file-position (&whole this-form)
215 #!+sb-doc
216 "Return character position of this macro invocation or NIL if unavailable."
217 ;; Counting characters is intuitive because the transfer element size is 1
218 ;; measurement unit. The standard allows counting in something other than
219 ;; characters (namely bytes) for character streams, which is basically
220 ;; irrelevant here, as we don't need random access to the file.
221 (compute-compile-file-position this-form nil))
223 (defmacro compile-file-line (&whole this-form)
224 #!+sb-doc
225 "Return line# and column# of this macro invocation as multiple values."
226 (compute-compile-file-position this-form t))
228 (defun compute-compile-file-position (this-form as-line/col-p)
229 (let (file-info stream charpos)
230 (flet ((find-form-eq (form &optional fallback-path)
231 (with-array-data ((vect (file-info-subforms file-info))
232 (start) (end) :check-fill-pointer t)
233 (declare (ignore start))
234 (do ((i (1- end) (- i 3)))
235 ((< i 0))
236 (declare (index-or-minus-1 i))
237 (when (eq form (svref vect i))
238 (if charpos ; ambiguous
239 (return
240 (setq charpos
241 (and fallback-path
242 (compile-file-position-helper
243 file-info fallback-path))))
244 (setq charpos (svref vect (- i 2)))))))))
245 (let ((source-info *source-info*))
246 (when (and source-info (boundp '*current-path*))
247 (setq file-info (source-info-file-info source-info)
248 stream (source-info-stream source-info))
249 (cond
250 ((not *current-path*)
251 ;; probably a read-time eval
252 (find-form-eq this-form))
253 ;; Hmm, would a &WHOLE argument would work better or worse in general?
255 (let* ((original-source-path
256 (cddr (member 'original-source-start *current-path*)))
257 (path (reverse original-source-path)))
258 (when (file-info-subforms file-info)
259 (let ((form (elt (file-info-forms file-info) (car path))))
260 (dolist (p (cdr path))
261 (setq form (nth p form)))
262 (find-form-eq form (cdr path))))
263 (unless charpos
264 (let ((parent (source-info-parent *source-info*)))
265 ;; probably in a local macro executing COMPILE-FILE-POSITION,
266 ;; not producing a sexpr containing an invocation of C-F-P.
267 (when parent
268 (setq file-info (source-info-file-info parent)
269 stream (source-info-stream parent))
270 (find-form-eq this-form))))))))))
271 (if as-line/col-p
272 (if (and charpos (form-tracking-stream-p stream))
273 (let ((line/col (line/col-from-charpos stream charpos)))
274 `(values ,(car line/col) ,(cdr line/col)))
275 '(values 0 -1))
276 charpos)))
278 ;; Find FORM's character position in FILE-INFO by looking for PATH-TO-FIND.
279 ;; This is done by imparting tree structure to the annotations
280 ;; more-or-less paralleling construction of the original sexpr.
281 ;; Unfortunately, though this was a nice idea, it is not terribly useful.
282 ;; FIND-SOURCE-PATHS can not supply the correct path because it assumes
283 ;; that a form determines a path, whereas the opposite is more accurate.
284 ;; e.g. below are two functions that cause misbehavior.
286 * (defun example1 (x)
287 (if x
288 #1=(format t "Err#2 @~D~%" (compile-file-position))
289 (progn #1#)))
290 * (defconstant +foo+ '(format t "Err#1 @~D~%" (compile-file-position))))
291 * (defun example2 (x) (if x #.+foo+ (progn #.+foo+)))
293 ;; In each case the compiler assigns the same source path to two logically
294 ;; different paths that it takes as it IR1-translates each half of the IF
295 ;; expression, though the ELSE branch obviously has a longer path.
296 ;; However, if you _could_ supply correct paths, this would compute correct
297 ;; answers. (Modulo any bugs due to near-total lack of testing)
299 (defun compile-file-position-helper (file-info path-to-find)
300 (let (found-form start-char)
301 (labels
302 ((recurse (subpath upper-bound queue)
303 (let ((index -1))
304 (declare (type index-or-minus-1 index))
305 (loop
306 (let* ((item (car queue))
307 (end (cdar item)))
308 (when (> end upper-bound)
309 (return))
310 (pop queue)
311 (incf index)
312 (when (and (eql index (car subpath)) (not (cdr subpath)))
313 ;; This does not eagerly declare victory, because we want
314 ;; to find the rightmost match. In "#1=(FOO)" there are two
315 ;; different annotations pointing to (FOO).
316 (setq found-form (cdr item)
317 start-char (caar item)))
318 (unless queue (return))
319 (let* ((next (car queue))
320 (next-end (cdar next)))
321 (cond ((< next-end end) ; could descend
322 ;; only scan children if we're on the correct path
323 (if (eql index (car subpath))
324 (setf queue (recurse (cdr subpath) end queue))
325 ;; else skip quickly by finding the next sibling
326 (loop
327 (pop queue)
328 (when (or (endp queue) (>= (caaar queue) end))
329 (return))))
330 (unless queue (return)))
331 ((= next-end end) ; probably because of "#n="
332 (decf (truly-the (integer 0) index))))))))
333 queue))
334 (let ((list
335 (with-array-data ((v (file-info-subforms file-info))
336 (start) (end) :check-fill-pointer t)
337 (declare (ignore start))
338 (sort (loop for i from 0 below end by 3
339 collect (acons (aref v i)
340 (aref v (+ i 1))
341 (aref v (+ i 2))))
342 #'< :key 'caar))))
343 (recurse path-to-find (cdaar list) (cdr list))))
344 start-char))