1:- module(dirfil, []).    2
    3% ?- working_directory(W, '/Users/cantor/local/lib/pacpl7').
    4% ?- dirfil:process(depth_first_walk, leaf_node, node((.), (.)), Y).
    5
    6% ?- dirfil:process(replace_top_for_next, empty_list, [d((.), (.), S)], _).
    7
    8% :- meta_predicate process(2, 1, +, -).
    9% process(_, Final, S, S):- call(Final, S).
   10% process(Delta, Final, S, S0):-
   11% 		call(Delta, S, S1),
   12% 		process(Delta, Final, S1, S0).
   13
   14%
   15ignore_special((.)).
   16ignore_special((..)).
   17ignore_special('.git').
   18ignore_special('.DS_Store').
   19
   20
   21		/***************************************
   22		*     file_under/2 by process.         *
   23		***************************************/
   24
   25% ?- file_under_by_fold('/path/to/directory/', Y).
   26file_under_by_fold(W, Y):-
   27		process(depth_first_walk, leaf_node, node(W, W), Y).
   28
   29%
   30depth_first_walk(node((.), N), A):- !,
   31				working_directory(_, .),
   32				working_directory(W, W),
   33				depth_first_walk(node(W, N), A).
   34depth_first_walk(node(W, (.)), A):- !,
   35				depth_first_walk(node(W, W), A).
   36depth_first_walk(Node, A):- child_nodes(Node, Ss),
   37				member(A, Ss).
   38
   39%
   40leaf_node(node(_, '.git')).
   41leaf_node(node(W, N)):- working_directory(_, W),
   42				  exists_file(N).
   43
   44% ?-  child_nodes(node('/path/to/directory/', directory), L).
   45child_nodes(node((.), N), Ss):- !, working_directory(W, W),
   46	child_nodes(node(W, N), Ss).
   47child_nodes(node(W, (.)), Ss):- !,
   48	child_nodes(node(W, W), Ss).
   49child_nodes(node(W, N), Ss):-
   50	working_directory(_,W),
   51	exists_directory(N),
   52	directory_files(N, Fs),
   53	working_directory(W,N),
   54	working_directory(W0, W0),
   55	child_nodes(Fs, W0, Ss).
   56
   57%
   58child_nodes([], _, []).
   59% child_nodes([X|Y], W, Z):- (X=(.);X=(..)), !,
   60child_nodes([X|Y], W, Z):- ignore_special(X), !,
   61	child_nodes(Y, W, Z).
   62child_nodes([X|Y], W, [node(W, X)|Z]):-
   63	child_nodes(Y, W, Z).
   64
   65		/****************************************
   66		*     dict_of_files by process.		    *
   67		****************************************/
   68
   69% ?- dict_of_files_by_fold('/path/to/directory/', S).
   70dict_of_files_by_fold(W, S):-
   71			process(replace_top_for_next, empty_list,
   72						 [d(W, W, S)], _).
List files recursively under the working directory, and unify D with the result in the form of the dict with <subdirectory name> - <sub list> for subdirectories.

?- dict_of_files_by_fold(D).

   81dict_of_files_by_fold(S):-  working_directory(W,W),
   82			dict_of_files_by_fold(W, S).
   83
   84%
   85empty_list([]).
   86
   87%
   88replace_top_for_next([d(W, N, S)|X], Z):-
   89	working_directory(_, W),
   90	child_directories(N, S, Z, X).
   91
   92%
   93child_directories(N, S, A, B):- exists_directory(N),
   94						 directory_files(N, S0),
   95						 working_directory(W, N),
   96						 working_directory(W0, W0),
   97						 residue_for_next(S0, W0, S, A, B),
   98						 working_directory(_, W).
   99
  100%
  101residue_for_next([], _, [], A, A).
  102residue_for_next([I|X], W, Y, A, B):- ignore_special(I),!,
  103		residue_for_next(X, W, Y, A, B).
  104residue_for_next([I|X], W, [I|Y], A, B):- exists_file(I), !,
  105		residue_for_next(X, W, Y, A, B).
  106residue_for_next([I|X], W, [I-U|Y], [d(W,I,U)|A], B):-
  107		exists_directory(I),
  108		!,
  109		residue_for_next(X, W, Y, A, B).
  110residue_for_next([I|X], W, [I|Y], A, B):- residue_for_next(X, W, Y, A, B)