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