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