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-unix-directory)
27 (unparse-file #'unparse-unix-file)
28 (unparse-enough #'unparse-unix-enough)
29 (unparse-directory-separator "/")
30 (customary-case :lower))))
31 (defvar *unix-host* (make-unix-host))
32 (defun make-unix-host-load-form (host)
33 (declare (ignore host))
36 (def!struct (win32-host
37 (:make-load-form-fun make-win32-host-load-form)
39 (parse #'parse-win32-namestring)
40 (parse-native #'parse-native-win32-namestring)
41 (unparse #'unparse-win32-namestring)
42 (unparse-native #'unparse-native-win32-namestring)
43 (unparse-host #'unparse-win32-host)
44 (unparse-directory #'unparse-win32-directory)
45 (unparse-file #'unparse-win32-file)
46 (unparse-enough #'unparse-win32-enough)
47 (unparse-directory-separator "\\")
48 (customary-case :upper))))
49 (defvar *win32-host* (make-win32-host))
50 (defun make-win32-host-load-form (host)
51 (declare (ignore host))
54 (defvar *physical-host*
56 #!+win32 *win32-host*)
58 ;;; Return a value suitable, e.g., for preinitializing
59 ;;; *DEFAULT-PATHNAME-DEFAULTS* before *DEFAULT-PATHNAME-DEFAULTS* is
60 ;;; initialized (at which time we can't safely call e.g. #'PATHNAME).
61 (defun make-trivial-default-pathname ()
62 (%make-pathname *physical-host* nil nil nil nil :newest))
66 (def!method print-object ((pathname pathname) stream)
67 (let ((namestring (handler-case (namestring pathname)
71 (if (or *print-readably* *print-escape*)
74 (coerce namestring '(simple-array character (*))))
75 (print-unreadable-object (pathname stream :type t)
77 "~@<(with no namestring) ~_:HOST ~S ~_:DEVICE ~S ~_:DIRECTORY ~S ~
78 ~_:NAME ~S ~_:TYPE ~S ~_:VERSION ~S~:>"
79 (%pathname-host pathname)
80 (%pathname-device pathname)
81 (%pathname-directory pathname)
82 (%pathname-name pathname)
83 (%pathname-type pathname)
84 (%pathname-version pathname))))))
86 (def!method make-load-form ((pathname pathname) &optional environment)
87 (make-load-form-saving-slots pathname :environment environment))
89 ;;; A pathname is logical if the host component is a logical host.
90 ;;; This constructor is used to make an instance of the correct type
91 ;;; from parsed arguments.
92 (defun %make-maybe-logical-pathname (host device directory name type version)
93 ;; We canonicalize logical pathname components to uppercase. ANSI
94 ;; doesn't strictly require this, leaving it up to the implementor;
95 ;; but the arguments given in the X3J13 cleanup issue
96 ;; PATHNAME-LOGICAL:ADD seem compelling: we should canonicalize the
97 ;; case, and uppercase is the ordinary way to do that.
98 (flet ((upcase-maybe (x) (typecase x (string (logical-word-or-lose x)) (t x))))
99 (if (typep host 'logical-host)
100 (%make-logical-pathname host
102 (mapcar #'upcase-maybe directory)
107 (aver (eq host *physical-host*))
108 (%make-pathname host device directory name type version)))))
110 ;;; Hash table searching maps a logical pathname's host to its
111 ;;; physical pathname translation.
112 (defvar *logical-hosts* (make-hash-table :test 'equal))
116 (def!method make-load-form ((pattern pattern) &optional environment)
117 (make-load-form-saving-slots pattern :environment environment))
119 (def!method print-object ((pattern pattern) stream)
120 (print-unreadable-object (pattern stream :type t)
122 (let ((*print-escape* t))
123 (pprint-fill stream (pattern-pieces pattern) nil))
124 (prin1 (pattern-pieces pattern) stream))))
126 (defun pattern= (pattern1 pattern2)
127 (declare (type pattern pattern1 pattern2))
128 (let ((pieces1 (pattern-pieces pattern1))
129 (pieces2 (pattern-pieces pattern2)))
130 (and (= (length pieces1) (length pieces2))
131 (every (lambda (piece1 piece2)
134 (and (simple-string-p piece2)
135 (string= piece1 piece2)))
138 (eq (car piece1) (car piece2))
139 (string= (cdr piece1) (cdr piece2))))
141 (eq piece1 piece2))))
145 ;;; If the string matches the pattern returns the multiple values T
146 ;;; and a list of the matched strings.
147 (defun pattern-matches (pattern string)
148 (declare (type pattern pattern)
149 (type simple-string string))
150 (let ((len (length string)))
151 (labels ((maybe-prepend (subs cur-sub chars)
153 (let* ((len (length chars))
154 (new (make-string len))
157 (setf (schar new (decf index)) char))
160 (matches (pieces start subs cur-sub chars)
163 (values t (maybe-prepend subs cur-sub chars))
165 (let ((piece (car pieces)))
168 (let ((end (+ start (length piece))))
170 (string= piece string
171 :start2 start :end2 end)
172 (matches (cdr pieces) end
173 (maybe-prepend subs cur-sub chars)
179 (let ((char (schar string start)))
180 (if (find char (cdr piece) :test #'char=)
181 (matches (cdr pieces) (1+ start) subs t
182 (cons char chars))))))))
183 ((member :single-char-wild)
185 (matches (cdr pieces) (1+ start) subs t
186 (cons (schar string start) chars))))
187 ((member :multi-char-wild)
188 (multiple-value-bind (won new-subs)
189 (matches (cdr pieces) start subs t chars)
193 (matches pieces (1+ start) subs t
194 (cons (schar string start)
196 (multiple-value-bind (won subs)
197 (matches (pattern-pieces pattern) 0 nil nil nil)
198 (values won (reverse subs))))))
200 ;;; PATHNAME-MATCH-P for directory components
201 (defun directory-components-match (thing wild)
204 ;; If THING has a null directory, assume that it matches
205 ;; (:ABSOLUTE :WILD-INFERIORS) or (:RELATIVE :WILD-INFERIORS).
208 (member (first wild) '(:absolute :relative))
209 (eq (second wild) :wild-inferiors))
211 (let ((wild1 (first wild)))
212 (if (eq wild1 :wild-inferiors)
213 (let ((wild-subdirs (rest wild)))
214 (or (null wild-subdirs)
216 (when (directory-components-match thing wild-subdirs)
219 (unless thing (return nil)))))
221 (components-match (first thing) wild1)
222 (directory-components-match (rest thing)
225 ;;; Return true if pathname component THING is matched by WILD. (not
227 (defun components-match (thing wild)
228 (declare (type (or pattern symbol simple-string integer) thing wild))
233 ;; String is matched by itself, a matching pattern or :WILD.
236 (values (pattern-matches wild thing)))
238 (string= thing wild))))
240 ;; A pattern is only matched by an identical pattern.
241 (and (pattern-p wild) (pattern= thing wild)))
243 ;; An integer (version number) is matched by :WILD or the
244 ;; same integer. This branch will actually always be NIL as
245 ;; long as the version is a fixnum.
248 ;;; a predicate for comparing two pathname slot component sub-entries
249 (defun compare-component (this that)
253 (and (simple-string-p that)
254 (string= this that)))
256 (and (pattern-p that)
257 (pattern= this that)))
260 (compare-component (car this) (car that))
261 (compare-component (cdr this) (cdr that)))))))
263 ;;;; pathname functions
265 (defun pathname= (pathname1 pathname2)
266 (declare (type pathname pathname1)
267 (type pathname pathname2))
268 (and (eq (%pathname-host pathname1)
269 (%pathname-host pathname2))
270 (compare-component (%pathname-device pathname1)
271 (%pathname-device pathname2))
272 (compare-component (%pathname-directory pathname1)
273 (%pathname-directory pathname2))
274 (compare-component (%pathname-name pathname1)
275 (%pathname-name pathname2))
276 (compare-component (%pathname-type pathname1)
277 (%pathname-type pathname2))
278 (or (eq (%pathname-host pathname1) *unix-host*)
279 (compare-component (%pathname-version pathname1)
280 (%pathname-version pathname2)))))
282 ;;; Convert PATHNAME-DESIGNATOR (a pathname, or string, or
283 ;;; stream), into a pathname in pathname.
285 ;;; FIXME: was rewritten, should be tested (or rewritten again, this
286 ;;; time using ONCE-ONLY, *then* tested)
287 ;;; FIXME: become SB!XC:DEFMACRO inside EVAL-WHEN (COMPILE EVAL)?
288 (defmacro with-pathname ((pathname pathname-designator) &body body)
289 (let ((pd0 (gensym)))
290 `(let* ((,pd0 ,pathname-designator)
291 (,pathname (etypecase ,pd0
293 (string (parse-namestring ,pd0))
294 (file-stream (file-name ,pd0)))))
297 (defmacro with-native-pathname ((pathname pathname-designator) &body body)
298 (let ((pd0 (gensym)))
299 `(let* ((,pd0 ,pathname-designator)
300 (,pathname (etypecase ,pd0
302 (string (parse-native-namestring ,pd0))
305 (file-stream (file-name ,pd0)))))
308 (defmacro with-host ((host host-designator) &body body)
309 ;; Generally, redundant specification of information in software,
310 ;; whether in code or in comments, is bad. However, the ANSI spec
311 ;; for this is messy enough that it's hard to hold in short-term
312 ;; memory, so I've recorded these redundant notes on the
313 ;; implications of the ANSI spec.
315 ;; According to the ANSI spec, HOST can be a valid pathname host, or
316 ;; a logical host, or NIL.
318 ;; A valid pathname host can be a valid physical pathname host or a
319 ;; valid logical pathname host.
321 ;; A valid physical pathname host is "any of a string, a list of
322 ;; strings, or the symbol :UNSPECIFIC, that is recognized by the
323 ;; implementation as the name of a host". In SBCL as of 0.6.9.8,
324 ;; that means :UNSPECIFIC: though someday we might want to
325 ;; generalize it to allow strings like "RTFM.MIT.EDU" or lists like
326 ;; '("RTFM" "MIT" "EDU"), that's not supported now.
328 ;; A valid logical pathname host is a string which has been defined as
329 ;; the name of a logical host, as with LOAD-LOGICAL-PATHNAME-TRANSLATIONS.
331 ;; A logical host is an object of implementation-dependent nature. In
332 ;; SBCL, it's a member of the HOST class (a subclass of STRUCTURE-OBJECT).
333 (let ((hd0 (gensym)))
334 `(let* ((,hd0 ,host-designator)
335 (,host (etypecase ,hd0
337 ;; This is a special host. It's not valid as a
338 ;; logical host, so it is a sensible thing to
339 ;; designate the physical host object. So we do
343 ;; In general ANSI-compliant Common Lisps, a
344 ;; string might also be a physical pathname
345 ;; host, but ANSI leaves this up to the
346 ;; implementor, and in SBCL we don't do it, so
347 ;; it must be a logical host.
348 (find-logical-host ,hd0))
349 ((or null (member :unspecific))
350 ;; CLHS says that HOST=:UNSPECIFIC has
351 ;; implementation-defined behavior. We
352 ;; just turn it into NIL.
355 ;; ANSI also allows LISTs to designate hosts,
356 ;; but leaves its interpretation
357 ;; implementation-defined. Our interpretation
358 ;; is that it's unsupported.:-|
359 (error "A LIST representing a pathname host is not ~
360 supported in this implementation:~% ~S"
365 (defun find-host (host-designator &optional (errorp t))
366 (with-host (host host-designator)
367 (when (and errorp (not host))
368 (error "Couldn't find host: ~S" host-designator))
371 (defun pathname (pathspec)
373 "Convert PATHSPEC (a pathname designator) into a pathname."
374 (declare (type pathname-designator pathspec))
375 (with-pathname (pathname pathspec)
378 (defun native-pathname (pathspec)
380 "Convert PATHSPEC (a pathname designator) into a pathname, assuming
381 the operating system native pathname conventions."
382 (with-native-pathname (pathname pathspec)
385 ;;; Change the case of thing if DIDDLE-P.
386 (defun maybe-diddle-case (thing diddle-p)
387 (if (and diddle-p (not (or (symbolp thing) (integerp thing))))
388 (labels ((check-for (pred in)
391 (dolist (piece (pattern-pieces in))
392 (when (typecase piece
394 (check-for pred piece))
398 (check-for pred (cdr piece))))))
402 (when (check-for pred x)
405 (dotimes (i (length in))
406 (when (funcall pred (schar in i))
409 (diddle-with (fun thing)
413 (mapcar (lambda (piece)
421 (funcall fun (cdr piece))))
426 (pattern-pieces thing))))
433 (let ((any-uppers (check-for #'upper-case-p thing))
434 (any-lowers (check-for #'lower-case-p thing)))
435 (cond ((and any-uppers any-lowers)
436 ;; mixed case, stays the same
439 ;; all uppercase, becomes all lower case
440 (diddle-with (lambda (x) (if (stringp x)
444 ;; all lowercase, becomes all upper case
445 (diddle-with (lambda (x) (if (stringp x)
449 ;; no letters? I guess just leave it.
453 (defun merge-directories (dir1 dir2 diddle-case)
454 (if (or (eq (car dir1) :absolute)
459 (if (and (eq dir :back)
461 (not (member (car results)
462 '(:back :wild-inferiors :relative :absolute))))
464 (push dir results))))
465 (dolist (dir (maybe-diddle-case dir2 diddle-case))
467 (dolist (dir (cdr dir1))
471 (defun merge-pathnames (pathname
473 (defaults *default-pathname-defaults*)
474 (default-version :newest))
476 "Construct a filled in pathname by completing the unspecified components
478 (declare (type pathname-designator pathname)
479 (type pathname-designator defaults)
481 (with-pathname (defaults defaults)
482 (let ((pathname (let ((*default-pathname-defaults* defaults))
483 (pathname pathname))))
484 (let* ((default-host (%pathname-host defaults))
485 (pathname-host (%pathname-host pathname))
487 (and default-host pathname-host
488 (not (eq (host-customary-case default-host)
489 (host-customary-case pathname-host))))))
490 (%make-maybe-logical-pathname
491 (or pathname-host default-host)
492 (or (%pathname-device pathname)
493 (maybe-diddle-case (%pathname-device defaults)
495 (merge-directories (%pathname-directory pathname)
496 (%pathname-directory defaults)
498 (or (%pathname-name pathname)
499 (maybe-diddle-case (%pathname-name defaults)
501 (or (%pathname-type pathname)
502 (maybe-diddle-case (%pathname-type defaults)
504 (or (%pathname-version pathname)
505 (and (not (%pathname-name pathname)) (%pathname-version defaults))
506 default-version))))))
508 (defun import-directory (directory diddle-case)
511 ((member :wild) '(:absolute :wild-inferiors))
512 ((member :unspecific) '(:relative))
515 (results (pop directory))
516 (dolist (piece directory)
517 (cond ((member piece '(:wild :wild-inferiors :up :back))
519 ((or (simple-string-p piece) (pattern-p piece))
520 (results (maybe-diddle-case piece diddle-case)))
522 (results (maybe-diddle-case (coerce piece 'simple-string)
525 (error "~S is not allowed as a directory component." piece))))
529 ,(maybe-diddle-case directory diddle-case)))
532 ,(maybe-diddle-case (coerce directory 'simple-string)
535 (defun make-pathname (&key host
540 (version nil versionp)
544 "Makes a new pathname from the component arguments. Note that host is
545 a host-structure or string."
546 (declare (type (or string host pathname-component-tokens) host)
547 (type (or string pathname-component-tokens) device)
548 (type (or list string pattern pathname-component-tokens) directory)
549 (type (or string pattern pathname-component-tokens) name type)
550 (type (or integer pathname-component-tokens (member :newest))
552 (type (or pathname-designator null) defaults)
553 (type (member :common :local) case))
554 (let* ((defaults (when defaults
555 (with-pathname (defaults defaults) defaults)))
556 (default-host (if defaults
557 (%pathname-host defaults)
558 (pathname-host *default-pathname-defaults*)))
559 ;; Raymond Toy writes: CLHS says make-pathname can take a
560 ;; string (as a logical-host) for the host part. We map that
561 ;; string into the corresponding logical host structure.
563 ;; Paul Werkowski writes:
564 ;; HyperSpec says for the arg to MAKE-PATHNAME;
565 ;; "host---a valid physical pathname host. ..."
566 ;; where it probably means -- a valid pathname host.
567 ;; "valid pathname host n. a valid physical pathname host or
568 ;; a valid logical pathname host."
570 ;; "valid physical pathname host n. any of a string,
571 ;; a list of strings, or the symbol :unspecific,
572 ;; that is recognized by the implementation as the name of a host."
573 ;; "valid logical pathname host n. a string that has been defined
574 ;; as the name of a logical host. ..."
575 ;; HS is silent on what happens if the :HOST arg is NOT one of these.
576 ;; It seems an error message is appropriate.
577 (host (or (find-host host nil) default-host))
578 (diddle-args (and (eq (host-customary-case host) :lower)
581 (not (eq (host-customary-case host)
582 (host-customary-case default-host))))
583 (dev (if devp device (if defaults (%pathname-device defaults))))
584 (dir (import-directory directory diddle-args))
587 (defaults (%pathname-version defaults))
589 (when (and defaults (not dirp))
591 (merge-directories dir
592 (%pathname-directory defaults)
595 (macrolet ((pick (var varp field)
596 `(cond ((or (simple-string-p ,var)
598 (maybe-diddle-case ,var diddle-args))
600 (maybe-diddle-case (coerce ,var 'simple-string)
603 (maybe-diddle-case ,var diddle-args))
605 (maybe-diddle-case (,field defaults)
609 (%make-maybe-logical-pathname host
610 dev ; forced to :UNSPECIFIC when logical
612 (pick name namep %pathname-name)
613 (pick type typep %pathname-type)
616 (defun pathname-host (pathname &key (case :local))
618 "Return PATHNAME's host."
619 (declare (type pathname-designator pathname)
620 (type (member :local :common) case)
623 (with-pathname (pathname pathname)
624 (%pathname-host pathname)))
626 (defun pathname-device (pathname &key (case :local))
628 "Return PATHNAME's device."
629 (declare (type pathname-designator pathname)
630 (type (member :local :common) case))
631 (with-pathname (pathname pathname)
632 (maybe-diddle-case (%pathname-device pathname)
633 (and (eq case :common)
634 (eq (host-customary-case
635 (%pathname-host pathname))
638 (defun pathname-directory (pathname &key (case :local))
640 "Return PATHNAME's directory."
641 (declare (type pathname-designator pathname)
642 (type (member :local :common) case))
643 (with-pathname (pathname pathname)
644 (maybe-diddle-case (%pathname-directory pathname)
645 (and (eq case :common)
646 (eq (host-customary-case
647 (%pathname-host pathname))
649 (defun pathname-name (pathname &key (case :local))
651 "Return PATHNAME's name."
652 (declare (type pathname-designator pathname)
653 (type (member :local :common) case))
654 (with-pathname (pathname pathname)
655 (maybe-diddle-case (%pathname-name pathname)
656 (and (eq case :common)
657 (eq (host-customary-case
658 (%pathname-host pathname))
661 (defun pathname-type (pathname &key (case :local))
663 "Return PATHNAME's type."
664 (declare (type pathname-designator pathname)
665 (type (member :local :common) case))
666 (with-pathname (pathname pathname)
667 (maybe-diddle-case (%pathname-type pathname)
668 (and (eq case :common)
669 (eq (host-customary-case
670 (%pathname-host pathname))
673 (defun pathname-version (pathname)
675 "Return PATHNAME's version."
676 (declare (type pathname-designator pathname))
677 (with-pathname (pathname pathname)
678 (%pathname-version pathname)))
682 ;;; Handle the case for PARSE-NAMESTRING parsing a potentially
683 ;;; syntactically valid logical namestring with an explicit host.
685 ;;; This then isn't fully general -- we are relying on the fact that
686 ;;; we will only pass to parse-namestring namestring with an explicit
687 ;;; logical host, so that we can pass the host return from
688 ;;; parse-logical-namestring through to %PARSE-NAMESTRING as a truth
689 ;;; value. Yeah, this is probably a KLUDGE - CSR, 2002-04-18
690 (defun parseable-logical-namestring-p (namestr start end)
693 ((namestring-parse-error (lambda (c)
696 (let ((colon (position #\: namestr :start start :end end)))
698 (let ((potential-host
699 (logical-word-or-lose (subseq namestr start colon))))
700 ;; depending on the outcome of CSR comp.lang.lisp post
701 ;; "can PARSE-NAMESTRING create logical hosts", we may need
702 ;; to do things with potential-host (create it
703 ;; temporarily, parse the namestring and unintern the
704 ;; logical host potential-host on failure.
705 (declare (ignore potential-host))
708 ((simple-type-error (lambda (c)
711 (parse-logical-namestring namestr start end))))
712 ;; if we got this far, we should have an explicit host
713 ;; (first return value of parse-logical-namestring)
717 ;;; Handle the case where PARSE-NAMESTRING is actually parsing a
718 ;;; namestring. We pick off the :JUNK-ALLOWED case then find a host to
719 ;;; use for parsing, call the parser, then check whether the host matches.
720 (defun %parse-namestring (namestr host defaults start end junk-allowed)
721 (declare (type (or host null) host)
722 (type string namestr)
724 (type (or index null) end))
728 (%parse-namestring namestr host defaults start end nil)
729 (namestring-parse-error (condition)
730 (values nil (namestring-parse-error-offset condition)))))
732 (let* ((end (%check-vector-sequence-bounds namestr start end)))
733 (multiple-value-bind (new-host device directory file type version)
734 ;; Comments below are quotes from the HyperSpec
735 ;; PARSE-NAMESTRING entry, reproduced here to demonstrate
736 ;; that we actually have to do things this way rather than
737 ;; some possibly more logical way. - CSR, 2002-04-18
739 ;; "If host is a logical host then thing is parsed as a
740 ;; logical pathname namestring on the host."
741 (host (funcall (host-parse host) namestr start end))
742 ;; "If host is nil and thing is a syntactically valid
743 ;; logical pathname namestring containing an explicit
744 ;; host, then it is parsed as a logical pathname
746 ((parseable-logical-namestring-p namestr start end)
747 (parse-logical-namestring namestr start end))
748 ;; "If host is nil, default-pathname is a logical
749 ;; pathname, and thing is a syntactically valid logical
750 ;; pathname namestring without an explicit host, then it
751 ;; is parsed as a logical pathname namestring on the
752 ;; host that is the host component of default-pathname."
754 ;; "Otherwise, the parsing of thing is
755 ;; implementation-defined."
757 ;; Both clauses are handled here, as the default
758 ;; *DEFAULT-PATHNAME-DEFAULTS* has a SB-IMPL::UNIX-HOST
760 ((pathname-host defaults)
761 (funcall (host-parse (pathname-host defaults))
765 ;; I don't think we should ever get here, as the default
766 ;; host will always have a non-null HOST, given that we
767 ;; can't create a new pathname without going through
768 ;; *DEFAULT-PATHNAME-DEFAULTS*, which has a non-null
770 (t (bug "Fallen through COND in %PARSE-NAMESTRING")))
771 (when (and host new-host (not (eq new-host host)))
772 (error 'simple-type-error
774 ;; Note: ANSI requires that this be a TYPE-ERROR,
775 ;; but there seems to be no completely correct
776 ;; value to use for TYPE-ERROR-EXPECTED-TYPE.
777 ;; Instead, we return a sort of "type error allowed
778 ;; type", trying to say "it would be OK if you
779 ;; passed NIL as the host value" but not mentioning
780 ;; that a matching string would be OK too.
783 "The host in the namestring, ~S,~@
784 does not match the explicit HOST argument, ~S."
785 :format-arguments (list new-host host)))
786 (let ((pn-host (or new-host host (pathname-host defaults))))
787 (values (%make-maybe-logical-pathname
788 pn-host device directory file type version)
791 ;;; If NAMESTR begins with a colon-terminated, defined, logical host,
792 ;;; then return that host, otherwise return NIL.
793 (defun extract-logical-host-prefix (namestr start end)
794 (declare (type simple-string namestr)
795 (type index start end)
796 (values (or logical-host null)))
797 (let ((colon-pos (position #\: namestr :start start :end end)))
799 (values (gethash (nstring-upcase (subseq namestr start colon-pos))
803 (defun parse-namestring (thing
806 (defaults *default-pathname-defaults*)
807 &key (start 0) end junk-allowed)
808 (declare (type pathname-designator thing defaults)
809 (type (or list host string (member :unspecific)) host)
811 (type (or index null) end)
812 (type (or t null) junk-allowed)
813 (values (or null pathname) (or null index)))
814 (with-host (found-host host)
815 (let (;; According to ANSI defaults may be any valid pathname designator
816 (defaults (etypecase defaults
820 (aver (pathnamep *default-pathname-defaults*))
821 (parse-namestring defaults))
823 (truename defaults)))))
824 (declare (type pathname defaults))
827 (%parse-namestring thing found-host defaults start end junk-allowed))
829 (%parse-namestring (coerce thing 'simple-string)
830 found-host defaults start end junk-allowed))
832 (let ((defaulted-host (or found-host (%pathname-host defaults))))
833 (declare (type host defaulted-host))
834 (unless (eq defaulted-host (%pathname-host thing))
835 (error "The HOST argument doesn't match the pathname host:~% ~
837 defaulted-host (%pathname-host thing))))
838 (values thing start))
840 (let ((name (file-name thing)))
842 (error "can't figure out the file associated with stream:~% ~S"
844 (values name nil)))))))
846 (defun %parse-native-namestring (namestr host defaults start end junk-allowed)
847 (declare (type (or host null) host)
848 (type string namestr)
850 (type (or index null) end))
854 (%parse-namestring namestr host defaults start end nil)
855 (namestring-parse-error (condition)
856 (values nil (namestring-parse-error-offset condition)))))
858 (let* ((end (%check-vector-sequence-bounds namestr start end)))
859 (multiple-value-bind (new-host device directory file type version)
861 (host (funcall (host-parse-native host) namestr start end))
862 ((pathname-host defaults)
863 (funcall (host-parse-native (pathname-host defaults))
867 ;; I don't think we should ever get here, as the default
868 ;; host will always have a non-null HOST, given that we
869 ;; can't create a new pathname without going through
870 ;; *DEFAULT-PATHNAME-DEFAULTS*, which has a non-null
872 (t (bug "Fallen through COND in %PARSE-NAMESTRING")))
873 (when (and host new-host (not (eq new-host host)))
874 (error 'simple-type-error
876 :expected-type `(or null (eql ,host))
878 "The host in the namestring, ~S,~@
879 does not match the explicit HOST argument, ~S."
880 :format-arguments (list new-host host)))
881 (let ((pn-host (or new-host host (pathname-host defaults))))
882 (values (%make-pathname
883 pn-host device directory file type version)
886 (defun parse-native-namestring (thing
889 (defaults *default-pathname-defaults*)
890 &key (start 0) end junk-allowed)
892 "Convert THING into a pathname, using the native conventions
893 appropriate for the pathname host HOST, or if not specified the host
894 of DEFAULTS. If THING is a string, the parse is bounded by START and
895 END, and error behaviour is controlled by JUNK-ALLOWED, as with
897 (declare (type pathname-designator thing defaults)
898 (type (or list host string (member :unspecific)) host)
900 (type (or index null) end)
901 (type (or t null) junk-allowed)
902 (values (or null pathname) (or null index)))
903 (with-host (found-host host)
904 (let ((defaults (etypecase defaults
908 (aver (pathnamep *default-pathname-defaults*))
909 (parse-native-namestring defaults))
911 (truename defaults)))))
912 (declare (type pathname defaults))
915 (%parse-native-namestring
916 thing found-host defaults start end junk-allowed))
918 (%parse-native-namestring (coerce thing 'simple-string)
919 found-host defaults start end junk-allowed))
921 (let ((defaulted-host (or found-host (%pathname-host defaults))))
922 (declare (type host defaulted-host))
923 (unless (eq defaulted-host (%pathname-host thing))
924 (error "The HOST argument doesn't match the pathname host:~% ~
926 defaulted-host (%pathname-host thing))))
927 (values thing start))
930 (let ((name (file-name thing)))
932 (error "can't figure out the file associated with stream:~% ~S"
934 (values name nil)))))))
936 (defun namestring (pathname)
938 "Construct the full (name)string form of the pathname."
939 (declare (type pathname-designator pathname))
940 (with-pathname (pathname pathname)
942 (let ((host (%pathname-host pathname)))
944 (error "can't determine the namestring for pathnames with no ~
945 host:~% ~S" pathname))
946 (funcall (host-unparse host) pathname)))))
948 (defun native-namestring (pathname)
950 "Construct the full native (name)string form of PATHNAME."
951 (declare (type pathname-designator pathname))
952 (with-native-pathname (pathname pathname)
954 (let ((host (%pathname-host pathname)))
956 (error "can't determine the native namestring for pathnames with no ~
957 host:~% ~S" pathname))
958 (funcall (host-unparse-native host) pathname)))))
960 (defun host-namestring (pathname)
962 "Return a string representation of the name of the host in the pathname."
963 (declare (type pathname-designator pathname))
964 (with-pathname (pathname pathname)
965 (let ((host (%pathname-host pathname)))
967 (funcall (host-unparse-host host) pathname)
969 "can't determine the namestring for pathnames with no host:~% ~S"
972 (defun directory-namestring (pathname)
974 "Return a string representation of the directories used in the pathname."
975 (declare (type pathname-designator pathname))
976 (with-pathname (pathname pathname)
977 (let ((host (%pathname-host pathname)))
979 (funcall (host-unparse-directory host) pathname)
981 "can't determine the namestring for pathnames with no host:~% ~S"
984 (defun file-namestring (pathname)
986 "Return a string representation of the name used in the pathname."
987 (declare (type pathname-designator pathname))
988 (with-pathname (pathname pathname)
989 (let ((host (%pathname-host pathname)))
991 (funcall (host-unparse-file host) pathname)
993 "can't determine the namestring for pathnames with no host:~% ~S"
996 (defun enough-namestring (pathname
998 (defaults *default-pathname-defaults*))
1000 "Return an abbreviated pathname sufficent to identify the pathname relative
1002 (declare (type pathname-designator pathname))
1003 (with-pathname (pathname pathname)
1004 (let ((host (%pathname-host pathname)))
1006 (with-pathname (defaults defaults)
1007 (funcall (host-unparse-enough host) pathname defaults))
1009 "can't determine the namestring for pathnames with no host:~% ~S"
1014 (defun wild-pathname-p (pathname &optional field-key)
1016 "Predicate for determining whether pathname contains any wildcards."
1017 (declare (type pathname-designator pathname)
1018 (type (member nil :host :device :directory :name :type :version)
1020 (with-pathname (pathname pathname)
1022 (or (pattern-p x) (member x '(:wild :wild-inferiors)))))
1025 (or (wild-pathname-p pathname :host)
1026 (wild-pathname-p pathname :device)
1027 (wild-pathname-p pathname :directory)
1028 (wild-pathname-p pathname :name)
1029 (wild-pathname-p pathname :type)
1030 (wild-pathname-p pathname :version)))
1031 (:host (frob (%pathname-host pathname)))
1032 (:device (frob (%pathname-host pathname)))
1033 (:directory (some #'frob (%pathname-directory pathname)))
1034 (:name (frob (%pathname-name pathname)))
1035 (:type (frob (%pathname-type pathname)))
1036 (:version (frob (%pathname-version pathname)))))))
1038 (defun pathname-match-p (in-pathname in-wildname)
1040 "Pathname matches the wildname template?"
1041 (declare (type pathname-designator in-pathname))
1042 (with-pathname (pathname in-pathname)
1043 (with-pathname (wildname in-wildname)
1044 (macrolet ((frob (field &optional (op 'components-match))
1045 `(or (null (,field wildname))
1046 (,op (,field pathname) (,field wildname)))))
1047 (and (or (null (%pathname-host wildname))
1048 (eq (%pathname-host wildname) (%pathname-host pathname)))
1049 (frob %pathname-device)
1050 (frob %pathname-directory directory-components-match)
1051 (frob %pathname-name)
1052 (frob %pathname-type)
1053 (or (eq (%pathname-host wildname) *unix-host*)
1054 (frob %pathname-version)))))))
1056 ;;; Place the substitutions into the pattern and return the string or pattern
1057 ;;; that results. If DIDDLE-CASE is true, we diddle the result case as well,
1058 ;;; in case we are translating between hosts with difference conventional case.
1059 ;;; The second value is the tail of subs with all of the values that we used up
1060 ;;; stripped off. Note that PATTERN-MATCHES matches all consecutive wildcards
1061 ;;; as a single string, so we ignore subsequent contiguous wildcards.
1062 (defun substitute-into (pattern subs diddle-case)
1063 (declare (type pattern pattern)
1065 (values (or simple-string pattern) list))
1066 (let ((in-wildcard nil)
1069 (dolist (piece (pattern-pieces pattern))
1070 (cond ((simple-string-p piece)
1071 (push piece strings)
1072 (setf in-wildcard nil))
1075 (setf in-wildcard t)
1077 (error "not enough wildcards in FROM pattern to match ~
1080 (let ((sub (pop subs)))
1084 (push (apply #'concatenate 'simple-string
1087 (dolist (piece (pattern-pieces sub))
1088 (push piece pieces)))
1092 (error "can't substitute this into the middle of a word:~
1097 (push (apply #'concatenate 'simple-string (nreverse strings))
1101 (if (and pieces (simple-string-p (car pieces)) (null (cdr pieces)))
1103 (make-pattern (nreverse pieces)))
1107 ;;; Called when we can't see how source and from matched.
1108 (defun didnt-match-error (source from)
1109 (error "Pathname components from SOURCE and FROM args to TRANSLATE-PATHNAME~@
1110 did not match:~% ~S ~S"
1113 ;;; Do TRANSLATE-COMPONENT for all components except host, directory
1115 (defun translate-component (source from to diddle-case)
1122 (if (pattern= from source)
1124 (didnt-match-error source from)))
1126 (multiple-value-bind (won subs) (pattern-matches from source)
1128 (values (substitute-into to subs diddle-case))
1129 (didnt-match-error source from))))
1131 (maybe-diddle-case source diddle-case))))
1133 (values (substitute-into to (list source) diddle-case)))
1135 (if (components-match source from)
1136 (maybe-diddle-case source diddle-case)
1137 (didnt-match-error source from)))))
1139 (maybe-diddle-case source diddle-case))
1141 (if (components-match source from)
1143 (didnt-match-error source from)))))
1145 ;;; Return a list of all the things that we want to substitute into the TO
1146 ;;; pattern (the things matched by from on source.) When From contains
1147 ;;; :WILD-INFERIORS, the result contains a sublist of the matched source
1149 (defun compute-directory-substitutions (orig-source orig-from)
1150 (let ((source orig-source)
1155 (unless (every (lambda (x) (eq x :wild-inferiors)) from)
1156 (didnt-match-error orig-source orig-from))
1159 (unless from (didnt-match-error orig-source orig-from))
1160 (let ((from-part (pop from))
1161 (source-part (pop source)))
1164 (typecase source-part
1166 (if (pattern= from-part source-part)
1168 (didnt-match-error orig-source orig-from)))
1170 (multiple-value-bind (won new-subs)
1171 (pattern-matches from-part source-part)
1173 (dolist (sub new-subs)
1175 (didnt-match-error orig-source orig-from))))
1177 (didnt-match-error orig-source orig-from))))
1180 ((member :wild-inferiors)
1181 (let ((remaining-source (cons source-part source)))
1184 (when (directory-components-match remaining-source from)
1186 (unless remaining-source
1187 (didnt-match-error orig-source orig-from))
1188 (res (pop remaining-source)))
1190 (setq source remaining-source))))
1192 (unless (and (simple-string-p source-part)
1193 (string= from-part source-part))
1194 (didnt-match-error orig-source orig-from)))
1196 (didnt-match-error orig-source orig-from)))))
1199 ;;; This is called by TRANSLATE-PATHNAME on the directory components
1200 ;;; of its argument pathnames to produce the result directory
1201 ;;; component. If this leaves the directory NIL, we return the source
1202 ;;; directory. The :RELATIVE or :ABSOLUTE is taken from the source
1203 ;;; directory, except if TO is :ABSOLUTE, in which case the result
1204 ;;; will be :ABSOLUTE.
1205 (defun translate-directories (source from to diddle-case)
1206 (if (not (and source to from))
1207 (or (and to (null source) (remove :wild-inferiors to))
1208 (mapcar (lambda (x) (maybe-diddle-case x diddle-case)) source))
1210 ;; If TO is :ABSOLUTE, the result should still be :ABSOLUTE.
1211 (res (if (eq (first to) :absolute)
1214 (let ((subs-left (compute-directory-substitutions (rest source)
1216 (dolist (to-part (rest to))
1220 (let ((match (pop subs-left)))
1222 (error ":WILD-INFERIORS is not paired in from and to ~
1223 patterns:~% ~S ~S" from to))
1224 (res (maybe-diddle-case match diddle-case))))
1225 ((member :wild-inferiors)
1227 (let ((match (pop subs-left)))
1228 (unless (listp match)
1229 (error ":WILD-INFERIORS not paired in from and to ~
1230 patterns:~% ~S ~S" from to))
1232 (res (maybe-diddle-case x diddle-case)))))
1234 (multiple-value-bind
1236 (substitute-into to-part subs-left diddle-case)
1237 (setf subs-left new-subs-left)
1239 (t (res to-part)))))
1242 (defun translate-pathname (source from-wildname to-wildname &key)
1244 "Use the source pathname to translate the from-wildname's wild and
1245 unspecified elements into a completed to-pathname based on the to-wildname."
1246 (declare (type pathname-designator source from-wildname to-wildname))
1247 (with-pathname (source source)
1248 (with-pathname (from from-wildname)
1249 (with-pathname (to to-wildname)
1250 (let* ((source-host (%pathname-host source))
1251 (from-host (%pathname-host from))
1252 (to-host (%pathname-host to))
1254 (and source-host to-host
1255 (not (eq (host-customary-case source-host)
1256 (host-customary-case to-host))))))
1257 (macrolet ((frob (field &optional (op 'translate-component))
1258 `(let ((result (,op (,field source)
1262 (if (eq result :error)
1263 (error "~S doesn't match ~S." source from)
1265 (%make-maybe-logical-pathname
1266 (or to-host source-host)
1267 (frob %pathname-device)
1268 (frob %pathname-directory translate-directories)
1269 (frob %pathname-name)
1270 (frob %pathname-type)
1271 (if (eq from-host *unix-host*)
1272 (if (eq (%pathname-version to) :wild)
1273 (%pathname-version from)
1274 (%pathname-version to))
1275 (frob %pathname-version)))))))))
1277 ;;;; logical pathname support. ANSI 92-102 specification.
1279 ;;;; As logical-pathname translations are loaded they are
1280 ;;;; canonicalized as patterns to enable rapid efficient translation
1281 ;;;; into physical pathnames.
1285 ;;; Canonicalize a logical pathname word by uppercasing it checking that it
1286 ;;; contains only legal characters.
1287 (defun logical-word-or-lose (word)
1288 (declare (string word))
1289 (when (string= word "")
1290 (error 'namestring-parse-error
1291 :complaint "Attempted to treat invalid logical hostname ~
1292 as a logical host:~% ~S"
1294 :namestring word :offset 0))
1295 (let ((word (string-upcase word)))
1296 (dotimes (i (length word))
1297 (let ((ch (schar word i)))
1298 (unless (and (typep ch 'standard-char)
1299 (or (alpha-char-p ch) (digit-char-p ch) (char= ch #\-)))
1300 (error 'namestring-parse-error
1301 :complaint "logical namestring character which ~
1302 is not alphanumeric or hyphen:~% ~S"
1304 :namestring word :offset i))))
1305 (coerce word 'base-string)))
1307 ;;; Given a logical host or string, return a logical host. If ERROR-P
1308 ;;; is NIL, then return NIL when no such host exists.
1309 (defun find-logical-host (thing &optional (errorp t))
1312 (let ((found (gethash (logical-word-or-lose thing)
1314 (if (or found (not errorp))
1316 ;; This is the error signalled from e.g.
1317 ;; LOGICAL-PATHNAME-TRANSLATIONS when host is not a defined
1318 ;; host, and ANSI specifies that that's a TYPE-ERROR.
1319 (error 'simple-type-error
1321 ;; God only knows what ANSI expects us to use for
1322 ;; the EXPECTED-TYPE here. Maybe this will be OK..
1324 '(and string (satisfies logical-pathname-translations))
1325 :format-control "logical host not yet defined: ~S"
1326 :format-arguments (list thing)))))
1327 (logical-host thing)))
1329 ;;; Given a logical host name or host, return a logical host, creating
1330 ;;; a new one if necessary.
1331 (defun intern-logical-host (thing)
1332 (declare (values logical-host))
1333 (or (find-logical-host thing nil)
1334 (let* ((name (logical-word-or-lose thing))
1335 (new (make-logical-host :name name)))
1336 (setf (gethash name *logical-hosts*) new)
1339 ;;;; logical pathname parsing
1341 ;;; Deal with multi-char wildcards in a logical pathname token.
1342 (defun maybe-make-logical-pattern (namestring chunks)
1343 (let ((chunk (caar chunks)))
1344 (collect ((pattern))
1346 (len (length chunk)))
1347 (declare (fixnum last-pos))
1349 (when (= last-pos len) (return))
1350 (let ((pos (or (position #\* chunk :start last-pos) len)))
1351 (if (= pos last-pos)
1353 (error 'namestring-parse-error
1354 :complaint "double asterisk inside of logical ~
1357 :namestring namestring
1358 :offset (+ (cdar chunks) pos)))
1359 (pattern (subseq chunk last-pos pos)))
1362 (pattern :multi-char-wild))
1363 (setq last-pos (1+ pos)))))
1366 (make-pattern (pattern))
1367 (let ((x (car (pattern))))
1368 (if (eq x :multi-char-wild)
1372 ;;; Return a list of conses where the CDR is the start position and
1373 ;;; the CAR is a string (token) or character (punctuation.)
1374 (defun logical-chunkify (namestr start end)
1376 (do ((i start (1+ i))
1380 (chunks (cons (nstring-upcase (subseq namestr prev end)) prev))))
1381 (let ((ch (schar namestr i)))
1382 (unless (or (alpha-char-p ch) (digit-char-p ch)
1383 (member ch '(#\- #\*)))
1385 (chunks (cons (nstring-upcase (subseq namestr prev i)) prev)))
1387 (unless (member ch '(#\; #\: #\.))
1388 (error 'namestring-parse-error
1389 :complaint "illegal character for logical pathname:~% ~S"
1393 (chunks (cons ch i)))))
1396 ;;; Break up a logical-namestring, always a string, into its
1397 ;;; constituent parts.
1398 (defun parse-logical-namestring (namestr start end)
1399 (declare (type simple-string namestr)
1400 (type index start end))
1401 (collect ((directory))
1406 (labels ((expecting (what chunks)
1407 (unless (and chunks (simple-string-p (caar chunks)))
1408 (error 'namestring-parse-error
1409 :complaint "expecting ~A, got ~:[nothing~;~S~]."
1410 :args (list what (caar chunks) (caar chunks))
1412 :offset (if chunks (cdar chunks) end)))
1414 (parse-host (chunks)
1415 (case (caadr chunks)
1418 (find-logical-host (expecting "a host name" chunks)))
1419 (parse-relative (cddr chunks)))
1421 (parse-relative chunks))))
1422 (parse-relative (chunks)
1425 (directory :relative)
1426 (parse-directory (cdr chunks)))
1428 (directory :absolute) ; Assumption! Maybe revoked later.
1429 (parse-directory chunks))))
1430 (parse-directory (chunks)
1431 (case (caadr chunks)
1434 (let ((res (expecting "a directory name" chunks)))
1435 (cond ((string= res "..") :up)
1436 ((string= res "**") :wild-inferiors)
1438 (maybe-make-logical-pattern namestr chunks)))))
1439 (parse-directory (cddr chunks)))
1441 (parse-name chunks))))
1442 (parse-name (chunks)
1444 (expecting "a file name" chunks)
1445 (setq name (maybe-make-logical-pattern namestr chunks))
1446 (expecting-dot (cdr chunks))))
1447 (expecting-dot (chunks)
1449 (unless (eql (caar chunks) #\.)
1450 (error 'namestring-parse-error
1451 :complaint "expecting a dot, got ~S."
1452 :args (list (caar chunks))
1454 :offset (cdar chunks)))
1456 (parse-version (cdr chunks))
1457 (parse-type (cdr chunks)))))
1458 (parse-type (chunks)
1459 (expecting "a file type" chunks)
1460 (setq type (maybe-make-logical-pattern namestr chunks))
1461 (expecting-dot (cdr chunks)))
1462 (parse-version (chunks)
1463 (let ((str (expecting "a positive integer, * or NEWEST"
1466 ((string= str "*") (setq version :wild))
1467 ((string= str "NEWEST") (setq version :newest))
1469 (multiple-value-bind (res pos)
1470 (parse-integer str :junk-allowed t)
1471 (unless (and res (plusp res))
1472 (error 'namestring-parse-error
1473 :complaint "expected a positive integer, ~
1477 :offset (+ pos (cdar chunks))))
1478 (setq version res)))))
1480 (error 'namestring-parse-error
1481 :complaint "extra stuff after end of file name"
1483 :offset (cdadr chunks)))))
1484 (parse-host (logical-chunkify namestr start end)))
1485 (values host :unspecific (directory) name type version))))
1487 ;;; We can't initialize this yet because not all host methods are
1489 (defvar *logical-pathname-defaults*)
1491 (defun logical-pathname (pathspec)
1493 "Converts the pathspec argument to a logical-pathname and returns it."
1494 (declare (type (or logical-pathname string stream) pathspec)
1495 (values logical-pathname))
1496 (if (typep pathspec 'logical-pathname)
1498 (let ((res (parse-namestring pathspec nil *logical-pathname-defaults*)))
1499 (when (eq (%pathname-host res)
1500 (%pathname-host *logical-pathname-defaults*))
1501 (error "This logical namestring does not specify a host:~% ~S"
1505 ;;;; logical pathname unparsing
1507 (defun unparse-logical-directory (pathname)
1508 (declare (type pathname pathname))
1510 (let ((directory (%pathname-directory pathname)))
1512 (ecase (pop directory)
1513 (:absolute) ; nothing special
1514 (:relative (pieces ";")))
1515 (dolist (dir directory)
1516 (cond ((or (stringp dir) (pattern-p dir))
1517 (pieces (unparse-logical-piece dir))
1521 ((eq dir :wild-inferiors)
1524 (error "invalid directory component: ~S" dir))))))
1525 (apply #'concatenate 'simple-string (pieces))))
1527 (defun unparse-logical-piece (thing)
1529 ((member :wild) "*")
1530 (simple-string thing)
1532 (collect ((strings))
1533 (dolist (piece (pattern-pieces thing))
1535 (simple-string (strings piece))
1537 (cond ((eq piece :wild-inferiors)
1539 ((eq piece :multi-char-wild)
1541 (t (error "invalid keyword: ~S" piece))))))
1542 (apply #'concatenate 'simple-string (strings))))))
1544 (defun unparse-logical-file (pathname)
1545 (declare (type pathname pathname))
1546 (collect ((strings))
1547 (let* ((name (%pathname-name pathname))
1548 (type (%pathname-type pathname))
1549 (version (%pathname-version pathname))
1550 (type-supplied (not (or (null type) (eq type :unspecific))))
1551 (version-supplied (not (or (null version)
1552 (eq version :unspecific)))))
1554 (when (and (null type)
1555 (typep name 'string)
1556 (position #\. name :start 1))
1557 (error "too many dots in the name: ~S" pathname))
1558 (strings (unparse-logical-piece name)))
1561 (error "cannot specify the type without a file: ~S" pathname))
1562 (when (typep type 'string)
1563 (when (position #\. type)
1564 (error "type component can't have a #\. inside: ~S" pathname)))
1566 (strings (unparse-logical-piece type)))
1567 (when version-supplied
1568 (unless type-supplied
1569 (error "cannot specify the version without a type: ~S" pathname))
1571 ((member :newest) (strings ".NEWEST"))
1572 ((member :wild) (strings ".*"))
1573 (fixnum (strings ".") (strings (format nil "~D" version))))))
1574 (apply #'concatenate 'simple-string (strings))))
1576 ;;; Unparse a logical pathname string.
1577 (defun unparse-enough-namestring (pathname defaults)
1578 (let* ((path-directory (pathname-directory pathname))
1579 (def-directory (pathname-directory defaults))
1581 ;; Go down the directory lists to see what matches. What's
1582 ;; left is what we want, more or less.
1583 (cond ((and (eq (first path-directory) (first def-directory))
1584 (eq (first path-directory) :absolute))
1585 ;; Both paths are :ABSOLUTE, so find where the
1586 ;; common parts end and return what's left
1587 (do* ((p (rest path-directory) (rest p))
1588 (d (rest def-directory) (rest d)))
1589 ((or (endp p) (endp d)
1590 (not (equal (first p) (first d))))
1593 ;; At least one path is :RELATIVE, so just return the
1594 ;; original path. If the original path is :RELATIVE,
1595 ;; then that's the right one. If PATH-DIRECTORY is
1596 ;; :ABSOLUTE, we want to return that except when
1597 ;; DEF-DIRECTORY is :ABSOLUTE, as handled above. so return
1598 ;; the original directory.
1600 (unparse-logical-namestring
1601 (make-pathname :host (pathname-host pathname)
1602 :directory enough-directory
1603 :name (pathname-name pathname)
1604 :type (pathname-type pathname)
1605 :version (pathname-version pathname)))))
1607 (defun unparse-logical-namestring (pathname)
1608 (declare (type logical-pathname pathname))
1609 (concatenate 'simple-string
1610 (logical-host-name (%pathname-host pathname)) ":"
1611 (unparse-logical-directory pathname)
1612 (unparse-logical-file pathname)))
1614 ;;;; logical pathname translations
1616 ;;; Verify that the list of translations consists of lists and prepare
1617 ;;; canonical translations. (Parse pathnames and expand out wildcards
1619 (defun canonicalize-logical-pathname-translations (translation-list host)
1620 (declare (type list translation-list) (type host host)
1622 (mapcar (lambda (translation)
1623 (destructuring-bind (from to) translation
1624 (list (if (typep from 'logical-pathname)
1626 (parse-namestring from host))
1630 (defun logical-pathname-translations (host)
1632 "Return the (logical) host object argument's list of translations."
1633 (declare (type (or string logical-host) host)
1635 (logical-host-translations (find-logical-host host)))
1637 (defun (setf logical-pathname-translations) (translations host)
1639 "Set the translations list for the logical host argument."
1640 (declare (type (or string logical-host) host)
1641 (type list translations)
1643 (let ((host (intern-logical-host host)))
1644 (setf (logical-host-canon-transls host)
1645 (canonicalize-logical-pathname-translations translations host))
1646 (setf (logical-host-translations host) translations)))
1648 (defun translate-logical-pathname (pathname &key)
1650 "Translate PATHNAME to a physical pathname, which is returned."
1651 (declare (type pathname-designator pathname)
1652 (values (or null pathname)))
1655 (dolist (x (logical-host-canon-transls (%pathname-host pathname))
1656 (error 'simple-file-error
1658 :format-control "no translation for ~S"
1659 :format-arguments (list pathname)))
1660 (destructuring-bind (from to) x
1661 (when (pathname-match-p pathname from)
1662 (return (translate-logical-pathname
1663 (translate-pathname pathname from to)))))))
1665 (t (translate-logical-pathname (pathname pathname)))))
1667 (defvar *logical-pathname-defaults*
1668 (%make-logical-pathname
1669 (make-logical-host :name (logical-word-or-lose "BOGUS"))
1670 :unspecific nil nil nil nil))
1672 (defun load-logical-pathname-translations (host)
1674 (declare (type string host)
1675 (values (member t nil)))
1676 (if (find-logical-host host nil)
1677 ;; This host is already defined, all is well and good.
1679 ;; ANSI: "The specific nature of the search is
1680 ;; implementation-defined." SBCL: doesn't search at all
1682 ;; FIXME: now that we have a SYS host that the system uses, it
1683 ;; might be cute to search in "SYS:TRANSLATIONS;<name>.LISP"
1684 (error "logical host ~S not found" host)))