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 (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-win32-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 ;;; FIXME: become SB!XC:DEFMACRO inside EVAL-WHEN (COMPILE EVAL)?
290 (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 (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 (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"
367 (defun find-host (host-designator &optional (errorp t))
368 (with-host (host host-designator)
369 (when (and errorp (not host))
370 (error "Couldn't find host: ~S" host-designator))
373 (defun pathname (pathspec)
375 "Convert PATHSPEC (a pathname designator) into a pathname."
376 (declare (type pathname-designator pathspec))
377 (with-pathname (pathname pathspec)
380 (defun native-pathname (pathspec)
382 "Convert PATHSPEC (a pathname designator) into a pathname, assuming
383 the operating system native pathname conventions."
384 (with-native-pathname (pathname pathspec)
387 ;;; Change the case of thing if DIDDLE-P.
388 (defun maybe-diddle-case (thing diddle-p)
389 (if (and diddle-p (not (or (symbolp thing) (integerp thing))))
390 (labels ((check-for (pred in)
393 (dolist (piece (pattern-pieces in))
394 (when (typecase piece
396 (check-for pred piece))
400 (check-for pred (cdr piece))))))
404 (when (check-for pred x)
407 (dotimes (i (length in))
408 (when (funcall pred (schar in i))
411 (diddle-with (fun thing)
415 (mapcar (lambda (piece)
423 (funcall fun (cdr piece))))
428 (pattern-pieces thing))))
435 (let ((any-uppers (check-for #'upper-case-p thing))
436 (any-lowers (check-for #'lower-case-p thing)))
437 (cond ((and any-uppers any-lowers)
438 ;; mixed case, stays the same
441 ;; all uppercase, becomes all lower case
442 (diddle-with (lambda (x) (if (stringp x)
446 ;; all lowercase, becomes all upper case
447 (diddle-with (lambda (x) (if (stringp x)
451 ;; no letters? I guess just leave it.
455 (defun merge-directories (dir1 dir2 diddle-case)
456 (if (or (eq (car dir1) :absolute)
461 (if (and (eq dir :back)
463 (not (member (car results)
464 '(:back :wild-inferiors :relative :absolute))))
466 (push dir results))))
467 (dolist (dir (maybe-diddle-case dir2 diddle-case))
469 (dolist (dir (cdr dir1))
473 (defun merge-pathnames (pathname
475 (defaults *default-pathname-defaults*)
476 (default-version :newest))
478 "Construct a filled in pathname by completing the unspecified components
480 (declare (type pathname-designator pathname)
481 (type pathname-designator defaults)
483 (with-pathname (defaults defaults)
484 (let ((pathname (let ((*default-pathname-defaults* defaults))
485 (pathname pathname))))
486 (let* ((default-host (%pathname-host defaults))
487 (pathname-host (%pathname-host pathname))
489 (and default-host pathname-host
490 (not (eq (host-customary-case default-host)
491 (host-customary-case pathname-host))))))
492 (%make-maybe-logical-pathname
493 (or pathname-host default-host)
494 (or (%pathname-device pathname)
495 (maybe-diddle-case (%pathname-device defaults)
497 (merge-directories (%pathname-directory pathname)
498 (%pathname-directory defaults)
500 (or (%pathname-name pathname)
501 (maybe-diddle-case (%pathname-name defaults)
503 (or (%pathname-type pathname)
504 (maybe-diddle-case (%pathname-type defaults)
506 (or (%pathname-version pathname)
507 (and (not (%pathname-name pathname)) (%pathname-version defaults))
508 default-version))))))
510 (defun import-directory (directory diddle-case)
513 ((member :wild) '(:absolute :wild-inferiors))
514 ((member :unspecific) '(:relative))
517 (results (pop directory))
518 (dolist (piece directory)
519 (cond ((member piece '(:wild :wild-inferiors :up :back))
521 ((or (simple-string-p piece) (pattern-p piece))
522 (results (maybe-diddle-case piece diddle-case)))
524 (results (maybe-diddle-case (coerce piece 'simple-string)
527 (error "~S is not allowed as a directory component." piece))))
530 `(:absolute ,(maybe-diddle-case directory diddle-case)))
533 ,(maybe-diddle-case (coerce directory 'simple-string) diddle-case)))))
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
848 (declare (type (or host null) host)
849 (type string namestr)
851 (type (or index null) end))
855 (%parse-namestring namestr host defaults start end nil)
856 (namestring-parse-error (condition)
857 (values nil (namestring-parse-error-offset condition)))))
859 (let* ((end (%check-vector-sequence-bounds namestr start end)))
860 (multiple-value-bind (new-host device directory file type version)
863 (funcall (host-parse-native host) namestr start end as-directory))
864 ((pathname-host defaults)
865 (funcall (host-parse-native (pathname-host defaults))
870 ;; I don't think we should ever get here, as the default
871 ;; host will always have a non-null HOST, given that we
872 ;; can't create a new pathname without going through
873 ;; *DEFAULT-PATHNAME-DEFAULTS*, which has a non-null
875 (t (bug "Fallen through COND in %PARSE-NAMESTRING")))
876 (when (and host new-host (not (eq new-host host)))
877 (error 'simple-type-error
879 :expected-type `(or null (eql ,host))
881 "The host in the namestring, ~S,~@
882 does not match the explicit HOST argument, ~S."
883 :format-arguments (list new-host host)))
884 (let ((pn-host (or new-host host (pathname-host defaults))))
885 (values (%make-pathname
886 pn-host device directory file type version)
889 (defun parse-native-namestring (thing
892 (defaults *default-pathname-defaults*)
893 &key (start 0) end junk-allowed
896 "Convert THING into a pathname, using the native conventions
897 appropriate for the pathname host HOST, or if not specified the
898 host of DEFAULTS. If THING is a string, the parse is bounded by
899 START and END, and error behaviour is controlled by JUNK-ALLOWED,
900 as with PARSE-NAMESTRING. For file systems whose native
901 conventions allow directories to be indicated as files, if
902 AS-DIRECTORY is true, return a pathname denoting THING as a
904 (declare (type pathname-designator thing defaults)
905 (type (or list host string (member :unspecific)) host)
907 (type (or index null) end)
908 (type (or t null) junk-allowed)
909 (values (or null pathname) (or null index)))
910 (with-host (found-host host)
911 (let ((defaults (etypecase defaults
915 (aver (pathnamep *default-pathname-defaults*))
916 (parse-native-namestring defaults))
918 (truename defaults)))))
919 (declare (type pathname defaults))
922 (%parse-native-namestring
923 thing found-host defaults start end junk-allowed as-directory))
925 (%parse-native-namestring (coerce thing 'simple-string)
926 found-host defaults start end junk-allowed
929 (let ((defaulted-host (or found-host (%pathname-host defaults))))
930 (declare (type host defaulted-host))
931 (unless (eq defaulted-host (%pathname-host thing))
932 (error "The HOST argument doesn't match the pathname host:~% ~
934 defaulted-host (%pathname-host thing))))
935 (values thing start))
938 (let ((name (file-name thing)))
940 (error "can't figure out the file associated with stream:~% ~S"
942 (values name nil)))))))
944 (defun namestring (pathname)
946 "Construct the full (name)string form of the pathname."
947 (declare (type pathname-designator pathname))
948 (with-pathname (pathname pathname)
950 (let ((host (%pathname-host pathname)))
952 (error "can't determine the namestring for pathnames with no ~
953 host:~% ~S" pathname))
954 (funcall (host-unparse host) pathname)))))
956 (defun native-namestring (pathname &key as-file)
958 "Construct the full native (name)string form of PATHNAME. For
959 file systems whose native conventions allow directories to be
960 indicated as files, if AS-FILE is true and the name, type, and
961 version components of PATHNAME are all NIL or :UNSPECIFIC,
962 construct a string that names the directory according to the file
963 system's syntax for files."
964 (declare (type pathname-designator pathname))
965 (with-native-pathname (pathname pathname)
967 (let ((host (%pathname-host pathname)))
969 (error "can't determine the native namestring for pathnames with no ~
970 host:~% ~S" pathname))
971 (funcall (host-unparse-native host) pathname as-file)))))
973 (defun host-namestring (pathname)
975 "Return a string representation of the name of the host in the pathname."
976 (declare (type pathname-designator pathname))
977 (with-pathname (pathname pathname)
978 (let ((host (%pathname-host pathname)))
980 (funcall (host-unparse-host host) pathname)
982 "can't determine the namestring for pathnames with no host:~% ~S"
985 (defun directory-namestring (pathname)
987 "Return a string representation of the directories used in the pathname."
988 (declare (type pathname-designator pathname))
989 (with-pathname (pathname pathname)
990 (let ((host (%pathname-host pathname)))
992 (funcall (host-unparse-directory host) pathname)
994 "can't determine the namestring for pathnames with no host:~% ~S"
997 (defun file-namestring (pathname)
999 "Return a string representation of the name used in the pathname."
1000 (declare (type pathname-designator pathname))
1001 (with-pathname (pathname pathname)
1002 (let ((host (%pathname-host pathname)))
1004 (funcall (host-unparse-file host) pathname)
1006 "can't determine the namestring for pathnames with no host:~% ~S"
1009 (defun enough-namestring (pathname
1011 (defaults *default-pathname-defaults*))
1013 "Return an abbreviated pathname sufficent to identify the pathname relative
1015 (declare (type pathname-designator pathname))
1016 (with-pathname (pathname pathname)
1017 (let ((host (%pathname-host pathname)))
1019 (with-pathname (defaults defaults)
1020 (funcall (host-unparse-enough host) pathname defaults))
1022 "can't determine the namestring for pathnames with no host:~% ~S"
1027 (defun wild-pathname-p (pathname &optional field-key)
1029 "Predicate for determining whether pathname contains any wildcards."
1030 (declare (type pathname-designator pathname)
1031 (type (member nil :host :device :directory :name :type :version)
1033 (with-pathname (pathname pathname)
1035 (or (pattern-p x) (member x '(:wild :wild-inferiors)))))
1038 (or (wild-pathname-p pathname :host)
1039 (wild-pathname-p pathname :device)
1040 (wild-pathname-p pathname :directory)
1041 (wild-pathname-p pathname :name)
1042 (wild-pathname-p pathname :type)
1043 (wild-pathname-p pathname :version)))
1044 (:host (frob (%pathname-host pathname)))
1045 (:device (frob (%pathname-host pathname)))
1046 (:directory (some #'frob (%pathname-directory pathname)))
1047 (:name (frob (%pathname-name pathname)))
1048 (:type (frob (%pathname-type pathname)))
1049 (:version (frob (%pathname-version pathname)))))))
1051 (defun pathname-match-p (in-pathname in-wildname)
1053 "Pathname matches the wildname template?"
1054 (declare (type pathname-designator in-pathname))
1055 (with-pathname (pathname in-pathname)
1056 (with-pathname (wildname in-wildname)
1057 (macrolet ((frob (field &optional (op 'components-match))
1058 `(or (null (,field wildname))
1059 (,op (,field pathname) (,field wildname)))))
1060 (and (or (null (%pathname-host wildname))
1061 (eq (%pathname-host wildname) (%pathname-host pathname)))
1062 (frob %pathname-device)
1063 (frob %pathname-directory directory-components-match)
1064 (frob %pathname-name)
1065 (frob %pathname-type)
1066 (or (eq (%pathname-host wildname) *unix-host*)
1067 (frob %pathname-version)))))))
1069 ;;; Place the substitutions into the pattern and return the string or pattern
1070 ;;; that results. If DIDDLE-CASE is true, we diddle the result case as well,
1071 ;;; in case we are translating between hosts with difference conventional case.
1072 ;;; The second value is the tail of subs with all of the values that we used up
1073 ;;; stripped off. Note that PATTERN-MATCHES matches all consecutive wildcards
1074 ;;; as a single string, so we ignore subsequent contiguous wildcards.
1075 (defun substitute-into (pattern subs diddle-case)
1076 (declare (type pattern pattern)
1078 (values (or simple-string pattern) list))
1079 (let ((in-wildcard nil)
1082 (dolist (piece (pattern-pieces pattern))
1083 (cond ((simple-string-p piece)
1084 (push piece strings)
1085 (setf in-wildcard nil))
1088 (setf in-wildcard t)
1090 (error "not enough wildcards in FROM pattern to match ~
1093 (let ((sub (pop subs)))
1097 (push (apply #'concatenate 'simple-string
1100 (dolist (piece (pattern-pieces sub))
1101 (push piece pieces)))
1105 (error "can't substitute this into the middle of a word:~
1110 (push (apply #'concatenate 'simple-string (nreverse strings))
1114 (if (and pieces (simple-string-p (car pieces)) (null (cdr pieces)))
1116 (make-pattern (nreverse pieces)))
1120 ;;; Called when we can't see how source and from matched.
1121 (defun didnt-match-error (source from)
1122 (error "Pathname components from SOURCE and FROM args to TRANSLATE-PATHNAME~@
1123 did not match:~% ~S ~S"
1126 ;;; Do TRANSLATE-COMPONENT for all components except host, directory
1128 (defun translate-component (source from to diddle-case)
1135 (if (pattern= from source)
1137 (didnt-match-error source from)))
1139 (multiple-value-bind (won subs) (pattern-matches from source)
1141 (values (substitute-into to subs diddle-case))
1142 (didnt-match-error source from))))
1144 (maybe-diddle-case source diddle-case))))
1146 (values (substitute-into to (list source) diddle-case)))
1148 (if (components-match source from)
1149 (maybe-diddle-case source diddle-case)
1150 (didnt-match-error source from)))))
1152 (maybe-diddle-case source diddle-case))
1154 (if (components-match source from)
1156 (didnt-match-error source from)))))
1158 ;;; Return a list of all the things that we want to substitute into the TO
1159 ;;; pattern (the things matched by from on source.) When From contains
1160 ;;; :WILD-INFERIORS, the result contains a sublist of the matched source
1162 (defun compute-directory-substitutions (orig-source orig-from)
1163 (let ((source orig-source)
1168 (unless (every (lambda (x) (eq x :wild-inferiors)) from)
1169 (didnt-match-error orig-source orig-from))
1172 (unless from (didnt-match-error orig-source orig-from))
1173 (let ((from-part (pop from))
1174 (source-part (pop source)))
1177 (typecase source-part
1179 (if (pattern= from-part source-part)
1181 (didnt-match-error orig-source orig-from)))
1183 (multiple-value-bind (won new-subs)
1184 (pattern-matches from-part source-part)
1186 (dolist (sub new-subs)
1188 (didnt-match-error orig-source orig-from))))
1190 (didnt-match-error orig-source orig-from))))
1193 ((member :wild-inferiors)
1194 (let ((remaining-source (cons source-part source)))
1197 (when (directory-components-match remaining-source from)
1199 (unless remaining-source
1200 (didnt-match-error orig-source orig-from))
1201 (res (pop remaining-source)))
1203 (setq source remaining-source))))
1205 (unless (and (simple-string-p source-part)
1206 (string= from-part source-part))
1207 (didnt-match-error orig-source orig-from)))
1209 (didnt-match-error orig-source orig-from)))))
1212 ;;; This is called by TRANSLATE-PATHNAME on the directory components
1213 ;;; of its argument pathnames to produce the result directory
1214 ;;; component. If this leaves the directory NIL, we return the source
1215 ;;; directory. The :RELATIVE or :ABSOLUTE is taken from the source
1216 ;;; directory, except if TO is :ABSOLUTE, in which case the result
1217 ;;; will be :ABSOLUTE.
1218 (defun translate-directories (source from to diddle-case)
1219 (if (not (and source to from))
1220 (or (and to (null source) (remove :wild-inferiors to))
1221 (mapcar (lambda (x) (maybe-diddle-case x diddle-case)) source))
1223 ;; If TO is :ABSOLUTE, the result should still be :ABSOLUTE.
1224 (res (if (eq (first to) :absolute)
1227 (let ((subs-left (compute-directory-substitutions (rest source)
1229 (dolist (to-part (rest to))
1233 (let ((match (pop subs-left)))
1235 (error ":WILD-INFERIORS is not paired in from and to ~
1236 patterns:~% ~S ~S" from to))
1237 (res (maybe-diddle-case match diddle-case))))
1238 ((member :wild-inferiors)
1240 (let ((match (pop subs-left)))
1241 (unless (listp match)
1242 (error ":WILD-INFERIORS not paired in from and to ~
1243 patterns:~% ~S ~S" from to))
1245 (res (maybe-diddle-case x diddle-case)))))
1247 (multiple-value-bind
1249 (substitute-into to-part subs-left diddle-case)
1250 (setf subs-left new-subs-left)
1252 (t (res to-part)))))
1255 (defun translate-pathname (source from-wildname to-wildname &key)
1257 "Use the source pathname to translate the from-wildname's wild and
1258 unspecified elements into a completed to-pathname based on the to-wildname."
1259 (declare (type pathname-designator source from-wildname to-wildname))
1260 (with-pathname (source source)
1261 (with-pathname (from from-wildname)
1262 (with-pathname (to to-wildname)
1263 (let* ((source-host (%pathname-host source))
1264 (from-host (%pathname-host from))
1265 (to-host (%pathname-host to))
1267 (and source-host to-host
1268 (not (eq (host-customary-case source-host)
1269 (host-customary-case to-host))))))
1270 (macrolet ((frob (field &optional (op 'translate-component))
1271 `(let ((result (,op (,field source)
1275 (if (eq result :error)
1276 (error "~S doesn't match ~S." source from)
1278 (%make-maybe-logical-pathname
1279 (or to-host source-host)
1280 (frob %pathname-device)
1281 (frob %pathname-directory translate-directories)
1282 (frob %pathname-name)
1283 (frob %pathname-type)
1284 (if (eq from-host *unix-host*)
1285 (if (or (eq (%pathname-version to) :wild)
1286 (eq (%pathname-version to) nil))
1287 (%pathname-version source)
1288 (%pathname-version to))
1289 (frob %pathname-version)))))))))
1291 ;;;; logical pathname support. ANSI 92-102 specification.
1293 ;;;; As logical-pathname translations are loaded they are
1294 ;;;; canonicalized as patterns to enable rapid efficient translation
1295 ;;;; into physical pathnames.
1299 (defun simplify-namestring (namestring &optional host)
1300 (funcall (host-simplify-namestring
1302 (pathname-host (sane-default-pathname-defaults))))
1305 ;;; Canonicalize a logical pathname word by uppercasing it checking that it
1306 ;;; contains only legal characters.
1307 (defun logical-word-or-lose (word)
1308 (declare (string word))
1309 (when (string= word "")
1310 (error 'namestring-parse-error
1311 :complaint "Attempted to treat invalid logical hostname ~
1312 as a logical host:~% ~S"
1314 :namestring word :offset 0))
1315 (let ((word (string-upcase word)))
1316 (dotimes (i (length word))
1317 (let ((ch (schar word i)))
1318 (unless (and (typep ch 'standard-char)
1319 (or (alpha-char-p ch) (digit-char-p ch) (char= ch #\-)))
1320 (error 'namestring-parse-error
1321 :complaint "logical namestring character which ~
1322 is not alphanumeric or hyphen:~% ~S"
1324 :namestring word :offset i))))
1325 (coerce word 'string))) ; why not simple-string?
1327 ;;; Given a logical host or string, return a logical host. If ERROR-P
1328 ;;; is NIL, then return NIL when no such host exists.
1329 (defun find-logical-host (thing &optional (errorp t))
1332 (let ((found (gethash (logical-word-or-lose thing)
1334 (if (or found (not errorp))
1336 ;; This is the error signalled from e.g.
1337 ;; LOGICAL-PATHNAME-TRANSLATIONS when host is not a defined
1338 ;; host, and ANSI specifies that that's a TYPE-ERROR.
1339 (error 'simple-type-error
1341 ;; God only knows what ANSI expects us to use for
1342 ;; the EXPECTED-TYPE here. Maybe this will be OK..
1344 '(and string (satisfies logical-pathname-translations))
1345 :format-control "logical host not yet defined: ~S"
1346 :format-arguments (list thing)))))
1347 (logical-host thing)))
1349 ;;; Given a logical host name or host, return a logical host, creating
1350 ;;; a new one if necessary.
1351 (defun intern-logical-host (thing)
1352 (declare (values logical-host))
1353 (with-locked-hash-table (*logical-hosts*)
1354 (or (find-logical-host thing nil)
1355 (let* ((name (logical-word-or-lose thing))
1356 (new (make-logical-host :name name)))
1357 (setf (gethash name *logical-hosts*) new)
1360 ;;;; logical pathname parsing
1362 ;;; Deal with multi-char wildcards in a logical pathname token.
1363 (defun maybe-make-logical-pattern (namestring chunks)
1364 (let ((chunk (caar chunks)))
1365 (collect ((pattern))
1367 (len (length chunk)))
1368 (declare (fixnum last-pos))
1370 (when (= last-pos len) (return))
1371 (let ((pos (or (position #\* chunk :start last-pos) len)))
1372 (if (= pos last-pos)
1374 (error 'namestring-parse-error
1375 :complaint "double asterisk inside of logical ~
1378 :namestring namestring
1379 :offset (+ (cdar chunks) pos)))
1380 (pattern (subseq chunk last-pos pos)))
1383 (pattern :multi-char-wild))
1384 (setq last-pos (1+ pos)))))
1387 (make-pattern (pattern))
1388 (let ((x (car (pattern))))
1389 (if (eq x :multi-char-wild)
1393 ;;; Return a list of conses where the CDR is the start position and
1394 ;;; the CAR is a string (token) or character (punctuation.)
1395 (defun logical-chunkify (namestr start end)
1397 (do ((i start (1+ i))
1401 (chunks (cons (nstring-upcase (subseq namestr prev end)) prev))))
1402 (let ((ch (schar namestr i)))
1403 (unless (or (alpha-char-p ch) (digit-char-p ch)
1404 (member ch '(#\- #\*)))
1406 (chunks (cons (nstring-upcase (subseq namestr prev i)) prev)))
1408 (unless (member ch '(#\; #\: #\.))
1409 (error 'namestring-parse-error
1410 :complaint "illegal character for logical pathname:~% ~S"
1414 (chunks (cons ch i)))))
1417 ;;; Break up a logical-namestring, always a string, into its
1418 ;;; constituent parts.
1419 (defun parse-logical-namestring (namestr start end)
1420 (declare (type simple-string namestr)
1421 (type index start end))
1422 (collect ((directory))
1427 (labels ((expecting (what chunks)
1428 (unless (and chunks (simple-string-p (caar chunks)))
1429 (error 'namestring-parse-error
1430 :complaint "expecting ~A, got ~:[nothing~;~S~]."
1431 :args (list what (caar chunks) (caar chunks))
1433 :offset (if chunks (cdar chunks) end)))
1435 (parse-host (chunks)
1436 (case (caadr chunks)
1439 (find-logical-host (expecting "a host name" chunks)))
1440 (parse-relative (cddr chunks)))
1442 (parse-relative chunks))))
1443 (parse-relative (chunks)
1446 (directory :relative)
1447 (parse-directory (cdr chunks)))
1449 (directory :absolute) ; Assumption! Maybe revoked later.
1450 (parse-directory chunks))))
1451 (parse-directory (chunks)
1452 (case (caadr chunks)
1455 (let ((res (expecting "a directory name" chunks)))
1456 (cond ((string= res "..") :up)
1457 ((string= res "**") :wild-inferiors)
1459 (maybe-make-logical-pattern namestr chunks)))))
1460 (parse-directory (cddr chunks)))
1462 (parse-name chunks))))
1463 (parse-name (chunks)
1465 (expecting "a file name" chunks)
1466 (setq name (maybe-make-logical-pattern namestr chunks))
1467 (expecting-dot (cdr chunks))))
1468 (expecting-dot (chunks)
1470 (unless (eql (caar chunks) #\.)
1471 (error 'namestring-parse-error
1472 :complaint "expecting a dot, got ~S."
1473 :args (list (caar chunks))
1475 :offset (cdar chunks)))
1477 (parse-version (cdr chunks))
1478 (parse-type (cdr chunks)))))
1479 (parse-type (chunks)
1480 (expecting "a file type" chunks)
1481 (setq type (maybe-make-logical-pattern namestr chunks))
1482 (expecting-dot (cdr chunks)))
1483 (parse-version (chunks)
1484 (let ((str (expecting "a positive integer, * or NEWEST"
1487 ((string= str "*") (setq version :wild))
1488 ((string= str "NEWEST") (setq version :newest))
1490 (multiple-value-bind (res pos)
1491 (parse-integer str :junk-allowed t)
1492 (unless (and res (plusp res))
1493 (error 'namestring-parse-error
1494 :complaint "expected a positive integer, ~
1498 :offset (+ pos (cdar chunks))))
1499 (setq version res)))))
1501 (error 'namestring-parse-error
1502 :complaint "extra stuff after end of file name"
1504 :offset (cdadr chunks)))))
1505 (parse-host (logical-chunkify namestr start end)))
1506 (values host :unspecific (directory) name type version))))
1508 ;;; We can't initialize this yet because not all host methods are
1510 (defvar *logical-pathname-defaults*)
1512 (defun logical-pathname (pathspec)
1514 "Converts the pathspec argument to a logical-pathname and returns it."
1515 (declare (type (or logical-pathname string stream) pathspec)
1516 (values logical-pathname))
1517 (if (typep pathspec 'logical-pathname)
1519 (let ((res (parse-namestring pathspec nil *logical-pathname-defaults*)))
1520 (when (eq (%pathname-host res)
1521 (%pathname-host *logical-pathname-defaults*))
1522 (error "This logical namestring does not specify a host:~% ~S"
1526 ;;;; logical pathname unparsing
1528 (defun unparse-logical-directory (pathname)
1529 (declare (type pathname pathname))
1531 (let ((directory (%pathname-directory pathname)))
1533 (ecase (pop directory)
1534 (:absolute) ; nothing special
1535 (:relative (pieces ";")))
1536 (dolist (dir directory)
1537 (cond ((or (stringp dir) (pattern-p dir))
1538 (pieces (unparse-logical-piece dir))
1542 ((eq dir :wild-inferiors)
1545 (error "invalid directory component: ~S" dir))))))
1546 (apply #'concatenate 'simple-string (pieces))))
1548 (defun unparse-logical-piece (thing)
1550 ((member :wild) "*")
1551 (simple-string thing)
1553 (collect ((strings))
1554 (dolist (piece (pattern-pieces thing))
1556 (simple-string (strings piece))
1558 (cond ((eq piece :wild-inferiors)
1560 ((eq piece :multi-char-wild)
1562 (t (error "invalid keyword: ~S" piece))))))
1563 (apply #'concatenate 'simple-string (strings))))))
1565 (defun unparse-logical-file (pathname)
1566 (declare (type pathname pathname))
1567 (collect ((strings))
1568 (let* ((name (%pathname-name pathname))
1569 (type (%pathname-type pathname))
1570 (version (%pathname-version pathname))
1571 (type-supplied (not (or (null type) (eq type :unspecific))))
1572 (version-supplied (not (or (null version)
1573 (eq version :unspecific)))))
1575 (when (and (null type)
1576 (typep name 'string)
1577 (position #\. name :start 1))
1578 (error "too many dots in the name: ~S" pathname))
1579 (strings (unparse-logical-piece name)))
1582 (error "cannot specify the type without a file: ~S" pathname))
1583 (when (typep type 'string)
1584 (when (position #\. type)
1585 (error "type component can't have a #\. inside: ~S" pathname)))
1587 (strings (unparse-logical-piece type)))
1588 (when version-supplied
1589 (unless type-supplied
1590 (error "cannot specify the version without a type: ~S" pathname))
1592 ((member :newest) (strings ".NEWEST"))
1593 ((member :wild) (strings ".*"))
1594 (fixnum (strings ".") (strings (format nil "~D" version))))))
1595 (apply #'concatenate 'simple-string (strings))))
1597 ;;; Unparse a logical pathname string.
1598 (defun unparse-enough-namestring (pathname defaults)
1599 (let* ((path-directory (pathname-directory pathname))
1600 (def-directory (pathname-directory defaults))
1602 ;; Go down the directory lists to see what matches. What's
1603 ;; left is what we want, more or less.
1604 (cond ((and (eq (first path-directory) (first def-directory))
1605 (eq (first path-directory) :absolute))
1606 ;; Both paths are :ABSOLUTE, so find where the
1607 ;; common parts end and return what's left
1608 (do* ((p (rest path-directory) (rest p))
1609 (d (rest def-directory) (rest d)))
1610 ((or (endp p) (endp d)
1611 (not (equal (first p) (first d))))
1614 ;; At least one path is :RELATIVE, so just return the
1615 ;; original path. If the original path is :RELATIVE,
1616 ;; then that's the right one. If PATH-DIRECTORY is
1617 ;; :ABSOLUTE, we want to return that except when
1618 ;; DEF-DIRECTORY is :ABSOLUTE, as handled above. so return
1619 ;; the original directory.
1621 (unparse-logical-namestring
1622 (make-pathname :host (pathname-host pathname)
1623 :directory enough-directory
1624 :name (pathname-name pathname)
1625 :type (pathname-type pathname)
1626 :version (pathname-version pathname)))))
1628 (defun unparse-logical-namestring (pathname)
1629 (declare (type logical-pathname pathname))
1630 (concatenate 'simple-string
1631 (logical-host-name (%pathname-host pathname)) ":"
1632 (unparse-logical-directory pathname)
1633 (unparse-logical-file pathname)))
1635 ;;;; logical pathname translations
1637 ;;; Verify that the list of translations consists of lists and prepare
1638 ;;; canonical translations. (Parse pathnames and expand out wildcards
1640 (defun canonicalize-logical-pathname-translations (translation-list host)
1641 (declare (type list translation-list) (type host host)
1643 (mapcar (lambda (translation)
1644 (destructuring-bind (from to) translation
1645 (list (if (typep from 'logical-pathname)
1647 (parse-namestring from host))
1651 (defun logical-pathname-translations (host)
1653 "Return the (logical) host object argument's list of translations."
1654 (declare (type (or string logical-host) host)
1656 (logical-host-translations (find-logical-host host)))
1658 (defun (setf logical-pathname-translations) (translations host)
1660 "Set the translations list for the logical host argument."
1661 (declare (type (or string logical-host) host)
1662 (type list translations)
1664 (let ((host (intern-logical-host host)))
1665 (setf (logical-host-canon-transls host)
1666 (canonicalize-logical-pathname-translations translations host))
1667 (setf (logical-host-translations host) translations)))
1669 (defun translate-logical-pathname (pathname &key)
1671 "Translate PATHNAME to a physical pathname, which is returned."
1672 (declare (type pathname-designator pathname)
1673 (values (or null pathname)))
1676 (dolist (x (logical-host-canon-transls (%pathname-host pathname))
1677 (error 'simple-file-error
1679 :format-control "no translation for ~S"
1680 :format-arguments (list pathname)))
1681 (destructuring-bind (from to) x
1682 (when (pathname-match-p pathname from)
1683 (return (translate-logical-pathname
1684 (translate-pathname pathname from to)))))))
1686 (t (translate-logical-pathname (pathname pathname)))))
1688 (defvar *logical-pathname-defaults*
1689 (%make-logical-pathname
1690 (make-logical-host :name (logical-word-or-lose "BOGUS"))
1691 :unspecific nil nil nil nil))
1693 (defun load-logical-pathname-translations (host)
1695 (declare (type string host)
1696 (values (member t nil)))
1697 (if (find-logical-host host nil)
1698 ;; This host is already defined, all is well and good.
1700 ;; ANSI: "The specific nature of the search is
1701 ;; implementation-defined." SBCL: doesn't search at all
1703 ;; FIXME: now that we have a SYS host that the system uses, it
1704 ;; might be cute to search in "SYS:TRANSLATIONS;<name>.LISP"
1705 (error "logical host ~S not found" host)))