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