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