1/* File: dcg/files.pl 2 Author: Roy Ratcliffe 3 Created: May 11 2025 4 Purpose: Neat Filesystem Traversal by DCG 5 6Copyright (c) 2025, Roy Ratcliffe, Northumberland, United Kingdom 7 8Permission is hereby granted, free of charge, to any person obtaining a 9copy of this software and associated documentation files (the 10"Software"), to deal in the Software without restriction, including 11without limitation the rights to use, copy, modify, merge, publish, 12distribute, sub-license, and/or sell copies of the Software, and to 13permit persons to whom the Software is furnished to do so, subject to 14the following conditions: 15 16 The above copyright notice and this permission notice shall be 17 included in all copies or substantial portions of the Software. 18 19THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS 20OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF 21MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. 22IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY 23CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, 24TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE 25SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. 26 27*/ 28 29:- module(dcg_files, 30 [ directory_entry//2, % +Directory, ?Entry 31 directory_entry/2 % +Directory, ?Entry 32 ]). 33:- autoload(library(lists), [member/2]).
Finds files and skips the special dot entries. Here, Entry refers to a file. The grammar recursively traverses sub-directories beneath the given Directory and yields every existing file path at Entry. The directory acts as the root of the scan; it joins with the entry to yield the full path of the file, but not with the difference list. The second List argument of phrase/2 unifies with a list of the corresponding sub-path components without the root. The caller sees the full path and the relative sub-components.
Note that the second clause appears in the DCG expanded form with the
two hidden arguments: the pre-parsed input list S0 and the
post-parsed output list S. For non-directory entries, the input list
unifies with nil []
because it represents a terminal node in the
directory tree, and the post-parsed terms amount to the accumulated
Entries spanning the sub-directory entries in-between the original
root directory and the file itself.
57directory_entry(Directory, Entry) --> 58 { exists_directory(Directory), 59 !, 60 directory_entry(Directory, Entry_), 61 entries_entry([Directory, Entry_], Directory_) 62 }, 63 [Entry_], 64 directory_entry(Directory_, Entry). 65directory_entry(Directory, Entry, [], Entries) :- 66 entries_entry([Directory|Entries], Entry). 67 68entries_entry(Entries, Entry) :- atomic_list_concat(Entries, /, Entry).
No need to check if the Entry exists. It does exist at the time of directory iteration. That could easily change by deleting, moving or renaming the entry.
79directory_entry(Directory, Entry) :- 80 directory_files(Directory, Entries), 81 member(Entry, Entries), 82 \+ special(Entry). 83 84special(.). 85special(..)