source: branches/1.0.x/abcl/src/org/armedbear/lisp/asdf.lisp

Last change on this file was 13718, checked in by Mark Evenson, 12 years ago

backport r13704: Fix problems loading ABCL-CONTRIB.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 182.3 KB
Line 
1;;; -*- mode: Common-Lisp; Base: 10 ; Syntax: ANSI-Common-Lisp -*-
2;;; This is ASDF 2.019: 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 master
14;;; branch is the latest development version, whereas the git release
15;;; branch 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-2011 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 #-genera :common-lisp-user #+genera :future-common-lisp-user)
51
52#-(or abcl allegro clisp clozure cmu cormanlisp ecl gcl genera lispworks mcl sbcl scl xcl)
53(error "ASDF is not supported on your implementation. Please help us port it.")
54
55#+gcl (defpackage :asdf (:use :cl)) ;; GCL treats defpackage magically and needs this
56
57(eval-when (:compile-toplevel :load-toplevel :execute)
58  ;;; Implementation-dependent tweaks
59  ;; (declaim (optimize (speed 1) (debug 3) (safety 3))) ; NO: trust implementation defaults.
60  #+allegro
61  (setf excl::*autoload-package-name-alist*
62        (remove "asdf" excl::*autoload-package-name-alist*
63                :test 'equalp :key 'car)) ; need that BEFORE any mention of package ASDF as below
64  #+ecl (unless (member :ecl-bytecmp *features*) (require :cmp))
65  #+gcl ;; Debian's GCL 2.7 has bugs with compiling multiple-value stuff, but can run ASDF 2.011
66  (when (or (< system::*gcl-major-version* 2) ;; GCL 2.6 fails to fully compile ASDF at all
67            (and (= system::*gcl-major-version* 2)
68                 (< system::*gcl-minor-version* 7)))
69    (pushnew :gcl-pre2.7 *features*))
70  ;;; make package if it doesn't exist yet.
71  ;;; DEFPACKAGE may cause errors on discrepancies, so we avoid it.
72  (unless (find-package :asdf)
73    (make-package :asdf :use '(:common-lisp))))
74
75(in-package :asdf)
76
77;;;; Create packages in a way that is compatible with hot-upgrade.
78;;;; See https://bugs.launchpad.net/asdf/+bug/485687
79;;;; See more near the end of the file.
80
81(eval-when (:load-toplevel :compile-toplevel :execute)
82  (defvar *asdf-version* nil)
83  (defvar *upgraded-p* nil)
84  (defvar *asdf-verbose* nil) ; was t from 2.000 to 2.014.12.
85  (defun find-symbol* (s p)
86    (find-symbol (string s) p))
87  ;; Strip out formatting that is not supported on Genera.
88  ;; Has to be inside the eval-when to make Lispworks happy (!)
89  (defun strcat (&rest strings)
90    (apply 'concatenate 'string strings))
91  (defmacro compatfmt (format)
92    #-(or gcl genera) format
93    #+(or gcl genera)
94    (loop :for (unsupported . replacement) :in
95      `(("~3i~_" . "")
96        #+genera
97        ,@(("~@<" . "")
98           ("; ~@;" . "; ")
99           ("~@:>" . "")
100           ("~:>" . ""))) :do
101      (loop :for found = (search unsupported format) :while found :do
102        (setf format (strcat (subseq format 0 found) replacement
103                             (subseq format (+ found (length unsupported)))))))
104    format)
105  (let* (;; For bug reporting sanity, please always bump this version when you modify this file.
106         ;; Please also modify asdf.asd to reflect this change. The script bin/bump-version
107         ;; can help you do these changes in synch (look at the source for documentation).
108         ;; Relying on its automation, the version is now redundantly present on top of this file.
109         ;; "2.345" would be an official release
110         ;; "2.345.6" would be a development version in the official upstream
111         ;; "2.345.0.7" would be your seventh local modification of official release 2.345
112         ;; "2.345.6.7" would be your seventh local modification of development version 2.345.6
113         (asdf-version "2.019")
114         (existing-asdf (find-class 'component nil))
115         (existing-version *asdf-version*)
116         (already-there (equal asdf-version existing-version)))
117    (unless (and existing-asdf already-there)
118      (when (and existing-asdf *asdf-verbose*)
119        (format *trace-output*
120                (compatfmt "~&~@<; ~@;Upgrading ASDF ~@[from version ~A ~]to version ~A~@:>~%")
121                existing-version asdf-version))
122      (labels
123          ((present-symbol-p (symbol package)
124             (member (nth-value 1 (find-symbol* symbol package)) '(:internal :external)))
125           (present-symbols (package)
126             ;; #-genera (loop :for s :being :the :present-symbols :in package :collect s) #+genera
127             (let (l)
128               (do-symbols (s package)
129                 (when (present-symbol-p s package) (push s l)))
130               (reverse l)))
131           (unlink-package (package)
132             (let ((u (find-package package)))
133               (when u
134                 (ensure-unintern u (present-symbols u))
135                 (loop :for p :in (package-used-by-list u) :do
136                   (unuse-package u p))
137                 (delete-package u))))
138           (ensure-exists (name nicknames use)
139             (let ((previous
140                    (remove-duplicates
141                     (mapcar #'find-package (cons name nicknames))
142                     :from-end t)))
143               ;; do away with packages with conflicting (nick)names
144               (map () #'unlink-package (cdr previous))
145               ;; reuse previous package with same name
146               (let ((p (car previous)))
147                 (cond
148                   (p
149                    (rename-package p name nicknames)
150                    (ensure-use p use)
151                    p)
152                   (t
153                    (make-package name :nicknames nicknames :use use))))))
154           (intern* (symbol package)
155             (intern (string symbol) package))
156           (remove-symbol (symbol package)
157             (let ((sym (find-symbol* symbol package)))
158               (when sym
159                 #-cormanlisp (unexport sym package)
160                 (unintern sym package)
161                 sym)))
162           (ensure-unintern (package symbols)
163             (loop :with packages = (list-all-packages)
164               :for sym :in symbols
165               :for removed = (remove-symbol sym package)
166               :when removed :do
167               (loop :for p :in packages :do
168                 (when (eq removed (find-symbol* sym p))
169                   (unintern removed p)))))
170           (ensure-shadow (package symbols)
171             (shadow symbols package))
172           (ensure-use (package use)
173             (dolist (used (reverse use))
174               (do-external-symbols (sym used)
175                 (unless (eq sym (find-symbol* sym package))
176                   (remove-symbol sym package)))
177               (use-package used package)))
178           (ensure-fmakunbound (package symbols)
179             (loop :for name :in symbols
180               :for sym = (find-symbol* name package)
181               :when sym :do (fmakunbound sym)))
182           (ensure-export (package export)
183             (let ((formerly-exported-symbols nil)
184                   (bothly-exported-symbols nil)
185                   (newly-exported-symbols nil))
186               (do-external-symbols (sym package)
187                 (if (member sym export :test 'string-equal)
188                     (push sym bothly-exported-symbols)
189                     (push sym formerly-exported-symbols)))
190               (loop :for sym :in export :do
191                 (unless (member sym bothly-exported-symbols :test 'equal)
192                   (push sym newly-exported-symbols)))
193               (loop :for user :in (package-used-by-list package)
194                 :for shadowing = (package-shadowing-symbols user) :do
195                 (loop :for new :in newly-exported-symbols
196                   :for old = (find-symbol* new user)
197                   :when (and old (not (member old shadowing)))
198                   :do (unintern old user)))
199               (loop :for x :in newly-exported-symbols :do
200                 (export (intern* x package)))))
201           (ensure-package (name &key nicknames use unintern
202                                 shadow export redefined-functions)
203             (let* ((p (ensure-exists name nicknames use)))
204               (ensure-unintern p unintern)
205               (ensure-shadow p shadow)
206               (ensure-export p export)
207               (ensure-fmakunbound p redefined-functions)
208               p)))
209        (macrolet
210            ((pkgdcl (name &key nicknames use export
211                           redefined-functions unintern shadow)
212                 `(ensure-package
213                   ',name :nicknames ',nicknames :use ',use :export ',export
214                   :shadow ',shadow
215                   :unintern ',unintern
216                   :redefined-functions ',redefined-functions)))
217          (pkgdcl
218           :asdf
219           :nicknames (:asdf-utilities) ;; DEPRECATED! Do not use, for backward compatibility only.
220           :use (:common-lisp)
221           :redefined-functions
222           (#:perform #:explain #:output-files #:operation-done-p
223            #:perform-with-restarts #:component-relative-pathname
224            #:system-source-file #:operate #:find-component #:find-system
225            #:apply-output-translations #:translate-pathname* #:resolve-location
226            #:system-relative-pathname
227            #:inherit-source-registry #:process-source-registry
228            #:process-source-registry-directive
229            #:compile-file* #:source-file-type)
230           :unintern
231           (#:*asdf-revision* #:around #:asdf-method-combination
232            #:split #:make-collector #:do-dep #:do-one-dep
233            #:resolve-relative-location-component #:resolve-absolute-location-component
234            #:output-files-for-system-and-operation) ; obsolete ASDF-BINARY-LOCATION function
235           :export
236           (#:defsystem #:oos #:operate #:find-system #:locate-system #:run-shell-command
237            #:system-definition-pathname #:with-system-definitions
238            #:search-for-system-definition #:find-component #:component-find-path
239            #:compile-system #:load-system #:load-systems #:test-system #:clear-system
240            #:operation #:compile-op #:load-op #:load-source-op #:test-op
241            #:feature #:version #:version-satisfies
242            #:upgrade-asdf
243            #:implementation-identifier #:implementation-type
244            #:input-files #:output-files #:output-file #:perform
245            #:operation-done-p #:explain
246
247            #:component #:source-file
248            #:c-source-file #:cl-source-file #:java-source-file
249            #:cl-source-file.cl #:cl-source-file.lsp
250            #:static-file
251            #:doc-file
252            #:html-file
253            #:text-file
254            #:source-file-type
255            #:module                     ; components
256            #:system
257            #:unix-dso
258
259            #:module-components          ; component accessors
260            #:module-components-by-name  ; component accessors
261            #:component-pathname
262            #:component-relative-pathname
263            #:component-name
264            #:component-version
265            #:component-parent
266            #:component-property
267            #:component-system
268
269            #:component-depends-on
270
271            #:system-description
272            #:system-long-description
273            #:system-author
274            #:system-maintainer
275            #:system-license
276            #:system-licence
277            #:system-source-file
278            #:system-source-directory
279            #:system-relative-pathname
280            #:map-systems
281
282            #:operation-description
283            #:operation-on-warnings
284            #:operation-on-failure
285            #:component-visited-p
286            ;;#:*component-parent-pathname*
287            #:*system-definition-search-functions*
288            #:*central-registry*         ; variables
289            #:*compile-file-warnings-behaviour*
290            #:*compile-file-failure-behaviour*
291            #:*resolve-symlinks*
292            #:*require-asdf-operator*
293            #:*asdf-verbose*
294            #:*verbose-out*
295
296            #:asdf-version
297
298            #:operation-error #:compile-failed #:compile-warned #:compile-error
299            #:error-name
300            #:error-pathname
301            #:load-system-definition-error
302            #:error-component #:error-operation
303            #:system-definition-error
304            #:missing-component
305            #:missing-component-of-version
306            #:missing-dependency
307            #:missing-dependency-of-version
308            #:circular-dependency        ; errors
309            #:duplicate-names
310
311            #:try-recompiling
312            #:retry
313            #:accept                     ; restarts
314            #:coerce-entry-to-directory
315            #:remove-entry-from-registry
316
317            #:clear-configuration
318            #:*output-translations-parameter*
319            #:initialize-output-translations
320            #:disable-output-translations
321            #:clear-output-translations
322            #:ensure-output-translations
323            #:apply-output-translations
324            #:compile-file*
325            #:compile-file-pathname*
326            #:enable-asdf-binary-locations-compatibility
327            #:*default-source-registries*
328            #:*source-registry-parameter*
329            #:initialize-source-registry
330            #:compute-source-registry
331            #:clear-source-registry
332            #:ensure-source-registry
333            #:process-source-registry
334            #:system-registered-p
335            #:asdf-message
336            #:user-output-translations-pathname
337            #:system-output-translations-pathname
338            #:user-output-translations-directory-pathname
339            #:system-output-translations-directory-pathname
340            #:user-source-registry
341            #:system-source-registry
342            #:user-source-registry-directory
343            #:system-source-registry-directory
344
345            ;; Utilities
346            #:absolute-pathname-p
347            ;; #:aif #:it
348            ;; #:appendf #:orf
349            #:coerce-name
350            #:directory-pathname-p
351            ;; #:ends-with
352            #:ensure-directory-pathname
353            #:getenv
354            ;; #:length=n-p
355            ;; #:find-symbol*
356            #:merge-pathnames* #:coerce-pathname #:subpathname
357            #:pathname-directory-pathname
358            #:read-file-forms
359            ;; #:remove-keys
360            ;; #:remove-keyword
361            #:resolve-symlinks
362            #:split-string
363            #:component-name-to-pathname-components
364            #:split-name-type
365            #:subdirectories
366            #:truenamize
367            #:while-collecting)))
368        #+genera (import 'scl:boolean :asdf)
369        (setf *asdf-version* asdf-version
370              *upgraded-p* (if existing-version
371                               (cons existing-version *upgraded-p*)
372                               *upgraded-p*))))))
373
374;;;; -------------------------------------------------------------------------
375;;;; User-visible parameters
376;;;;
377(defvar *resolve-symlinks* t
378  "Determine whether or not ASDF resolves symlinks when defining systems.
379
380Defaults to T.")
381
382(defvar *compile-file-warnings-behaviour*
383  (or #+clisp :ignore :warn)
384  "How should ASDF react if it encounters a warning when compiling a file?
385Valid values are :error, :warn, and :ignore.")
386
387(defvar *compile-file-failure-behaviour*
388  (or #+sbcl :error #+clisp :ignore :warn)
389  "How should ASDF react if it encounters a failure (per the ANSI spec of COMPILE-FILE)
390when compiling a file?  Valid values are :error, :warn, and :ignore.
391Note that ASDF ALWAYS raises an error if it fails to create an output file when compiling.")
392
393(defvar *verbose-out* nil)
394
395(defparameter +asdf-methods+
396  '(perform-with-restarts perform explain output-files operation-done-p))
397
398#+allegro
399(eval-when (:compile-toplevel :execute)
400  (defparameter *acl-warn-save*
401                (when (boundp 'excl:*warn-on-nested-reader-conditionals*)
402                  excl:*warn-on-nested-reader-conditionals*))
403  (when (boundp 'excl:*warn-on-nested-reader-conditionals*)
404    (setf excl:*warn-on-nested-reader-conditionals* nil)))
405
406;;;; -------------------------------------------------------------------------
407;;;; Resolve forward references
408
409(declaim (ftype (function (t) t)
410                format-arguments format-control
411                error-name error-pathname error-condition
412                duplicate-names-name
413                error-component error-operation
414                module-components module-components-by-name
415                circular-dependency-components
416                condition-arguments condition-form
417                condition-format condition-location
418                coerce-name)
419         (ftype (function (&optional t) (values)) initialize-source-registry)
420         #-(or cormanlisp gcl-pre2.7)
421         (ftype (function (t t) t) (setf module-components-by-name)))
422
423;;;; -------------------------------------------------------------------------
424;;;; Compatibility various implementations
425#+cormanlisp
426(progn
427  (deftype logical-pathname () nil)
428  (defun make-broadcast-stream () *error-output*)
429  (defun file-namestring (p)
430    (setf p (pathname p))
431    (format nil "~@[~A~]~@[.~A~]" (pathname-name p) (pathname-type p))))
432
433#.(or #+mcl ;; the #$ doesn't work on other lisps, even protected by #+mcl
434      (read-from-string
435       "(eval-when (:compile-toplevel :load-toplevel :execute)
436          (ccl:define-entry-point (_getenv \"getenv\") ((name :string)) :string)
437          (ccl:define-entry-point (_system \"system\") ((name :string)) :int)
438          ;; Note: ASDF may expect user-homedir-pathname to provide
439          ;; the pathname of the current user's home directory, whereas
440          ;; MCL by default provides the directory from which MCL was started.
441          ;; See http://code.google.com/p/mcl/wiki/Portability
442          (defun current-user-homedir-pathname ()
443            (ccl::findfolder #$kuserdomain #$kCurrentUserFolderType))
444          (defun probe-posix (posix-namestring)
445            \"If a file exists for the posix namestring, return the pathname\"
446            (ccl::with-cstrs ((cpath posix-namestring))
447              (ccl::rlet ((is-dir :boolean)
448                          (fsref :fsref))
449                (when (eq #$noerr (#_fspathmakeref cpath fsref is-dir))
450                  (ccl::%path-from-fsref fsref is-dir))))))"))
451
452;;;; -------------------------------------------------------------------------
453;;;; General Purpose Utilities
454
455(macrolet
456    ((defdef (def* def)
457       `(defmacro ,def* (name formals &rest rest)
458          `(progn
459             #+(or ecl (and gcl (not gcl-pre2.7))) (fmakunbound ',name)
460             #-gcl ; gcl 2.7.0 notinline functions lose secondary return values :-(
461             ,(when (and #+ecl (symbolp name)) ; fails for setf functions on ecl
462                `(declaim (notinline ,name)))
463             (,',def ,name ,formals ,@rest)))))
464  (defdef defgeneric* defgeneric)
465  (defdef defun* defun))
466
467(defmacro while-collecting ((&rest collectors) &body body)
468  "COLLECTORS should be a list of names for collections.  A collector
469defines a function that, when applied to an argument inside BODY, will
470add its argument to the corresponding collection.  Returns multiple values,
471a list for each collection, in order.
472   E.g.,
473\(while-collecting \(foo bar\)
474           \(dolist \(x '\(\(a 1\) \(b 2\) \(c 3\)\)\)
475             \(foo \(first x\)\)
476             \(bar \(second x\)\)\)\)
477Returns two values: \(A B C\) and \(1 2 3\)."
478  (let ((vars (mapcar #'(lambda (x) (gensym (symbol-name x))) collectors))
479        (initial-values (mapcar (constantly nil) collectors)))
480    `(let ,(mapcar #'list vars initial-values)
481       (flet ,(mapcar #'(lambda (c v) `(,c (x) (push x ,v) (values))) collectors vars)
482         ,@body
483         (values ,@(mapcar #'(lambda (v) `(reverse ,v)) vars))))))
484
485(defmacro aif (test then &optional else)
486  `(let ((it ,test)) (if it ,then ,else)))
487
488(defun* pathname-directory-pathname (pathname)
489  "Returns a new pathname with same HOST, DEVICE, DIRECTORY as PATHNAME,
490and NIL NAME, TYPE and VERSION components"
491  (when pathname
492    (make-pathname :name nil :type nil :version nil :defaults pathname)))
493
494(defun* normalize-pathname-directory-component (directory)
495  (cond
496    #-(or cmu sbcl scl)
497    ((stringp directory) `(:absolute ,directory) directory)
498    #+gcl
499    ((and (consp directory) (stringp (first directory)))
500     `(:absolute ,@directory))
501    ((or (null directory)
502         (and (consp directory) (member (first directory) '(:absolute :relative))))
503     directory)
504    (t
505     (error (compatfmt "~@<Unrecognized pathname directory component ~S~@:>") directory))))
506
507(defun* merge-pathname-directory-components (specified defaults)
508  (let ((directory (normalize-pathname-directory-component specified)))
509    (ecase (first directory)
510      ((nil) defaults)
511      (:absolute specified)
512      (:relative
513       (let ((defdir (normalize-pathname-directory-component defaults))
514             (reldir (cdr directory)))
515         (cond
516           ((null defdir)
517            directory)
518           ((not (eq :back (first reldir)))
519            (append defdir reldir))
520           (t
521            (loop :with defabs = (first defdir)
522              :with defrev = (reverse (rest defdir))
523              :while (and (eq :back (car reldir))
524                          (or (and (eq :absolute defabs) (null defrev))
525                              (stringp (car defrev))))
526              :do (pop reldir) (pop defrev)
527              :finally (return (cons defabs (append (reverse defrev) reldir)))))))))))
528
529(defun* ununspecific (x)
530  (if (eq x :unspecific) nil x))
531
532(defun* merge-pathnames* (specified &optional (defaults *default-pathname-defaults*))
533  "MERGE-PATHNAMES* is like MERGE-PATHNAMES except that
534if the SPECIFIED pathname does not have an absolute directory,
535then the HOST and DEVICE both come from the DEFAULTS, whereas
536if the SPECIFIED pathname does have an absolute directory,
537then the HOST and DEVICE both come from the SPECIFIED.
538Also, if either argument is NIL, then the other argument is returned unmodified."
539  (when (null specified) (return-from merge-pathnames* defaults))
540  (when (null defaults) (return-from merge-pathnames* specified))
541  #+scl
542  (ext:resolve-pathname specified defaults)
543  #-scl
544  (let* ((specified (pathname specified))
545         (defaults (pathname defaults))
546         (directory (normalize-pathname-directory-component (pathname-directory specified)))
547         (name (or (pathname-name specified) (pathname-name defaults)))
548         (type (or (pathname-type specified) (pathname-type defaults)))
549         (version (or (pathname-version specified) (pathname-version defaults))))
550    (labels ((unspecific-handler (p)
551               (if (typep p 'logical-pathname) #'ununspecific #'identity)))
552      (multiple-value-bind (host device directory unspecific-handler)
553          (ecase (first directory)
554            ((:absolute)
555             (values (pathname-host specified)
556                     (pathname-device specified)
557                     directory
558                     (unspecific-handler specified)))
559            ((nil :relative)
560             (values (pathname-host defaults)
561                     (pathname-device defaults)
562                     (merge-pathname-directory-components directory (pathname-directory defaults))
563                     (unspecific-handler defaults))))
564        (make-pathname :host host :device device :directory directory
565                       :name (funcall unspecific-handler name)
566                       :type (funcall unspecific-handler type)
567                       :version (funcall unspecific-handler version))))))
568
569(defun* pathname-parent-directory-pathname (pathname)
570  "Returns a new pathname with same HOST, DEVICE, DIRECTORY as PATHNAME,
571and NIL NAME, TYPE and VERSION components"
572  (when pathname
573    (make-pathname :name nil :type nil :version nil
574                   :directory (merge-pathname-directory-components
575                               '(:relative :back) (pathname-directory pathname))
576                   :defaults pathname)))
577
578(define-modify-macro appendf (&rest args)
579  append "Append onto list") ;; only to be used on short lists.
580
581(define-modify-macro orf (&rest args)
582  or "or a flag")
583
584(defun* first-char (s)
585  (and (stringp s) (plusp (length s)) (char s 0)))
586
587(defun* last-char (s)
588  (and (stringp s) (plusp (length s)) (char s (1- (length s)))))
589
590
591(defun* asdf-message (format-string &rest format-args)
592  (declare (dynamic-extent format-args))
593  (apply 'format *verbose-out* format-string format-args))
594
595(defun* split-string (string &key max (separator '(#\Space #\Tab)))
596  "Split STRING into a list of components separated by
597any of the characters in the sequence SEPARATOR.
598If MAX is specified, then no more than max(1,MAX) components will be returned,
599starting the separation from the end, e.g. when called with arguments
600 \"a.b.c.d.e\" :max 3 :separator \".\" it will return (\"a.b.c\" \"d\" \"e\")."
601  (catch nil
602    (let ((list nil) (words 0) (end (length string)))
603      (flet ((separatorp (char) (find char separator))
604             (done () (throw nil (cons (subseq string 0 end) list))))
605        (loop
606          :for start = (if (and max (>= words (1- max)))
607                           (done)
608                           (position-if #'separatorp string :end end :from-end t)) :do
609          (when (null start)
610            (done))
611          (push (subseq string (1+ start) end) list)
612          (incf words)
613          (setf end start))))))
614
615(defun* split-name-type (filename)
616  (let ((unspecific
617         ;; Giving :unspecific as argument to make-pathname is not portable.
618         ;; See CLHS make-pathname and 19.2.2.2.3.
619         ;; We only use it on implementations that support it.
620         (or #+(or clozure gcl lispworks sbcl) :unspecific)))
621    (destructuring-bind (name &optional (type unspecific))
622        (split-string filename :max 2 :separator ".")
623      (if (equal name "")
624          (values filename unspecific)
625          (values name type)))))
626
627(defun* component-name-to-pathname-components (s &key force-directory force-relative)
628  "Splits the path string S, returning three values:
629A flag that is either :absolute or :relative, indicating
630   how the rest of the values are to be interpreted.
631A directory path --- a list of strings, suitable for
632   use with MAKE-PATHNAME when prepended with the flag
633   value.
634A filename with type extension, possibly NIL in the
635   case of a directory pathname.
636FORCE-DIRECTORY forces S to be interpreted as a directory
637pathname \(third return value will be NIL, final component
638of S will be treated as part of the directory path.
639
640The intention of this function is to support structured component names,
641e.g., \(:file \"foo/bar\"\), which will be unpacked to relative
642pathnames."
643  (check-type s string)
644  (when (find #\: s)
645    (error (compatfmt "~@<A portable ASDF pathname designator cannot include a #\: character: ~3i~_~S~@:>") s))
646  (let* ((components (split-string s :separator "/"))
647         (last-comp (car (last components))))
648    (multiple-value-bind (relative components)
649        (if (equal (first components) "")
650            (if (equal (first-char s) #\/)
651                (progn
652                  (when force-relative
653                    (error (compatfmt "~@<Absolute pathname designator not allowed: ~3i~_~S~@:>") s))
654                  (values :absolute (cdr components)))
655                (values :relative nil))
656          (values :relative components))
657      (setf components (remove-if #'(lambda (x) (member x '("" ".") :test #'equal)) components))
658      (setf components (substitute :back ".." components :test #'equal))
659      (cond
660        ((equal last-comp "")
661         (values relative components nil)) ; "" already removed
662        (force-directory
663         (values relative components nil))
664        (t
665         (values relative (butlast components) last-comp))))))
666
667(defun* remove-keys (key-names args)
668  (loop :for (name val) :on args :by #'cddr
669    :unless (member (symbol-name name) key-names
670                    :key #'symbol-name :test 'equal)
671    :append (list name val)))
672
673(defun* remove-keyword (key args)
674  (loop :for (k v) :on args :by #'cddr
675    :unless (eq k key)
676    :append (list k v)))
677
678(defun* getenv (x)
679  (declare (ignorable x))
680  #+(or abcl clisp ecl xcl) (ext:getenv x)
681  #+allegro (sys:getenv x)
682  #+clozure (ccl:getenv x)
683  #+(or cmu scl) (cdr (assoc x ext:*environment-list* :test #'string=))
684  #+cormanlisp
685  (let* ((buffer (ct:malloc 1))
686         (cname (ct:lisp-string-to-c-string x))
687         (needed-size (win:getenvironmentvariable cname buffer 0))
688         (buffer1 (ct:malloc (1+ needed-size))))
689    (prog1 (if (zerop (win:getenvironmentvariable cname buffer1 needed-size))
690               nil
691               (ct:c-string-to-lisp-string buffer1))
692      (ct:free buffer)
693      (ct:free buffer1)))
694  #+gcl (system:getenv x)
695  #+genera nil
696  #+lispworks (lispworks:environment-variable x)
697  #+mcl (ccl:with-cstrs ((name x))
698          (let ((value (_getenv name)))
699            (unless (ccl:%null-ptr-p value)
700              (ccl:%get-cstring value))))
701  #+sbcl (sb-ext:posix-getenv x)
702  #-(or abcl allegro clisp clozure cmu cormanlisp ecl gcl genera lispworks mcl sbcl scl xcl)
703  (error "~S is not supported on your implementation" 'getenv))
704
705(defun* directory-pathname-p (pathname)
706  "Does PATHNAME represent a directory?
707
708A directory-pathname is a pathname _without_ a filename. The three
709ways that the filename components can be missing are for it to be NIL,
710:UNSPECIFIC or the empty string.
711
712Note that this does _not_ check to see that PATHNAME points to an
713actually-existing directory."
714  (when pathname
715    (let ((pathname (pathname pathname)))
716      (flet ((check-one (x)
717               (member x '(nil :unspecific "") :test 'equal)))
718        (and (not (wild-pathname-p pathname))
719             (check-one (pathname-name pathname))
720             (check-one (pathname-type pathname))
721             t)))))
722
723(defun* ensure-directory-pathname (pathspec)
724  "Converts the non-wild pathname designator PATHSPEC to directory form."
725  (cond
726   ((stringp pathspec)
727    (ensure-directory-pathname (pathname pathspec)))
728   ((not (pathnamep pathspec))
729    (error (compatfmt "~@<Invalid pathname designator ~S~@:>") pathspec))
730   ((wild-pathname-p pathspec)
731    (error (compatfmt "~@<Can't reliably convert wild pathname ~3i~_~S~@:>") pathspec))
732   ((directory-pathname-p pathspec)
733    pathspec)
734   (t
735    (make-pathname :directory (append (or (pathname-directory pathspec)
736                                          (list :relative))
737                                      (list (file-namestring pathspec)))
738                   :name nil :type nil :version nil
739                   :defaults pathspec))))
740
741#+genera
742(unless (fboundp 'ensure-directories-exist)
743  (defun* ensure-directories-exist (path)
744    (fs:create-directories-recursively (pathname path))))
745
746(defun* absolute-pathname-p (pathspec)
747  (and (typep pathspec '(or pathname string))
748       (eq :absolute (car (pathname-directory (pathname pathspec))))))
749
750(defun* length=n-p (x n) ;is it that (= (length x) n) ?
751  (check-type n (integer 0 *))
752  (loop
753    :for l = x :then (cdr l)
754    :for i :downfrom n :do
755    (cond
756      ((zerop i) (return (null l)))
757      ((not (consp l)) (return nil)))))
758
759(defun* ends-with (s suffix)
760  (check-type s string)
761  (check-type suffix string)
762  (let ((start (- (length s) (length suffix))))
763    (and (<= 0 start)
764         (string-equal s suffix :start1 start))))
765
766(defun* read-file-forms (file)
767  (with-open-file (in file)
768    (loop :with eof = (list nil)
769     :for form = (read in nil eof)
770     :until (eq form eof)
771     :collect form)))
772
773(defun* pathname-root (pathname)
774  (make-pathname :directory '(:absolute)
775                 :name nil :type nil :version nil
776                 :defaults pathname ;; host device, and on scl, *some*
777                 ;; scheme-specific parts: port username password, not others:
778                 . #.(or #+scl '(:parameters nil :query nil :fragment nil))))
779
780(defun* probe-file* (p)
781  "when given a pathname P, probes the filesystem for a file or directory
782with given pathname and if it exists return its truename."
783  (etypecase p
784    (null nil)
785    (string (probe-file* (parse-namestring p)))
786    (pathname (unless (wild-pathname-p p)
787                #.(or #+(or allegro clozure cmu cormanlisp ecl lispworks sbcl scl)
788                      '(probe-file p)
789                      #+clisp (aif (find-symbol* '#:probe-pathname :ext)
790                                   `(ignore-errors (,it p)))
791                      '(ignore-errors (truename p)))))))
792
793(defun* truenamize (pathname &optional (defaults *default-pathname-defaults*))
794  "Resolve as much of a pathname as possible"
795  (block nil
796    (when (typep pathname '(or null logical-pathname)) (return pathname))
797    (let ((p (merge-pathnames* pathname defaults)))
798      (when (typep p 'logical-pathname) (return p))
799      (let ((found (probe-file* p)))
800        (when found (return found)))
801      (unless (absolute-pathname-p p)
802        (let ((true-defaults (ignore-errors (truename defaults))))
803          (when true-defaults
804            (setf p (merge-pathnames pathname true-defaults)))))
805      (unless (absolute-pathname-p p) (return p))
806      (let ((sofar (probe-file* (pathname-root p))))
807        (unless sofar (return p))
808        (flet ((solution (directories)
809                 (merge-pathnames*
810                  (make-pathname :host nil :device nil
811                                 :directory `(:relative ,@directories)
812                                 :name (pathname-name p)
813                                 :type (pathname-type p)
814                                 :version (pathname-version p))
815                  sofar)))
816          (loop :with directory = (normalize-pathname-directory-component
817                                   (pathname-directory p))
818            :for component :in (cdr directory)
819            :for rest :on (cdr directory)
820            :for more = (probe-file*
821                         (merge-pathnames*
822                          (make-pathname :directory `(:relative ,component))
823                          sofar)) :do
824            (if more
825                (setf sofar more)
826                (return (solution rest)))
827            :finally
828            (return (solution nil))))))))
829
830(defun* resolve-symlinks (path)
831  #-allegro (truenamize path)
832  #+allegro (if (typep path 'logical-pathname)
833                path
834                (excl:pathname-resolve-symbolic-links path)))
835
836(defun* resolve-symlinks* (path)
837  (if *resolve-symlinks*
838      (and path (resolve-symlinks path))
839      path))
840
841(defun* ensure-pathname-absolute (path)
842  (cond
843    ((absolute-pathname-p path) path)
844    ((stringp path) (ensure-pathname-absolute (pathname path)))
845    ((not (pathnamep path)) (error "not a valid pathname designator ~S" path))
846    (t (let ((resolved (resolve-symlinks path)))
847         (assert (absolute-pathname-p resolved))
848         resolved))))
849
850(defun* default-directory ()
851  (truenamize (pathname-directory-pathname *default-pathname-defaults*)))
852
853(defun* lispize-pathname (input-file)
854  (make-pathname :type "lisp" :defaults input-file))
855
856(defparameter *wild* #-cormanlisp :wild #+cormanlisp "*")
857(defparameter *wild-file*
858  (make-pathname :name *wild* :type *wild*
859                 :version (or #-(or abcl xcl) *wild*) :directory nil))
860(defparameter *wild-directory*
861  (make-pathname :directory `(:relative ,*wild*) :name nil :type nil :version nil))
862(defparameter *wild-inferiors*
863  (make-pathname :directory '(:relative :wild-inferiors) :name nil :type nil :version nil))
864(defparameter *wild-path*
865  (merge-pathnames *wild-file* *wild-inferiors*))
866
867(defun* wilden (path)
868  (merge-pathnames* *wild-path* path))
869
870#-scl
871(defun* directory-separator-for-host (&optional (pathname *default-pathname-defaults*))
872  (let ((foo (make-pathname :directory '(:absolute "FOO") :defaults pathname)))
873    (last-char (namestring foo))))
874
875#-scl
876(defun* directorize-pathname-host-device (pathname)
877  (let* ((root (pathname-root pathname))
878         (wild-root (wilden root))
879         (absolute-pathname (merge-pathnames* pathname root))
880         (separator (directory-separator-for-host root))
881         (root-namestring (namestring root))
882         (root-string
883          (substitute-if #\/
884                         #'(lambda (x) (or (eql x #\:)
885                                           (eql x separator)))
886                         root-namestring)))
887    (multiple-value-bind (relative path filename)
888        (component-name-to-pathname-components root-string :force-directory t)
889      (declare (ignore relative filename))
890      (let ((new-base
891             (make-pathname :defaults root
892                            :directory `(:absolute ,@path))))
893        (translate-pathname absolute-pathname wild-root (wilden new-base))))))
894
895#+scl
896(defun* directorize-pathname-host-device (pathname)
897  (let ((scheme (ext:pathname-scheme pathname))
898        (host (pathname-host pathname))
899        (port (ext:pathname-port pathname))
900        (directory (pathname-directory pathname)))
901    (if (or (ununspecific port)
902            (and (ununspecific host) (plusp (length host)))
903            (ununspecific scheme))
904        (let ((prefix ""))
905          (when (ununspecific port)
906            (setf prefix (format nil ":~D" port)))
907          (when (and (ununspecific host) (plusp (length host)))
908            (setf prefix (strcat host prefix)))
909          (setf prefix (strcat ":" prefix))
910          (when (ununspecific scheme)
911            (setf prefix (strcat scheme prefix)))
912          (assert (and directory (eq (first directory) :absolute)))
913          (make-pathname :directory `(:absolute ,prefix ,@(rest directory))
914                         :defaults pathname)))
915    pathname))
916
917;;;; -------------------------------------------------------------------------
918;;;; ASDF Interface, in terms of generic functions.
919(defgeneric* find-system (system &optional error-p))
920(defgeneric* perform-with-restarts (operation component))
921(defgeneric* perform (operation component))
922(defgeneric* operation-done-p (operation component))
923(defgeneric* mark-operation-done (operation component))
924(defgeneric* explain (operation component))
925(defgeneric* output-files (operation component))
926(defgeneric* input-files (operation component))
927(defgeneric* component-operation-time (operation component))
928(defgeneric* operation-description (operation component)
929  (:documentation "returns a phrase that describes performing this operation
930on this component, e.g. \"loading /a/b/c\".
931You can put together sentences using this phrase."))
932
933(defgeneric* system-source-file (system)
934  (:documentation "Return the source file in which system is defined."))
935
936(defgeneric* component-system (component)
937  (:documentation "Find the top-level system containing COMPONENT"))
938
939(defgeneric* component-pathname (component)
940  (:documentation "Extracts the pathname applicable for a particular component."))
941
942(defgeneric* component-relative-pathname (component)
943  (:documentation "Returns a pathname for the component argument intended to be
944interpreted relative to the pathname of that component's parent.
945Despite the function's name, the return value may be an absolute
946pathname, because an absolute pathname may be interpreted relative to
947another pathname in a degenerate way."))
948
949(defgeneric* component-property (component property))
950
951(defgeneric* (setf component-property) (new-value component property))
952
953(eval-when (#-gcl :compile-toplevel :load-toplevel :execute)
954  (defgeneric* (setf module-components-by-name) (new-value module)))
955
956(defgeneric* version-satisfies (component version))
957
958(defgeneric* find-component (base path)
959  (:documentation "Finds the component with PATH starting from BASE module;
960if BASE is nil, then the component is assumed to be a system."))
961
962(defgeneric* source-file-type (component system))
963
964(defgeneric* operation-ancestor (operation)
965  (:documentation
966   "Recursively chase the operation's parent pointer until we get to
967the head of the tree"))
968
969(defgeneric* component-visited-p (operation component)
970  (:documentation "Returns the value stored by a call to
971VISIT-COMPONENT, if that has been called, otherwise NIL.
972This value stored will be a cons cell, the first element
973of which is a computed key, so not interesting.  The
974CDR wil be the DATA value stored by VISIT-COMPONENT; recover
975it as (cdr (component-visited-p op c)).
976  In the current form of ASDF, the DATA value retrieved is
977effectively a boolean, indicating whether some operations are
978to be performed in order to do OPERATION X COMPONENT.  If the
979data value is NIL, the combination had been explored, but no
980operations needed to be performed."))
981
982(defgeneric* visit-component (operation component data)
983  (:documentation "Record DATA as being associated with OPERATION
984and COMPONENT.  This is a side-effecting function:  the association
985will be recorded on the ROOT OPERATION \(OPERATION-ANCESTOR of the
986OPERATION\).
987  No evidence that DATA is ever interesting, beyond just being
988non-NIL.  Using the data field is probably very risky; if there is
989already a record for OPERATION X COMPONENT, DATA will be quietly
990discarded instead of recorded.
991  Starting with 2.006, TRAVERSE will store an integer in data,
992so that nodes can be sorted in decreasing order of traversal."))
993
994
995(defgeneric* (setf visiting-component) (new-value operation component))
996
997(defgeneric* component-visiting-p (operation component))
998
999(defgeneric* component-depends-on (operation component)
1000  (:documentation
1001   "Returns a list of dependencies needed by the component to perform
1002    the operation.  A dependency has one of the following forms:
1003
1004      (<operation> <component>*), where <operation> is a class
1005        designator and each <component> is a component
1006        designator, which means that the component depends on
1007        <operation> having been performed on each <component>; or
1008
1009      (FEATURE <feature>), which means that the component depends
1010        on <feature>'s presence in *FEATURES*.
1011
1012    Methods specialized on subclasses of existing component types
1013    should usually append the results of CALL-NEXT-METHOD to the
1014    list."))
1015
1016(defgeneric* component-self-dependencies (operation component))
1017
1018(defgeneric* traverse (operation component)
1019  (:documentation
1020"Generate and return a plan for performing OPERATION on COMPONENT.
1021
1022The plan returned is a list of dotted-pairs. Each pair is the CONS
1023of ASDF operation object and a COMPONENT object. The pairs will be
1024processed in order by OPERATE."))
1025
1026
1027;;;; -------------------------------------------------------------------------
1028;;; Methods in case of hot-upgrade. See https://bugs.launchpad.net/asdf/+bug/485687
1029(when *upgraded-p*
1030   (when (find-class 'module nil)
1031     (eval
1032      '(defmethod update-instance-for-redefined-class :after
1033           ((m module) added deleted plist &key)
1034         (declare (ignorable deleted plist))
1035         (when *asdf-verbose*
1036           (asdf-message (compatfmt "~&~@<; ~@;Updating ~A for ASDF ~A~@:>~%")
1037                         m (asdf-version)))
1038         (when (member 'components-by-name added)
1039           (compute-module-components-by-name m))
1040         (when (typep m 'system)
1041           (when (member 'source-file added)
1042             (%set-system-source-file
1043              (probe-asd (component-name m) (component-pathname m)) m)
1044             (when (equal (component-name m) "asdf")
1045               (setf (component-version m) *asdf-version*))))))))
1046
1047;;;; -------------------------------------------------------------------------
1048;;;; Classes, Conditions
1049
1050(define-condition system-definition-error (error) ()
1051  ;; [this use of :report should be redundant, but unfortunately it's not.
1052  ;; cmucl's lisp::output-instance prefers the kernel:slot-class-print-function
1053  ;; over print-object; this is always conditions::%print-condition for
1054  ;; condition objects, which in turn does inheritance of :report options at
1055  ;; run-time.  fortunately, inheritance means we only need this kludge here in
1056  ;; order to fix all conditions that build on it.  -- rgr, 28-Jul-02.]
1057  #+cmu (:report print-object))
1058
1059(define-condition formatted-system-definition-error (system-definition-error)
1060  ((format-control :initarg :format-control :reader format-control)
1061   (format-arguments :initarg :format-arguments :reader format-arguments))
1062  (:report (lambda (c s)
1063               (apply 'format s (format-control c) (format-arguments c)))))
1064
1065(define-condition load-system-definition-error (system-definition-error)
1066  ((name :initarg :name :reader error-name)
1067   (pathname :initarg :pathname :reader error-pathname)
1068   (condition :initarg :condition :reader error-condition))
1069  (:report (lambda (c s)
1070             (format s (compatfmt "~@<Error while trying to load definition for system ~A from pathname ~A: ~3i~_~A~@:>")
1071                     (error-name c) (error-pathname c) (error-condition c)))))
1072
1073(define-condition circular-dependency (system-definition-error)
1074  ((components :initarg :components :reader circular-dependency-components))
1075  (:report (lambda (c s)
1076             (format s (compatfmt "~@<Circular dependency: ~3i~_~S~@:>")
1077                     (circular-dependency-components c)))))
1078
1079(define-condition duplicate-names (system-definition-error)
1080  ((name :initarg :name :reader duplicate-names-name))
1081  (:report (lambda (c s)
1082             (format s (compatfmt "~@<Error while defining system: multiple components are given same name ~A~@:>")
1083                     (duplicate-names-name c)))))
1084
1085(define-condition missing-component (system-definition-error)
1086  ((requires :initform "(unnamed)" :reader missing-requires :initarg :requires)
1087   (parent :initform nil :reader missing-parent :initarg :parent)))
1088
1089(define-condition missing-component-of-version (missing-component)
1090  ((version :initform nil :reader missing-version :initarg :version)))
1091
1092(define-condition missing-dependency (missing-component)
1093  ((required-by :initarg :required-by :reader missing-required-by)))
1094
1095(define-condition missing-dependency-of-version (missing-dependency
1096                                                 missing-component-of-version)
1097  ())
1098
1099(define-condition operation-error (error)
1100  ((component :reader error-component :initarg :component)
1101   (operation :reader error-operation :initarg :operation))
1102  (:report (lambda (c s)
1103               (format s (compatfmt "~@<Error while invoking ~A on ~A~@:>")
1104                       (error-operation c) (error-component c)))))
1105(define-condition compile-error (operation-error) ())
1106(define-condition compile-failed (compile-error) ())
1107(define-condition compile-warned (compile-error) ())
1108
1109(define-condition invalid-configuration ()
1110  ((form :reader condition-form :initarg :form)
1111   (location :reader condition-location :initarg :location)
1112   (format :reader condition-format :initarg :format)
1113   (arguments :reader condition-arguments :initarg :arguments :initform nil))
1114  (:report (lambda (c s)
1115               (format s (compatfmt "~@<~? (will be skipped)~@:>")
1116                       (condition-format c)
1117                       (list* (condition-form c) (condition-location c)
1118                              (condition-arguments c))))))
1119(define-condition invalid-source-registry (invalid-configuration warning)
1120  ((format :initform (compatfmt "~@<Invalid source registry ~S~@[ in ~S~]~@{ ~@?~}~@:>"))))
1121(define-condition invalid-output-translation (invalid-configuration warning)
1122  ((format :initform (compatfmt "~@<Invalid asdf output-translation ~S~@[ in ~S~]~@{ ~@?~}~@:>"))))
1123
1124(defclass component ()
1125  ((name :accessor component-name :initarg :name :type string :documentation
1126         "Component name: designator for a string composed of portable pathname characters")
1127   ;; We might want to constrain version with
1128   ;; :type (and string (satisfies parse-version))
1129   ;; but we cannot until we fix all systems that don't use it correctly!
1130   (version :accessor component-version :initarg :version)
1131   (description :accessor component-description :initarg :description)
1132   (long-description :accessor component-long-description :initarg :long-description)
1133   ;; This one below is used by POIU - http://www.cliki.net/poiu
1134   ;; a parallelizing extension of ASDF that compiles in multiple parallel
1135   ;; slave processes (forked on demand) and loads in the master process.
1136   ;; Maybe in the future ASDF may use it internally instead of in-order-to.
1137   (load-dependencies :accessor component-load-dependencies :initform nil)
1138   ;; In the ASDF object model, dependencies exist between *actions*
1139   ;; (an action is a pair of operation and component). They are represented
1140   ;; alists of operations to dependencies (other actions) in each component.
1141   ;; There are two kinds of dependencies, each stored in its own slot:
1142   ;; in-order-to and do-first dependencies. These two kinds are related to
1143   ;; the fact that some actions modify the filesystem,
1144   ;; whereas other actions modify the current image, and
1145   ;; this implies a difference in how to interpret timestamps.
1146   ;; in-order-to dependencies will trigger re-performing the action
1147   ;; when the timestamp of some dependency
1148   ;; makes the timestamp of current action out-of-date;
1149   ;; do-first dependencies do not trigger such re-performing.
1150   ;; Therefore, a FASL must be recompiled if it is obsoleted
1151   ;; by any of its FASL dependencies (in-order-to); but
1152   ;; it needn't be recompiled just because one of these dependencies
1153   ;; hasn't yet been loaded in the current image (do-first).
1154   ;; The names are crap, but they have been the official API since Dan Barlow's ASDF 1.52!
1155   ;; See our ASDF 2 paper for more complete explanations.
1156   (in-order-to :initform nil :initarg :in-order-to
1157                :accessor component-in-order-to)
1158   (do-first :initform nil :initarg :do-first
1159             :accessor component-do-first)
1160   ;; methods defined using the "inline" style inside a defsystem form:
1161   ;; need to store them somewhere so we can delete them when the system
1162   ;; is re-evaluated
1163   (inline-methods :accessor component-inline-methods :initform nil)
1164   (parent :initarg :parent :initform nil :reader component-parent)
1165   ;; no direct accessor for pathname, we do this as a method to allow
1166   ;; it to default in funky ways if not supplied
1167   (relative-pathname :initarg :pathname)
1168   ;; the absolute-pathname is computed based on relative-pathname...
1169   (absolute-pathname)
1170   (operation-times :initform (make-hash-table)
1171                    :accessor component-operation-times)
1172   (around-compile :initarg :around-compile)
1173   ;; XXX we should provide some atomic interface for updating the
1174   ;; component properties
1175   (properties :accessor component-properties :initarg :properties
1176               :initform nil)))
1177
1178(defun* component-find-path (component)
1179  (reverse
1180   (loop :for c = component :then (component-parent c)
1181     :while c :collect (component-name c))))
1182
1183(defmethod print-object ((c component) stream)
1184  (print-unreadable-object (c stream :type t :identity nil)
1185    (format stream "~{~S~^ ~}" (component-find-path c))))
1186
1187
1188;;;; methods: conditions
1189
1190(defmethod print-object ((c missing-dependency) s)
1191  (format s (compatfmt "~@<~A, required by ~A~@:>")
1192          (call-next-method c nil) (missing-required-by c)))
1193
1194(defun* sysdef-error (format &rest arguments)
1195  (error 'formatted-system-definition-error :format-control
1196         format :format-arguments arguments))
1197
1198;;;; methods: components
1199
1200(defmethod print-object ((c missing-component) s)
1201  (format s (compatfmt "~@<Component ~S not found~@[ in ~A~]~@:>")
1202          (missing-requires c)
1203          (when (missing-parent c)
1204            (coerce-name (missing-parent c)))))
1205
1206(defmethod print-object ((c missing-component-of-version) s)
1207  (format s (compatfmt "~@<Component ~S does not match version ~A~@[ in ~A~]~@:>")
1208          (missing-requires c)
1209          (missing-version c)
1210          (when (missing-parent c)
1211            (coerce-name (missing-parent c)))))
1212
1213(defmethod component-system ((component component))
1214  (aif (component-parent component)
1215       (component-system it)
1216       component))
1217
1218(defvar *default-component-class* 'cl-source-file)
1219
1220(defun* compute-module-components-by-name (module)
1221  (let ((hash (make-hash-table :test 'equal)))
1222    (setf (module-components-by-name module) hash)
1223    (loop :for c :in (module-components module)
1224      :for name = (component-name c)
1225      :for previous = (gethash name (module-components-by-name module))
1226      :do
1227      (when previous
1228        (error 'duplicate-names :name name))
1229      :do (setf (gethash name (module-components-by-name module)) c))
1230    hash))
1231
1232(defclass module (component)
1233  ((components
1234    :initform nil
1235    :initarg :components
1236    :accessor module-components)
1237   (components-by-name
1238    :accessor module-components-by-name)
1239   ;; What to do if we can't satisfy a dependency of one of this module's
1240   ;; components.  This allows a limited form of conditional processing.
1241   (if-component-dep-fails
1242    :initform :fail
1243    :initarg :if-component-dep-fails
1244    :accessor module-if-component-dep-fails)
1245   (default-component-class
1246    :initform *default-component-class*
1247    :initarg :default-component-class
1248    :accessor module-default-component-class)))
1249
1250(defun* component-parent-pathname (component)
1251  ;; No default anymore (in particular, no *default-pathname-defaults*).
1252  ;; If you force component to have a NULL pathname, you better arrange
1253  ;; for any of its children to explicitly provide a proper absolute pathname
1254  ;; wherever a pathname is actually wanted.
1255  (let ((parent (component-parent component)))
1256    (when parent
1257      (component-pathname parent))))
1258
1259(defmethod component-pathname ((component component))
1260  (if (slot-boundp component 'absolute-pathname)
1261      (slot-value component 'absolute-pathname)
1262      (let ((pathname
1263             (merge-pathnames*
1264              (component-relative-pathname component)
1265              (pathname-directory-pathname (component-parent-pathname component)))))
1266        (unless (or (null pathname) (absolute-pathname-p pathname))
1267          (error (compatfmt "~@<Invalid relative pathname ~S for component ~S~@:>")
1268                 pathname (component-find-path component)))
1269        (setf (slot-value component 'absolute-pathname) pathname)
1270        pathname)))
1271
1272(defmethod component-property ((c component) property)
1273  (cdr (assoc property (slot-value c 'properties) :test #'equal)))
1274
1275(defmethod (setf component-property) (new-value (c component) property)
1276  (let ((a (assoc property (slot-value c 'properties) :test #'equal)))
1277    (if a
1278        (setf (cdr a) new-value)
1279        (setf (slot-value c 'properties)
1280              (acons property new-value (slot-value c 'properties)))))
1281  new-value)
1282
1283(defclass proto-system () ; slots to keep when resetting a system
1284  ;; To preserve identity for all objects, we'd need keep the components slots
1285  ;; but also to modify parse-component-form to reset the recycled objects.
1286  ((name) #|(components) (components-by-names)|#))
1287
1288(defclass system (module proto-system)
1289  (;; description and long-description are now available for all component's,
1290   ;; but now also inherited from component, but we add the legacy accessor
1291   (description :accessor system-description :initarg :description)
1292   (long-description :accessor system-long-description :initarg :long-description)
1293   (author :accessor system-author :initarg :author)
1294   (maintainer :accessor system-maintainer :initarg :maintainer)
1295   (licence :accessor system-licence :initarg :licence
1296            :accessor system-license :initarg :license)
1297   (source-file :reader %system-source-file :initarg :source-file ; for CLISP upgrade
1298                :writer %set-system-source-file)
1299   (defsystem-depends-on :reader system-defsystem-depends-on :initarg :defsystem-depends-on)))
1300
1301;;;; -------------------------------------------------------------------------
1302;;;; version-satisfies
1303
1304(defmethod version-satisfies ((c component) version)
1305  (unless (and version (slot-boundp c 'version))
1306    (when version
1307      (warn "Requested version ~S but component ~S has no version" version c))
1308    (return-from version-satisfies t))
1309  (version-satisfies (component-version c) version))
1310
1311(defun* asdf-version ()
1312  "Exported interface to the version of ASDF currently installed. A string.
1313You can compare this string with e.g.:
1314(ASDF:VERSION-SATISFIES (ASDF:ASDF-VERSION) \"2.345.67\")."
1315  *asdf-version*)
1316
1317(defun* parse-version (string &optional on-error)
1318  "Parse a version string as a series of natural integers separated by dots.
1319Return a (non-null) list of integers if the string is valid, NIL otherwise.
1320If on-error is error, warn, or designates a function of compatible signature,
1321the function is called with an explanation of what is wrong with the argument.
1322NB: ignores leading zeroes, and so doesn't distinguish between 2.003 and 2.3"
1323  (and
1324   (or (stringp string)
1325       (when on-error
1326         (funcall on-error "~S: ~S is not a string"
1327                  'parse-version string)) nil)
1328   (or (loop :for prev = nil :then c :for c :across string
1329         :always (or (digit-char-p c)
1330                     (and (eql c #\.) prev (not (eql prev #\.))))
1331         :finally (return (and c (digit-char-p c))))
1332       (when on-error
1333         (funcall on-error "~S: ~S doesn't follow asdf version numbering convention"
1334                  'parse-version string)) nil)
1335   (mapcar #'parse-integer (split-string string :separator "."))))
1336
1337(defmethod version-satisfies ((cver string) version)
1338  (let ((x (parse-version cver 'warn))
1339        (y (parse-version version 'warn)))
1340    (labels ((bigger (x y)
1341               (cond ((not y) t)
1342                     ((not x) nil)
1343                     ((> (car x) (car y)) t)
1344                     ((= (car x) (car y))
1345                      (bigger (cdr x) (cdr y))))))
1346      (and x y (= (car x) (car y))
1347           (or (not (cdr y)) (bigger (cdr x) (cdr y)))))))
1348
1349;;;; -----------------------------------------------------------------
1350;;;; Windows shortcut support.  Based on:
1351;;;;
1352;;;; Jesse Hager: The Windows Shortcut File Format.
1353;;;; http://www.wotsit.org/list.asp?fc=13
1354
1355#-clisp
1356(progn
1357(defparameter *link-initial-dword* 76)
1358(defparameter *link-guid* #(1 20 2 0 0 0 0 0 192 0 0 0 0 0 0 70))
1359
1360(defun* read-null-terminated-string (s)
1361  (with-output-to-string (out)
1362    (loop :for code = (read-byte s)
1363      :until (zerop code)
1364      :do (write-char (code-char code) out))))
1365
1366(defun* read-little-endian (s &optional (bytes 4))
1367  (loop :for i :from 0 :below bytes
1368    :sum (ash (read-byte s) (* 8 i))))
1369
1370(defun* parse-file-location-info (s)
1371  (let ((start (file-position s))
1372        (total-length (read-little-endian s))
1373        (end-of-header (read-little-endian s))
1374        (fli-flags (read-little-endian s))
1375        (local-volume-offset (read-little-endian s))
1376        (local-offset (read-little-endian s))
1377        (network-volume-offset (read-little-endian s))
1378        (remaining-offset (read-little-endian s)))
1379    (declare (ignore total-length end-of-header local-volume-offset))
1380    (unless (zerop fli-flags)
1381      (cond
1382        ((logbitp 0 fli-flags)
1383          (file-position s (+ start local-offset)))
1384        ((logbitp 1 fli-flags)
1385          (file-position s (+ start
1386                              network-volume-offset
1387                              #x14))))
1388      (strcat (read-null-terminated-string s)
1389              (progn
1390                (file-position s (+ start remaining-offset))
1391                (read-null-terminated-string s))))))
1392
1393(defun* parse-windows-shortcut (pathname)
1394  (with-open-file (s pathname :element-type '(unsigned-byte 8))
1395    (handler-case
1396        (when (and (= (read-little-endian s) *link-initial-dword*)
1397                   (let ((header (make-array (length *link-guid*))))
1398                     (read-sequence header s)
1399                     (equalp header *link-guid*)))
1400          (let ((flags (read-little-endian s)))
1401            (file-position s 76)        ;skip rest of header
1402            (when (logbitp 0 flags)
1403              ;; skip shell item id list
1404              (let ((length (read-little-endian s 2)))
1405                (file-position s (+ length (file-position s)))))
1406            (cond
1407              ((logbitp 1 flags)
1408                (parse-file-location-info s))
1409              (t
1410                (when (logbitp 2 flags)
1411                  ;; skip description string
1412                  (let ((length (read-little-endian s 2)))
1413                    (file-position s (+ length (file-position s)))))
1414                (when (logbitp 3 flags)
1415                  ;; finally, our pathname
1416                  (let* ((length (read-little-endian s 2))
1417                         (buffer (make-array length)))
1418                    (read-sequence buffer s)
1419                    (map 'string #'code-char buffer)))))))
1420      (end-of-file ()
1421        nil)))))
1422
1423;;;; -------------------------------------------------------------------------
1424;;;; Finding systems
1425
1426(defun* make-defined-systems-table ()
1427  (make-hash-table :test 'equal))
1428
1429(defvar *defined-systems* (make-defined-systems-table)
1430  "This is a hash table whose keys are strings, being the
1431names of the systems, and whose values are pairs, the first
1432element of which is a universal-time indicating when the
1433system definition was last updated, and the second element
1434of which is a system object.")
1435
1436(defun* coerce-name (name)
1437  (typecase name
1438    (component (component-name name))
1439    (symbol (string-downcase (symbol-name name)))
1440    (string name)
1441    (t (sysdef-error (compatfmt "~@<Invalid component designator: ~3i~_~A~@:>") name))))
1442
1443(defun* system-registered-p (name)
1444  (gethash (coerce-name name) *defined-systems*))
1445
1446(defun* register-system (system)
1447  (check-type system system)
1448  (let ((name (component-name system)))
1449    (check-type name string)
1450    (asdf-message (compatfmt "~&~@<; ~@;Registering ~3i~_~A~@:>~%") system)
1451    (unless (eq system (cdr (gethash name *defined-systems*)))
1452      (setf (gethash name *defined-systems*)
1453            (cons (get-universal-time) system)))))
1454
1455(defun* clear-system (name)
1456  "Clear the entry for a system in the database of systems previously loaded.
1457Note that this does NOT in any way cause the code of the system to be unloaded."
1458  ;; There is no "unload" operation in Common Lisp, and
1459  ;; a general such operation cannot be portably written,
1460  ;; considering how much CL relies on side-effects to global data structures.
1461  (remhash (coerce-name name) *defined-systems*))
1462
1463(defun* map-systems (fn)
1464  "Apply FN to each defined system.
1465
1466FN should be a function of one argument. It will be
1467called with an object of type asdf:system."
1468  (maphash #'(lambda (_ datum)
1469               (declare (ignore _))
1470               (destructuring-bind (_ . def) datum
1471                 (declare (ignore _))
1472                 (funcall fn def)))
1473           *defined-systems*))
1474
1475;;; for the sake of keeping things reasonably neat, we adopt a
1476;;; convention that functions in this list are prefixed SYSDEF-
1477
1478(defvar *system-definition-search-functions* '())
1479
1480(setf *system-definition-search-functions*
1481      (append
1482       ;; Remove known-incompatible sysdef functions from ancient sbcl asdf.
1483       (remove 'contrib-sysdef-search *system-definition-search-functions*)
1484       ;; Tuck our defaults at the end of the list if they were absent.
1485       ;; This is imperfect, in case they were removed on purpose,
1486       ;; but then it will be the responsibility of whoever does that
1487       ;; to upgrade asdf before he does such a thing rather than after.
1488       (remove-if #'(lambda (x) (member x *system-definition-search-functions*))
1489                  '(sysdef-central-registry-search
1490                    sysdef-source-registry-search
1491                    sysdef-find-asdf))))
1492
1493(defun* search-for-system-definition (system)
1494  (some (let ((name (coerce-name system))) #'(lambda (x) (funcall x name)))
1495        (cons 'find-system-if-being-defined
1496              *system-definition-search-functions*)))
1497
1498(defvar *central-registry* nil
1499"A list of 'system directory designators' ASDF uses to find systems.
1500
1501A 'system directory designator' is a pathname or an expression
1502which evaluates to a pathname. For example:
1503
1504    (setf asdf:*central-registry*
1505          (list '*default-pathname-defaults*
1506                #p\"/home/me/cl/systems/\"
1507                #p\"/usr/share/common-lisp/systems/\"))
1508
1509This is for backward compatibilily.
1510Going forward, we recommend new users should be using the source-registry.
1511")
1512
1513(defun* featurep (x &optional (features *features*))
1514  (cond
1515    ((atom x)
1516     (and (member x features) t))
1517    ((eq 'not (car x))
1518     (assert (null (cddr x)))
1519     (not (featurep (cadr x) features)))
1520    ((eq 'or (car x))
1521     (some #'(lambda (x) (featurep x features)) (cdr x)))
1522    ((eq 'and (car x))
1523     (every #'(lambda (x) (featurep x features)) (cdr x)))
1524    (t
1525     (error "Malformed feature specification ~S" x))))
1526
1527(defun* os-unix-p ()
1528  (featurep '(or :unix :cygwin :darwin)))
1529
1530(defun* os-windows-p ()
1531  (and (not (os-unix-p)) (featurep '(or :win32 :windows :mswindows :mingw32))))
1532
1533(defun* probe-asd (name defaults)
1534  (block nil
1535    (when (directory-pathname-p defaults)
1536      (let ((file (make-pathname
1537                   :defaults defaults :name name
1538                   :version :newest :case :local :type "asd")))
1539        (when (probe-file* file)
1540          (return file)))
1541      #-clisp
1542      (when (os-windows-p)
1543        (let ((shortcut
1544               (make-pathname
1545                :defaults defaults :version :newest :case :local
1546                :name (strcat name ".asd")
1547                :type "lnk")))
1548          (when (probe-file* shortcut)
1549            (let ((target (parse-windows-shortcut shortcut)))
1550              (when target
1551                (return (pathname target))))))))))
1552
1553(defun* sysdef-central-registry-search (system)
1554  (let ((name (coerce-name system))
1555        (to-remove nil)
1556        (to-replace nil))
1557    (block nil
1558      (unwind-protect
1559           (dolist (dir *central-registry*)
1560             (let ((defaults (eval dir)))
1561               (when defaults
1562                 (cond ((directory-pathname-p defaults)
1563                        (let ((file (probe-asd name defaults)))
1564                          (when file
1565                            (return file))))
1566                       (t
1567                        (restart-case
1568                            (let* ((*print-circle* nil)
1569                                   (message
1570                                    (format nil
1571                                            (compatfmt "~@<While searching for system ~S: ~3i~_~S evaluated to ~S which is not a directory.~@:>")
1572                                            system dir defaults)))
1573                              (error message))
1574                          (remove-entry-from-registry ()
1575                            :report "Remove entry from *central-registry* and continue"
1576                            (push dir to-remove))
1577                          (coerce-entry-to-directory ()
1578                            :report (lambda (s)
1579                                      (format s (compatfmt "~@<Coerce entry to ~a, replace ~a and continue.~@:>")
1580                                              (ensure-directory-pathname defaults) dir))
1581                            (push (cons dir (ensure-directory-pathname defaults)) to-replace))))))))
1582        ;; cleanup
1583        (dolist (dir to-remove)
1584          (setf *central-registry* (remove dir *central-registry*)))
1585        (dolist (pair to-replace)
1586          (let* ((current (car pair))
1587                 (new (cdr pair))
1588                 (position (position current *central-registry*)))
1589            (setf *central-registry*
1590                  (append (subseq *central-registry* 0 position)
1591                          (list new)
1592                          (subseq *central-registry* (1+ position))))))))))
1593
1594(defun* make-temporary-package ()
1595  (flet ((try (counter)
1596           (ignore-errors
1597             (make-package (format nil "~A~D" :asdf counter)
1598                           :use '(:cl :asdf)))))
1599    (do* ((counter 0 (+ counter 1))
1600          (package (try counter) (try counter)))
1601         (package package))))
1602
1603(defun* safe-file-write-date (pathname)
1604  ;; If FILE-WRITE-DATE returns NIL, it's possible that
1605  ;; the user or some other agent has deleted an input file.
1606  ;; Also, generated files will not exist at the time planning is done
1607  ;; and calls operation-done-p which calls safe-file-write-date.
1608  ;; So it is very possible that we can't get a valid file-write-date,
1609  ;; and we can survive and we will continue the planning
1610  ;; as if the file were very old.
1611  ;; (or should we treat the case in a different, special way?)
1612  (or (and pathname (probe-file* pathname) (ignore-errors (file-write-date pathname)))
1613      (progn
1614        (when (and pathname *asdf-verbose*)
1615          (warn (compatfmt "~@<Missing FILE-WRITE-DATE for ~S, treating it as zero.~@:>")
1616                pathname))
1617        0)))
1618
1619(defmethod find-system ((name null) &optional (error-p t))
1620  (declare (ignorable name))
1621  (when error-p
1622    (sysdef-error (compatfmt "~@<NIL is not a valid system name~@:>"))))
1623
1624(defmethod find-system (name &optional (error-p t))
1625  (find-system (coerce-name name) error-p))
1626
1627(defvar *systems-being-defined* nil
1628  "A hash-table of systems currently being defined keyed by name, or NIL")
1629
1630(defun* find-system-if-being-defined (name)
1631  (when *systems-being-defined*
1632    (gethash (coerce-name name) *systems-being-defined*)))
1633
1634(defun* call-with-system-definitions (thunk)
1635  (if *systems-being-defined*
1636      (funcall thunk)
1637      (let ((*systems-being-defined* (make-hash-table :test 'equal)))
1638        (funcall thunk))))
1639
1640(defmacro with-system-definitions ((&optional) &body body)
1641  `(call-with-system-definitions #'(lambda () ,@body)))
1642
1643(defun* load-sysdef (name pathname)
1644  ;; Tries to load system definition with canonical NAME from PATHNAME.
1645  (with-system-definitions ()
1646    (let ((package (make-temporary-package)))
1647      (unwind-protect
1648           (handler-bind
1649               ((error #'(lambda (condition)
1650                           (error 'load-system-definition-error
1651                                  :name name :pathname pathname
1652                                  :condition condition))))
1653             (let ((*package* package)
1654                   (*default-pathname-defaults*
1655                    (pathname-directory-pathname pathname)))
1656               (asdf-message (compatfmt "~&~@<; ~@;Loading system definition from ~A into ~A~@:>~%")
1657                             pathname package)
1658               (load pathname)))
1659        (delete-package package)))))
1660
1661(defun* locate-system (name)
1662  "Given a system NAME designator, try to locate where to load the system from.
1663Returns four values: FOUND-SYSTEM PATHNAME PREVIOUS PREVIOUS-TIME
1664FOUNDP is true when a new was found, either a new unregistered one or a previously registered one.
1665FOUND-SYSTEM when not null is a SYSTEM object that may be REGISTER-SYSTEM'ed as is
1666PATHNAME when not null is a path from where to load the system, associated with FOUND-SYSTEM, or with the PREVIOUS system.
1667PREVIOUS when not null is a previously loaded SYSTEM object of same name.
1668PREVIOUS-TIME when not null is the time at which the PREVIOUS system was loaded."
1669  (let* ((name (coerce-name name))
1670         (in-memory (system-registered-p name)) ; load from disk if absent or newer on disk
1671         (previous (cdr in-memory))
1672         (previous (and (typep previous 'system) previous))
1673         (previous-time (car in-memory))
1674           (found (search-for-system-definition name))
1675         (found-system (and (typep found 'system) found))
1676         (pathname (or (and (typep found '(or pathname string)) (pathname found))
1677                       (and found-system (system-source-file found-system))
1678                       (and previous (system-source-file previous))))
1679         (foundp (and (or found-system pathname previous) t)))
1680    (check-type found (or null pathname system))
1681    (when foundp
1682      (setf pathname (resolve-symlinks* pathname))
1683      (when (and pathname (not (absolute-pathname-p pathname)))
1684        (setf pathname (ensure-pathname-absolute pathname))
1685        (when found-system
1686          (%set-system-source-file pathname found-system)))
1687      (when (and previous (not (#-cormanlisp equal #+cormanlisp equalp
1688                                             (system-source-file previous) pathname)))
1689        (%set-system-source-file pathname previous)
1690        (setf previous-time nil))
1691      (values foundp found-system pathname previous previous-time))))
1692
1693(defmethod find-system ((name string) &optional (error-p t))
1694  (with-system-definitions ()
1695    (loop
1696      (restart-case
1697          (multiple-value-bind (foundp found-system pathname previous previous-time)
1698              (locate-system name)
1699            (declare (ignore foundp))
1700            (when (and found-system (not previous))
1701              (register-system found-system))
1702            (when (and pathname
1703                       (or (not previous-time)
1704                           ;; don't reload if it's already been loaded,
1705                           ;; or its filestamp is in the future which means some clock is skewed
1706                           ;; and trying to load might cause an infinite loop.
1707                           (< previous-time (safe-file-write-date pathname) (get-universal-time))))
1708              (load-sysdef name pathname))
1709            (let ((in-memory (system-registered-p name))) ; try again after loading from disk if needed
1710              (return
1711                (cond
1712                  (in-memory
1713                   (when pathname
1714                     (setf (car in-memory) (safe-file-write-date pathname)))
1715                   (cdr in-memory))
1716                  (error-p
1717                   (error 'missing-component :requires name))))))
1718        (reinitialize-source-registry-and-retry ()
1719          :report (lambda (s)
1720                    (format s "~@<Retry finding system ~A after reinitializing the source-registry.~@:>" name))
1721          (initialize-source-registry))))))
1722
1723(defun* find-system-fallback (requested fallback &rest keys &key source-file &allow-other-keys)
1724  (setf fallback (coerce-name fallback)
1725        requested (coerce-name requested))
1726  (when (equal requested fallback)
1727    (let ((registered (cdr (gethash fallback *defined-systems*))))
1728      (or registered
1729          (apply 'make-instance 'system
1730                 :name fallback :source-file source-file keys)))))
1731
1732(defun* sysdef-find-asdf (name)
1733  ;; Bug: :version *asdf-version* won't be updated when ASDF is updated.
1734  (find-system-fallback name "asdf" :version *asdf-version*))
1735
1736
1737;;;; -------------------------------------------------------------------------
1738;;;; Finding components
1739
1740(defmethod find-component ((base string) path)
1741  (let ((s (find-system base nil)))
1742    (and s (find-component s path))))
1743
1744(defmethod find-component ((base symbol) path)
1745  (cond
1746    (base (find-component (coerce-name base) path))
1747    (path (find-component path nil))
1748    (t    nil)))
1749
1750(defmethod find-component ((base cons) path)
1751  (find-component (car base) (cons (cdr base) path)))
1752
1753(defmethod find-component ((module module) (name string))
1754  (unless (slot-boundp module 'components-by-name) ;; SBCL may miss the u-i-f-r-c method!!!
1755    (compute-module-components-by-name module))
1756  (values (gethash name (module-components-by-name module))))
1757
1758(defmethod find-component ((component component) (name symbol))
1759  (if name
1760      (find-component component (coerce-name name))
1761      component))
1762
1763(defmethod find-component ((module module) (name cons))
1764  (find-component (find-component module (car name)) (cdr name)))
1765
1766
1767;;; component subclasses
1768
1769(defclass source-file (component)
1770  ((type :accessor source-file-explicit-type :initarg :type :initform nil)))
1771
1772(defclass cl-source-file (source-file)
1773  ((type :initform "lisp")))
1774(defclass cl-source-file.cl (cl-source-file)
1775  ((type :initform "cl")))
1776(defclass cl-source-file.lsp (cl-source-file)
1777  ((type :initform "lsp")))
1778(defclass c-source-file (source-file)
1779  ((type :initform "c")))
1780(defclass java-source-file (source-file)
1781  ((type :initform "java")))
1782(defclass static-file (source-file) ())
1783(defclass doc-file (static-file) ())
1784(defclass html-file (doc-file)
1785  ((type :initform "html")))
1786
1787(defmethod source-file-type ((component module) (s module))
1788  (declare (ignorable component s))
1789  :directory)
1790(defmethod source-file-type ((component source-file) (s module))
1791  (declare (ignorable s))
1792  (source-file-explicit-type component))
1793
1794(defun* coerce-pathname (name &key type defaults)
1795  "coerce NAME into a PATHNAME.
1796When given a string, portably decompose it into a relative pathname:
1797#\\/ separates subdirectories. The last #\\/-separated string is as follows:
1798if TYPE is NIL, its last #\\. if any separates name and type from from type;
1799if TYPE is a string, it is the type, and the whole string is the name;
1800if TYPE is :DIRECTORY, the string is a directory component;
1801if the string is empty, it's a directory.
1802Any directory named .. is read as :BACK.
1803Host, device and version components are taken from DEFAULTS."
1804  ;; The defaults are required notably because they provide the default host
1805  ;; to the below make-pathname, which may crucially matter to people using
1806  ;; merge-pathnames with non-default hosts,  e.g. for logical-pathnames.
1807  ;; NOTE that the host and device slots will be taken from the defaults,
1808  ;; but that should only matter if you later merge relative pathnames with
1809  ;; CL:MERGE-PATHNAMES instead of ASDF:MERGE-PATHNAMES*
1810  (etypecase name
1811    ((or null pathname)
1812     name)
1813    (symbol
1814     (coerce-pathname (string-downcase name) :type type :defaults defaults))
1815    (string
1816     (multiple-value-bind (relative path filename)
1817         (component-name-to-pathname-components name :force-directory (eq type :directory)
1818                                                :force-relative t)
1819       (multiple-value-bind (name type)
1820           (cond
1821             ((or (eq type :directory) (null filename))
1822              (values nil nil))
1823             (type
1824              (values filename type))
1825             (t
1826              (split-name-type filename)))
1827         (apply 'make-pathname :directory (cons relative path) :name name :type type
1828                (when defaults `(:defaults ,defaults))))))))
1829
1830(defun* merge-component-name-type (name &key type defaults)
1831  ;; For backwards compatibility only, for people using internals.
1832  ;; Will be removed in a future release, e.g. 2.016.
1833  (warn "Please don't use ASDF::MERGE-COMPONENT-NAME-TYPE. Use ASDF:COERCE-PATHNAME.")
1834  (coerce-pathname name :type type :defaults defaults))
1835
1836(defmethod component-relative-pathname ((component component))
1837  (coerce-pathname
1838   (or (slot-value component 'relative-pathname)
1839       (component-name component))
1840   :type (source-file-type component (component-system component))
1841   :defaults (component-parent-pathname component)))
1842
1843<<<<<<< .working
1844=======
1845(defun* subpathname (pathname subpath &key type)
1846  (and pathname (merge-pathnames* (coerce-pathname subpath :type type)
1847                                  (pathname-directory-pathname pathname))))
1848
1849(defun subpathname* (pathname subpath &key type)
1850  (and pathname
1851       (subpathname (ensure-directory-pathname pathname) subpath :type type)))
1852
1853>>>>>>> .merge-right.r13702
1854;;;; -------------------------------------------------------------------------
1855;;;; Operations
1856
1857;;; one of these is instantiated whenever #'operate is called
1858
1859(defclass operation ()
1860  (;; as of danb's 2003-03-16 commit e0d02781, :force can be:
1861   ;; T to force the inside of the specified system,
1862   ;;   but not recurse to other systems we depend on.
1863   ;; :ALL (or any other atom) to force all systems
1864   ;;   including other systems we depend on.
1865   ;; (SYSTEM1 SYSTEM2 ... SYSTEMN)
1866   ;;   to force systems named in a given list
1867   ;; However, but this feature has only ever worked but starting with ASDF 2.014.5
1868   (forced :initform nil :initarg :force :accessor operation-forced)
1869   (original-initargs :initform nil :initarg :original-initargs
1870                      :accessor operation-original-initargs)
1871   (visited-nodes :initform (make-hash-table :test 'equal) :accessor operation-visited-nodes)
1872   (visiting-nodes :initform (make-hash-table :test 'equal) :accessor operation-visiting-nodes)
1873   (parent :initform nil :initarg :parent :accessor operation-parent)))
1874
1875(defmethod print-object ((o operation) stream)
1876  (print-unreadable-object (o stream :type t :identity t)
1877    (ignore-errors
1878      (prin1 (operation-original-initargs o) stream))))
1879
1880(defmethod shared-initialize :after ((operation operation) slot-names
1881                                     &key force
1882                                     &allow-other-keys)
1883  (declare (ignorable operation slot-names force))
1884  ;; empty method to disable initarg validity checking
1885  (values))
1886
1887(defun* node-for (o c)
1888  (cons (class-name (class-of o)) c))
1889
1890(defmethod operation-ancestor ((operation operation))
1891  (aif (operation-parent operation)
1892       (operation-ancestor it)
1893       operation))
1894
1895
1896(defun* make-sub-operation (c o dep-c dep-o)
1897  "C is a component, O is an operation, DEP-C is another
1898component, and DEP-O, confusingly enough, is an operation
1899class specifier, not an operation."
1900  (let* ((args (copy-list (operation-original-initargs o)))
1901         (force-p (getf args :force)))
1902    ;; note explicit comparison with T: any other non-NIL force value
1903    ;; (e.g. :recursive) will pass through
1904    (cond ((and (null (component-parent c))
1905                (null (component-parent dep-c))
1906                (not (eql c dep-c)))
1907           (when (eql force-p t)
1908             (setf (getf args :force) nil))
1909           (apply 'make-instance dep-o
1910                  :parent o
1911                  :original-initargs args args))
1912          ((subtypep (type-of o) dep-o)
1913           o)
1914          (t
1915           (apply 'make-instance dep-o
1916                  :parent o :original-initargs args args)))))
1917
1918
1919(defmethod visit-component ((o operation) (c component) data)
1920  (unless (component-visited-p o c)
1921    (setf (gethash (node-for o c)
1922                   (operation-visited-nodes (operation-ancestor o)))
1923          (cons t data))))
1924
1925(defmethod component-visited-p ((o operation) (c component))
1926  (gethash (node-for o c)
1927           (operation-visited-nodes (operation-ancestor o))))
1928
1929(defmethod (setf visiting-component) (new-value operation component)
1930  ;; MCL complains about unused lexical variables
1931  (declare (ignorable operation component))
1932  new-value)
1933
1934(defmethod (setf visiting-component) (new-value (o operation) (c component))
1935  (let ((node (node-for o c))
1936        (a (operation-ancestor o)))
1937    (if new-value
1938        (setf (gethash node (operation-visiting-nodes a)) t)
1939        (remhash node (operation-visiting-nodes a)))
1940    new-value))
1941
1942(defmethod component-visiting-p ((o operation) (c component))
1943  (let ((node (node-for o c)))
1944    (gethash node (operation-visiting-nodes (operation-ancestor o)))))
1945
1946(defmethod component-depends-on ((op-spec symbol) (c component))
1947  ;; Note: we go from op-spec to operation via make-instance
1948  ;; to allow for specialization through defmethod's, even though
1949  ;; it's a detour in the default case below.
1950  (component-depends-on (make-instance op-spec) c))
1951
1952(defmethod component-depends-on ((o operation) (c component))
1953  (cdr (assoc (type-of o) (component-in-order-to c))))
1954
1955(defmethod component-self-dependencies ((o operation) (c component))
1956  (remove-if-not
1957   #'(lambda (x) (member (component-name c) (cdr x) :test #'string=))
1958   (component-depends-on o c)))
1959
1960(defmethod input-files ((operation operation) (c component))
1961  (let ((parent (component-parent c))
1962        (self-deps (component-self-dependencies operation c)))
1963    (if self-deps
1964        (mapcan #'(lambda (dep)
1965                    (destructuring-bind (op name) dep
1966                      (output-files (make-instance op)
1967                                    (find-component parent name))))
1968                self-deps)
1969        ;; no previous operations needed?  I guess we work with the
1970        ;; original source file, then
1971        (list (component-pathname c)))))
1972
1973(defmethod input-files ((operation operation) (c module))
1974  (declare (ignorable operation c))
1975  nil)
1976
1977(defmethod component-operation-time (o c)
1978  (gethash (type-of o) (component-operation-times c)))
1979
1980(defmethod operation-done-p ((o operation) (c component))
1981  (let ((out-files (output-files o c))
1982        (in-files (input-files o c))
1983        (op-time (component-operation-time o c)))
1984    (flet ((earliest-out ()
1985             (reduce #'min (mapcar #'safe-file-write-date out-files)))
1986           (latest-in ()
1987             (reduce #'max (mapcar #'safe-file-write-date in-files))))
1988      (cond
1989        ((and (not in-files) (not out-files))
1990         ;; arbitrary decision: an operation that uses nothing to
1991         ;; produce nothing probably isn't doing much.
1992         ;; e.g. operations on systems, modules that have no immediate action,
1993         ;; but are only meaningful through traversed dependencies
1994         t)
1995        ((not out-files)
1996         ;; an operation without output-files is probably meant
1997         ;; for its side-effects in the current image,
1998         ;; assumed to be idem-potent,
1999         ;; e.g. LOAD-OP or LOAD-SOURCE-OP of some CL-SOURCE-FILE.
2000         (and op-time (>= op-time (latest-in))))
2001        ((not in-files)
2002         ;; an operation with output-files and no input-files
2003         ;; is probably meant for its side-effects on the file-system,
2004         ;; assumed to have to be done everytime.
2005         ;; (I don't think there is any such case in ASDF unless extended)
2006         nil)
2007        (t
2008         ;; an operation with both input and output files is assumed
2009         ;; as computing the latter from the former,
2010         ;; assumed to have been done if the latter are all older
2011         ;; than the former.
2012         ;; e.g. COMPILE-OP of some CL-SOURCE-FILE.
2013         ;; We use >= instead of > to play nice with generated files.
2014         ;; This opens a race condition if an input file is changed
2015         ;; after the output is created but within the same second
2016         ;; of filesystem time; but the same race condition exists
2017         ;; whenever the computation from input to output takes more
2018         ;; than one second of filesystem time (or just crosses the
2019         ;; second). So that's cool.
2020         (and
2021          (every #'probe-file* in-files)
2022          (every #'probe-file* out-files)
2023          (>= (earliest-out) (latest-in))))))))
2024
2025
2026
2027;;; For 1.700 I've done my best to refactor TRAVERSE
2028;;; by splitting it up in a bunch of functions,
2029;;; so as to improve the collection and use-detection algorithm. --fare
2030;;; The protocol is as follows: we pass around operation, dependency,
2031;;; bunch of other stuff, and a force argument. Return a force flag.
2032;;; The returned flag is T if anything has changed that requires a rebuild.
2033;;; The force argument is a list of components that will require a rebuild
2034;;; if the flag is T, at which point whoever returns the flag has to
2035;;; mark them all as forced, and whoever recurses again can use a NIL list
2036;;; as a further argument.
2037
2038(defvar *forcing* nil
2039  "This dynamically-bound variable is used to force operations in
2040recursive calls to traverse.")
2041
2042(defgeneric* do-traverse (operation component collect))
2043
2044(defun* resolve-dependency-name (component name &optional version)
2045  (loop
2046    (restart-case
2047        (return
2048          (let ((comp (find-component (component-parent component) name)))
2049            (unless comp
2050              (error 'missing-dependency
2051                     :required-by component
2052                     :requires name))
2053            (when version
2054              (unless (version-satisfies comp version)
2055                (error 'missing-dependency-of-version
2056                       :required-by component
2057                       :version version
2058                       :requires name)))
2059            comp))
2060      (retry ()
2061        :report (lambda (s)
2062                  (format s "~@<Retry loading ~3i~_~A.~@:>" name))
2063        :test
2064        (lambda (c)
2065          (or (null c)
2066              (and (typep c 'missing-dependency)
2067                   (eq (missing-required-by c) component)
2068                   (equal (missing-requires c) name))))))))
2069
2070(defun* resolve-dependency-spec (component dep-spec)
2071  (cond
2072    ((atom dep-spec)
2073     (resolve-dependency-name component dep-spec))
2074    ;; Structured dependencies --- this parses keywords.
2075    ;; The keywords could conceivably be broken out and cleanly (extensibly)
2076    ;; processed by EQL methods. But for now, here's what we've got.
2077    ((eq :version (first dep-spec))
2078     ;; https://bugs.launchpad.net/asdf/+bug/527788
2079     (resolve-dependency-name component (second dep-spec) (third dep-spec)))
2080    ((eq :feature (first dep-spec))
2081     ;; This particular subform is not documented and
2082     ;; has always been broken in the past.
2083     ;; Therefore no one uses it, and I'm cerroring it out,
2084     ;; after fixing it
2085     ;; See https://bugs.launchpad.net/asdf/+bug/518467
2086     (cerror "Continue nonetheless."
2087             "Congratulations, you're the first ever user of FEATURE dependencies! Please contact the asdf-devel mailing-list.")
2088     (when (find (second dep-spec) *features* :test 'string-equal)
2089       (resolve-dependency-name component (third dep-spec))))
2090    (t
2091     (error (compatfmt "~@<Bad dependency ~s.  Dependencies must be (:version <name> <version>), (:feature <feature> <name>), or <name>.~@:>") dep-spec))))
2092
2093(defun* do-one-dep (op c collect dep-op dep-c)
2094  ;; Collects a partial plan for performing dep-op on dep-c
2095  ;; as dependencies of a larger plan involving op and c.
2096  ;; Returns t if this should force recompilation of those who depend on us.
2097  ;; dep-op is an operation class name (not an operation object),
2098  ;; whereas dep-c is a component object.n
2099  (do-traverse (make-sub-operation c op dep-c dep-op) dep-c collect))
2100
2101(defun* do-dep (op c collect dep-op-spec dep-c-specs)
2102  ;; Collects a partial plan for performing dep-op-spec on each of dep-c-specs
2103  ;; as dependencies of a larger plan involving op and c.
2104  ;; Returns t if this should force recompilation of those who depend on us.
2105  ;; dep-op-spec is either an operation class name (not an operation object),
2106  ;; or the magic symbol asdf:feature.
2107  ;; If dep-op-spec is asdf:feature, then the first dep-c-specs is a keyword,
2108  ;; and the plan will succeed if that keyword is present in *feature*,
2109  ;; or fail if it isn't
2110  ;; (at which point c's :if-component-dep-fails will kick in).
2111  ;; If dep-op-spec is an operation class name,
2112  ;; then dep-c-specs specifies a list of sibling component of c,
2113  ;; as per resolve-dependency-spec, such that operating op on c
2114  ;; depends on operating dep-op-spec on each of them.
2115  (cond ((eq dep-op-spec 'feature)
2116         (if (member (car dep-c-specs) *features*)
2117             nil
2118             (error 'missing-dependency
2119                    :required-by c
2120                    :requires (list :feature (car dep-c-specs)))))
2121        (t
2122         (let ((flag nil))
2123           (dolist (d dep-c-specs)
2124             (when (do-one-dep op c collect dep-op-spec
2125                               (resolve-dependency-spec c d))
2126               (setf flag t)))
2127           flag))))
2128
2129(defvar *visit-count* 0) ; counter that allows to sort nodes from operation-visited-nodes
2130
2131(defun* do-collect (collect x)
2132  (funcall collect x))
2133
2134(defmethod do-traverse ((operation operation) (c component) collect)
2135  (let ((*forcing* *forcing*)
2136        (flag nil)) ;; return value: must we rebuild this and its dependencies?
2137    (labels
2138        ((update-flag (x)
2139           (orf flag x))
2140         (dep (op comp)
2141           (update-flag (do-dep operation c collect op comp))))
2142      ;; Have we been visited yet? If so, just process the result.
2143      (aif (component-visited-p operation c)
2144           (progn
2145             (update-flag (cdr it))
2146             (return-from do-traverse flag)))
2147      ;; dependencies
2148      (when (component-visiting-p operation c)
2149        (error 'circular-dependency :components (list c)))
2150      (setf (visiting-component operation c) t)
2151      (unwind-protect
2152           (progn
2153             (let ((f (operation-forced
2154                       (operation-ancestor operation))))
2155               (when (and f (or (not (consp f)) ;; T or :ALL
2156                                (and (typep c 'system) ;; list of names of systems to force
2157                                     (member (component-name c) f
2158                                             :test #'string=))))
2159                 (setf *forcing* t)))
2160             ;; first we check and do all the dependencies for the module.
2161             ;; Operations planned in this loop will show up
2162             ;; in the results, and are consumed below.
2163             (let ((*forcing* nil))
2164               ;; upstream dependencies are never forced to happen just because
2165               ;; the things that depend on them are....
2166               (loop
2167                 :for (required-op . deps) :in (component-depends-on operation c)
2168                 :do (dep required-op deps)))
2169             ;; constituent bits
2170             (let ((module-ops
2171                    (when (typep c 'module)
2172                      (let ((at-least-one nil)
2173                            ;; This is set based on the results of the
2174                            ;; dependencies and whether we are in the
2175                            ;; context of a *forcing* call...
2176                            ;; inter-system dependencies do NOT trigger
2177                            ;; building components
2178                            (*forcing*
2179                             (or *forcing*
2180                                 (and flag (not (typep c 'system)))))
2181                            (error nil))
2182                        (while-collecting (internal-collect)
2183                          (dolist (kid (module-components c))
2184                            (handler-case
2185                                (update-flag
2186                                 (do-traverse operation kid #'internal-collect))
2187                              (missing-dependency (condition)
2188                                (when (eq (module-if-component-dep-fails c)
2189                                          :fail)
2190                                  (error condition))
2191                                (setf error condition))
2192                              (:no-error (c)
2193                                (declare (ignore c))
2194                                (setf at-least-one t))))
2195                          (when (and (eq (module-if-component-dep-fails c)
2196                                         :try-next)
2197                                     (not at-least-one))
2198                            (error error)))))))
2199               (update-flag (or *forcing* (not (operation-done-p operation c))))
2200                 ;; For sub-operations, check whether
2201                 ;; the original ancestor operation was forced,
2202                 ;; or names us amongst an explicit list of things to force...
2203                 ;; except that this check doesn't distinguish
2204                 ;; between all the things with a given name. Sigh.
2205                 ;; BROKEN!
2206               (when flag
2207                 (let ((do-first (cdr (assoc (class-name (class-of operation))
2208                                             (component-do-first c)))))
2209                   (loop :for (required-op . deps) :in do-first
2210                     :do (do-dep operation c collect required-op deps)))
2211                 (do-collect collect (vector module-ops))
2212                 (do-collect collect (cons operation c)))))
2213             (setf (visiting-component operation c) nil)))
2214      (visit-component operation c (when flag (incf *visit-count*)))
2215      flag))
2216
2217(defun* flatten-tree (l)
2218  ;; You collected things into a list.
2219  ;; Most elements are just things to collect again.
2220  ;; A (simple-vector 1) indicate that you should recurse into its contents.
2221  ;; This way, in two passes (rather than N being the depth of the tree),
2222  ;; you can collect things with marginally constant-time append,
2223  ;; achieving linear time collection instead of quadratic time.
2224  (while-collecting (c)
2225    (labels ((r (x)
2226               (if (typep x '(simple-vector 1))
2227                   (r* (svref x 0))
2228                   (c x)))
2229             (r* (l)
2230               (dolist (x l) (r x))))
2231      (r* l))))
2232
2233(defmethod traverse ((operation operation) (c component))
2234  (when (consp (operation-forced operation))
2235    (setf (operation-forced operation)
2236          (mapcar #'coerce-name (operation-forced operation))))
2237  (flatten-tree
2238   (while-collecting (collect)
2239     (let ((*visit-count* 0))
2240       (do-traverse operation c #'collect)))))
2241
2242(defmethod perform ((operation operation) (c source-file))
2243  (sysdef-error
2244   (compatfmt "~@<Required method PERFORM not implemented for operation ~A, component ~A~@:>")
2245   (class-of operation) (class-of c)))
2246
2247(defmethod perform ((operation operation) (c module))
2248  (declare (ignorable operation c))
2249  nil)
2250
2251(defmethod mark-operation-done ((operation operation) (c component))
2252  (setf (gethash (type-of operation) (component-operation-times c))
2253    (reduce #'max
2254            (cons (get-universal-time)
2255                  (mapcar #'safe-file-write-date (input-files operation c))))))
2256
2257(defmethod perform-with-restarts (operation component)
2258  ;; TOO verbose, especially as the default. Add your own :before method
2259  ;; to perform-with-restart or perform if you want that:
2260  #|(when *asdf-verbose* (explain operation component))|#
2261  (perform operation component))
2262
2263(defmethod perform-with-restarts :around (operation component)
2264  (loop
2265    (restart-case
2266        (return (call-next-method))
2267      (retry ()
2268        :report
2269        (lambda (s)
2270          (format s (compatfmt "~@<Retry ~A.~@:>")
2271                  (operation-description operation component))))
2272      (accept ()
2273        :report
2274        (lambda (s)
2275          (format s (compatfmt "~@<Continue, treating ~A as having been successful.~@:>")
2276                  (operation-description operation component)))
2277        (mark-operation-done operation component)
2278        (return)))))
2279
2280(defmethod explain ((operation operation) (component component))
2281  (asdf-message (compatfmt "~&~@<; ~@;~A~:>~%")
2282                (operation-description operation component)))
2283
2284(defmethod operation-description (operation component)
2285  (format nil (compatfmt "~@<~A on ~A~@:>")
2286          (class-of operation) component))
2287
2288;;;; -------------------------------------------------------------------------
2289;;;; compile-op
2290
2291(defclass compile-op (operation)
2292  ((proclamations :initarg :proclamations :accessor compile-op-proclamations :initform nil)
2293   (on-warnings :initarg :on-warnings :accessor operation-on-warnings
2294                :initform *compile-file-warnings-behaviour*)
2295   (on-failure :initarg :on-failure :accessor operation-on-failure
2296               :initform *compile-file-failure-behaviour*)
2297   (flags :initarg :flags :accessor compile-op-flags
2298          :initform nil)))
2299
2300(defun* output-file (operation component)
2301  "The unique output file of performing OPERATION on COMPONENT"
2302  (let ((files (output-files operation component)))
2303    (assert (length=n-p files 1))
2304    (first files)))
2305
2306(defun* ensure-all-directories-exist (pathnames)
2307   (loop :for pn :in pathnames
2308     :for pathname = (if (typep pn 'logical-pathname)
2309                         (translate-logical-pathname pn)
2310                         pn)
2311     :do (ensure-directories-exist pathname)))
2312
2313(defmethod perform :before ((operation compile-op) (c source-file))
2314  (ensure-all-directories-exist (asdf:output-files operation c)))
2315
2316(defmethod perform :after ((operation operation) (c component))
2317  (mark-operation-done operation c))
2318
2319(defgeneric* around-compile-hook (component))
2320(defgeneric* call-with-around-compile-hook (component thunk))
2321
2322(defmethod around-compile-hook ((c component))
2323  (cond
2324    ((slot-boundp c 'around-compile)
2325     (slot-value c 'around-compile))
2326    ((component-parent c)
2327     (around-compile-hook (component-parent c)))))
2328
2329(defun ensure-function (fun &key (package :asdf))
2330  (etypecase fun
2331    ((or symbol function) fun)
2332    (cons (eval `(function ,fun)))
2333    (string (eval `(function ,(with-standard-io-syntax
2334                               (let ((*package* (find-package package)))
2335                                 (read-from-string fun))))))))
2336
2337(defmethod call-with-around-compile-hook ((c component) thunk)
2338  (let ((hook (around-compile-hook c)))
2339    (if hook
2340        (funcall (ensure-function hook) thunk)
2341        (funcall thunk))))
2342
2343(defvar *compile-op-compile-file-function* 'compile-file*
2344  "Function used to compile lisp files.")
2345
2346;;; perform is required to check output-files to find out where to put
2347;;; its answers, in case it has been overridden for site policy
2348(defmethod perform ((operation compile-op) (c cl-source-file))
2349  #-:broken-fasl-loader
2350  (let ((source-file (component-pathname c))
2351        ;; on some implementations, there are more than one output-file,
2352        ;; but the first one should always be the primary fasl that gets loaded.
2353        (output-file (first (output-files operation c)))
2354        (*compile-file-warnings-behaviour* (operation-on-warnings operation))
2355        (*compile-file-failure-behaviour* (operation-on-failure operation)))
2356    (multiple-value-bind (output warnings-p failure-p)
2357        (call-with-around-compile-hook
2358         c (lambda ()
2359             (apply *compile-op-compile-file-function* source-file
2360                    :output-file output-file (compile-op-flags operation))))
2361      (unless output
2362        (error 'compile-error :component c :operation operation))
2363      (when failure-p
2364        (case (operation-on-failure operation)
2365          (:warn (warn
2366                  (compatfmt "~@<COMPILE-FILE failed while performing ~A on ~A.~@:>")
2367                  operation c))
2368          (:error (error 'compile-failed :component c :operation operation))
2369          (:ignore nil)))
2370      (when warnings-p
2371        (case (operation-on-warnings operation)
2372          (:warn (warn
2373                  (compatfmt "~@<COMPILE-FILE warned while performing ~A on ~A.~@:>")
2374                  operation c))
2375          (:error (error 'compile-warned :component c :operation operation))
2376          (:ignore nil))))))
2377
2378(defmethod output-files ((operation compile-op) (c cl-source-file))
2379  (declare (ignorable operation))
2380  (let ((p (lispize-pathname (component-pathname c))))
2381    #-broken-fasl-loader (list (compile-file-pathname p))
2382    #+broken-fasl-loader (list p)))
2383
2384(defmethod perform ((operation compile-op) (c static-file))
2385  (declare (ignorable operation c))
2386  nil)
2387
2388(defmethod output-files ((operation compile-op) (c static-file))
2389  (declare (ignorable operation c))
2390  nil)
2391
2392(defmethod input-files ((operation compile-op) (c static-file))
2393  (declare (ignorable operation c))
2394  nil)
2395
2396(defmethod operation-description ((operation compile-op) component)
2397  (declare (ignorable operation))
2398  (format nil (compatfmt "~@<compiling ~3i~_~A~@:>") component))
2399
2400(defmethod operation-description ((operation compile-op) (component module))
2401  (declare (ignorable operation))
2402  (format nil (compatfmt "~@<compiled ~3i~_~A~@:>") component))
2403
2404
2405;;;; -------------------------------------------------------------------------
2406;;;; load-op
2407
2408(defclass basic-load-op (operation) ())
2409
2410(defclass load-op (basic-load-op) ())
2411
2412(defmethod perform-with-restarts ((o load-op) (c cl-source-file))
2413  (loop
2414    (restart-case
2415        (return (call-next-method))
2416      (try-recompiling ()
2417        :report (lambda (s)
2418                  (format s "Recompile ~a and try loading it again"
2419                          (component-name c)))
2420        (perform (make-sub-operation c o c 'compile-op) c)))))
2421
2422(defmethod perform ((o load-op) (c cl-source-file))
2423  (map () #'load (input-files o c)))
2424
2425(defmethod perform ((operation load-op) (c static-file))
2426  (declare (ignorable operation c))
2427  nil)
2428
2429(defmethod operation-done-p ((operation load-op) (c static-file))
2430  (declare (ignorable operation c))
2431  t)
2432
2433(defmethod output-files ((operation operation) (c component))
2434  (declare (ignorable operation c))
2435  nil)
2436
2437(defmethod component-depends-on ((operation load-op) (c component))
2438  (declare (ignorable operation))
2439  (cons (list 'compile-op (component-name c))
2440        (call-next-method)))
2441
2442(defmethod operation-description ((operation load-op) component)
2443  (declare (ignorable operation))
2444  (format nil (compatfmt "~@<loading ~3i~_~A~@:>")
2445          component))
2446
2447(defmethod operation-description ((operation load-op) (component cl-source-file))
2448  (declare (ignorable operation))
2449  (format nil (compatfmt "~@<loading FASL for ~3i~_~A~@:>")
2450          component))
2451
2452(defmethod operation-description ((operation load-op) (component module))
2453  (declare (ignorable operation))
2454  (format nil (compatfmt "~@<loaded ~3i~_~A~@:>")
2455          component))
2456
2457;;;; -------------------------------------------------------------------------
2458;;;; load-source-op
2459
2460(defclass load-source-op (basic-load-op) ())
2461
2462(defmethod perform ((o load-source-op) (c cl-source-file))
2463  (declare (ignorable o))
2464  (let ((source (component-pathname c)))
2465    (setf (component-property c 'last-loaded-as-source)
2466          (and (call-with-around-compile-hook c (lambda () (load source)))
2467               (get-universal-time)))))
2468
2469(defmethod perform ((operation load-source-op) (c static-file))
2470  (declare (ignorable operation c))
2471  nil)
2472
2473(defmethod output-files ((operation load-source-op) (c component))
2474  (declare (ignorable operation c))
2475  nil)
2476
2477;;; FIXME: We simply copy load-op's dependencies.  This is Just Not Right.
2478(defmethod component-depends-on ((o load-source-op) (c component))
2479  (declare (ignorable o))
2480  (loop :with what-would-load-op-do = (component-depends-on 'load-op c)
2481    :for (op . co) :in what-would-load-op-do
2482    :when (eq op 'load-op) :collect (cons 'load-source-op co)))
2483
2484(defmethod operation-done-p ((o load-source-op) (c source-file))
2485  (declare (ignorable o))
2486  (if (or (not (component-property c 'last-loaded-as-source))
2487          (> (safe-file-write-date (component-pathname c))
2488             (component-property c 'last-loaded-as-source)))
2489      nil t))
2490
2491(defmethod operation-description ((operation load-source-op) component)
2492  (declare (ignorable operation))
2493  (format nil (compatfmt "~@<Loading source of ~3i~_~A~@:>")
2494          component))
2495
2496(defmethod operation-description ((operation load-source-op) (component module))
2497  (declare (ignorable operation))
2498  (format nil (compatfmt "~@<Loaded source of ~3i~_~A~@:>") component))
2499
2500
2501;;;; -------------------------------------------------------------------------
2502;;;; test-op
2503
2504(defclass test-op (operation) ())
2505
2506(defmethod perform ((operation test-op) (c component))
2507  (declare (ignorable operation c))
2508  nil)
2509
2510(defmethod operation-done-p ((operation test-op) (c system))
2511  "Testing a system is _never_ done."
2512  (declare (ignorable operation c))
2513  nil)
2514
2515(defmethod component-depends-on :around ((o test-op) (c system))
2516  (declare (ignorable o))
2517  (cons `(load-op ,(component-name c)) (call-next-method)))
2518
2519
2520;;;; -------------------------------------------------------------------------
2521;;;; Invoking Operations
2522
2523(defgeneric* operate (operation-class system &key &allow-other-keys))
2524(defgeneric* perform-plan (plan &key))
2525
2526;;;; Separating this into a different function makes it more forward-compatible
2527(defun* cleanup-upgraded-asdf (old-version)
2528  (let ((new-version (asdf:asdf-version)))
2529    (unless (equal old-version new-version)
2530      (cond
2531        ((version-satisfies new-version old-version)
2532         (asdf-message (compatfmt "~&~@<; ~@;Upgraded ASDF from version ~A to version ~A~@:>~%")
2533                       old-version new-version))
2534        ((version-satisfies old-version new-version)
2535         (warn (compatfmt "~&~@<; ~@;Downgraded ASDF from version ~A to version ~A~@:>~%")
2536               old-version new-version))
2537        (t
2538         (asdf-message (compatfmt "~&~@<; ~@;Changed ASDF from version ~A to incompatible version ~A~@:>~%")
2539                       old-version new-version)))
2540      (let ((asdf (funcall (find-symbol* 'find-system :asdf) :asdf)))
2541        ;; Invalidate all systems but ASDF itself.
2542        (setf *defined-systems* (make-defined-systems-table))
2543        (register-system asdf)
2544        ;; If we're in the middle of something, restart it.
2545        (when *systems-being-defined*
2546          (let ((l (loop :for name :being :the :hash-keys :of *systems-being-defined* :collect name)))
2547            (clrhash *systems-being-defined*)
2548            (dolist (s l) (find-system s nil))))
2549        t))))
2550
2551;;;; Try to upgrade of ASDF. If a different version was used, return T.
2552;;;; We need do that before we operate on anything that depends on ASDF.
2553(defun* upgrade-asdf ()
2554  (let ((version (asdf:asdf-version)))
2555    (handler-bind (((or style-warning warning) #'muffle-warning))
2556      (operate 'load-op :asdf :verbose nil))
2557    (cleanup-upgraded-asdf version)))
2558
2559(defmethod perform-plan ((steps list) &key)
2560  (let ((*package* *package*)
2561        (*readtable* *readtable*))
2562    (with-compilation-unit ()
2563      (loop :for (op . component) :in steps :do
2564        (perform-with-restarts op component)))))
2565
2566(defmethod operate (operation-class system &rest args
2567                    &key ((:verbose *asdf-verbose*) *asdf-verbose*) version force
2568                    &allow-other-keys)
2569  (declare (ignore force))
2570  (with-system-definitions ()
2571    (let* ((op (apply 'make-instance operation-class
2572                      :original-initargs args
2573                      args))
2574           (*verbose-out* (if *asdf-verbose* *standard-output* (make-broadcast-stream)))
2575           (system (etypecase system
2576                     (system system)
2577                     ((or string symbol) (find-system system)))))
2578      (unless (version-satisfies system version)
2579        (error 'missing-component-of-version :requires system :version version))
2580      (let ((steps (traverse op system)))
2581        (when (and (not (equal '("asdf") (component-find-path system)))
2582                   (find '("asdf") (mapcar 'cdr steps)
2583                         :test 'equal :key 'component-find-path)
2584                   (upgrade-asdf))
2585          ;; If we needed to upgrade ASDF to achieve our goal,
2586          ;; then do it specially as the first thing, then
2587          ;; invalidate all existing system
2588          ;; retry the whole thing with the new OPERATE function,
2589          ;; which on some implementations
2590          ;; has a new symbol shadowing the current one.
2591          (return-from operate
2592            (apply (find-symbol* 'operate :asdf) operation-class system args)))
2593        (perform-plan steps)
2594        (values op steps)))))
2595
2596(defun* oos (operation-class system &rest args &key force verbose version
2597            &allow-other-keys)
2598  (declare (ignore force verbose version))
2599  (apply 'operate operation-class system args))
2600
2601(let ((operate-docstring
2602  "Operate does three things:
2603
26041. It creates an instance of OPERATION-CLASS using any keyword parameters
2605as initargs.
26062. It finds the  asdf-system specified by SYSTEM (possibly loading
2607it from disk).
26083. It then calls TRAVERSE with the operation and system as arguments
2609
2610The traverse operation is wrapped in WITH-COMPILATION-UNIT and error
2611handling code. If a VERSION argument is supplied, then operate also
2612ensures that the system found satisfies it using the VERSION-SATISFIES
2613method.
2614
2615Note that dependencies may cause the operation to invoke other
2616operations on the system or its components: the new operations will be
2617created with the same initargs as the original one.
2618"))
2619  (setf (documentation 'oos 'function)
2620        (format nil
2621                "Short for _operate on system_ and an alias for the OPERATE function.~%~%~a"
2622                operate-docstring))
2623  (setf (documentation 'operate 'function)
2624        operate-docstring))
2625
2626(defun* load-system (system &rest args &key force verbose version &allow-other-keys)
2627  "Shorthand for `(operate 'asdf:load-op system)`.
2628See OPERATE for details."
2629  (declare (ignore force verbose version))
2630  (apply 'operate 'load-op system args)
2631  t)
2632
2633(defun* load-systems (&rest systems)
2634  (map () 'load-system systems))
2635
2636(defun* compile-system (system &rest args &key force verbose version
2637                       &allow-other-keys)
2638  "Shorthand for `(operate 'asdf:compile-op system)`. See OPERATE
2639for details."
2640  (declare (ignore force verbose version))
2641  (apply 'operate 'compile-op system args)
2642  t)
2643
2644(defun* test-system (system &rest args &key force verbose version
2645                    &allow-other-keys)
2646  "Shorthand for `(operate 'asdf:test-op system)`. See OPERATE for
2647details."
2648  (declare (ignore force verbose version))
2649  (apply 'operate 'test-op system args)
2650  t)
2651
2652;;;; -------------------------------------------------------------------------
2653;;;; Defsystem
2654
2655(defun* load-pathname ()
2656  (resolve-symlinks* (or *load-pathname* *compile-file-pathname*)))
2657
2658(defun* determine-system-pathname (pathname pathname-supplied-p)
2659  ;; The defsystem macro calls us to determine
2660  ;; the pathname of a system as follows:
2661  ;; 1. the one supplied,
2662  ;; 2. derived from *load-pathname* via load-pathname
2663  ;; 3. taken from the *default-pathname-defaults* via default-directory
2664  (let* ((file-pathname (load-pathname))
2665         (directory-pathname (and file-pathname (pathname-directory-pathname file-pathname))))
2666    (or (and pathname-supplied-p
2667             (merge-pathnames* (coerce-pathname pathname :type :directory)
2668                               directory-pathname))
2669        directory-pathname
2670        (default-directory))))
2671
2672(defun* class-for-type (parent type)
2673  (or (loop :for symbol :in (list
2674                             type
2675                             (find-symbol* type *package*)
2676                             (find-symbol* type :asdf))
2677        :for class = (and symbol (find-class symbol nil))
2678        :when (and class
2679                   (#-cormanlisp subtypep #+cormanlisp cl::subclassp
2680                                 class (find-class 'component)))
2681        :return class)
2682      (and (eq type :file)
2683           (or (and parent (module-default-component-class parent))
2684               (find-class *default-component-class*)))
2685      (sysdef-error "don't recognize component type ~A" type)))
2686
2687(defun* maybe-add-tree (tree op1 op2 c)
2688  "Add the node C at /OP1/OP2 in TREE, unless it's there already.
2689Returns the new tree (which probably shares structure with the old one)"
2690  (let ((first-op-tree (assoc op1 tree)))
2691    (if first-op-tree
2692        (progn
2693          (aif (assoc op2 (cdr first-op-tree))
2694               (if (find c (cdr it) :test #'equal)
2695                   nil
2696                   (setf (cdr it) (cons c (cdr it))))
2697               (setf (cdr first-op-tree)
2698                     (acons op2 (list c) (cdr first-op-tree))))
2699          tree)
2700        (acons op1 (list (list op2 c)) tree))))
2701
2702(defun* union-of-dependencies (&rest deps)
2703  (let ((new-tree nil))
2704    (dolist (dep deps)
2705      (dolist (op-tree dep)
2706        (dolist (op  (cdr op-tree))
2707          (dolist (c (cdr op))
2708            (setf new-tree
2709                  (maybe-add-tree new-tree (car op-tree) (car op) c))))))
2710    new-tree))
2711
2712
2713(defvar *serial-depends-on* nil)
2714
2715(defun* sysdef-error-component (msg type name value)
2716  (sysdef-error (strcat msg (compatfmt "~&~@<The value specified for ~(~A~) ~A is ~S~@:>"))
2717                type name value))
2718
2719(defun* check-component-input (type name weakly-depends-on
2720                              depends-on components in-order-to)
2721  "A partial test of the values of a component."
2722  (unless (listp depends-on)
2723    (sysdef-error-component ":depends-on must be a list."
2724                            type name depends-on))
2725  (unless (listp weakly-depends-on)
2726    (sysdef-error-component ":weakly-depends-on must be a list."
2727                            type name weakly-depends-on))
2728  (unless (listp components)
2729    (sysdef-error-component ":components must be NIL or a list of components."
2730                            type name components))
2731  (unless (and (listp in-order-to) (listp (car in-order-to)))
2732    (sysdef-error-component ":in-order-to must be NIL or a list of components."
2733                            type name in-order-to)))
2734
2735(defun* %remove-component-inline-methods (component)
2736  (dolist (name +asdf-methods+)
2737    (map ()
2738         ;; this is inefficient as most of the stored
2739         ;; methods will not be for this particular gf
2740         ;; But this is hardly performance-critical
2741         #'(lambda (m)
2742             (remove-method (symbol-function name) m))
2743         (component-inline-methods component)))
2744  ;; clear methods, then add the new ones
2745  (setf (component-inline-methods component) nil))
2746
2747(defun* %define-component-inline-methods (ret rest)
2748  (dolist (name +asdf-methods+)
2749    (let ((keyword (intern (symbol-name name) :keyword)))
2750      (loop :for data = rest :then (cddr data)
2751        :for key = (first data)
2752        :for value = (second data)
2753        :while data
2754        :when (eq key keyword) :do
2755        (destructuring-bind (op qual (o c) &body body) value
2756          (pushnew
2757           (eval `(defmethod ,name ,qual ((,o ,op) (,c (eql ,ret)))
2758                             ,@body))
2759           (component-inline-methods ret)))))))
2760
2761(defun* %refresh-component-inline-methods (component rest)
2762  (%remove-component-inline-methods component)
2763  (%define-component-inline-methods component rest))
2764
2765(defun* parse-component-form (parent options)
2766  (destructuring-bind
2767        (type name &rest rest &key
2768              ;; the following list of keywords is reproduced below in the
2769              ;; remove-keys form.  important to keep them in sync
2770              components pathname default-component-class
2771              perform explain output-files operation-done-p
2772              weakly-depends-on
2773              depends-on serial in-order-to do-first
2774              (version nil versionp)
2775              ;; list ends
2776              &allow-other-keys) options
2777    (declare (ignorable perform explain output-files operation-done-p))
2778    (check-component-input type name weakly-depends-on depends-on components in-order-to)
2779
2780    (when (and parent
2781               (find-component parent name)
2782               ;; ignore the same object when rereading the defsystem
2783               (not
2784                (typep (find-component parent name)
2785                       (class-for-type parent type))))
2786      (error 'duplicate-names :name name))
2787
2788    (when versionp
2789      (unless (parse-version version nil)
2790        (warn (compatfmt "~@<Invalid version ~S for component ~S~@[ of ~S~]~@:>")
2791              version name parent)))
2792
2793    (let* ((args (list* :name (coerce-name name)
2794                        :pathname pathname
2795                        :parent parent
2796                        (remove-keys
2797                         '(components pathname default-component-class
2798                           perform explain output-files operation-done-p
2799                           weakly-depends-on depends-on serial in-order-to)
2800                         rest)))
2801           (ret (find-component parent name)))
2802      (when weakly-depends-on
2803        (appendf depends-on (remove-if (complement #'find-system) weakly-depends-on)))
2804      (when *serial-depends-on*
2805        (push *serial-depends-on* depends-on))
2806      (if ret ; preserve identity
2807          (apply 'reinitialize-instance ret args)
2808          (setf ret (apply 'make-instance (class-for-type parent type) args)))
2809      (component-pathname ret) ; eagerly compute the absolute pathname
2810      (when (typep ret 'module)
2811        (setf (module-default-component-class ret)
2812              (or default-component-class
2813                  (and (typep parent 'module)
2814                       (module-default-component-class parent))))
2815        (let ((*serial-depends-on* nil))
2816          (setf (module-components ret)
2817                (loop
2818                  :for c-form :in components
2819                  :for c = (parse-component-form ret c-form)
2820                  :for name = (component-name c)
2821                  :collect c
2822                  :when serial :do (setf *serial-depends-on* name))))
2823        (compute-module-components-by-name ret))
2824
2825      (setf (component-load-dependencies ret) depends-on) ;; Used by POIU
2826
2827      (setf (component-in-order-to ret)
2828            (union-of-dependencies
2829             in-order-to
2830             `((compile-op (compile-op ,@depends-on))
2831               (load-op (load-op ,@depends-on)))))
2832      (setf (component-do-first ret)
2833            (union-of-dependencies
2834             do-first
2835             `((compile-op (load-op ,@depends-on)))))
2836
2837      (%refresh-component-inline-methods ret rest)
2838      ret)))
2839
2840(defun* reset-system (system &rest keys &key &allow-other-keys)
2841  (change-class (change-class system 'proto-system) 'system)
2842  (apply 'reinitialize-instance system keys))
2843
2844(defun* do-defsystem (name &rest options
2845                           &key (pathname nil pathname-arg-p) (class 'system)
2846                           defsystem-depends-on &allow-other-keys)
2847  ;; The system must be registered before we parse the body,
2848  ;; otherwise we recur when trying to find an existing system
2849  ;; of the same name to reuse options (e.g. pathname) from.
2850  ;; To avoid infinite recursion in cases where you defsystem a system
2851  ;; that is registered to a different location to find-system,
2852  ;; we also need to remember it in a special variable *systems-being-defined*.
2853  (with-system-definitions ()
2854    (let* ((name (coerce-name name))
2855           (registered (system-registered-p name))
2856           (registered! (if registered
2857                            (rplaca registered (get-universal-time))
2858                            (register-system (make-instance 'system :name name))))
2859           (system (reset-system (cdr registered!)
2860                                :name name :source-file (load-pathname)))
2861           (component-options (remove-keys '(:class) options)))
2862      (setf (gethash name *systems-being-defined*) system)
2863      (apply 'load-systems defsystem-depends-on)
2864      ;; We change-class (when necessary) AFTER we load the defsystem-dep's
2865      ;; since the class might not be defined as part of those.
2866      (let ((class (class-for-type nil class)))
2867        (unless (eq (type-of system) class)
2868          (change-class system class)))
2869      (parse-component-form
2870       nil (list*
2871            :module name
2872            :pathname (determine-system-pathname pathname pathname-arg-p)
2873            component-options)))))
2874
2875(defmacro defsystem (name &body options)
2876  `(apply 'do-defsystem ',name ',options))
2877
2878;;;; ---------------------------------------------------------------------------
2879;;;; run-shell-command
2880;;;;
2881;;;; run-shell-command functions for other lisp implementations will be
2882;;;; gratefully accepted, if they do the same thing.
2883;;;; If the docstring is ambiguous, send a bug report.
2884;;;;
2885;;;; WARNING! The function below is mostly dysfunctional.
2886;;;; For instance, it will probably run fine on most implementations on Unix,
2887;;;; which will hopefully use the shell /bin/sh (which we force in some cases)
2888;;;; which is hopefully reasonably compatible with a POSIX *or* Bourne shell.
2889;;;; But behavior on Windows may vary wildly between implementations,
2890;;;; either relying on your having installed a POSIX sh, or going through
2891;;;; the CMD.EXE interpreter, for a totally different meaning, depending on
2892;;;; what is easily expressible in said implementation.
2893;;;;
2894;;;; We probably should move this functionality to its own system and deprecate
2895;;;; use of it from the asdf package. However, this would break unspecified
2896;;;; existing software, so until a clear alternative exists, we can't deprecate
2897;;;; it, and even after it's been deprecated, we will support it for a few
2898;;;; years so everyone has time to migrate away from it. -- fare 2009-12-01
2899;;;;
2900;;;; As a suggested replacement which is portable to all ASDF-supported
2901;;;; implementations and operating systems except Genera, I recommend
2902;;;; xcvb-driver's xcvb-driver:run-program/process-output-stream and its
2903;;;; derivatives such as xcvb-driver:run-program/for-side-effects.
2904
2905(defun* run-shell-command (control-string &rest args)
2906  "Interpolate ARGS into CONTROL-STRING as if by FORMAT, and
2907synchronously execute the result using a Bourne-compatible shell, with
2908output to *VERBOSE-OUT*.  Returns the shell's exit code."
2909  (let ((command (apply 'format nil control-string args)))
2910    (asdf-message "; $ ~A~%" command)
2911
2912    #+abcl
2913    (ext:run-shell-command command :output *verbose-out*)
2914
2915    #+allegro
2916    ;; will this fail if command has embedded quotes - it seems to work
2917    (multiple-value-bind (stdout stderr exit-code)
2918        (excl.osi:command-output
2919         #-mswindows (vector "/bin/sh" "/bin/sh" "-c" command)
2920         #+mswindows command ; BEWARE!
2921         :input nil :whole nil
2922         #+mswindows :show-window #+mswindows :hide)
2923      (asdf-message "~{~&~a~%~}~%" stderr)
2924      (asdf-message "~{~&~a~%~}~%" stdout)
2925      exit-code)
2926
2927    #+clisp
2928    ;; CLISP returns NIL for exit status zero.
2929    (if *verbose-out*
2930        (let* ((new-command (format nil "( ~A ) ; r=$? ; echo ; echo ASDF-EXIT-STATUS $r"
2931                                    command))
2932               (outstream (ext:run-shell-command new-command :output :stream :wait t)))
2933            (multiple-value-bind (retval out-lines)
2934                (unwind-protect
2935                     (parse-clisp-shell-output outstream)
2936                  (ignore-errors (close outstream)))
2937              (asdf-message "~{~&~a~%~}~%" out-lines)
2938              retval))
2939        ;; there will be no output, just grab up the exit status
2940        (or (ext:run-shell-command command :output nil :wait t) 0))
2941
2942    #+clozure
2943    (nth-value 1
2944               (ccl:external-process-status
2945                (ccl:run-program
2946                 (cond
2947                   ((os-unix-p) "/bin/sh")
2948                   ((os-windows-p) (strcat "CMD /C " command)) ; BEWARE!
2949                   (t (error "Unsupported OS")))
2950                 (if (os-unix-p) (list "-c" command) '())
2951                 :input nil :output *verbose-out* :wait t)))
2952
2953    #+(or cmu scl)
2954    (ext:process-exit-code
2955     (ext:run-program
2956      "/bin/sh"
2957      (list "-c" command)
2958      :input nil :output *verbose-out*))
2959
2960    #+cormanlisp
2961    (win32:system command)
2962
2963    #+ecl ;; courtesy of Juan Jose Garcia Ripoll
2964    (ext:system command)
2965
2966    #+gcl
2967    (lisp:system command)
2968
2969    #+lispworks
2970    (apply 'system:call-system-showing-output command
2971           :show-cmd nil :prefix "" :output-stream *verbose-out*
2972           (when (os-unix-p) '(:shell-type "/bin/sh")))
2973
2974    #+mcl
2975    (ccl::with-cstrs ((%command command)) (_system %command))
2976
2977    #+sbcl
2978    (sb-ext:process-exit-code
2979     (apply 'sb-ext:run-program
2980            #+win32 "sh" #-win32 "/bin/sh"
2981            (list  "-c" command)
2982            :input nil :output *verbose-out*
2983            #+win32 '(:search t) #-win32 nil))
2984
2985    #+xcl
2986    (ext:run-shell-command command)
2987
2988    #-(or abcl allegro clisp clozure cmu ecl gcl lispworks mcl sbcl scl xcl)
2989    (error "RUN-SHELL-COMMAND not implemented for this Lisp")))
2990
2991#+clisp
2992(defun* parse-clisp-shell-output (stream)
2993  "Helper function for running shell commands under clisp.  Parses a specially-
2994crafted output string to recover the exit status of the shell command and a
2995list of lines of output."
2996  (loop :with status-prefix = "ASDF-EXIT-STATUS "
2997    :with prefix-length = (length status-prefix)
2998    :with exit-status = -1 :with lines = ()
2999    :for line = (read-line stream nil nil)
3000    :while line :do (push line lines) :finally
3001    (let* ((last (car lines))
3002           (status (and last (>= (length last) prefix-length)
3003                        (string-equal last status-prefix :end1 prefix-length)
3004                        (parse-integer last :start prefix-length :junk-allowed t))))
3005      (when status
3006        (setf exit-status status)
3007        (pop lines) (when (equal "" (car lines)) (pop lines)))
3008      (return (values exit-status (reverse lines))))))
3009
3010;;;; ---------------------------------------------------------------------------
3011;;;; system-relative-pathname
3012
3013(defun* system-definition-pathname (x)
3014  ;; As of 2.014.8, we mean to make this function obsolete,
3015  ;; but that won't happen until all clients have been updated.
3016  ;;(cerror "Use ASDF:SYSTEM-SOURCE-FILE instead"
3017  "Function ASDF:SYSTEM-DEFINITION-PATHNAME is obsolete.
3018It used to expose ASDF internals with subtle differences with respect to
3019user expectations, that have been refactored away since.
3020We recommend you use ASDF:SYSTEM-SOURCE-FILE instead
3021for a mostly compatible replacement that we're supporting,
3022or even ASDF:SYSTEM-SOURCE-DIRECTORY or ASDF:SYSTEM-RELATIVE-PATHNAME
3023if that's whay you mean." ;;)
3024  (system-source-file x))
3025
3026(defmethod system-source-file ((system system))
3027  (%system-source-file system))
3028(defmethod system-source-file ((system-name string))
3029  (%system-source-file (find-system system-name)))
3030(defmethod system-source-file ((system-name symbol))
3031  (%system-source-file (find-system system-name)))
3032
3033(defun* system-source-directory (system-designator)
3034  "Return a pathname object corresponding to the
3035directory in which the system specification (.asd file) is
3036located."
3037  (pathname-directory-pathname (system-source-file system-designator)))
3038
3039(defun* relativize-directory (directory)
3040  (cond
3041    ((stringp directory)
3042     (list :relative directory))
3043    ((eq (car directory) :absolute)
3044     (cons :relative (cdr directory)))
3045    (t
3046     directory)))
3047
3048(defun* relativize-pathname-directory (pathspec)
3049  (let ((p (pathname pathspec)))
3050    (make-pathname
3051     :directory (relativize-directory (pathname-directory p))
3052     :defaults p)))
3053
3054(defun* system-relative-pathname (system name &key type)
3055  (merge-pathnames*
3056   (coerce-pathname name :type type)
3057   (system-source-directory system)))
3058
3059
3060;;; ---------------------------------------------------------------------------
3061;;; implementation-identifier
3062;;;
3063;;; produce a string to identify current implementation.
3064;;; Initially stolen from SLIME's SWANK, rewritten since.
3065;;; The (car '(...)) idiom avoids unreachable code warnings.
3066
3067(defparameter *implementation-type*
3068  (car '(#+abcl :abcl #+allegro :acl
3069         #+clozure :ccl #+clisp :clisp #+cormanlisp :corman #+cmu :cmu
3070         #+ecl :ecl #+gcl :gcl #+lispworks :lw #+mcl :mcl
3071         #+sbcl :sbcl #+scl :scl #+symbolics :symbolic #+xcl :xcl)))
3072
3073(defparameter *operating-system*
3074  (car '(#+cygwin :cygwin #+(or windows mswindows win32 mingw32) :win
3075         #+(or linux linux-target) :linux ;; for GCL at least, must appear before :bsd.
3076         #+(or macosx darwin darwin-target apple) :macosx ; also before :bsd
3077         #+(or solaris sunos) :solaris
3078         #+(or freebsd netbsd openbsd bsd) :bsd
3079         #+unix :unix
3080         #+genera :genera)))
3081
3082(defparameter *architecture*
3083  (car '(#+(or amd64 x86-64 x86_64 x8664-target (and word-size=64 pc386)) :x64
3084         #+(or x86 i386 i486 i586 i686 pentium3 pentium4 pc386 iapx386 x8632-target) :x86
3085         #+hppa64 :hppa64 #+hppa :hppa
3086         #+(or ppc64 ppc64-target) :ppc64
3087         #+(or ppc32 ppc32-target ppc powerpc) :ppc32
3088         #+sparc64 :sparc64 #+(or sparc32 sparc) :sparc32
3089         #+(or arm arm-target) :arm
3090         #+(or java java-1.4 java-1.5 java-1.6 java-1.7) :java
3091         #+mipsel :mispel #+mipseb :mipseb #+mips :mips
3092         #+alpha :alpha #+imach :imach)))
3093
3094(defparameter *lisp-version-string*
3095  (let ((s (lisp-implementation-version)))
3096    (car
3097     (list
3098      #+allegro
3099      (format nil "~A~A~@[~A~]"
3100              excl::*common-lisp-version-number*
3101              ;; ANSI vs MoDeRn - thanks to Robert Goldman and Charley Cox
3102              (if (eq excl:*current-case-mode* :case-sensitive-lower) "M" "A")
3103              ;; Note if not using International ACL
3104              ;; see http://www.franz.com/support/documentation/8.1/doc/operators/excl/ics-target-case.htm
3105              (excl:ics-target-case (:-ics "8")))
3106      #+armedbear (format nil "~a-fasl~a" s system::*fasl-version*)
3107      #+clisp
3108      (subseq s 0 (position #\space s)) ; strip build information (date, etc.)
3109      #+clozure
3110      (format nil "~d.~d-f~d" ; shorten for windows
3111              ccl::*openmcl-major-version*
3112              ccl::*openmcl-minor-version*
3113              (logand ccl::fasl-version #xFF))
3114      #+cmu (substitute #\- #\/ s)
3115      #+ecl (format nil "~A~@[-~A~]" s
3116                    (let ((vcs-id (ext:lisp-implementation-vcs-id)))
3117                      (subseq vcs-id 0 (min (length vcs-id) 8))))
3118      #+gcl (subseq s (1+ (position #\space s)))
3119      #+genera
3120      (multiple-value-bind (major minor) (sct:get-system-version "System")
3121        (format nil "~D.~D" major minor))
3122      #+mcl (subseq s 8) ; strip the leading "Version "
3123      s))))
3124
3125(defun* implementation-type ()
3126  *implementation-type*)
3127
3128(defun* implementation-identifier ()
3129  (substitute-if
3130   #\_ #'(lambda (x) (find x " /:;&^\\|?<>(){}[]$#`'\""))
3131   (format nil "~(~a~@{~@[-~a~]~}~)"
3132           (or *implementation-type* (lisp-implementation-type))
3133           (or *lisp-version-string* (lisp-implementation-version))
3134           (or *operating-system* (software-type))
3135           (or *architecture* (machine-type)))))
3136
3137
3138;;; ---------------------------------------------------------------------------
3139;;; Generic support for configuration files
3140
3141(defun inter-directory-separator ()
3142  (if (os-unix-p) #\: #\;))
3143
3144(defun* user-homedir ()
3145  (truenamize
3146   (pathname-directory-pathname
3147    #+mcl (current-user-homedir-pathname)
3148    #-mcl (user-homedir-pathname))))
3149
3150(defun* try-directory-subpath (x sub &key type)
3151  (let* ((p (and x (ensure-directory-pathname x)))
3152         (tp (and p (probe-file* p)))
3153         (sp (and tp (merge-pathnames* (coerce-pathname sub :type type) p)))
3154         (ts (and sp (probe-file* sp))))
3155    (and ts (values sp ts))))
3156(defun* user-configuration-directories ()
3157  (let ((dirs
3158         `(,@(when (os-unix-p)
3159               (cons
3160                (subpathname* (getenv "XDG_CONFIG_HOME") "common-lisp/")
3161                (loop :with dirs = (getenv "XDG_CONFIG_DIRS")
3162                  :for dir :in (split-string dirs :separator ":")
3163                  :collect (subpathname* dir "common-lisp/"))))
3164           ,@(when (os-windows-p)
3165               `(,(subpathname* (or #+lispworks (sys:get-folder-path :local-appdata)
3166                                    (getenv "LOCALAPPDATA"))
3167                               "common-lisp/config/")
3168                 ;; read-windows-registry HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Windows\CurrentVersion\Explorer\User Shell Folders\AppData
3169                 ,(subpathname* (or #+lispworks (sys:get-folder-path :appdata)
3170                                    (getenv "APPDATA"))
3171                                "common-lisp/config/")))
3172           ,(subpathname (user-homedir) ".config/common-lisp/"))))
3173    (remove-duplicates (remove-if-not #'absolute-pathname-p dirs)
3174                       :from-end t :test 'equal)))
3175(defun* system-configuration-directories ()
3176  (cond
3177    ((os-unix-p) '(#p"/etc/common-lisp/"))
3178    ((os-windows-p)
3179     (aif
3180      ;; read-windows-registry HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Windows\CurrentVersion\Explorer\User Shell Folders\Common AppData
3181      (subpathname* (or #+lispworks (sys:get-folder-path :common-appdata)
3182                        (getenv "ALLUSERSAPPDATA")
3183                        (subpathname* (getenv "ALLUSERSPROFILE") "Application Data/"))
3184                    "common-lisp/config/")
3185      (list it)))))
3186
3187(defun* in-first-directory (dirs x &key (direction :input))
3188  (loop :with fun = (ecase direction
3189                      ((nil :input :probe) 'probe-file*)
3190                      ((:output :io) 'identity))
3191    :for dir :in dirs
3192    :thereis (and dir (funcall fun (merge-pathnames* x (ensure-directory-pathname dir))))))
3193
3194(defun* in-user-configuration-directory (x &key (direction :input))
3195  (in-first-directory (user-configuration-directories) x :direction direction))
3196(defun* in-system-configuration-directory (x &key (direction :input))
3197  (in-first-directory (system-configuration-directories) x :direction direction))
3198
3199(defun* configuration-inheritance-directive-p (x)
3200  (let ((kw '(:inherit-configuration :ignore-inherited-configuration)))
3201    (or (member x kw)
3202        (and (length=n-p x 1) (member (car x) kw)))))
3203
3204(defun* report-invalid-form (reporter &rest args)
3205  (etypecase reporter
3206    (null
3207     (apply 'error 'invalid-configuration args))
3208    (function
3209     (apply reporter args))
3210    ((or symbol string)
3211     (apply 'error reporter args))
3212    (cons
3213     (apply 'apply (append reporter args)))))
3214
3215(defvar *ignored-configuration-form* nil)
3216
3217(defun* validate-configuration-form (form tag directive-validator
3218                                    &key location invalid-form-reporter)
3219  (unless (and (consp form) (eq (car form) tag))
3220    (setf *ignored-configuration-form* t)
3221    (report-invalid-form invalid-form-reporter :form form :location location)
3222    (return-from validate-configuration-form nil))
3223  (loop :with inherit = 0 :with ignore-invalid-p = nil :with x = (list tag)
3224    :for directive :in (cdr form)
3225    :when (cond
3226            ((configuration-inheritance-directive-p directive)
3227             (incf inherit) t)
3228            ((eq directive :ignore-invalid-entries)
3229             (setf ignore-invalid-p t) t)
3230            ((funcall directive-validator directive)
3231             t)
3232            (ignore-invalid-p
3233             nil)
3234            (t
3235             (setf *ignored-configuration-form* t)
3236             (report-invalid-form invalid-form-reporter :form directive :location location)
3237             nil))
3238    :do (push directive x)
3239    :finally
3240    (unless (= inherit 1)
3241      (report-invalid-form invalid-form-reporter
3242             :arguments (list (compatfmt "~@<One and only one of ~S or ~S is required.~@:>")
3243                              :inherit-configuration :ignore-inherited-configuration)))
3244    (return (nreverse x))))
3245
3246(defun* validate-configuration-file (file validator &key description)
3247  (let ((forms (read-file-forms file)))
3248    (unless (length=n-p forms 1)
3249      (error (compatfmt "~@<One and only one form allowed for ~A. Got: ~3i~_~S~@:>~%")
3250             description forms))
3251    (funcall validator (car forms) :location file)))
3252
3253(defun* hidden-file-p (pathname)
3254  (equal (first-char (pathname-name pathname)) #\.))
3255
3256(defun* directory* (pathname-spec &rest keys &key &allow-other-keys)
3257  (apply 'directory pathname-spec
3258         (append keys '#.(or #+allegro '(:directories-are-files nil :follow-symbolic-links nil)
3259                             #+clozure '(:follow-links nil)
3260                             #+clisp '(:circle t :if-does-not-exist :ignore)
3261                             #+(or cmu scl) '(:follow-links nil :truenamep nil)
3262                             #+sbcl (when (find-symbol* :resolve-symlinks '#:sb-impl)
3263                                      '(:resolve-symlinks nil))))))
3264
3265(defun* validate-configuration-directory (directory tag validator &key invalid-form-reporter)
3266  "Map the VALIDATOR across the .conf files in DIRECTORY, the TAG will
3267be applied to the results to yield a configuration form.  Current
3268values of TAG include :source-registry and :output-translations."
3269  (let ((files (sort (ignore-errors
3270                       (remove-if
3271                        'hidden-file-p
3272                        (directory* (make-pathname :name :wild :type "conf" :defaults directory))))
3273                     #'string< :key #'namestring)))
3274    `(,tag
3275      ,@(loop :for file :in files :append
3276          (loop :with ignore-invalid-p = nil
3277            :for form :in (read-file-forms file)
3278            :when (eq form :ignore-invalid-entries)
3279              :do (setf ignore-invalid-p t)
3280            :else
3281              :when (funcall validator form)
3282                :collect form
3283              :else
3284                :when ignore-invalid-p
3285                  :do (setf *ignored-configuration-form* t)
3286                :else
3287                  :do (report-invalid-form invalid-form-reporter :form form :location file)))
3288      :inherit-configuration)))
3289
3290
3291;;; ---------------------------------------------------------------------------
3292;;; asdf-output-translations
3293;;;
3294;;; this code is heavily inspired from
3295;;; asdf-binary-translations, common-lisp-controller and cl-launch.
3296;;; ---------------------------------------------------------------------------
3297
3298(defvar *output-translations* ()
3299  "Either NIL (for uninitialized), or a list of one element,
3300said element itself being a sorted list of mappings.
3301Each mapping is a pair of a source pathname and destination pathname,
3302and the order is by decreasing length of namestring of the source pathname.")
3303
3304(defvar *user-cache*
3305  (flet ((try (x &rest sub) (and x `(,x ,@sub))))
3306    (or
3307     (try (getenv "XDG_CACHE_HOME") "common-lisp" :implementation)
3308     (when (os-windows-p)
3309       (try (or #+lispworks (sys:get-folder-path :local-appdata)
3310                (getenv "LOCALAPPDATA")
3311                #+lispworks (sys:get-folder-path :appdata)
3312                (getenv "APPDATA"))
3313            "common-lisp" "cache" :implementation))
3314     '(:home ".cache" "common-lisp" :implementation))))
3315
3316(defun* output-translations ()
3317  (car *output-translations*))
3318
3319(defun* (setf output-translations) (new-value)
3320  (setf *output-translations*
3321        (list
3322         (stable-sort (copy-list new-value) #'>
3323                      :key #'(lambda (x)
3324                               (etypecase (car x)
3325                                 ((eql t) -1)
3326                                 (pathname
3327                                  (let ((directory (pathname-directory (car x))))
3328                                    (if (listp directory) (length directory) 0))))))))
3329  new-value)
3330
3331(defun* output-translations-initialized-p ()
3332  (and *output-translations* t))
3333
3334(defun* clear-output-translations ()
3335  "Undoes any initialization of the output translations.
3336You might want to call that before you dump an image that would be resumed
3337with a different configuration, so the configuration would be re-read then."
3338  (setf *output-translations* '())
3339  (values))
3340
3341(declaim (ftype (function (t &key (:directory boolean) (:wilden boolean))
3342                          (values (or null pathname) &optional))
3343                resolve-location))
3344
3345(defun* resolve-relative-location-component (x &key directory wilden)
3346  (let ((r (etypecase x
3347             (pathname x)
3348             (string (coerce-pathname x :type (when directory :directory)))
3349             (cons
3350              (if (null (cdr x))
3351                  (resolve-relative-location-component
3352                   (car x) :directory directory :wilden wilden)
3353                  (let* ((car (resolve-relative-location-component
3354                               (car x) :directory t :wilden nil)))
3355                    (merge-pathnames*
3356                     (resolve-relative-location-component
3357                      (cdr x) :directory directory :wilden wilden)
3358                     car))))
3359             ((eql :default-directory)
3360              (relativize-pathname-directory (default-directory)))
3361             ((eql :*/) *wild-directory*)
3362             ((eql :**/) *wild-inferiors*)
3363             ((eql :*.*.*) *wild-file*)
3364             ((eql :implementation)
3365              (coerce-pathname (implementation-identifier) :type :directory))
3366             ((eql :implementation-type)
3367              (coerce-pathname (string-downcase (implementation-type)) :type :directory)))))
3368    (when (absolute-pathname-p r)
3369      (error (compatfmt "~@<pathname ~S is not relative~@:>") x))
3370    (if (or (pathnamep x) (not wilden)) r (wilden r))))
3371
3372(defvar *here-directory* nil
3373  "This special variable is bound to the currect directory during calls to
3374PROCESS-SOURCE-REGISTRY in order that we be able to interpret the :here
3375directive.")
3376
3377(defun* resolve-absolute-location-component (x &key directory wilden)
3378  (let* ((r
3379          (etypecase x
3380            (pathname x)
3381            (string (let ((p (#+mcl probe-posix #-mcl parse-namestring x)))
3382                      #+mcl (unless p (error "POSIX pathname ~S does not exist" x))
3383                      (if directory (ensure-directory-pathname p) p)))
3384            (cons
3385             (return-from resolve-absolute-location-component
3386               (if (null (cdr x))
3387                   (resolve-absolute-location-component
3388                    (car x) :directory directory :wilden wilden)
3389                   (merge-pathnames*
3390                    (resolve-relative-location-component
3391                     (cdr x) :directory directory :wilden wilden)
3392                    (resolve-absolute-location-component
3393                     (car x) :directory t :wilden nil)))))
3394            ((eql :root)
3395             ;; special magic! we encode such paths as relative pathnames,
3396             ;; but it means "relative to the root of the source pathname's host and device".
3397             (return-from resolve-absolute-location-component
3398               (let ((p (make-pathname :directory '(:relative))))
3399                 (if wilden (wilden p) p))))
3400            ((eql :home) (user-homedir))
3401            ((eql :here)
3402             (resolve-location (or *here-directory*
3403                                   ;; give semantics in the case of use interactively
3404                                   :default-directory)
3405                          :directory t :wilden nil))
3406            ((eql :user-cache) (resolve-location *user-cache* :directory t :wilden nil))
3407            ((eql :system-cache)
3408             (error "Using the :system-cache is deprecated. ~%~
3409Please remove it from your ASDF configuration"))
3410            ((eql :default-directory) (default-directory))))
3411         (s (if (and wilden (not (pathnamep x)))
3412                (wilden r)
3413                r)))
3414    (unless (absolute-pathname-p s)
3415      (error (compatfmt "~@<Invalid designator for an absolute pathname: ~3i~_~S~@:>") x))
3416    s))
3417
3418(defun* resolve-location (x &key directory wilden)
3419  (if (atom x)
3420      (resolve-absolute-location-component x :directory directory :wilden wilden)
3421      (loop :with path = (resolve-absolute-location-component
3422                          (car x) :directory (and (or directory (cdr x)) t)
3423                          :wilden (and wilden (null (cdr x))))
3424        :for (component . morep) :on (cdr x)
3425        :for dir = (and (or morep directory) t)
3426        :for wild = (and wilden (not morep))
3427        :do (setf path (merge-pathnames*
3428                        (resolve-relative-location-component
3429                         component :directory dir :wilden wild)
3430                        path))
3431        :finally (return path))))
3432
3433(defun* location-designator-p (x)
3434  (flet ((absolute-component-p (c)
3435           (typep c '(or string pathname
3436                      (member :root :home :here :user-cache :system-cache :default-directory))))
3437         (relative-component-p (c)
3438           (typep c '(or string pathname
3439                      (member :default-directory :*/ :**/ :*.*.*
3440                        :implementation :implementation-type)))))
3441    (or (typep x 'boolean)
3442        (absolute-component-p x)
3443        (and (consp x) (absolute-component-p (first x)) (every #'relative-component-p (rest x))))))
3444
3445(defun* location-function-p (x)
3446  (and
3447   (consp x)
3448   (length=n-p x 2)
3449   (or (and (equal (first x) :function)
3450            (typep (second x) 'symbol))
3451       (and (equal (first x) 'lambda)
3452            (cddr x)
3453            (length=n-p (second x) 2)))))
3454
3455(defun* validate-output-translations-directive (directive)
3456  (or (member directive '(:enable-user-cache :disable-cache nil))
3457      (and (consp directive)
3458           (or (and (length=n-p directive 2)
3459                    (or (and (eq (first directive) :include)
3460                             (typep (second directive) '(or string pathname null)))
3461                        (and (location-designator-p (first directive))
3462                             (or (location-designator-p (second directive))
3463                                 (location-function-p (second directive))))))
3464               (and (length=n-p directive 1)
3465                    (location-designator-p (first directive)))))))
3466
3467(defun* validate-output-translations-form (form &key location)
3468  (validate-configuration-form
3469   form
3470   :output-translations
3471   'validate-output-translations-directive
3472   :location location :invalid-form-reporter 'invalid-output-translation))
3473
3474(defun* validate-output-translations-file (file)
3475  (validate-configuration-file
3476   file 'validate-output-translations-form :description "output translations"))
3477
3478(defun* validate-output-translations-directory (directory)
3479  (validate-configuration-directory
3480   directory :output-translations 'validate-output-translations-directive
3481   :invalid-form-reporter 'invalid-output-translation))
3482
3483(defun* parse-output-translations-string (string &key location)
3484  (cond
3485    ((or (null string) (equal string ""))
3486     '(:output-translations :inherit-configuration))
3487    ((not (stringp string))
3488     (error (compatfmt "~@<Environment string isn't: ~3i~_~S~@:>") string))
3489    ((eql (char string 0) #\")
3490     (parse-output-translations-string (read-from-string string) :location location))
3491    ((eql (char string 0) #\()
3492     (validate-output-translations-form (read-from-string string) :location location))
3493    (t
3494     (loop
3495      :with inherit = nil
3496      :with directives = ()
3497      :with start = 0
3498      :with end = (length string)
3499      :with source = nil
3500      :with separator = (inter-directory-separator)
3501      :for i = (or (position separator string :start start) end) :do
3502      (let ((s (subseq string start i)))
3503        (cond
3504          (source
3505           (push (list source (if (equal "" s) nil s)) directives)
3506           (setf source nil))
3507          ((equal "" s)
3508           (when inherit
3509             (error (compatfmt "~@<Only one inherited configuration allowed: ~3i~_~S~@:>")
3510                    string))
3511           (setf inherit t)
3512           (push :inherit-configuration directives))
3513          (t
3514           (setf source s)))
3515        (setf start (1+ i))
3516        (when (> start end)
3517          (when source
3518            (error (compatfmt "~@<Uneven number of components in source to destination mapping: ~3i~_~S~@:>")
3519                   string))
3520          (unless inherit
3521            (push :ignore-inherited-configuration directives))
3522          (return `(:output-translations ,@(nreverse directives)))))))))
3523
3524(defparameter *default-output-translations*
3525  '(environment-output-translations
3526    user-output-translations-pathname
3527    user-output-translations-directory-pathname
3528    system-output-translations-pathname
3529    system-output-translations-directory-pathname))
3530
3531(defun* wrapping-output-translations ()
3532  `(:output-translations
3533    ;; Some implementations have precompiled ASDF systems,
3534    ;; so we must disable translations for implementation paths.
3535    #+sbcl ,(let ((h (getenv "SBCL_HOME")))
3536                 (when (plusp (length h)) `((,(truenamize h) ,*wild-inferiors*) ())))
3537    ;; The below two are not needed: no precompiled ASDF system there
3538    ;; #+ecl (,(translate-logical-pathname "SYS:**;*.*") ())
3539    ;; #+clozure ,(ignore-errors (list (wilden (let ((*default-pathname-defaults* #p"")) (truename #p"ccl:"))) ()))
3540    ;; All-import, here is where we want user stuff to be:
3541    :inherit-configuration
3542    ;; These are for convenience, and can be overridden by the user:
3543    #+abcl (#p"/___jar___file___root___/**/*.*" (:user-cache #p"**/*.*"))
3544    #+abcl (#p"jar:file:/**/*.jar!/**/*.*" (:function translate-jar-pathname))
3545    ;; We enable the user cache by default, and here is the place we do:
3546    :enable-user-cache))
3547
3548(defparameter *output-translations-file* (coerce-pathname "asdf-output-translations.conf"))
3549(defparameter *output-translations-directory* (coerce-pathname "asdf-output-translations.conf.d/"))
3550
3551(defun* user-output-translations-pathname (&key (direction :input))
3552  (in-user-configuration-directory *output-translations-file* :direction direction))
3553(defun* system-output-translations-pathname (&key (direction :input))
3554  (in-system-configuration-directory *output-translations-file* :direction direction))
3555(defun* user-output-translations-directory-pathname (&key (direction :input))
3556  (in-user-configuration-directory *output-translations-directory* :direction direction))
3557(defun* system-output-translations-directory-pathname (&key (direction :input))
3558  (in-system-configuration-directory *output-translations-directory* :direction direction))
3559(defun* environment-output-translations ()
3560  (getenv "ASDF_OUTPUT_TRANSLATIONS"))
3561
3562(defgeneric* process-output-translations (spec &key inherit collect))
3563(declaim (ftype (function (t &key (:collect (or symbol function))) t)
3564                inherit-output-translations))
3565(declaim (ftype (function (t &key (:collect (or symbol function)) (:inherit list)) t)
3566                process-output-translations-directive))
3567
3568(defmethod process-output-translations ((x symbol) &key
3569                                        (inherit *default-output-translations*)
3570                                        collect)
3571  (process-output-translations (funcall x) :inherit inherit :collect collect))
3572(defmethod process-output-translations ((pathname pathname) &key inherit collect)
3573  (cond
3574    ((directory-pathname-p pathname)
3575     (process-output-translations (validate-output-translations-directory pathname)
3576                                  :inherit inherit :collect collect))
3577    ((probe-file* pathname)
3578     (process-output-translations (validate-output-translations-file pathname)
3579                                  :inherit inherit :collect collect))
3580    (t
3581     (inherit-output-translations inherit :collect collect))))
3582(defmethod process-output-translations ((string string) &key inherit collect)
3583  (process-output-translations (parse-output-translations-string string)
3584                               :inherit inherit :collect collect))
3585(defmethod process-output-translations ((x null) &key inherit collect)
3586  (declare (ignorable x))
3587  (inherit-output-translations inherit :collect collect))
3588(defmethod process-output-translations ((form cons) &key inherit collect)
3589  (dolist (directive (cdr (validate-output-translations-form form)))
3590    (process-output-translations-directive directive :inherit inherit :collect collect)))
3591
3592(defun* inherit-output-translations (inherit &key collect)
3593  (when inherit
3594    (process-output-translations (first inherit) :collect collect :inherit (rest inherit))))
3595
3596(defun* process-output-translations-directive (directive &key inherit collect)
3597  (if (atom directive)
3598      (ecase directive
3599        ((:enable-user-cache)
3600         (process-output-translations-directive '(t :user-cache) :collect collect))
3601        ((:disable-cache)
3602         (process-output-translations-directive '(t t) :collect collect))
3603        ((:inherit-configuration)
3604         (inherit-output-translations inherit :collect collect))
3605        ((:ignore-inherited-configuration :ignore-invalid-entries nil)
3606         nil))
3607      (let ((src (first directive))
3608            (dst (second directive)))
3609        (if (eq src :include)
3610            (when dst
3611              (process-output-translations (pathname dst) :inherit nil :collect collect))
3612            (when src
3613              (let ((trusrc (or (eql src t)
3614                                (let ((loc (resolve-location src :directory t :wilden t)))
3615                                  (if (absolute-pathname-p loc) (truenamize loc) loc)))))
3616                (cond
3617                  ((location-function-p dst)
3618                   (funcall collect
3619                            (list trusrc
3620                                  (if (symbolp (second dst))
3621                                      (fdefinition (second dst))
3622                                      (eval (second dst))))))
3623                  ((eq dst t)
3624                   (funcall collect (list trusrc t)))
3625                  (t
3626                   (let* ((trudst (if dst
3627                                      (resolve-location dst :directory t :wilden t)
3628                                      trusrc))
3629                          (wilddst (merge-pathnames* *wild-file* trudst)))
3630                     (funcall collect (list wilddst t))
3631                     (funcall collect (list trusrc trudst)))))))))))
3632
3633(defun* compute-output-translations (&optional parameter)
3634  "read the configuration, return it"
3635  (remove-duplicates
3636   (while-collecting (c)
3637     (inherit-output-translations
3638      `(wrapping-output-translations ,parameter ,@*default-output-translations*) :collect #'c))
3639   :test 'equal :from-end t))
3640
3641(defvar *output-translations-parameter* nil)
3642
3643(defun* initialize-output-translations (&optional (parameter *output-translations-parameter*))
3644  "read the configuration, initialize the internal configuration variable,
3645return the configuration"
3646  (setf *output-translations-parameter* parameter
3647        (output-translations) (compute-output-translations parameter)))
3648
3649(defun* disable-output-translations ()
3650  "Initialize output translations in a way that maps every file to itself,
3651effectively disabling the output translation facility."
3652  (initialize-output-translations
3653   '(:output-translations :disable-cache :ignore-inherited-configuration)))
3654
3655;; checks an initial variable to see whether the state is initialized
3656;; or cleared. In the former case, return current configuration; in
3657;; the latter, initialize.  ASDF will call this function at the start
3658;; of (asdf:find-system).
3659(defun* ensure-output-translations ()
3660  (if (output-translations-initialized-p)
3661      (output-translations)
3662      (initialize-output-translations)))
3663
3664(defun* translate-pathname* (path absolute-source destination &optional root source)
3665  (declare (ignore source))
3666  (cond
3667    ((functionp destination)
3668     (funcall destination path absolute-source))
3669    ((eq destination t)
3670     path)
3671    ((not (pathnamep destination))
3672     (error "Invalid destination"))
3673    ((not (absolute-pathname-p destination))
3674     (translate-pathname path absolute-source (merge-pathnames* destination root)))
3675    (root
3676     (translate-pathname (directorize-pathname-host-device path) absolute-source destination))
3677    (t
3678     (translate-pathname path absolute-source destination))))
3679
3680(defun* apply-output-translations (path)
3681  #+cormanlisp (truenamize path) #-cormanlisp
3682  (etypecase path
3683    (logical-pathname
3684     path)
3685    ((or pathname string)
3686     (ensure-output-translations)
3687     (loop :with p = (truenamize path)
3688       :for (source destination) :in (car *output-translations*)
3689       :for root = (when (or (eq source t)
3690                             (and (pathnamep source)
3691                                  (not (absolute-pathname-p source))))
3692                     (pathname-root p))
3693       :for absolute-source = (cond
3694                                ((eq source t) (wilden root))
3695                                (root (merge-pathnames* source root))
3696                                (t source))
3697       :when (or (eq source t) (pathname-match-p p absolute-source))
3698       :return (translate-pathname* p absolute-source destination root source)
3699       :finally (return p)))))
3700
3701(defmethod output-files :around (operation component)
3702  "Translate output files, unless asked not to"
3703  (declare (ignorable operation component))
3704  (values
3705   (multiple-value-bind (files fixedp) (call-next-method)
3706     (if fixedp
3707         files
3708         (mapcar #'apply-output-translations files)))
3709   t))
3710
3711(defun* compile-file-pathname* (input-file &rest keys &key output-file &allow-other-keys)
3712  (if (absolute-pathname-p output-file)
3713      ;; what cfp should be doing, w/ mp* instead of mp
3714      (let* ((type (pathname-type (apply 'compile-file-pathname "x.lisp" keys)))
3715             (defaults (make-pathname
3716                        :type type :defaults (merge-pathnames* input-file))))
3717        (merge-pathnames* output-file defaults))
3718      (apply-output-translations
3719       (apply 'compile-file-pathname input-file keys))))
3720
3721(defun* tmpize-pathname (x)
3722  (make-pathname
3723   :name (strcat "ASDF-TMP-" (pathname-name x))
3724   :defaults x))
3725
3726(defun* delete-file-if-exists (x)
3727  (when (and x (probe-file* x))
3728    (delete-file x)))
3729
3730(defun* compile-file* (input-file &rest keys &key output-file &allow-other-keys)
3731  (let* ((output-file (apply 'compile-file-pathname* input-file :output-file output-file keys))
3732         (tmp-file (tmpize-pathname output-file))
3733         (status :error))
3734    (multiple-value-bind (output-truename warnings-p failure-p)
3735        (apply 'compile-file input-file :output-file tmp-file keys)
3736      (cond
3737        (failure-p
3738         (setf status *compile-file-failure-behaviour*))
3739        (warnings-p
3740         (setf status *compile-file-warnings-behaviour*))
3741        (t
3742         (setf status :success)))
3743      (ecase status
3744        ((:success :warn :ignore)
3745         (delete-file-if-exists output-file)
3746         (when output-truename
3747           (rename-file output-truename output-file)
3748           (setf output-truename output-file)))
3749        (:error
3750         (delete-file-if-exists output-truename)
3751         (setf output-truename nil)))
3752      (values output-truename warnings-p failure-p))))
3753
3754#+abcl
3755(defun* translate-jar-pathname (source wildcard)
3756  (declare (ignore wildcard))
3757  (let* ((p (pathname (first (pathname-device source))))
3758         (root (format nil "/___jar___file___root___/~@[~A/~]"
3759                       (and (find :windows *features*)
3760                            (pathname-device p)))))
3761    (apply-output-translations
3762     (merge-pathnames*
3763      (relativize-pathname-directory source)
3764      (merge-pathnames*
3765       (relativize-pathname-directory (ensure-directory-pathname p))
3766       root)))))
3767
3768;;;; -----------------------------------------------------------------
3769;;;; Compatibility mode for ASDF-Binary-Locations
3770
3771(defmethod operate :before (operation-class system &rest args &key &allow-other-keys)
3772  (declare (ignorable operation-class system args))
3773  (when (find-symbol* '#:output-files-for-system-and-operation :asdf)
3774    (error "ASDF 2 is not compatible with ASDF-BINARY-LOCATIONS, which you are using.
3775ASDF 2 now achieves the same purpose with its builtin ASDF-OUTPUT-TRANSLATIONS,
3776which should be easier to configure. Please stop using ASDF-BINARY-LOCATIONS,
3777and instead use ASDF-OUTPUT-TRANSLATIONS. See the ASDF manual for details.
3778In case you insist on preserving your previous A-B-L configuration, but
3779do not know how to achieve the same effect with A-O-T, you may use function
3780ASDF:ENABLE-ASDF-BINARY-LOCATIONS-COMPATIBILITY as documented in the manual;
3781call that function where you would otherwise have loaded and configured A-B-L.")))
3782
3783(defun* enable-asdf-binary-locations-compatibility
3784    (&key
3785     (centralize-lisp-binaries nil)
3786     (default-toplevel-directory
3787         ;; Use ".cache/common-lisp" instead ???
3788         (merge-pathnames* (make-pathname :directory '(:relative ".fasls"))
3789                           (user-homedir)))
3790     (include-per-user-information nil)
3791     (map-all-source-files (or #+(or ecl clisp) t nil))
3792     (source-to-target-mappings nil))
3793  #+(or ecl clisp)
3794  (when (null map-all-source-files)
3795    (error "asdf:enable-asdf-binary-locations-compatibility doesn't support :map-all-source-files nil on ECL and CLISP"))
3796  (let* ((fasl-type (pathname-type (compile-file-pathname "foo.lisp")))
3797         (mapped-files (if map-all-source-files *wild-file*
3798                           (make-pathname :type fasl-type :defaults *wild-file*)))
3799         (destination-directory
3800          (if centralize-lisp-binaries
3801              `(,default-toplevel-directory
3802                ,@(when include-per-user-information
3803                        (cdr (pathname-directory (user-homedir))))
3804                :implementation ,*wild-inferiors*)
3805              `(:root ,*wild-inferiors* :implementation))))
3806    (initialize-output-translations
3807     `(:output-translations
3808       ,@source-to-target-mappings
3809       ((:root ,*wild-inferiors* ,mapped-files)
3810        (,@destination-directory ,mapped-files))
3811       (t t)
3812       :ignore-inherited-configuration))))
3813
3814;;;; -----------------------------------------------------------------
3815;;;; Source Registry Configuration, by Francois-Rene Rideau
3816;;;; See the Manual and https://bugs.launchpad.net/asdf/+bug/485918
3817
3818;; Using ack 1.2 exclusions
3819(defvar *default-source-registry-exclusions*
3820  '(".bzr" ".cdv"
3821    ;; "~.dep" "~.dot" "~.nib" "~.plst" ; we don't support ack wildcards
3822    ".git" ".hg" ".pc" ".svn" "CVS" "RCS" "SCCS" "_darcs"
3823    "_sgbak" "autom4te.cache" "cover_db" "_build"
3824    "debian")) ;; debian often builds stuff under the debian directory... BAD.
3825
3826(defvar *source-registry-exclusions* *default-source-registry-exclusions*)
3827
3828(defvar *source-registry* nil
3829  "Either NIL (for uninitialized), or an equal hash-table, mapping
3830system names to pathnames of .asd files")
3831
3832(defun* source-registry-initialized-p ()
3833  (typep *source-registry* 'hash-table))
3834
3835(defun* clear-source-registry ()
3836  "Undoes any initialization of the source registry.
3837You might want to call that before you dump an image that would be resumed
3838with a different configuration, so the configuration would be re-read then."
3839  (setf *source-registry* nil)
3840  (values))
3841
3842(defparameter *wild-asd*
3843  (make-pathname :directory nil :name *wild* :type "asd" :version :newest))
3844
3845(defun* filter-logical-directory-results (directory entries merger)
3846  (if (typep directory 'logical-pathname)
3847      ;; Try hard to not resolve logical-pathname into physical pathnames;
3848      ;; otherwise logical-pathname users/lovers will be disappointed.
3849      ;; If directory* could use some implementation-dependent magic,
3850      ;; we will have logical pathnames already; otherwise,
3851      ;; we only keep pathnames for which specifying the name and
3852      ;; translating the LPN commute.
3853      (loop :for f :in entries
3854        :for p = (or (and (typep f 'logical-pathname) f)
3855                     (let* ((u (ignore-errors (funcall merger f))))
3856                       ;; The first u avoids a cumbersome (truename u) error
3857                       (and u (equal (ignore-errors (truename u)) f) u)))
3858        :when p :collect p)
3859      entries))
3860
3861(defun* directory-files (directory &optional (pattern *wild-file*))
3862  (when (wild-pathname-p directory)
3863    (error "Invalid wild in ~S" directory))
3864  (unless (member (pathname-directory pattern) '(() (:relative)) :test 'equal)
3865    (error "Invalid file pattern ~S" pattern))
3866  (let ((entries (ignore-errors (directory* (merge-pathnames* pattern directory)))))
3867    (filter-logical-directory-results
3868     directory entries
3869     #'(lambda (f)
3870         (make-pathname :defaults directory
3871                        :name (pathname-name f) :type (ununspecific (pathname-type f))
3872                        :version (ununspecific (pathname-version f)))))))
3873
3874(defun* directory-asd-files (directory)
3875  (directory-files directory *wild-asd*))
3876
3877(defun* subdirectories (directory)
3878  (let* ((directory (ensure-directory-pathname directory))
3879         #-(or abcl cormanlisp genera xcl)
3880         (wild (merge-pathnames*
3881                #-(or abcl allegro cmu lispworks sbcl scl xcl)
3882                *wild-directory*
3883                #+(or abcl allegro cmu lispworks sbcl scl xcl) "*.*"
3884                directory))
3885         (dirs
3886          #-(or abcl cormanlisp genera xcl)
3887          (ignore-errors
3888            (directory* wild . #.(or #+clozure '(:directories t :files nil)
3889                                     #+mcl '(:directories t))))
3890          #+(or abcl xcl) (system:list-directory directory)
3891          #+cormanlisp (cl::directory-subdirs directory)
3892          #+genera (fs:directory-list directory))
3893         #+(or abcl allegro cmu genera lispworks sbcl scl xcl)
3894         (dirs (loop :for x :in dirs
3895                 :for d = #+(or abcl xcl) (extensions:probe-directory x)
3896                          #+allegro (excl:probe-directory x)
3897                          #+(or cmu sbcl scl) (directory-pathname-p x)
3898                          #+genera (getf (cdr x) :directory)
3899                          #+lispworks (lw:file-directory-p x)
3900                 :when d :collect #+(or abcl allegro xcl) d
3901                                  #+genera (ensure-directory-pathname (first x))
3902                                  #+(or cmu lispworks sbcl scl) x)))
3903    (filter-logical-directory-results
3904     directory dirs
3905     (let ((prefix (normalize-pathname-directory-component
3906                    (pathname-directory directory))))
3907       #'(lambda (d)
3908           (let ((dir (normalize-pathname-directory-component
3909                       (pathname-directory d))))
3910             (and (consp dir) (consp (cdr dir))
3911                  (make-pathname
3912                   :defaults directory :name nil :type nil :version nil
3913                   :directory (append prefix (last dir))))))))))
3914
3915(defun* collect-asds-in-directory (directory collect)
3916  (map () collect (directory-asd-files directory)))
3917
3918(defun* collect-sub*directories (directory collectp recursep collector)
3919  (when (funcall collectp directory)
3920    (funcall collector directory))
3921  (dolist (subdir (subdirectories directory))
3922    (when (funcall recursep subdir)
3923      (collect-sub*directories subdir collectp recursep collector))))
3924
3925(defun* collect-sub*directories-asd-files
3926    (directory &key
3927     (exclude *default-source-registry-exclusions*)
3928     collect)
3929  (collect-sub*directories
3930   directory
3931   (constantly t)
3932   #'(lambda (x) (not (member (car (last (pathname-directory x))) exclude :test #'equal)))
3933   #'(lambda (dir) (collect-asds-in-directory dir collect))))
3934
3935(defun* validate-source-registry-directive (directive)
3936  (or (member directive '(:default-registry))
3937      (and (consp directive)
3938           (let ((rest (rest directive)))
3939             (case (first directive)
3940               ((:include :directory :tree)
3941                (and (length=n-p rest 1)
3942                     (location-designator-p (first rest))))
3943               ((:exclude :also-exclude)
3944                (every #'stringp rest))
3945               ((:default-registry)
3946                (null rest)))))))
3947
3948(defun* validate-source-registry-form (form &key location)
3949  (validate-configuration-form
3950   form :source-registry 'validate-source-registry-directive
3951   :location location :invalid-form-reporter 'invalid-source-registry))
3952
3953(defun* validate-source-registry-file (file)
3954  (validate-configuration-file
3955   file 'validate-source-registry-form :description "a source registry"))
3956
3957(defun* validate-source-registry-directory (directory)
3958  (validate-configuration-directory
3959   directory :source-registry 'validate-source-registry-directive
3960   :invalid-form-reporter 'invalid-source-registry))
3961
3962(defun* parse-source-registry-string (string &key location)
3963  (cond
3964    ((or (null string) (equal string ""))
3965     '(:source-registry :inherit-configuration))
3966    ((not (stringp string))
3967     (error (compatfmt "~@<Environment string isn't: ~3i~_~S~@:>") string))
3968    ((find (char string 0) "\"(")
3969     (validate-source-registry-form (read-from-string string) :location location))
3970    (t
3971     (loop
3972      :with inherit = nil
3973      :with directives = ()
3974      :with start = 0
3975      :with end = (length string)
3976      :with separator = (inter-directory-separator)
3977      :for pos = (position separator string :start start) :do
3978      (let ((s (subseq string start (or pos end))))
3979        (flet ((check (dir)
3980                 (unless (absolute-pathname-p dir)
3981                   (error (compatfmt "~@<source-registry string must specify absolute pathnames: ~3i~_~S~@:>") string))
3982                 dir))
3983          (cond
3984            ((equal "" s) ; empty element: inherit
3985             (when inherit
3986               (error (compatfmt "~@<Only one inherited configuration allowed: ~3i~_~S~@:>")
3987                      string))
3988             (setf inherit t)
3989             (push ':inherit-configuration directives))
3990            ((ends-with s "//") ;; TODO: allow for doubling of separator even outside Unix?
3991             (push `(:tree ,(check (subseq s 0 (- (length s) 2)))) directives))
3992            (t
3993             (push `(:directory ,(check s)) directives))))
3994        (cond
3995          (pos
3996           (setf start (1+ pos)))
3997          (t
3998           (unless inherit
3999             (push '(:ignore-inherited-configuration) directives))
4000           (return `(:source-registry ,@(nreverse directives))))))))))
4001
4002(defun* register-asd-directory (directory &key recurse exclude collect)
4003  (if (not recurse)
4004      (collect-asds-in-directory directory collect)
4005      (collect-sub*directories-asd-files
4006       directory :exclude exclude :collect collect)))
4007
4008(defparameter *default-source-registries*
4009  '(environment-source-registry
4010    user-source-registry
4011    user-source-registry-directory
4012    system-source-registry
4013    system-source-registry-directory
4014    default-source-registry))
4015
4016(defparameter *source-registry-file* (coerce-pathname "source-registry.conf"))
4017(defparameter *source-registry-directory* (coerce-pathname "source-registry.conf.d/"))
4018
4019(defun* wrapping-source-registry ()
4020  `(:source-registry
4021    #+sbcl (:tree ,(truenamize (getenv "SBCL_HOME")))
4022    :inherit-configuration
4023    #+cmu (:tree #p"modules:")))
4024(defun* default-source-registry ()
4025  `(:source-registry
4026    #+sbcl (:directory ,(subpathname (user-homedir) ".sbcl/systems/"))
4027    (:directory ,(default-directory))
4028      ,@(loop :for dir :in
4029          `(,@(when (os-unix-p)
4030                `(,(or (getenv "XDG_DATA_HOME")
4031                       (subpathname (user-homedir) ".local/share/"))
4032                  ,@(split-string (or (getenv "XDG_DATA_DIRS")
4033                                      "/usr/local/share:/usr/share")
4034                                  :separator ":")))
4035            ,@(when (os-windows-p)
4036                `(,(or #+lispworks (sys:get-folder-path :local-appdata)
4037                       (getenv "LOCALAPPDATA"))
4038                  ,(or #+lispworks (sys:get-folder-path :appdata)
4039                       (getenv "APPDATA"))
4040                  ,(or #+lispworks (sys:get-folder-path :common-appdata)
4041                       (getenv "ALLUSERSAPPDATA")
4042                       (subpathname* (getenv "ALLUSERSPROFILE") "Application Data/")))))
4043          :collect `(:directory ,(subpathname* dir "common-lisp/systems/"))
4044          :collect `(:tree ,(subpathname* dir "common-lisp/source/")))
4045      :inherit-configuration))
4046(defun* user-source-registry (&key (direction :input))
4047  (in-user-configuration-directory *source-registry-file* :direction direction))
4048(defun* system-source-registry (&key (direction :input))
4049  (in-system-configuration-directory *source-registry-file* :direction direction))
4050(defun* user-source-registry-directory (&key (direction :input))
4051  (in-user-configuration-directory *source-registry-directory* :direction direction))
4052(defun* system-source-registry-directory (&key (direction :input))
4053  (in-system-configuration-directory *source-registry-directory* :direction direction))
4054(defun* environment-source-registry ()
4055  (getenv "CL_SOURCE_REGISTRY"))
4056
4057(defgeneric* process-source-registry (spec &key inherit register))
4058(declaim (ftype (function (t &key (:register (or symbol function))) t)
4059                inherit-source-registry))
4060(declaim (ftype (function (t &key (:register (or symbol function)) (:inherit list)) t)
4061                process-source-registry-directive))
4062
4063(defmethod process-source-registry ((x symbol) &key inherit register)
4064  (process-source-registry (funcall x) :inherit inherit :register register))
4065(defmethod process-source-registry ((pathname pathname) &key inherit register)
4066  (cond
4067    ((directory-pathname-p pathname)
4068     (let ((*here-directory* (truenamize pathname)))
4069       (process-source-registry (validate-source-registry-directory pathname)
4070                                :inherit inherit :register register)))
4071    ((probe-file* pathname)
4072     (let ((*here-directory* (pathname-directory-pathname pathname)))
4073       (process-source-registry (validate-source-registry-file pathname)
4074                                :inherit inherit :register register)))
4075    (t
4076     (inherit-source-registry inherit :register register))))
4077(defmethod process-source-registry ((string string) &key inherit register)
4078  (process-source-registry (parse-source-registry-string string)
4079                           :inherit inherit :register register))
4080(defmethod process-source-registry ((x null) &key inherit register)
4081  (declare (ignorable x))
4082  (inherit-source-registry inherit :register register))
4083(defmethod process-source-registry ((form cons) &key inherit register)
4084  (let ((*source-registry-exclusions* *default-source-registry-exclusions*))
4085    (dolist (directive (cdr (validate-source-registry-form form)))
4086      (process-source-registry-directive directive :inherit inherit :register register))))
4087
4088(defun* inherit-source-registry (inherit &key register)
4089  (when inherit
4090    (process-source-registry (first inherit) :register register :inherit (rest inherit))))
4091
4092(defun* process-source-registry-directive (directive &key inherit register)
4093  (destructuring-bind (kw &rest rest) (if (consp directive) directive (list directive))
4094    (ecase kw
4095      ((:include)
4096       (destructuring-bind (pathname) rest
4097         (process-source-registry (resolve-location pathname) :inherit nil :register register)))
4098      ((:directory)
4099       (destructuring-bind (pathname) rest
4100         (when pathname
4101           (funcall register (resolve-location pathname :directory t)))))
4102      ((:tree)
4103       (destructuring-bind (pathname) rest
4104         (when pathname
4105           (funcall register (resolve-location pathname :directory t)
4106                    :recurse t :exclude *source-registry-exclusions*))))
4107      ((:exclude)
4108       (setf *source-registry-exclusions* rest))
4109      ((:also-exclude)
4110       (appendf *source-registry-exclusions* rest))
4111      ((:default-registry)
4112       (inherit-source-registry '(default-source-registry) :register register))
4113      ((:inherit-configuration)
4114       (inherit-source-registry inherit :register register))
4115      ((:ignore-inherited-configuration)
4116       nil)))
4117  nil)
4118
4119(defun* flatten-source-registry (&optional parameter)
4120  (remove-duplicates
4121   (while-collecting (collect)
4122     (let ((*default-pathname-defaults* (default-directory)))
4123       (inherit-source-registry
4124        `(wrapping-source-registry
4125          ,parameter
4126          ,@*default-source-registries*)
4127        :register #'(lambda (directory &key recurse exclude)
4128                      (collect (list directory :recurse recurse :exclude exclude)))))
4129     :test 'equal :from-end t)))
4130
4131;; Will read the configuration and initialize all internal variables.
4132(defun* compute-source-registry (&optional parameter (registry *source-registry*))
4133  (dolist (entry (flatten-source-registry parameter))
4134    (destructuring-bind (directory &key recurse exclude) entry
4135      (let* ((h (make-hash-table :test 'equal))) ; table to detect duplicates
4136        (register-asd-directory
4137         directory :recurse recurse :exclude exclude :collect
4138         #'(lambda (asd)
4139             (let* ((name (pathname-name asd))
4140                    (name (if (typep asd 'logical-pathname)
4141                              ;; logical pathnames are upper-case,
4142                              ;; at least in the CLHS and on SBCL,
4143                              ;; yet (coerce-name :foo) is lower-case.
4144                              ;; won't work well with (load-system "Foo")
4145                              ;; instead of (load-system 'foo)
4146                              (string-downcase name)
4147                              name)))
4148               (cond
4149                 ((gethash name registry) ; already shadowed by something else
4150                  nil)
4151                 ((gethash name h) ; conflict at current level
4152                  (when *asdf-verbose*
4153                    (warn (compatfmt "~@<In source-registry entry ~A~@[/~*~] ~
4154                                found several entries for ~A - picking ~S over ~S~:>")
4155                          directory recurse name (gethash name h) asd)))
4156                 (t
4157                  (setf (gethash name registry) asd)
4158                  (setf (gethash name h) asd))))))
4159        h)))
4160  (values))
4161
4162(defvar *source-registry-parameter* nil)
4163
4164(defun* initialize-source-registry (&optional (parameter *source-registry-parameter*))
4165  (setf *source-registry-parameter* parameter)
4166  (setf *source-registry* (make-hash-table :test 'equal))
4167  (compute-source-registry parameter))
4168
4169;; Checks an initial variable to see whether the state is initialized
4170;; or cleared. In the former case, return current configuration; in
4171;; the latter, initialize.  ASDF will call this function at the start
4172;; of (asdf:find-system) to make sure the source registry is initialized.
4173;; However, it will do so *without* a parameter, at which point it
4174;; will be too late to provide a parameter to this function, though
4175;; you may override the configuration explicitly by calling
4176;; initialize-source-registry directly with your parameter.
4177(defun* ensure-source-registry (&optional parameter)
4178  (unless (source-registry-initialized-p)
4179    (initialize-source-registry parameter))
4180  (values))
4181
4182(defun* sysdef-source-registry-search (system)
4183  (ensure-source-registry)
4184  (values (gethash (coerce-name system) *source-registry*)))
4185
4186(defun* clear-configuration ()
4187  (clear-source-registry)
4188  (clear-output-translations))
4189
4190
4191;;; ECL support for COMPILE-OP / LOAD-OP
4192;;;
4193;;; In ECL, these operations produce both FASL files and the
4194;;; object files that they are built from. Having both of them allows
4195;;; us to later on reuse the object files for bundles, libraries,
4196;;; standalone executables, etc.
4197;;;
4198;;; This has to be in asdf.lisp and not asdf-ecl.lisp, or else it becomes
4199;;; a problem for asdf on ECL to compile asdf-ecl.lisp after loading asdf.lisp.
4200;;;
4201#+ecl
4202(progn
4203  (setf *compile-op-compile-file-function* 'ecl-compile-file)
4204
4205  (defun use-ecl-byte-compiler-p ()
4206    (member :ecl-bytecmp *features*))
4207
4208  (defun ecl-compile-file (input-file &rest keys &key &allow-other-keys)
4209    (if (use-ecl-byte-compiler-p)
4210        (apply 'compile-file* input-file keys)
4211        (multiple-value-bind (object-file flags1 flags2)
4212            (apply 'compile-file* input-file :system-p t keys)
4213          (values (and object-file
4214                       (c::build-fasl (compile-file-pathname object-file :type :fasl)
4215                                      :lisp-files (list object-file))
4216                       object-file)
4217                  flags1
4218                  flags2))))
4219
4220  (defmethod output-files ((operation compile-op) (c cl-source-file))
4221    (declare (ignorable operation))
4222    (let* ((p (lispize-pathname (component-pathname c)))
4223           (f (compile-file-pathname p :type :fasl)))
4224      (if (use-ecl-byte-compiler-p)
4225          (list f)
4226          (list (compile-file-pathname p :type :object) f))))
4227
4228  (defmethod perform ((o load-op) (c cl-source-file))
4229    (map () #'load
4230         (loop :for i :in (input-files o c)
4231           :unless (string= (pathname-type i) "fas")
4232               :collect (compile-file-pathname (lispize-pathname i))))))
4233
4234;;;; -----------------------------------------------------------------
4235;;;; Hook into REQUIRE for ABCL, CLISP, ClozureCL, CMUCL, ECL and SBCL
4236;;;;
4237(defvar *require-asdf-operator* 'load-op)
4238
4239(defun* module-provide-asdf (name)
4240  (handler-bind
4241      ((style-warning #'muffle-warning)
4242       (missing-component (constantly nil))
4243       (error #'(lambda (e)
4244                  (format *error-output* (compatfmt "~@<ASDF could not load ~(~A~) because ~A.~@:>~%")
4245                          name e))))
4246    (let ((*verbose-out* (make-broadcast-stream))
4247          (system (find-system (string-downcase name) nil)))
4248      (when system
4249        (operate *require-asdf-operator* system :verbose nil)
4250        t))))
4251
4252#+(or abcl clisp clozure cmu ecl sbcl)
4253(let ((x (and #+clisp (find-symbol* '#:*module-provider-functions* :custom))))
4254  (when x
4255    (eval `(pushnew 'module-provide-asdf
4256            #+abcl sys::*module-provider-functions*
4257            #+clisp ,x
4258            #+clozure ccl:*module-provider-functions*
4259            #+(or cmu ecl) ext:*module-provider-functions*
4260            #+sbcl sb-ext:*module-provider-functions*))))
4261
4262
4263;;;; -------------------------------------------------------------------------
4264;;;; Cleanups after hot-upgrade.
4265;;;; Things to do in case we're upgrading from a previous version of ASDF.
4266;;;; See https://bugs.launchpad.net/asdf/+bug/485687
4267;;;;
4268
4269;;; If a previous version of ASDF failed to read some configuration, try again.
4270(when *ignored-configuration-form*
4271  (clear-configuration)
4272  (setf *ignored-configuration-form* nil))
4273
4274;;;; -----------------------------------------------------------------
4275;;;; Done!
4276(when *load-verbose*
4277  (asdf-message ";; ASDF, version ~a~%" (asdf-version)))
4278
4279#+allegro
4280(eval-when (:compile-toplevel :execute)
4281  (when (boundp 'excl:*warn-on-nested-reader-conditionals*)
4282    (setf excl:*warn-on-nested-reader-conditionals* *acl-warn-save*)))
4283
4284(pushnew :asdf *features*)
4285(pushnew :asdf2 *features*)
4286
4287(provide :asdf)
4288
4289;;; Local Variables:
4290;;; mode: lisp
4291;;; End:
Note: See TracBrowser for help on using the repository browser.