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