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