1.0.29.10: one more DIRECTORY regression
[sbcl.git] / src / code / filesys.lisp
1 ;;;; file system interface functions -- fairly Unix-centric, but with
2 ;;;; differences between Unix and Win32 papered over.
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
12
13 (in-package "SB!IMPL")
14 \f
15 ;;;; Unix pathname host support
16
17 ;;; FIXME: the below shouldn't really be here, but in documentation
18 ;;; (chapter 19 makes a lot of requirements for documenting
19 ;;; implementation-dependent decisions), but anyway it's probably not
20 ;;; what we currently do.
21 ;;;
22 ;;; Unix namestrings have the following format:
23 ;;;
24 ;;; namestring := [ directory ] [ file [ type [ version ]]]
25 ;;; directory := [ "/" ] { file "/" }*
26 ;;; file := [^/]*
27 ;;; type := "." [^/.]*
28 ;;; version := "." ([0-9]+ | "*")
29 ;;;
30 ;;; Note: this grammar is ambiguous. The string foo.bar.5 can be
31 ;;; parsed as either just the file specified or as specifying the
32 ;;; file, type, and version. Therefore, we use the following rules
33 ;;; when confronted with an ambiguous file.type.version string:
34 ;;;
35 ;;; - If the first character is a dot, it's part of the file. It is not
36 ;;; considered a dot in the following rules.
37 ;;;
38 ;;; - Otherwise, the last dot separates the file and the type.
39 ;;;
40 ;;; Wildcard characters:
41 ;;;
42 ;;; If the directory, file, type components contain any of the
43 ;;; following characters, it is considered part of a wildcard pattern
44 ;;; and has the following meaning.
45 ;;;
46 ;;; ? - matches any one character
47 ;;; * - matches any zero or more characters.
48 ;;; [abc] - matches any of a, b, or c.
49 ;;; {str1,str2,...,strn} - matches any of str1, str2, ..., or strn.
50 ;;;   (FIXME: no it doesn't)
51 ;;;
52 ;;; Any of these special characters can be preceded by a backslash to
53 ;;; cause it to be treated as a regular character.
54 (defun remove-backslashes (namestr start end)
55   #!+sb-doc
56   "Remove any occurrences of #\\ from the string because we've already
57    checked for whatever they may have protected."
58   (declare (type simple-string namestr)
59            (type index start end))
60   (let* ((result (make-string (- end start) :element-type 'character))
61          (dst 0)
62          (quoted nil))
63     (do ((src start (1+ src)))
64         ((= src end))
65       (cond (quoted
66              (setf (schar result dst) (schar namestr src))
67              (setf quoted nil)
68              (incf dst))
69             (t
70              (let ((char (schar namestr src)))
71                (cond ((char= char #\\)
72                       (setq quoted t))
73                      (t
74                       (setf (schar result dst) char)
75                       (incf dst)))))))
76     (when quoted
77       (error 'namestring-parse-error
78              :complaint "backslash in a bad place"
79              :namestring namestr
80              :offset (1- end)))
81     (%shrink-vector result dst)))
82
83 (defun maybe-make-pattern (namestr start end)
84   (declare (type simple-string namestr)
85            (type index start end))
86   (collect ((pattern))
87     (let ((quoted nil)
88           (any-quotes nil)
89           (last-regular-char nil)
90           (index start))
91       (flet ((flush-pending-regulars ()
92                (when last-regular-char
93                  (pattern (if any-quotes
94                               (remove-backslashes namestr
95                                                   last-regular-char
96                                                   index)
97                               (subseq namestr last-regular-char index)))
98                  (setf any-quotes nil)
99                  (setf last-regular-char nil))))
100         (loop
101           (when (>= index end)
102             (return))
103           (let ((char (schar namestr index)))
104             (cond (quoted
105                    (incf index)
106                    (setf quoted nil))
107                   ((char= char #\\)
108                    (setf quoted t)
109                    (setf any-quotes t)
110                    (unless last-regular-char
111                      (setf last-regular-char index))
112                    (incf index))
113                   ((char= char #\?)
114                    (flush-pending-regulars)
115                    (pattern :single-char-wild)
116                    (incf index))
117                   ((char= char #\*)
118                    (flush-pending-regulars)
119                    (pattern :multi-char-wild)
120                    (incf index))
121                   ((char= char #\[)
122                    (flush-pending-regulars)
123                    (let ((close-bracket
124                           (position #\] namestr :start index :end end)))
125                      (unless close-bracket
126                        (error 'namestring-parse-error
127                               :complaint "#\\[ with no corresponding #\\]"
128                               :namestring namestr
129                               :offset index))
130                      (pattern (cons :character-set
131                                     (subseq namestr
132                                             (1+ index)
133                                             close-bracket)))
134                      (setf index (1+ close-bracket))))
135                   (t
136                    (unless last-regular-char
137                      (setf last-regular-char index))
138                    (incf index)))))
139         (flush-pending-regulars)))
140     (cond ((null (pattern))
141            "")
142           ((null (cdr (pattern)))
143            (let ((piece (first (pattern))))
144              (typecase piece
145                ((member :multi-char-wild) :wild)
146                (simple-string piece)
147                (t
148                 (make-pattern (pattern))))))
149           (t
150            (make-pattern (pattern))))))
151
152 (defun unparse-physical-piece (thing)
153   (etypecase thing
154     ((member :wild) "*")
155     (simple-string
156      (let* ((srclen (length thing))
157             (dstlen srclen))
158        (dotimes (i srclen)
159          (case (schar thing i)
160            ((#\* #\? #\[)
161             (incf dstlen))))
162        (let ((result (make-string dstlen))
163              (dst 0))
164          (dotimes (src srclen)
165            (let ((char (schar thing src)))
166              (case char
167                ((#\* #\? #\[)
168                 (setf (schar result dst) #\\)
169                 (incf dst)))
170              (setf (schar result dst) char)
171              (incf dst)))
172          result)))
173     (pattern
174      (with-output-to-string (s)
175        (dolist (piece (pattern-pieces thing))
176          (etypecase piece
177            (simple-string
178             (write-string piece s))
179            (symbol
180             (ecase piece
181               (:multi-char-wild
182                (write-string "*" s))
183               (:single-char-wild
184                (write-string "?" s))))
185            (cons
186             (case (car piece)
187               (:character-set
188                (write-string "[" s)
189                (write-string (cdr piece) s)
190                (write-string "]" s))
191               (t
192                (error "invalid pattern piece: ~S" piece))))))))))
193
194 (defun make-matcher (piece)
195   (cond ((eq piece :wild)
196          (constantly t))
197         ((typep piece 'pattern)
198          (lambda (other)
199            (when (stringp other)
200              (pattern-matches piece other))))
201         (t
202          (lambda (other)
203            (equal piece other)))))
204
205 (/show0 "filesys.lisp 160")
206
207 (defun extract-name-type-and-version (namestr start end)
208   (declare (type simple-string namestr)
209            (type index start end))
210   (let* ((last-dot (position #\. namestr :start (1+ start) :end end
211                              :from-end t)))
212     (cond
213       (last-dot
214        (values (maybe-make-pattern namestr start last-dot)
215                (maybe-make-pattern namestr (1+ last-dot) end)
216                :newest))
217       (t
218        (values (maybe-make-pattern namestr start end)
219                nil
220                :newest)))))
221
222 (/show0 "filesys.lisp 200")
223
224 \f
225 ;;;; Grabbing the kind of file when we have a namestring.
226 (defun native-file-kind (namestring)
227   (multiple-value-bind (existsp errno ino mode)
228       #!-win32
229       (sb!unix:unix-lstat namestring)
230       #!+win32
231       (sb!unix:unix-stat namestring)
232     (declare (ignore errno ino))
233     (when existsp
234       (let ((ifmt (logand mode sb!unix:s-ifmt)))
235        (case ifmt
236          (#.sb!unix:s-ifreg :file)
237          (#.sb!unix:s-ifdir :directory)
238          #!-win32
239          (#.sb!unix:s-iflnk :symlink)
240          (t :special))))))
241 \f
242 ;;;; TRUENAME, PROBE-FILE, FILE-AUTHOR, FILE-WRITE-DATE.
243
244 ;;; Rewritten in 12/2007 by RMK, replacing 13+ year old CMU code that
245 ;;; made a mess of things in order to support search lists (which SBCL
246 ;;; has never had).  These are now all relatively straightforward
247 ;;; wrappers around stat(2) and realpath(2), with the same basic logic
248 ;;; in all cases.  The wrinkles to be aware of:
249 ;;;
250 ;;; * SBCL defines the truename of an existing, dangling or
251 ;;;   self-referring symlink to be the symlink itself.
252 ;;; * The old version of PROBE-FILE merged the pathspec against
253 ;;;   *DEFAULT-PATHNAME-DEFAULTS* twice, and so lost when *D-P-D*
254 ;;;   was a relative pathname.  Even if the case where *D-P-D* is a
255 ;;;   relative pathname is problematic, there's no particular reason
256 ;;;   to get that wrong, so let's try not to.
257 ;;; * Note that while stat(2) is probably atomic, getting the truename
258 ;;;   for a filename involves poking all over the place, and so is
259 ;;;   subject to race conditions if other programs mutate the file
260 ;;;   system while we're resolving symlinks.  So it's not implausible for
261 ;;;   realpath(3) to fail even if stat(2) succeeded.  There's nothing
262 ;;;   obvious we can do about this, however.
263 ;;; * Windows' apparent analogue of realpath(3) is called
264 ;;;   GetFullPathName, and it's a bit less useful than realpath(3).
265 ;;;   In particular, while realpath(3) errors in case the file doesn't
266 ;;;   exist, GetFullPathName seems to return a filename in all cases.
267 ;;;   As realpath(3) is not atomic anyway, we only ever call it when
268 ;;;   we think a file exists, so just be careful when rewriting this
269 ;;;   routine.
270 ;;;
271 ;;; Given a pathname designator, some quality to query for, return one
272 ;;; of a pathname, a universal time, or a string (a file-author), or
273 ;;; NIL.  QUERY-FOR may be one of :TRUENAME, :EXISTENCE, :WRITE-DATE,
274 ;;; :AUTHOR.  If ERRORP is false, return NIL in case the file system
275 ;;; returns an error code; otherwise, signal an error.  Accepts
276 ;;; logical pathnames, too (but never returns LPNs).  For internal
277 ;;; use.
278 (defun query-file-system (pathspec query-for &optional (errorp t))
279   (let ((pathname (translate-logical-pathname
280                    (merge-pathnames
281                     (pathname pathspec)
282                     (sane-default-pathname-defaults)))))
283     (when (wild-pathname-p pathname)
284       (error 'simple-file-error
285              :pathname pathname
286              :format-control "~@<can't find the ~A of wild pathname ~A~
287                               (physicalized from ~A).~:>"
288              :format-arguments (list query-for pathname pathspec)))
289     (flet ((fail (note-format pathname errno)
290              (if errorp
291                  (simple-file-perror note-format pathname errno)
292                  (return-from query-file-system nil))))
293       (let ((filename (native-namestring pathname :as-file t)))
294         (multiple-value-bind (existsp errno ino mode nlink uid gid rdev size
295                                       atime mtime)
296             (sb!unix:unix-stat filename)
297           (declare (ignore ino nlink gid rdev size atime
298                            #!+win32 uid))
299           (if existsp
300               (case query-for
301                 (:existence (nth-value
302                              0
303                              (parse-native-namestring
304                               filename
305                               (pathname-host pathname)
306                               (sane-default-pathname-defaults)
307                               :as-directory (eql (logand mode sb!unix:s-ifmt)
308                                                  sb!unix:s-ifdir))))
309                 (:truename (nth-value
310                             0
311                             (parse-native-namestring
312                              ;; Note: in case the file is stat'able, POSIX
313                              ;; realpath(3) gets us a canonical absolute
314                              ;; filename, even if the post-merge PATHNAME
315                              ;; is not absolute...
316                              (multiple-value-bind (realpath errno)
317                                  (sb!unix:unix-realpath filename)
318                                (if realpath
319                                    realpath
320                                    (fail "couldn't resolve ~A" filename errno)))
321                              (pathname-host pathname)
322                              (sane-default-pathname-defaults)
323                              ;; ... but without any trailing slash.
324                              :as-directory (eql (logand  mode sb!unix:s-ifmt)
325                                                 sb!unix:s-ifdir))))
326                 (:author
327                  #!-win32
328                  (sb!unix:uid-username uid))
329                 (:write-date (+ unix-to-universal-time mtime)))
330               (progn
331                 ;; SBCL has for many years had a policy that a pathname
332                 ;; that names an existing, dangling or self-referential
333                 ;; symlink denotes the symlink itself.  stat(2) fails
334                 ;; and sets errno to ENOENT or ELOOP respectively, but
335                 ;; we must distinguish cases where the symlink exists
336                 ;; from ones where there's a loop in the apparent
337                 ;; containing directory.
338                 #!-win32
339                 (multiple-value-bind (linkp ignore ino mode nlink uid gid rdev
340                                             size atime mtime)
341                     (sb!unix:unix-lstat filename)
342                   (declare (ignore ignore ino mode nlink gid rdev size atime))
343                   (when (and (or (= errno sb!unix:enoent)
344                                  (= errno sb!unix:eloop))
345                              linkp)
346                     (return-from query-file-system
347                       (case query-for
348                         (:existence
349                          ;; We do this reparse so as to return a
350                          ;; normalized pathname.
351                          (parse-native-namestring
352                           filename (pathname-host pathname)))
353                         (:truename
354                          ;; So here's a trick: since lstat succeded,
355                          ;; FILENAME exists, so its directory exists and
356                          ;; only the non-directory part is loopy.  So
357                          ;; let's resolve FILENAME's directory part with
358                          ;; realpath(3), in order to get a canonical
359                          ;; absolute name for the directory, and then
360                          ;; return a pathname having PATHNAME's name,
361                          ;; type, and version, but the rest from the
362                          ;; truename of the directory.  Since we turned
363                          ;; PATHNAME into FILENAME "as a file", FILENAME
364                          ;; does not end in a slash, and so we get the
365                          ;; directory part of FILENAME by reparsing
366                          ;; FILENAME and masking off its name, type, and
367                          ;; version bits.  But note not to call ourselves
368                          ;; recursively, because we don't want to
369                          ;; re-merge against *DEFAULT-PATHNAME-DEFAULTS*,
370                          ;; since PATHNAME may be a relative pathname.
371                          (merge-pathnames
372                           (nth-value
373                            0
374                            (parse-native-namestring
375                             (multiple-value-bind (realpath errno)
376                                 (sb!unix:unix-realpath
377                                  (native-namestring
378                                   (make-pathname
379                                    :name :unspecific
380                                    :type :unspecific
381                                    :version :unspecific
382                                    :defaults (parse-native-namestring
383                                               filename
384                                               (pathname-host pathname)
385                                               (sane-default-pathname-defaults)))))
386                               (if realpath
387                                   realpath
388                                   (fail "couldn't resolve ~A" filename errno)))
389                             (pathname-host pathname)
390                             (sane-default-pathname-defaults)
391                             :as-directory t))
392                           pathname))
393                         (:author (sb!unix:uid-username uid))
394                         (:write-date (+ unix-to-universal-time mtime))))))
395                 ;; If we're still here, the file doesn't exist; error.
396                 (fail
397                  (format nil "failed to find the ~A of ~~A" query-for)
398                  pathspec errno))))))))
399
400
401 (defun probe-file (pathspec)
402   #!+sb-doc
403   "Return the truename of PATHSPEC if the truename can be found,
404 or NIL otherwise.  See TRUENAME for more information."
405   (query-file-system pathspec :truename nil))
406
407 (defun truename (pathspec)
408   #!+sb-doc
409   "If PATHSPEC is a pathname that names an existing file, return
410 a pathname that denotes a canonicalized name for the file.  If
411 pathspec is a stream associated with a file, return a pathname
412 that denotes a canonicalized name for the file associated with
413 the stream.
414
415 An error of type FILE-ERROR is signalled if no such file exists
416 or if the file system is such that a canonicalized file name
417 cannot be determined or if the pathname is wild.
418
419 Under Unix, the TRUENAME of a symlink that links to itself or to
420 a file that doesn't exist is considered to be the name of the
421 broken symlink itself."
422   ;; Note that eventually this routine might be different for streams
423   ;; than for other pathname designators.
424   (if (streamp pathspec)
425       (query-file-system pathspec :truename)
426       (query-file-system pathspec :truename)))
427
428 (defun file-author (pathspec)
429   #!+sb-doc
430   "Return the author of the file specified by PATHSPEC. Signal an
431 error of type FILE-ERROR if no such file exists, or if PATHSPEC
432 is a wild pathname."
433   (query-file-system pathspec :author))
434
435 (defun file-write-date (pathspec)
436   #!+sb-doc
437   "Return the write date of the file specified by PATHSPEC.
438 An error of type FILE-ERROR is signaled if no such file exists,
439 or if PATHSPEC is a wild pathname."
440   (query-file-system pathspec :write-date))
441 \f
442 ;;;; miscellaneous other operations
443
444 (/show0 "filesys.lisp 700")
445
446 (defun rename-file (file new-name)
447   #!+sb-doc
448   "Rename FILE to have the specified NEW-NAME. If FILE is a stream open to a
449   file, then the associated file is renamed."
450   (let* ((original (truename file))
451          (original-namestring (native-namestring original :as-file t))
452          (new-name (merge-pathnames new-name original))
453          (new-namestring (native-namestring (physicalize-pathname new-name)
454                                             :as-file t)))
455     (unless new-namestring
456       (error 'simple-file-error
457              :pathname new-name
458              :format-control "~S can't be created."
459              :format-arguments (list new-name)))
460     (multiple-value-bind (res error)
461         (sb!unix:unix-rename original-namestring new-namestring)
462       (unless res
463         (error 'simple-file-error
464                :pathname new-name
465                :format-control "~@<couldn't rename ~2I~_~A ~I~_to ~2I~_~A: ~
466                                 ~I~_~A~:>"
467                :format-arguments (list original new-name (strerror error))))
468       (when (streamp file)
469         (file-name file new-name))
470       (values new-name original (truename new-name)))))
471
472 (defun delete-file (file)
473   #!+sb-doc
474   "Delete the specified FILE."
475   (let* ((truename (probe-file file))
476          (namestring (when truename
477                        (native-namestring truename :as-file t))))
478     (when (streamp file)
479       (close file :abort t))
480     (unless namestring
481       (error 'simple-file-error
482              :pathname file
483              :format-control "~S doesn't exist."
484              :format-arguments (list file)))
485     (multiple-value-bind (res err) (sb!unix:unix-unlink namestring)
486       (unless res
487         (simple-file-perror "couldn't delete ~A" namestring err))))
488   t)
489 \f
490 (defun sbcl-homedir-pathname ()
491   (let ((sbcl-home (posix-getenv "SBCL_HOME")))
492     ;; SBCL_HOME isn't set for :EXECUTABLE T embedded cores
493     (when (and sbcl-home (not (string= sbcl-home "")))
494       (parse-native-namestring sbcl-home
495                                #!-win32 sb!impl::*unix-host*
496                                #!+win32 sb!impl::*win32-host*
497                                *default-pathname-defaults*
498                                :as-directory t))))
499
500 ;;; (This is an ANSI Common Lisp function.)
501 (defun user-homedir-pathname (&optional host)
502   #!+sb-doc
503   "Return the home directory of the user as a pathname. If the HOME
504 environment variable has been specified, the directory it designates
505 is returned; otherwise obtains the home directory from the operating
506 system."
507   (declare (ignore host))
508   (let ((env-home (posix-getenv "HOME")))
509     (values
510      (parse-native-namestring
511       (if (and env-home (not (string= env-home "")))
512           env-home
513           #!-win32
514           (sb!unix:uid-homedir (sb!unix:unix-getuid))
515           #!+win32
516           ;; Needs to bypass PARSE-NATIVE-NAMESTRING & ENSURE-TRAILING-SLASH
517           ;; What?! -- RMK, 2007-12-31
518           (return-from user-homedir-pathname
519             (sb!win32::get-folder-pathname sb!win32::csidl_profile)))
520       #!-win32 sb!impl::*unix-host*
521       #!+win32 sb!impl::*win32-host*
522       *default-pathname-defaults*
523       :as-directory t))))
524
525 \f
526 ;;;; DIRECTORY
527
528 (defun directory (pathspec &key (resolve-symlinks t))
529   #!+sb-doc
530   "Return a list of PATHNAMEs, each the TRUENAME of a file that matched the
531 given pathname. Note that the interaction between this ANSI-specified
532 TRUENAMEing and the semantics of the Unix filesystem (symbolic links..) means
533 this function can sometimes return files which don't have the same directory
534 as PATHNAME. If :RESOLVE-SYMLINKS is NIL, don't resolve symbolic links in
535 matching filenames."
536   (let (;; We create one entry in this hash table for each truename,
537         ;; as an asymptotically efficient way of removing duplicates
538         ;; (which can arise when e.g. multiple symlinks map to the
539         ;; same truename).
540         (truenames (make-hash-table :test #'equal)))
541     (labels ((record (pathname)
542                (let ((truename (if resolve-symlinks
543                                    ;; FIXME: Why not not TRUENAME?  As reported by
544                                    ;; Milan Zamazal sbcl-devel 2003-10-05, using
545                                    ;; TRUENAME causes a race condition whereby
546                                    ;; removal of a file during the directory
547                                    ;; operation causes an error.  It's not clear
548                                    ;; what the right thing to do is, though.  --
549                                    ;; CSR, 2003-10-13
550                                    (query-file-system pathname :truename nil)
551                                    (query-file-system pathname :existence nil))))
552                  (when truename
553                    (setf (gethash (namestring truename) truenames)
554                          truename))))
555              (do-physical-pathnames (pathname)
556                (aver (not (logical-pathname-p pathname)))
557                (let* (;; KLUDGE: Since we don't canonize pathnames on construction,
558                       ;; we really have to do it here to get #p"foo/." mean the same
559                       ;; as #p"foo/./".
560                       (pathname (canonicalize-pathname pathname))
561                       (name (pathname-name pathname))
562                       (type (pathname-type pathname))
563                       ;; KLUDGE: We want #p"/foo" to match #p"/foo/, so cobble
564                       ;; up a directory name component from name and type --
565                       ;; and we need to take care with * as type: we want
566                       ;; "*.*", "x*.*", and "x.*" to match directories without
567                       ;; dots in their names...
568                       (dirname (if (and (eq :wild name) (eq :wild type))
569                                    "*"
570                                    (with-output-to-string (s)
571                                      (when name
572                                        (write-string (unparse-physical-piece name) s))
573                                      (when (and type (not (and name (eq type :wild))))
574                                        (write-string "." s)
575                                        (write-string (unparse-physical-piece type) s)))))
576                       (dir (maybe-make-pattern dirname 0 (length dirname)))
577                       (match-name (make-matcher name))
578                       (match-type (make-matcher type))
579                       (match-dir (make-matcher dir)))
580                  (map-matching-directories
581                   (if (or name type)
582                       (lambda (directory)
583                         (map-matching-files #'record
584                                             directory
585                                             match-name
586                                             match-type
587                                             match-dir))
588                       #'record)
589                   pathname)))
590              (do-pathnames (pathname)
591                (if (logical-pathname-p pathname)
592                    (let ((host (intern-logical-host (pathname-host pathname))))
593                      (dolist (x (logical-host-canon-transls host))
594                        (destructuring-bind (from to) x
595                          (let ((intersections
596                                 (pathname-intersections pathname from)))
597                            (dolist (p intersections)
598                              (do-pathnames (translate-pathname p from to)))))))
599                    (do-physical-pathnames pathname))))
600       (declare (truly-dynamic-extent #'record))
601       (do-pathnames (merge-pathnames pathspec)))
602     (mapcar #'cdr
603             ;; Sorting isn't required by the ANSI spec, but sorting into some
604             ;; canonical order seems good just on the grounds that the
605             ;; implementation should have repeatable behavior when possible.
606             (sort (loop for namestring being each hash-key in truenames
607                         using (hash-value truename)
608                         collect (cons namestring truename))
609                   #'string<
610                   :key #'car))))
611
612 (defun canonicalize-pathname (pathname)
613   ;; We're really only interested in :UNSPECIFIC -> NIL, :BACK and :UP,
614   ;; and dealing with #p"foo/.." and #p"foo/."
615   (labels ((simplify (piece)
616              (unless (eq :unspecific piece)
617                piece))
618            (canonicalize-directory (directory)
619              (let (pieces)
620                (dolist (piece directory)
621                  (if (and pieces (member piece '(:back :up)))
622                      ;; FIXME: We should really canonicalize when we construct
623                      ;; pathnames. This is just wrong.
624                      (case (car pieces)
625                        ((:absolute :wild-inferiors)
626                         (error 'simple-file-error
627                                :format-control "Invalid use of ~S after ~S."
628                                :format-arguments (list piece (car pieces))
629                                :pathname pathname))
630                        ((:relative :up :back)
631                         (push piece pieces))
632                        (t
633                         (pop pieces)))
634                      (push piece pieces)))
635                (nreverse pieces))))
636     (let ((name (simplify (pathname-name pathname)))
637           (type (simplify (pathname-type pathname)))
638           (dir (canonicalize-directory (pathname-directory pathname))))
639       (cond ((equal "." name)
640              (cond ((not type)
641                     (make-pathname :name nil :defaults pathname))
642                    ((equal "" type)
643                     (make-pathname :name nil
644                                    :type nil
645                                    :directory (butlast dir)
646                                    :defaults pathname))))
647             (t
648              (make-pathname :name name :type type
649                             :directory dir
650                             :defaults pathname))))))
651
652 ;;; Given a native namestring, provides a WITH-HASH-TABLE-ITERATOR style
653 ;;; interface to mapping over namestrings of entries in the corresponding
654 ;;; directory.
655 (defmacro with-native-directory-iterator ((iterator namestring &key errorp) &body body)
656   (with-unique-names (one-iter)
657     `(dx-flet
658          ((iterate (,one-iter)
659             (declare (type function ,one-iter))
660             (macrolet ((,iterator ()
661                          `(funcall ,',one-iter)))
662               ,@body)))
663        (call-with-native-directory-iterator #'iterate ,namestring ,errorp))))
664
665 (defun call-with-native-directory-iterator (function namestring errorp)
666   (declare (type (or null string) namestring)
667            (function function))
668   (let (dp)
669     (when namestring
670       (dx-flet
671           ((one-iter ()
672              (tagbody
673               :next
674                 (let ((ent (sb!unix:unix-readdir dp nil)))
675                   (when ent
676                     (let ((name (sb!unix:unix-dirent-name ent)))
677                       (when name
678                         (cond ((equal "." name)
679                                (go :next))
680                               ((equal ".." name)
681                                (go :next))
682                               (t
683                                (return-from one-iter name))))))))))
684         (unwind-protect
685              (progn
686                (setf dp (sb!unix:unix-opendir namestring errorp))
687                (when dp
688                  (funcall function #'one-iter)))
689           (when dp
690             (sb!unix:unix-closedir dp nil)))))))
691
692 ;;; This is our core directory access interface that we use to implement
693 ;;; DIRECTORY.
694 (defun map-directory (function directory &key (files t) (directories t) (errorp t))
695   #!+sb-doc
696   "Call FUNCTION with the pathname for each entry in DIRECTORY as follows: if
697 FILES is true (the default), FUNCTION is called for each file in the
698 directory; if DIRECTORIES is true (the default), FUNCTION is called for each
699 subdirectory. If ERRORP is true (the default) signal an error if DIRECTORY
700 does not exist, cannot be read, etc.
701
702 On platforms supporting symbolic links the decision to call FUNCTION with its
703 pathname depends on the resolution of the link: if it points to a directory,
704 it is considered a directory entry. Whether it is considered a file or a
705 directory, the provided pathname is not fully resolved, but rather names the
706 symbolic link as an immediate child of DIRECTORY.
707
708 Experimental: interface subject to change."
709   (declare (pathname-designator directory))
710   (let* ((fun (%coerce-callable-to-fun function))
711          (physical (physicalize-pathname directory))
712          ;; Not QUERY-FILE-SYSTEM :EXISTENCE, since it doesn't work on Windows
713          ;; network shares.
714          (realname (sb!unix:unix-realpath (native-namestring physical :as-file t)))
715          (canonical (if realname
716                         (parse-native-namestring realname
717                                                  (pathname-host physical)
718                                                  (sane-default-pathname-defaults)
719                                                  :as-directory t)
720                         (return-from map-directory nil)))
721          (dirname (native-namestring canonical)))
722     (flet ((map-it (name dirp)
723              (funcall fun
724                       (merge-pathnames (parse-native-namestring
725                                         name nil physical :as-directory dirp)
726                                        physical))))
727       (with-native-directory-iterator (next dirname :errorp errorp)
728        (loop for name = (next)
729              while name
730              do (let* ((full (concatenate 'string dirname name))
731                        (kind (native-file-kind full)))
732                   (when kind
733                     (case kind
734                       (:directory
735                        (when directories
736                          (map-it name t)))
737                       (:symlink
738                        (let* ((tmpname (merge-pathnames
739                                         (parse-native-namestring
740                                          name nil physical :as-directory nil)
741                                         physical))
742                               (truename (query-file-system tmpname :truename nil)))
743                          (if (or (not truename)
744                                  (or (pathname-name truename) (pathname-type truename)))
745                              (when files
746                                (funcall fun tmpname))
747                              (when directories
748                                (map-it name t)))))
749                       (t
750                        ;; Anything else parses as a file.
751                        (when files
752                          (map-it name nil)))))))))))
753
754 ;;; Part of DIRECTORY: implements matching the directory spec. Calls FUNCTION
755 ;;; with all DIRECTORIES that match the directory portion of PATHSPEC.
756 (defun map-matching-directories (function pathspec)
757   (let* ((dir (pathname-directory pathspec))
758          (length (length dir))
759          (wild (position-if (lambda (elt)
760                               (or (eq :wild elt) (typep elt 'pattern)))
761                             dir))
762          (wild-inferiors (position :wild-inferiors dir))
763          (end (cond ((and wild wild-inferiors)
764                      (min wild wild-inferiors))
765                     (t
766                      (or wild wild-inferiors length))))
767          (rest (subseq dir end))
768          (starting-point (make-pathname :directory (subseq dir 0 end)
769                                         :device (pathname-device pathspec)
770                                         :host (pathname-host pathspec)
771                                         :name nil
772                                         :type nil
773                                         :version nil)))
774     (cond (wild-inferiors
775            (map-wild-inferiors function rest starting-point))
776           (wild
777            (map-wild function rest starting-point))
778           (t
779            ;; Nothing wild -- the directory matches itself.
780            (funcall function starting-point))))
781   nil)
782
783 (defun last-directory-piece (pathname)
784   (car (last (pathname-directory pathname))))
785
786 ;;; Part of DIRECTORY: implements iterating over a :WILD or pattern component
787 ;;; in the directory spec.
788 (defun map-wild (function more directory)
789   (let ((this (pop more))
790         (next (car more)))
791     (flet ((cont (subdirectory)
792              (cond ((not more)
793                     ;; end of the line
794                     (funcall function subdirectory))
795                    ((or (eq :wild next) (typep next 'pattern))
796                     (lambda (pathname)
797                       (map-wild function more pathname)))
798                    ((eq :wild-inferiors next)
799                     (lambda (pathname)
800                       (map-wild-inferiors function more pathname)))
801                    (t
802                     (lambda (pathname)
803                       (let ((this (pathname-directory pathname)))
804                         (when (equal next (car (last this)))
805                           (map-matching-directories
806                            function
807                            (make-pathname :directory (append this more)
808                                           :defaults pathname)))))))))
809       (map-directory
810        (if (eq :wild this)
811            #'cont
812            (lambda (sub)
813              (when (pattern-matches this (last-directory-piece sub))
814                (funcall #'cont sub))))
815        directory
816        :files nil
817        :directories t
818        :errorp nil))))
819
820 ;;; Part of DIRECTORY: implements iterating over a :WILD-INFERIORS component
821 ;;; in the directory spec.
822 (defun map-wild-inferiors (function more directory)
823   (loop while (member (car more) '(:wild :wild-inferiors))
824         do (pop more))
825   (let ((next (car more))
826         (rest (cdr more)))
827     (unless more
828       (funcall function directory))
829     (map-directory
830      (cond ((not more)
831             (lambda (pathname)
832               (funcall function pathname)
833               (map-wild-inferiors function more pathname)))
834            (t
835             (lambda (pathname)
836               (let ((this (pathname-directory pathname)))
837                 (when (equal next (car (last this)))
838                   (map-matching-directories
839                    function
840                    (make-pathname :directory (append this rest)
841                                   :defaults pathname)))
842                 (map-wild-inferiors function more pathname)))))
843      directory
844      :files nil
845      :directories t
846      :errorp nil)))
847
848 ;;; Part of DIRECTORY: implements iterating over files in a directory, and matching
849 ;;; them.
850 (defun map-matching-files (function directory match-name match-type match-dir)
851   (map-directory
852    (lambda (file)
853      (let ((pname (pathname-name file))
854            (ptype (pathname-type file)))
855        (when (if (or pname ptype)
856                  (and (funcall match-name pname) (funcall match-type ptype))
857                  (funcall match-dir (last-directory-piece file)))
858          (funcall function file))))
859    directory
860    :files t
861    :directories t
862    :errorp nil))
863
864 ;;; NOTE: There is a fair amount of hair below that is probably not
865 ;;; strictly necessary.
866 ;;;
867 ;;; The issue is the following: what does (DIRECTORY "SYS:*;") mean?
868 ;;; Until 2004-01, SBCL's behaviour was unquestionably wrong, as it
869 ;;; did not translate the logical pathname at all, but instead treated
870 ;;; it as a physical one.  Other Lisps seem to to treat this call as
871 ;;; equivalent to (DIRECTORY (TRANSLATE-LOGICAL-PATHNAME "SYS:*;")),
872 ;;; which is fine as far as it goes, but not very interesting, and
873 ;;; arguably counterintuitive.  (PATHNAME-MATCH-P "SYS:SRC;" "SYS:*;")
874 ;;; is true, so why should "SYS:SRC;" not show up in the call to
875 ;;; DIRECTORY?  (assuming the physical pathname corresponding to it
876 ;;; exists, of course).
877 ;;;
878 ;;; So, the interpretation that I am pushing is for all pathnames
879 ;;; matching the input pathname to be queried.  This means that we
880 ;;; need to compute the intersection of the input pathname and the
881 ;;; logical host FROM translations, and then translate the resulting
882 ;;; pathname using the host to the TO translation; this treatment is
883 ;;; recursively invoked until we get a physical pathname, whereupon
884 ;;; our physical DIRECTORY implementation takes over.
885
886 ;;; FIXME: this is an incomplete implementation.  It only works when
887 ;;; both are logical pathnames (which is OK, because that's the only
888 ;;; case when we call it), but there are other pitfalls as well: see
889 ;;; the DIRECTORY-HELPER below for some, but others include a lack of
890 ;;; pattern handling.
891
892 ;;; The above was written by CSR, I (RMK) believe.  The argument that
893 ;;; motivates the interpretation is faulty, however: PATHNAME-MATCH-P
894 ;;; returns true for (PATHNAME-MATCH-P #P"/tmp/*/" #P"/tmp/../"), but
895 ;;; the latter pathname is not in the result of DIRECTORY on the
896 ;;; former.  Indeed, if DIRECTORY were constrained to return the
897 ;;; truename for every pathname for which PATHNAME-MATCH-P returned
898 ;;; true and which denoted a filename that named an existing file,
899 ;;; (DIRECTORY #P"/tmp/**/") would be required to list every file on a
900 ;;; Unix system, since any file can be named as though it were "below"
901 ;;; /tmp, given the dotdot entries.  So I think the strongest
902 ;;; "consistency" we can define between PATHNAME-MATCH-P and DIRECTORY
903 ;;; is that PATHNAME-MATCH-P returns true of everything DIRECTORY
904 ;;; returns, but not vice versa.
905
906 ;;; In any case, even if the motivation were sound, DIRECTORY on a
907 ;;; wild logical pathname has no portable semantics.  I see nothing in
908 ;;; ANSI that requires implementations to support wild physical
909 ;;; pathnames, and so there need not be any translation of a wild
910 ;;; logical pathname to a phyiscal pathname.  So a program that calls
911 ;;; DIRECTORY on a wild logical pathname is doing something
912 ;;; non-portable at best.  And if the only sensible semantics for
913 ;;; DIRECTORY on a wild logical pathname is something like the
914 ;;; following, it would be just as well if it signaled an error, since
915 ;;; a program can't possibly rely on the result of an intersection of
916 ;;; user-defined translations with a file system probe.  (Potentially
917 ;;; useful kinds of "pathname" that might not support wildcards could
918 ;;; include pathname hosts that model unqueryable namespaces like HTTP
919 ;;; URIs, or that model namespaces that it's not convenient to
920 ;;; investigate, such as the namespace of TCP ports that some network
921 ;;; host listens on.  I happen to think it a bad idea to try to
922 ;;; shoehorn such namespaces into a pathnames system, but people
923 ;;; sometimes claim to want pathnames for these things.)  -- RMK
924 ;;; 2007-12-31.
925
926 (defun pathname-intersections (one two)
927   (aver (logical-pathname-p one))
928   (aver (logical-pathname-p two))
929   (labels
930       ((intersect-version (one two)
931          (aver (typep one '(or null (member :newest :wild :unspecific)
932                             integer)))
933          (aver (typep two '(or null (member :newest :wild :unspecific)
934                             integer)))
935          (cond
936            ((eq one :wild) two)
937            ((eq two :wild) one)
938            ((or (null one) (eq one :unspecific)) two)
939            ((or (null two) (eq two :unspecific)) one)
940            ((eql one two) one)
941            (t nil)))
942        (intersect-name/type (one two)
943          (aver (typep one '(or null (member :wild :unspecific) string)))
944          (aver (typep two '(or null (member :wild :unspecific) string)))
945          (cond
946            ((eq one :wild) two)
947            ((eq two :wild) one)
948            ((or (null one) (eq one :unspecific)) two)
949            ((or (null two) (eq two :unspecific)) one)
950            ((string= one two) one)
951            (t nil)))
952        (intersect-directory (one two)
953          (aver (typep one '(or null (member :wild :unspecific) list)))
954          (aver (typep two '(or null (member :wild :unspecific) list)))
955          (cond
956            ((eq one :wild) two)
957            ((eq two :wild) one)
958            ((or (null one) (eq one :unspecific)) two)
959            ((or (null two) (eq two :unspecific)) one)
960            (t (aver (eq (car one) (car two)))
961               (mapcar
962                (lambda (x) (cons (car one) x))
963                (intersect-directory-helper (cdr one) (cdr two)))))))
964     (let ((version (intersect-version
965                     (pathname-version one) (pathname-version two)))
966           (name (intersect-name/type
967                  (pathname-name one) (pathname-name two)))
968           (type (intersect-name/type
969                  (pathname-type one) (pathname-type two)))
970           (host (pathname-host one)))
971       (mapcar (lambda (d)
972                 (make-pathname :host host :name name :type type
973                                :version version :directory d))
974               (intersect-directory
975                (pathname-directory one) (pathname-directory two))))))
976
977 ;;; FIXME: written as its own function because I (CSR) don't
978 ;;; understand it, so helping both debuggability and modularity.  In
979 ;;; case anyone is motivated to rewrite it, it returns a list of
980 ;;; sublists representing the intersection of the two input directory
981 ;;; paths (excluding the initial :ABSOLUTE or :RELATIVE).
982 ;;;
983 ;;; FIXME: Does not work with :UP or :BACK
984 ;;; FIXME: Does not work with patterns
985 ;;;
986 ;;; FIXME: PFD suggests replacing this implementation with a DFA
987 ;;; conversion of a NDFA.  Find out (a) what this means and (b) if it
988 ;;; turns out to be worth it.
989 (defun intersect-directory-helper (one two)
990   (flet ((simple-intersection (cone ctwo)
991            (cond
992              ((eq cone :wild) ctwo)
993              ((eq ctwo :wild) cone)
994              (t (aver (typep cone 'string))
995                 (aver (typep ctwo 'string))
996                 (if (string= cone ctwo) cone nil)))))
997     (macrolet
998         ((loop-possible-wild-inferiors-matches
999              (lower-bound bounding-sequence order)
1000            (let ((index (gensym)) (g2 (gensym)) (g3 (gensym)) (l (gensym)))
1001              `(let ((,l (length ,bounding-sequence)))
1002                (loop for ,index from ,lower-bound to ,l
1003                 append (mapcar (lambda (,g2)
1004                                  (append
1005                                   (butlast ,bounding-sequence (- ,l ,index))
1006                                   ,g2))
1007                         (mapcar
1008                          (lambda (,g3)
1009                            (append
1010                             (if (eq (car (nthcdr ,index ,bounding-sequence))
1011                                     :wild-inferiors)
1012                                 '(:wild-inferiors)
1013                                 nil) ,g3))
1014                          (intersect-directory-helper
1015                           ,@(if order
1016                                 `((nthcdr ,index one) (cdr two))
1017                                 `((cdr one) (nthcdr ,index two)))))))))))
1018       (cond
1019         ((and (eq (car one) :wild-inferiors)
1020               (eq (car two) :wild-inferiors))
1021          (delete-duplicates
1022           (append (mapcar (lambda (x) (cons :wild-inferiors x))
1023                           (intersect-directory-helper (cdr one) (cdr two)))
1024                   (loop-possible-wild-inferiors-matches 2 one t)
1025                   (loop-possible-wild-inferiors-matches 2 two nil))
1026           :test 'equal))
1027         ((eq (car one) :wild-inferiors)
1028          (delete-duplicates (loop-possible-wild-inferiors-matches 0 two nil)
1029                             :test 'equal))
1030         ((eq (car two) :wild-inferiors)
1031          (delete-duplicates (loop-possible-wild-inferiors-matches 0 one t)
1032                             :test 'equal))
1033         ((and (null one) (null two)) (list nil))
1034         ((null one) nil)
1035         ((null two) nil)
1036         (t (and (simple-intersection (car one) (car two))
1037                 (mapcar (lambda (x) (cons (simple-intersection
1038                                            (car one) (car two)) x))
1039                         (intersect-directory-helper (cdr one) (cdr two)))))))))
1040 \f
1041 (defun ensure-directories-exist (pathspec &key verbose (mode #o777))
1042   #!+sb-doc
1043   "Test whether the directories containing the specified file
1044   actually exist, and attempt to create them if they do not.
1045   The MODE argument is a CMUCL/SBCL-specific extension to control
1046   the Unix permission bits."
1047   (let ((pathname (physicalize-pathname (merge-pathnames (pathname pathspec))))
1048         (created-p nil))
1049     (when (wild-pathname-p pathname)
1050       (error 'simple-file-error
1051              :format-control "bad place for a wild pathname"
1052              :pathname pathspec))
1053     (let ((dir (pathname-directory pathname)))
1054       (loop for i from 1 upto (length dir)
1055             do (let ((newpath (make-pathname
1056                                :host (pathname-host pathname)
1057                                :device (pathname-device pathname)
1058                                :directory (subseq dir 0 i))))
1059                  (unless (probe-file newpath)
1060                    (let ((namestring (coerce (native-namestring newpath)
1061                                              'string)))
1062                      (when verbose
1063                        (format *standard-output*
1064                                "~&creating directory: ~A~%"
1065                                namestring))
1066                      (sb!unix:unix-mkdir namestring mode)
1067                      (unless (probe-file newpath)
1068                        (restart-case (error
1069                                       'simple-file-error
1070                                       :pathname pathspec
1071                                       :format-control
1072                                       "can't create directory ~A"
1073                                       :format-arguments (list namestring))
1074                          (retry ()
1075                            :report "Retry directory creation."
1076                            (ensure-directories-exist
1077                             pathspec
1078                             :verbose verbose :mode mode))
1079                          (continue ()
1080                            :report
1081                            "Continue as if directory creation was successful."
1082                            nil)))
1083                      (setf created-p t)))))
1084       (values pathspec created-p))))
1085
1086 (/show0 "filesys.lisp 1000")