Fix typos in docstrings and function names.
[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         #!+win32
295         (case query-for
296           ((:existence :truename)
297            (multiple-value-bind (file kind)
298                (sb!win32::native-probe-file-name filename)
299              (when (and (not file) kind)
300                (setf file filename))
301              ;; The following OR was an AND, but that breaks files like NUL,
302              ;; for which GetLongPathName succeeds yet GetFileAttributesEx
303              ;; fails to return the file kind. --DFL
304              (if (or file kind)
305                  (values
306                   (parse-native-namestring
307                    file
308                    (pathname-host pathname)
309                    (sane-default-pathname-defaults)
310                    :as-directory (eq :directory kind)))
311                  (fail "couldn't resolve ~A" filename
312                        (- (sb!win32:get-last-error))))))
313           (:write-date
314            (or (sb!win32::native-file-write-date filename)
315                (fail "couldn't query write date of ~A" filename
316                      (- (sb!win32:get-last-error))))))
317         #!-win32
318         (multiple-value-bind (existsp errno ino mode nlink uid gid rdev size
319                                       atime mtime)
320             (sb!unix:unix-stat filename)
321           (declare (ignore ino nlink gid rdev size atime))
322           (labels ((parse (filename &key (as-directory
323                                           (eql (logand mode
324                                                        sb!unix:s-ifmt)
325                                                sb!unix:s-ifdir)))
326                      (values
327                       (parse-native-namestring
328                        filename
329                        (pathname-host pathname)
330                        (sane-default-pathname-defaults)
331                        :as-directory as-directory)))
332                    (resolve-problematic-symlink (&optional realpath-failed)
333                      ;; SBCL has for many years had a policy that a pathname
334                      ;; that names an existing, dangling or self-referential
335                      ;; symlink denotes the symlink itself.  stat(2) fails
336                      ;; and sets errno to ENOENT or ELOOP respectively, but
337                      ;; we must distinguish cases where the symlink exists
338                      ;; from ones where there's a loop in the apparent
339                      ;; containing directory.
340                      ;; Also handles symlinks in /proc/pid/fd/ to
341                      ;; pipes or sockets on Linux
342                      (multiple-value-bind (linkp ignore ino mode nlink uid gid rdev
343                                            size atime mtime)
344                          (sb!unix:unix-lstat filename)
345                        (declare (ignore ignore ino mode nlink gid rdev size atime))
346                        (when (and (or (= errno sb!unix:enoent)
347                                       (= errno sb!unix:eloop)
348                                       realpath-failed)
349                                   linkp)
350                          (return-from query-file-system
351                            (case query-for
352                              (:existence
353                               ;; We do this reparse so as to return a
354                               ;; normalized pathname.
355                               (parse filename :as-directory nil))
356                              (:truename
357                               ;; So here's a trick: since lstat succeded,
358                               ;; FILENAME exists, so its directory exists and
359                               ;; only the non-directory part is loopy.  So
360                               ;; let's resolve FILENAME's directory part with
361                               ;; realpath(3), in order to get a canonical
362                               ;; absolute name for the directory, and then
363                               ;; return a pathname having PATHNAME's name,
364                               ;; type, and version, but the rest from the
365                               ;; truename of the directory.  Since we turned
366                               ;; PATHNAME into FILENAME "as a file", FILENAME
367                               ;; does not end in a slash, and so we get the
368                               ;; directory part of FILENAME by reparsing
369                               ;; FILENAME and masking off its name, type, and
370                               ;; version bits.  But note not to call ourselves
371                               ;; recursively, because we don't want to
372                               ;; re-merge against *DEFAULT-PATHNAME-DEFAULTS*,
373                               ;; since PATHNAME may be a relative pathname.
374                               (merge-pathnames
375                                (parse
376                                 (multiple-value-bind (realpath errno)
377                                     (sb!unix:unix-realpath
378                                      (native-namestring
379                                       (make-pathname
380                                        :name :unspecific
381                                        :type :unspecific
382                                        :version :unspecific
383                                        :defaults (parse filename
384                                                         :as-directory nil))))
385                                   (or realpath
386                                       (fail "couldn't resolve ~A" filename errno)))
387                                 :as-directory t)
388                                pathname))
389                              (:author (sb!unix:uid-username uid))
390                              (:write-date (+ unix-to-universal-time mtime))))))
391                      ;; If we're still here, the file doesn't exist; error.
392                      (fail
393                       (format nil "failed to find the ~A of ~~A" query-for)
394                       pathspec errno)))
395             (if existsp
396                 (case query-for
397                   (:existence (parse filename))
398                   (:truename
399                    ;; Note: in case the file is stat'able, POSIX
400                    ;; realpath(3) gets us a canonical absolute
401                    ;; filename, even if the post-merge PATHNAME
402                    ;; is not absolute
403                    (parse (or (sb!unix:unix-realpath filename)
404                               (resolve-problematic-symlink t))))
405                   (:author (sb!unix:uid-username uid))
406                   (:write-date (+ unix-to-universal-time mtime)))
407                 (resolve-problematic-symlink))))))))
408
409
410 (defun probe-file (pathspec)
411   #!+sb-doc
412   "Return the truename of PATHSPEC if the truename can be found,
413 or NIL otherwise.  See TRUENAME for more information."
414   (query-file-system pathspec :truename nil))
415
416 (defun truename (pathspec)
417   #!+sb-doc
418   "If PATHSPEC is a pathname that names an existing file, return
419 a pathname that denotes a canonicalized name for the file.  If
420 pathspec is a stream associated with a file, return a pathname
421 that denotes a canonicalized name for the file associated with
422 the stream.
423
424 An error of type FILE-ERROR is signalled if no such file exists
425 or if the file system is such that a canonicalized file name
426 cannot be determined or if the pathname is wild.
427
428 Under Unix, the TRUENAME of a symlink that links to itself or to
429 a file that doesn't exist is considered to be the name of the
430 broken symlink itself."
431   ;; Note that eventually this routine might be different for streams
432   ;; than for other pathname designators.
433   (if (streamp pathspec)
434       (query-file-system pathspec :truename)
435       (query-file-system pathspec :truename)))
436
437 (defun file-author (pathspec)
438   #!+sb-doc
439   "Return the author of the file specified by PATHSPEC. Signal an
440 error of type FILE-ERROR if no such file exists, or if PATHSPEC
441 is a wild pathname."
442   (query-file-system pathspec :author))
443
444 (defun file-write-date (pathspec)
445   #!+sb-doc
446   "Return the write date of the file specified by PATHSPEC.
447 An error of type FILE-ERROR is signaled if no such file exists,
448 or if PATHSPEC is a wild pathname."
449   (query-file-system pathspec :write-date))
450 \f
451 ;;;; miscellaneous other operations
452
453 (/show0 "filesys.lisp 700")
454
455 (defun rename-file (file new-name)
456   #!+sb-doc
457   "Rename FILE to have the specified NEW-NAME. If FILE is a stream open to a
458 file, then the associated file is renamed."
459   (let* ((original (merge-pathnames file (sane-default-pathname-defaults)))
460          (old-truename (truename original))
461          (original-namestring (native-namestring (physicalize-pathname original)
462                                                  :as-file t))
463          (new-name (merge-pathnames new-name original))
464          (new-namestring (native-namestring (physicalize-pathname new-name)
465                                             :as-file t)))
466     (unless new-namestring
467       (error 'simple-file-error
468              :pathname new-name
469              :format-control "~S can't be created."
470              :format-arguments (list new-name)))
471     (multiple-value-bind (res error)
472         (sb!unix:unix-rename original-namestring new-namestring)
473       (unless res
474         (error 'simple-file-error
475                :pathname new-name
476                :format-control "~@<couldn't rename ~2I~_~A ~I~_to ~2I~_~A: ~
477                                 ~I~_~A~:>"
478                :format-arguments (list original new-name (strerror error))))
479       (when (streamp file)
480         (file-name file new-name))
481       (values new-name old-truename (truename new-name)))))
482
483 (defun delete-file (file)
484   #!+sb-doc
485   "Delete the specified FILE.
486
487 If FILE is a stream, on Windows the stream is closed immediately. On Unix
488 platforms the stream remains open, allowing IO to continue: the OS resources
489 associated with the deleted file remain available till the stream is closed as
490 per standard Unix unlink() behaviour."
491   (let* ((pathname (translate-logical-pathname
492                     (merge-pathnames file (sane-default-pathname-defaults))))
493          (namestring (native-namestring pathname :as-file t)))
494     #!+win32
495     (when (streamp file)
496       (close file))
497     (multiple-value-bind (res err)
498         #!-win32 (sb!unix:unix-unlink namestring)
499         #!+win32 (or (sb!win32::native-delete-file namestring)
500                      (values nil (- (sb!win32:get-last-error))))
501         (unless res
502           (simple-file-perror "couldn't delete ~A" namestring err))))
503   t)
504
505 (defun directorize-pathname (pathname)
506   (if (or (pathname-name pathname)
507           (pathname-type pathname))
508       (make-pathname :directory (append (pathname-directory pathname)
509                                         (list (file-namestring pathname)))
510                      :host (pathname-host pathname)
511                      :device (pathname-device pathname))
512       pathname))
513
514 (defun delete-directory (pathspec &key recursive)
515   "Deletes the directory designated by PATHSPEC (a pathname designator).
516 Returns the truename of the directory deleted.
517
518 If RECURSIVE is false \(the default), signals an error unless the directory is
519 empty. If RECURSIVE is true, first deletes all files and subdirectories. If
520 RECURSIVE is true and the directory contains symbolic links, the links are
521 deleted, not the files and directories they point to.
522
523 Signals an error if PATHSPEC designates a file or a symbolic link instead of a
524 directory, or if the directory could not be deleted for any reason.
525
526 Both
527
528    \(DELETE-DIRECTORY \"/tmp/foo\")
529    \(DELETE-DIRECTORY \"/tmp/foo/\")
530
531 delete the \"foo\" subdirectory of \"/tmp\", or signal an error if it does not
532 exist or if is a file or a symbolic link."
533   (declare (type pathname-designator pathspec))
534   (let ((physical (directorize-pathname
535                    (physicalize-pathname
536                     (merge-pathnames
537                      pathspec (sane-default-pathname-defaults))))))
538     (labels ((recurse-merged (dir)
539                (lambda (sub)
540                  (recurse (merge-pathnames sub dir))))
541              (delete-merged (dir)
542                (lambda (file)
543                  (delete-file (merge-pathnames file dir))))
544              (recurse (dir)
545                (map-directory (recurse-merged dir) dir
546                               :files nil
547                               :directories t
548                               :classify-symlinks nil)
549                (map-directory (delete-merged dir) dir
550                               :files t
551                               :directories nil
552                               :classify-symlinks nil)
553                (delete-dir dir))
554              (delete-dir (dir)
555                (let ((namestring (native-namestring dir :as-file t)))
556                  (multiple-value-bind (res errno)
557                      #!+win32
558                      (or (sb!win32::native-delete-directory namestring)
559                          (values nil (- (sb!win32:get-last-error))))
560                      #!-win32
561                      (values
562                       (not (minusp (alien-funcall
563                                     (extern-alien "rmdir"
564                                                   (function int c-string))
565                                     namestring)))
566                       (get-errno))
567                      (if res
568                          dir
569                          (simple-file-perror
570                           "Could not delete directory ~A"
571                           namestring errno))))))
572       (if recursive
573           (recurse physical)
574           (delete-dir physical)))))
575
576 \f
577 (defun sbcl-homedir-pathname ()
578   (let ((sbcl-home (posix-getenv "SBCL_HOME")))
579     ;; SBCL_HOME isn't set for :EXECUTABLE T embedded cores
580     (when (and sbcl-home (not (string= sbcl-home "")))
581       (parse-native-namestring sbcl-home
582                                *physical-host*
583                                *default-pathname-defaults*
584                                :as-directory t))))
585
586 (defun user-homedir-namestring (&optional username)
587   (flet ((not-empty (x)
588            (and (not (equal x "")) x)))
589     (if username
590         (sb!unix:user-homedir username)
591         (or (not-empty (posix-getenv "HOME"))
592             #!+win32
593             (not-empty (posix-getenv "USERPROFILE"))
594             #!+win32
595             (let ((drive (not-empty (posix-getenv "HOMEDRIVE")))
596                   (path (not-empty (posix-getenv "HOMEPATH"))))
597               (and drive path
598                    (concatenate 'string drive path)))
599             #!-win32
600             (not-empty (sb!unix:uid-homedir (sb!unix:unix-getuid)))
601             (error "Couldn't find home directory.")))))
602
603 ;;; (This is an ANSI Common Lisp function.)
604 (defun user-homedir-pathname (&optional host)
605   #!+sb-doc
606   "Return the home directory of the user as a pathname. If the HOME
607 environment variable has been specified, the directory it designates
608 is returned; otherwise obtains the home directory from the operating
609 system. HOST argument is ignored by SBCL."
610   (declare (ignore host))
611   (values
612    (parse-native-namestring
613     (or (user-homedir-namestring)
614         #!+win32
615         (sb!win32::get-folder-namestring sb!win32::csidl_profile))
616     *physical-host*
617     *default-pathname-defaults*
618     :as-directory t)))
619
620 \f
621 ;;;; DIRECTORY
622
623 (defun directory (pathspec &key (resolve-symlinks t))
624   #!+sb-doc
625   "Return a list of PATHNAMEs, each the TRUENAME of a file that matched the
626 given pathname. Note that the interaction between this ANSI-specified
627 TRUENAMEing and the semantics of the Unix filesystem (symbolic links..) means
628 this function can sometimes return files which don't have the same directory
629 as PATHNAME. If :RESOLVE-SYMLINKS is NIL, don't resolve symbolic links in
630 matching filenames."
631   (let (;; We create one entry in this hash table for each truename,
632         ;; as an asymptotically efficient way of removing duplicates
633         ;; (which can arise when e.g. multiple symlinks map to the
634         ;; same truename).
635         (truenames (make-hash-table :test #'equal)))
636     (labels ((record (pathname)
637                (let ((truename (if resolve-symlinks
638                                    ;; FIXME: Why not not TRUENAME?  As reported by
639                                    ;; Milan Zamazal sbcl-devel 2003-10-05, using
640                                    ;; TRUENAME causes a race condition whereby
641                                    ;; removal of a file during the directory
642                                    ;; operation causes an error.  It's not clear
643                                    ;; what the right thing to do is, though.  --
644                                    ;; CSR, 2003-10-13
645                                    (query-file-system pathname :truename nil)
646                                    (query-file-system pathname :existence nil))))
647                  (when truename
648                    (setf (gethash (namestring truename) truenames)
649                          truename))))
650              (do-physical-pathnames (pathname)
651                (aver (not (logical-pathname-p pathname)))
652                (let* (;; KLUDGE: Since we don't canonize pathnames on construction,
653                       ;; we really have to do it here to get #p"foo/." mean the same
654                       ;; as #p"foo/./".
655                       (pathname (canonicalize-pathname pathname))
656                       (name (pathname-name pathname))
657                       (type (pathname-type pathname))
658                       (match-name (make-matcher name))
659                       (match-type (make-matcher type)))
660                  (map-matching-directories
661                   (if (or name type)
662                       (lambda (directory)
663                         (map-matching-entries #'record
664                                               directory
665                                               match-name
666                                               match-type))
667                       #'record)
668                   pathname)))
669              (do-pathnames (pathname)
670                (if (logical-pathname-p pathname)
671                    (let ((host (intern-logical-host (pathname-host pathname))))
672                      (dolist (x (logical-host-canon-transls host))
673                        (destructuring-bind (from to) x
674                          (let ((intersections
675                                 (pathname-intersections pathname from)))
676                            (dolist (p intersections)
677                              (do-pathnames (translate-pathname p from to)))))))
678                    (do-physical-pathnames pathname))))
679       (declare (truly-dynamic-extent #'record))
680       (do-pathnames (merge-pathnames pathspec)))
681     (mapcar #'cdr
682             ;; Sorting isn't required by the ANSI spec, but sorting into some
683             ;; canonical order seems good just on the grounds that the
684             ;; implementation should have repeatable behavior when possible.
685             (sort (loop for namestring being each hash-key in truenames
686                         using (hash-value truename)
687                         collect (cons namestring truename))
688                   #'string<
689                   :key #'car))))
690
691 (defun canonicalize-pathname (pathname)
692   ;; We're really only interested in :UNSPECIFIC -> NIL, :BACK and :UP,
693   ;; and dealing with #p"foo/.." and #p"foo/."
694   (labels ((simplify (piece)
695              (unless (eq :unspecific piece)
696                piece))
697            (canonicalize-directory (directory)
698              (let (pieces)
699                (dolist (piece directory)
700                  (cond
701                     ((and pieces (member piece '(:back :up)))
702                      ;; FIXME: We should really canonicalize when we construct
703                      ;; pathnames. This is just wrong.
704                      (case (car pieces)
705                        ((:absolute :wild-inferiors)
706                         (error 'simple-file-error
707                                :format-control "Invalid use of ~S after ~S."
708                                :format-arguments (list piece (car pieces))
709                                :pathname pathname))
710                        ((:relative :up :back)
711                         (push piece pieces))
712                        (t
713                         (pop pieces))))
714                     ((equal piece ".")
715                      ;; This case only really matters on Windows,
716                      ;; because on POSIX, our call site (TRUENAME via
717                      ;; QUERY-FILE-SYSTEM) only passes in pathnames from
718                      ;; realpath(3), in which /./ has been removed
719                      ;; already.  Windows, however, depends on us to
720                      ;; perform this fixup. -- DFL
721                      )
722                     (t
723                      (push piece pieces))))
724                (nreverse pieces))))
725     (let ((name (simplify (pathname-name pathname)))
726           (type (simplify (pathname-type pathname)))
727           (dir (canonicalize-directory (pathname-directory pathname))))
728       (cond ((equal "." name)
729              (cond ((not type)
730                     (make-pathname :name nil :defaults pathname))
731                    ((equal "" type)
732                     (make-pathname :name nil
733                                    :type nil
734                                    :directory (butlast dir)
735                                    :defaults pathname))))
736             (t
737              (make-pathname :name name :type type
738                             :directory dir
739                             :defaults pathname))))))
740
741 ;;; Given a native namestring, provides a WITH-HASH-TABLE-ITERATOR style
742 ;;; interface to mapping over namestrings of entries in the corresponding
743 ;;; directory.
744 (defmacro with-native-directory-iterator ((iterator namestring &key errorp) &body body)
745   (with-unique-names (one-iter)
746     `(dx-flet
747          ((iterate (,one-iter)
748             (declare (type function ,one-iter))
749             (macrolet ((,iterator ()
750                          `(funcall ,',one-iter)))
751               ,@body)))
752        #!+win32
753        (sb!win32::native-call-with-directory-iterator
754         #'iterate ,namestring ,errorp)
755        #!-win32
756        (call-with-native-directory-iterator #'iterate ,namestring ,errorp))))
757
758 (defun call-with-native-directory-iterator (function namestring errorp)
759   (declare (type (or null string) namestring)
760            (function function))
761   (let (dp)
762     (when namestring
763       (dx-flet
764           ((one-iter ()
765              (tagbody
766               :next
767                 (let ((ent (sb!unix:unix-readdir dp nil)))
768                   (when ent
769                     (let ((name (sb!unix:unix-dirent-name ent)))
770                       (when name
771                         (cond ((equal "." name)
772                                (go :next))
773                               ((equal ".." name)
774                                (go :next))
775                               (t
776                                (return-from one-iter name))))))))))
777         (unwind-protect
778              (progn
779                (setf dp (sb!unix:unix-opendir namestring errorp))
780                (when dp
781                  (funcall function #'one-iter)))
782           (when dp
783             (sb!unix:unix-closedir dp nil)))))))
784
785 ;;; This is our core directory access interface that we use to implement
786 ;;; DIRECTORY.
787 (defun map-directory (function directory &key (files t) (directories t)
788                       (classify-symlinks t) (errorp t))
789   #!+sb-doc
790   "Map over entries in DIRECTORY. Keyword arguments specify which entries to
791 map over, and how:
792
793  :FILES
794     If true, call FUNCTION with the pathname of each file in DIRECTORY.
795     Defaults to T.
796
797  :DIRECTORIES
798    If true, call FUNCTION with a pathname for each subdirectory of DIRECTORY.
799    If :AS-FILES, the pathname used is a pathname designating the subdirectory
800    as a file in DIRECTORY. Otherwise the pathname used is a directory
801    pathname. Defaults to T.
802
803  :CLASSIFY-SYMLINKS
804    If true, the decision to call FUNCTION with the pathname of a symbolic link
805    depends on the resolution of the link: if it points to a directory, it is
806    considered a directory entry, otherwise a file entry. If false, all
807    symbolic links are considered file entries. In both cases the pathname used
808    for the symbolic link is not fully resolved, but names it as an immediate
809    child of DIRECTORY. Defaults to T.
810
811  :ERRORP
812    If true, signal an error if DIRECTORY does not exist, cannot be read, etc.
813    Defaults to T.
814
815 Experimental: interface subject to change."
816   (declare (pathname-designator directory))
817   (let* ((fun (%coerce-callable-to-fun function))
818          (as-files (eq :as-files directories))
819          (physical (physicalize-pathname directory))
820          (realname (query-file-system physical :existence nil))
821          (canonical (if realname
822                         (parse-native-namestring realname
823                                                  (pathname-host physical)
824                                                  (sane-default-pathname-defaults)
825                                                  :as-directory t)
826                         (return-from map-directory nil)))
827          (dirname (native-namestring canonical)))
828     (flet ((map-it (name dirp)
829              (funcall fun
830                       (merge-pathnames (parse-native-namestring
831                                         name nil physical
832                                         :as-directory (and dirp (not as-files)))
833                                        physical))))
834       (with-native-directory-iterator (next dirname :errorp errorp)
835         (loop
836           ;; provision for FindFirstFileExW-based iterator that should be used
837           ;; on Windows: file kind is known instantly there, so we'll have it
838           ;; returned by (next) soon.
839           (multiple-value-bind (name kind) (next)
840             (unless (or name kind) (return))
841             (unless kind
842               (setf kind (native-file-kind
843                           (concatenate 'string dirname name))))
844             (when kind
845               (case kind
846                 (:directory
847                  (when directories
848                    (map-it name t)))
849                 (:symlink
850                  (if classify-symlinks
851                      (let* ((tmpname (merge-pathnames
852                                       (parse-native-namestring
853                                        name nil physical :as-directory nil)
854                                       physical))
855                             (truename (query-file-system tmpname :truename nil)))
856                        (if (or (not truename)
857                                (or (pathname-name truename) (pathname-type truename)))
858                            (when files
859                              (funcall fun tmpname))
860                            (when directories
861                              (map-it name t))))
862                      (when files
863                        (map-it name nil))))
864                 (t
865                  ;; Anything else parses as a file.
866                  (when files
867                    (map-it name nil)))))))))))
868
869 ;;; Part of DIRECTORY: implements matching the directory spec. Calls FUNCTION
870 ;;; with all DIRECTORIES that match the directory portion of PATHSPEC.
871 (defun map-matching-directories (function pathspec)
872   (let* ((dir (pathname-directory pathspec))
873          (length (length dir))
874          (wild (position-if (lambda (elt)
875                               (or (eq :wild elt) (typep elt 'pattern)))
876                             dir))
877          (wild-inferiors (position :wild-inferiors dir))
878          (end (cond ((and wild wild-inferiors)
879                      (min wild wild-inferiors))
880                     (t
881                      (or wild wild-inferiors length))))
882          (rest (subseq dir end))
883          (starting-point (make-pathname :directory (subseq dir 0 end)
884                                         :device (pathname-device pathspec)
885                                         :host (pathname-host pathspec)
886                                         :name nil
887                                         :type nil
888                                         :version nil)))
889     (cond (wild-inferiors
890            (map-wild-inferiors function rest starting-point))
891           (wild
892            (map-wild function rest starting-point))
893           (t
894            ;; Nothing wild -- the directory matches itself.
895            (funcall function starting-point))))
896   nil)
897
898 (defun last-directory-piece (pathname)
899   (car (last (pathname-directory pathname))))
900
901 ;;; Part of DIRECTORY: implements iterating over a :WILD or pattern component
902 ;;; in the directory spec.
903 (defun map-wild (function more directory)
904   (let ((this (pop more))
905         (next (car more)))
906     (flet ((cont (subdirectory)
907              (cond ((not more)
908                     ;; end of the line
909                     (funcall function subdirectory))
910                    ((or (eq :wild next) (typep next 'pattern))
911                     (map-wild function more subdirectory))
912                    ((eq :wild-inferiors next)
913                     (map-wild-inferiors function more subdirectory))
914                    (t
915                     (let ((this (pathname-directory subdirectory)))
916                       (map-matching-directories
917                        function
918                        (make-pathname :directory (append this more)
919                                       :defaults subdirectory)))))))
920       (map-directory
921        (if (eq :wild this)
922            #'cont
923            (lambda (sub)
924              (when (pattern-matches this (last-directory-piece sub))
925                (funcall #'cont sub))))
926        directory
927        :files nil
928        :directories t
929        :errorp nil))))
930
931 ;;; Part of DIRECTORY: implements iterating over a :WILD-INFERIORS component
932 ;;; in the directory spec.
933 (defun map-wild-inferiors (function more directory)
934   (loop while (member (car more) '(:wild :wild-inferiors))
935         do (pop more))
936   (let ((next (car more))
937         (rest (cdr more)))
938     (unless more
939       (funcall function directory))
940     (map-directory
941      (cond ((not more)
942             (lambda (pathname)
943               (funcall function pathname)
944               (map-wild-inferiors function more pathname)))
945            (t
946             (lambda (pathname)
947               (let ((this (pathname-directory pathname)))
948                 (when (equal next (car (last this)))
949                   (map-matching-directories
950                    function
951                    (make-pathname :directory (append this rest)
952                                   :defaults pathname)))
953                 (map-wild-inferiors function more pathname)))))
954      directory
955      :files nil
956      :directories t
957      :errorp nil)))
958
959 ;;; Part of DIRECTORY: implements iterating over entries in a directory, and
960 ;;; matching them.
961 (defun map-matching-entries (function directory match-name match-type)
962   (map-directory
963    (lambda (file)
964      (when (and (funcall match-name (pathname-name file))
965                 (funcall match-type (pathname-type file)))
966        (funcall function file)))
967    directory
968    :files t
969    :directories :as-files
970    :errorp nil))
971
972 ;;; NOTE: There is a fair amount of hair below that is probably not
973 ;;; strictly necessary.
974 ;;;
975 ;;; The issue is the following: what does (DIRECTORY "SYS:*;") mean?
976 ;;; Until 2004-01, SBCL's behaviour was unquestionably wrong, as it
977 ;;; did not translate the logical pathname at all, but instead treated
978 ;;; it as a physical one.  Other Lisps seem to to treat this call as
979 ;;; equivalent to (DIRECTORY (TRANSLATE-LOGICAL-PATHNAME "SYS:*;")),
980 ;;; which is fine as far as it goes, but not very interesting, and
981 ;;; arguably counterintuitive.  (PATHNAME-MATCH-P "SYS:SRC;" "SYS:*;")
982 ;;; is true, so why should "SYS:SRC;" not show up in the call to
983 ;;; DIRECTORY?  (assuming the physical pathname corresponding to it
984 ;;; exists, of course).
985 ;;;
986 ;;; So, the interpretation that I am pushing is for all pathnames
987 ;;; matching the input pathname to be queried.  This means that we
988 ;;; need to compute the intersection of the input pathname and the
989 ;;; logical host FROM translations, and then translate the resulting
990 ;;; pathname using the host to the TO translation; this treatment is
991 ;;; recursively invoked until we get a physical pathname, whereupon
992 ;;; our physical DIRECTORY implementation takes over.
993
994 ;;; FIXME: this is an incomplete implementation.  It only works when
995 ;;; both are logical pathnames (which is OK, because that's the only
996 ;;; case when we call it), but there are other pitfalls as well: see
997 ;;; the DIRECTORY-HELPER below for some, but others include a lack of
998 ;;; pattern handling.
999
1000 ;;; The above was written by CSR, I (RMK) believe.  The argument that
1001 ;;; motivates the interpretation is faulty, however: PATHNAME-MATCH-P
1002 ;;; returns true for (PATHNAME-MATCH-P #P"/tmp/*/" #P"/tmp/../"), but
1003 ;;; the latter pathname is not in the result of DIRECTORY on the
1004 ;;; former.  Indeed, if DIRECTORY were constrained to return the
1005 ;;; truename for every pathname for which PATHNAME-MATCH-P returned
1006 ;;; true and which denoted a filename that named an existing file,
1007 ;;; (DIRECTORY #P"/tmp/**/") would be required to list every file on a
1008 ;;; Unix system, since any file can be named as though it were "below"
1009 ;;; /tmp, given the dotdot entries.  So I think the strongest
1010 ;;; "consistency" we can define between PATHNAME-MATCH-P and DIRECTORY
1011 ;;; is that PATHNAME-MATCH-P returns true of everything DIRECTORY
1012 ;;; returns, but not vice versa.
1013
1014 ;;; In any case, even if the motivation were sound, DIRECTORY on a
1015 ;;; wild logical pathname has no portable semantics.  I see nothing in
1016 ;;; ANSI that requires implementations to support wild physical
1017 ;;; pathnames, and so there need not be any translation of a wild
1018 ;;; logical pathname to a phyiscal pathname.  So a program that calls
1019 ;;; DIRECTORY on a wild logical pathname is doing something
1020 ;;; non-portable at best.  And if the only sensible semantics for
1021 ;;; DIRECTORY on a wild logical pathname is something like the
1022 ;;; following, it would be just as well if it signaled an error, since
1023 ;;; a program can't possibly rely on the result of an intersection of
1024 ;;; user-defined translations with a file system probe.  (Potentially
1025 ;;; useful kinds of "pathname" that might not support wildcards could
1026 ;;; include pathname hosts that model unqueryable namespaces like HTTP
1027 ;;; URIs, or that model namespaces that it's not convenient to
1028 ;;; investigate, such as the namespace of TCP ports that some network
1029 ;;; host listens on.  I happen to think it a bad idea to try to
1030 ;;; shoehorn such namespaces into a pathnames system, but people
1031 ;;; sometimes claim to want pathnames for these things.)  -- RMK
1032 ;;; 2007-12-31.
1033
1034 (defun pathname-intersections (one two)
1035   (aver (logical-pathname-p one))
1036   (aver (logical-pathname-p two))
1037   (labels
1038       ((intersect-version (one two)
1039          (aver (typep one '(or null (member :newest :wild :unspecific)
1040                             integer)))
1041          (aver (typep two '(or null (member :newest :wild :unspecific)
1042                             integer)))
1043          (cond
1044            ((eq one :wild) two)
1045            ((eq two :wild) one)
1046            ((or (null one) (eq one :unspecific)) two)
1047            ((or (null two) (eq two :unspecific)) one)
1048            ((eql one two) one)
1049            (t nil)))
1050        (intersect-name/type (one two)
1051          (aver (typep one '(or null (member :wild :unspecific) string)))
1052          (aver (typep two '(or null (member :wild :unspecific) string)))
1053          (cond
1054            ((eq one :wild) two)
1055            ((eq two :wild) one)
1056            ((or (null one) (eq one :unspecific)) two)
1057            ((or (null two) (eq two :unspecific)) one)
1058            ((string= one two) one)
1059            (t (return-from pathname-intersections nil))))
1060        (intersect-directory (one two)
1061          (aver (typep one '(or null (member :wild :unspecific) list)))
1062          (aver (typep two '(or null (member :wild :unspecific) list)))
1063          (cond
1064            ((eq one :wild) two)
1065            ((eq two :wild) one)
1066            ((or (null one) (eq one :unspecific)) two)
1067            ((or (null two) (eq two :unspecific)) one)
1068            (t (aver (eq (car one) (car two)))
1069               (mapcar
1070                (lambda (x) (cons (car one) x))
1071                (intersect-directory-helper (cdr one) (cdr two)))))))
1072     (let ((version (intersect-version
1073                     (pathname-version one) (pathname-version two)))
1074           (name (intersect-name/type
1075                  (pathname-name one) (pathname-name two)))
1076           (type (intersect-name/type
1077                  (pathname-type one) (pathname-type two)))
1078           (host (pathname-host one)))
1079       (mapcar (lambda (d)
1080                 (make-pathname :host host :name name :type type
1081                                :version version :directory d))
1082               (intersect-directory
1083                (pathname-directory one) (pathname-directory two))))))
1084
1085 ;;; FIXME: written as its own function because I (CSR) don't
1086 ;;; understand it, so helping both debuggability and modularity.  In
1087 ;;; case anyone is motivated to rewrite it, it returns a list of
1088 ;;; sublists representing the intersection of the two input directory
1089 ;;; paths (excluding the initial :ABSOLUTE or :RELATIVE).
1090 ;;;
1091 ;;; FIXME: Does not work with :UP or :BACK
1092 ;;; FIXME: Does not work with patterns
1093 ;;;
1094 ;;; FIXME: PFD suggests replacing this implementation with a DFA
1095 ;;; conversion of a NDFA.  Find out (a) what this means and (b) if it
1096 ;;; turns out to be worth it.
1097 (defun intersect-directory-helper (one two)
1098   (flet ((simple-intersection (cone ctwo)
1099            (cond
1100              ((eq cone :wild) ctwo)
1101              ((eq ctwo :wild) cone)
1102              (t (aver (typep cone 'string))
1103                 (aver (typep ctwo 'string))
1104                 (if (string= cone ctwo) cone nil)))))
1105     (macrolet
1106         ((loop-possible-wild-inferiors-matches
1107              (lower-bound bounding-sequence order)
1108            (let ((index (gensym)) (g2 (gensym)) (g3 (gensym)) (l (gensym)))
1109              `(let ((,l (length ,bounding-sequence)))
1110                (loop for ,index from ,lower-bound to ,l
1111                 append (mapcar (lambda (,g2)
1112                                  (append
1113                                   (butlast ,bounding-sequence (- ,l ,index))
1114                                   ,g2))
1115                         (mapcar
1116                          (lambda (,g3)
1117                            (append
1118                             (if (eq (car (nthcdr ,index ,bounding-sequence))
1119                                     :wild-inferiors)
1120                                 '(:wild-inferiors)
1121                                 nil) ,g3))
1122                          (intersect-directory-helper
1123                           ,@(if order
1124                                 `((nthcdr ,index one) (cdr two))
1125                                 `((cdr one) (nthcdr ,index two)))))))))))
1126       (cond
1127         ((and (eq (car one) :wild-inferiors)
1128               (eq (car two) :wild-inferiors))
1129          (delete-duplicates
1130           (append (mapcar (lambda (x) (cons :wild-inferiors x))
1131                           (intersect-directory-helper (cdr one) (cdr two)))
1132                   (loop-possible-wild-inferiors-matches 2 one t)
1133                   (loop-possible-wild-inferiors-matches 2 two nil))
1134           :test 'equal))
1135         ((eq (car one) :wild-inferiors)
1136          (delete-duplicates (loop-possible-wild-inferiors-matches 0 two nil)
1137                             :test 'equal))
1138         ((eq (car two) :wild-inferiors)
1139          (delete-duplicates (loop-possible-wild-inferiors-matches 0 one t)
1140                             :test 'equal))
1141         ((and (null one) (null two)) (list nil))
1142         ((null one) nil)
1143         ((null two) nil)
1144         (t (and (simple-intersection (car one) (car two))
1145                 (mapcar (lambda (x) (cons (simple-intersection
1146                                            (car one) (car two)) x))
1147                         (intersect-directory-helper (cdr one) (cdr two)))))))))
1148 \f
1149
1150 (defun directory-pathname-p (pathname)
1151   (and (pathnamep pathname)
1152        (null (pathname-name pathname))
1153        (null (pathname-type pathname))))
1154
1155 (defun ensure-directories-exist (pathspec &key verbose (mode #o777))
1156   #!+sb-doc
1157   "Test whether the directories containing the specified file
1158   actually exist, and attempt to create them if they do not.
1159   The MODE argument is a CMUCL/SBCL-specific extension to control
1160   the Unix permission bits."
1161   (let ((pathname (physicalize-pathname (merge-pathnames (pathname pathspec))))
1162         (created-p nil))
1163     (when (wild-pathname-p pathname)
1164       (error 'simple-file-error
1165              :format-control "bad place for a wild pathname"
1166              :pathname pathspec))
1167     (let* ((dir (pathname-directory pathname))
1168            (*default-pathname-defaults*
1169              (make-pathname :directory dir :device (pathname-device pathname)))
1170           (dev (pathname-device pathname)))
1171       (loop for i from (case dev (:unc 3) (otherwise 2))
1172               upto (length dir)
1173             do
1174             (let* ((newpath (make-pathname
1175                              :host (pathname-host pathname)
1176                              :device dev
1177                              :directory (subseq dir 0 i)))
1178                    (probed (probe-file newpath)))
1179               (unless (directory-pathname-p probed)
1180                 (let ((namestring (coerce (native-namestring newpath)
1181                                           'string)))
1182                   (when verbose
1183                     (format *standard-output*
1184                             "~&creating directory: ~A~%"
1185                             namestring))
1186                   (sb!unix:unix-mkdir namestring mode)
1187                   (unless (directory-pathname-p (probe-file newpath))
1188                     (restart-case
1189                         (error
1190                          'simple-file-error
1191                          :pathname pathspec
1192                          :format-control
1193                          (if (and probed
1194                                   (not (directory-pathname-p probed)))
1195                              "Can't create directory ~A,~
1196                                  ~%a file with the same name already exists."
1197                              "Can't create directory ~A")
1198                          :format-arguments (list namestring))
1199                       (retry ()
1200                         :report "Retry directory creation."
1201                         (ensure-directories-exist
1202                          pathspec
1203                          :verbose verbose :mode mode))
1204                       (continue ()
1205                         :report
1206                         "Continue as if directory creation was successful."
1207                         nil)))
1208                   (setf created-p t)))))
1209       (values pathspec created-p))))
1210
1211 (/show0 "filesys.lisp 1000")