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