0.8.7.24:
[sbcl.git] / src / code / target-pathname.lisp
1 ;;;; machine/filesystem-independent pathname functions
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
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.
11
12 (in-package "SB!IMPL")
13
14 #!-sb-fluid (declaim (freeze-type logical-pathname logical-host))
15 \f
16 ;;;; UNIX-HOST stuff
17
18 (def!struct (unix-host
19              (:make-load-form-fun make-unix-host-load-form)
20              (:include host
21                        (parse #'parse-unix-namestring)
22                        (unparse #'unparse-unix-namestring)
23                        (unparse-host #'unparse-unix-host)
24                        (unparse-directory #'unparse-unix-directory)
25                        (unparse-file #'unparse-unix-file)
26                        (unparse-enough #'unparse-unix-enough)
27                        (customary-case :lower))))
28
29 (defvar *unix-host* (make-unix-host))
30
31 (defun make-unix-host-load-form (host)
32   (declare (ignore host))
33   '*unix-host*)
34
35 ;;; Return a value suitable, e.g., for preinitializing
36 ;;; *DEFAULT-PATHNAME-DEFAULTS* before *DEFAULT-PATHNAME-DEFAULTS* is
37 ;;; initialized (at which time we can't safely call e.g. #'PATHNAME).
38 (defun make-trivial-default-pathname ()
39   (%make-pathname *unix-host* nil nil nil nil :newest))
40 \f
41 ;;; pathname methods
42
43 (def!method print-object ((pathname pathname) stream)
44   (let ((namestring (handler-case (namestring pathname)
45                       (error nil))))
46     (if namestring
47         (format stream "#P~S" namestring)
48         (print-unreadable-object (pathname stream :type t)
49           (format stream
50                   "~@<(with no namestring) ~_:HOST ~S ~_:DEVICE ~S ~_:DIRECTORY ~S ~
51                   ~_:NAME ~S ~_:TYPE ~S ~_:VERSION ~S~:>"
52                   (%pathname-host pathname)
53                   (%pathname-device pathname)
54                   (%pathname-directory pathname)
55                   (%pathname-name pathname)
56                   (%pathname-type pathname)
57                   (%pathname-version pathname))))))
58
59 (def!method make-load-form ((pathname pathname) &optional environment)
60   (make-load-form-saving-slots pathname :environment environment))
61
62 ;;; The potential conflict with search lists requires isolating the
63 ;;; printed representation to use the i/o macro #.(logical-pathname
64 ;;; <path-designator>).
65 ;;;
66 ;;; FIXME: We don't use search lists any more, so that comment is
67 ;;; stale, right?
68 (def!method print-object ((pathname logical-pathname) stream)
69   (let ((namestring (handler-case (namestring pathname)
70                       (error nil))))
71     (if namestring
72         (format stream "#.(CL:LOGICAL-PATHNAME ~S)" namestring)
73         (print-unreadable-object (pathname stream :type t)
74           (format
75            stream
76            "~_:HOST ~S ~_:DIRECTORY ~S ~_:FILE ~S ~_:NAME ~S ~_:VERSION ~S"
77            (%pathname-host pathname)
78            (%pathname-directory pathname)
79            (%pathname-name pathname)
80            (%pathname-type pathname)
81            (%pathname-version pathname))))))
82 \f
83 ;;; A pathname is logical if the host component is a logical host.
84 ;;; This constructor is used to make an instance of the correct type
85 ;;; from parsed arguments.
86 (defun %make-maybe-logical-pathname (host device directory name type version)
87   ;; We canonicalize logical pathname components to uppercase. ANSI
88   ;; doesn't strictly require this, leaving it up to the implementor;
89   ;; but the arguments given in the X3J13 cleanup issue
90   ;; PATHNAME-LOGICAL:ADD seem compelling: we should canonicalize the
91   ;; case, and uppercase is the ordinary way to do that.
92   (flet ((upcase-maybe (x) (typecase x (string (logical-word-or-lose x)) (t x))))
93     (if (typep host 'logical-host)
94         (%make-logical-pathname host
95                                 :unspecific
96                                 (mapcar #'upcase-maybe directory)
97                                 (upcase-maybe name)
98                                 (upcase-maybe type)
99                                 version)
100         (progn
101           (aver (eq host *unix-host*))
102           (%make-pathname host device directory name type version)))))
103
104 ;;; Hash table searching maps a logical pathname's host to its
105 ;;; physical pathname translation.
106 (defvar *logical-hosts* (make-hash-table :test 'equal))
107 \f
108 ;;;; patterns
109
110 (def!method make-load-form ((pattern pattern) &optional environment)
111   (make-load-form-saving-slots pattern :environment environment))
112
113 (def!method print-object ((pattern pattern) stream)
114   (print-unreadable-object (pattern stream :type t)
115     (if *print-pretty*
116         (let ((*print-escape* t))
117           (pprint-fill stream (pattern-pieces pattern) nil))
118         (prin1 (pattern-pieces pattern) stream))))
119
120 (defun pattern= (pattern1 pattern2)
121   (declare (type pattern pattern1 pattern2))
122   (let ((pieces1 (pattern-pieces pattern1))
123         (pieces2 (pattern-pieces pattern2)))
124     (and (= (length pieces1) (length pieces2))
125          (every (lambda (piece1 piece2)
126                   (typecase piece1
127                     (simple-string
128                      (and (simple-string-p piece2)
129                           (string= piece1 piece2)))
130                     (cons
131                      (and (consp piece2)
132                           (eq (car piece1) (car piece2))
133                           (string= (cdr piece1) (cdr piece2))))
134                     (t
135                      (eq piece1 piece2))))
136                 pieces1
137                 pieces2))))
138
139 ;;; If the string matches the pattern returns the multiple values T
140 ;;; and a list of the matched strings.
141 (defun pattern-matches (pattern string)
142   (declare (type pattern pattern)
143            (type simple-string string))
144   (let ((len (length string)))
145     (labels ((maybe-prepend (subs cur-sub chars)
146                (if cur-sub
147                    (let* ((len (length chars))
148                           (new (make-string len))
149                           (index len))
150                      (dolist (char chars)
151                        (setf (schar new (decf index)) char))
152                      (cons new subs))
153                    subs))
154              (matches (pieces start subs cur-sub chars)
155                (if (null pieces)
156                    (if (= start len)
157                        (values t (maybe-prepend subs cur-sub chars))
158                        (values nil nil))
159                    (let ((piece (car pieces)))
160                      (etypecase piece
161                        (simple-string
162                         (let ((end (+ start (length piece))))
163                           (and (<= end len)
164                                (string= piece string
165                                         :start2 start :end2 end)
166                                (matches (cdr pieces) end
167                                         (maybe-prepend subs cur-sub chars)
168                                         nil nil))))
169                        (list
170                         (ecase (car piece)
171                           (:character-set
172                            (and (< start len)
173                                 (let ((char (schar string start)))
174                                   (if (find char (cdr piece) :test #'char=)
175                                       (matches (cdr pieces) (1+ start) subs t
176                                                (cons char chars))))))))
177                        ((member :single-char-wild)
178                         (and (< start len)
179                              (matches (cdr pieces) (1+ start) subs t
180                                       (cons (schar string start) chars))))
181                        ((member :multi-char-wild)
182                         (multiple-value-bind (won new-subs)
183                             (matches (cdr pieces) start subs t chars)
184                           (if won
185                               (values t new-subs)
186                               (and (< start len)
187                                    (matches pieces (1+ start) subs t
188                                             (cons (schar string start)
189                                                   chars)))))))))))
190       (multiple-value-bind (won subs)
191           (matches (pattern-pieces pattern) 0 nil nil nil)
192         (values won (reverse subs))))))
193
194 ;;; PATHNAME-MATCH-P for directory components
195 (defun directory-components-match (thing wild)
196   (or (eq thing wild)
197       (eq wild :wild)
198       ;; If THING has a null directory, assume that it matches
199       ;; (:ABSOLUTE :WILD-INFERIORS) or (:RELATIVE :WILD-INFERIORS).
200       (and (consp wild)
201            (null thing)
202            (member (first wild) '(:absolute :relative))
203            (eq (second wild) :wild-inferiors))
204       (and (consp wild)
205            (let ((wild1 (first wild)))
206              (if (eq wild1 :wild-inferiors)
207                  (let ((wild-subdirs (rest wild)))
208                    (or (null wild-subdirs)
209                        (loop
210                          (when (directory-components-match thing wild-subdirs)
211                            (return t))
212                          (pop thing)
213                          (unless thing (return nil)))))
214                  (and (consp thing)
215                       (components-match (first thing) wild1)
216                       (directory-components-match (rest thing)
217                                                   (rest wild))))))))
218
219 ;;; Return true if pathname component THING is matched by WILD. (not
220 ;;; commutative)
221 (defun components-match (thing wild)
222   (declare (type (or pattern symbol simple-string integer) thing wild))
223   (or (eq thing wild)
224       (eq wild :wild)
225       (typecase thing
226         (simple-base-string
227          ;; String is matched by itself, a matching pattern or :WILD.
228          (typecase wild
229            (pattern
230             (values (pattern-matches wild thing)))
231            (simple-base-string
232             (string= thing wild))))
233         (pattern
234          ;; A pattern is only matched by an identical pattern.
235          (and (pattern-p wild) (pattern= thing wild)))
236         (integer
237          ;; An integer (version number) is matched by :WILD or the
238          ;; same integer. This branch will actually always be NIL as
239          ;; long as the version is a fixnum.
240          (eql thing wild)))))
241
242 ;;; a predicate for comparing two pathname slot component sub-entries
243 (defun compare-component (this that)
244   (or (eql this that)
245       (typecase this
246         (simple-string
247          (and (simple-string-p that)
248               (string= this that)))
249         (pattern
250          (and (pattern-p that)
251               (pattern= this that)))
252         (cons
253          (and (consp that)
254               (compare-component (car this) (car that))
255               (compare-component (cdr this) (cdr that)))))))
256 \f
257 ;;;; pathname functions
258
259 (defun pathname= (pathname1 pathname2)
260   (declare (type pathname pathname1)
261            (type pathname pathname2))
262   (and (eq (%pathname-host pathname1)
263            (%pathname-host pathname2))
264        (compare-component (%pathname-device pathname1)
265                           (%pathname-device pathname2))
266        (compare-component (%pathname-directory pathname1)
267                           (%pathname-directory pathname2))
268        (compare-component (%pathname-name pathname1)
269                           (%pathname-name pathname2))
270        (compare-component (%pathname-type pathname1)
271                           (%pathname-type pathname2))
272        (or (eq (%pathname-host pathname1) *unix-host*)
273            (compare-component (%pathname-version pathname1)
274                               (%pathname-version pathname2)))))
275
276 ;;; Convert PATHNAME-DESIGNATOR (a pathname, or string, or
277 ;;; stream), into a pathname in pathname.
278 ;;;
279 ;;; FIXME: was rewritten, should be tested (or rewritten again, this
280 ;;; time using ONCE-ONLY, *then* tested)
281 ;;; FIXME: become SB!XC:DEFMACRO inside EVAL-WHEN (COMPILE EVAL)?
282 (defmacro with-pathname ((pathname pathname-designator) &body body)
283   (let ((pd0 (gensym)))
284     `(let* ((,pd0 ,pathname-designator)
285             (,pathname (etypecase ,pd0
286                          (pathname ,pd0)
287                          (string (parse-namestring ,pd0))
288                          (file-stream (file-name ,pd0)))))
289        ,@body)))
290
291 ;;; Convert the var, a host or string name for a host, into a
292 ;;; LOGICAL-HOST structure or nil if not defined.
293 ;;;
294 ;;; pw notes 1/12/97 this potentially useful macro is not used anywhere
295 ;;; and 'find-host' is not defined. 'find-logical-host' seems to be needed.
296 #|
297 (defmacro with-host ((var expr) &body body)
298   `(let ((,var (let ((,var ,expr))
299                  (typecase ,var
300                    (logical-host ,var)
301                    (string (find-logical-host ,var nil))
302                    (t nil)))))
303      ,@body))
304 |#
305
306 (defun pathname (thing)
307   #!+sb-doc
308   "Convert thing (a pathname, string or stream) into a pathname."
309   (declare (type pathname-designator thing))
310   (with-pathname (pathname thing)
311     pathname))
312
313 ;;; Change the case of thing if DIDDLE-P.
314 (defun maybe-diddle-case (thing diddle-p)
315   (if (and diddle-p (not (or (symbolp thing) (integerp thing))))
316       (labels ((check-for (pred in)
317                  (typecase in
318                    (pattern
319                     (dolist (piece (pattern-pieces in))
320                       (when (typecase piece
321                               (simple-string
322                                (check-for pred piece))
323                               (cons
324                                (case (car piece)
325                                  (:character-set
326                                   (check-for pred (cdr piece))))))
327                         (return t))))
328                    (list
329                     (dolist (x in)
330                       (when (check-for pred x)
331                         (return t))))
332                    (simple-base-string
333                     (dotimes (i (length in))
334                       (when (funcall pred (schar in i))
335                         (return t))))
336                    (t nil)))
337                (diddle-with (fun thing)
338                  (typecase thing
339                    (pattern
340                     (make-pattern
341                      (mapcar (lambda (piece)
342                                (typecase piece
343                                  (simple-base-string
344                                   (funcall fun piece))
345                                  (cons
346                                   (case (car piece)
347                                     (:character-set
348                                      (cons :character-set
349                                            (funcall fun (cdr piece))))
350                                     (t
351                                      piece)))
352                                  (t
353                                   piece)))
354                              (pattern-pieces thing))))
355                    (list
356                     (mapcar fun thing))
357                    (simple-base-string
358                     (funcall fun thing))
359                    (t
360                     thing))))
361         (let ((any-uppers (check-for #'upper-case-p thing))
362               (any-lowers (check-for #'lower-case-p thing)))
363           (cond ((and any-uppers any-lowers)
364                  ;; mixed case, stays the same
365                  thing)
366                 (any-uppers
367                  ;; all uppercase, becomes all lower case
368                  (diddle-with (lambda (x) (if (stringp x)
369                                               (string-downcase x)
370                                               x)) thing))
371                 (any-lowers
372                  ;; all lowercase, becomes all upper case
373                  (diddle-with (lambda (x) (if (stringp x)
374                                               (string-upcase x)
375                                               x)) thing))
376                 (t
377                  ;; no letters?  I guess just leave it.
378                  thing))))
379       thing))
380
381 (defun merge-directories (dir1 dir2 diddle-case)
382   (if (or (eq (car dir1) :absolute)
383           (null dir2))
384       dir1
385       (let ((results nil))
386         (flet ((add (dir)
387                  (if (and (eq dir :back)
388                           results
389                           (not (member (car results)
390                                        '(:back :wild-inferiors))))
391                      (pop results)
392                      (push dir results))))
393           (dolist (dir (maybe-diddle-case dir2 diddle-case))
394             (add dir))
395           (dolist (dir (cdr dir1))
396             (add dir)))
397         (reverse results))))
398
399 (defun merge-pathnames (pathname
400                         &optional
401                         (defaults *default-pathname-defaults*)
402                         (default-version :newest))
403   #!+sb-doc
404   "Construct a filled in pathname by completing the unspecified components
405    from the defaults."
406   (declare (type pathname-designator pathname)
407            (type pathname-designator defaults)
408            (values pathname))
409   (with-pathname (defaults defaults)
410     (let ((pathname (let ((*default-pathname-defaults* defaults))
411                       (pathname pathname))))
412       (let* ((default-host (%pathname-host defaults))
413              (pathname-host (%pathname-host pathname))
414              (diddle-case
415               (and default-host pathname-host
416                    (not (eq (host-customary-case default-host)
417                             (host-customary-case pathname-host))))))
418         (%make-maybe-logical-pathname
419          (or pathname-host default-host)
420          (or (%pathname-device pathname)
421              (maybe-diddle-case (%pathname-device defaults)
422                                 diddle-case))
423          (merge-directories (%pathname-directory pathname)
424                             (%pathname-directory defaults)
425                             diddle-case)
426          (or (%pathname-name pathname)
427              (maybe-diddle-case (%pathname-name defaults)
428                                 diddle-case))
429          (or (%pathname-type pathname)
430              (maybe-diddle-case (%pathname-type defaults)
431                                 diddle-case))
432          (or (%pathname-version pathname)
433              (and (not (%pathname-name pathname)) (%pathname-version defaults))
434              default-version))))))
435
436 (defun import-directory (directory diddle-case)
437   (etypecase directory
438     (null nil)
439     ((member :wild) '(:absolute :wild-inferiors))
440     ((member :unspecific) '(:relative))
441     (list
442      (collect ((results))
443        (results (pop directory))
444        (dolist (piece directory)
445          (cond ((member piece '(:wild :wild-inferiors :up :back))
446                 (results piece))
447                ((or (simple-string-p piece) (pattern-p piece))
448                 (results (maybe-diddle-case piece diddle-case)))
449                ((stringp piece)
450                 (results (maybe-diddle-case (coerce piece 'simple-string)
451                                             diddle-case)))
452                (t
453                 (error "~S is not allowed as a directory component." piece))))
454        (results)))
455     (simple-string
456      `(:absolute
457        ,(maybe-diddle-case directory diddle-case)))
458     (string
459      `(:absolute
460        ,(maybe-diddle-case (coerce directory 'simple-string)
461                            diddle-case)))))
462
463 (defun make-pathname (&key host
464                            (device nil devp)
465                            (directory nil dirp)
466                            (name nil namep)
467                            (type nil typep)
468                            (version nil versionp)
469                            defaults
470                            (case :local))
471   #!+sb-doc
472   "Makes a new pathname from the component arguments. Note that host is
473 a host-structure or string."
474   (declare (type (or string host pathname-component-tokens) host)
475            (type (or string pathname-component-tokens) device)
476            (type (or list string pattern pathname-component-tokens) directory)
477            (type (or string pattern pathname-component-tokens) name type)
478            (type (or integer pathname-component-tokens (member :newest))
479                  version)
480            (type (or pathname-designator null) defaults)
481            (type (member :common :local) case))
482   (let* ((defaults (when defaults
483                      (with-pathname (defaults defaults) defaults)))
484          (default-host (if defaults
485                            (%pathname-host defaults)
486                            (pathname-host *default-pathname-defaults*)))
487          ;; Raymond Toy writes: CLHS says make-pathname can take a
488          ;; string (as a logical-host) for the host part. We map that
489          ;; string into the corresponding logical host structure.
490          ;;
491          ;; Paul Werkowski writes:
492          ;; HyperSpec says for the arg to MAKE-PATHNAME;
493          ;; "host---a valid physical pathname host. ..."
494          ;; where it probably means -- a valid pathname host.
495          ;; "valid pathname host n. a valid physical pathname host or
496          ;; a valid logical pathname host."
497          ;; and defines
498          ;; "valid physical pathname host n. any of a string,
499          ;; a list of strings, or the symbol :unspecific,
500          ;; that is recognized by the implementation as the name of a host."
501          ;; "valid logical pathname host n. a string that has been defined
502          ;; as the name of a logical host. ..."
503          ;; HS is silent on what happens if the :HOST arg is NOT one of these.
504          ;; It seems an error message is appropriate.
505          (host (typecase host
506                  (host host)            ; A valid host, use it.
507                  ((string 0) *unix-host*) ; "" cannot be a logical host
508                  (string (find-logical-host host t)) ; logical-host or lose.
509                  (t default-host)))     ; unix-host
510          (diddle-args (and (eq (host-customary-case host) :lower)
511                            (eq case :common)))
512          (diddle-defaults
513           (not (eq (host-customary-case host)
514                    (host-customary-case default-host))))
515          (dev (if devp device (if defaults (%pathname-device defaults))))
516          (dir (import-directory directory diddle-args))
517          (ver (cond
518                (versionp version)
519                (defaults (%pathname-version defaults))
520                (t nil))))
521     (when (and defaults (not dirp))
522       (setf dir
523             (merge-directories dir
524                                (%pathname-directory defaults)
525                                diddle-defaults)))
526
527     (macrolet ((pick (var varp field)
528                  `(cond ((or (simple-string-p ,var)
529                              (pattern-p ,var))
530                          (maybe-diddle-case ,var diddle-args))
531                         ((stringp ,var)
532                          (maybe-diddle-case (coerce ,var 'simple-string)
533                                             diddle-args))
534                         (,varp
535                          (maybe-diddle-case ,var diddle-args))
536                         (defaults
537                          (maybe-diddle-case (,field defaults)
538                                             diddle-defaults))
539                         (t
540                          nil))))
541       (%make-maybe-logical-pathname host
542                                     dev ; forced to :UNSPECIFIC when logical
543                                     dir
544                                     (pick name namep %pathname-name)
545                                     (pick type typep %pathname-type)
546                                     ver))))
547
548 (defun pathname-host (pathname &key (case :local))
549   #!+sb-doc
550   "Return PATHNAME's host."
551   (declare (type pathname-designator pathname)
552            (type (member :local :common) case)
553            (values host)
554            (ignore case))
555   (with-pathname (pathname pathname)
556     (%pathname-host pathname)))
557
558 (defun pathname-device (pathname &key (case :local))
559   #!+sb-doc
560   "Return PATHNAME's device."
561   (declare (type pathname-designator pathname)
562            (type (member :local :common) case))
563   (with-pathname (pathname pathname)
564     (maybe-diddle-case (%pathname-device pathname)
565                        (and (eq case :common)
566                             (eq (host-customary-case
567                                  (%pathname-host pathname))
568                                 :lower)))))
569
570 (defun pathname-directory (pathname &key (case :local))
571   #!+sb-doc
572   "Return PATHNAME's directory."
573   (declare (type pathname-designator pathname)
574            (type (member :local :common) case))
575   (with-pathname (pathname pathname)
576     (maybe-diddle-case (%pathname-directory pathname)
577                        (and (eq case :common)
578                             (eq (host-customary-case
579                                  (%pathname-host pathname))
580                                 :lower)))))
581 (defun pathname-name (pathname &key (case :local))
582   #!+sb-doc
583   "Return PATHNAME's name."
584   (declare (type pathname-designator pathname)
585            (type (member :local :common) case))
586   (with-pathname (pathname pathname)
587     (maybe-diddle-case (%pathname-name pathname)
588                        (and (eq case :common)
589                             (eq (host-customary-case
590                                  (%pathname-host pathname))
591                                 :lower)))))
592
593 (defun pathname-type (pathname &key (case :local))
594   #!+sb-doc
595   "Return PATHNAME's type."
596   (declare (type pathname-designator pathname)
597            (type (member :local :common) case))
598   (with-pathname (pathname pathname)
599     (maybe-diddle-case (%pathname-type pathname)
600                        (and (eq case :common)
601                             (eq (host-customary-case
602                                  (%pathname-host pathname))
603                                 :lower)))))
604
605 (defun pathname-version (pathname)
606   #!+sb-doc
607   "Return PATHNAME's version."
608   (declare (type pathname-designator pathname))
609   (with-pathname (pathname pathname)
610     (%pathname-version pathname)))
611 \f
612 ;;;; namestrings
613
614 ;;; Handle the case for PARSE-NAMESTRING parsing a potentially
615 ;;; syntactically valid logical namestring with an explicit host.
616 ;;;
617 ;;; This then isn't fully general -- we are relying on the fact that
618 ;;; we will only pass to parse-namestring namestring with an explicit
619 ;;; logical host, so that we can pass the host return from
620 ;;; parse-logical-namestring through to %PARSE-NAMESTRING as a truth
621 ;;; value. Yeah, this is probably a KLUDGE - CSR, 2002-04-18
622 (defun parseable-logical-namestring-p (namestr start end)
623   (catch 'exit
624     (handler-bind
625         ((namestring-parse-error (lambda (c)
626                                    (declare (ignore c))
627                                    (throw 'exit nil))))
628       (let ((colon (position #\: namestr :start start :end end)))
629         (when colon
630           (let ((potential-host
631                  (logical-word-or-lose (subseq namestr start colon))))
632             ;; depending on the outcome of CSR comp.lang.lisp post
633             ;; "can PARSE-NAMESTRING create logical hosts", we may need
634             ;; to do things with potential-host (create it
635             ;; temporarily, parse the namestring and unintern the
636             ;; logical host potential-host on failure.
637             (declare (ignore potential-host))
638             (let ((result
639                    (handler-bind
640                        ((simple-type-error (lambda (c)
641                                              (declare (ignore c))
642                                              (throw 'exit nil))))
643                      (parse-logical-namestring namestr start end))))
644               ;; if we got this far, we should have an explicit host
645               ;; (first return value of parse-logical-namestring)
646               (aver result)
647               result)))))))
648
649 ;;; Handle the case where PARSE-NAMESTRING is actually parsing a
650 ;;; namestring. We pick off the :JUNK-ALLOWED case then find a host to
651 ;;; use for parsing, call the parser, then check whether the host matches.
652 (defun %parse-namestring (namestr host defaults start end junk-allowed)
653   (declare (type (or host null) host)
654            (type string namestr)
655            (type index start)
656            (type (or index null) end))
657   (cond
658     (junk-allowed
659      (handler-case
660          (%parse-namestring namestr host defaults start end nil)
661        (namestring-parse-error (condition)
662          (values nil (namestring-parse-error-offset condition)))))
663     (t
664      (let* ((end (%check-vector-sequence-bounds namestr start end)))
665        (multiple-value-bind (new-host device directory file type version)
666            ;; Comments below are quotes from the HyperSpec
667            ;; PARSE-NAMESTRING entry, reproduced here to demonstrate
668            ;; that we actually have to do things this way rather than
669            ;; some possibly more logical way. - CSR, 2002-04-18
670            (cond
671              ;; "If host is a logical host then thing is parsed as a
672              ;; logical pathname namestring on the host."
673              (host (funcall (host-parse host) namestr start end))
674              ;; "If host is nil and thing is a syntactically valid
675              ;; logical pathname namestring containing an explicit
676              ;; host, then it is parsed as a logical pathname
677              ;; namestring."
678              ((parseable-logical-namestring-p namestr start end)
679               (parse-logical-namestring namestr start end))
680              ;; "If host is nil, default-pathname is a logical
681              ;; pathname, and thing is a syntactically valid logical
682              ;; pathname namestring without an explicit host, then it
683              ;; is parsed as a logical pathname namestring on the
684              ;; host that is the host component of default-pathname."
685              ;;
686              ;; "Otherwise, the parsing of thing is
687              ;; implementation-defined."
688              ;;
689              ;; Both clauses are handled here, as the default
690              ;; *DEFAULT-PATHNAME-DEFAULTS has a SB-IMPL::UNIX-HOST
691              ;; for a host.
692              ((pathname-host defaults)
693               (funcall (host-parse (pathname-host defaults))
694                        namestr
695                        start
696                        end))
697              ;; I don't think we should ever get here, as the default
698              ;; host will always have a non-null HOST, given that we
699              ;; can't create a new pathname without going through
700              ;; *DEFAULT-PATHNAME-DEFAULTS*, which has a non-null
701              ;; host...
702              (t (bug "Fallen through COND in %PARSE-NAMESTRING")))
703          (when (and host new-host (not (eq new-host host)))
704            (error 'simple-type-error
705                   :datum new-host
706                   ;; Note: ANSI requires that this be a TYPE-ERROR,
707                   ;; but there seems to be no completely correct
708                   ;; value to use for TYPE-ERROR-EXPECTED-TYPE.
709                   ;; Instead, we return a sort of "type error allowed
710                   ;; type", trying to say "it would be OK if you
711                   ;; passed NIL as the host value" but not mentioning
712                   ;; that a matching string would be OK too.
713                   :expected-type 'null
714                   :format-control
715                   "The host in the namestring, ~S,~@
716                     does not match the explicit HOST argument, ~S."
717                   :format-arguments (list new-host host)))
718          (let ((pn-host (or new-host host (pathname-host defaults))))
719            (values (%make-maybe-logical-pathname
720                     pn-host device directory file type version)
721                    end)))))))
722
723 ;;; If NAMESTR begins with a colon-terminated, defined, logical host,
724 ;;; then return that host, otherwise return NIL.
725 (defun extract-logical-host-prefix (namestr start end)
726   (declare (type simple-base-string namestr)
727            (type index start end)
728            (values (or logical-host null)))
729   (let ((colon-pos (position #\: namestr :start start :end end)))
730     (if colon-pos
731         (values (gethash (nstring-upcase (subseq namestr start colon-pos))
732                          *logical-hosts*))
733         nil)))
734
735 (defun parse-namestring (thing
736                          &optional
737                          host
738                          (defaults *default-pathname-defaults*)
739                          &key (start 0) end junk-allowed)
740   (declare (type pathname-designator thing)
741            (type (or list host string (member :unspecific)) host)
742            (type pathname defaults)
743            (type index start)
744            (type (or index null) end)
745            (type (or t null) junk-allowed)
746            (values (or null pathname) (or null index)))
747   ;; Generally, redundant specification of information in software,
748   ;; whether in code or in comments, is bad. However, the ANSI spec
749   ;; for this is messy enough that it's hard to hold in short-term
750   ;; memory, so I've recorded these redundant notes on the
751   ;; implications of the ANSI spec.
752   ;; 
753   ;; According to the ANSI spec, HOST can be a valid pathname host, or
754   ;; a logical host, or NIL.
755   ;;
756   ;; A valid pathname host can be a valid physical pathname host or a
757   ;; valid logical pathname host.
758   ;; 
759   ;; A valid physical pathname host is "any of a string, a list of
760   ;; strings, or the symbol :UNSPECIFIC, that is recognized by the
761   ;; implementation as the name of a host". In SBCL as of 0.6.9.8,
762   ;; that means :UNSPECIFIC: though someday we might want to
763   ;; generalize it to allow strings like "RTFM.MIT.EDU" or lists like
764   ;; '("RTFM" "MIT" "EDU"), that's not supported now.
765   ;; 
766   ;; A valid logical pathname host is a string which has been defined as
767   ;; the name of a logical host, as with LOAD-LOGICAL-PATHNAME-TRANSLATIONS.
768   ;; 
769   ;; A logical host is an object of implementation-dependent nature. In
770   ;; SBCL, it's a member of the HOST class (a subclass of STRUCTURE-OBJECT).
771   (let ((found-host (etypecase host
772                       ((string 0)
773                        ;; This is a special host. It's not valid as a
774                        ;; logical host, so it is a sensible thing to
775                        ;; designate the physical Unix host object. So
776                        ;; we do that.
777                        *unix-host*)
778                       (string
779                        ;; In general ANSI-compliant Common Lisps, a
780                        ;; string might also be a physical pathname host,
781                        ;; but ANSI leaves this up to the implementor,
782                        ;; and in SBCL we don't do it, so it must be a
783                        ;; logical host.
784                        (find-logical-host host))
785                       ((or null (member :unspecific))
786                        ;; CLHS says that HOST=:UNSPECIFIC has
787                        ;; implementation-defined behavior. We
788                        ;; just turn it into NIL.
789                        nil)
790                       (list
791                        ;; ANSI also allows LISTs to designate hosts,
792                        ;; but leaves its interpretation
793                        ;; implementation-defined. Our interpretation
794                        ;; is that it's unsupported.:-|
795                        (error "A LIST representing a pathname host is not ~
796                               supported in this implementation:~%  ~S"
797                               host))
798                       (host
799                        host))))
800     (declare (type (or null host) found-host))
801     (etypecase thing
802       (simple-string
803        (%parse-namestring thing found-host defaults start end junk-allowed))
804       (string
805        (%parse-namestring (coerce thing 'simple-string)
806                           found-host defaults start end junk-allowed))
807       (pathname
808        (let ((defaulted-host (or found-host (%pathname-host defaults))))
809          (declare (type host defaulted-host))
810          (unless (eq defaulted-host (%pathname-host thing))
811            (error "The HOST argument doesn't match the pathname host:~%  ~
812                   ~S and ~S."
813                   defaulted-host (%pathname-host thing))))
814        (values thing start))
815       (stream
816        (let ((name (file-name thing)))
817          (unless name
818            (error "can't figure out the file associated with stream:~%  ~S"
819                   thing))
820          (values name nil))))))
821
822 (defun namestring (pathname)
823   #!+sb-doc
824   "Construct the full (name)string form of the pathname."
825   (declare (type pathname-designator pathname))
826   (with-pathname (pathname pathname)
827     (when pathname
828       (let ((host (%pathname-host pathname)))
829         (unless host
830           (error "can't determine the namestring for pathnames with no ~
831                   host:~%  ~S" pathname))
832         (funcall (host-unparse host) pathname)))))
833
834 (defun host-namestring (pathname)
835   #!+sb-doc
836   "Return a string representation of the name of the host in the pathname."
837   (declare (type pathname-designator pathname))
838   (with-pathname (pathname pathname)
839     (let ((host (%pathname-host pathname)))
840       (if host
841           (funcall (host-unparse-host host) pathname)
842           (error
843            "can't determine the namestring for pathnames with no host:~%  ~S"
844            pathname)))))
845
846 (defun directory-namestring (pathname)
847   #!+sb-doc
848   "Return a string representation of the directories used in the pathname."
849   (declare (type pathname-designator pathname))
850   (with-pathname (pathname pathname)
851     (let ((host (%pathname-host pathname)))
852       (if host
853           (funcall (host-unparse-directory host) pathname)
854           (error
855            "can't determine the namestring for pathnames with no host:~%  ~S"
856            pathname)))))
857
858 (defun file-namestring (pathname)
859   #!+sb-doc
860   "Return a string representation of the name used in the pathname."
861   (declare (type pathname-designator pathname))
862   (with-pathname (pathname pathname)
863     (let ((host (%pathname-host pathname)))
864       (if host
865           (funcall (host-unparse-file host) pathname)
866           (error
867            "can't determine the namestring for pathnames with no host:~%  ~S"
868            pathname)))))
869
870 (defun enough-namestring (pathname
871                           &optional
872                           (defaults *default-pathname-defaults*))
873   #!+sb-doc
874   "Return an abbreviated pathname sufficent to identify the pathname relative
875    to the defaults."
876   (declare (type pathname-designator pathname))
877   (with-pathname (pathname pathname)
878     (let ((host (%pathname-host pathname)))
879       (if host
880           (with-pathname (defaults defaults)
881             (funcall (host-unparse-enough host) pathname defaults))
882           (error
883            "can't determine the namestring for pathnames with no host:~%  ~S"
884            pathname)))))
885 \f
886 ;;;; wild pathnames
887
888 (defun wild-pathname-p (pathname &optional field-key)
889   #!+sb-doc
890   "Predicate for determining whether pathname contains any wildcards."
891   (declare (type pathname-designator pathname)
892            (type (member nil :host :device :directory :name :type :version)
893                  field-key))
894   (with-pathname (pathname pathname)
895     (flet ((frob (x)
896              (or (pattern-p x) (member x '(:wild :wild-inferiors)))))
897       (ecase field-key
898         ((nil)
899          (or (wild-pathname-p pathname :host)
900              (wild-pathname-p pathname :device)
901              (wild-pathname-p pathname :directory)
902              (wild-pathname-p pathname :name)
903              (wild-pathname-p pathname :type)
904              (wild-pathname-p pathname :version)))
905         (:host (frob (%pathname-host pathname)))
906         (:device (frob (%pathname-host pathname)))
907         (:directory (some #'frob (%pathname-directory pathname)))
908         (:name (frob (%pathname-name pathname)))
909         (:type (frob (%pathname-type pathname)))
910         (:version (frob (%pathname-version pathname)))))))
911
912 (defun pathname-match-p (in-pathname in-wildname)
913   #!+sb-doc
914   "Pathname matches the wildname template?"
915   (declare (type pathname-designator in-pathname))
916   (with-pathname (pathname in-pathname)
917     (with-pathname (wildname in-wildname)
918       (macrolet ((frob (field &optional (op 'components-match))
919                    `(or (null (,field wildname))
920                         (,op (,field pathname) (,field wildname)))))
921         (and (or (null (%pathname-host wildname))
922                  (eq (%pathname-host wildname) (%pathname-host pathname)))
923              (frob %pathname-device)
924              (frob %pathname-directory directory-components-match)
925              (frob %pathname-name)
926              (frob %pathname-type)
927              (or (eq (%pathname-host wildname) *unix-host*)
928                  (frob %pathname-version)))))))
929
930 ;;; Place the substitutions into the pattern and return the string or pattern
931 ;;; that results. If DIDDLE-CASE is true, we diddle the result case as well,
932 ;;; in case we are translating between hosts with difference conventional case.
933 ;;; The second value is the tail of subs with all of the values that we used up
934 ;;; stripped off. Note that PATTERN-MATCHES matches all consecutive wildcards
935 ;;; as a single string, so we ignore subsequent contiguous wildcards.
936 (defun substitute-into (pattern subs diddle-case)
937   (declare (type pattern pattern)
938            (type list subs)
939            (values (or simple-base-string pattern) list))
940   (let ((in-wildcard nil)
941         (pieces nil)
942         (strings nil))
943     (dolist (piece (pattern-pieces pattern))
944       (cond ((simple-string-p piece)
945              (push piece strings)
946              (setf in-wildcard nil))
947             (in-wildcard)
948             (t
949              (setf in-wildcard t)
950              (unless subs
951                (error "not enough wildcards in FROM pattern to match ~
952                        TO pattern:~%  ~S"
953                       pattern))
954              (let ((sub (pop subs)))
955                (typecase sub
956                  (pattern
957                   (when strings
958                     (push (apply #'concatenate 'simple-string
959                                  (nreverse strings))
960                           pieces))
961                   (dolist (piece (pattern-pieces sub))
962                     (push piece pieces)))
963                  (simple-string
964                   (push sub strings))
965                  (t
966                   (error "can't substitute this into the middle of a word:~
967                           ~%  ~S"
968                          sub)))))))
969
970     (when strings
971       (push (apply #'concatenate 'simple-string (nreverse strings))
972             pieces))
973     (values
974      (maybe-diddle-case
975       (if (and pieces (simple-string-p (car pieces)) (null (cdr pieces)))
976           (car pieces)
977           (make-pattern (nreverse pieces)))
978       diddle-case)
979      subs)))
980
981 ;;; Called when we can't see how source and from matched.
982 (defun didnt-match-error (source from)
983   (error "Pathname components from SOURCE and FROM args to TRANSLATE-PATHNAME~@
984           did not match:~%  ~S ~S"
985          source from))
986
987 ;;; Do TRANSLATE-COMPONENT for all components except host, directory
988 ;;; and version.
989 (defun translate-component (source from to diddle-case)
990   (typecase to
991     (pattern
992      (typecase from
993        (pattern
994         (typecase source
995           (pattern
996            (if (pattern= from source)
997                source
998                (didnt-match-error source from)))
999           (simple-string
1000            (multiple-value-bind (won subs) (pattern-matches from source)
1001              (if won
1002                  (values (substitute-into to subs diddle-case))
1003                  (didnt-match-error source from))))
1004           (t
1005            (maybe-diddle-case source diddle-case))))
1006        ((member :wild)
1007         (values (substitute-into to (list source) diddle-case)))
1008        (t
1009         (if (components-match source from)
1010             (maybe-diddle-case source diddle-case)
1011             (didnt-match-error source from)))))
1012     ((member nil :wild)
1013      (maybe-diddle-case source diddle-case))
1014     (t
1015      (if (components-match source from)
1016          to
1017          (didnt-match-error source from)))))
1018
1019 ;;; Return a list of all the things that we want to substitute into the TO
1020 ;;; pattern (the things matched by from on source.)  When From contains
1021 ;;; :WILD-INFERIORS, the result contains a sublist of the matched source
1022 ;;; subdirectories.
1023 (defun compute-directory-substitutions (orig-source orig-from)
1024   (let ((source orig-source)
1025         (from orig-from))
1026     (collect ((subs))
1027       (loop
1028         (unless source
1029           (unless (every (lambda (x) (eq x :wild-inferiors)) from)
1030             (didnt-match-error orig-source orig-from))
1031           (subs ())
1032           (return))
1033         (unless from (didnt-match-error orig-source orig-from))
1034         (let ((from-part (pop from))
1035               (source-part (pop source)))
1036           (typecase from-part
1037             (pattern
1038              (typecase source-part
1039                (pattern
1040                 (if (pattern= from-part source-part)
1041                     (subs source-part)
1042                     (didnt-match-error orig-source orig-from)))
1043                (simple-string
1044                 (multiple-value-bind (won new-subs)
1045                     (pattern-matches from-part source-part)
1046                   (if won
1047                       (dolist (sub new-subs)
1048                         (subs sub))
1049                       (didnt-match-error orig-source orig-from))))
1050                (t
1051                 (didnt-match-error orig-source orig-from))))
1052             ((member :wild)
1053              (subs source-part))
1054             ((member :wild-inferiors)
1055              (let ((remaining-source (cons source-part source)))
1056                (collect ((res))
1057                  (loop
1058                    (when (directory-components-match remaining-source from)
1059                      (return))
1060                    (unless remaining-source
1061                      (didnt-match-error orig-source orig-from))
1062                    (res (pop remaining-source)))
1063                  (subs (res))
1064                  (setq source remaining-source))))
1065             (simple-string
1066              (unless (and (simple-string-p source-part)
1067                           (string= from-part source-part))
1068                (didnt-match-error orig-source orig-from)))
1069             (t
1070              (didnt-match-error orig-source orig-from)))))
1071       (subs))))
1072
1073 ;;; This is called by TRANSLATE-PATHNAME on the directory components
1074 ;;; of its argument pathnames to produce the result directory
1075 ;;; component. If this leaves the directory NIL, we return the source
1076 ;;; directory. The :RELATIVE or :ABSOLUTE is taken from the source
1077 ;;; directory, except if TO is :ABSOLUTE, in which case the result
1078 ;;; will be :ABSOLUTE.
1079 (defun translate-directories (source from to diddle-case)
1080   (if (not (and source to from))
1081       (or (and to (null source) (remove :wild-inferiors to))
1082           (mapcar (lambda (x) (maybe-diddle-case x diddle-case)) source))
1083       (collect ((res))
1084                ;; If TO is :ABSOLUTE, the result should still be :ABSOLUTE.
1085                (res (if (eq (first to) :absolute)
1086                  :absolute
1087                  (first source)))
1088         (let ((subs-left (compute-directory-substitutions (rest source)
1089                                                           (rest from))))
1090           (dolist (to-part (rest to))
1091             (typecase to-part
1092               ((member :wild)
1093                (aver subs-left)
1094                (let ((match (pop subs-left)))
1095                  (when (listp match)
1096                    (error ":WILD-INFERIORS is not paired in from and to ~
1097                            patterns:~%  ~S ~S" from to))
1098                  (res (maybe-diddle-case match diddle-case))))
1099               ((member :wild-inferiors)
1100                (aver subs-left)
1101                (let ((match (pop subs-left)))
1102                  (unless (listp match)
1103                    (error ":WILD-INFERIORS not paired in from and to ~
1104                            patterns:~%  ~S ~S" from to))
1105                  (dolist (x match)
1106                    (res (maybe-diddle-case x diddle-case)))))
1107               (pattern
1108                (multiple-value-bind
1109                    (new new-subs-left)
1110                    (substitute-into to-part subs-left diddle-case)
1111                  (setf subs-left new-subs-left)
1112                  (res new)))
1113               (t (res to-part)))))
1114         (res))))
1115
1116 (defun translate-pathname (source from-wildname to-wildname &key)
1117   #!+sb-doc
1118   "Use the source pathname to translate the from-wildname's wild and
1119    unspecified elements into a completed to-pathname based on the to-wildname."
1120   (declare (type pathname-designator source from-wildname to-wildname))
1121   (with-pathname (source source)
1122     (with-pathname (from from-wildname)
1123       (with-pathname (to to-wildname)
1124           (let* ((source-host (%pathname-host source))
1125                  (from-host (%pathname-host from))
1126                  (to-host (%pathname-host to))
1127                  (diddle-case
1128                   (and source-host to-host
1129                        (not (eq (host-customary-case source-host)
1130                                 (host-customary-case to-host))))))
1131             (macrolet ((frob (field &optional (op 'translate-component))
1132                          `(let ((result (,op (,field source)
1133                                              (,field from)
1134                                              (,field to)
1135                                              diddle-case)))
1136                             (if (eq result :error)
1137                                 (error "~S doesn't match ~S." source from)
1138                                 result))))
1139               (%make-maybe-logical-pathname
1140                (or to-host source-host)
1141                (frob %pathname-device)
1142                (frob %pathname-directory translate-directories)
1143                (frob %pathname-name)
1144                (frob %pathname-type)
1145                (if (eq from-host *unix-host*)
1146                    (if (eq (%pathname-version to) :wild)
1147                        (%pathname-version from)
1148                        (%pathname-version to))
1149                    (frob %pathname-version)))))))))
1150 \f
1151 ;;;;  logical pathname support. ANSI 92-102 specification.
1152 ;;;;
1153 ;;;;  As logical-pathname translations are loaded they are
1154 ;;;;  canonicalized as patterns to enable rapid efficient translation
1155 ;;;;  into physical pathnames.
1156
1157 ;;;; utilities
1158
1159 ;;; Canonicalize a logical pathname word by uppercasing it checking that it
1160 ;;; contains only legal characters.
1161 (defun logical-word-or-lose (word)
1162   (declare (string word))
1163   (when (string= word "")
1164     (error 'namestring-parse-error
1165            :complaint "Attempted to treat invalid logical hostname ~
1166                        as a logical host:~%  ~S"
1167            :args (list word)
1168            :namestring word :offset 0))
1169   (let ((word (string-upcase word)))
1170     (dotimes (i (length word))
1171       (let ((ch (schar word i)))
1172         (unless (or (alpha-char-p ch) (digit-char-p ch) (char= ch #\-))
1173           (error 'namestring-parse-error
1174                  :complaint "logical namestring character which ~
1175                              is not alphanumeric or hyphen:~%  ~S"
1176                  :args (list ch)
1177                  :namestring word :offset i))))
1178     word))
1179
1180 ;;; Given a logical host or string, return a logical host. If ERROR-P
1181 ;;; is NIL, then return NIL when no such host exists.
1182 (defun find-logical-host (thing &optional (errorp t))
1183   (etypecase thing
1184     (string
1185      (let ((found (gethash (logical-word-or-lose thing)
1186                            *logical-hosts*)))
1187        (if (or found (not errorp))
1188            found
1189            ;; This is the error signalled from e.g.
1190            ;; LOGICAL-PATHNAME-TRANSLATIONS when host is not a defined
1191            ;; host, and ANSI specifies that that's a TYPE-ERROR.
1192            (error 'simple-type-error
1193                   :datum thing
1194                   ;; God only knows what ANSI expects us to use for
1195                   ;; the EXPECTED-TYPE here. Maybe this will be OK..
1196                   :expected-type
1197                   '(and string (satisfies logical-pathname-translations))
1198                   :format-control "logical host not yet defined: ~S"
1199                   :format-arguments (list thing)))))
1200     (logical-host thing)))
1201
1202 ;;; Given a logical host name or host, return a logical host, creating
1203 ;;; a new one if necessary.
1204 (defun intern-logical-host (thing)
1205   (declare (values logical-host))
1206   (or (find-logical-host thing nil)
1207       (let* ((name (logical-word-or-lose thing))
1208              (new (make-logical-host :name name)))
1209         (setf (gethash name *logical-hosts*) new)
1210         new)))
1211 \f
1212 ;;;; logical pathname parsing
1213
1214 ;;; Deal with multi-char wildcards in a logical pathname token.
1215 (defun maybe-make-logical-pattern (namestring chunks)
1216   (let ((chunk (caar chunks)))
1217     (collect ((pattern))
1218       (let ((last-pos 0)
1219             (len (length chunk)))
1220         (declare (fixnum last-pos))
1221         (loop
1222           (when (= last-pos len) (return))
1223           (let ((pos (or (position #\* chunk :start last-pos) len)))
1224             (if (= pos last-pos)
1225                 (when (pattern)
1226                   (error 'namestring-parse-error
1227                          :complaint "double asterisk inside of logical ~
1228                                      word: ~S"
1229                          :args (list chunk)
1230                          :namestring namestring
1231                          :offset (+ (cdar chunks) pos)))
1232                 (pattern (subseq chunk last-pos pos)))
1233             (if (= pos len)
1234                 (return)
1235                 (pattern :multi-char-wild))
1236             (setq last-pos (1+ pos)))))
1237         (aver (pattern))
1238         (if (cdr (pattern))
1239             (make-pattern (pattern))
1240             (let ((x (car (pattern))))
1241               (if (eq x :multi-char-wild)
1242                   :wild
1243                   x))))))
1244
1245 ;;; Return a list of conses where the CDR is the start position and
1246 ;;; the CAR is a string (token) or character (punctuation.)
1247 (defun logical-chunkify (namestr start end)
1248   (collect ((chunks))
1249     (do ((i start (1+ i))
1250          (prev 0))
1251         ((= i end)
1252          (when (> end prev)
1253             (chunks (cons (nstring-upcase (subseq namestr prev end)) prev))))
1254       (let ((ch (schar namestr i)))
1255         (unless (or (alpha-char-p ch) (digit-char-p ch)
1256                     (member ch '(#\- #\*)))
1257           (when (> i prev)
1258             (chunks (cons (nstring-upcase (subseq namestr prev i)) prev)))
1259           (setq prev (1+ i))
1260           (unless (member ch '(#\; #\: #\.))
1261             (error 'namestring-parse-error
1262                    :complaint "illegal character for logical pathname:~%  ~S"
1263                    :args (list ch)
1264                    :namestring namestr
1265                    :offset i))
1266           (chunks (cons ch i)))))
1267     (chunks)))
1268
1269 ;;; Break up a logical-namestring, always a string, into its
1270 ;;; constituent parts.
1271 (defun parse-logical-namestring (namestr start end)
1272   (declare (type simple-base-string namestr)
1273            (type index start end))
1274   (collect ((directory))
1275     (let ((host nil)
1276           (name nil)
1277           (type nil)
1278           (version nil))
1279       (labels ((expecting (what chunks)
1280                  (unless (and chunks (simple-string-p (caar chunks)))
1281                    (error 'namestring-parse-error
1282                           :complaint "expecting ~A, got ~:[nothing~;~S~]."
1283                           :args (list what (caar chunks) (caar chunks))
1284                           :namestring namestr
1285                           :offset (if chunks (cdar chunks) end)))
1286                  (caar chunks))
1287                (parse-host (chunks)
1288                  (case (caadr chunks)
1289                    (#\:
1290                     (setq host
1291                           (find-logical-host (expecting "a host name" chunks)))
1292                     (parse-relative (cddr chunks)))
1293                    (t
1294                     (parse-relative chunks))))
1295                (parse-relative (chunks)
1296                  (case (caar chunks)
1297                    (#\;
1298                     (directory :relative)
1299                     (parse-directory (cdr chunks)))
1300                    (t
1301                     (directory :absolute) ; Assumption! Maybe revoked later.
1302                     (parse-directory chunks))))
1303                (parse-directory (chunks)
1304                  (case (caadr chunks)
1305                    (#\;
1306                     (directory
1307                      (let ((res (expecting "a directory name" chunks)))
1308                        (cond ((string= res "..") :up)
1309                              ((string= res "**") :wild-inferiors)
1310                              (t
1311                               (maybe-make-logical-pattern namestr chunks)))))
1312                     (parse-directory (cddr chunks)))
1313                    (t
1314                     (parse-name chunks))))
1315                (parse-name (chunks)
1316                  (when chunks
1317                    (expecting "a file name" chunks)
1318                    (setq name (maybe-make-logical-pattern namestr chunks))
1319                    (expecting-dot (cdr chunks))))
1320                (expecting-dot (chunks)
1321                  (when chunks
1322                    (unless (eql (caar chunks) #\.)
1323                      (error 'namestring-parse-error
1324                             :complaint "expecting a dot, got ~S."
1325                             :args (list (caar chunks))
1326                             :namestring namestr
1327                             :offset (cdar chunks)))
1328                    (if type
1329                        (parse-version (cdr chunks))
1330                        (parse-type (cdr chunks)))))
1331                (parse-type (chunks)
1332                  (expecting "a file type" chunks)
1333                  (setq type (maybe-make-logical-pattern namestr chunks))
1334                  (expecting-dot (cdr chunks)))
1335                (parse-version (chunks)
1336                  (let ((str (expecting "a positive integer, * or NEWEST"
1337                                        chunks)))
1338                    (cond
1339                     ((string= str "*") (setq version :wild))
1340                     ((string= str "NEWEST") (setq version :newest))
1341                     (t
1342                      (multiple-value-bind (res pos)
1343                          (parse-integer str :junk-allowed t)
1344                        (unless (and res (plusp res))
1345                          (error 'namestring-parse-error
1346                                 :complaint "expected a positive integer, ~
1347                                             got ~S"
1348                                 :args (list str)
1349                                 :namestring namestr
1350                                 :offset (+ pos (cdar chunks))))
1351                        (setq version res)))))
1352                  (when (cdr chunks)
1353                    (error 'namestring-parse-error
1354                           :complaint "extra stuff after end of file name"
1355                           :namestring namestr
1356                           :offset (cdadr chunks)))))
1357         (parse-host (logical-chunkify namestr start end)))
1358       (values host :unspecific (directory) name type version))))
1359
1360 ;;; We can't initialize this yet because not all host methods are
1361 ;;; loaded yet.
1362 (defvar *logical-pathname-defaults*)
1363
1364 (defun logical-pathname (pathspec)
1365   #!+sb-doc
1366   "Converts the pathspec argument to a logical-pathname and returns it."
1367   (declare (type (or logical-pathname string stream) pathspec)
1368            (values logical-pathname))
1369   (if (typep pathspec 'logical-pathname)
1370       pathspec
1371       (let ((res (parse-namestring pathspec nil *logical-pathname-defaults*)))
1372         (when (eq (%pathname-host res)
1373                   (%pathname-host *logical-pathname-defaults*))
1374           (error "This logical namestring does not specify a host:~%  ~S"
1375                  pathspec))
1376         res)))
1377 \f
1378 ;;;; logical pathname unparsing
1379
1380 (defun unparse-logical-directory (pathname)
1381   (declare (type pathname pathname))
1382   (collect ((pieces))
1383     (let ((directory (%pathname-directory pathname)))
1384       (when directory
1385         (ecase (pop directory)
1386           (:absolute) ; nothing special
1387           (:relative (pieces ";")))
1388         (dolist (dir directory)
1389           (cond ((or (stringp dir) (pattern-p dir))
1390                  (pieces (unparse-logical-piece dir))
1391                  (pieces ";"))
1392                 ((eq dir :wild)
1393                  (pieces "*;"))
1394                 ((eq dir :wild-inferiors)
1395                  (pieces "**;"))
1396                 (t
1397                  (error "invalid directory component: ~S" dir))))))
1398     (apply #'concatenate 'simple-string (pieces))))
1399
1400 (defun unparse-logical-piece (thing)
1401   (etypecase thing
1402     (simple-string thing)
1403     (pattern
1404      (collect ((strings))
1405        (dolist (piece (pattern-pieces thing))
1406          (etypecase piece
1407            (simple-string (strings piece))
1408            (keyword
1409             (cond ((eq piece :wild-inferiors)
1410                    (strings "**"))
1411                   ((eq piece :multi-char-wild)
1412                    (strings "*"))
1413                   (t (error "invalid keyword: ~S" piece))))))
1414        (apply #'concatenate 'simple-string (strings))))))
1415
1416 (defun unparse-logical-file (pathname)
1417   (declare (type pathname pathname))
1418     (collect ((strings))
1419     (let* ((name (%pathname-name pathname))
1420            (type (%pathname-type pathname))
1421            (version (%pathname-version pathname))
1422            (type-supplied (not (or (null type) (eq type :unspecific))))
1423            (version-supplied (not (or (null version)
1424                                       (eq version :unspecific)))))
1425       (when name
1426         (when (and (null type) (position #\. name :start 1))
1427           (error "too many dots in the name: ~S" pathname))
1428         (strings (unparse-logical-piece name)))
1429       (when type-supplied
1430         (unless name
1431           (error "cannot specify the type without a file: ~S" pathname))
1432         (when (typep type 'simple-base-string)
1433           (when (position #\. type)
1434             (error "type component can't have a #\. inside: ~S" pathname)))
1435         (strings ".")
1436         (strings (unparse-logical-piece type)))
1437       (when version-supplied
1438         (unless type-supplied
1439           (error "cannot specify the version without a type: ~S" pathname))
1440         (etypecase version
1441           ((member :newest) (strings ".NEWEST"))
1442           ((member :wild) (strings ".*"))
1443           (fixnum (strings ".") (strings (format nil "~D" version))))))
1444     (apply #'concatenate 'simple-string (strings))))
1445
1446 ;;; Unparse a logical pathname string.
1447 (defun unparse-enough-namestring (pathname defaults)
1448   (let* ((path-directory (pathname-directory pathname))
1449          (def-directory (pathname-directory defaults))
1450          (enough-directory
1451            ;; Go down the directory lists to see what matches.  What's
1452            ;; left is what we want, more or less.
1453            (cond ((and (eq (first path-directory) (first def-directory))
1454                        (eq (first path-directory) :absolute))
1455                    ;; Both paths are :ABSOLUTE, so find where the
1456                    ;; common parts end and return what's left
1457                    (do* ((p (rest path-directory) (rest p))
1458                          (d (rest def-directory) (rest d)))
1459                         ((or (endp p) (endp d)
1460                              (not (equal (first p) (first d))))
1461                          `(:relative ,@p))))
1462                  (t
1463                    ;; At least one path is :RELATIVE, so just return the
1464                    ;; original path.  If the original path is :RELATIVE,
1465                    ;; then that's the right one.  If PATH-DIRECTORY is
1466                    ;; :ABSOLUTE, we want to return that except when
1467                    ;; DEF-DIRECTORY is :ABSOLUTE, as handled above. so return
1468                    ;; the original directory.
1469                    path-directory))))
1470     (unparse-logical-namestring
1471      (make-pathname :host (pathname-host pathname)
1472                     :directory enough-directory
1473                     :name (pathname-name pathname)
1474                     :type (pathname-type pathname)
1475                     :version (pathname-version pathname)))))
1476
1477 (defun unparse-logical-namestring (pathname)
1478   (declare (type logical-pathname pathname))
1479   (concatenate 'simple-string
1480                (logical-host-name (%pathname-host pathname)) ":"
1481                (unparse-logical-directory pathname)
1482                (unparse-logical-file pathname)))
1483 \f
1484 ;;;; logical pathname translations
1485
1486 ;;; Verify that the list of translations consists of lists and prepare
1487 ;;; canonical translations. (Parse pathnames and expand out wildcards
1488 ;;; into patterns.)
1489 (defun canonicalize-logical-pathname-translations (translation-list host)
1490   (declare (type list translation-list) (type host host)
1491            (values list))
1492   (mapcar (lambda (translation)
1493             (destructuring-bind (from to) translation
1494               (list (if (typep from 'logical-pathname)
1495                         from
1496                         (parse-namestring from host))
1497                     (pathname to)))) 
1498           translation-list))
1499
1500 (defun logical-pathname-translations (host)
1501   #!+sb-doc
1502   "Return the (logical) host object argument's list of translations."
1503   (declare (type (or string logical-host) host)
1504            (values list))
1505   (logical-host-translations (find-logical-host host)))
1506
1507 (defun (setf logical-pathname-translations) (translations host)
1508   #!+sb-doc
1509   "Set the translations list for the logical host argument."
1510   (declare (type (or string logical-host) host)
1511            (type list translations)
1512            (values list))
1513   (let ((host (intern-logical-host host)))
1514     (setf (logical-host-canon-transls host)
1515           (canonicalize-logical-pathname-translations translations host))
1516     (setf (logical-host-translations host) translations)))
1517
1518 (defun translate-logical-pathname (pathname &key)
1519   #!+sb-doc
1520   "Translate PATHNAME to a physical pathname, which is returned."
1521   (declare (type pathname-designator pathname)
1522            (values (or null pathname)))
1523   (typecase pathname
1524     (logical-pathname
1525      (dolist (x (logical-host-canon-transls (%pathname-host pathname))
1526                 (error 'simple-file-error
1527                        :pathname pathname
1528                        :format-control "no translation for ~S"
1529                        :format-arguments (list pathname)))
1530        (destructuring-bind (from to) x
1531          (when (pathname-match-p pathname from)
1532            (return (translate-logical-pathname
1533                     (translate-pathname pathname from to)))))))
1534     (pathname pathname)
1535     (t (translate-logical-pathname (pathname pathname)))))
1536
1537 (defvar *logical-pathname-defaults*
1538   (%make-logical-pathname (make-logical-host :name "BOGUS")
1539                           :unspecific
1540                           nil
1541                           nil
1542                           nil
1543                           nil))
1544
1545 (defun load-logical-pathname-translations (host)
1546   #!+sb-doc
1547   (declare (type string host)
1548            (values (member t nil)))
1549   (if (find-logical-host host nil)
1550       ;; This host is already defined, all is well and good.
1551       nil
1552       ;; ANSI: "The specific nature of the search is
1553       ;; implementation-defined." SBCL: doesn't search at all
1554       ;;
1555       ;; FIXME: now that we have a SYS host that the system uses, it
1556       ;; might be cute to search in "SYS:TRANSLATIONS;<name>.LISP"
1557       (error "logical host ~S not found" host)))