Newer
Older
;;; -*- mode: common-lisp; package: asdf; -*-

Daniel Barlow
committed
;;;
Francois-Rene Rideau
committed
;;; Feedback, bug reports, and patches are all welcome:
;;; please mail to <asdf-devel@common-lisp.net>.
;;; Note first that the canonical source for ASDF is presently
Francois-Rene Rideau
committed
;;; <URL:http://common-lisp.net/project/asdf/>.

Daniel Barlow
committed
;;;
;;; If you obtained this copy from anywhere else, and you experience
;;; trouble using it, or find bugs, you may want to check at the
;;; location above for a more recent version (and for documentation
;;; and test files, if your copy came without them) before reporting
;;; bugs. There are usually two "supported" revisions - the git HEAD

Daniel Barlow
committed
;;; is the latest development version, whereas the revision tagged
;;; RELEASE may be slightly older but is considered `stable'
;;; (This is the MIT / X Consortium license as taken from
;;; http://www.opensource.org/licenses/mit-license.html on or about
;;; Monday; July 13, 2009)
;;;
;;; Copyright (c) 2001-2010 Daniel Barlow and contributors

Daniel Barlow
committed
;;;
;;; Permission is hereby granted, free of charge, to any person obtaining
;;; a copy of this software and associated documentation files (the
;;; "Software"), to deal in the Software without restriction, including
;;; without limitation the rights to use, copy, modify, merge, publish,
;;; distribute, sublicense, and/or sell copies of the Software, and to
;;; permit persons to whom the Software is furnished to do so, subject to
;;; the following conditions:
;;;
;;; The above copyright notice and this permission notice shall be
;;; included in all copies or substantial portions of the Software.
;;;
;;; THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
;;; EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
;;; MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
;;; NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
;;; LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION
;;; OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION
;;; WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.

Daniel Barlow
committed
;;; The problem with writing a defsystem replacement is bootstrapping:
;;; we can't use defsystem to compile it. Hence, all in one file.
(cl:in-package :cl-user)
#|(declaim (optimize (speed 2) (debug 2) (safety 3))
#+sbcl (sb-ext:muffle-conditions sb-ext:compiler-note))|#
;;;; Create packages in a way that is compatible with hot-upgrade.
;;;; See https://bugs.launchpad.net/asdf/+bug/485687
;;;; See more at the end of the file.
#+gcl
(eval-when (:compile-toplevel :load-toplevel)
(defpackage :asdf-utilities (:use :cl))
(defpackage :asdf (:use :cl :asdf-utilities)))
(eval-when (:load-toplevel :compile-toplevel :execute)
#+allegro
(setf excl::*autoload-package-name-alist*
(remove "asdf" excl::*autoload-package-name-alist*
:test 'equalp :key 'car))
(let* ((asdf-version
;; the 1+ helps the version bumping script discriminate
(subseq "VERSION:2.002" (1+ (length "VERSION"))))
(existing-asdf (find-package :asdf))
(vername '#:*asdf-version*)
(versym (and existing-asdf
(find-symbol (string vername) existing-asdf)))
(existing-version (and versym (boundp versym) (symbol-value versym)))
(already-there (equal asdf-version existing-version)))
(unless (and existing-asdf already-there)
(when existing-asdf
Francois-Rene Rideau
committed
(format *trace-output*
"~&Upgrading ASDF package ~@[from version ~A ~]to version ~A~%"
existing-version asdf-version))
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
(labels
((rename-away (package)
(loop :with name = (package-name package)
:for i :from 1 :for new = (format nil "~A.~D" name i)
:unless (find-package new) :do
(rename-package-name package name new)))
(rename-package-name (package old new)
(let* ((old-names (cons (package-name package)
(package-nicknames package)))
(new-names (subst new old old-names :test 'equal))
(new-name (car new-names))
(new-nicknames (cdr new-names)))
(rename-package package new-name new-nicknames)))
(ensure-exists (name nicknames use)
(let* ((previous
(remove-duplicates
(remove-if
#'null
(mapcar #'find-package (cons name nicknames)))
:from-end t)))
(cond
(previous
;; do away with packages with conflicting (nick)names
(map () #'rename-away (cdr previous))
;; reuse previous package with same name
(let ((p (car previous)))
(rename-package p name nicknames)
(ensure-use p use)
p))
(t
(make-package name :nicknames nicknames :use use)))))
(find-sym (symbol package)
(find-symbol (string symbol) package))
(intern* (symbol package)
(intern (string symbol) package))
(remove-symbol (symbol package)
(let ((sym (find-sym symbol package)))
(when sym
(unexport sym package)
(unintern sym package))))
(ensure-unintern (package symbols)
(dolist (sym symbols) (remove-symbol sym package)))
(ensure-shadow (package symbols)
(shadow symbols package))
(ensure-use (package use)
(dolist (used (reverse use))
(do-external-symbols (sym used)
(unless (eq sym (find-sym sym package))
(remove-symbol sym package)))
(use-package used package)))
(ensure-fmakunbound (package symbols)
(loop :for name :in symbols
:for sym = (find-sym name package)
:when sym :do (fmakunbound sym)))
(ensure-export (package export)
(let ((syms (loop :for x :in export :collect
(intern* x package))))
(do-external-symbols (sym package)
(unless (member sym syms)
(remove-symbol sym package)))
(dolist (sym syms)
(export sym package))))
(ensure-package (name &key nicknames use unintern fmakunbound shadow export)
(let ((p (ensure-exists name nicknames use)))
(ensure-unintern p unintern)
(ensure-shadow p shadow)
(ensure-export p export)
(ensure-fmakunbound p fmakunbound)
p)))
(macrolet
((pkgdcl (name &key nicknames use export
redefined-functions unintern fmakunbound shadow)
`(ensure-package
',name :nicknames ',nicknames :use ',use :export ',export
:shadow ',shadow
:unintern ',(append #-(or gcl ecl) redefined-functions
unintern)
:fmakunbound ',(append #+(or gcl ecl) redefined-functions
fmakunbound))))
(pkgdcl
:asdf-utilities
:nicknames (#:asdf-extensions)
:use (#:common-lisp)
:unintern (#:split #:make-collector)
:export
(#:absolute-pathname-p
#:aif
#:appendf
#:asdf-message
#:coerce-name
#:directory-pathname-p
#:ends-with
#:ensure-directory-pathname
#:getenv
#:get-uid
#:length=n-p
#:merge-pathnames*
#:pathname-directory-pathname
#:read-file-forms
#:remove-keys
#:remove-keyword
#:resolve-symlinks
#:split-string
#:component-name-to-pathname-components
#:split-name-type
#:system-registered-p
#:truenamize
#:while-collecting))
(pkgdcl
:asdf
:use (:common-lisp :asdf-utilities)
:redefined-functions
(#:perform #:explain #:output-files #:operation-done-p
#:perform-with-restarts #:component-relative-pathname
#:system-source-file #:operate #:find-component)
:unintern
(#:*asdf-revision* #:around #:asdf-method-combination
#:split #:make-collector)
:fmakunbound
(#:system-source-file
#:component-relative-pathname #:system-relative-pathname
#:process-source-registry
#:inherit-source-registry #:process-source-registry-directive)
:export
(#:defsystem #:oos #:operate #:find-system #:run-shell-command
#:system-definition-pathname #:find-component ; miscellaneous
#:compile-system #:load-system #:test-system
#:compile-op #:load-op #:load-source-op
#:test-op
#:operation ; operations
#:feature ; sort-of operation
#:version ; metaphorically sort-of an operation
#:version-satisfies
#:input-files #:output-files #:perform ; operation methods
#:operation-done-p #:explain
#:component #:source-file
#:c-source-file #:cl-source-file #:java-source-file
#:static-file
#:doc-file
#:html-file
#:text-file
#:source-file-type
#:module ; components
#:system
#:unix-dso
#:module-components ; component accessors
#:module-components-by-name ; component accessors
#:component-pathname
#:component-relative-pathname
#:component-name
#:component-version
#:component-parent
#:component-property
#:component-system
#:component-depends-on
#:system-description
#:system-long-description
#:system-author
#:system-maintainer
#:system-license
#:system-licence
#:system-source-file
#:system-source-directory
#:system-relative-pathname
#:map-systems
#:operation-on-warnings
#:operation-on-failure
;;#:*component-parent-pathname*
#:*system-definition-search-functions*
#:*central-registry* ; variables
#:*compile-file-warnings-behaviour*
#:*compile-file-failure-behaviour*
#:*resolve-symlinks*
#:*asdf-verbose*
#:asdf-version
#:operation-error #:compile-failed #:compile-warned #:compile-error
#:error-name
#:error-pathname
#:load-system-definition-error
#:error-component #:error-operation
#:system-definition-error
#:missing-component
#:missing-component-of-version
#:missing-dependency
#:missing-dependency-of-version
#:circular-dependency ; errors
#:duplicate-names
#:try-recompiling
#:retry
#:accept ; restarts
#:coerce-entry-to-directory
#:remove-entry-from-registry
#:initialize-output-translations
#:disable-output-translations
#:clear-output-translations
#:ensure-output-translations
#:apply-output-translations
#:compile-file-pathname*
#:enable-asdf-binary-locations-compatibility
#:*default-source-registries*
#:initialize-source-registry
#:compute-source-registry
#:clear-source-registry
#:ensure-source-registry
#:process-source-registry)))
(let* ((version (intern* vername :asdf))
(upvar (intern* '#:*upgraded-p* :asdf))
(upval0 (and (boundp upvar) (symbol-value upvar)))
(upval1 (if existing-version (cons existing-version upval0) upval0)))
(eval `(progn
(defparameter ,version ,asdf-version)
(defparameter ,upvar ',upval1))))))))
Gary King
committed
Francois-Rene Rideau
committed
(in-package :asdf)
;; More cleanups in case of hot-upgrade. See https://bugs.launchpad.net/asdf/+bug/485687
#+gcl
(eval-when (:compile-toplevel :load-toplevel)
(defvar *asdf-version* nil)
(defvar *upgraded-p* nil))
(when (find-class 'compile-op nil)
(defmethod update-instance-for-redefined-class :after
((c compile-op) added deleted plist &key)
(declare (ignore added deleted))
(let ((system-p (getf plist 'system-p)))
(when system-p (setf (getf (slot-value c 'flags) :system-p) system-p)))))
(when (find-class 'module nil)
(eval
'(defmethod update-instance-for-redefined-class :after
((m module) added deleted plist &key)
(declare (ignorable deleted plist))
Francois-Rene Rideau
committed
(format *trace-output* "Updating ~A~%" m)
(when (member 'components-by-name added)
(compute-module-components-by-name m))))))
Francois-Rene Rideau
committed
;;;; -------------------------------------------------------------------------
;;;; User-visible parameters
;;;;
Francois-Rene Rideau
committed
(defun asdf-version ()
"Exported interface to the version of ASDF currently installed. A string.
(ASDF:VERSION-SATISFIES (ASDF:ASDF-VERSION) \"2.000\")."
Francois-Rene Rideau
committed
*asdf-version*)
(defvar *resolve-symlinks* t
"Determine whether or not ASDF resolves symlinks when defining systems.
Defaults to `t`.")
(defvar *compile-file-warnings-behaviour* :warn)
(defvar *compile-file-failure-behaviour* #+sbcl :error #-sbcl :warn)
(defvar *verbose-out* nil)

Daniel Barlow
committed
(defvar *asdf-verbose* t)
Gary King
committed
(defparameter +asdf-methods+
Francois-Rene Rideau
committed
'(perform-with-restarts perform explain output-files operation-done-p))
Gary King
committed
#+allegro
(eval-when (:compile-toplevel :execute)
(defparameter *acl-warn-save*
(when (boundp 'excl:*warn-on-nested-reader-conditionals*)
excl:*warn-on-nested-reader-conditionals*))
(when (boundp 'excl:*warn-on-nested-reader-conditionals*)
(setf excl:*warn-on-nested-reader-conditionals* nil)))
;;;; -------------------------------------------------------------------------
;;;; ASDF Interface, in terms of generic functions.
Francois-Rene Rideau
committed
(defgeneric perform-with-restarts (operation component))
(defgeneric perform (operation component))
(defgeneric operation-done-p (operation component))
(defgeneric explain (operation component))
(defgeneric output-files (operation component))
(defgeneric input-files (operation component))
(defgeneric component-operation-time (operation component))
(defgeneric system-source-file (system)
(:documentation "Return the source file in which system is defined."))
(defgeneric component-system (component)
(:documentation "Find the top-level system containing COMPONENT"))
(defgeneric component-pathname (component)
(:documentation "Extracts the pathname applicable for a particular component."))
(defgeneric component-relative-pathname (component)
(:documentation "Returns a pathname for the component argument intended to be
interpreted relative to the pathname of that component's parent.
Despite the function's name, the return value may be an absolute
pathname, because an absolute pathname may be interpreted relative to
another pathname in a degenerate way."))
(defgeneric component-property (component property))
(defgeneric (setf component-property) (new-value component property))
(defgeneric version-satisfies (component version))
(defgeneric find-component (base path)
(:documentation "Finds the component with PATH starting from BASE module;
if BASE is nil, then the component is assumed to be a system."))
(defgeneric source-file-type (component system))
(defgeneric operation-ancestor (operation)
(:documentation
"Recursively chase the operation's parent pointer until we get to
the head of the tree"))
(defgeneric component-visited-p (operation component)
(:documentation "Returns the value stored by a call to
VISIT-COMPONENT, if that has been called, otherwise NIL.
This value stored will be a cons cell, the first element
of which is a computed key, so not interesting. The
CDR wil be the DATA value stored by VISIT-COMPONENT; recover
it as (cdr (component-visited-p op c)).
In the current form of ASDF, the DATA value retrieved is
effectively a boolean, indicating whether some operations are
to be performed in order to do OPERATION X COMPONENT. If the
data value is NIL, the combination had been explored, but no
operations needed to be performed."))
(defgeneric visit-component (operation component data)
(:documentation "Record DATA as being associated with OPERATION
and COMPONENT. This is a side-effecting function: the association
will be recorded on the ROOT OPERATION \(OPERATION-ANCESTOR of the
OPERATION\).
No evidence that DATA is ever interesting, beyond just being
non-NIL. Using the data field is probably very risky; if there is
already a record for OPERATION X COMPONENT, DATA will be quietly
discarded instead of recorded."))
(defgeneric (setf visiting-component) (new-value operation component))
(defgeneric component-visiting-p (operation component))
(defgeneric component-depends-on (operation component)
(:documentation
"Returns a list of dependencies needed by the component to perform
the operation. A dependency has one of the following forms:
(<operation> <component>*), where <operation> is a class
designator and each <component> is a component
designator, which means that the component depends on
<operation> having been performed on each <component>; or
(FEATURE <feature>), which means that the component depends
on <feature>'s presence in *FEATURES*.
Methods specialized on subclasses of existing component types
should usually append the results of CALL-NEXT-METHOD to the
list."))
(defgeneric component-self-dependencies (operation component))
Francois-Rene Rideau
committed
"Generate and return a plan for performing OPERATION on COMPONENT.
Francois-Rene Rideau
committed
The plan returned is a list of dotted-pairs. Each pair is the CONS
of ASDF operation object and a COMPONENT object. The pairs will be
processed in order by OPERATE."))
;;;; -------------------------------------------------------------------------
;;;; General Purpose Utilities
(defmacro while-collecting ((&rest collectors) &body body)
"COLLECTORS should be a list of names for collections. A collector
defines a function that, when applied to an argument inside BODY, will
add its argument to the corresponding collection. Returns multiple values,
a list for each collection, in order.
E.g.,
\(while-collecting \(foo bar\)
\(dolist \(x '\(\(a 1\) \(b 2\) \(c 3\)\)\)
\(foo \(first x\)\)
\(bar \(second x\)\)\)\)
Returns two values: \(A B C\) and \(1 2 3\)."
(let ((vars (mapcar #'(lambda (x) (gensym (symbol-name x))) collectors))
(initial-values (mapcar (constantly nil) collectors)))
`(let ,(mapcar #'list vars initial-values)
(flet ,(mapcar #'(lambda (c v) `(,c (x) (push x ,v) (values))) collectors vars)
,@body
(values ,@(mapcar #'(lambda (v) `(reverse ,v)) vars))))))
(defmacro aif (test then &optional else)
`(let ((it ,test)) (if it ,then ,else)))
(defun pathname-directory-pathname (pathname)
"Returns a new pathname with same HOST, DEVICE, DIRECTORY as PATHNAME,
and NIL NAME, TYPE and VERSION components"
Francois-Rene Rideau
committed
(when pathname
(make-pathname :name nil :type nil :version nil :defaults pathname)))
(defun merge-pathnames* (specified &optional (defaults *default-pathname-defaults*))
"MERGE-PATHNAMES* is like MERGE-PATHNAMES except that if the SPECIFIED pathname
does not have an absolute directory, then the HOST and DEVICE come from the DEFAULTS.
Also, if either argument is NIL, then the other argument is returned unmodified."
(when (null specified) (return-from merge-pathnames* defaults))
(when (null defaults) (return-from merge-pathnames* specified))
(let* ((specified (pathname specified))
(defaults (pathname defaults))
(directory (pathname-directory specified))
Francois-Rene Rideau
committed
#-sbcl (directory (if (stringp directory) `(:absolute ,directory) directory))
(name (or (pathname-name specified) (pathname-name defaults)))
(type (or (pathname-type specified) (pathname-type defaults)))
(version (or (pathname-version specified) (pathname-version defaults))))
Francois-Rene Rideau
committed
(labels ((ununspecific (x)
(if (eq x :unspecific) nil x))
(unspecific-handler (p)
(if (typep p 'logical-pathname) #'ununspecific #'identity)))
(multiple-value-bind (host device directory unspecific-handler)
(#-gcl ecase #+gcl case (first directory)
Francois-Rene Rideau
committed
((nil)
(values (pathname-host defaults)
(pathname-device defaults)
(pathname-directory defaults)
(unspecific-handler defaults)))
((:absolute)
(values (pathname-host specified)
(pathname-device specified)
directory
(unspecific-handler specified)))
((:relative)
(values (pathname-host defaults)
(pathname-device defaults)
Francois-Rene Rideau
committed
(if (pathname-directory defaults)
(append (pathname-directory defaults) (cdr directory))
directory)
(unspecific-handler defaults)))
#+gcl
(t
(assert (stringp (first directory)))
(values (pathname-host defaults)
(pathname-device defaults)
(append (pathname-directory defaults) directory)
Francois-Rene Rideau
committed
(unspecific-handler defaults))))
(make-pathname :host host :device device :directory directory
:name (funcall unspecific-handler name)
:type (funcall unspecific-handler type)
:version (funcall unspecific-handler version))))))
(define-modify-macro appendf (&rest args)
append "Append onto list") ;; only to be used on short lists.
(define-modify-macro orf (&rest args)
or "or a flag")
Francois-Rene Rideau
committed
(defun first-char (s)
(and (stringp s) (plusp (length s)) (char s 0)))
(defun last-char (s)
(and (stringp s) (plusp (length s)) (char s (1- (length s)))))
(defun asdf-message (format-string &rest format-args)
(declare (dynamic-extent format-args))
(apply #'format *verbose-out* format-string format-args))
(defun split-string (string &key max (separator '(#\Space #\Tab)))
Francois-Rene Rideau
committed
"Split STRING into a list of components separated by
any of the characters in the sequence SEPARATOR.
If MAX is specified, then no more than max(1,MAX) components will be returned,
starting the separation from the end, e.g. when called with arguments
\"a.b.c.d.e\" :max 3 :separator \".\" it will return (\"a.b.c\" \"d\" \"e\")."
(block nil
(let ((list nil) (words 0) (end (length string)))
(flet ((separatorp (char) (find char separator))
(done () (return (cons (subseq string 0 end) list))))
(loop
:for start = (if (and max (>= words (1- max)))
(done)
(position-if #'separatorp string :end end :from-end t)) :do
(when (null start)
(done))
(push (subseq string (1+ start) end) list)
(incf words)
(setf end start))))))
(defun split-name-type (filename)
Francois-Rene Rideau
committed
(let ((unspecific
;; Giving :unspecific as argument to make-pathname is not portable.
;; See CLHS make-pathname and 19.2.2.2.3.
;; We only use it on implementations that support it.
(or #+(or ccl ecl gcl lispworks sbcl) :unspecific)))
(destructuring-bind (name &optional (type unspecific))
(split-string filename :max 2 :separator ".")
(if (equal name "")
(values filename unspecific)
(values name type)))))
Francois-Rene Rideau
committed
(defun component-name-to-pathname-components (s &optional force-directory)
"Splits the path string S, returning three values:
A flag that is either :absolute or :relative, indicating
how the rest of the values are to be interpreted.
A directory path --- a list of strings, suitable for
use with MAKE-PATHNAME when prepended with the flag
value.
A filename with type extension, possibly NIL in the
case of a directory pathname.
FORCE-DIRECTORY forces S to be interpreted as a directory
pathname \(third return value will be NIL, final component
of S will be treated as part of the directory path.
The intention of this function is to support structured component names,
e.g., \(:file \"foo/bar\"\), which will be unpacked to relative
pathnames."
(let* ((components (split-string s :separator "/"))
(last-comp (car (last components))))
(multiple-value-bind (relative components)
(if (equal (first components) "")
(if (equal (first-char s) #\/)
(values :absolute (cdr components))
(values :relative nil))
(values :relative components))
(setf components (remove "" components :test #'equal))
(cond
((equal last-comp "")
(values relative components nil)) ; "" already removed
(force-directory
(values relative components nil))
(t
(values relative (butlast components) last-comp))))))
Francois-Rene Rideau
committed
(defun remove-keys (key-names args)
(loop :for (name val) :on args :by #'cddr
:unless (member (symbol-name name) key-names
:key #'symbol-name :test 'equal)
:append (list name val)))
(defun remove-keyword (key args)
(loop :for (k v) :on args :by #'cddr
:unless (eq k key)
:append (list k v)))
Francois-Rene Rideau
committed
(defun getenv (x)
#+sbcl
(sb-ext:posix-getenv x)
#+clozure
#+clisp
(ext:getenv x)
#+cmu
(cdr (assoc (intern x :keyword) ext:*environment-list*))
#+lispworks
(lispworks:environment-variable x)
#+allegro
(sys:getenv x)
#+gcl
(system:getenv x)
#+ecl
(si:getenv x))
Francois-Rene Rideau
committed
"Does PATHNAME represent a directory?
A directory-pathname is a pathname _without_ a filename. The three
Francois-Rene Rideau
committed
ways that the filename components can be missing are for it to be NIL,
:UNSPECIFIC or the empty string.
Francois-Rene Rideau
committed
Note that this does _not_ check to see that PATHNAME points to an
actually-existing directory."
(flet ((check-one (x)
(member x '(nil :unspecific "") :test 'equal)))
(and (check-one (pathname-name pathname))
(check-one (pathname-type pathname))
t)))
(defun ensure-directory-pathname (pathspec)
"Converts the non-wild pathname designator PATHSPEC to directory form."
Francois-Rene Rideau
committed
(cond
((stringp pathspec)
(ensure-directory-pathname (pathname pathspec)))
Francois-Rene Rideau
committed
((not (pathnamep pathspec))
(error "Invalid pathname designator ~S" pathspec))
((wild-pathname-p pathspec)
(error "Can't reliably convert wild pathnames."))
((directory-pathname-p pathspec)
pathspec)
(t
(make-pathname :directory (append (or (pathname-directory pathspec)
(list :relative))
(list (file-namestring pathspec)))
:name nil :type nil :version nil
:defaults pathspec))))
Francois-Rene Rideau
committed
(defun absolute-pathname-p (pathspec)
(eq :absolute (car (pathname-directory (pathname pathspec)))))
Francois-Rene Rideau
committed
(defun length=n-p (x n) ;is it that (= (length x) n) ?
(check-type n (integer 0 *))
(loop
:for l = x :then (cdr l)
:for i :downfrom n :do
(cond
((zerop i) (return (null l)))
((not (consp l)) (return nil)))))
(defun ends-with (s suffix)
(check-type s string)
(check-type suffix string)
(let ((start (- (length s) (length suffix))))
(and (<= 0 start)
(string-equal s suffix :start1 start))))
Francois-Rene Rideau
committed
(defun read-file-forms (file)
(with-open-file (in file)
(loop :with eof = (list nil)
:for form = (read in nil eof)
:until (eq form eof)
:collect form)))
#-(and (or win32 windows mswindows mingw32) (not cygwin))
Francois-Rene Rideau
committed
(progn
Francois-Rene Rideau
committed
#+clisp (defun get-uid () (posix:uid))
Francois-Rene Rideau
committed
#+sbcl (defun get-uid () (sb-unix:unix-getuid))
#+cmu (defun get-uid () (unix:unix-getuid))
Francois-Rene Rideau
committed
#+ecl (ffi:clines "#include <sys/types.h>" "#include <unistd.h>")
Francois-Rene Rideau
committed
#+ecl (defun get-uid () (ffi:c-inline () () :int "getuid()" :one-liner t))
#+allegro (defun get-uid () (excl.osi:getuid))
#-(or cmu sbcl clisp allegro ecl)
(defun get-uid ()
(let ((uid-string
(with-output-to-string (*verbose-out*)
Francois-Rene Rideau
committed
(run-shell-command "id -ur"))))
Francois-Rene Rideau
committed
(with-input-from-string (stream uid-string)
(read-line stream)
(handler-case (parse-integer (read-line stream))
(error () (error "Unable to find out user ID")))))))
Francois-Rene Rideau
committed
(defun pathname-root (pathname)
(make-pathname :host (pathname-host pathname)
:device (pathname-device pathname)
:directory '(:absolute)
:name nil :type nil :version nil))
Francois-Rene Rideau
committed
(defun truenamize (p)
"Resolve as much of a pathname as possible"
(block nil
(when (typep p 'logical-pathname) (return p))
(let* ((p (merge-pathnames* p))
(directory (pathname-directory p)))
(when (typep p 'logical-pathname) (return p))
(ignore-errors (return (truename p)))
Francois-Rene Rideau
committed
#-sbcl (when (stringp directory) (return p))
(when (not (eq :absolute (car directory))) (return p))
Francois-Rene Rideau
committed
(let ((sofar (ignore-errors (truename (pathname-root p)))))
(unless sofar (return p))
(flet ((solution (directories)
(merge-pathnames*
(make-pathname :host nil :device nil
:directory `(:relative ,@directories)
:name (pathname-name p)
:type (pathname-type p)
:version (pathname-version p))
sofar)))
(loop :for component :in (cdr directory)
:for rest :on (cdr directory)
:for more = (ignore-errors
(truename
(merge-pathnames*
(make-pathname :directory `(:relative ,component))
sofar))) :do
(if more
(setf sofar more)
(return (solution rest)))
:finally
(return (solution nil))))))))
Francois-Rene Rideau
committed
Francois-Rene Rideau
committed
(defun resolve-symlinks (path)
#-allegro (truenamize path)
#+allegro (excl:pathname-resolve-symbolic-links path))
(defun default-directory ()
(truenamize (pathname-directory-pathname *default-pathname-defaults*)))
(defun lispize-pathname (input-file)
(make-pathname :type "lisp" :defaults input-file))
Francois-Rene Rideau
committed
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
(defparameter *wild-path*
(make-pathname :directory '(:relative :wild-inferiors)
:name :wild :type :wild :version :wild))
(defun wilden (path)
(merge-pathnames* *wild-path* path))
(defun directorize-pathname-host-device (pathname)
(let* ((root (pathname-root pathname))
(wild-root (wilden root))
(absolute-pathname (merge-pathnames* pathname root))
(foo (make-pathname :directory '(:absolute "FOO") :defaults root))
(separator (last-char (namestring foo)))
(root-namestring (namestring root))
(root-string
(substitute-if #\/
(lambda (x) (or (eql x #\:)
(eql x separator)))
root-namestring)))
(multiple-value-bind (relative path filename)
(component-name-to-pathname-components root-string t)
(declare (ignore relative filename))
(let ((new-base
(make-pathname :defaults root
:directory `(:absolute ,@path))))
(translate-pathname absolute-pathname wild-root (wilden new-base))))))
;;;; -------------------------------------------------------------------------
;;;; Classes, Conditions
(define-condition system-definition-error (error) ()
;; [this use of :report should be redundant, but unfortunately it's not.
;; cmucl's lisp::output-instance prefers the kernel:slot-class-print-function
;; over print-object; this is always conditions::%print-condition for
;; condition objects, which in turn does inheritance of :report options at
;; run-time. fortunately, inheritance means we only need this kludge here in
;; order to fix all conditions that build on it. -- rgr, 28-Jul-02.]
#+cmu (:report print-object))
Francois-Rene Rideau
committed
(declaim (ftype (function (t) t)
format-arguments format-control
error-name error-pathname error-condition
duplicate-names-name
error-component error-operation
module-components module-components-by-name)
(ftype (function (t t) t) (setf module-components-by-name)))
(define-condition formatted-system-definition-error (system-definition-error)
((format-control :initarg :format-control :reader format-control)
(format-arguments :initarg :format-arguments :reader format-arguments))
(:report (lambda (c s)
(apply #'format s (format-control c) (format-arguments c)))))
(define-condition load-system-definition-error (system-definition-error)
((name :initarg :name :reader error-name)
(pathname :initarg :pathname :reader error-pathname)
(condition :initarg :condition :reader error-condition))
(:report (lambda (c s)
(format s "~@<Error while trying to load definition for system ~A from pathname ~A: ~A~@:>"
(error-name c) (error-pathname c) (error-condition c)))))
(define-condition circular-dependency (system-definition-error)

Daniel Barlow
committed
((components :initarg :components :reader circular-dependency-components)))
(define-condition duplicate-names (system-definition-error)
((name :initarg :name :reader duplicate-names-name))
(:report (lambda (c s)
(format s "~@<Error while defining system: multiple components are given same name ~A~@:>"
(duplicate-names-name c)))))
(define-condition missing-component (system-definition-error)
((requires :initform "(unnamed)" :reader missing-requires :initarg :requires)
(parent :initform nil :reader missing-parent :initarg :parent)))
Gary King
committed
(define-condition missing-component-of-version (missing-component)
((version :initform nil :reader missing-version :initarg :version)))
(define-condition missing-dependency (missing-component)
((required-by :initarg :required-by :reader missing-required-by)))
Gary King
committed
(define-condition missing-dependency-of-version (missing-dependency
Gary King
committed
())
(define-condition operation-error (error)
((component :reader error-component :initarg :component)
(operation :reader error-operation :initarg :operation))
(:report (lambda (c s)
(format s "~@<erred while invoking ~A on ~A~@:>"
(error-operation c) (error-component c)))))
(define-condition compile-error (operation-error) ())
(define-condition compile-failed (compile-error) ())
(define-condition compile-warned (compile-error) ())
((name :accessor component-name :initarg :name :documentation
"Component name: designator for a string composed of portable pathname characters")
(version :accessor component-version :initarg :version)
Francois-Rene Rideau
committed
(in-order-to :initform nil :initarg :in-order-to
:accessor component-in-order-to)
;; This one is used by POIU. Maybe in the future by ASDF instead of in-order-to?
(load-dependencies :accessor component-load-dependencies :initform nil)
;; XXX crap name, but it's an official API name!
Francois-Rene Rideau
committed
(do-first :initform nil :initarg :do-first
:accessor component-do-first)
;; methods defined using the "inline" style inside a defsystem form:
;; need to store them somewhere so we can delete them when the system
;; is re-evaluated
(inline-methods :accessor component-inline-methods :initform nil)
(parent :initarg :parent :initform nil :reader component-parent)
;; no direct accessor for pathname, we do this as a method to allow
;; it to default in funky ways if not supplied
Francois-Rene Rideau
committed
(operation-times :initform (make-hash-table)
;; XXX we should provide some atomic interface for updating the
;; component properties

Daniel Barlow
committed
(properties :accessor component-properties :initarg :properties
(defun component-find-path (component)
(reverse
(loop :for c = component :then (component-parent c)
:while c :collect (component-name c))))
(defmethod print-object ((c component) stream)
(print-unreadable-object (c stream :type t :identity nil)
(format stream "~@<~{~S~^ ~}~@:>" (component-find-path c))))
;;;; methods: conditions
(defmethod print-object ((c missing-dependency) s)
Christophe Rhodes
committed
(format s "~@<~A, required by ~A~@:>"
(call-next-method c nil) (missing-required-by c)))
(error 'formatted-system-definition-error :format-control
;;;; methods: components
(defmethod print-object ((c missing-component) s)
Gary King
committed
(format s "~@<component ~S not found~
Christophe Rhodes
committed
~@[ in ~A~]~@:>"
(missing-requires c)
(when (missing-parent c)
(component-name (missing-parent c)))))
Gary King
committed
(defmethod print-object ((c missing-component-of-version) s)
(format s "~@<component ~S does not match version ~A~
~@[ in ~A~]~@:>"
(missing-requires c)
(missing-version c)
(when (missing-parent c)
(component-name (missing-parent c)))))
Gary King
committed
(defmethod component-system ((component component))
(aif (component-parent component)
(component-system it)
component))
(defvar *default-component-class* 'cl-source-file)
(defun compute-module-components-by-name (module)
Francois-Rene Rideau
committed
(let ((hash (make-hash-table :test 'equal)))
(setf (module-components-by-name module) hash)
(loop :for c :in (module-components module)
:for name = (component-name c)
:for previous = (gethash name (module-components-by-name module))
:do
(when previous
(error 'duplicate-names :name name))
:do (setf (gethash name (module-components-by-name module)) c))
hash))
((components
:initform nil
:initarg :components
:accessor module-components)
(components-by-name
:accessor module-components-by-name)
;; What to do if we can't satisfy a dependency of one of this module's
;; components. This allows a limited form of conditional processing.
(if-component-dep-fails
:initform :fail
:initarg :if-component-dep-fails
:accessor module-if-component-dep-fails)
(default-component-class
:initform *default-component-class*
:initarg :default-component-class
:accessor module-default-component-class)))
;; No default anymore (in particular, no *default-pathname-defaults*).
;; If you force component to have a NULL pathname, you better arrange
;; for any of its children to explicitly provide a proper absolute pathname
;; wherever a pathname is actually wanted.
(let ((parent (component-parent component)))
(when parent
(component-pathname parent))))
(if (slot-boundp component 'absolute-pathname)
(slot-value component 'absolute-pathname)
(let ((pathname
(merge-pathnames*
(component-relative-pathname component)
Francois-Rene Rideau
committed
(pathname-directory-pathname (component-parent-pathname component)))))
(unless (or (null pathname) (absolute-pathname-p pathname))
(error "Invalid relative pathname ~S for component ~S" pathname component))
(setf (slot-value component 'absolute-pathname) pathname)
pathname)))

Daniel Barlow
committed
(defmethod component-property ((c component) property)