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