contrib/toolbar.lisp (clock): Add a clock module.
[clfswm.git] / contrib / asdf.lisp
blob1518e38e8caa95a48b3a496ba36cac6453681775
1 ;;; -*- mode: common-lisp; package: asdf; -*-
2 ;;; This is ASDF: Another System Definition Facility.
3 ;;;
4 ;;; Feedback, bug reports, and patches are all welcome:
5 ;;; please mail to <asdf-devel@common-lisp.net>.
6 ;;; Note first that the canonical source for ASDF is presently
7 ;;; <URL:http://common-lisp.net/project/asdf/>.
8 ;;;
9 ;;; If you obtained this copy from anywhere else, and you experience
10 ;;; trouble using it, or find bugs, you may want to check at the
11 ;;; location above for a more recent version (and for documentation
12 ;;; and test files, if your copy came without them) before reporting
13 ;;; bugs. There are usually two "supported" revisions - the git HEAD
14 ;;; is the latest development version, whereas the revision tagged
15 ;;; RELEASE may be slightly older but is considered `stable'
17 ;;; -- LICENSE START
18 ;;; (This is the MIT / X Consortium license as taken from
19 ;;; http://www.opensource.org/licenses/mit-license.html on or about
20 ;;; Monday; July 13, 2009)
21 ;;;
22 ;;; Copyright (c) 2001-2010 Daniel Barlow and contributors
23 ;;;
24 ;;; Permission is hereby granted, free of charge, to any person obtaining
25 ;;; a copy of this software and associated documentation files (the
26 ;;; "Software"), to deal in the Software without restriction, including
27 ;;; without limitation the rights to use, copy, modify, merge, publish,
28 ;;; distribute, sublicense, and/or sell copies of the Software, and to
29 ;;; permit persons to whom the Software is furnished to do so, subject to
30 ;;; the following conditions:
31 ;;;
32 ;;; The above copyright notice and this permission notice shall be
33 ;;; included in all copies or substantial portions of the Software.
34 ;;;
35 ;;; THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
36 ;;; EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
37 ;;; MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
38 ;;; NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
39 ;;; LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION
40 ;;; OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION
41 ;;; WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
42 ;;;
43 ;;; -- LICENSE END
45 ;;; The problem with writing a defsystem replacement is bootstrapping:
46 ;;; we can't use defsystem to compile it. Hence, all in one file.
48 #+xcvb (module ())
50 (cl:in-package :cl-user)
52 (eval-when (:compile-toplevel :load-toplevel :execute)
53 ;;; make package if it doesn't exist yet.
54 ;;; DEFPACKAGE may cause errors on discrepancies, so we avoid it.
55 (unless (find-package :asdf)
56 (make-package :asdf :use '(:cl)))
57 ;;; Implementation-dependent tweaks
58 ;; (declaim (optimize (speed 2) (debug 2) (safety 3))) ; NO: rely on the implementation defaults.
59 #+allegro
60 (setf excl::*autoload-package-name-alist*
61 (remove "asdf" excl::*autoload-package-name-alist*
62 :test 'equalp :key 'car))
63 #+ecl (require :cmp))
65 (in-package :asdf)
67 ;;;; Create packages in a way that is compatible with hot-upgrade.
68 ;;;; See https://bugs.launchpad.net/asdf/+bug/485687
69 ;;;; See more at the end of the file.
71 (eval-when (:load-toplevel :compile-toplevel :execute)
72 (defvar *asdf-version* nil)
73 (defvar *upgraded-p* nil)
74 (let* ((asdf-version ;; the 1+ helps the version bumping script discriminate
75 (subseq "VERSION:2.131" (1+ (length "VERSION"))))
76 (existing-asdf (fboundp 'find-system))
77 (existing-version *asdf-version*)
78 (already-there (equal asdf-version existing-version)))
79 (unless (and existing-asdf already-there)
80 (when existing-asdf
81 (format *trace-output*
82 "~&Upgrading ASDF package ~@[from version ~A ~]to version ~A~%"
83 existing-version asdf-version))
84 (labels
85 ((unlink-package (package)
86 (let ((u (find-package package)))
87 (when u
88 (ensure-unintern u
89 (loop :for s :being :each :present-symbol :in u :collect s))
90 (loop :for p :in (package-used-by-list u) :do
91 (unuse-package u p))
92 (delete-package u))))
93 (ensure-exists (name nicknames use)
94 (let ((previous
95 (remove-duplicates
96 (mapcar #'find-package (cons name nicknames))
97 :from-end t)))
98 ;; do away with packages with conflicting (nick)names
99 (map () #'unlink-package (cdr previous))
100 ;; reuse previous package with same name
101 (let ((p (car previous)))
102 (cond
104 (rename-package p name nicknames)
105 (ensure-use p use)
108 (make-package name :nicknames nicknames :use use))))))
109 (find-sym (symbol package)
110 (find-symbol (string symbol) package))
111 (intern* (symbol package)
112 (intern (string symbol) package))
113 (remove-symbol (symbol package)
114 (let ((sym (find-sym symbol package)))
115 (when sym
116 (unexport sym package)
117 (unintern sym package)
118 sym)))
119 (ensure-unintern (package symbols)
120 (loop :with packages = (list-all-packages)
121 :for sym :in symbols
122 :for removed = (remove-symbol sym package)
123 :when removed :do
124 (loop :for p :in packages :do
125 (when (eq removed (find-sym sym p))
126 (unintern removed p)))))
127 (ensure-shadow (package symbols)
128 (shadow symbols package))
129 (ensure-use (package use)
130 (dolist (used (reverse use))
131 (do-external-symbols (sym used)
132 (unless (eq sym (find-sym sym package))
133 (remove-symbol sym package)))
134 (use-package used package)))
135 (ensure-fmakunbound (package symbols)
136 (loop :for name :in symbols
137 :for sym = (find-sym name package)
138 :when sym :do (fmakunbound sym)))
139 (ensure-export (package export)
140 (let ((formerly-exported-symbols nil)
141 (bothly-exported-symbols nil)
142 (newly-exported-symbols nil))
143 (loop :for sym :being :each :external-symbol :in package :do
144 (if (member sym export :test 'string-equal)
145 (push sym bothly-exported-symbols)
146 (push sym formerly-exported-symbols)))
147 (loop :for sym :in export :do
148 (unless (member sym bothly-exported-symbols :test 'string-equal)
149 (push sym newly-exported-symbols)))
150 (loop :for user :in (package-used-by-list package)
151 :for shadowing = (package-shadowing-symbols user) :do
152 (loop :for new :in newly-exported-symbols
153 :for old = (find-sym new user)
154 :when (and old (not (member old shadowing)))
155 :do (unintern old user)))
156 (loop :for x :in newly-exported-symbols :do
157 (export (intern* x package)))))
158 (ensure-package (name &key nicknames use unintern fmakunbound shadow export)
159 (let* ((p (ensure-exists name nicknames use)))
160 (ensure-unintern p unintern)
161 (ensure-shadow p shadow)
162 (ensure-export p export)
163 (ensure-fmakunbound p fmakunbound)
164 p)))
165 (macrolet
166 ((pkgdcl (name &key nicknames use export
167 redefined-functions unintern fmakunbound shadow)
168 `(ensure-package
169 ',name :nicknames ',nicknames :use ',use :export ',export
170 :shadow ',shadow
171 :unintern ',(append #-(or gcl ecl) redefined-functions unintern)
172 :fmakunbound ',(append fmakunbound))))
173 (unlink-package :asdf-utilities)
174 (pkgdcl
175 :asdf
176 :use (:common-lisp)
177 :redefined-functions
178 (#:perform #:explain #:output-files #:operation-done-p
179 #:perform-with-restarts #:component-relative-pathname
180 #:system-source-file #:operate #:find-component #:find-system
181 #:apply-output-translations #:translate-pathname*)
182 :unintern
183 (#:*asdf-revision* #:around #:asdf-method-combination
184 #:split #:make-collector)
185 :fmakunbound
186 (#:system-source-file
187 #:component-relative-pathname #:system-relative-pathname
188 #:process-source-registry
189 #:inherit-source-registry #:process-source-registry-directive)
190 :export
191 (#:defsystem #:oos #:operate #:find-system #:run-shell-command
192 #:system-definition-pathname #:find-component ; miscellaneous
193 #:compile-system #:load-system #:test-system #:clear-system
194 #:compile-op #:load-op #:load-source-op
195 #:test-op
196 #:operation ; operations
197 #:feature ; sort-of operation
198 #:version ; metaphorically sort-of an operation
199 #:version-satisfies
201 #:input-files #:output-files #:output-file #:perform ; operation methods
202 #:operation-done-p #:explain
204 #:component #:source-file
205 #:c-source-file #:cl-source-file #:java-source-file
206 #:static-file
207 #:doc-file
208 #:html-file
209 #:text-file
210 #:source-file-type
211 #:module ; components
212 #:system
213 #:unix-dso
215 #:module-components ; component accessors
216 #:module-components-by-name ; component accessors
217 #:component-pathname
218 #:component-relative-pathname
219 #:component-name
220 #:component-version
221 #:component-parent
222 #:component-property
223 #:component-system
225 #:component-depends-on
227 #:system-description
228 #:system-long-description
229 #:system-author
230 #:system-maintainer
231 #:system-license
232 #:system-licence
233 #:system-source-file
234 #:system-source-directory
235 #:system-relative-pathname
236 #:map-systems
238 #:operation-on-warnings
239 #:operation-on-failure
240 #:component-visited-p
241 ;;#:*component-parent-pathname*
242 #:*system-definition-search-functions*
243 #:*central-registry* ; variables
244 #:*compile-file-warnings-behaviour*
245 #:*compile-file-failure-behaviour*
246 #:*resolve-symlinks*
247 #:*asdf-verbose*
249 #:asdf-version
251 #:operation-error #:compile-failed #:compile-warned #:compile-error
252 #:error-name
253 #:error-pathname
254 #:load-system-definition-error
255 #:error-component #:error-operation
256 #:system-definition-error
257 #:missing-component
258 #:missing-component-of-version
259 #:missing-dependency
260 #:missing-dependency-of-version
261 #:circular-dependency ; errors
262 #:duplicate-names
264 #:try-recompiling
265 #:retry
266 #:accept ; restarts
267 #:coerce-entry-to-directory
268 #:remove-entry-from-registry
270 #:clear-configuration
271 #:initialize-output-translations
272 #:disable-output-translations
273 #:clear-output-translations
274 #:ensure-output-translations
275 #:apply-output-translations
276 #:compile-file*
277 #:compile-file-pathname*
278 #:enable-asdf-binary-locations-compatibility
279 #:*default-source-registries*
280 #:initialize-source-registry
281 #:compute-source-registry
282 #:clear-source-registry
283 #:ensure-source-registry
284 #:process-source-registry
285 #:system-registered-p
286 #:asdf-message
288 ;; Utilities
289 #:absolute-pathname-p
290 ;; #:aif #:it
291 ;; #:appendf
292 #:coerce-name
293 #:directory-pathname-p
294 ;; #:ends-with
295 #:ensure-directory-pathname
296 #:getenv
297 ;; #:get-uid
298 ;; #:length=n-p
299 #:merge-pathnames*
300 #:pathname-directory-pathname
301 #:read-file-forms
302 ;; #:remove-keys
303 ;; #:remove-keyword
304 #:resolve-symlinks
305 #:split-string
306 #:component-name-to-pathname-components
307 #:split-name-type
308 #:truenamize
309 #:while-collecting)))
310 (setf *asdf-version* asdf-version
311 *upgraded-p* (if existing-version
312 (cons existing-version *upgraded-p*)
313 *upgraded-p*))))))
315 ;; More cleanups in case of hot-upgrade. See https://bugs.launchpad.net/asdf/+bug/485687
316 (when *upgraded-p*
317 #+ecl
318 (when (find-class 'compile-op nil)
319 (defmethod update-instance-for-redefined-class :after
320 ((c compile-op) added deleted plist &key)
321 (declare (ignore added deleted))
322 (let ((system-p (getf plist 'system-p)))
323 (when system-p (setf (getf (slot-value c 'flags) :system-p) system-p)))))
324 (when (find-class 'module nil)
325 (eval
326 '(defmethod update-instance-for-redefined-class :after
327 ((m module) added deleted plist &key)
328 (declare (ignorable deleted plist))
329 (when *asdf-verbose* (format *trace-output* "Updating ~A~%" m))
330 (when (member 'components-by-name added)
331 (compute-module-components-by-name m))))))
333 ;;;; -------------------------------------------------------------------------
334 ;;;; User-visible parameters
335 ;;;;
336 (defun asdf-version ()
337 "Exported interface to the version of ASDF currently installed. A string.
338 You can compare this string with e.g.:
339 (ASDF:VERSION-SATISFIES (ASDF:ASDF-VERSION) \"2.000\")."
340 *asdf-version*)
342 (defvar *resolve-symlinks* t
343 "Determine whether or not ASDF resolves symlinks when defining systems.
345 Defaults to T.")
347 (defvar *compile-file-warnings-behaviour*
348 (or #+clisp :ignore :warn)
349 "How should ASDF react if it encounters a warning when compiling a file?
350 Valid values are :error, :warn, and :ignore.")
352 (defvar *compile-file-failure-behaviour*
353 (or #+sbcl :error #+clisp :ignore :warn)
354 "How should ASDF react if it encounters a failure (per the ANSI spec of COMPILE-FILE)
355 when compiling a file? Valid values are :error, :warn, and :ignore.
356 Note that ASDF ALWAYS raises an error if it fails to create an output file when compiling.")
358 (defvar *verbose-out* nil)
360 (defvar *asdf-verbose* t)
362 (defparameter +asdf-methods+
363 '(perform-with-restarts perform explain output-files operation-done-p))
365 #+allegro
366 (eval-when (:compile-toplevel :execute)
367 (defparameter *acl-warn-save*
368 (when (boundp 'excl:*warn-on-nested-reader-conditionals*)
369 excl:*warn-on-nested-reader-conditionals*))
370 (when (boundp 'excl:*warn-on-nested-reader-conditionals*)
371 (setf excl:*warn-on-nested-reader-conditionals* nil)))
373 ;;;; -------------------------------------------------------------------------
374 ;;;; ASDF Interface, in terms of generic functions.
375 (macrolet
376 ((defdef (def* def)
377 `(defmacro ,def* (name formals &rest rest)
378 `(progn
379 #+(or ecl gcl) (fmakunbound ',name)
380 ,(when (and #+ecl (symbolp name))
381 `(declaim (notinline ,name))) ; fails for setf functions on ecl
382 (,',def ,name ,formals ,@rest)))))
383 (defdef defgeneric* defgeneric)
384 (defdef defun* defun))
386 (defgeneric* find-system (system &optional error-p))
387 (defgeneric* perform-with-restarts (operation component))
388 (defgeneric* perform (operation component))
389 (defgeneric* operation-done-p (operation component))
390 (defgeneric* explain (operation component))
391 (defgeneric* output-files (operation component))
392 (defgeneric* input-files (operation component))
393 (defgeneric* component-operation-time (operation component))
394 (defgeneric* operation-description (operation component)
395 (:documentation "returns a phrase that describes performing this operation
396 on this component, e.g. \"loading /a/b/c\".
397 You can put together sentences using this phrase."))
399 (defgeneric* system-source-file (system)
400 (:documentation "Return the source file in which system is defined."))
402 (defgeneric* component-system (component)
403 (:documentation "Find the top-level system containing COMPONENT"))
405 (defgeneric* component-pathname (component)
406 (:documentation "Extracts the pathname applicable for a particular component."))
408 (defgeneric* component-relative-pathname (component)
409 (:documentation "Returns a pathname for the component argument intended to be
410 interpreted relative to the pathname of that component's parent.
411 Despite the function's name, the return value may be an absolute
412 pathname, because an absolute pathname may be interpreted relative to
413 another pathname in a degenerate way."))
415 (defgeneric* component-property (component property))
417 (defgeneric* (setf component-property) (new-value component property))
419 (defgeneric* version-satisfies (component version))
421 (defgeneric* find-component (base path)
422 (:documentation "Finds the component with PATH starting from BASE module;
423 if BASE is nil, then the component is assumed to be a system."))
425 (defgeneric* source-file-type (component system))
427 (defgeneric* operation-ancestor (operation)
428 (:documentation
429 "Recursively chase the operation's parent pointer until we get to
430 the head of the tree"))
432 (defgeneric* component-visited-p (operation component)
433 (:documentation "Returns the value stored by a call to
434 VISIT-COMPONENT, if that has been called, otherwise NIL.
435 This value stored will be a cons cell, the first element
436 of which is a computed key, so not interesting. The
437 CDR wil be the DATA value stored by VISIT-COMPONENT; recover
438 it as (cdr (component-visited-p op c)).
439 In the current form of ASDF, the DATA value retrieved is
440 effectively a boolean, indicating whether some operations are
441 to be performed in order to do OPERATION X COMPONENT. If the
442 data value is NIL, the combination had been explored, but no
443 operations needed to be performed."))
445 (defgeneric* visit-component (operation component data)
446 (:documentation "Record DATA as being associated with OPERATION
447 and COMPONENT. This is a side-effecting function: the association
448 will be recorded on the ROOT OPERATION \(OPERATION-ANCESTOR of the
449 OPERATION\).
450 No evidence that DATA is ever interesting, beyond just being
451 non-NIL. Using the data field is probably very risky; if there is
452 already a record for OPERATION X COMPONENT, DATA will be quietly
453 discarded instead of recorded.
454 Starting with 2.006, TRAVERSE will store an integer in data,
455 so that nodes can be sorted in decreasing order of traversal."))
458 (defgeneric* (setf visiting-component) (new-value operation component))
460 (defgeneric* component-visiting-p (operation component))
462 (defgeneric* component-depends-on (operation component)
463 (:documentation
464 "Returns a list of dependencies needed by the component to perform
465 the operation. A dependency has one of the following forms:
467 (<operation> <component>*), where <operation> is a class
468 designator and each <component> is a component
469 designator, which means that the component depends on
470 <operation> having been performed on each <component>; or
472 (FEATURE <feature>), which means that the component depends
473 on <feature>'s presence in *FEATURES*.
475 Methods specialized on subclasses of existing component types
476 should usually append the results of CALL-NEXT-METHOD to the
477 list."))
479 (defgeneric* component-self-dependencies (operation component))
481 (defgeneric* traverse (operation component)
482 (:documentation
483 "Generate and return a plan for performing OPERATION on COMPONENT.
485 The plan returned is a list of dotted-pairs. Each pair is the CONS
486 of ASDF operation object and a COMPONENT object. The pairs will be
487 processed in order by OPERATE."))
490 ;;;; -------------------------------------------------------------------------
491 ;;;; General Purpose Utilities
493 (defmacro while-collecting ((&rest collectors) &body body)
494 "COLLECTORS should be a list of names for collections. A collector
495 defines a function that, when applied to an argument inside BODY, will
496 add its argument to the corresponding collection. Returns multiple values,
497 a list for each collection, in order.
498 E.g.,
499 \(while-collecting \(foo bar\)
500 \(dolist \(x '\(\(a 1\) \(b 2\) \(c 3\)\)\)
501 \(foo \(first x\)\)
502 \(bar \(second x\)\)\)\)
503 Returns two values: \(A B C\) and \(1 2 3\)."
504 (let ((vars (mapcar #'(lambda (x) (gensym (symbol-name x))) collectors))
505 (initial-values (mapcar (constantly nil) collectors)))
506 `(let ,(mapcar #'list vars initial-values)
507 (flet ,(mapcar #'(lambda (c v) `(,c (x) (push x ,v) (values))) collectors vars)
508 ,@body
509 (values ,@(mapcar #'(lambda (v) `(reverse ,v)) vars))))))
511 (defmacro aif (test then &optional else)
512 `(let ((it ,test)) (if it ,then ,else)))
514 (defun* pathname-directory-pathname (pathname)
515 "Returns a new pathname with same HOST, DEVICE, DIRECTORY as PATHNAME,
516 and NIL NAME, TYPE and VERSION components"
517 (when pathname
518 (make-pathname :name nil :type nil :version nil :defaults pathname)))
520 (defun* merge-pathnames* (specified &optional (defaults *default-pathname-defaults*))
521 "MERGE-PATHNAMES* is like MERGE-PATHNAMES except that if the SPECIFIED pathname
522 does not have an absolute directory, then the HOST and DEVICE come from the DEFAULTS.
523 Also, if either argument is NIL, then the other argument is returned unmodified."
524 (when (null specified) (return-from merge-pathnames* defaults))
525 (when (null defaults) (return-from merge-pathnames* specified))
526 (let* ((specified (pathname specified))
527 (defaults (pathname defaults))
528 (directory (pathname-directory specified))
529 #-(or sbcl cmu) (directory (if (stringp directory) `(:absolute ,directory) directory))
530 (name (or (pathname-name specified) (pathname-name defaults)))
531 (type (or (pathname-type specified) (pathname-type defaults)))
532 (version (or (pathname-version specified) (pathname-version defaults))))
533 (labels ((ununspecific (x)
534 (if (eq x :unspecific) nil x))
535 (unspecific-handler (p)
536 (if (typep p 'logical-pathname) #'ununspecific #'identity)))
537 (multiple-value-bind (host device directory unspecific-handler)
538 (#-gcl ecase #+gcl case (first directory)
539 ((nil)
540 (values (pathname-host defaults)
541 (pathname-device defaults)
542 (pathname-directory defaults)
543 (unspecific-handler defaults)))
544 ((:absolute)
545 (values (pathname-host specified)
546 (pathname-device specified)
547 directory
548 (unspecific-handler specified)))
549 ((:relative)
550 (values (pathname-host defaults)
551 (pathname-device defaults)
552 (if (pathname-directory defaults)
553 (append (pathname-directory defaults) (cdr directory))
554 directory)
555 (unspecific-handler defaults)))
556 #+gcl
558 (assert (stringp (first directory)))
559 (values (pathname-host defaults)
560 (pathname-device defaults)
561 (append (pathname-directory defaults) directory)
562 (unspecific-handler defaults))))
563 (make-pathname :host host :device device :directory directory
564 :name (funcall unspecific-handler name)
565 :type (funcall unspecific-handler type)
566 :version (funcall unspecific-handler version))))))
568 (define-modify-macro appendf (&rest args)
569 append "Append onto list") ;; only to be used on short lists.
571 (define-modify-macro orf (&rest args)
572 or "or a flag")
574 (defun* first-char (s)
575 (and (stringp s) (plusp (length s)) (char s 0)))
577 (defun* last-char (s)
578 (and (stringp s) (plusp (length s)) (char s (1- (length s)))))
580 (defun* asdf-message (format-string &rest format-args)
581 (declare (dynamic-extent format-args))
582 (apply #'format *verbose-out* format-string format-args))
584 (defun* split-string (string &key max (separator '(#\Space #\Tab)))
585 "Split STRING into a list of components separated by
586 any of the characters in the sequence SEPARATOR.
587 If MAX is specified, then no more than max(1,MAX) components will be returned,
588 starting the separation from the end, e.g. when called with arguments
589 \"a.b.c.d.e\" :max 3 :separator \".\" it will return (\"a.b.c\" \"d\" \"e\")."
590 (block nil
591 (let ((list nil) (words 0) (end (length string)))
592 (flet ((separatorp (char) (find char separator))
593 (done () (return (cons (subseq string 0 end) list))))
594 (loop
595 :for start = (if (and max (>= words (1- max)))
596 (done)
597 (position-if #'separatorp string :end end :from-end t)) :do
598 (when (null start)
599 (done))
600 (push (subseq string (1+ start) end) list)
601 (incf words)
602 (setf end start))))))
604 (defun* split-name-type (filename)
605 (let ((unspecific
606 ;; Giving :unspecific as argument to make-pathname is not portable.
607 ;; See CLHS make-pathname and 19.2.2.2.3.
608 ;; We only use it on implementations that support it.
609 (or #+(or ccl ecl gcl lispworks sbcl) :unspecific)))
610 (destructuring-bind (name &optional (type unspecific))
611 (split-string filename :max 2 :separator ".")
612 (if (equal name "")
613 (values filename unspecific)
614 (values name type)))))
616 (defun* component-name-to-pathname-components (s &optional force-directory)
617 "Splits the path string S, returning three values:
618 A flag that is either :absolute or :relative, indicating
619 how the rest of the values are to be interpreted.
620 A directory path --- a list of strings, suitable for
621 use with MAKE-PATHNAME when prepended with the flag
622 value.
623 A filename with type extension, possibly NIL in the
624 case of a directory pathname.
625 FORCE-DIRECTORY forces S to be interpreted as a directory
626 pathname \(third return value will be NIL, final component
627 of S will be treated as part of the directory path.
629 The intention of this function is to support structured component names,
630 e.g., \(:file \"foo/bar\"\), which will be unpacked to relative
631 pathnames."
632 (check-type s string)
633 (let* ((components (split-string s :separator "/"))
634 (last-comp (car (last components))))
635 (multiple-value-bind (relative components)
636 (if (equal (first components) "")
637 (if (equal (first-char s) #\/)
638 (values :absolute (cdr components))
639 (values :relative nil))
640 (values :relative components))
641 (setf components (remove "" components :test #'equal))
642 (cond
643 ((equal last-comp "")
644 (values relative components nil)) ; "" already removed
645 (force-directory
646 (values relative components nil))
648 (values relative (butlast components) last-comp))))))
650 (defun* remove-keys (key-names args)
651 (loop :for (name val) :on args :by #'cddr
652 :unless (member (symbol-name name) key-names
653 :key #'symbol-name :test 'equal)
654 :append (list name val)))
656 (defun* remove-keyword (key args)
657 (loop :for (k v) :on args :by #'cddr
658 :unless (eq k key)
659 :append (list k v)))
661 (defun* getenv (x)
662 (#+abcl ext:getenv
663 #+allegro sys:getenv
664 #+clisp ext:getenv
665 #+clozure ccl:getenv
666 #+(or cmu scl) (lambda (x) (cdr (assoc x ext:*environment-list* :test #'string=)))
667 #+ecl si:getenv
668 #+gcl system:getenv
669 #+lispworks lispworks:environment-variable
670 #+sbcl sb-ext:posix-getenv
673 (defun* directory-pathname-p (pathname)
674 "Does PATHNAME represent a directory?
676 A directory-pathname is a pathname _without_ a filename. The three
677 ways that the filename components can be missing are for it to be NIL,
678 :UNSPECIFIC or the empty string.
680 Note that this does _not_ check to see that PATHNAME points to an
681 actually-existing directory."
682 (flet ((check-one (x)
683 (member x '(nil :unspecific "") :test 'equal)))
684 (and (check-one (pathname-name pathname))
685 (check-one (pathname-type pathname))
686 t)))
688 (defun* ensure-directory-pathname (pathspec)
689 "Converts the non-wild pathname designator PATHSPEC to directory form."
690 (cond
691 ((stringp pathspec)
692 (ensure-directory-pathname (pathname pathspec)))
693 ((not (pathnamep pathspec))
694 (error "Invalid pathname designator ~S" pathspec))
695 ((wild-pathname-p pathspec)
696 (error "Can't reliably convert wild pathnames."))
697 ((directory-pathname-p pathspec)
698 pathspec)
700 (make-pathname :directory (append (or (pathname-directory pathspec)
701 (list :relative))
702 (list (file-namestring pathspec)))
703 :name nil :type nil :version nil
704 :defaults pathspec))))
706 (defun* absolute-pathname-p (pathspec)
707 (and pathspec (eq :absolute (car (pathname-directory (pathname pathspec))))))
709 (defun* length=n-p (x n) ;is it that (= (length x) n) ?
710 (check-type n (integer 0 *))
711 (loop
712 :for l = x :then (cdr l)
713 :for i :downfrom n :do
714 (cond
715 ((zerop i) (return (null l)))
716 ((not (consp l)) (return nil)))))
718 (defun* ends-with (s suffix)
719 (check-type s string)
720 (check-type suffix string)
721 (let ((start (- (length s) (length suffix))))
722 (and (<= 0 start)
723 (string-equal s suffix :start1 start))))
725 (defun* read-file-forms (file)
726 (with-open-file (in file)
727 (loop :with eof = (list nil)
728 :for form = (read in nil eof)
729 :until (eq form eof)
730 :collect form)))
732 #-(and (or win32 windows mswindows mingw32) (not cygwin))
733 (progn
734 #+ecl #.(cl:and (cl:< ext:+ecl-version-number+ 100601)
735 '(ffi:clines "#include <sys/types.h>" "#include <unistd.h>"))
736 (defun* get-uid ()
737 #+allegro (excl.osi:getuid)
738 #+clisp (loop :for s :in '("posix:uid" "LINUX:getuid")
739 :for f = (ignore-errors (read-from-string s))
740 :when f :return (funcall f))
741 #+(or cmu scl) (unix:unix-getuid)
742 #+ecl #.(cl:if (cl:< ext:+ecl-version-number+ 100601)
743 '(ffi:c-inline () () :int "getuid()" :one-liner t)
744 '(ext::getuid))
745 #+sbcl (sb-unix:unix-getuid)
746 #-(or allegro clisp cmu ecl sbcl scl)
747 (let ((uid-string
748 (with-output-to-string (*verbose-out*)
749 (run-shell-command "id -ur"))))
750 (with-input-from-string (stream uid-string)
751 (read-line stream)
752 (handler-case (parse-integer (read-line stream))
753 (error () (error "Unable to find out user ID")))))))
755 (defun* pathname-root (pathname)
756 (make-pathname :host (pathname-host pathname)
757 :device (pathname-device pathname)
758 :directory '(:absolute)
759 :name nil :type nil :version nil))
761 (defun* probe-file* (p)
762 "when given a pathname P, probes the filesystem for a file or directory
763 with given pathname and if it exists return its truename."
764 (etypecase p
765 (null nil)
766 (string (probe-file* (parse-namestring p)))
767 (pathname (unless (wild-pathname-p p)
768 #.(or #+(or allegro clozure cmu ecl sbcl scl) '(probe-file p)
769 #+clisp (aif (find-symbol (string :probe-pathname) :ext) `(,it p))
770 '(ignore-errors (truename p)))))))
772 (defun* truenamize (p)
773 "Resolve as much of a pathname as possible"
774 (block nil
775 (when (typep p 'logical-pathname) (return p))
776 (let* ((p (merge-pathnames* p))
777 (directory (pathname-directory p)))
778 (when (typep p 'logical-pathname) (return p))
779 (let ((found (probe-file* p)))
780 (when found (return found)))
781 #-(or sbcl cmu) (when (stringp directory) (return p))
782 (when (not (eq :absolute (car directory))) (return p))
783 (let ((sofar (probe-file* (pathname-root p))))
784 (unless sofar (return p))
785 (flet ((solution (directories)
786 (merge-pathnames*
787 (make-pathname :host nil :device nil
788 :directory `(:relative ,@directories)
789 :name (pathname-name p)
790 :type (pathname-type p)
791 :version (pathname-version p))
792 sofar)))
793 (loop :for component :in (cdr directory)
794 :for rest :on (cdr directory)
795 :for more = (probe-file*
796 (merge-pathnames*
797 (make-pathname :directory `(:relative ,component))
798 sofar)) :do
799 (if more
800 (setf sofar more)
801 (return (solution rest)))
802 :finally
803 (return (solution nil))))))))
805 (defun* resolve-symlinks (path)
806 #-allegro (truenamize path)
807 #+allegro (excl:pathname-resolve-symbolic-links path))
809 (defun* default-directory ()
810 (truenamize (pathname-directory-pathname *default-pathname-defaults*)))
812 (defun* lispize-pathname (input-file)
813 (make-pathname :type "lisp" :defaults input-file))
815 (defparameter *wild-path*
816 (make-pathname :directory '(:relative :wild-inferiors)
817 :name :wild :type :wild :version :wild))
819 (defun* wilden (path)
820 (merge-pathnames* *wild-path* path))
822 (defun* directorize-pathname-host-device (pathname)
823 (let* ((root (pathname-root pathname))
824 (wild-root (wilden root))
825 (absolute-pathname (merge-pathnames* pathname root))
826 (foo (make-pathname :directory '(:absolute "FOO") :defaults root))
827 (separator (last-char (namestring foo)))
828 (root-namestring (namestring root))
829 (root-string
830 (substitute-if #\/
831 (lambda (x) (or (eql x #\:)
832 (eql x separator)))
833 root-namestring)))
834 (multiple-value-bind (relative path filename)
835 (component-name-to-pathname-components root-string t)
836 (declare (ignore relative filename))
837 (let ((new-base
838 (make-pathname :defaults root
839 :directory `(:absolute ,@path))))
840 (translate-pathname absolute-pathname wild-root (wilden new-base))))))
842 ;;;; -------------------------------------------------------------------------
843 ;;;; Classes, Conditions
845 (define-condition system-definition-error (error) ()
846 ;; [this use of :report should be redundant, but unfortunately it's not.
847 ;; cmucl's lisp::output-instance prefers the kernel:slot-class-print-function
848 ;; over print-object; this is always conditions::%print-condition for
849 ;; condition objects, which in turn does inheritance of :report options at
850 ;; run-time. fortunately, inheritance means we only need this kludge here in
851 ;; order to fix all conditions that build on it. -- rgr, 28-Jul-02.]
852 #+cmu (:report print-object))
854 (declaim (ftype (function (t) t)
855 format-arguments format-control
856 error-name error-pathname error-condition
857 duplicate-names-name
858 error-component error-operation
859 module-components module-components-by-name
860 circular-dependency-components)
861 (ftype (function (t t) t) (setf module-components-by-name)))
864 (define-condition formatted-system-definition-error (system-definition-error)
865 ((format-control :initarg :format-control :reader format-control)
866 (format-arguments :initarg :format-arguments :reader format-arguments))
867 (:report (lambda (c s)
868 (apply #'format s (format-control c) (format-arguments c)))))
870 (define-condition load-system-definition-error (system-definition-error)
871 ((name :initarg :name :reader error-name)
872 (pathname :initarg :pathname :reader error-pathname)
873 (condition :initarg :condition :reader error-condition))
874 (:report (lambda (c s)
875 (format s "~@<Error while trying to load definition for system ~A from pathname ~A: ~A~@:>"
876 (error-name c) (error-pathname c) (error-condition c)))))
878 (define-condition circular-dependency (system-definition-error)
879 ((components :initarg :components :reader circular-dependency-components))
880 (:report (lambda (c s)
881 (format s "~@<Circular dependency: ~S~@:>" (circular-dependency-components c)))))
883 (define-condition duplicate-names (system-definition-error)
884 ((name :initarg :name :reader duplicate-names-name))
885 (:report (lambda (c s)
886 (format s "~@<Error while defining system: multiple components are given same name ~A~@:>"
887 (duplicate-names-name c)))))
889 (define-condition missing-component (system-definition-error)
890 ((requires :initform "(unnamed)" :reader missing-requires :initarg :requires)
891 (parent :initform nil :reader missing-parent :initarg :parent)))
893 (define-condition missing-component-of-version (missing-component)
894 ((version :initform nil :reader missing-version :initarg :version)))
896 (define-condition missing-dependency (missing-component)
897 ((required-by :initarg :required-by :reader missing-required-by)))
899 (define-condition missing-dependency-of-version (missing-dependency
900 missing-component-of-version)
903 (define-condition operation-error (error)
904 ((component :reader error-component :initarg :component)
905 (operation :reader error-operation :initarg :operation))
906 (:report (lambda (c s)
907 (format s "~@<erred while invoking ~A on ~A~@:>"
908 (error-operation c) (error-component c)))))
909 (define-condition compile-error (operation-error) ())
910 (define-condition compile-failed (compile-error) ())
911 (define-condition compile-warned (compile-error) ())
913 (defclass component ()
914 ((name :accessor component-name :initarg :name :documentation
915 "Component name: designator for a string composed of portable pathname characters")
916 (version :accessor component-version :initarg :version)
917 (in-order-to :initform nil :initarg :in-order-to
918 :accessor component-in-order-to)
919 ;; This one is used by POIU. Maybe in the future by ASDF instead of in-order-to?
920 ;; POIU is a parallel (multi-process build) extension of ASDF. See
921 ;; http://www.cliki.net/poiu
922 (load-dependencies :accessor component-load-dependencies :initform nil)
923 ;; XXX crap name, but it's an official API name!
924 (do-first :initform nil :initarg :do-first
925 :accessor component-do-first)
926 ;; methods defined using the "inline" style inside a defsystem form:
927 ;; need to store them somewhere so we can delete them when the system
928 ;; is re-evaluated
929 (inline-methods :accessor component-inline-methods :initform nil)
930 (parent :initarg :parent :initform nil :reader component-parent)
931 ;; no direct accessor for pathname, we do this as a method to allow
932 ;; it to default in funky ways if not supplied
933 (relative-pathname :initarg :pathname)
934 (absolute-pathname)
935 (operation-times :initform (make-hash-table)
936 :accessor component-operation-times)
937 ;; XXX we should provide some atomic interface for updating the
938 ;; component properties
939 (properties :accessor component-properties :initarg :properties
940 :initform nil)))
942 (defun* component-find-path (component)
943 (reverse
944 (loop :for c = component :then (component-parent c)
945 :while c :collect (component-name c))))
947 (defmethod print-object ((c component) stream)
948 (print-unreadable-object (c stream :type t :identity nil)
949 (format stream "~@<~{~S~^ ~}~@:>" (component-find-path c))))
952 ;;;; methods: conditions
954 (defmethod print-object ((c missing-dependency) s)
955 (format s "~@<~A, required by ~A~@:>"
956 (call-next-method c nil) (missing-required-by c)))
958 (defun* sysdef-error (format &rest arguments)
959 (error 'formatted-system-definition-error :format-control
960 format :format-arguments arguments))
962 ;;;; methods: components
964 (defmethod print-object ((c missing-component) s)
965 (format s "~@<component ~S not found~@[ in ~A~]~@:>"
966 (missing-requires c)
967 (when (missing-parent c)
968 (component-name (missing-parent c)))))
970 (defmethod print-object ((c missing-component-of-version) s)
971 (format s "~@<component ~S does not match version ~A~@[ in ~A~]~@:>"
972 (missing-requires c)
973 (missing-version c)
974 (when (missing-parent c)
975 (component-name (missing-parent c)))))
977 (defmethod component-system ((component component))
978 (aif (component-parent component)
979 (component-system it)
980 component))
982 (defvar *default-component-class* 'cl-source-file)
984 (defun* compute-module-components-by-name (module)
985 (let ((hash (make-hash-table :test 'equal)))
986 (setf (module-components-by-name module) hash)
987 (loop :for c :in (module-components module)
988 :for name = (component-name c)
989 :for previous = (gethash name (module-components-by-name module))
991 (when previous
992 (error 'duplicate-names :name name))
993 :do (setf (gethash name (module-components-by-name module)) c))
994 hash))
996 (defclass module (component)
997 ((components
998 :initform nil
999 :initarg :components
1000 :accessor module-components)
1001 (components-by-name
1002 :accessor module-components-by-name)
1003 ;; What to do if we can't satisfy a dependency of one of this module's
1004 ;; components. This allows a limited form of conditional processing.
1005 (if-component-dep-fails
1006 :initform :fail
1007 :initarg :if-component-dep-fails
1008 :accessor module-if-component-dep-fails)
1009 (default-component-class
1010 :initform *default-component-class*
1011 :initarg :default-component-class
1012 :accessor module-default-component-class)))
1014 (defun* component-parent-pathname (component)
1015 ;; No default anymore (in particular, no *default-pathname-defaults*).
1016 ;; If you force component to have a NULL pathname, you better arrange
1017 ;; for any of its children to explicitly provide a proper absolute pathname
1018 ;; wherever a pathname is actually wanted.
1019 (let ((parent (component-parent component)))
1020 (when parent
1021 (component-pathname parent))))
1023 (defmethod component-pathname ((component component))
1024 (if (slot-boundp component 'absolute-pathname)
1025 (slot-value component 'absolute-pathname)
1026 (let ((pathname
1027 (merge-pathnames*
1028 (component-relative-pathname component)
1029 (pathname-directory-pathname (component-parent-pathname component)))))
1030 (unless (or (null pathname) (absolute-pathname-p pathname))
1031 (error "Invalid relative pathname ~S for component ~S"
1032 pathname (component-find-path component)))
1033 (setf (slot-value component 'absolute-pathname) pathname)
1034 pathname)))
1036 (defmethod component-property ((c component) property)
1037 (cdr (assoc property (slot-value c 'properties) :test #'equal)))
1039 (defmethod (setf component-property) (new-value (c component) property)
1040 (let ((a (assoc property (slot-value c 'properties) :test #'equal)))
1041 (if a
1042 (setf (cdr a) new-value)
1043 (setf (slot-value c 'properties)
1044 (acons property new-value (slot-value c 'properties)))))
1045 new-value)
1047 (defclass system (module)
1048 ((description :accessor system-description :initarg :description)
1049 (long-description
1050 :accessor system-long-description :initarg :long-description)
1051 (author :accessor system-author :initarg :author)
1052 (maintainer :accessor system-maintainer :initarg :maintainer)
1053 (licence :accessor system-licence :initarg :licence
1054 :accessor system-license :initarg :license)
1055 (source-file :reader system-source-file :initarg :source-file
1056 :writer %set-system-source-file)))
1058 ;;;; -------------------------------------------------------------------------
1059 ;;;; version-satisfies
1061 (defmethod version-satisfies ((c component) version)
1062 (unless (and version (slot-boundp c 'version))
1063 (return-from version-satisfies t))
1064 (version-satisfies (component-version c) version))
1066 (defmethod version-satisfies ((cver string) version)
1067 (let ((x (mapcar #'parse-integer
1068 (split-string cver :separator ".")))
1069 (y (mapcar #'parse-integer
1070 (split-string version :separator "."))))
1071 (labels ((bigger (x y)
1072 (cond ((not y) t)
1073 ((not x) nil)
1074 ((> (car x) (car y)) t)
1075 ((= (car x) (car y))
1076 (bigger (cdr x) (cdr y))))))
1077 (and (= (car x) (car y))
1078 (or (not (cdr y)) (bigger (cdr x) (cdr y)))))))
1080 ;;;; -------------------------------------------------------------------------
1081 ;;;; Finding systems
1083 (defun* make-defined-systems-table ()
1084 (make-hash-table :test 'equal))
1086 (defvar *defined-systems* (make-defined-systems-table)
1087 "This is a hash table whose keys are strings, being the
1088 names of the systems, and whose values are pairs, the first
1089 element of which is a universal-time indicating when the
1090 system definition was last updated, and the second element
1091 of which is a system object.")
1093 (defun* coerce-name (name)
1094 (typecase name
1095 (component (component-name name))
1096 (symbol (string-downcase (symbol-name name)))
1097 (string name)
1098 (t (sysdef-error "~@<invalid component designator ~A~@:>" name))))
1100 (defun* system-registered-p (name)
1101 (gethash (coerce-name name) *defined-systems*))
1103 (defun* clear-system (name)
1104 "Clear the entry for a system in the database of systems previously loaded.
1105 Note that this does NOT in any way cause the code of the system to be unloaded."
1106 ;; There is no "unload" operation in Common Lisp, and a general such operation
1107 ;; cannot be portably written, considering how much CL relies on side-effects
1108 ;; of global data structures.
1109 ;; Note that this does a setf gethash instead of a remhash
1110 ;; this way there remains a hint in the *defined-systems* table
1111 ;; that the system was loaded at some point.
1112 (setf (gethash (coerce-name name) *defined-systems*) nil))
1114 (defun* map-systems (fn)
1115 "Apply FN to each defined system.
1117 FN should be a function of one argument. It will be
1118 called with an object of type asdf:system."
1119 (maphash (lambda (_ datum)
1120 (declare (ignore _))
1121 (destructuring-bind (_ . def) datum
1122 (declare (ignore _))
1123 (funcall fn def)))
1124 *defined-systems*))
1126 ;;; for the sake of keeping things reasonably neat, we adopt a
1127 ;;; convention that functions in this list are prefixed SYSDEF-
1129 (defparameter *system-definition-search-functions*
1130 '(sysdef-central-registry-search sysdef-source-registry-search sysdef-find-asdf))
1132 (defun* system-definition-pathname (system)
1133 (let ((system-name (coerce-name system)))
1135 (some (lambda (x) (funcall x system-name))
1136 *system-definition-search-functions*)
1137 (let ((system-pair (system-registered-p system-name)))
1138 (and system-pair
1139 (system-source-file (cdr system-pair)))))))
1141 (defvar *central-registry* nil
1142 "A list of 'system directory designators' ASDF uses to find systems.
1144 A 'system directory designator' is a pathname or an expression
1145 which evaluates to a pathname. For example:
1147 (setf asdf:*central-registry*
1148 (list '*default-pathname-defaults*
1149 #p\"/home/me/cl/systems/\"
1150 #p\"/usr/share/common-lisp/systems/\"))
1152 This is for backward compatibilily.
1153 Going forward, we recommend new users should be using the source-registry.
1156 (defun* probe-asd (name defaults)
1157 (block nil
1158 (when (directory-pathname-p defaults)
1159 (let ((file
1160 (make-pathname
1161 :defaults defaults :version :newest :case :local
1162 :name name
1163 :type "asd")))
1164 (when (probe-file file)
1165 (return file)))
1166 #+(and (or win32 windows mswindows mingw32) (not cygwin) (not clisp))
1167 (let ((shortcut
1168 (make-pathname
1169 :defaults defaults :version :newest :case :local
1170 :name (concatenate 'string name ".asd")
1171 :type "lnk")))
1172 (when (probe-file shortcut)
1173 (let ((target (parse-windows-shortcut shortcut)))
1174 (when target
1175 (return (pathname target)))))))))
1177 (defun* sysdef-central-registry-search (system)
1178 (let ((name (coerce-name system))
1179 (to-remove nil)
1180 (to-replace nil))
1181 (block nil
1182 (unwind-protect
1183 (dolist (dir *central-registry*)
1184 (let ((defaults (eval dir)))
1185 (when defaults
1186 (cond ((directory-pathname-p defaults)
1187 (let ((file (probe-asd name defaults)))
1188 (when file
1189 (return file))))
1191 (restart-case
1192 (let* ((*print-circle* nil)
1193 (message
1194 (format nil
1195 "~@<While searching for system ~S: ~S evaluated to ~S which is not a directory.~@:>"
1196 system dir defaults)))
1197 (error message))
1198 (remove-entry-from-registry ()
1199 :report "Remove entry from *central-registry* and continue"
1200 (push dir to-remove))
1201 (coerce-entry-to-directory ()
1202 :report (lambda (s)
1203 (format s "Coerce entry to ~a, replace ~a and continue."
1204 (ensure-directory-pathname defaults) dir))
1205 (push (cons dir (ensure-directory-pathname defaults)) to-replace))))))))
1206 ;; cleanup
1207 (dolist (dir to-remove)
1208 (setf *central-registry* (remove dir *central-registry*)))
1209 (dolist (pair to-replace)
1210 (let* ((current (car pair))
1211 (new (cdr pair))
1212 (position (position current *central-registry*)))
1213 (setf *central-registry*
1214 (append (subseq *central-registry* 0 position)
1215 (list new)
1216 (subseq *central-registry* (1+ position))))))))))
1218 (defun* make-temporary-package ()
1219 (flet ((try (counter)
1220 (ignore-errors
1221 (make-package (format nil "~A~D" :asdf counter)
1222 :use '(:cl :asdf)))))
1223 (do* ((counter 0 (+ counter 1))
1224 (package (try counter) (try counter)))
1225 (package package))))
1227 (defun* safe-file-write-date (pathname)
1228 ;; If FILE-WRITE-DATE returns NIL, it's possible that
1229 ;; the user or some other agent has deleted an input file.
1230 ;; Also, generated files will not exist at the time planning is done
1231 ;; and calls operation-done-p which calls safe-file-write-date.
1232 ;; So it is very possible that we can't get a valid file-write-date,
1233 ;; and we can survive and we will continue the planning
1234 ;; as if the file were very old.
1235 ;; (or should we treat the case in a different, special way?)
1236 (or (and pathname (probe-file pathname) (file-write-date pathname))
1237 (progn
1238 (when (and pathname *asdf-verbose*)
1239 (warn "Missing FILE-WRITE-DATE for ~S: treating it as zero."
1240 pathname))
1241 0)))
1243 (defmethod find-system (name &optional (error-p t))
1244 (find-system (coerce-name name) error-p))
1246 (defmethod find-system ((name string) &optional (error-p t))
1247 (catch 'find-system
1248 (let* ((in-memory (system-registered-p name))
1249 (on-disk (system-definition-pathname name)))
1250 (when (and on-disk
1251 (or (not in-memory)
1252 (< (car in-memory) (safe-file-write-date on-disk))))
1253 (let ((package (make-temporary-package)))
1254 (unwind-protect
1255 (handler-bind
1256 ((error (lambda (condition)
1257 (error 'load-system-definition-error
1258 :name name :pathname on-disk
1259 :condition condition))))
1260 (let ((*package* package))
1261 (asdf-message
1262 "~&~@<; ~@;loading system definition from ~A into ~A~@:>~%"
1263 on-disk *package*)
1264 (load on-disk)))
1265 (delete-package package))))
1266 (let ((in-memory (system-registered-p name)))
1267 (cond
1268 (in-memory
1269 (when on-disk
1270 (setf (car in-memory) (safe-file-write-date on-disk)))
1271 (cdr in-memory))
1272 (error-p
1273 (error 'missing-component :requires name)))))))
1275 (defun* register-system (name system)
1276 (asdf-message "~&~@<; ~@;registering ~A as ~A~@:>~%" system name)
1277 (setf (gethash (coerce-name name) *defined-systems*)
1278 (cons (get-universal-time) system)))
1280 (defun* find-system-fallback (requested fallback &optional source-file)
1281 (setf fallback (coerce-name fallback)
1282 source-file (or source-file *compile-file-truename* *load-truename*)
1283 requested (coerce-name requested))
1284 (when (equal requested fallback)
1285 (let* ((registered (cdr (gethash fallback *defined-systems*)))
1286 (system (or registered
1287 (make-instance
1288 'system :name fallback
1289 :source-file source-file))))
1290 (unless registered
1291 (register-system fallback system))
1292 (throw 'find-system system))))
1294 (defun* sysdef-find-asdf (name)
1295 (find-system-fallback name "asdf"))
1298 ;;;; -------------------------------------------------------------------------
1299 ;;;; Finding components
1301 (defmethod find-component ((base string) path)
1302 (let ((s (find-system base nil)))
1303 (and s (find-component s path))))
1305 (defmethod find-component ((base symbol) path)
1306 (cond
1307 (base (find-component (coerce-name base) path))
1308 (path (find-component path nil))
1309 (t nil)))
1311 (defmethod find-component ((base cons) path)
1312 (find-component (car base) (cons (cdr base) path)))
1314 (defmethod find-component ((module module) (name string))
1315 (unless (slot-boundp module 'components-by-name) ;; SBCL may miss the u-i-f-r-c method!!!
1316 (compute-module-components-by-name module))
1317 (values (gethash name (module-components-by-name module))))
1319 (defmethod find-component ((component component) (name symbol))
1320 (if name
1321 (find-component component (coerce-name name))
1322 component))
1324 (defmethod find-component ((module module) (name cons))
1325 (find-component (find-component module (car name)) (cdr name)))
1328 ;;; component subclasses
1330 (defclass source-file (component)
1331 ((type :accessor source-file-explicit-type :initarg :type :initform nil)))
1333 (defclass cl-source-file (source-file)
1334 ((type :initform "lisp")))
1335 (defclass c-source-file (source-file)
1336 ((type :initform "c")))
1337 (defclass java-source-file (source-file)
1338 ((type :initform "java")))
1339 (defclass static-file (source-file) ())
1340 (defclass doc-file (static-file) ())
1341 (defclass html-file (doc-file)
1342 ((type :initform "html")))
1344 (defmethod source-file-type ((component module) (s module))
1345 (declare (ignorable component s))
1346 :directory)
1347 (defmethod source-file-type ((component source-file) (s module))
1348 (declare (ignorable s))
1349 (source-file-explicit-type component))
1351 (defun* merge-component-name-type (name &key type defaults)
1352 ;; The defaults are required notably because they provide the default host
1353 ;; to the below make-pathname, which may crucially matter to people using
1354 ;; merge-pathnames with non-default hosts, e.g. for logical-pathnames.
1355 ;; NOTE that the host and device slots will be taken from the defaults,
1356 ;; but that should only matter if you either (a) use absolute pathnames, or
1357 ;; (b) later merge relative pathnames with CL:MERGE-PATHNAMES instead of
1358 ;; ASDF:MERGE-PATHNAMES*
1359 (etypecase name
1360 (pathname
1361 name)
1362 (symbol
1363 (merge-component-name-type (string-downcase name) :type type :defaults defaults))
1364 (string
1365 (multiple-value-bind (relative path filename)
1366 (component-name-to-pathname-components name (eq type :directory))
1367 (multiple-value-bind (name type)
1368 (cond
1369 ((or (eq type :directory) (null filename))
1370 (values nil nil))
1371 (type
1372 (values filename type))
1374 (split-name-type filename)))
1375 (let* ((defaults (pathname (or defaults *default-pathname-defaults*)))
1376 (host (pathname-host defaults))
1377 (device (pathname-device defaults)))
1378 (make-pathname :directory `(,relative ,@path)
1379 :name name :type type
1380 :host host :device device)))))))
1382 (defmethod component-relative-pathname ((component component))
1383 (merge-component-name-type
1384 (or (slot-value component 'relative-pathname)
1385 (component-name component))
1386 :type (source-file-type component (component-system component))
1387 :defaults (component-parent-pathname component)))
1389 ;;;; -------------------------------------------------------------------------
1390 ;;;; Operations
1392 ;;; one of these is instantiated whenever #'operate is called
1394 (defclass operation ()
1396 ;; as of danb's 2003-03-16 commit e0d02781, :force can be:
1397 ;; T to force the inside of existing system,
1398 ;; but not recurse to other systems we depend on.
1399 ;; :ALL (or any other atom) to force all systems
1400 ;; including other systems we depend on.
1401 ;; (SYSTEM1 SYSTEM2 ... SYSTEMN)
1402 ;; to force systems named in a given list
1403 ;; However, but this feature never worked before ASDF 1.700 and is currently cerror'ed out.
1404 (forced :initform nil :initarg :force :accessor operation-forced)
1405 (original-initargs :initform nil :initarg :original-initargs
1406 :accessor operation-original-initargs)
1407 (visited-nodes :initform (make-hash-table :test 'equal) :accessor operation-visited-nodes)
1408 (visiting-nodes :initform (make-hash-table :test 'equal) :accessor operation-visiting-nodes)
1409 (parent :initform nil :initarg :parent :accessor operation-parent)))
1411 (defmethod print-object ((o operation) stream)
1412 (print-unreadable-object (o stream :type t :identity t)
1413 (ignore-errors
1414 (prin1 (operation-original-initargs o) stream))))
1416 (defmethod shared-initialize :after ((operation operation) slot-names
1417 &key force
1418 &allow-other-keys)
1419 (declare (ignorable operation slot-names force))
1420 ;; empty method to disable initarg validity checking
1421 (values))
1423 (defun* node-for (o c)
1424 (cons (class-name (class-of o)) c))
1426 (defmethod operation-ancestor ((operation operation))
1427 (aif (operation-parent operation)
1428 (operation-ancestor it)
1429 operation))
1432 (defun* make-sub-operation (c o dep-c dep-o)
1433 "C is a component, O is an operation, DEP-C is another
1434 component, and DEP-O, confusingly enough, is an operation
1435 class specifier, not an operation."
1436 (let* ((args (copy-list (operation-original-initargs o)))
1437 (force-p (getf args :force)))
1438 ;; note explicit comparison with T: any other non-NIL force value
1439 ;; (e.g. :recursive) will pass through
1440 (cond ((and (null (component-parent c))
1441 (null (component-parent dep-c))
1442 (not (eql c dep-c)))
1443 (when (eql force-p t)
1444 (setf (getf args :force) nil))
1445 (apply #'make-instance dep-o
1446 :parent o
1447 :original-initargs args args))
1448 ((subtypep (type-of o) dep-o)
1451 (apply #'make-instance dep-o
1452 :parent o :original-initargs args args)))))
1455 (defmethod visit-component ((o operation) (c component) data)
1456 (unless (component-visited-p o c)
1457 (setf (gethash (node-for o c)
1458 (operation-visited-nodes (operation-ancestor o)))
1459 (cons t data))))
1461 (defmethod component-visited-p ((o operation) (c component))
1462 (gethash (node-for o c)
1463 (operation-visited-nodes (operation-ancestor o))))
1465 (defmethod (setf visiting-component) (new-value operation component)
1466 ;; MCL complains about unused lexical variables
1467 (declare (ignorable operation component))
1468 new-value)
1470 (defmethod (setf visiting-component) (new-value (o operation) (c component))
1471 (let ((node (node-for o c))
1472 (a (operation-ancestor o)))
1473 (if new-value
1474 (setf (gethash node (operation-visiting-nodes a)) t)
1475 (remhash node (operation-visiting-nodes a)))
1476 new-value))
1478 (defmethod component-visiting-p ((o operation) (c component))
1479 (let ((node (node-for o c)))
1480 (gethash node (operation-visiting-nodes (operation-ancestor o)))))
1482 (defmethod component-depends-on ((op-spec symbol) (c component))
1483 (component-depends-on (make-instance op-spec) c))
1485 (defmethod component-depends-on ((o operation) (c component))
1486 (cdr (assoc (class-name (class-of o))
1487 (component-in-order-to c))))
1489 (defmethod component-self-dependencies ((o operation) (c component))
1490 (let ((all-deps (component-depends-on o c)))
1491 (remove-if-not (lambda (x)
1492 (member (component-name c) (cdr x) :test #'string=))
1493 all-deps)))
1495 (defmethod input-files ((operation operation) (c component))
1496 (let ((parent (component-parent c))
1497 (self-deps (component-self-dependencies operation c)))
1498 (if self-deps
1499 (mapcan (lambda (dep)
1500 (destructuring-bind (op name) dep
1501 (output-files (make-instance op)
1502 (find-component parent name))))
1503 self-deps)
1504 ;; no previous operations needed? I guess we work with the
1505 ;; original source file, then
1506 (list (component-pathname c)))))
1508 (defmethod input-files ((operation operation) (c module))
1509 (declare (ignorable operation c))
1510 nil)
1512 (defmethod component-operation-time (o c)
1513 (gethash (type-of o) (component-operation-times c)))
1515 (defmethod operation-done-p ((o operation) (c component))
1516 (let ((out-files (output-files o c))
1517 (in-files (input-files o c))
1518 (op-time (component-operation-time o c)))
1519 (flet ((earliest-out ()
1520 (reduce #'min (mapcar #'safe-file-write-date out-files)))
1521 (latest-in ()
1522 (reduce #'max (mapcar #'safe-file-write-date in-files))))
1523 (cond
1524 ((and (not in-files) (not out-files))
1525 ;; arbitrary decision: an operation that uses nothing to
1526 ;; produce nothing probably isn't doing much.
1527 ;; e.g. operations on systems, modules that have no immediate action,
1528 ;; but are only meaningful through traversed dependencies
1530 ((not out-files)
1531 ;; an operation without output-files is probably meant
1532 ;; for its side-effects in the current image,
1533 ;; assumed to be idem-potent,
1534 ;; e.g. LOAD-OP or LOAD-SOURCE-OP of some CL-SOURCE-FILE.
1535 (and op-time (>= op-time (latest-in))))
1536 ((not in-files)
1537 ;; an operation without output-files and no input-files
1538 ;; is probably meant for its side-effects on the file-system,
1539 ;; assumed to have to be done everytime.
1540 ;; (I don't think there is any such case in ASDF unless extended)
1541 nil)
1543 ;; an operation with both input and output files is assumed
1544 ;; as computing the latter from the former,
1545 ;; assumed to have been done if the latter are all older
1546 ;; than the former.
1547 ;; e.g. COMPILE-OP of some CL-SOURCE-FILE.
1548 ;; We use >= instead of > to play nice with generated files.
1549 ;; This opens a race condition if an input file is changed
1550 ;; after the output is created but within the same second
1551 ;; of filesystem time; but the same race condition exists
1552 ;; whenever the computation from input to output takes more
1553 ;; than one second of filesystem time (or just crosses the
1554 ;; second). So that's cool.
1555 (and
1556 (every #'probe-file in-files)
1557 (every #'probe-file out-files)
1558 (>= (earliest-out) (latest-in))))))))
1562 ;;; For 1.700 I've done my best to refactor TRAVERSE
1563 ;;; by splitting it up in a bunch of functions,
1564 ;;; so as to improve the collection and use-detection algorithm. --fare
1565 ;;; The protocol is as follows: we pass around operation, dependency,
1566 ;;; bunch of other stuff, and a force argument. Return a force flag.
1567 ;;; The returned flag is T if anything has changed that requires a rebuild.
1568 ;;; The force argument is a list of components that will require a rebuild
1569 ;;; if the flag is T, at which point whoever returns the flag has to
1570 ;;; mark them all as forced, and whoever recurses again can use a NIL list
1571 ;;; as a further argument.
1573 (defvar *forcing* nil
1574 "This dynamically-bound variable is used to force operations in
1575 recursive calls to traverse.")
1577 (defgeneric* do-traverse (operation component collect))
1579 (defun* %do-one-dep (operation c collect required-op required-c required-v)
1580 ;; collects a partial plan that results from performing required-op
1581 ;; on required-c, possibly with a required-vERSION
1582 (let* ((dep-c (or (let ((d (find-component (component-parent c) required-c)))
1583 (and d (version-satisfies d required-v) d))
1584 (if required-v
1585 (error 'missing-dependency-of-version
1586 :required-by c
1587 :version required-v
1588 :requires required-c)
1589 (error 'missing-dependency
1590 :required-by c
1591 :requires required-c))))
1592 (op (make-sub-operation c operation dep-c required-op)))
1593 (do-traverse op dep-c collect)))
1595 (defun* do-one-dep (operation c collect required-op required-c required-v)
1596 ;; this function is a thin, error-handling wrapper around
1597 ;; %do-one-dep. Returns a partial plan per that function.
1598 (loop
1599 (restart-case
1600 (return (%do-one-dep operation c collect
1601 required-op required-c required-v))
1602 (retry ()
1603 :report (lambda (s)
1604 (format s "~@<Retry loading component ~S.~@:>"
1605 (component-find-path required-c)))
1606 :test
1607 (lambda (c)
1609 (print (list :c1 c (typep c 'missing-dependency)))
1610 (when (typep c 'missing-dependency)
1611 (print (list :c2 (missing-requires c) required-c
1612 (equalp (missing-requires c)
1613 required-c))))
1615 (or (null c)
1616 (and (typep c 'missing-dependency)
1617 (equalp (missing-requires c)
1618 required-c))))))))
1620 (defun* do-dep (operation c collect op dep)
1621 ;; type of arguments uncertain:
1622 ;; op seems to at least potentially be a symbol, rather than an operation
1623 ;; dep is a list of component names
1624 (cond ((eq op 'feature)
1625 (if (member (car dep) *features*)
1627 (error 'missing-dependency
1628 :required-by c
1629 :requires (car dep))))
1631 (let ((flag nil))
1632 (flet ((dep (op comp ver)
1633 (when (do-one-dep operation c collect
1634 op comp ver)
1635 (setf flag t))))
1636 (dolist (d dep)
1637 (if (atom d)
1638 (dep op d nil)
1639 ;; structured dependencies --- this parses keywords
1640 ;; the keywords could be broken out and cleanly (extensibly)
1641 ;; processed by EQL methods
1642 (cond ((eq :version (first d))
1643 ;; https://bugs.launchpad.net/asdf/+bug/527788
1644 (dep op (second d) (third d)))
1645 ;; This particular subform is not documented and
1646 ;; has always been broken in the past.
1647 ;; Therefore no one uses it, and I'm cerroring it out,
1648 ;; after fixing it
1649 ;; See https://bugs.launchpad.net/asdf/+bug/518467
1650 ((eq :feature (first d))
1651 (cerror "Continue nonetheless."
1652 "Congratulations, you're the first ever user of FEATURE dependencies! Please contact the asdf-devel mailing-list.")
1653 (when (find (second d) *features* :test 'string-equal)
1654 (dep op (third d) nil)))
1656 (error "Bad dependency ~a. Dependencies must be (:version <version>), (:feature <feature> [version]), or a name" d))))))
1657 flag))))
1659 (defvar *visit-count* 0) ; counter that allows to sort nodes from operation-visited-nodes
1661 (defun* do-collect (collect x)
1662 (funcall collect x))
1664 (defmethod do-traverse ((operation operation) (c component) collect)
1665 (let ((flag nil)) ;; return value: must we rebuild this and its dependencies?
1666 (labels
1667 ((update-flag (x)
1668 (when x
1669 (setf flag t)))
1670 (dep (op comp)
1671 (update-flag (do-dep operation c collect op comp))))
1672 ;; Have we been visited yet? If so, just process the result.
1673 (aif (component-visited-p operation c)
1674 (progn
1675 (update-flag (cdr it))
1676 (return-from do-traverse flag)))
1677 ;; dependencies
1678 (when (component-visiting-p operation c)
1679 (error 'circular-dependency :components (list c)))
1680 (setf (visiting-component operation c) t)
1681 (unwind-protect
1682 (progn
1683 ;; first we check and do all the dependencies for the module.
1684 ;; Operations planned in this loop will show up
1685 ;; in the results, and are consumed below.
1686 (let ((*forcing* nil))
1687 ;; upstream dependencies are never forced to happen just because
1688 ;; the things that depend on them are....
1689 (loop
1690 :for (required-op . deps) :in (component-depends-on operation c)
1691 :do (dep required-op deps)))
1692 ;; constituent bits
1693 (let ((module-ops
1694 (when (typep c 'module)
1695 (let ((at-least-one nil)
1696 ;; This is set based on the results of the
1697 ;; dependencies and whether we are in the
1698 ;; context of a *forcing* call...
1699 ;; inter-system dependencies do NOT trigger
1700 ;; building components
1701 (*forcing*
1702 (or *forcing*
1703 (and flag (not (typep c 'system)))))
1704 (error nil))
1705 (while-collecting (internal-collect)
1706 (dolist (kid (module-components c))
1707 (handler-case
1708 (update-flag
1709 (do-traverse operation kid #'internal-collect))
1710 (missing-dependency (condition)
1711 (when (eq (module-if-component-dep-fails c)
1712 :fail)
1713 (error condition))
1714 (setf error condition))
1715 (:no-error (c)
1716 (declare (ignore c))
1717 (setf at-least-one t))))
1718 (when (and (eq (module-if-component-dep-fails c)
1719 :try-next)
1720 (not at-least-one))
1721 (error error)))))))
1722 (update-flag
1724 *forcing*
1725 (not (operation-done-p operation c))
1726 ;; For sub-operations, check whether
1727 ;; the original ancestor operation was forced,
1728 ;; or names us amongst an explicit list of things to force...
1729 ;; except that this check doesn't distinguish
1730 ;; between all the things with a given name. Sigh.
1731 ;; BROKEN!
1732 (let ((f (operation-forced
1733 (operation-ancestor operation))))
1734 (and f (or (not (consp f)) ;; T or :ALL
1735 (and (typep c 'system) ;; list of names of systems to force
1736 (member (component-name c) f
1737 :test #'string=)))))))
1738 (when flag
1739 (let ((do-first (cdr (assoc (class-name (class-of operation))
1740 (component-do-first c)))))
1741 (loop :for (required-op . deps) :in do-first
1742 :do (do-dep operation c collect required-op deps)))
1743 (do-collect collect (vector module-ops))
1744 (do-collect collect (cons operation c)))))
1745 (setf (visiting-component operation c) nil)))
1746 (visit-component operation c (when flag (incf *visit-count*)))
1747 flag))
1749 (defun* flatten-tree (l)
1750 ;; You collected things into a list.
1751 ;; Most elements are just things to collect again.
1752 ;; A (simple-vector 1) indicate that you should recurse into its contents.
1753 ;; This way, in two passes (rather than N being the depth of the tree),
1754 ;; you can collect things with marginally constant-time append,
1755 ;; achieving linear time collection instead of quadratic time.
1756 (while-collecting (c)
1757 (labels ((r (x)
1758 (if (typep x '(simple-vector 1))
1759 (r* (svref x 0))
1760 (c x)))
1761 (r* (l)
1762 (dolist (x l) (r x))))
1763 (r* l))))
1765 (defmethod traverse ((operation operation) (c component))
1766 ;; cerror'ing a feature that seems to have NEVER EVER worked
1767 ;; ever since danb created it in his 2003-03-16 commit e0d02781.
1768 ;; It was both fixed and disabled in the 1.700 rewrite.
1769 (when (consp (operation-forced operation))
1770 (cerror "Continue nonetheless."
1771 "Congratulations, you're the first ever user of the :force (list of system names) feature! Please contact the asdf-devel mailing-list to collect a cookie.")
1772 (setf (operation-forced operation)
1773 (mapcar #'coerce-name (operation-forced operation))))
1774 (flatten-tree
1775 (while-collecting (collect)
1776 (let ((*visit-count* 0))
1777 (do-traverse operation c #'collect)))))
1779 (defmethod perform ((operation operation) (c source-file))
1780 (sysdef-error
1781 "~@<required method PERFORM not implemented for operation ~A, component ~A~@:>"
1782 (class-of operation) (class-of c)))
1784 (defmethod perform ((operation operation) (c module))
1785 (declare (ignorable operation c))
1786 nil)
1788 (defmethod explain ((operation operation) (component component))
1789 (asdf-message "~&;;; ~A~%" (operation-description operation component)))
1791 (defmethod operation-description (operation component)
1792 (format nil "~A on component ~S" (class-of operation) (component-find-path component)))
1794 ;;;; -------------------------------------------------------------------------
1795 ;;;; compile-op
1797 (defclass compile-op (operation)
1798 ((proclamations :initarg :proclamations :accessor compile-op-proclamations :initform nil)
1799 (on-warnings :initarg :on-warnings :accessor operation-on-warnings
1800 :initform *compile-file-warnings-behaviour*)
1801 (on-failure :initarg :on-failure :accessor operation-on-failure
1802 :initform *compile-file-failure-behaviour*)
1803 (flags :initarg :flags :accessor compile-op-flags
1804 :initform #-ecl nil #+ecl '(:system-p t))))
1806 (defun output-file (operation component)
1807 "The unique output file of performing OPERATION on COMPONENT"
1808 (let ((files (output-files operation component)))
1809 (assert (length=n-p files 1))
1810 (first files)))
1812 (defmethod perform :before ((operation compile-op) (c source-file))
1813 (map nil #'ensure-directories-exist (output-files operation c)))
1815 #+ecl
1816 (defmethod perform :after ((o compile-op) (c cl-source-file))
1817 ;; Note how we use OUTPUT-FILES to find the binary locations
1818 ;; This allows the user to override the names.
1819 (let* ((files (output-files o c))
1820 (object (first files))
1821 (fasl (second files)))
1822 (c:build-fasl fasl :lisp-files (list object))))
1824 (defmethod perform :after ((operation operation) (c component))
1825 (setf (gethash (type-of operation) (component-operation-times c))
1826 (get-universal-time)))
1828 (declaim (ftype (function ((or pathname string) &rest t &key &allow-other-keys)
1829 (values t t t))
1830 compile-file*))
1832 ;;; perform is required to check output-files to find out where to put
1833 ;;; its answers, in case it has been overridden for site policy
1834 (defmethod perform ((operation compile-op) (c cl-source-file))
1835 #-:broken-fasl-loader
1836 (let ((source-file (component-pathname c))
1837 ;; on some implementations, there are more than one output-file,
1838 ;; but the first one should always be the primary fasl that gets loaded.
1839 (output-file (first (output-files operation c)))
1840 (*compile-file-warnings-behaviour* (operation-on-warnings operation))
1841 (*compile-file-failure-behaviour* (operation-on-failure operation)))
1842 (multiple-value-bind (output warnings-p failure-p)
1843 (apply #'compile-file* source-file :output-file output-file
1844 (compile-op-flags operation))
1845 (when warnings-p
1846 (case (operation-on-warnings operation)
1847 (:warn (warn
1848 "~@<COMPILE-FILE warned while performing ~A on ~A.~@:>"
1849 operation c))
1850 (:error (error 'compile-warned :component c :operation operation))
1851 (:ignore nil)))
1852 (when failure-p
1853 (case (operation-on-failure operation)
1854 (:warn (warn
1855 "~@<COMPILE-FILE failed while performing ~A on ~A.~@:>"
1856 operation c))
1857 (:error (error 'compile-failed :component c :operation operation))
1858 (:ignore nil)))
1859 (unless output
1860 (error 'compile-error :component c :operation operation)))))
1862 (defmethod output-files ((operation compile-op) (c cl-source-file))
1863 (declare (ignorable operation))
1864 (let ((p (lispize-pathname (component-pathname c))))
1865 #-:broken-fasl-loader
1866 (list (compile-file-pathname p #+ecl :type #+ecl :object)
1867 #+ecl (compile-file-pathname p :type :fasl))
1868 #+:broken-fasl-loader (list p)))
1870 (defmethod perform ((operation compile-op) (c static-file))
1871 (declare (ignorable operation c))
1872 nil)
1874 (defmethod output-files ((operation compile-op) (c static-file))
1875 (declare (ignorable operation c))
1876 nil)
1878 (defmethod input-files ((operation compile-op) (c static-file))
1879 (declare (ignorable operation c))
1880 nil)
1882 (defmethod operation-description ((operation compile-op) component)
1883 (declare (ignorable operation))
1884 (format nil "compiling component ~S" (component-find-path component)))
1886 ;;;; -------------------------------------------------------------------------
1887 ;;;; load-op
1889 (defclass basic-load-op (operation) ())
1891 (defclass load-op (basic-load-op) ())
1893 (defmethod perform ((o load-op) (c cl-source-file))
1894 #-ecl (mapcar #'load (input-files o c))
1895 #+ecl (loop :for i :in (input-files o c)
1896 :unless (string= (pathname-type i) "fas")
1897 :collect (let ((output (compile-file-pathname (lispize-pathname i))))
1898 (load output))))
1900 (defmethod perform-with-restarts (operation component)
1901 (perform operation component))
1903 (defmethod perform-with-restarts ((o load-op) (c cl-source-file))
1904 (declare (ignorable o))
1905 (loop :with state = :initial
1906 :until (or (eq state :success)
1907 (eq state :failure)) :do
1908 (case state
1909 (:recompiled
1910 (setf state :failure)
1911 (call-next-method)
1912 (setf state :success))
1913 (:failed-load
1914 (setf state :recompiled)
1915 (perform (make-instance 'compile-op) c))
1917 (with-simple-restart
1918 (try-recompiling "Recompile ~a and try loading it again"
1919 (component-name c))
1920 (setf state :failed-load)
1921 (call-next-method)
1922 (setf state :success))))))
1924 (defmethod perform-with-restarts ((o compile-op) (c cl-source-file))
1925 (loop :with state = :initial
1926 :until (or (eq state :success)
1927 (eq state :failure)) :do
1928 (case state
1929 (:recompiled
1930 (setf state :failure)
1931 (call-next-method)
1932 (setf state :success))
1933 (:failed-compile
1934 (setf state :recompiled)
1935 (perform-with-restarts o c))
1937 (with-simple-restart
1938 (try-recompiling "Try recompiling ~a"
1939 (component-name c))
1940 (setf state :failed-compile)
1941 (call-next-method)
1942 (setf state :success))))))
1944 (defmethod perform ((operation load-op) (c static-file))
1945 (declare (ignorable operation c))
1946 nil)
1948 (defmethod operation-done-p ((operation load-op) (c static-file))
1949 (declare (ignorable operation c))
1952 (defmethod output-files ((operation operation) (c component))
1953 (declare (ignorable operation c))
1954 nil)
1956 (defmethod component-depends-on ((operation load-op) (c component))
1957 (declare (ignorable operation))
1958 (cons (list 'compile-op (component-name c))
1959 (call-next-method)))
1961 (defmethod operation-description ((operation load-op) component)
1962 (declare (ignorable operation))
1963 (format nil "loading component ~S" (component-find-path component)))
1966 ;;;; -------------------------------------------------------------------------
1967 ;;;; load-source-op
1969 (defclass load-source-op (basic-load-op) ())
1971 (defmethod perform ((o load-source-op) (c cl-source-file))
1972 (declare (ignorable o))
1973 (let ((source (component-pathname c)))
1974 (setf (component-property c 'last-loaded-as-source)
1975 (and (load source)
1976 (get-universal-time)))))
1978 (defmethod perform ((operation load-source-op) (c static-file))
1979 (declare (ignorable operation c))
1980 nil)
1982 (defmethod output-files ((operation load-source-op) (c component))
1983 (declare (ignorable operation c))
1984 nil)
1986 ;;; FIXME: we simply copy load-op's dependencies. this is Just Not Right.
1987 (defmethod component-depends-on ((o load-source-op) (c component))
1988 (declare (ignorable o))
1989 (let ((what-would-load-op-do (cdr (assoc 'load-op
1990 (component-in-order-to c)))))
1991 (mapcar (lambda (dep)
1992 (if (eq (car dep) 'load-op)
1993 (cons 'load-source-op (cdr dep))
1994 dep))
1995 what-would-load-op-do)))
1997 (defmethod operation-done-p ((o load-source-op) (c source-file))
1998 (declare (ignorable o))
1999 (if (or (not (component-property c 'last-loaded-as-source))
2000 (> (safe-file-write-date (component-pathname c))
2001 (component-property c 'last-loaded-as-source)))
2002 nil t))
2004 (defmethod operation-description ((operation load-source-op) component)
2005 (declare (ignorable operation))
2006 (format nil "loading component ~S" (component-find-path component)))
2009 ;;;; -------------------------------------------------------------------------
2010 ;;;; test-op
2012 (defclass test-op (operation) ())
2014 (defmethod perform ((operation test-op) (c component))
2015 (declare (ignorable operation c))
2016 nil)
2018 (defmethod operation-done-p ((operation test-op) (c system))
2019 "Testing a system is _never_ done."
2020 (declare (ignorable operation c))
2021 nil)
2023 (defmethod component-depends-on :around ((o test-op) (c system))
2024 (declare (ignorable o))
2025 (cons `(load-op ,(component-name c)) (call-next-method)))
2028 ;;;; -------------------------------------------------------------------------
2029 ;;;; Invoking Operations
2031 (defgeneric* operate (operation-class system &key &allow-other-keys))
2033 (defmethod operate (operation-class system &rest args
2034 &key ((:verbose *asdf-verbose*) *asdf-verbose*) version force
2035 &allow-other-keys)
2036 (declare (ignore force))
2037 (let* ((*package* *package*)
2038 (*readtable* *readtable*)
2039 (op (apply #'make-instance operation-class
2040 :original-initargs args
2041 args))
2042 (*verbose-out* (if *asdf-verbose* *standard-output* (make-broadcast-stream)))
2043 (system (if (typep system 'component) system (find-system system))))
2044 (unless (version-satisfies system version)
2045 (error 'missing-component-of-version :requires system :version version))
2046 (let ((steps (traverse op system)))
2047 (with-compilation-unit ()
2048 (loop :for (op . component) :in steps :do
2049 (loop
2050 (restart-case
2051 (progn
2052 (perform-with-restarts op component)
2053 (return))
2054 (retry ()
2055 :report
2056 (lambda (s)
2057 (format s "~@<Retry ~A.~@:>" (operation-description op component))))
2058 (accept ()
2059 :report
2060 (lambda (s)
2061 (format s "~@<Continue, treating ~A as having been successful.~@:>"
2062 (operation-description op component)))
2063 (setf (gethash (type-of op)
2064 (component-operation-times component))
2065 (get-universal-time))
2066 (return))))))
2067 (values op steps))))
2069 (defun* oos (operation-class system &rest args &key force verbose version
2070 &allow-other-keys)
2071 (declare (ignore force verbose version))
2072 (apply #'operate operation-class system args))
2074 (let ((operate-docstring
2075 "Operate does three things:
2077 1. It creates an instance of OPERATION-CLASS using any keyword parameters
2078 as initargs.
2079 2. It finds the asdf-system specified by SYSTEM (possibly loading
2080 it from disk).
2081 3. It then calls TRAVERSE with the operation and system as arguments
2083 The traverse operation is wrapped in WITH-COMPILATION-UNIT and error
2084 handling code. If a VERSION argument is supplied, then operate also
2085 ensures that the system found satisfies it using the VERSION-SATISFIES
2086 method.
2088 Note that dependencies may cause the operation to invoke other
2089 operations on the system or its components: the new operations will be
2090 created with the same initargs as the original one.
2092 (setf (documentation 'oos 'function)
2093 (format nil
2094 "Short for _operate on system_ and an alias for the OPERATE function. ~&~&~a"
2095 operate-docstring))
2096 (setf (documentation 'operate 'function)
2097 operate-docstring))
2099 (defun* load-system (system &rest args &key force verbose version
2100 &allow-other-keys)
2101 "Shorthand for `(operate 'asdf:load-op system)`. See OPERATE for
2102 details."
2103 (declare (ignore force verbose version))
2104 (apply #'operate 'load-op system args))
2106 (defun* compile-system (system &rest args &key force verbose version
2107 &allow-other-keys)
2108 "Shorthand for `(operate 'asdf:compile-op system)`. See OPERATE
2109 for details."
2110 (declare (ignore force verbose version))
2111 (apply #'operate 'compile-op system args))
2113 (defun* test-system (system &rest args &key force verbose version
2114 &allow-other-keys)
2115 "Shorthand for `(operate 'asdf:test-op system)`. See OPERATE for
2116 details."
2117 (declare (ignore force verbose version))
2118 (apply #'operate 'test-op system args))
2120 ;;;; -------------------------------------------------------------------------
2121 ;;;; Defsystem
2123 (defun* load-pathname ()
2124 (let ((pn (or *load-pathname* *compile-file-pathname*)))
2125 (if *resolve-symlinks*
2126 (and pn (resolve-symlinks pn))
2127 pn)))
2129 (defun* determine-system-pathname (pathname pathname-supplied-p)
2130 ;; The defsystem macro calls us to determine
2131 ;; the pathname of a system as follows:
2132 ;; 1. the one supplied,
2133 ;; 2. derived from *load-pathname* via load-pathname
2134 ;; 3. taken from the *default-pathname-defaults* via default-directory
2135 (let* ((file-pathname (load-pathname))
2136 (directory-pathname (and file-pathname (pathname-directory-pathname file-pathname))))
2137 (or (and pathname-supplied-p (merge-pathnames* pathname directory-pathname))
2138 directory-pathname
2139 (default-directory))))
2141 (defmacro defsystem (name &body options)
2142 (destructuring-bind (&key (pathname nil pathname-arg-p) (class 'system)
2143 defsystem-depends-on &allow-other-keys)
2144 options
2145 (let ((component-options (remove-keys '(:defsystem-depends-on :class) options)))
2146 `(progn
2147 ;; system must be registered before we parse the body, otherwise
2148 ;; we recur when trying to find an existing system of the same name
2149 ;; to reuse options (e.g. pathname) from
2150 ,@(loop :for system :in defsystem-depends-on
2151 :collect `(load-system ,system))
2152 (let ((s (system-registered-p ',name)))
2153 (cond ((and s (eq (type-of (cdr s)) ',class))
2154 (setf (car s) (get-universal-time)))
2156 (change-class (cdr s) ',class))
2158 (register-system (quote ,name)
2159 (make-instance ',class :name ',name))))
2160 (%set-system-source-file (load-pathname)
2161 (cdr (system-registered-p ',name))))
2162 (parse-component-form
2163 nil (list*
2164 :module (coerce-name ',name)
2165 :pathname
2166 ,(determine-system-pathname pathname pathname-arg-p)
2167 ',component-options))))))
2169 (defun* class-for-type (parent type)
2170 (or (loop :for symbol :in (list
2171 (unless (keywordp type) type)
2172 (find-symbol (symbol-name type) *package*)
2173 (find-symbol (symbol-name type) :asdf))
2174 :for class = (and symbol (find-class symbol nil))
2175 :when (and class (subtypep class 'component))
2176 :return class)
2177 (and (eq type :file)
2178 (or (module-default-component-class parent)
2179 (find-class *default-component-class*)))
2180 (sysdef-error "~@<don't recognize component type ~A~@:>" type)))
2182 (defun* maybe-add-tree (tree op1 op2 c)
2183 "Add the node C at /OP1/OP2 in TREE, unless it's there already.
2184 Returns the new tree (which probably shares structure with the old one)"
2185 (let ((first-op-tree (assoc op1 tree)))
2186 (if first-op-tree
2187 (progn
2188 (aif (assoc op2 (cdr first-op-tree))
2189 (if (find c (cdr it))
2191 (setf (cdr it) (cons c (cdr it))))
2192 (setf (cdr first-op-tree)
2193 (acons op2 (list c) (cdr first-op-tree))))
2194 tree)
2195 (acons op1 (list (list op2 c)) tree))))
2197 (defun* union-of-dependencies (&rest deps)
2198 (let ((new-tree nil))
2199 (dolist (dep deps)
2200 (dolist (op-tree dep)
2201 (dolist (op (cdr op-tree))
2202 (dolist (c (cdr op))
2203 (setf new-tree
2204 (maybe-add-tree new-tree (car op-tree) (car op) c))))))
2205 new-tree))
2208 (defvar *serial-depends-on* nil)
2210 (defun* sysdef-error-component (msg type name value)
2211 (sysdef-error (concatenate 'string msg
2212 "~&The value specified for ~(~A~) ~A is ~S")
2213 type name value))
2215 (defun* check-component-input (type name weakly-depends-on
2216 depends-on components in-order-to)
2217 "A partial test of the values of a component."
2218 (unless (listp depends-on)
2219 (sysdef-error-component ":depends-on must be a list."
2220 type name depends-on))
2221 (unless (listp weakly-depends-on)
2222 (sysdef-error-component ":weakly-depends-on must be a list."
2223 type name weakly-depends-on))
2224 (unless (listp components)
2225 (sysdef-error-component ":components must be NIL or a list of components."
2226 type name components))
2227 (unless (and (listp in-order-to) (listp (car in-order-to)))
2228 (sysdef-error-component ":in-order-to must be NIL or a list of components."
2229 type name in-order-to)))
2231 (defun* %remove-component-inline-methods (component)
2232 (dolist (name +asdf-methods+)
2233 (map ()
2234 ;; this is inefficient as most of the stored
2235 ;; methods will not be for this particular gf
2236 ;; But this is hardly performance-critical
2237 (lambda (m)
2238 (remove-method (symbol-function name) m))
2239 (component-inline-methods component)))
2240 ;; clear methods, then add the new ones
2241 (setf (component-inline-methods component) nil))
2243 (defun* %define-component-inline-methods (ret rest)
2244 (dolist (name +asdf-methods+)
2245 (let ((keyword (intern (symbol-name name) :keyword)))
2246 (loop :for data = rest :then (cddr data)
2247 :for key = (first data)
2248 :for value = (second data)
2249 :while data
2250 :when (eq key keyword) :do
2251 (destructuring-bind (op qual (o c) &body body) value
2252 (pushnew
2253 (eval `(defmethod ,name ,qual ((,o ,op) (,c (eql ,ret)))
2254 ,@body))
2255 (component-inline-methods ret)))))))
2257 (defun* %refresh-component-inline-methods (component rest)
2258 (%remove-component-inline-methods component)
2259 (%define-component-inline-methods component rest))
2261 (defun* parse-component-form (parent options)
2262 (destructuring-bind
2263 (type name &rest rest &key
2264 ;; the following list of keywords is reproduced below in the
2265 ;; remove-keys form. important to keep them in sync
2266 components pathname default-component-class
2267 perform explain output-files operation-done-p
2268 weakly-depends-on
2269 depends-on serial in-order-to
2270 ;; list ends
2271 &allow-other-keys) options
2272 (declare (ignorable perform explain output-files operation-done-p))
2273 (check-component-input type name weakly-depends-on depends-on components in-order-to)
2275 (when (and parent
2276 (find-component parent name)
2277 ;; ignore the same object when rereading the defsystem
2278 (not
2279 (typep (find-component parent name)
2280 (class-for-type parent type))))
2281 (error 'duplicate-names :name name))
2283 (let* ((other-args (remove-keys
2284 '(components pathname default-component-class
2285 perform explain output-files operation-done-p
2286 weakly-depends-on
2287 depends-on serial in-order-to)
2288 rest))
2289 (ret
2290 (or (find-component parent name)
2291 (make-instance (class-for-type parent type)))))
2292 (when weakly-depends-on
2293 (appendf depends-on (remove-if (complement #'find-system) weakly-depends-on)))
2294 (when *serial-depends-on*
2295 (push *serial-depends-on* depends-on))
2296 (apply #'reinitialize-instance ret
2297 :name (coerce-name name)
2298 :pathname pathname
2299 :parent parent
2300 other-args)
2301 (component-pathname ret) ; eagerly compute the absolute pathname
2302 (when (typep ret 'module)
2303 (setf (module-default-component-class ret)
2304 (or default-component-class
2305 (and (typep parent 'module)
2306 (module-default-component-class parent))))
2307 (let ((*serial-depends-on* nil))
2308 (setf (module-components ret)
2309 (loop
2310 :for c-form :in components
2311 :for c = (parse-component-form ret c-form)
2312 :for name = (component-name c)
2313 :collect c
2314 :when serial :do (setf *serial-depends-on* name))))
2315 (compute-module-components-by-name ret))
2317 (setf (component-load-dependencies ret) depends-on) ;; Used by POIU
2319 (setf (component-in-order-to ret)
2320 (union-of-dependencies
2321 in-order-to
2322 `((compile-op (compile-op ,@depends-on))
2323 (load-op (load-op ,@depends-on)))))
2324 (setf (component-do-first ret) `((compile-op (load-op ,@depends-on))))
2326 (%refresh-component-inline-methods ret rest)
2327 ret)))
2329 ;;;; ---------------------------------------------------------------------------
2330 ;;;; run-shell-command
2331 ;;;;
2332 ;;;; run-shell-command functions for other lisp implementations will be
2333 ;;;; gratefully accepted, if they do the same thing.
2334 ;;;; If the docstring is ambiguous, send a bug report.
2335 ;;;;
2336 ;;;; We probably should move this functionality to its own system and deprecate
2337 ;;;; use of it from the asdf package. However, this would break unspecified
2338 ;;;; existing software, so until a clear alternative exists, we can't deprecate
2339 ;;;; it, and even after it's been deprecated, we will support it for a few
2340 ;;;; years so everyone has time to migrate away from it. -- fare 2009-12-01
2342 (defun* run-shell-command (control-string &rest args)
2343 "Interpolate ARGS into CONTROL-STRING as if by FORMAT, and
2344 synchronously execute the result using a Bourne-compatible shell, with
2345 output to *VERBOSE-OUT*. Returns the shell's exit code."
2346 (let ((command (apply #'format nil control-string args)))
2347 (asdf-message "; $ ~A~%" command)
2349 #+abcl
2350 (ext:run-shell-command command :output *verbose-out*)
2352 #+allegro
2353 ;; will this fail if command has embedded quotes - it seems to work
2354 (multiple-value-bind (stdout stderr exit-code)
2355 (excl.osi:command-output
2356 (format nil "~a -c \"~a\""
2357 #+mswindows "sh" #-mswindows "/bin/sh" command)
2358 :input nil :whole nil
2359 #+mswindows :show-window #+mswindows :hide)
2360 (format *verbose-out* "~{~&; ~a~%~}~%" stderr)
2361 (format *verbose-out* "~{~&; ~a~%~}~%" stdout)
2362 exit-code)
2364 #+clisp ;XXX not exactly *verbose-out*, I know
2365 (ext:run-shell-command command :output :terminal :wait t)
2367 #+clozure
2368 (nth-value 1
2369 (ccl:external-process-status
2370 (ccl:run-program "/bin/sh" (list "-c" command)
2371 :input nil :output *verbose-out*
2372 :wait t)))
2374 #+ecl ;; courtesy of Juan Jose Garcia Ripoll
2375 (si:system command)
2377 #+gcl
2378 (lisp:system command)
2380 #+lispworks
2381 (system:call-system-showing-output
2382 command
2383 :shell-type "/bin/sh"
2384 :show-cmd nil
2385 :prefix ""
2386 :output-stream *verbose-out*)
2388 #+sbcl
2389 (sb-ext:process-exit-code
2390 (apply #'sb-ext:run-program
2391 #+win32 "sh" #-win32 "/bin/sh"
2392 (list "-c" command)
2393 :input nil :output *verbose-out*
2394 #+win32 '(:search t) #-win32 nil))
2396 #+(or cmu scl)
2397 (ext:process-exit-code
2398 (ext:run-program
2399 "/bin/sh"
2400 (list "-c" command)
2401 :input nil :output *verbose-out*))
2403 #-(or abcl allegro clisp clozure cmu ecl gcl lispworks sbcl scl)
2404 (error "RUN-SHELL-COMMAND not implemented for this Lisp")))
2406 ;;;; ---------------------------------------------------------------------------
2407 ;;;; system-relative-pathname
2409 (defmethod system-source-file ((system-name string))
2410 (system-source-file (find-system system-name)))
2411 (defmethod system-source-file ((system-name symbol))
2412 (system-source-file (find-system system-name)))
2414 (defun* system-source-directory (system-designator)
2415 "Return a pathname object corresponding to the
2416 directory in which the system specification (.asd file) is
2417 located."
2418 (make-pathname :name nil
2419 :type nil
2420 :defaults (system-source-file system-designator)))
2422 (defun* relativize-directory (directory)
2423 (cond
2424 ((stringp directory)
2425 (list :relative directory))
2426 ((eq (car directory) :absolute)
2427 (cons :relative (cdr directory)))
2429 directory)))
2431 (defun* relativize-pathname-directory (pathspec)
2432 (let ((p (pathname pathspec)))
2433 (make-pathname
2434 :directory (relativize-directory (pathname-directory p))
2435 :defaults p)))
2437 (defun* system-relative-pathname (system name &key type)
2438 (merge-pathnames*
2439 (merge-component-name-type name :type type)
2440 (system-source-directory system)))
2443 ;;; ---------------------------------------------------------------------------
2444 ;;; implementation-identifier
2446 ;;; produce a string to identify current implementation.
2447 ;;; Initially stolen from SLIME's SWANK, hacked since.
2449 (defparameter *implementation-features*
2450 '(:allegro :lispworks :sbcl :clozure :digitool :cmu :clisp
2451 :corman :cormanlisp :armedbear :gcl :ecl :scl))
2453 (defparameter *os-features*
2454 '((:windows :mswindows :win32 :mingw32)
2455 (:solaris :sunos)
2456 :linux ;; for GCL at least, must appear before :bsd.
2457 :macosx :darwin :apple
2458 :freebsd :netbsd :openbsd :bsd
2459 :unix))
2461 (defparameter *architecture-features*
2462 '((:x86-64 :amd64 :x86_64 :x8664-target)
2463 (:x86 :i686 :i586 :pentium3 :i486 :i386 :pc386 :iapx386 :x8632-target :pentium4)
2464 :hppa64 :hppa :ppc64 (:ppc32 :ppc :powerpc) :sparc64 :sparc
2465 :java-1.4 :java-1.5 :java-1.6 :java-1.7))
2468 (defun* lisp-version-string ()
2469 (let ((s (lisp-implementation-version)))
2470 (declare (ignorable s))
2471 #+allegro (format nil
2472 "~A~A~A~A"
2473 excl::*common-lisp-version-number*
2474 ;; ANSI vs MoDeRn - thanks to Robert Goldman and Charley Cox
2475 (if (eq excl:*current-case-mode*
2476 :case-sensitive-lower) "M" "A")
2477 ;; Note if not using International ACL
2478 ;; see http://www.franz.com/support/documentation/8.1/doc/operators/excl/ics-target-case.htm
2479 (excl:ics-target-case
2480 (:-ics "8")
2481 (:+ics ""))
2482 (if (member :64bit *features*) "-64bit" ""))
2483 #+armedbear (format nil "~a-fasl~a" s system::*fasl-version*)
2484 #+clisp (subseq s 0 (position #\space s))
2485 #+clozure (format nil "~d.~d-fasl~d"
2486 ccl::*openmcl-major-version*
2487 ccl::*openmcl-minor-version*
2488 (logand ccl::fasl-version #xFF))
2489 #+cmu (substitute #\- #\/ s)
2490 #+digitool (subseq s 8)
2491 #+ecl (format nil "~A~@[-~A~]" s
2492 (let ((vcs-id (ext:lisp-implementation-vcs-id)))
2493 (when (>= (length vcs-id) 8)
2494 (subseq vcs-id 0 8))))
2495 #+gcl (subseq s (1+ (position #\space s)))
2496 #+lispworks (format nil "~A~@[~A~]" s
2497 (when (member :lispworks-64bit *features*) "-64bit"))
2498 ;; #+sbcl (format nil "~a-fasl~d" s sb-fasl:+fasl-file-version+) ; f-f-v redundant w/ version
2499 #+(or cormanlisp mcl sbcl scl) s
2500 #-(or allegro armedbear clisp clozure cmu cormanlisp digitool
2501 ecl gcl lispworks mcl sbcl scl) s))
2503 (defun* first-feature (features)
2504 (labels
2505 ((fp (thing)
2506 (etypecase thing
2507 (symbol
2508 (let ((feature (find thing *features*)))
2509 (when feature (return-from fp feature))))
2510 ;; allows features to be lists of which the first
2511 ;; member is the "main name", the rest being aliases
2512 (cons
2513 (dolist (subf thing)
2514 (when (find subf *features*) (return-from fp (first thing))))))
2515 nil))
2516 (loop :for f :in features
2517 :when (fp f) :return :it)))
2519 (defun* implementation-type ()
2520 (first-feature *implementation-features*))
2522 (defun* implementation-identifier ()
2523 (labels
2524 ((maybe-warn (value fstring &rest args)
2525 (cond (value)
2526 (t (apply #'warn fstring args)
2527 "unknown"))))
2528 (let ((lisp (maybe-warn (implementation-type)
2529 "No implementation feature found in ~a."
2530 *implementation-features*))
2531 (os (maybe-warn (first-feature *os-features*)
2532 "No os feature found in ~a." *os-features*))
2533 (arch (maybe-warn (first-feature *architecture-features*)
2534 "No architecture feature found in ~a."
2535 *architecture-features*))
2536 (version (maybe-warn (lisp-version-string)
2537 "Don't know how to get Lisp implementation version.")))
2538 (substitute-if
2539 #\_ (lambda (x) (find x " /:\\(){}[]$#`'\""))
2540 (format nil "~(~@{~a~^-~}~)" lisp version os arch)))))
2544 ;;; ---------------------------------------------------------------------------
2545 ;;; Generic support for configuration files
2547 (defparameter *inter-directory-separator*
2548 #+(or unix cygwin) #\:
2549 #-(or unix cygwin) #\;)
2551 (defun* user-homedir ()
2552 (truename (user-homedir-pathname)))
2554 (defun* try-directory-subpath (x sub &key type)
2555 (let* ((p (and x (ensure-directory-pathname x)))
2556 (tp (and p (probe-file* p)))
2557 (sp (and tp (merge-pathnames* (merge-component-name-type sub :type type) p)))
2558 (ts (and sp (probe-file* sp))))
2559 (and ts (values sp ts))))
2560 (defun* user-configuration-directories ()
2561 (remove-if
2562 #'null
2563 (flet ((try (x sub) (try-directory-subpath x sub :type :directory)))
2564 `(,(try (getenv "XDG_CONFIG_HOME") "common-lisp/")
2565 ,@(loop :with dirs = (getenv "XDG_CONFIG_DIRS")
2566 :for dir :in (split-string dirs :separator ":")
2567 :collect (try dir "common-lisp/"))
2568 #+(and (or win32 windows mswindows mingw32) (not cygwin))
2569 ,@`(#+lispworks ,(try (sys:get-folder-path :common-appdata) "common-lisp/config/")
2570 ;;; read-windows-registry HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Windows\CurrentVersion\Explorer\User Shell Folders\AppData
2571 ,(try (getenv "APPDATA") "common-lisp/config/"))
2572 ,(try (user-homedir) ".config/common-lisp/")))))
2573 (defun* system-configuration-directories ()
2574 (remove-if
2575 #'null
2576 (append
2577 #+(and (or win32 windows mswindows mingw32) (not cygwin))
2578 (flet ((try (x sub) (try-directory-subpath x sub :type :directory)))
2579 `(,@`(#+lispworks ,(try (sys:get-folder-path :local-appdata) "common-lisp/config/")
2580 ;;; read-windows-registry HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Windows\CurrentVersion\Explorer\User Shell Folders\Common AppData
2581 ,(try (getenv "ALLUSERSPROFILE") "Application Data/common-lisp/config/"))))
2582 (list #p"/etc/common-lisp/"))))
2583 (defun* in-first-directory (dirs x)
2584 (loop :for dir :in dirs
2585 :thereis (and dir (probe-file* (merge-pathnames* x (ensure-directory-pathname dir))))))
2586 (defun* in-user-configuration-directory (x)
2587 (in-first-directory (user-configuration-directories) x))
2588 (defun* in-system-configuration-directory (x)
2589 (in-first-directory (system-configuration-directories) x))
2591 (defun* configuration-inheritance-directive-p (x)
2592 (let ((kw '(:inherit-configuration :ignore-inherited-configuration)))
2593 (or (member x kw)
2594 (and (length=n-p x 1) (member (car x) kw)))))
2596 (defun* validate-configuration-form (form tag directive-validator
2597 &optional (description tag))
2598 (unless (and (consp form) (eq (car form) tag))
2599 (error "Error: Form doesn't specify ~A ~S~%" description form))
2600 (loop :with inherit = 0
2601 :for directive :in (cdr form) :do
2602 (if (configuration-inheritance-directive-p directive)
2603 (incf inherit)
2604 (funcall directive-validator directive))
2605 :finally
2606 (unless (= inherit 1)
2607 (error "One and only one of ~S or ~S is required"
2608 :inherit-configuration :ignore-inherited-configuration)))
2609 form)
2611 (defun* validate-configuration-file (file validator description)
2612 (let ((forms (read-file-forms file)))
2613 (unless (length=n-p forms 1)
2614 (error "One and only one form allowed for ~A. Got: ~S~%" description forms))
2615 (funcall validator (car forms))))
2617 (defun* hidden-file-p (pathname)
2618 (equal (first-char (pathname-name pathname)) #\.))
2620 (defun* validate-configuration-directory (directory tag validator)
2621 (let ((files (sort (ignore-errors
2622 (remove-if
2623 'hidden-file-p
2624 (directory (make-pathname :name :wild :type "conf" :defaults directory)
2625 #+sbcl :resolve-symlinks #+sbcl nil)))
2626 #'string< :key #'namestring)))
2627 `(,tag
2628 ,@(loop :for file :in files :append
2629 (mapcar validator (read-file-forms file)))
2630 :inherit-configuration)))
2633 ;;; ---------------------------------------------------------------------------
2634 ;;; asdf-output-translations
2636 ;;; this code is heavily inspired from
2637 ;;; asdf-binary-translations, common-lisp-controller and cl-launch.
2638 ;;; ---------------------------------------------------------------------------
2640 (defvar *output-translations* ()
2641 "Either NIL (for uninitialized), or a list of one element,
2642 said element itself being a sorted list of mappings.
2643 Each mapping is a pair of a source pathname and destination pathname,
2644 and the order is by decreasing length of namestring of the source pathname.")
2646 (defvar *user-cache*
2647 (flet ((try (x &rest sub) (and x `(,x ,@sub))))
2649 (try (getenv "XDG_CACHE_HOME") "common-lisp" :implementation)
2650 #+(and (or win32 windows mswindows mingw32) (not cygwin))
2651 (try (getenv "APPDATA") "common-lisp" "cache" :implementation)
2652 '(:home ".cache" "common-lisp" :implementation))))
2653 (defvar *system-cache*
2654 ;; No good default, plus there's a security problem
2655 ;; with other users messing with such directories.
2656 *user-cache*)
2658 (defun* output-translations ()
2659 (car *output-translations*))
2661 (defun* (setf output-translations) (new-value)
2662 (setf *output-translations*
2663 (list
2664 (stable-sort (copy-list new-value) #'>
2665 :key (lambda (x)
2666 (etypecase (car x)
2667 ((eql t) -1)
2668 (pathname
2669 (length (pathname-directory (car x)))))))))
2670 new-value)
2672 (defun* output-translations-initialized-p ()
2673 (and *output-translations* t))
2675 (defun* clear-output-translations ()
2676 "Undoes any initialization of the output translations.
2677 You might want to call that before you dump an image that would be resumed
2678 with a different configuration, so the configuration would be re-read then."
2679 (setf *output-translations* '())
2680 (values))
2682 (defparameter *wild-asd*
2683 (make-pathname :directory '(:relative :wild-inferiors)
2684 :name :wild :type "asd" :version :newest))
2686 (declaim (ftype (function (t &optional boolean) (values (or null pathname) &optional))
2687 resolve-location))
2689 (defun* resolve-relative-location-component (super x &optional wildenp)
2690 (let* ((r (etypecase x
2691 (pathname x)
2692 (string x)
2693 (cons
2694 (let ((car (resolve-relative-location-component super (car x) nil)))
2695 (if (null (cdr x))
2697 (let ((cdr (resolve-relative-location-component
2698 (merge-pathnames* car super) (cdr x) wildenp)))
2699 (merge-pathnames* cdr car)))))
2700 ((eql :default-directory)
2701 (relativize-pathname-directory (default-directory)))
2702 ((eql :implementation) (implementation-identifier))
2703 ((eql :implementation-type) (string-downcase (implementation-type)))
2704 #-(and (or win32 windows mswindows mingw32) (not cygwin))
2705 ((eql :uid) (princ-to-string (get-uid)))))
2706 (d (if (pathnamep x) r (ensure-directory-pathname r)))
2707 (s (if (and wildenp (not (pathnamep x)))
2708 (wilden d)
2709 d)))
2710 (when (and (absolute-pathname-p s) (not (pathname-match-p s (wilden super))))
2711 (error "pathname ~S is not relative to ~S" s super))
2712 (merge-pathnames* s super)))
2714 (defun* resolve-absolute-location-component (x wildenp)
2715 (let* ((r
2716 (etypecase x
2717 (pathname x)
2718 (string (ensure-directory-pathname x))
2719 (cons
2720 (let ((car (resolve-absolute-location-component (car x) nil)))
2721 (if (null (cdr x))
2723 (let ((cdr (resolve-relative-location-component
2724 car (cdr x) wildenp)))
2725 (merge-pathnames* cdr car)))))
2726 ((eql :root)
2727 ;; special magic! we encode such paths as relative pathnames,
2728 ;; but it means "relative to the root of the source pathname's host and device".
2729 (return-from resolve-absolute-location-component
2730 (make-pathname :directory '(:relative))))
2731 ((eql :home) (user-homedir))
2732 ((eql :user-cache) (resolve-location *user-cache* nil))
2733 ((eql :system-cache) (resolve-location *system-cache* nil))
2734 ((eql :default-directory) (default-directory))))
2735 (s (if (and wildenp (not (pathnamep x)))
2736 (wilden r)
2737 r)))
2738 (unless (absolute-pathname-p s)
2739 (error "Not an absolute pathname ~S" s))
2742 (defun* resolve-location (x &optional wildenp)
2743 (if (atom x)
2744 (resolve-absolute-location-component x wildenp)
2745 (loop :with path = (resolve-absolute-location-component (car x) nil)
2746 :for (component . morep) :on (cdr x)
2747 :do (setf path (resolve-relative-location-component
2748 path component (and wildenp (not morep))))
2749 :finally (return path))))
2751 (defun* location-designator-p (x)
2752 (flet ((componentp (c) (typep c '(or string pathname keyword))))
2753 (or (typep x 'boolean) (componentp x) (and (consp x) (every #'componentp x)))))
2755 (defun* location-function-p (x)
2756 (and
2757 (consp x)
2758 (length=n-p x 2)
2759 (or (and (equal (first x) :function)
2760 (typep (second x) 'symbol))
2761 (and (equal (first x) 'lambda)
2762 (cddr x)
2763 (length=n-p (second x) 2)))))
2765 (defun* validate-output-translations-directive (directive)
2766 (unless
2767 (or (member directive '(:inherit-configuration
2768 :ignore-inherited-configuration
2769 :enable-user-cache :disable-cache nil))
2770 (and (consp directive)
2771 (or (and (length=n-p directive 2)
2772 (or (and (eq (first directive) :include)
2773 (typep (second directive) '(or string pathname null)))
2774 (and (location-designator-p (first directive))
2775 (or (location-designator-p (second directive))
2776 (location-function-p (second directive))))))
2777 (and (length=n-p directive 1)
2778 (location-designator-p (first directive))))))
2779 (error "Invalid directive ~S~%" directive))
2780 directive)
2782 (defun* validate-output-translations-form (form)
2783 (validate-configuration-form
2784 form
2785 :output-translations
2786 'validate-output-translations-directive
2787 "output translations"))
2789 (defun* validate-output-translations-file (file)
2790 (validate-configuration-file
2791 file 'validate-output-translations-form "output translations"))
2793 (defun* validate-output-translations-directory (directory)
2794 (validate-configuration-directory
2795 directory :output-translations 'validate-output-translations-directive))
2797 (defun* parse-output-translations-string (string)
2798 (cond
2799 ((or (null string) (equal string ""))
2800 '(:output-translations :inherit-configuration))
2801 ((not (stringp string))
2802 (error "environment string isn't: ~S" string))
2803 ((eql (char string 0) #\")
2804 (parse-output-translations-string (read-from-string string)))
2805 ((eql (char string 0) #\()
2806 (validate-output-translations-form (read-from-string string)))
2808 (loop
2809 :with inherit = nil
2810 :with directives = ()
2811 :with start = 0
2812 :with end = (length string)
2813 :with source = nil
2814 :for i = (or (position *inter-directory-separator* string :start start) end) :do
2815 (let ((s (subseq string start i)))
2816 (cond
2817 (source
2818 (push (list source (if (equal "" s) nil s)) directives)
2819 (setf source nil))
2820 ((equal "" s)
2821 (when inherit
2822 (error "only one inherited configuration allowed: ~S" string))
2823 (setf inherit t)
2824 (push :inherit-configuration directives))
2826 (setf source s)))
2827 (setf start (1+ i))
2828 (when (> start end)
2829 (when source
2830 (error "Uneven number of components in source to destination mapping ~S" string))
2831 (unless inherit
2832 (push :ignore-inherited-configuration directives))
2833 (return `(:output-translations ,@(nreverse directives)))))))))
2835 (defparameter *default-output-translations*
2836 '(environment-output-translations
2837 user-output-translations-pathname
2838 user-output-translations-directory-pathname
2839 system-output-translations-pathname
2840 system-output-translations-directory-pathname))
2842 (defun* wrapping-output-translations ()
2843 `(:output-translations
2844 ;; Some implementations have precompiled ASDF systems,
2845 ;; so we must disable translations for implementation paths.
2846 #+sbcl ,(let ((h (getenv "SBCL_HOME"))) (when (plusp (length h)) `(,h ())))
2847 #+ecl (,(translate-logical-pathname "SYS:**;*.*") ()) ; not needed: no precompiled ASDF system
2848 #+clozure ,(ignore-errors (list (wilden (let ((*default-pathname-defaults* #p"")) (truename #p"ccl:"))) ())) ; not needed: no precompiled ASDF system
2849 ;; All-import, here is where we want user stuff to be:
2850 :inherit-configuration
2851 ;; These are for convenience, and can be overridden by the user:
2852 #+abcl (#p"/___jar___file___root___/**/*.*" (:user-cache #p"**/*.*"))
2853 #+abcl (#p"jar:file:/**/*.jar!/**/*.*" (:function translate-jar-pathname))
2854 ;; If we want to enable the user cache by default, here would be the place:
2855 :enable-user-cache))
2857 (defparameter *output-translations-file* #p"asdf-output-translations.conf")
2858 (defparameter *output-translations-directory* #p"asdf-output-translations.conf.d/")
2860 (defun* user-output-translations-pathname ()
2861 (in-user-configuration-directory *output-translations-file* ))
2862 (defun* system-output-translations-pathname ()
2863 (in-system-configuration-directory *output-translations-file*))
2864 (defun* user-output-translations-directory-pathname ()
2865 (in-user-configuration-directory *output-translations-directory*))
2866 (defun* system-output-translations-directory-pathname ()
2867 (in-system-configuration-directory *output-translations-directory*))
2868 (defun* environment-output-translations ()
2869 (getenv "ASDF_OUTPUT_TRANSLATIONS"))
2871 (defgeneric* process-output-translations (spec &key inherit collect))
2872 (declaim (ftype (function (t &key (:collect (or symbol function))) t)
2873 inherit-output-translations))
2874 (declaim (ftype (function (t &key (:collect (or symbol function)) (:inherit list)) t)
2875 process-output-translations-directive))
2877 (defmethod process-output-translations ((x symbol) &key
2878 (inherit *default-output-translations*)
2879 collect)
2880 (process-output-translations (funcall x) :inherit inherit :collect collect))
2881 (defmethod process-output-translations ((pathname pathname) &key inherit collect)
2882 (cond
2883 ((directory-pathname-p pathname)
2884 (process-output-translations (validate-output-translations-directory pathname)
2885 :inherit inherit :collect collect))
2886 ((probe-file pathname)
2887 (process-output-translations (validate-output-translations-file pathname)
2888 :inherit inherit :collect collect))
2890 (inherit-output-translations inherit :collect collect))))
2891 (defmethod process-output-translations ((string string) &key inherit collect)
2892 (process-output-translations (parse-output-translations-string string)
2893 :inherit inherit :collect collect))
2894 (defmethod process-output-translations ((x null) &key inherit collect)
2895 (declare (ignorable x))
2896 (inherit-output-translations inherit :collect collect))
2897 (defmethod process-output-translations ((form cons) &key inherit collect)
2898 (dolist (directive (cdr (validate-output-translations-form form)))
2899 (process-output-translations-directive directive :inherit inherit :collect collect)))
2901 (defun* inherit-output-translations (inherit &key collect)
2902 (when inherit
2903 (process-output-translations (first inherit) :collect collect :inherit (rest inherit))))
2905 (defun* process-output-translations-directive (directive &key inherit collect)
2906 (if (atom directive)
2907 (ecase directive
2908 ((:enable-user-cache)
2909 (process-output-translations-directive '(t :user-cache) :collect collect))
2910 ((:disable-cache)
2911 (process-output-translations-directive '(t t) :collect collect))
2912 ((:inherit-configuration)
2913 (inherit-output-translations inherit :collect collect))
2914 ((:ignore-inherited-configuration nil)
2915 nil))
2916 (let ((src (first directive))
2917 (dst (second directive)))
2918 (if (eq src :include)
2919 (when dst
2920 (process-output-translations (pathname dst) :inherit nil :collect collect))
2921 (when src
2922 (let ((trusrc (or (eql src t)
2923 (let ((loc (resolve-location src t)))
2924 (if (absolute-pathname-p loc) (truenamize loc) loc)))))
2925 (cond
2926 ((location-function-p dst)
2927 (funcall collect
2928 (list trusrc
2929 (if (symbolp (second dst))
2930 (fdefinition (second dst))
2931 (eval (second dst))))))
2932 ((eq dst t)
2933 (funcall collect (list trusrc t)))
2935 (let* ((trudst (make-pathname
2936 :defaults (if dst (resolve-location dst t) trusrc)))
2937 (wilddst (make-pathname
2938 :name :wild :type :wild :version :wild
2939 :defaults trudst)))
2940 (funcall collect (list wilddst t))
2941 (funcall collect (list trusrc trudst)))))))))))
2943 (defun* compute-output-translations (&optional parameter)
2944 "read the configuration, return it"
2945 (remove-duplicates
2946 (while-collecting (c)
2947 (inherit-output-translations
2948 `(wrapping-output-translations ,parameter ,@*default-output-translations*) :collect #'c))
2949 :test 'equal :from-end t))
2951 (defun* initialize-output-translations (&optional parameter)
2952 "read the configuration, initialize the internal configuration variable,
2953 return the configuration"
2954 (setf (output-translations) (compute-output-translations parameter)))
2956 (defun* disable-output-translations ()
2957 "Initialize output translations in a way that maps every file to itself,
2958 effectively disabling the output translation facility."
2959 (initialize-output-translations
2960 '(:output-translations :disable-cache :ignore-inherited-configuration)))
2962 ;; checks an initial variable to see whether the state is initialized
2963 ;; or cleared. In the former case, return current configuration; in
2964 ;; the latter, initialize. ASDF will call this function at the start
2965 ;; of (asdf:find-system).
2966 (defun* ensure-output-translations ()
2967 (if (output-translations-initialized-p)
2968 (output-translations)
2969 (initialize-output-translations)))
2971 (defun* translate-pathname* (path absolute-source destination &optional root source)
2972 (declare (ignore source))
2973 (cond
2974 ((functionp destination)
2975 (funcall destination path absolute-source))
2976 ((eq destination t)
2977 path)
2978 ((not (pathnamep destination))
2979 (error "invalid destination"))
2980 ((not (absolute-pathname-p destination))
2981 (translate-pathname path absolute-source (merge-pathnames* destination root)))
2982 (root
2983 (translate-pathname (directorize-pathname-host-device path) absolute-source destination))
2985 (translate-pathname path absolute-source destination))))
2987 (defun* apply-output-translations (path)
2988 (etypecase path
2989 (logical-pathname
2990 path)
2991 ((or pathname string)
2992 (ensure-output-translations)
2993 (loop :with p = (truenamize path)
2994 :for (source destination) :in (car *output-translations*)
2995 :for root = (when (or (eq source t)
2996 (and (pathnamep source)
2997 (not (absolute-pathname-p source))))
2998 (pathname-root p))
2999 :for absolute-source = (cond
3000 ((eq source t) (wilden root))
3001 (root (merge-pathnames* source root))
3002 (t source))
3003 :when (or (eq source t) (pathname-match-p p absolute-source))
3004 :return (translate-pathname* p absolute-source destination root source)
3005 :finally (return p)))))
3007 (defmethod output-files :around (operation component)
3008 "Translate output files, unless asked not to"
3009 (declare (ignorable operation component))
3010 (values
3011 (multiple-value-bind (files fixedp) (call-next-method)
3012 (if fixedp
3013 files
3014 (mapcar #'apply-output-translations files)))
3017 (defun* compile-file-pathname* (input-file &rest keys &key output-file &allow-other-keys)
3018 (or output-file
3019 (apply-output-translations
3020 (apply 'compile-file-pathname
3021 (truenamize (lispize-pathname input-file))
3022 keys))))
3024 (defun* tmpize-pathname (x)
3025 (make-pathname
3026 :name (format nil "ASDF-TMP-~A" (pathname-name x))
3027 :defaults x))
3029 (defun* delete-file-if-exists (x)
3030 (when (and x (probe-file x))
3031 (delete-file x)))
3033 (defun* compile-file* (input-file &rest keys &key &allow-other-keys)
3034 (let* ((output-file (apply 'compile-file-pathname* input-file keys))
3035 (tmp-file (tmpize-pathname output-file))
3036 (status :error))
3037 (multiple-value-bind (output-truename warnings-p failure-p)
3038 (apply 'compile-file input-file :output-file tmp-file keys)
3039 (cond
3040 (failure-p
3041 (setf status *compile-file-failure-behaviour*))
3042 (warnings-p
3043 (setf status *compile-file-warnings-behaviour*))
3045 (setf status :success)))
3046 (ecase status
3047 ((:success :warn :ignore)
3048 (delete-file-if-exists output-file)
3049 (when output-truename
3050 (rename-file output-truename output-file)
3051 (setf output-truename output-file)))
3052 (:error
3053 (delete-file-if-exists output-truename)
3054 (setf output-truename nil)))
3055 (values output-truename warnings-p failure-p))))
3057 #+abcl
3058 (defun* translate-jar-pathname (source wildcard)
3059 (declare (ignore wildcard))
3060 (let* ((p (pathname (first (pathname-device source))))
3061 (root (format nil "/___jar___file___root___/~@[~A/~]"
3062 (and (find :windows *features*)
3063 (pathname-device p)))))
3064 (apply-output-translations
3065 (merge-pathnames*
3066 (relativize-pathname-directory source)
3067 (merge-pathnames*
3068 (relativize-pathname-directory (ensure-directory-pathname p))
3069 root)))))
3071 ;;;; -----------------------------------------------------------------
3072 ;;;; Compatibility mode for ASDF-Binary-Locations
3074 (defun* enable-asdf-binary-locations-compatibility
3075 (&key
3076 (centralize-lisp-binaries nil)
3077 (default-toplevel-directory
3078 ;; Use ".cache/common-lisp" instead ???
3079 (merge-pathnames* (make-pathname :directory '(:relative ".fasls"))
3080 (user-homedir)))
3081 (include-per-user-information nil)
3082 (map-all-source-files nil)
3083 (source-to-target-mappings nil))
3084 (let* ((fasl-type (pathname-type (compile-file-pathname "foo.lisp")))
3085 (wild-inferiors (make-pathname :directory '(:relative :wild-inferiors)))
3086 (mapped-files (make-pathname
3087 :name :wild :version :wild
3088 :type (if map-all-source-files :wild fasl-type)))
3089 (destination-directory
3090 (if centralize-lisp-binaries
3091 `(,default-toplevel-directory
3092 ,@(when include-per-user-information
3093 (cdr (pathname-directory (user-homedir))))
3094 :implementation ,wild-inferiors)
3095 `(:root ,wild-inferiors :implementation))))
3096 (initialize-output-translations
3097 `(:output-translations
3098 ,@source-to-target-mappings
3099 ((:root ,wild-inferiors ,mapped-files)
3100 (,@destination-directory ,mapped-files))
3101 (t t)
3102 :ignore-inherited-configuration))))
3104 ;;;; -----------------------------------------------------------------
3105 ;;;; Windows shortcut support. Based on:
3106 ;;;;
3107 ;;;; Jesse Hager: The Windows Shortcut File Format.
3108 ;;;; http://www.wotsit.org/list.asp?fc=13
3110 #+(and (or win32 windows mswindows mingw32) (not cygwin) (not clisp))
3111 (progn
3112 (defparameter *link-initial-dword* 76)
3113 (defparameter *link-guid* #(1 20 2 0 0 0 0 0 192 0 0 0 0 0 0 70))
3115 (defun* read-null-terminated-string (s)
3116 (with-output-to-string (out)
3117 (loop :for code = (read-byte s)
3118 :until (zerop code)
3119 :do (write-char (code-char code) out))))
3121 (defun* read-little-endian (s &optional (bytes 4))
3122 (loop
3123 :for i :from 0 :below bytes
3124 :sum (ash (read-byte s) (* 8 i))))
3126 (defun* parse-file-location-info (s)
3127 (let ((start (file-position s))
3128 (total-length (read-little-endian s))
3129 (end-of-header (read-little-endian s))
3130 (fli-flags (read-little-endian s))
3131 (local-volume-offset (read-little-endian s))
3132 (local-offset (read-little-endian s))
3133 (network-volume-offset (read-little-endian s))
3134 (remaining-offset (read-little-endian s)))
3135 (declare (ignore total-length end-of-header local-volume-offset))
3136 (unless (zerop fli-flags)
3137 (cond
3138 ((logbitp 0 fli-flags)
3139 (file-position s (+ start local-offset)))
3140 ((logbitp 1 fli-flags)
3141 (file-position s (+ start
3142 network-volume-offset
3143 #x14))))
3144 (concatenate 'string
3145 (read-null-terminated-string s)
3146 (progn
3147 (file-position s (+ start remaining-offset))
3148 (read-null-terminated-string s))))))
3150 (defun* parse-windows-shortcut (pathname)
3151 (with-open-file (s pathname :element-type '(unsigned-byte 8))
3152 (handler-case
3153 (when (and (= (read-little-endian s) *link-initial-dword*)
3154 (let ((header (make-array (length *link-guid*))))
3155 (read-sequence header s)
3156 (equalp header *link-guid*)))
3157 (let ((flags (read-little-endian s)))
3158 (file-position s 76) ;skip rest of header
3159 (when (logbitp 0 flags)
3160 ;; skip shell item id list
3161 (let ((length (read-little-endian s 2)))
3162 (file-position s (+ length (file-position s)))))
3163 (cond
3164 ((logbitp 1 flags)
3165 (parse-file-location-info s))
3167 (when (logbitp 2 flags)
3168 ;; skip description string
3169 (let ((length (read-little-endian s 2)))
3170 (file-position s (+ length (file-position s)))))
3171 (when (logbitp 3 flags)
3172 ;; finally, our pathname
3173 (let* ((length (read-little-endian s 2))
3174 (buffer (make-array length)))
3175 (read-sequence buffer s)
3176 (map 'string #'code-char buffer)))))))
3177 (end-of-file ()
3178 nil)))))
3180 ;;;; -----------------------------------------------------------------
3181 ;;;; Source Registry Configuration, by Francois-Rene Rideau
3182 ;;;; See the Manual and https://bugs.launchpad.net/asdf/+bug/485918
3184 ;; Using ack 1.2 exclusions
3185 (defvar *default-source-registry-exclusions*
3186 '(".bzr" ".cdv" "~.dep" "~.dot" "~.nib" "~.plst"
3187 ".git" ".hg" ".pc" ".svn" "CVS" "RCS" "SCCS" "_darcs"
3188 "_sgbak" "autom4te.cache" "cover_db" "_build"
3189 "debian")) ;; debian often build stuff under the debian directory... BAD.
3191 (defvar *source-registry-exclusions* *default-source-registry-exclusions*)
3193 (defvar *source-registry* ()
3194 "Either NIL (for uninitialized), or a list of one element,
3195 said element itself being a list of directory pathnames where to look for .asd files")
3197 (defun* source-registry ()
3198 (car *source-registry*))
3200 (defun* (setf source-registry) (new-value)
3201 (setf *source-registry* (list new-value))
3202 new-value)
3204 (defun* source-registry-initialized-p ()
3205 (and *source-registry* t))
3207 (defun* clear-source-registry ()
3208 "Undoes any initialization of the source registry.
3209 You might want to call that before you dump an image that would be resumed
3210 with a different configuration, so the configuration would be re-read then."
3211 (setf *source-registry* '())
3212 (values))
3214 (defun* validate-source-registry-directive (directive)
3215 (unless
3216 (or (member directive '(:default-registry (:default-registry)) :test 'equal)
3217 (destructuring-bind (kw &rest rest) directive
3218 (case kw
3219 ((:include :directory :tree)
3220 (and (length=n-p rest 1)
3221 (typep (car rest) '(or pathname string null))))
3222 ((:exclude :also-exclude)
3223 (every #'stringp rest))
3224 (null rest))))
3225 (error "Invalid directive ~S~%" directive))
3226 directive)
3228 (defun* validate-source-registry-form (form)
3229 (validate-configuration-form
3230 form :source-registry 'validate-source-registry-directive "a source registry"))
3232 (defun* validate-source-registry-file (file)
3233 (validate-configuration-file
3234 file 'validate-source-registry-form "a source registry"))
3236 (defun* validate-source-registry-directory (directory)
3237 (validate-configuration-directory
3238 directory :source-registry 'validate-source-registry-directive))
3240 (defun* parse-source-registry-string (string)
3241 (cond
3242 ((or (null string) (equal string ""))
3243 '(:source-registry :inherit-configuration))
3244 ((not (stringp string))
3245 (error "environment string isn't: ~S" string))
3246 ((find (char string 0) "\"(")
3247 (validate-source-registry-form (read-from-string string)))
3249 (loop
3250 :with inherit = nil
3251 :with directives = ()
3252 :with start = 0
3253 :with end = (length string)
3254 :for pos = (position *inter-directory-separator* string :start start) :do
3255 (let ((s (subseq string start (or pos end))))
3256 (cond
3257 ((equal "" s) ; empty element: inherit
3258 (when inherit
3259 (error "only one inherited configuration allowed: ~S" string))
3260 (setf inherit t)
3261 (push ':inherit-configuration directives))
3262 ((ends-with s "//")
3263 (push `(:tree ,(subseq s 0 (1- (length s)))) directives))
3265 (push `(:directory ,s) directives)))
3266 (cond
3267 (pos
3268 (setf start (1+ pos)))
3270 (unless inherit
3271 (push '(:ignore-inherited-configuration) directives))
3272 (return `(:source-registry ,@(nreverse directives))))))))))
3274 (defun* register-asd-directory (directory &key recurse exclude collect)
3275 (if (not recurse)
3276 (funcall collect directory)
3277 (let* ((files
3278 (handler-case
3279 (directory (merge-pathnames* *wild-asd* directory)
3280 #+sbcl #+sbcl :resolve-symlinks nil
3281 #+clisp #+clisp :circle t)
3282 (error (c)
3283 (warn "Error while scanning system definitions under directory ~S:~%~A"
3284 directory c)
3285 nil)))
3286 (dirs (remove-duplicates (mapcar #'pathname-directory-pathname files)
3287 :test #'equal :from-end t)))
3288 (loop
3289 :for dir :in dirs
3290 :unless (loop :for x :in exclude
3291 :thereis (find x (pathname-directory dir) :test #'equal))
3292 :do (funcall collect dir)))))
3294 (defparameter *default-source-registries*
3295 '(environment-source-registry
3296 user-source-registry
3297 user-source-registry-directory
3298 system-source-registry
3299 system-source-registry-directory
3300 default-source-registry))
3302 (defparameter *source-registry-file* #p"source-registry.conf")
3303 (defparameter *source-registry-directory* #p"source-registry.conf.d/")
3305 (defun* wrapping-source-registry ()
3306 `(:source-registry
3307 #+sbcl (:tree ,(getenv "SBCL_HOME"))
3308 :inherit-configuration
3309 #+cmu (:tree #p"modules:")))
3310 (defun* default-source-registry ()
3311 (flet ((try (x sub) (try-directory-subpath x sub :type :directory)))
3312 `(:source-registry
3313 #+sbcl (:directory ,(merge-pathnames* ".sbcl/systems/" (user-homedir)))
3314 (:directory ,(truenamize (directory-namestring *default-pathname-defaults*)))
3315 ,@(let*
3316 #+(or unix cygwin)
3317 ((datahome
3318 (or (getenv "XDG_DATA_HOME")
3319 (try (user-homedir) ".local/share/")))
3320 (datadirs
3321 (or (getenv "XDG_DATA_DIRS") "/usr/local/share:/usr/share"))
3322 (dirs (cons datahome (split-string datadirs :separator ":"))))
3323 #+(and (or win32 windows mswindows mingw32) (not cygwin))
3324 ((datahome (getenv "APPDATA"))
3325 (datadir
3326 #+lispworks (sys:get-folder-path :local-appdata)
3327 #-lispworks (try (getenv "ALLUSERSPROFILE")
3328 "Application Data"))
3329 (dirs (list datahome datadir)))
3330 #-(or unix win32 windows mswindows mingw32 cygwin)
3331 ((dirs ()))
3332 (loop :for dir :in dirs
3333 :collect `(:directory ,(try dir "common-lisp/systems/"))
3334 :collect `(:tree ,(try dir "common-lisp/source/"))))
3335 :inherit-configuration)))
3336 (defun* user-source-registry ()
3337 (in-user-configuration-directory *source-registry-file*))
3338 (defun* system-source-registry ()
3339 (in-system-configuration-directory *source-registry-file*))
3340 (defun* user-source-registry-directory ()
3341 (in-user-configuration-directory *source-registry-directory*))
3342 (defun* system-source-registry-directory ()
3343 (in-system-configuration-directory *source-registry-directory*))
3344 (defun* environment-source-registry ()
3345 (getenv "CL_SOURCE_REGISTRY"))
3347 (defgeneric* process-source-registry (spec &key inherit register))
3348 (declaim (ftype (function (t &key (:register (or symbol function))) t)
3349 inherit-source-registry))
3350 (declaim (ftype (function (t &key (:register (or symbol function)) (:inherit list)) t)
3351 process-source-registry-directive))
3353 (defmethod process-source-registry ((x symbol) &key inherit register)
3354 (process-source-registry (funcall x) :inherit inherit :register register))
3355 (defmethod process-source-registry ((pathname pathname) &key inherit register)
3356 (cond
3357 ((directory-pathname-p pathname)
3358 (process-source-registry (validate-source-registry-directory pathname)
3359 :inherit inherit :register register))
3360 ((probe-file pathname)
3361 (process-source-registry (validate-source-registry-file pathname)
3362 :inherit inherit :register register))
3364 (inherit-source-registry inherit :register register))))
3365 (defmethod process-source-registry ((string string) &key inherit register)
3366 (process-source-registry (parse-source-registry-string string)
3367 :inherit inherit :register register))
3368 (defmethod process-source-registry ((x null) &key inherit register)
3369 (declare (ignorable x))
3370 (inherit-source-registry inherit :register register))
3371 (defmethod process-source-registry ((form cons) &key inherit register)
3372 (let ((*source-registry-exclusions* *default-source-registry-exclusions*))
3373 (dolist (directive (cdr (validate-source-registry-form form)))
3374 (process-source-registry-directive directive :inherit inherit :register register))))
3376 (defun* inherit-source-registry (inherit &key register)
3377 (when inherit
3378 (process-source-registry (first inherit) :register register :inherit (rest inherit))))
3380 (defun* process-source-registry-directive (directive &key inherit register)
3381 (destructuring-bind (kw &rest rest) (if (consp directive) directive (list directive))
3382 (ecase kw
3383 ((:include)
3384 (destructuring-bind (pathname) rest
3385 (process-source-registry (pathname pathname) :inherit nil :register register)))
3386 ((:directory)
3387 (destructuring-bind (pathname) rest
3388 (when pathname
3389 (funcall register (ensure-directory-pathname pathname)))))
3390 ((:tree)
3391 (destructuring-bind (pathname) rest
3392 (when pathname
3393 (funcall register (ensure-directory-pathname pathname) :recurse t :exclude *source-registry-exclusions*))))
3394 ((:exclude)
3395 (setf *source-registry-exclusions* rest))
3396 ((:also-exclude)
3397 (appendf *source-registry-exclusions* rest))
3398 ((:default-registry)
3399 (inherit-source-registry '(default-source-registry) :register register))
3400 ((:inherit-configuration)
3401 (inherit-source-registry inherit :register register))
3402 ((:ignore-inherited-configuration)
3403 nil)))
3404 nil)
3406 (defun* flatten-source-registry (&optional parameter)
3407 (remove-duplicates
3408 (while-collecting (collect)
3409 (inherit-source-registry
3410 `(wrapping-source-registry
3411 ,parameter
3412 ,@*default-source-registries*)
3413 :register (lambda (directory &key recurse exclude)
3414 (collect (list directory :recurse recurse :exclude exclude)))))
3415 :test 'equal :from-end t))
3417 ;; Will read the configuration and initialize all internal variables,
3418 ;; and return the new configuration.
3419 (defun* compute-source-registry (&optional parameter)
3420 (while-collecting (collect)
3421 (dolist (entry (flatten-source-registry parameter))
3422 (destructuring-bind (directory &key recurse exclude) entry
3423 (register-asd-directory
3424 directory
3425 :recurse recurse :exclude exclude :collect #'collect)))))
3427 (defun* initialize-source-registry (&optional parameter)
3428 (setf (source-registry) (compute-source-registry parameter)))
3430 ;; Checks an initial variable to see whether the state is initialized
3431 ;; or cleared. In the former case, return current configuration; in
3432 ;; the latter, initialize. ASDF will call this function at the start
3433 ;; of (asdf:find-system) to make sure the source registry is initialized.
3434 ;; However, it will do so *without* a parameter, at which point it
3435 ;; will be too late to provide a parameter to this function, though
3436 ;; you may override the configuration explicitly by calling
3437 ;; initialize-source-registry directly with your parameter.
3438 (defun* ensure-source-registry (&optional parameter)
3439 (if (source-registry-initialized-p)
3440 (source-registry)
3441 (initialize-source-registry parameter)))
3443 (defun* sysdef-source-registry-search (system)
3444 (ensure-source-registry)
3445 (loop :with name = (coerce-name system)
3446 :for defaults :in (source-registry)
3447 :for file = (probe-asd name defaults)
3448 :when file :return file))
3450 (defun* clear-configuration ()
3451 (clear-source-registry)
3452 (clear-output-translations))
3454 ;;;; -----------------------------------------------------------------
3455 ;;;; Hook into REQUIRE for ABCL, ClozureCL, CMUCL, ECL and SBCL
3456 ;;;;
3457 (defun* module-provide-asdf (name)
3458 (handler-bind
3459 ((style-warning #'muffle-warning)
3460 (missing-component (constantly nil))
3461 (error (lambda (e)
3462 (format *error-output* "ASDF could not load ~(~A~) because ~A.~%"
3463 name e))))
3464 (let* ((*verbose-out* (make-broadcast-stream))
3465 (system (find-system (string-downcase name) nil)))
3466 (when system
3467 (load-system system)
3468 t))))
3470 #+(or abcl clisp clozure cmu ecl sbcl)
3471 (let ((x (and #+clisp (find-symbol "*MODULE-PROVIDER-FUNCTIONS*" :custom))))
3472 (when x
3473 (eval `(pushnew 'module-provide-asdf
3474 #+abcl sys::*module-provider-functions*
3475 #+clisp ,x
3476 #+clozure ccl:*module-provider-functions*
3477 #+cmu ext:*module-provider-functions*
3478 #+ecl si:*module-provider-functions*
3479 #+sbcl sb-ext:*module-provider-functions*))))
3482 ;;;; -------------------------------------------------------------------------
3483 ;;;; Cleanups after hot-upgrade.
3484 ;;;; Things to do in case we're upgrading from a previous version of ASDF.
3485 ;;;; See https://bugs.launchpad.net/asdf/+bug/485687
3486 ;;;;
3487 ;;;; TODO: debug why it's not enough to upgrade from ECL <= 9.11.1
3488 (eval-when (:compile-toplevel :load-toplevel :execute)
3489 #+ecl ;; Support upgrade from before ECL went to 1.369
3490 (when (fboundp 'compile-op-system-p)
3491 (defmethod compile-op-system-p ((op compile-op))
3492 (getf :system-p (compile-op-flags op)))
3493 (defmethod initialize-instance :after ((op compile-op)
3494 &rest initargs
3495 &key system-p &allow-other-keys)
3496 (declare (ignorable initargs))
3497 (when system-p (appendf (compile-op-flags op) (list :system-p system-p))))))
3499 ;;;; -----------------------------------------------------------------
3500 ;;;; Done!
3501 (when *load-verbose*
3502 (asdf-message ";; ASDF, version ~a~%" (asdf-version)))
3504 #+allegro
3505 (eval-when (:compile-toplevel :execute)
3506 (when (boundp 'excl:*warn-on-nested-reader-conditionals*)
3507 (setf excl:*warn-on-nested-reader-conditionals* *acl-warn-save*)))
3509 (pushnew :asdf *features*)
3510 (pushnew :asdf2 *features*)
3512 (provide :asdf)
3514 ;;; Local Variables:
3515 ;;; mode: lisp
3516 ;;; End: