1:- module(file_extras, [
    2    apply_directory_tree/2,     % :Goal, +RootDirectory:atom
    3    fold_directory_tree/4,      % :Goal, +RootDirectory:atom, +State0, -StateFinal
    4    path_to_posix/2             % +Path:atom, -Posix:atom
    5]).
    9:- meta_predicate 
   10    apply_directory_tree(1, +),
   11    fold_directory_tree(3, +, +, -).   12
   13:- multifile
   14    mime:mime_extension/2.   15
   16%%% PUBLIC PREDICATES %%%%%%%%%%%%%%%%%%%%%%%%%%
 apply_directory_tree(:Goal, +RootDirectory:atom) is det
Calls call(Goal, Arg) for each file or sub-directory in the RootDirectory tree, recursively. The scan is the depth-first.

The argument Arg is one of

   31apply_directory_tree(Goal, Root) :-    
   32    directory_file_path(Parent, Dir, Root),
   33    apply_directory_tree(
   34        [Arg, State, State] >> call(Goal, Arg),
   35        Parent,
   36        [Dir], _, _).
 fold_directory_tree(:Goal, +RootDirectory:atom, +State0, -StateFinal) is det
Calls call(Goal, Arg, StatePrev, StateNext) for each file or sub-directory in the RootDirectory tree, recursively. The scan is the depth-first.

The argument Arg is one of

   54fold_directory_tree(Goal, Root, State0, StateFinal) :-    
   55    directory_file_path(Parent, Dir, Root),
   56    apply_directory_tree(Goal, Parent, [Dir], State0, StateFinal).
 path_to_posix(+Path:atom, -Posix:atom) is det
Succeeds if Posix unifies with Path, given that backslashes in Path are replaced by forward slashes in Posix. Utility for windows paths, seems like multiple built-in predicates are sensitive to it.
   62path_to_posix(Path, Posix) :-
   63    atomic_list_concat(Segments, '\\', Path),
   64    atomic_list_concat(Segments, '/', Posix).
   65
   66
   67%%% PRIVATE PREDICATES %%%%%%%%%%%%%%%%%%%%%%%%%
   68
   69apply_directory_tree(_, _, [], State, State) :- !.
   70 apply_directory_tree(Goal, Parent, [Dir| SameLevel], State0, StateFinal) :-    
   71    directory_file_path(Parent, Dir, Path),
   72    exists_directory(Path),
   73    (   call(Goal, directory(Dir, Path), State0, State1)
   74    ->  directory_files(Path, Entries),
   75        exclude([D] >> memberchk(D, ['.','..']), Entries, Entries1),  
   76        !,
   77        apply_directory_tree(Goal, Path, Entries1, State1, State2)
   78    ;   true
   79    ),
   80    !,
   81    apply_directory_tree(Goal, Parent, SameLevel, State2, StateFinal),
   82    !.
   83 apply_directory_tree(Goal, Parent, [File| SameLevel], State0, StateFinal) :-    
   84    directory_file_path(Parent, File, Path),
   85    exists_file(Path),
   86    ignore(call(Goal, file(File, Path), State0, State1)),
   87    apply_directory_tree(Goal, Parent, SameLevel, State1, StateFinal),
   88    !.
   89
   90mime:mime_extension(rtf, 'application/rtf')