8161f5b0223be5ec2585bd2831e5b7cafe089375
[sbcl.git] / src / cold / shared.lisp
1 ;;;; stuff which is not specific to any particular build phase, but
2 ;;;; used by most of them
3 ;;;;
4 ;;;; Note: It's specifically not used when bootstrapping PCL, because
5 ;;;; we do SAVE-LISP after that, and we don't want to save extraneous
6 ;;;; bootstrapping machinery into the frozen image which will
7 ;;;; subsequently be used as the mother of all Lisp sessions.
8
9 ;;;; This software is part of the SBCL system. See the README file for
10 ;;;; more information.
11 ;;;;
12 ;;;; This software is derived from the CMU CL system, which was
13 ;;;; written at Carnegie Mellon University and released into the
14 ;;;; public domain. The software is in the public domain and is
15 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
16 ;;;; files for more information.
17
18 ;;; TO DO: Might it be possible to increase the efficiency of CMU CL's garbage
19 ;;; collection on my large (256Mb) machine by doing larger incremental GC steps
20 ;;; than the default 2 Mb of CMU CL 2.4.9? A quick test 19990729, setting this
21 ;;; to 5E6 showed no significant improvement, but it's possible that more
22 ;;; cleverness might help..
23 ;#+cmu (setf ext:*bytes-consed-between-gcs* (* 5 (expt 10 6)))
24
25 ;;; FIXME: I'm now inclined to make all the bootstrap stuff run in CL-USER
26 ;;; instead of SB-COLD. If I do so, I should first take care to
27 ;;; UNINTERN any old stuff in CL-USER, since ANSI says (11.1.2.2, "The
28 ;;; COMMON-LISP-USER Package") that CL-USER can have arbitrary symbols in
29 ;;; it. (And of course I should set the USE list to only CL.)
30 (defpackage "SB-COLD" (:use "CL"))
31 (in-package "SB-COLD")
32
33 ;;; prefix for source filename stems when cross-compiling
34 (defvar *src-prefix* "src/")
35 ;;; (We don't bother to specify the source suffix here because ".lisp" is such
36 ;;; a good default value that we never have to specify it explicitly.)
37
38 ;;; prefixes for filename stems when cross-compiling. These are quite arbitrary
39 ;;; (although of course they shouldn't collide with anything we don't want to
40 ;;; write over). In particular, they can be either relative path names (e.g.
41 ;;; "host-objects/" or absolute pathnames (e.g. "/tmp/sbcl-xc-host-objects/").
42 ;;;
43 ;;; The cross-compilation process will force the creation of these directories
44 ;;; by executing CL:ENSURE-DIRECTORIES-EXIST (on the host Common Lisp).
45 (defvar *host-obj-prefix*)
46 (defvar *target-obj-prefix*)
47
48 ;;; suffixes for filename stems when cross-compiling. Everything should work
49 ;;; fine for any arbitrary string values here. With more work maybe we
50 ;;; could cause these automatically to become the traditional extensions for
51 ;;; whatever host and target architectures (e.g. ".x86f" or ".axpf") we're
52 ;;; currently doing. That would make it easier for a human looking at the
53 ;;; temporary files to figure out what they're for, but it's not necessary for
54 ;;; the compilation process to work, so we haven't bothered.
55 (defvar *host-obj-suffix* ".lisp-obj")
56 (defvar *target-obj-suffix* ".lisp-obj")
57
58 ;;; a function of one functional argument, which calls its functional argument
59 ;;; in an environment suitable for compiling the target. (This environment
60 ;;; includes e.g. a suitable *FEATURES* value.)
61 (defvar *in-target-compilation-mode-fn*)
62
63 ;;; designator for a function with the same calling convention as
64 ;;; CL:COMPILE-FILE, to be used to translate ordinary Lisp source files into
65 ;;; target object files
66 (defvar *target-compile-file*)
67
68 ;;; designator for a function with the same calling convention as
69 ;;; SB-C:ASSEMBLE-FILE, to be used to translate assembly files into target
70 ;;; object files
71 (defvar *target-assemble-file*)
72 \f
73 ;;;; some tools
74
75 ;;; Take the file named X and make it into a file named Y. Sorta like UNIX, and
76 ;;; unlike Common Lisp's bare RENAME-FILE, we don't allow information
77 ;;; from the original filename to influence the final filename. (The reason
78 ;;; that it's only sorta like UNIX is that in UNIX "mv foo bar/" will work,
79 ;;; but the analogous (RENAME-FILE-A-LA-UNIX "foo" "bar/") should fail.)
80 ;;;
81 ;;; (This is a workaround for the weird behavior of Debian CMU CL 2.4.6, where
82 ;;; (RENAME-FILE "dir/x" "dir/y") tries to create a file called "dir/dir/y".
83 ;;; If that behavior goes away, then we should be able to get rid of this
84 ;;; function and use plain RENAME-FILE in the COMPILE-STEM function
85 ;;; above. -- WHN 19990321
86 (defun rename-file-a-la-unix (x y)
87   (rename-file x
88                ;; (Note that the TRUENAME expression here is lifted from an
89                ;; example in the ANSI spec for TRUENAME.)
90                (with-open-file (stream y :direction :output)
91                  (close stream)
92                  ;; From the ANSI spec: "In this case, the file is closed
93                  ;; when the truename is tried, so the truename
94                  ;; information is reliable."
95                  (truename stream))))
96 (compile 'rename-file-a-la-unix)
97
98 ;;; a wrapper for compilation/assembly, used mostly to centralize
99 ;;; the procedure for finding full filenames from "stems"
100 ;;;
101 ;;; Compile the source file whose basic name is STEM, using some
102 ;;; standard-for-the-SBCL-build-process procedures to generate the full
103 ;;; pathnames of source file and object file. Return the pathname of the object
104 ;;; file for STEM. Several keyword arguments are accepted:
105 ;;;   SRC-PREFIX, SRC-SUFFIX =
106 ;;; strings to be concatenated to STEM to produce source filename
107 ;;;   OBJ-PREFIX, OBJ-SUFFIX =
108 ;;; strings to be concatenated to STEM to produce object filename
109 ;;;   TMP-OBJ-SUFFIX-SUFFIX
110 ;;; string to be appended to the name of an object file to produce the
111 ;;; name of a temporary object file
112 ;;;   COMPILE-FILE, IGNORE-FAILURE-P =
113 ;;; COMPILE-FILE is a function to use for compiling the file (with the
114 ;;; same calling conventions as ANSI CL:COMPILE-FILE). If the third
115 ;;; return value (FAILURE-P) of this function is true, a continuable
116 ;;; error will be signalled, unless IGNORE-FAILURE-P is set, in which
117 ;;; case only a warning will be signalled.
118 (defun compile-stem (stem
119                      &key
120                      (obj-prefix "")
121                      (obj-suffix (error "missing OBJ-SUFFIX"))
122                      (tmp-obj-suffix-suffix "-tmp")
123                      (src-prefix "")
124                      (src-suffix ".lisp")
125                      (compile-file #'compile-file)
126                      ignore-failure-p)
127
128  (let* (;; KLUDGE: Note that this CONCATENATE 'STRING stuff is not The Common
129         ;; Lisp Way, although it works just fine for common UNIX environments.
130         ;; Should it come to pass that the system is ported to environments
131         ;; where version numbers and so forth become an issue, it might become
132         ;; urgent to rewrite this using the fancy Common Lisp PATHNAME
133         ;; machinery instead of just using strings. In the absence of such a
134         ;; port, it might or might be a good idea to do the rewrite.
135         ;; -- WHN 19990815
136         (src (concatenate 'string src-prefix stem src-suffix))
137         (obj (concatenate 'string obj-prefix stem obj-suffix))
138         (tmp-obj (concatenate 'string obj tmp-obj-suffix-suffix)))
139
140    (ensure-directories-exist obj :verbose t)
141
142    ;; We're about to set about building a new object file. First, we
143    ;; delete any preexisting object file in order to avoid confusing
144    ;; ourselves later should we happen to bail out of compilation with an
145    ;; error.
146    (when (probe-file obj)
147      (delete-file obj))
148
149    ;; Work around a bug in CLISP 1999-01-08 #'COMPILE-FILE: CLISP mangles
150    ;; relative pathnames passed as :OUTPUT-FILE arguments, but works OK
151    ;; with absolute pathnames.
152    #+clisp
153    (setf tmp-obj
154          ;; (Note that this idiom is taken from the ANSI documentation
155          ;; for TRUENAME.)
156          (with-open-file (stream tmp-obj :direction :output)
157            (close stream)
158            (truename stream)))
159
160    ;; Try to use the compiler to generate a new temporary object file.
161    (multiple-value-bind (output-truename warnings-p failure-p)
162        (funcall compile-file src :output-file tmp-obj)
163      (declare (ignore warnings-p))
164      (cond ((not output-truename)
165             (error "couldn't compile ~S" src))
166            (failure-p
167             (if ignore-failure-p
168                 (warn "ignoring FAILURE-P return value from compilation of ~S"
169                       src)
170                 (unwind-protect
171                     (progn
172                       ;; FIXME: This should have another option, redoing
173                       ;; compilation.
174                       (cerror "Continue, using possibly-bogus ~S."
175                               "FAILURE-P was set when creating ~S."
176                               obj)
177                       (setf failure-p nil))
178                   ;; Don't leave failed object files lying around.
179                   (when (and failure-p (probe-file tmp-obj))
180                     (delete-file tmp-obj)
181                     (format t "~&deleted ~S~%" tmp-obj)))))
182            ;; Otherwise: success, just fall through.
183            (t nil)))
184
185    ;; If we get to here, compilation succeeded, so it's OK to rename the
186    ;; temporary output file to the permanent object file.
187    (rename-file-a-la-unix tmp-obj obj)
188
189    ;; nice friendly traditional return value
190    (pathname obj)))
191 (compile 'compile-stem)
192
193 ;;; basic tool for building other tools
194 #+nil
195 (defun tool-cload-stem (stem)
196   (load (compile-stem stem
197                       :src-prefix *src-prefix*
198                       :obj-prefix *host-obj-prefix*
199                       :obj-suffix *host-obj-suffix*
200                       :compile-file #'compile-file))
201   (values))
202 #+nil (compile 'tool-cload-stem)
203
204 ;;; other miscellaneous tools
205 (load "src/cold/read-from-file.lisp")
206 (load "src/cold/rename-package-carefully.lisp")
207 (load "src/cold/with-stuff.lisp")
208
209 ;;; Try to minimize/conceal any non-standardness of the host Common Lisp.
210 (load "src/cold/ansify.lisp")
211 \f
212 ;;;; special read-macros for building the cold system (and even for
213 ;;;; building some of our tools for building the cold system)
214
215 (load "src/cold/shebang.lisp")
216
217 ;;; When cross-compiling, the *FEATURES* set for the target Lisp is
218 ;;; not in general the same as the *FEATURES* set for the host Lisp.
219 ;;; In order to refer to target features specifically, we refer to
220 ;;; *SHEBANG-FEATURES* instead of *FEATURES*, and use the #!+ and #!-
221 ;;; readmacros instead of the ordinary #+ and #- readmacros.
222 (setf *shebang-features*
223       (append (read-from-file "base-target-features.lisp-expr")
224               (read-from-file "local-target-features.lisp-expr")))
225 \f
226 ;;;; cold-init-related PACKAGE and SYMBOL tools
227
228 ;;; Once we're done with possibly ANSIfying the COMMON-LISP package,
229 ;;; it's probably a mistake if we change it (beyond changing the
230 ;;; values of special variables such as *** and +, anyway). Set up
231 ;;; machinery to warn us when/if we change it.
232 ;;;
233 ;;; FIXME: All this machinery should probably be conditional on
234 ;;; #!+SB-SHOW, i.e. we should be able to wrap #!+SB-SHOW around both
235 ;;; the LOAD and the DEFVAR here. 
236 (load "src/cold/snapshot.lisp")
237 (defvar *cl-snapshot* (take-snapshot "COMMON-LISP"))
238 \f
239 ;;;; master list of source files and their properties
240
241 ;;; flags which can be used to describe properties of source files
242 (defparameter
243   *expected-stem-flags*
244   '(;; meaning: This file is not to be compiled when building the
245     ;; cross-compiler which runs on the host ANSI Lisp.
246     :not-host
247     ;; meaning: This file is not to be compiled as part of the target
248     ;; SBCL.
249     :not-target
250     ;; meaning: This file is to be processed with the SBCL assembler,
251     ;; not COMPILE-FILE. (Note that this doesn't make sense unless
252     ;; :NOT-HOST is also set, since the SBCL assembler doesn't exist
253     ;; while the cross-compiler is being built in the host ANSI Lisp.)
254     :assem
255     ;; meaning: The COMPILE-STEM keyword argument called
256     ;; IGNORE-FAILURE-P should be true. (This is a KLUDGE: I'd like to
257     ;; get rid of it. For now, it exists so that compilation can
258     ;; proceed through the legacy warnings in
259     ;; src/compiler/x86/array.lisp, which I've never figured out but
260     ;; which were apparently acceptable in CMU CL. Eventually, it
261     ;; would be great to just get rid of all warnings and remove
262     ;; support for this flag. -- WHN 19990323)
263     :ignore-failure-p))
264
265 (defparameter *stems-and-flags* (read-from-file "stems-and-flags.lisp-expr"))
266
267 (defmacro for-stems-and-flags ((stem flags) &body body)
268   (let ((stem-and-flags (gensym "STEM-AND-FLAGS-")))
269     `(dolist (,stem-and-flags *stems-and-flags*)
270        (let ((,stem (first ,stem-and-flags))
271              (,flags (rest ,stem-and-flags)))
272          ,@body))))
273
274 ;;; Check for stupid typos in FLAGS list keywords.
275 (let ((stems (make-hash-table :test #'equal)))
276   (for-stems-and-flags (stem flags)
277     (if (gethash stem stems)
278       (error "duplicate stem ~S in stems-and-flags data" stem)
279       (setf (gethash stem stems) t))
280     (let ((set-difference (set-difference flags *expected-stem-flags*)))
281       (when set-difference
282         (error "found unexpected flag(s) in *STEMS-AND-FLAGS*: ~S"
283                set-difference)))))
284 \f
285 ;;;; compiling SBCL sources to create the cross-compiler
286
287 ;;; Execute function FN in an environment appropriate for compiling the
288 ;;; cross-compiler's source code in the cross-compilation host.
289 (defun in-host-compilation-mode (fn)
290   (let ((*features* (cons :sb-xc-host *features*)))
291     (with-additional-nickname ("SB-XC" "SB!XC")
292       (funcall fn))))
293 (compile 'in-host-compilation-mode)
294
295 ;;; Process a file as source code for the cross-compiler, compiling it
296 ;;; (if necessary) in the appropriate environment, then loading it
297 ;;; into the cross-compilation host Common lisp.
298 (defun host-cload-stem (stem &key ignore-failure-p)
299   (load (in-host-compilation-mode
300           (lambda ()
301             (compile-stem stem
302                           :src-prefix *src-prefix*
303                           :obj-prefix *host-obj-prefix*
304                           :obj-suffix *host-obj-suffix*
305                           :compile-file #'cl:compile-file
306                           :ignore-failure-p ignore-failure-p)))))
307 (compile 'host-cload-stem)
308
309 ;;; Like HOST-CLOAD-STEM, except that we don't bother to compile.
310 (defun host-load-stem (stem &key ignore-failure-p)
311   (declare (ignore ignore-failure-p)) ; (It's only relevant when
312   ;; compiling.) KLUDGE: It's untidy to have the knowledge of how to
313   ;; construct complete filenames from stems in here as well as in
314   ;; COMPILE-STEM. It should probably be factored out somehow. -- WHN
315   ;; 19990815
316   (load (concatenate 'simple-string *host-obj-prefix* stem *host-obj-suffix*)))
317 (compile 'host-load-stem)
318 \f
319 ;;;; compiling SBCL sources to create object files which will be used
320 ;;;; to create the target SBCL .core file
321
322 ;;; Run the cross-compiler on a file in the source directory tree to
323 ;;; produce a corresponding file in the target object directory tree.
324 (defun target-compile-stem (stem &key assem-p ignore-failure-p)
325   (funcall *in-target-compilation-mode-fn*
326            (lambda ()
327              (compile-stem stem
328                            :src-prefix *src-prefix*
329                            :obj-prefix *target-obj-prefix*
330                            :obj-suffix *target-obj-suffix*
331                            :ignore-failure-p ignore-failure-p
332                            :compile-file (if assem-p
333                                              *target-assemble-file*
334                                              *target-compile-file*)))))
335 (compile 'target-compile-stem)
336
337 ;;; (This function is not used by the build process, but is intended
338 ;;; for interactive use when experimenting with the system. It runs
339 ;;; the cross-compiler on test files with arbitrary filenames, not
340 ;;; necessarily in the source tree, e.g. in "/tmp/".)
341 (defun target-compile-file (filename)
342   (funcall *in-target-compilation-mode-fn*
343            (lambda ()
344              (funcall *target-compile-file* filename))))
345 (compile 'target-compile-file)