1 ;;;; machine/filesystem-independent pathname functions
3 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
12 (in-package "SB!IMPL")
14 #!-sb-fluid (declaim (freeze-type logical-pathname logical-host))
16 ;;;; PHYSICAL-HOST stuff
18 (def!struct (unix-host
19 (:make-load-form-fun make-unix-host-load-form)
21 (parse #'parse-unix-namestring)
22 (parse-native #'parse-native-unix-namestring)
23 (unparse #'unparse-unix-namestring)
24 (unparse-native #'unparse-native-unix-namestring)
25 (unparse-host #'unparse-unix-host)
26 (unparse-directory #'unparse-physical-directory)
27 (unparse-file #'unparse-unix-file)
28 (unparse-enough #'unparse-unix-enough)
29 (unparse-directory-separator "/")
30 (simplify-namestring #'simplify-unix-namestring)
31 (customary-case :lower))))
32 (defvar *unix-host* (make-unix-host))
33 (defun make-unix-host-load-form (host)
34 (declare (ignore host))
37 (def!struct (win32-host
38 (:make-load-form-fun make-win32-host-load-form)
40 (parse #'parse-win32-namestring)
41 (parse-native #'parse-native-win32-namestring)
42 (unparse #'unparse-win32-namestring)
43 (unparse-native #'unparse-native-win32-namestring)
44 (unparse-host #'unparse-win32-host)
45 (unparse-directory #'unparse-physical-directory)
46 (unparse-file #'unparse-win32-file)
47 (unparse-enough #'unparse-win32-enough)
48 (unparse-directory-separator "\\")
49 (simplify-namestring #'simplify-win32-namestring)
50 (customary-case :upper))))
51 (defparameter *win32-host* (make-win32-host))
52 (defun make-win32-host-load-form (host)
53 (declare (ignore host))
56 (defvar *physical-host*
58 #!+win32 *win32-host*)
60 ;;; Return a value suitable, e.g., for preinitializing
61 ;;; *DEFAULT-PATHNAME-DEFAULTS* before *DEFAULT-PATHNAME-DEFAULTS* is
62 ;;; initialized (at which time we can't safely call e.g. #'PATHNAME).
63 (defun make-trivial-default-pathname ()
64 (%make-pathname *physical-host* nil nil nil nil :newest))
68 (def!method print-object ((pathname pathname) stream)
69 (let ((namestring (handler-case (namestring pathname)
73 (if (or *print-readably* *print-escape*)
76 (coerce namestring '(simple-array character (*))))
77 (print-unreadable-object (pathname stream :type t)
79 "~@<(with no namestring) ~_:HOST ~S ~_:DEVICE ~S ~_:DIRECTORY ~S ~
80 ~_:NAME ~S ~_:TYPE ~S ~_:VERSION ~S~:>"
81 (%pathname-host pathname)
82 (%pathname-device pathname)
83 (%pathname-directory pathname)
84 (%pathname-name pathname)
85 (%pathname-type pathname)
86 (%pathname-version pathname))))))
88 (def!method make-load-form ((pathname pathname) &optional environment)
89 (make-load-form-saving-slots pathname :environment environment))
91 ;;; A pathname is logical if the host component is a logical host.
92 ;;; This constructor is used to make an instance of the correct type
93 ;;; from parsed arguments.
94 (defun %make-maybe-logical-pathname (host device directory name type version)
95 ;; We canonicalize logical pathname components to uppercase. ANSI
96 ;; doesn't strictly require this, leaving it up to the implementor;
97 ;; but the arguments given in the X3J13 cleanup issue
98 ;; PATHNAME-LOGICAL:ADD seem compelling: we should canonicalize the
99 ;; case, and uppercase is the ordinary way to do that.
100 (flet ((upcase-maybe (x) (typecase x (string (logical-word-or-lose x)) (t x))))
101 (if (typep host 'logical-host)
102 (%make-logical-pathname host
104 (mapcar #'upcase-maybe directory)
109 (aver (eq host *physical-host*))
110 (%make-pathname host device directory name type version)))))
112 ;;; Hash table searching maps a logical pathname's host to its
113 ;;; physical pathname translation.
114 (defvar *logical-hosts* (make-hash-table :test 'equal :synchronized t))
118 (def!method make-load-form ((pattern pattern) &optional environment)
119 (make-load-form-saving-slots pattern :environment environment))
121 (def!method print-object ((pattern pattern) stream)
122 (print-unreadable-object (pattern stream :type t)
124 (let ((*print-escape* t))
125 (pprint-fill stream (pattern-pieces pattern) nil))
126 (prin1 (pattern-pieces pattern) stream))))
128 (defun pattern= (pattern1 pattern2)
129 (declare (type pattern pattern1 pattern2))
130 (let ((pieces1 (pattern-pieces pattern1))
131 (pieces2 (pattern-pieces pattern2)))
132 (and (= (length pieces1) (length pieces2))
133 (every (lambda (piece1 piece2)
136 (and (simple-string-p piece2)
137 (string= piece1 piece2)))
140 (eq (car piece1) (car piece2))
141 (string= (cdr piece1) (cdr piece2))))
143 (eq piece1 piece2))))
147 ;;; If the string matches the pattern returns the multiple values T
148 ;;; and a list of the matched strings.
149 (defun pattern-matches (pattern string)
150 (declare (type pattern pattern)
151 (type simple-string string))
152 (let ((len (length string)))
153 (labels ((maybe-prepend (subs cur-sub chars)
155 (let* ((len (length chars))
156 (new (make-string len))
159 (setf (schar new (decf index)) char))
162 (matches (pieces start subs cur-sub chars)
165 (values t (maybe-prepend subs cur-sub chars))
167 (let ((piece (car pieces)))
170 (let ((end (+ start (length piece))))
172 (string= piece string
173 :start2 start :end2 end)
174 (matches (cdr pieces) end
175 (maybe-prepend subs cur-sub chars)
181 (let ((char (schar string start)))
182 (if (find char (cdr piece) :test #'char=)
183 (matches (cdr pieces) (1+ start) subs t
184 (cons char chars))))))))
185 ((member :single-char-wild)
187 (matches (cdr pieces) (1+ start) subs t
188 (cons (schar string start) chars))))
189 ((member :multi-char-wild)
190 (multiple-value-bind (won new-subs)
191 (matches (cdr pieces) start subs t chars)
195 (matches pieces (1+ start) subs t
196 (cons (schar string start)
198 (multiple-value-bind (won subs)
199 (matches (pattern-pieces pattern) 0 nil nil nil)
200 (values won (reverse subs))))))
202 ;;; PATHNAME-MATCH-P for directory components
203 (defun directory-components-match (thing wild)
206 ;; If THING has a null directory, assume that it matches
207 ;; (:ABSOLUTE :WILD-INFERIORS) or (:RELATIVE :WILD-INFERIORS).
210 (member (first wild) '(:absolute :relative))
211 (eq (second wild) :wild-inferiors))
213 (let ((wild1 (first wild)))
214 (if (eq wild1 :wild-inferiors)
215 (let ((wild-subdirs (rest wild)))
216 (or (null wild-subdirs)
218 (when (directory-components-match thing wild-subdirs)
221 (unless thing (return nil)))))
223 (components-match (first thing) wild1)
224 (directory-components-match (rest thing)
227 ;;; Return true if pathname component THING is matched by WILD. (not
229 (defun components-match (thing wild)
230 (declare (type (or pattern symbol simple-string integer) thing wild))
235 ;; String is matched by itself, a matching pattern or :WILD.
238 (values (pattern-matches wild thing)))
240 (string= thing wild))))
242 ;; A pattern is only matched by an identical pattern.
243 (and (pattern-p wild) (pattern= thing wild)))
245 ;; An integer (version number) is matched by :WILD or the
246 ;; same integer. This branch will actually always be NIL as
247 ;; long as the version is a fixnum.
250 ;;; a predicate for comparing two pathname slot component sub-entries
251 (defun compare-component (this that)
255 (and (simple-string-p that)
256 (string= this that)))
258 (and (pattern-p that)
259 (pattern= this that)))
262 (compare-component (car this) (car that))
263 (compare-component (cdr this) (cdr that)))))))
265 ;;;; pathname functions
267 (defun pathname= (pathname1 pathname2)
268 (declare (type pathname pathname1)
269 (type pathname pathname2))
270 (and (eq (%pathname-host pathname1)
271 (%pathname-host pathname2))
272 (compare-component (%pathname-device pathname1)
273 (%pathname-device pathname2))
274 (compare-component (%pathname-directory pathname1)
275 (%pathname-directory pathname2))
276 (compare-component (%pathname-name pathname1)
277 (%pathname-name pathname2))
278 (compare-component (%pathname-type pathname1)
279 (%pathname-type pathname2))
280 (or (eq (%pathname-host pathname1) *unix-host*)
281 (compare-component (%pathname-version pathname1)
282 (%pathname-version pathname2)))))
284 ;;; Convert PATHNAME-DESIGNATOR (a pathname, or string, or
285 ;;; stream), into a pathname in pathname.
287 ;;; FIXME: was rewritten, should be tested (or rewritten again, this
288 ;;; time using ONCE-ONLY, *then* tested)
289 (eval-when (:compile-toplevel :execute)
290 (sb!xc:defmacro with-pathname ((pathname pathname-designator) &body body)
291 (let ((pd0 (gensym)))
292 `(let* ((,pd0 ,pathname-designator)
293 (,pathname (etypecase ,pd0
295 (string (parse-namestring ,pd0))
296 (file-stream (file-name ,pd0)))))
299 (sb!xc:defmacro with-native-pathname ((pathname pathname-designator) &body body)
300 (let ((pd0 (gensym)))
301 `(let* ((,pd0 ,pathname-designator)
302 (,pathname (etypecase ,pd0
304 (string (parse-native-namestring ,pd0))
307 (file-stream (file-name ,pd0)))))
310 (sb!xc:defmacro with-host ((host host-designator) &body body)
311 ;; Generally, redundant specification of information in software,
312 ;; whether in code or in comments, is bad. However, the ANSI spec
313 ;; for this is messy enough that it's hard to hold in short-term
314 ;; memory, so I've recorded these redundant notes on the
315 ;; implications of the ANSI spec.
317 ;; According to the ANSI spec, HOST can be a valid pathname host, or
318 ;; a logical host, or NIL.
320 ;; A valid pathname host can be a valid physical pathname host or a
321 ;; valid logical pathname host.
323 ;; A valid physical pathname host is "any of a string, a list of
324 ;; strings, or the symbol :UNSPECIFIC, that is recognized by the
325 ;; implementation as the name of a host". In SBCL as of 0.6.9.8,
326 ;; that means :UNSPECIFIC: though someday we might want to
327 ;; generalize it to allow strings like "RTFM.MIT.EDU" or lists like
328 ;; '("RTFM" "MIT" "EDU"), that's not supported now.
330 ;; A valid logical pathname host is a string which has been defined as
331 ;; the name of a logical host, as with LOAD-LOGICAL-PATHNAME-TRANSLATIONS.
333 ;; A logical host is an object of implementation-dependent nature. In
334 ;; SBCL, it's a member of the HOST class (a subclass of STRUCTURE-OBJECT).
335 (let ((hd0 (gensym)))
336 `(let* ((,hd0 ,host-designator)
337 (,host (etypecase ,hd0
339 ;; This is a special host. It's not valid as a
340 ;; logical host, so it is a sensible thing to
341 ;; designate the physical host object. So we do
345 ;; In general ANSI-compliant Common Lisps, a
346 ;; string might also be a physical pathname
347 ;; host, but ANSI leaves this up to the
348 ;; implementor, and in SBCL we don't do it, so
349 ;; it must be a logical host.
350 (find-logical-host ,hd0))
351 ((or null (member :unspecific))
352 ;; CLHS says that HOST=:UNSPECIFIC has
353 ;; implementation-defined behavior. We
354 ;; just turn it into NIL.
357 ;; ANSI also allows LISTs to designate hosts,
358 ;; but leaves its interpretation
359 ;; implementation-defined. Our interpretation
360 ;; is that it's unsupported.:-|
361 (error "A LIST representing a pathname host is not ~
362 supported in this implementation:~% ~S"
368 (defun find-host (host-designator &optional (errorp t))
369 (with-host (host host-designator)
370 (when (and errorp (not host))
371 (error "Couldn't find host: ~S" host-designator))
374 (defun pathname (pathspec)
376 "Convert PATHSPEC (a pathname designator) into a pathname."
377 (declare (type pathname-designator pathspec))
378 (with-pathname (pathname pathspec)
381 (defun native-pathname (pathspec)
383 "Convert PATHSPEC (a pathname designator) into a pathname, assuming
384 the operating system native pathname conventions."
385 (with-native-pathname (pathname pathspec)
388 ;;; Change the case of thing if DIDDLE-P.
389 (defun maybe-diddle-case (thing diddle-p)
390 (if (and diddle-p (not (or (symbolp thing) (integerp thing))))
391 (labels ((check-for (pred in)
394 (dolist (piece (pattern-pieces in))
395 (when (typecase piece
397 (check-for pred piece))
401 (check-for pred (cdr piece))))))
405 (when (check-for pred x)
408 (dotimes (i (length in))
409 (when (funcall pred (schar in i))
412 (diddle-with (fun thing)
416 (mapcar (lambda (piece)
424 (funcall fun (cdr piece))))
429 (pattern-pieces thing))))
436 (let ((any-uppers (check-for #'upper-case-p thing))
437 (any-lowers (check-for #'lower-case-p thing)))
438 (cond ((and any-uppers any-lowers)
439 ;; mixed case, stays the same
442 ;; all uppercase, becomes all lower case
443 (diddle-with (lambda (x) (if (stringp x)
447 ;; all lowercase, becomes all upper case
448 (diddle-with (lambda (x) (if (stringp x)
452 ;; no letters? I guess just leave it.
456 (defun merge-directories (dir1 dir2 diddle-case)
457 (if (or (eq (car dir1) :absolute)
462 (if (and (eq dir :back)
464 (not (member (car results)
465 '(:back :wild-inferiors :relative :absolute))))
467 (push dir results))))
468 (dolist (dir (maybe-diddle-case dir2 diddle-case))
470 (dolist (dir (cdr dir1))
474 (defun merge-pathnames (pathname
476 (defaults *default-pathname-defaults*)
477 (default-version :newest))
479 "Construct a filled in pathname by completing the unspecified components
481 (declare (type pathname-designator pathname)
482 (type pathname-designator defaults)
484 (with-pathname (defaults defaults)
485 (let ((pathname (let ((*default-pathname-defaults* defaults))
486 (pathname pathname))))
487 (let* ((default-host (%pathname-host defaults))
488 (pathname-host (%pathname-host pathname))
490 (and default-host pathname-host
491 (not (eq (host-customary-case default-host)
492 (host-customary-case pathname-host))))))
493 (%make-maybe-logical-pathname
494 (or pathname-host default-host)
495 (or (%pathname-device pathname)
496 (maybe-diddle-case (%pathname-device defaults)
498 (merge-directories (%pathname-directory pathname)
499 (%pathname-directory defaults)
501 (or (%pathname-name pathname)
502 (maybe-diddle-case (%pathname-name defaults)
504 (or (%pathname-type pathname)
505 (maybe-diddle-case (%pathname-type defaults)
507 (or (%pathname-version pathname)
508 (and (not (%pathname-name pathname)) (%pathname-version defaults))
509 default-version))))))
511 (defun import-directory (directory diddle-case)
514 ((member :wild) '(:absolute :wild-inferiors))
515 ((member :unspecific) '(:relative))
518 (let ((root (pop directory)))
519 (if (member root '(:relative :absolute))
521 (error "List of directory components must start with ~S or ~S."
522 :absolute :relative)))
524 (let ((next (pop directory)))
525 (if (or (eq :home next)
526 (typep next '(cons (eql :home) (cons string null))))
528 (push next directory)))
529 (dolist (piece directory)
530 (cond ((member piece '(:wild :wild-inferiors :up :back))
532 ((or (simple-string-p piece) (pattern-p piece))
533 (results (maybe-diddle-case piece diddle-case)))
535 (results (maybe-diddle-case (coerce piece 'simple-string)
538 (error "~S is not allowed as a directory component." piece)))))
541 `(:absolute ,(maybe-diddle-case directory diddle-case)))
544 ,(maybe-diddle-case (coerce directory 'simple-string) diddle-case)))))
546 (defun make-pathname (&key host
551 (version nil versionp)
555 "Makes a new pathname from the component arguments. Note that host is
556 a host-structure or string."
557 (declare (type (or string host pathname-component-tokens) host)
558 (type (or string pathname-component-tokens) device)
559 (type (or list string pattern pathname-component-tokens) directory)
560 (type (or string pattern pathname-component-tokens) name type)
561 (type (or integer pathname-component-tokens (member :newest))
563 (type (or pathname-designator null) defaults)
564 (type (member :common :local) case))
565 (let* ((defaults (when defaults
566 (with-pathname (defaults defaults) defaults)))
567 (default-host (if defaults
568 (%pathname-host defaults)
569 (pathname-host *default-pathname-defaults*)))
570 ;; Raymond Toy writes: CLHS says make-pathname can take a
571 ;; string (as a logical-host) for the host part. We map that
572 ;; string into the corresponding logical host structure.
574 ;; Paul Werkowski writes:
575 ;; HyperSpec says for the arg to MAKE-PATHNAME;
576 ;; "host---a valid physical pathname host. ..."
577 ;; where it probably means -- a valid pathname host.
578 ;; "valid pathname host n. a valid physical pathname host or
579 ;; a valid logical pathname host."
581 ;; "valid physical pathname host n. any of a string,
582 ;; a list of strings, or the symbol :unspecific,
583 ;; that is recognized by the implementation as the name of a host."
584 ;; "valid logical pathname host n. a string that has been defined
585 ;; as the name of a logical host. ..."
586 ;; HS is silent on what happens if the :HOST arg is NOT one of these.
587 ;; It seems an error message is appropriate.
588 (host (or (find-host host nil) default-host))
589 (diddle-args (and (eq (host-customary-case host) :lower)
592 (not (eq (host-customary-case host)
593 (host-customary-case default-host))))
594 (dev (if devp device (if defaults (%pathname-device defaults))))
595 (dir (import-directory directory diddle-args))
598 (defaults (%pathname-version defaults))
600 (when (and defaults (not dirp))
602 (merge-directories dir
603 (%pathname-directory defaults)
606 (macrolet ((pick (var varp field)
607 `(cond ((or (simple-string-p ,var)
609 (maybe-diddle-case ,var diddle-args))
611 (maybe-diddle-case (coerce ,var 'simple-string)
614 (maybe-diddle-case ,var diddle-args))
616 (maybe-diddle-case (,field defaults)
620 (%make-maybe-logical-pathname host
621 dev ; forced to :UNSPECIFIC when logical
623 (pick name namep %pathname-name)
624 (pick type typep %pathname-type)
627 (defun pathname-host (pathname &key (case :local))
629 "Return PATHNAME's host."
630 (declare (type pathname-designator pathname)
631 (type (member :local :common) case)
634 (with-pathname (pathname pathname)
635 (%pathname-host pathname)))
637 (defun pathname-device (pathname &key (case :local))
639 "Return PATHNAME's device."
640 (declare (type pathname-designator pathname)
641 (type (member :local :common) case))
642 (with-pathname (pathname pathname)
643 (maybe-diddle-case (%pathname-device pathname)
644 (and (eq case :common)
645 (eq (host-customary-case
646 (%pathname-host pathname))
649 (defun pathname-directory (pathname &key (case :local))
651 "Return PATHNAME's directory."
652 (declare (type pathname-designator pathname)
653 (type (member :local :common) case))
654 (with-pathname (pathname pathname)
655 (maybe-diddle-case (%pathname-directory pathname)
656 (and (eq case :common)
657 (eq (host-customary-case
658 (%pathname-host pathname))
660 (defun pathname-name (pathname &key (case :local))
662 "Return PATHNAME's name."
663 (declare (type pathname-designator pathname)
664 (type (member :local :common) case))
665 (with-pathname (pathname pathname)
666 (maybe-diddle-case (%pathname-name pathname)
667 (and (eq case :common)
668 (eq (host-customary-case
669 (%pathname-host pathname))
672 (defun pathname-type (pathname &key (case :local))
674 "Return PATHNAME's type."
675 (declare (type pathname-designator pathname)
676 (type (member :local :common) case))
677 (with-pathname (pathname pathname)
678 (maybe-diddle-case (%pathname-type pathname)
679 (and (eq case :common)
680 (eq (host-customary-case
681 (%pathname-host pathname))
684 (defun pathname-version (pathname)
686 "Return PATHNAME's version."
687 (declare (type pathname-designator pathname))
688 (with-pathname (pathname pathname)
689 (%pathname-version pathname)))
693 ;;; Handle the case for PARSE-NAMESTRING parsing a potentially
694 ;;; syntactically valid logical namestring with an explicit host.
696 ;;; This then isn't fully general -- we are relying on the fact that
697 ;;; we will only pass to parse-namestring namestring with an explicit
698 ;;; logical host, so that we can pass the host return from
699 ;;; parse-logical-namestring through to %PARSE-NAMESTRING as a truth
700 ;;; value. Yeah, this is probably a KLUDGE - CSR, 2002-04-18
701 (defun parseable-logical-namestring-p (namestr start end)
704 ((namestring-parse-error (lambda (c)
707 (let ((colon (position #\: namestr :start start :end end)))
709 (let ((potential-host
710 (logical-word-or-lose (subseq namestr start colon))))
711 ;; depending on the outcome of CSR comp.lang.lisp post
712 ;; "can PARSE-NAMESTRING create logical hosts", we may need
713 ;; to do things with potential-host (create it
714 ;; temporarily, parse the namestring and unintern the
715 ;; logical host potential-host on failure.
716 (declare (ignore potential-host))
719 ((simple-type-error (lambda (c)
722 (parse-logical-namestring namestr start end))))
723 ;; if we got this far, we should have an explicit host
724 ;; (first return value of parse-logical-namestring)
728 ;;; Handle the case where PARSE-NAMESTRING is actually parsing a
729 ;;; namestring. We pick off the :JUNK-ALLOWED case then find a host to
730 ;;; use for parsing, call the parser, then check whether the host matches.
731 (defun %parse-namestring (namestr host defaults start end junk-allowed)
732 (declare (type (or host null) host)
733 (type string namestr)
735 (type (or index null) end))
739 (%parse-namestring namestr host defaults start end nil)
740 (namestring-parse-error (condition)
741 (values nil (namestring-parse-error-offset condition)))))
743 (let* ((end (%check-vector-sequence-bounds namestr start end)))
744 (multiple-value-bind (new-host device directory file type version)
745 ;; Comments below are quotes from the HyperSpec
746 ;; PARSE-NAMESTRING entry, reproduced here to demonstrate
747 ;; that we actually have to do things this way rather than
748 ;; some possibly more logical way. - CSR, 2002-04-18
750 ;; "If host is a logical host then thing is parsed as a
751 ;; logical pathname namestring on the host."
752 (host (funcall (host-parse host) namestr start end))
753 ;; "If host is nil and thing is a syntactically valid
754 ;; logical pathname namestring containing an explicit
755 ;; host, then it is parsed as a logical pathname
757 ((parseable-logical-namestring-p namestr start end)
758 (parse-logical-namestring namestr start end))
759 ;; "If host is nil, default-pathname is a logical
760 ;; pathname, and thing is a syntactically valid logical
761 ;; pathname namestring without an explicit host, then it
762 ;; is parsed as a logical pathname namestring on the
763 ;; host that is the host component of default-pathname."
765 ;; "Otherwise, the parsing of thing is
766 ;; implementation-defined."
768 ;; Both clauses are handled here, as the default
769 ;; *DEFAULT-PATHNAME-DEFAULTS* has a SB-IMPL::UNIX-HOST
771 ((pathname-host defaults)
772 (funcall (host-parse (pathname-host defaults))
776 ;; I don't think we should ever get here, as the default
777 ;; host will always have a non-null HOST, given that we
778 ;; can't create a new pathname without going through
779 ;; *DEFAULT-PATHNAME-DEFAULTS*, which has a non-null
781 (t (bug "Fallen through COND in %PARSE-NAMESTRING")))
782 (when (and host new-host (not (eq new-host host)))
783 (error 'simple-type-error
785 ;; Note: ANSI requires that this be a TYPE-ERROR,
786 ;; but there seems to be no completely correct
787 ;; value to use for TYPE-ERROR-EXPECTED-TYPE.
788 ;; Instead, we return a sort of "type error allowed
789 ;; type", trying to say "it would be OK if you
790 ;; passed NIL as the host value" but not mentioning
791 ;; that a matching string would be OK too.
794 "The host in the namestring, ~S,~@
795 does not match the explicit HOST argument, ~S."
796 :format-arguments (list new-host host)))
797 (let ((pn-host (or new-host host (pathname-host defaults))))
798 (values (%make-maybe-logical-pathname
799 pn-host device directory file type version)
802 ;;; If NAMESTR begins with a colon-terminated, defined, logical host,
803 ;;; then return that host, otherwise return NIL.
804 (defun extract-logical-host-prefix (namestr start end)
805 (declare (type simple-string namestr)
806 (type index start end)
807 (values (or logical-host null)))
808 (let ((colon-pos (position #\: namestr :start start :end end)))
810 (values (gethash (nstring-upcase (subseq namestr start colon-pos))
814 (defun parse-namestring (thing
817 (defaults *default-pathname-defaults*)
818 &key (start 0) end junk-allowed)
819 (declare (type pathname-designator thing defaults)
820 (type (or list host string (member :unspecific)) host)
822 (type (or index null) end)
823 (type (or t null) junk-allowed)
824 (values (or null pathname) (or null index)))
825 (with-host (found-host host)
826 (let (;; According to ANSI defaults may be any valid pathname designator
827 (defaults (etypecase defaults
831 (aver (pathnamep *default-pathname-defaults*))
832 (parse-namestring defaults))
834 (truename defaults)))))
835 (declare (type pathname defaults))
838 (%parse-namestring thing found-host defaults start end junk-allowed))
840 (%parse-namestring (coerce thing 'simple-string)
841 found-host defaults start end junk-allowed))
843 (let ((defaulted-host (or found-host (%pathname-host defaults))))
844 (declare (type host defaulted-host))
845 (unless (eq defaulted-host (%pathname-host thing))
846 (error "The HOST argument doesn't match the pathname host:~% ~
848 defaulted-host (%pathname-host thing))))
849 (values thing start))
851 (let ((name (file-name thing)))
853 (error "can't figure out the file associated with stream:~% ~S"
855 (values name nil)))))))
857 (defun %parse-native-namestring (namestr host defaults start end junk-allowed
859 (declare (type (or host null) host)
860 (type string namestr)
862 (type (or index null) end))
866 (%parse-namestring namestr host defaults start end nil)
867 (namestring-parse-error (condition)
868 (values nil (namestring-parse-error-offset condition)))))
870 (let* ((end (%check-vector-sequence-bounds namestr start end)))
871 (multiple-value-bind (new-host device directory file type version)
874 (funcall (host-parse-native host) namestr start end as-directory))
875 ((pathname-host defaults)
876 (funcall (host-parse-native (pathname-host defaults))
881 ;; I don't think we should ever get here, as the default
882 ;; host will always have a non-null HOST, given that we
883 ;; can't create a new pathname without going through
884 ;; *DEFAULT-PATHNAME-DEFAULTS*, which has a non-null
886 (t (bug "Fallen through COND in %PARSE-NAMESTRING")))
887 (when (and host new-host (not (eq new-host host)))
888 (error 'simple-type-error
890 :expected-type `(or null (eql ,host))
892 "The host in the namestring, ~S,~@
893 does not match the explicit HOST argument, ~S."
894 :format-arguments (list new-host host)))
895 (let ((pn-host (or new-host host (pathname-host defaults))))
896 (values (%make-pathname
897 pn-host device directory file type version)
900 (defun parse-native-namestring (thing
903 (defaults *default-pathname-defaults*)
904 &key (start 0) end junk-allowed
907 "Convert THING into a pathname, using the native conventions
908 appropriate for the pathname host HOST, or if not specified the
909 host of DEFAULTS. If THING is a string, the parse is bounded by
910 START and END, and error behaviour is controlled by JUNK-ALLOWED,
911 as with PARSE-NAMESTRING. For file systems whose native
912 conventions allow directories to be indicated as files, if
913 AS-DIRECTORY is true, return a pathname denoting THING as a
915 (declare (type pathname-designator thing defaults)
916 (type (or list host string (member :unspecific)) host)
918 (type (or index null) end)
919 (type (or t null) junk-allowed)
920 (values (or null pathname) (or null index)))
921 (with-host (found-host host)
922 (let ((defaults (etypecase defaults
926 (aver (pathnamep *default-pathname-defaults*))
927 (parse-native-namestring defaults))
929 (truename defaults)))))
930 (declare (type pathname defaults))
933 (%parse-native-namestring
934 thing found-host defaults start end junk-allowed as-directory))
936 (%parse-native-namestring (coerce thing 'simple-string)
937 found-host defaults start end junk-allowed
940 (let ((defaulted-host (or found-host (%pathname-host defaults))))
941 (declare (type host defaulted-host))
942 (unless (eq defaulted-host (%pathname-host thing))
943 (error "The HOST argument doesn't match the pathname host:~% ~
945 defaulted-host (%pathname-host thing))))
946 (values thing start))
949 (let ((name (file-name thing)))
951 (error "can't figure out the file associated with stream:~% ~S"
953 (values name nil)))))))
955 (defun namestring (pathname)
957 "Construct the full (name)string form of the pathname."
958 (declare (type pathname-designator pathname))
959 (with-pathname (pathname pathname)
961 (let ((host (%pathname-host pathname)))
963 (error "can't determine the namestring for pathnames with no ~
964 host:~% ~S" pathname))
965 (funcall (host-unparse host) pathname)))))
967 (defun native-namestring (pathname &key as-file)
969 "Construct the full native (name)string form of PATHNAME. For
970 file systems whose native conventions allow directories to be
971 indicated as files, if AS-FILE is true and the name, type, and
972 version components of PATHNAME are all NIL or :UNSPECIFIC,
973 construct a string that names the directory according to the file
974 system's syntax for files."
975 (declare (type pathname-designator pathname))
976 (with-native-pathname (pathname pathname)
978 (let ((host (%pathname-host pathname)))
980 (error "can't determine the native namestring for pathnames with no ~
981 host:~% ~S" pathname))
982 (funcall (host-unparse-native host) pathname as-file)))))
984 (defun host-namestring (pathname)
986 "Return a string representation of the name of the host in the pathname."
987 (declare (type pathname-designator pathname))
988 (with-pathname (pathname pathname)
989 (let ((host (%pathname-host pathname)))
991 (funcall (host-unparse-host host) pathname)
993 "can't determine the namestring for pathnames with no host:~% ~S"
996 (defun directory-namestring (pathname)
998 "Return a string representation of the directories used in the pathname."
999 (declare (type pathname-designator pathname))
1000 (with-pathname (pathname pathname)
1001 (let ((host (%pathname-host pathname)))
1003 (funcall (host-unparse-directory host) pathname)
1005 "can't determine the namestring for pathnames with no host:~% ~S"
1008 (defun file-namestring (pathname)
1010 "Return a string representation of the name used in the pathname."
1011 (declare (type pathname-designator pathname))
1012 (with-pathname (pathname pathname)
1013 (let ((host (%pathname-host pathname)))
1015 (funcall (host-unparse-file host) pathname)
1017 "can't determine the namestring for pathnames with no host:~% ~S"
1020 (defun enough-namestring (pathname
1022 (defaults *default-pathname-defaults*))
1024 "Return an abbreviated pathname sufficent to identify the pathname relative
1026 (declare (type pathname-designator pathname))
1027 (with-pathname (pathname pathname)
1028 (let ((host (%pathname-host pathname)))
1030 (with-pathname (defaults defaults)
1031 (funcall (host-unparse-enough host) pathname defaults))
1033 "can't determine the namestring for pathnames with no host:~% ~S"
1038 (defun wild-pathname-p (pathname &optional field-key)
1040 "Predicate for determining whether pathname contains any wildcards."
1041 (declare (type pathname-designator pathname)
1042 (type (member nil :host :device :directory :name :type :version)
1044 (with-pathname (pathname pathname)
1046 (or (pattern-p x) (member x '(:wild :wild-inferiors)))))
1049 (or (wild-pathname-p pathname :host)
1050 (wild-pathname-p pathname :device)
1051 (wild-pathname-p pathname :directory)
1052 (wild-pathname-p pathname :name)
1053 (wild-pathname-p pathname :type)
1054 (wild-pathname-p pathname :version)))
1055 (:host (frob (%pathname-host pathname)))
1056 (:device (frob (%pathname-host pathname)))
1057 (:directory (some #'frob (%pathname-directory pathname)))
1058 (:name (frob (%pathname-name pathname)))
1059 (:type (frob (%pathname-type pathname)))
1060 (:version (frob (%pathname-version pathname)))))))
1062 (defun pathname-match-p (in-pathname in-wildname)
1064 "Pathname matches the wildname template?"
1065 (declare (type pathname-designator in-pathname))
1066 (with-pathname (pathname in-pathname)
1067 (with-pathname (wildname in-wildname)
1068 (macrolet ((frob (field &optional (op 'components-match))
1069 `(or (null (,field wildname))
1070 (,op (,field pathname) (,field wildname)))))
1071 (and (or (null (%pathname-host wildname))
1072 (eq (%pathname-host wildname) (%pathname-host pathname)))
1073 (frob %pathname-device)
1074 (frob %pathname-directory directory-components-match)
1075 (frob %pathname-name)
1076 (frob %pathname-type)
1077 (or (eq (%pathname-host wildname) *physical-host*)
1078 (frob %pathname-version)))))))
1080 ;;; Place the substitutions into the pattern and return the string or pattern
1081 ;;; that results. If DIDDLE-CASE is true, we diddle the result case as well,
1082 ;;; in case we are translating between hosts with difference conventional case.
1083 ;;; The second value is the tail of subs with all of the values that we used up
1084 ;;; stripped off. Note that PATTERN-MATCHES matches all consecutive wildcards
1085 ;;; as a single string, so we ignore subsequent contiguous wildcards.
1086 (defun substitute-into (pattern subs diddle-case)
1087 (declare (type pattern pattern)
1089 (values (or simple-string pattern) list))
1090 (let ((in-wildcard nil)
1093 (dolist (piece (pattern-pieces pattern))
1094 (cond ((simple-string-p piece)
1095 (push piece strings)
1096 (setf in-wildcard nil))
1099 (setf in-wildcard t)
1101 (error "not enough wildcards in FROM pattern to match ~
1104 (let ((sub (pop subs)))
1108 (push (apply #'concatenate 'simple-string
1111 (dolist (piece (pattern-pieces sub))
1112 (push piece pieces)))
1116 (error "can't substitute this into the middle of a word:~
1121 (push (apply #'concatenate 'simple-string (nreverse strings))
1125 (if (and pieces (simple-string-p (car pieces)) (null (cdr pieces)))
1127 (make-pattern (nreverse pieces)))
1131 ;;; Called when we can't see how source and from matched.
1132 (defun didnt-match-error (source from)
1133 (error "Pathname components from SOURCE and FROM args to TRANSLATE-PATHNAME~@
1134 did not match:~% ~S ~S"
1137 ;;; Do TRANSLATE-COMPONENT for all components except host, directory
1139 (defun translate-component (source from to diddle-case)
1146 (if (pattern= from source)
1148 (didnt-match-error source from)))
1150 (multiple-value-bind (won subs) (pattern-matches from source)
1152 (values (substitute-into to subs diddle-case))
1153 (didnt-match-error source from))))
1155 (maybe-diddle-case source diddle-case))))
1157 (values (substitute-into to (list source) diddle-case)))
1159 (if (components-match source from)
1160 (maybe-diddle-case source diddle-case)
1161 (didnt-match-error source from)))))
1163 (maybe-diddle-case source diddle-case))
1165 (if (components-match source from)
1167 (didnt-match-error source from)))))
1169 ;;; Return a list of all the things that we want to substitute into the TO
1170 ;;; pattern (the things matched by from on source.) When From contains
1171 ;;; :WILD-INFERIORS, the result contains a sublist of the matched source
1173 (defun compute-directory-substitutions (orig-source orig-from)
1174 (let ((source orig-source)
1179 (unless (every (lambda (x) (eq x :wild-inferiors)) from)
1180 (didnt-match-error orig-source orig-from))
1183 (unless from (didnt-match-error orig-source orig-from))
1184 (let ((from-part (pop from))
1185 (source-part (pop source)))
1188 (typecase source-part
1190 (if (pattern= from-part source-part)
1192 (didnt-match-error orig-source orig-from)))
1194 (multiple-value-bind (won new-subs)
1195 (pattern-matches from-part source-part)
1197 (dolist (sub new-subs)
1199 (didnt-match-error orig-source orig-from))))
1201 (didnt-match-error orig-source orig-from))))
1204 ((member :wild-inferiors)
1205 (let ((remaining-source (cons source-part source)))
1208 (when (directory-components-match remaining-source from)
1210 (unless remaining-source
1211 (didnt-match-error orig-source orig-from))
1212 (res (pop remaining-source)))
1214 (setq source remaining-source))))
1216 (unless (and (simple-string-p source-part)
1217 (string= from-part source-part))
1218 (didnt-match-error orig-source orig-from)))
1220 (didnt-match-error orig-source orig-from)))))
1223 ;;; This is called by TRANSLATE-PATHNAME on the directory components
1224 ;;; of its argument pathnames to produce the result directory
1225 ;;; component. If this leaves the directory NIL, we return the source
1226 ;;; directory. The :RELATIVE or :ABSOLUTE is taken from the source
1227 ;;; directory, except if TO is :ABSOLUTE, in which case the result
1228 ;;; will be :ABSOLUTE.
1229 (defun translate-directories (source from to diddle-case)
1230 (if (not (and source to from))
1231 (or (and to (null source) (remove :wild-inferiors to))
1232 (mapcar (lambda (x) (maybe-diddle-case x diddle-case)) source))
1234 ;; If TO is :ABSOLUTE, the result should still be :ABSOLUTE.
1235 (res (if (eq (first to) :absolute)
1238 (let ((subs-left (compute-directory-substitutions (rest source)
1240 (dolist (to-part (rest to))
1244 (let ((match (pop subs-left)))
1246 (error ":WILD-INFERIORS is not paired in from and to ~
1247 patterns:~% ~S ~S" from to))
1248 (res (maybe-diddle-case match diddle-case))))
1249 ((member :wild-inferiors)
1251 (let ((match (pop subs-left)))
1252 (unless (listp match)
1253 (error ":WILD-INFERIORS not paired in from and to ~
1254 patterns:~% ~S ~S" from to))
1256 (res (maybe-diddle-case x diddle-case)))))
1258 (multiple-value-bind
1260 (substitute-into to-part subs-left diddle-case)
1261 (setf subs-left new-subs-left)
1263 (t (res to-part)))))
1266 (defun translate-pathname (source from-wildname to-wildname &key)
1268 "Use the source pathname to translate the from-wildname's wild and
1269 unspecified elements into a completed to-pathname based on the to-wildname."
1270 (declare (type pathname-designator source from-wildname to-wildname))
1271 (with-pathname (source source)
1272 (with-pathname (from from-wildname)
1273 (with-pathname (to to-wildname)
1274 (let* ((source-host (%pathname-host source))
1275 (from-host (%pathname-host from))
1276 (to-host (%pathname-host to))
1278 (and source-host to-host
1279 (not (eq (host-customary-case source-host)
1280 (host-customary-case to-host))))))
1281 (macrolet ((frob (field &optional (op 'translate-component))
1282 `(let ((result (,op (,field source)
1286 (if (eq result :error)
1287 (error "~S doesn't match ~S." source from)
1289 (%make-maybe-logical-pathname
1290 (or to-host source-host)
1291 (frob %pathname-device)
1292 (frob %pathname-directory translate-directories)
1293 (frob %pathname-name)
1294 (frob %pathname-type)
1295 (if (eq from-host *unix-host*)
1296 (if (or (eq (%pathname-version to) :wild)
1297 (eq (%pathname-version to) nil))
1298 (%pathname-version source)
1299 (%pathname-version to))
1300 (frob %pathname-version)))))))))
1302 ;;;; logical pathname support. ANSI 92-102 specification.
1304 ;;;; As logical-pathname translations are loaded they are
1305 ;;;; canonicalized as patterns to enable rapid efficient translation
1306 ;;;; into physical pathnames.
1310 (defun simplify-namestring (namestring &optional host)
1311 (funcall (host-simplify-namestring
1313 (pathname-host (sane-default-pathname-defaults))))
1316 ;;; Canonicalize a logical pathname word by uppercasing it checking that it
1317 ;;; contains only legal characters.
1318 (defun logical-word-or-lose (word)
1319 (declare (string word))
1320 (when (string= word "")
1321 (error 'namestring-parse-error
1322 :complaint "Attempted to treat invalid logical hostname ~
1323 as a logical host:~% ~S"
1325 :namestring word :offset 0))
1326 (let ((word (string-upcase word)))
1327 (dotimes (i (length word))
1328 (let ((ch (schar word i)))
1329 (unless (and (typep ch 'standard-char)
1330 (or (alpha-char-p ch) (digit-char-p ch) (char= ch #\-)))
1331 (error 'namestring-parse-error
1332 :complaint "logical namestring character which ~
1333 is not alphanumeric or hyphen:~% ~S"
1335 :namestring word :offset i))))
1336 (coerce word 'string))) ; why not simple-string?
1338 ;;; Given a logical host or string, return a logical host. If ERROR-P
1339 ;;; is NIL, then return NIL when no such host exists.
1340 (defun find-logical-host (thing &optional (errorp t))
1343 (let ((found (gethash (logical-word-or-lose thing)
1345 (if (or found (not errorp))
1347 ;; This is the error signalled from e.g.
1348 ;; LOGICAL-PATHNAME-TRANSLATIONS when host is not a defined
1349 ;; host, and ANSI specifies that that's a TYPE-ERROR.
1350 (error 'simple-type-error
1352 ;; God only knows what ANSI expects us to use for
1353 ;; the EXPECTED-TYPE here. Maybe this will be OK..
1355 '(and string (satisfies logical-pathname-translations))
1356 :format-control "logical host not yet defined: ~S"
1357 :format-arguments (list thing)))))
1358 (logical-host thing)))
1360 ;;; Given a logical host name or host, return a logical host, creating
1361 ;;; a new one if necessary.
1362 (defun intern-logical-host (thing)
1363 (declare (values logical-host))
1364 (with-locked-system-table (*logical-hosts*)
1365 (or (find-logical-host thing nil)
1366 (let* ((name (logical-word-or-lose thing))
1367 (new (make-logical-host :name name)))
1368 (setf (gethash name *logical-hosts*) new)
1371 ;;;; logical pathname parsing
1373 ;;; Deal with multi-char wildcards in a logical pathname token.
1374 (defun maybe-make-logical-pattern (namestring chunks)
1375 (let ((chunk (caar chunks)))
1376 (collect ((pattern))
1378 (len (length chunk)))
1379 (declare (fixnum last-pos))
1381 (when (= last-pos len) (return))
1382 (let ((pos (or (position #\* chunk :start last-pos) len)))
1383 (if (= pos last-pos)
1385 (error 'namestring-parse-error
1386 :complaint "double asterisk inside of logical ~
1389 :namestring namestring
1390 :offset (+ (cdar chunks) pos)))
1391 (pattern (subseq chunk last-pos pos)))
1394 (pattern :multi-char-wild))
1395 (setq last-pos (1+ pos)))))
1398 (make-pattern (pattern))
1399 (let ((x (car (pattern))))
1400 (if (eq x :multi-char-wild)
1404 ;;; Return a list of conses where the CDR is the start position and
1405 ;;; the CAR is a string (token) or character (punctuation.)
1406 (defun logical-chunkify (namestr start end)
1408 (do ((i start (1+ i))
1412 (chunks (cons (nstring-upcase (subseq namestr prev end)) prev))))
1413 (let ((ch (schar namestr i)))
1414 (unless (or (alpha-char-p ch) (digit-char-p ch)
1415 (member ch '(#\- #\*)))
1417 (chunks (cons (nstring-upcase (subseq namestr prev i)) prev)))
1419 (unless (member ch '(#\; #\: #\.))
1420 (error 'namestring-parse-error
1421 :complaint "illegal character for logical pathname:~% ~S"
1425 (chunks (cons ch i)))))
1428 ;;; Break up a logical-namestring, always a string, into its
1429 ;;; constituent parts.
1430 (defun parse-logical-namestring (namestr start end)
1431 (declare (type simple-string namestr)
1432 (type index start end))
1433 (collect ((directory))
1438 (labels ((expecting (what chunks)
1439 (unless (and chunks (simple-string-p (caar chunks)))
1440 (error 'namestring-parse-error
1441 :complaint "expecting ~A, got ~:[nothing~;~S~]."
1442 :args (list what (caar chunks) (caar chunks))
1444 :offset (if chunks (cdar chunks) end)))
1446 (parse-host (chunks)
1447 (case (caadr chunks)
1450 (find-logical-host (expecting "a host name" chunks)))
1451 (parse-relative (cddr chunks)))
1453 (parse-relative chunks))))
1454 (parse-relative (chunks)
1457 (directory :relative)
1458 (parse-directory (cdr chunks)))
1460 (directory :absolute) ; Assumption! Maybe revoked later.
1461 (parse-directory chunks))))
1462 (parse-directory (chunks)
1463 (case (caadr chunks)
1466 (let ((res (expecting "a directory name" chunks)))
1467 (cond ((string= res "..") :up)
1468 ((string= res "**") :wild-inferiors)
1470 (maybe-make-logical-pattern namestr chunks)))))
1471 (parse-directory (cddr chunks)))
1473 (parse-name chunks))))
1474 (parse-name (chunks)
1476 (expecting "a file name" chunks)
1477 (setq name (maybe-make-logical-pattern namestr chunks))
1478 (expecting-dot (cdr chunks))))
1479 (expecting-dot (chunks)
1481 (unless (eql (caar chunks) #\.)
1482 (error 'namestring-parse-error
1483 :complaint "expecting a dot, got ~S."
1484 :args (list (caar chunks))
1486 :offset (cdar chunks)))
1488 (parse-version (cdr chunks))
1489 (parse-type (cdr chunks)))))
1490 (parse-type (chunks)
1491 (expecting "a file type" chunks)
1492 (setq type (maybe-make-logical-pattern namestr chunks))
1493 (expecting-dot (cdr chunks)))
1494 (parse-version (chunks)
1495 (let ((str (expecting "a positive integer, * or NEWEST"
1498 ((string= str "*") (setq version :wild))
1499 ((string= str "NEWEST") (setq version :newest))
1501 (multiple-value-bind (res pos)
1502 (parse-integer str :junk-allowed t)
1503 (unless (and res (plusp res))
1504 (error 'namestring-parse-error
1505 :complaint "expected a positive integer, ~
1509 :offset (+ pos (cdar chunks))))
1510 (setq version res)))))
1512 (error 'namestring-parse-error
1513 :complaint "extra stuff after end of file name"
1515 :offset (cdadr chunks)))))
1516 (parse-host (logical-chunkify namestr start end)))
1517 (values host :unspecific (directory) name type version))))
1519 ;;; We can't initialize this yet because not all host methods are
1521 (defvar *logical-pathname-defaults*)
1523 (defun logical-namestring-p (x)
1526 (typep (pathname x) 'logical-pathname))))
1528 (deftype logical-namestring ()
1529 `(satisfies logical-namestring-p))
1531 (defun logical-pathname (pathspec)
1533 "Converts the pathspec argument to a logical-pathname and returns it."
1534 (declare (type (or logical-pathname string stream) pathspec)
1535 (values logical-pathname))
1536 (if (typep pathspec 'logical-pathname)
1538 (flet ((oops (problem)
1539 (error 'simple-type-error
1541 :expected-type 'logical-namestring
1542 :format-control "~S is not a valid logical namestring:~% ~A"
1543 :format-arguments (list pathspec problem))))
1544 (let ((res (handler-case
1545 (parse-namestring pathspec nil *logical-pathname-defaults*)
1546 (error (e) (oops e)))))
1547 (when (eq (%pathname-host res)
1548 (%pathname-host *logical-pathname-defaults*))
1549 (oops "no host specified"))
1552 ;;;; logical pathname unparsing
1554 (defun unparse-logical-directory (pathname)
1555 (declare (type pathname pathname))
1557 (let ((directory (%pathname-directory pathname)))
1559 (ecase (pop directory)
1560 (:absolute) ; nothing special
1561 (:relative (pieces ";")))
1562 (dolist (dir directory)
1563 (cond ((or (stringp dir) (pattern-p dir))
1564 (pieces (unparse-logical-piece dir))
1568 ((eq dir :wild-inferiors)
1571 (error "invalid directory component: ~S" dir))))))
1572 (apply #'concatenate 'simple-string (pieces))))
1574 (defun unparse-logical-piece (thing)
1576 ((member :wild) "*")
1577 (simple-string thing)
1579 (collect ((strings))
1580 (dolist (piece (pattern-pieces thing))
1582 (simple-string (strings piece))
1584 (cond ((eq piece :wild-inferiors)
1586 ((eq piece :multi-char-wild)
1588 (t (error "invalid keyword: ~S" piece))))))
1589 (apply #'concatenate 'simple-string (strings))))))
1591 (defun unparse-logical-file (pathname)
1592 (declare (type pathname pathname))
1593 (collect ((strings))
1594 (let* ((name (%pathname-name pathname))
1595 (type (%pathname-type pathname))
1596 (version (%pathname-version pathname))
1597 (type-supplied (not (or (null type) (eq type :unspecific))))
1598 (version-supplied (not (or (null version)
1599 (eq version :unspecific)))))
1601 (when (and (null type)
1602 (typep name 'string)
1603 (position #\. name :start 1))
1604 (error "too many dots in the name: ~S" pathname))
1605 (strings (unparse-logical-piece name)))
1608 (error "cannot specify the type without a file: ~S" pathname))
1609 (when (typep type 'string)
1610 (when (position #\. type)
1611 (error "type component can't have a #\. inside: ~S" pathname)))
1613 (strings (unparse-logical-piece type)))
1614 (when version-supplied
1615 (unless type-supplied
1616 (error "cannot specify the version without a type: ~S" pathname))
1618 ((member :newest) (strings ".NEWEST"))
1619 ((member :wild) (strings ".*"))
1620 (fixnum (strings ".") (strings (format nil "~D" version))))))
1621 (apply #'concatenate 'simple-string (strings))))
1623 ;;; Unparse a logical pathname string.
1624 (defun unparse-enough-namestring (pathname defaults)
1625 (let* ((path-directory (pathname-directory pathname))
1626 (def-directory (pathname-directory defaults))
1628 ;; Go down the directory lists to see what matches. What's
1629 ;; left is what we want, more or less.
1630 (cond ((and (eq (first path-directory) (first def-directory))
1631 (eq (first path-directory) :absolute))
1632 ;; Both paths are :ABSOLUTE, so find where the
1633 ;; common parts end and return what's left
1634 (do* ((p (rest path-directory) (rest p))
1635 (d (rest def-directory) (rest d)))
1636 ((or (endp p) (endp d)
1637 (not (equal (first p) (first d))))
1640 ;; At least one path is :RELATIVE, so just return the
1641 ;; original path. If the original path is :RELATIVE,
1642 ;; then that's the right one. If PATH-DIRECTORY is
1643 ;; :ABSOLUTE, we want to return that except when
1644 ;; DEF-DIRECTORY is :ABSOLUTE, as handled above. so return
1645 ;; the original directory.
1647 (unparse-logical-namestring
1648 (make-pathname :host (pathname-host pathname)
1649 :directory enough-directory
1650 :name (pathname-name pathname)
1651 :type (pathname-type pathname)
1652 :version (pathname-version pathname)))))
1654 (defun unparse-logical-namestring (pathname)
1655 (declare (type logical-pathname pathname))
1656 (concatenate 'simple-string
1657 (logical-host-name (%pathname-host pathname)) ":"
1658 (unparse-logical-directory pathname)
1659 (unparse-logical-file pathname)))
1661 ;;;; logical pathname translations
1663 ;;; Verify that the list of translations consists of lists and prepare
1664 ;;; canonical translations. (Parse pathnames and expand out wildcards
1666 (defun canonicalize-logical-pathname-translations (translation-list host)
1667 (declare (type list translation-list) (type host host)
1669 (mapcar (lambda (translation)
1670 (destructuring-bind (from to) translation
1671 (list (if (typep from 'logical-pathname)
1673 (parse-namestring from host))
1677 (defun logical-pathname-translations (host)
1679 "Return the (logical) host object argument's list of translations."
1680 (declare (type (or string logical-host) host)
1682 (logical-host-translations (find-logical-host host)))
1684 (defun (setf logical-pathname-translations) (translations host)
1686 "Set the translations list for the logical host argument."
1687 (declare (type (or string logical-host) host)
1688 (type list translations)
1690 (let ((host (intern-logical-host host)))
1691 (setf (logical-host-canon-transls host)
1692 (canonicalize-logical-pathname-translations translations host))
1693 (setf (logical-host-translations host) translations)))
1695 (defun translate-logical-pathname (pathname &key)
1697 "Translate PATHNAME to a physical pathname, which is returned."
1698 (declare (type pathname-designator pathname)
1699 (values (or null pathname)))
1702 (dolist (x (logical-host-canon-transls (%pathname-host pathname))
1703 (error 'simple-file-error
1705 :format-control "no translation for ~S"
1706 :format-arguments (list pathname)))
1707 (destructuring-bind (from to) x
1708 (when (pathname-match-p pathname from)
1709 (return (translate-logical-pathname
1710 (translate-pathname pathname from to)))))))
1712 (t (translate-logical-pathname (pathname pathname)))))
1714 (defvar *logical-pathname-defaults*
1715 (%make-logical-pathname
1716 (make-logical-host :name (logical-word-or-lose "BOGUS"))
1717 :unspecific nil nil nil nil))
1719 (defun load-logical-pathname-translations (host)
1721 "Reads logical pathname translations from SYS:SITE;HOST.TRANSLATIONS.NEWEST,
1722 with HOST replaced by the supplied parameter. Returns T on success.
1724 If HOST is already defined as logical pathname host, no file is loaded and NIL
1727 The file should contain a single form, suitable for use with
1728 \(SETF LOGICAL-PATHNAME-TRANSLATIONS).
1730 Note: behaviour of this function is higly implementation dependent, and
1731 historically it used to be a no-op in SBcL -- the current approach is somewhat
1732 experimental and subject to change."
1733 (declare (type string host)
1734 (values (member t nil)))
1735 (if (find-logical-host host nil)
1736 ;; This host is already defined, all is well and good.
1738 ;; ANSI: "The specific nature of the search is
1739 ;; implementation-defined."
1741 (setf (logical-pathname-translations host)
1742 (with-open-file (lpt (make-pathname :host "SYS"
1743 :directory '(:absolute "SITE")
1745 :type "TRANSLATIONS"
1749 (defun !pathname-cold-init ()
1750 (let* ((sys *default-pathname-defaults*)
1753 (make-pathname :directory '(:relative "src" :wild-inferiors)
1754 :name :wild :type :wild)
1758 (make-pathname :directory '(:relative "contrib" :wild-inferiors)
1759 :name :wild :type :wild)
1763 (make-pathname :directory '(:relative "output" :wild-inferiors)
1764 :name :wild :type :wild)
1766 (setf (logical-pathname-translations "SYS")
1767 `(("SYS:SRC;**;*.*.*" ,src)
1768 ("SYS:CONTRIB;**;*.*.*" ,contrib)
1769 ("SYS:OUTPUT;**;*.*.*" ,output)))))