1:- module(dpath,[
    2              dir/1,
    3              filetype/1,
    4              file/1,
    5              pathterm_atom/2,
    6              op(650,yfx, (:/))
    7          ]).

An file system traversing utility.

Traverses directory structure and backtracks when necessary.

Example:

  ?- file(A/B),atom_concat(t,_,B).

True when A is unified to a subdirectory and B is unified to a filename that begins with a letter t.

*/

   21:- use_module(library(dpathw)).
   22
   23% Dict-concept is using the dot-operator
   24:- redefine_system_predicate( dpath:(.(_,_,_))).
   25.(Data, Func, Value):-  Value =.. ['.', Data,Func].
   26
   27:- multifile prolog:message//1.
   28
   29prolog:message( dpath(Path,Because)) -->
   30	       ['dpath ignoring ~w in ~q'-[Because,Path]].
   31
   32%not sure if this is needed, a developer understands
   33%the too long paths in Windows and other exceptions
   34exists_directory_handle_exc(A):-
   35          catch(exists_directory(A),
   36                error(K,context(_,A)),
   37          ( (K=domain_error(foreign_return_value,-1))->
   38          fail;
   39          print_message(warning,dpath(A,K)),fail)).
   40
   41exists_file_handle_exc(A):-
   42          catch(exists_file(A),
   43                error(K,context(_,A)),
   44
   45          ( print_message(warning,dpath(A,K)),fail)).
 file(?Pathterm) is nondet
Check if the file exists or search for a file that matches.

Example:

?- file(c:/A/'explorer.exe').
A = 'Windows';
false.

Max path errors and other errors are shown as warnings

Errors
- Throws errors only when debug topic dpath(exceptions) is true
   64file(C):-
   65          ground(C),!,
   66          pathterm_atom(C,Atom),
   67          exists_file(Atom).
   68file(C):-
   69          \+compound(C),!,
   70          exists_file(C,cd('.')).
   71
   72
   73file( Drive:/Path):-
   74          atom(Drive),!,
   75          atom_concat(Drive,':/',DriveAtom),
   76          file(DriveAtom/Path).
   77
   78file( Drive :/ Path):-
   79          var(Drive),
   80          !,
   81          member(Drive,[c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y,z]),
   82          atom_concat(Drive,':/',DriveAtom),
   83          file(DriveAtom/Path).
   84
   85file(C):-
   86          compound(C),
   87          fold(C,A/_),
   88          var(A),!,
   89          exists_file(C,cd('.')).
   90
   91file(C) :-
   92          compound(C),
   93          fold(C,A/_),
   94          atom(A),!,
   95          split_pathterm(C,Cd,Rest),
   96          exists_file(Rest,cd(Cd)).
 filetype(?Pathterm_with_extension) is nondet
Check if the file exists or search for a file that matches. Uses the file base name and extension. Needs a dpath-qualifier because of @see ./3

Example:

?- dpath:filetype(c:/windows/A.exe).
A = bfsvc;
A = explorer;

Max path errors and other errors are shown as warnings

Errors
- throws errors only when debug topic dpath(exceptions) is true
  117filetype(C):-
  118          ground(C),!,
  119          pathterm_atom(C,Atom),
  120          exists_file(Atom).
  121
  122filetype(NotCompound):-
  123          \+compound(NotCompound),!,
  124          NotCompound=A.B,
  125          filetype('.'/A.B).
  126
  127
  128filetype( Drive:/Path):-
  129          %compound(DP),
  130          %DP=Drive :/ Path,
  131          atom(Drive),!,
  132          atom_concat(Drive,':/',DriveAtom),
  133          filetype(DriveAtom/Path).
  134
  135filetype( Drive:/Path):-
  136          %compound(DP),
  137          %DP=Drive :/ Path,
  138          var(Drive),
  139          !,
  140          member(Drive,[c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y,z]),
  141          atom_concat(Drive,':/',DriveAtom),
  142          filetype(DriveAtom/Path).
  143
  144filetype( C/K):-
  145          atom(C),
  146          !,
  147          exists_filetype(K,cd(C)).
  148
  149filetype( C/K):-
  150          compound(C),
  151          fold(C,A/_),
  152          atom(A),
  153          !,
  154          split_pathterm(C,Cd,Rest),
  155          exists_filetype(Rest/K,cd(Cd)).
  156
  157filetype( C/K):-
  158          compound(C),
  159          fold(C,A/_),
  160          var(A),
  161          !,
  162          exists_filetype(C/K,cd('.')).
  163
  164filetype( C/K):-
  165          atom(C),!,
  166          exists_filetype(C/K,cd('.')).
  167
  168filetype( C/K):-
  169          var(C),!,
  170          exists_filetype(C/K,cd('.')).
  171
  172filetype( CK):-
  173          exists_filetype(CK,cd('.')).
 dir(?PathTerm) is nondet
Check if directory exists or search for a matching directory.

True if PathTerm is unified to a existing path to a directory

Example:

?- dir(c:/windows/B/C).
B = appcompat,
C = appraiser ;
B = appcompat,
C = 'Programs'

Max path errors and other errors are shown as warnings

Errors
- throws errors only when debug topic dpath(exceptions) is true
  196dir(C):-
  197          ground(C),!,
  198          pathterm_atom(C,Atom),
  199          exists_directory(Atom).
  200dir( DP):-
  201          compound(DP),
  202          DP=Drive :/ Path,
  203          atom(Drive),!,
  204          atom_concat(Drive,':/',DriveAtom),
  205          dir(DriveAtom/Path).
  206
  207dir( DP):-
  208          compound(DP),
  209          DP=Drive :/ Path,
  210          var(Drive),
  211          !,
  212          member(Drive,[c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y,z]),
  213          atom_concat(Drive,':/',DriveAtom),
  214          dir(DriveAtom/Path).
  215
  216dir(C):-
  217          compound(C),
  218          fold(C,A/_),
  219          var(A),!,
  220          exists_dir(C,cd('.')).
  221
  222dir(C):-
  223          compound(C),
  224          fold(C,A/_),
  225          atom(A),!,
  226          split_pathterm(C,Cd,Rest),
  227          exists_dir(Rest,cd(Cd)).
  228
  229dir( A):-
  230          var(A),!,
  231          exists_dir(A,cd('.')).
  232
  233dir( A):-
  234          atom(A),
  235          exists_dir(A,cd('.')).
  236
  237%exists a file that is of  some filetype
  238exists_filetype('/'(A,B),cd(CD)):-
  239          !,
  240          exists_file(A/X,cd(CD)),
  241          filename_head_tail(X,B).
  242
  243/*exists_filetype(AB,cd(CD)):-
  244          compound(AB),ground(AB),
  245          !,
  246          pathterm_atom(CD/AB,Atom),
  247          exists_file(Atom).*/

  248
  249exists_filetype( AB,cd(CD)):-
  250          exists_file(D,cd(CD)),
  251          filename_head_tail(D,AB).
 exists_file(+PathTermFile:term, -VirtualCd:term) is nondet
PathTerm is path and VirtualCd is a virtual current directory.

Example:

exists_file(File,cd('.')).
  263exists_file(PathTerm,cd(CD)):-
  264          compound(PathTerm),!,
  265          PathTerm= /(PathTermyfx,File),
  266          fold(PathTermyfx,PathTermDir),
  267          exists_dir( PathTermDir,cd(CD)),
  268          pathterm_to_atom(CD/PathTermDir,Atom),
  269          directory_files2(Atom,Files),
  270          member(File,Files),
  271          \+File='.',
  272          \+File='..',
  273          pt_exists_file(CD/PathTermDir/File).
  274
  275exists_file(File,cd(CD)):-
  276          pathterm_to_atom(CD,Atom),
  277          directory_files2(Atom,Files),
  278          member(File,Files),
  279          \+File='.',
  280          \+File='..',
  281          pt_exists_file(CD/File).
  282
  283
  284% doesn't handle the var(FileName)
  285filename_head_tail(FileName,HeadTail):-
  286          read_term2(FileName,HeadTail,'.').
  287
  288%when in debug mode, writes out to stderr the exceptions
  289directory_files2(Directory,Files):-
  290          catch(directory_files(Directory,Files),Exc,
  291                (ignore( debug(dpath(exceptions),'~q',Exc)),fail)).
 split_pathterm(?PathTerm, -Head, -Tail) is det
Splits a pathterm ( +Head/?Tail) to a Head and to a Tail Head is the prefix of PathTerm

split_pathterm(H/T,S,Y) is true when S is the first atom on `/' multiply separated term and Y is rest

Example:

split_pathterm(a/b/c/d,a,b/c/d).

Rationale: pathterm has '/' operators that are interpreted differently than usually. They are interpreted as having a xfy associativity. See op/3.

  309split_pathterm( H/T,S,Y):-
  310          !,
  311          split_pathterm(H,Sd,Q), (atom(H),!,Y=T,S=H;Y=Q/T,S=Sd).
  312
  313split_pathterm(H,H,_).
 fold(-PathTermyfx, +PathTermxfy) is det
Example: folds a a/b/c to a/(b/c).
?- fold(a/b/c,a/(b/c).

If the operator `/' would be redefined as op(400,xfy,/) then the a/(b/c) would display as a/b/c.

Example: Interprete a/b/c as if the op(400,xfy,/) is true. (The default is op(400,yfx,/) ).

Rationale: if you don't want/can't re-define the `/'-operator to op(400,xfy,/) you can use this to transform terms from yfx to xfy.

PathTermyfx is an input term that will be interpreted in xfy-context. PathTermxfy is output term that is explicitly a xfy-term, you can't interpret it. PathTermxfy is a explicitly valid xfy-term and can be used in the yfx-context.

  338fold(KL,W):-
  339          compound(KL),KL=K/L,
  340          !,
  341          fold2(K,L,W).
  342
  343fold(K,K).
  344
  345
  346fold2(KL,X,R):-
  347          compound(KL),
  348          !,
  349          /(K,L)=KL,
  350          fold2(K, /(L,X),R).
  351
  352fold2(L,X,R):-
  353          R = /(L,X).
  354
  355
  356
  357% Reads from a atom a term that is delimited multiple
  358% times with the Delimiter
  359read_term2(Atom,Term,Delimiter):-
  360    atomic_list_concat(List,Delimiter,Atom),
  361    unify_term(Delimiter,List,Term).
  362
  363
  364% generates a multiply delimited term, where
  365% operands are taken from List
  366%
  367% example
  368% ==
  369% ?- unify('/',[A,B,C],R).
  370% R=A/B/C.
  371% ==
  372unify_term(OP,List,Res):-
  373    length(List,Len),
  374    Num is Len-1,
  375    reverse(List,RevList),
  376    unify_term(Num,OP,RevList,Res).
  377
  378unify_term(Num,OP,[H|T],Res):-
  379    Counter is Num-1,
  380    Num>0,
  381    !,
  382    unify_term(Counter,OP,T,ResD), Res=.. [OP,ResD,H].
  383
  384unify_term(_,_,[H],H).
  385
  386
  387pt_exists_file(PathTerm):-
  388          pathterm_to_atom(PathTerm,Atom),
  389          exists_file_handle_exc(Atom).
 exists_dir(?PathTerm, -VirtualCd) is nondet
On Linux exists_dir(A,cd('/')) unifies A with directories under root
  396exists_dir(A,cd(CD)):-
  397             fold(A,B),
  398             exists_dir2(B, cd(CD)).
  399
  400exists_dir2(AB,cd(CD)):-
  401          compound(AB),
  402          AB= /(A,B),
  403          directory_directories(A,cd(CD)),
  404          exists_dir2(B,cd(CD/A)).
  405
  406exists_dir2(A,cd(CD)):-
  407           atom(A),
  408           pathterm_to_atom(CD/A,Atom),
  409           exists_directory_handle_exc(Atom).
  410
  411exists_dir2(A,cd(CD)):-
  412          var(A),
  413          directory_directories(A,cd(CD)).
  414
  415
  416% directory_directories(Main/Sub)
  417% traverses all directories,
  418% Main and Sub are atoms or variables
  419% cd(CD) is a virtual current directory
  420% Main and Sub are relative to the CD
  421% CD can't be a variable but can be a
  422% compound
  423directory_directories(A,cd(CD)):-
  424         \+compound(A),var(A),!,
  425         pathterm_to_atom(CD,Atom),
  426         filtered_directory_has_a_member(Atom,A),
  427         pathterm_to_atom(CD/A,AAtom),
  428         exists_directory_handle_exc(AAtom).
  429
  430directory_directories( /(A,B),cd(CD)):-
  431         var(A),var(B), !,
  432         pathterm_to_atom(CD,Atom),
  433         filtered_directory_has_a_member(Atom,A),
  434         pathterm_to_atom(CD/A,BAtom),
  435         exists_directory_handle_exc(BAtom),
  436         directory_directories(A/B,cd(CD)).
  437
  438directory_directories( /(A,B),cd(CD)):-
  439         atom(A),var(B),!,
  440         pathterm_to_atom(CD/A,Atom),
  441         filtered_directory_has_a_member(Atom,B),
  442         pathterm_to_atom(CD/A/B,BAtom),
  443         exists_directory_handle_exc(BAtom).
  444
  445directory_directories( /(A,B),cd(CD)):-
  446         atom(A),atom(B),!,
  447         pathterm_to_atom(CD/A/B,Atom),
  448         exists_directory_handle_exc(Atom).
  449
  450directory_directories( /(A,B),cd(CD)):-
  451         var(A),atom(B),!,
  452         pathterm_to_atom(CD,Atom),
  453         filtered_directory_has_a_member(Atom,A),
  454         pathterm_to_atom(CD/A/B,BAtom2),
  455         exists_directory_handle_exc(BAtom2).
  456
  457directory_directories(A,cd(CD)):-
  458         atom(A),!,
  459         pathterm_to_atom(CD/A,Atom),
  460         exists_directory_handle_exc(Atom).
  461
  462
  463
  464filtered_directory_has_a_member(DirAtom,Member):-
  465         directory_files2(DirAtom,Files),
  466         member(Member,Files),
  467         \+Member='.',
  468         \+Member='..'.
 pathterm_to_atom(Pathterm, Res) is det
This is a private predicate does a term_to_atom/2 conversion of pathterms, so that Res can be used in OS calls like exists_directory/1

Example:

?- pathterm_to_atom((a/b)/c,Res).
Res='a/b/c'.

Bug: Doesn't handle a/b/c.txt, but the pathterm_atom/2 does.

  484pathterm_to_atom( /(A,B),Res):-
  485         !,
  486         pathterm_to_atom(A,Res2),
  487         pathterm_to_atom(B,Res3),
  488         atomic_list_concat([Res2,'/',Res3],Res).
  489
  490pathterm_to_atom(A,A).
 extterm_to_atom(-DotTerm, +Res) is det
Res is a atom from a dot-separated filename with extension.

Example:

extterm_to_atom(a.b.c,'a.b.c').
  502extterm_to_atom( .(A,B),Res):-
  503         !,
  504         extterm_to_atom(A,Res2),
  505         extterm_to_atom(B,Res3),
  506         atomic_list_concat([Res2,'.',Res3],Res).
  507
  508extterm_to_atom(A,A).
 pathterm_atom(++PathTerm, -Res) is det
Res is a atom from a path term Path must contain only ground variables

Example:

pathterm_atom(k/l/m/a.b,'k/l/m/a.b').
  519pathterm_atom(Drive:/Path,Res):-
  520          !,
  521          pathterm_atom(Path,A),
  522          atomic_list_concat([Drive,':/',A],Res).
  523
  524pathterm_atom( .(A,B),Res):-
  525         !,
  526         pathterm_atom(A,Res2),
  527         pathterm_atom(B,Res3),
  528         atomic_list_concat([Res2,'.',Res3],Res).
  529
  530pathterm_atom( /(A,B),Res):-
  531         !,
  532         pathterm_atom(A,Res2),
  533         pathterm_atom(B,Res3),
  534         atomic_list_concat([Res2,'/',Res3],Res).
  535
  536pathterm_atom(A,A).
 pathterm(+Len:number, +HT:list, -PT:pathterm) is semidet
Creates a pathterm that has Len-members HT is a list where (some) members of a pathterm are bind.

Example:

?- pathterm(5,[(1='c:'),(5=A.pl)],R).
R='c:'/X/Y/Z/A.pl.

Usage example: Find a prolog-file that is under c:/users and maximally 7 subdirectories deep

?-between(3,10,DE),pathterm(DE,[(1='c:'),(2=users),(DE=A.pl)],R),filetype(R).
DE=5,
A=c,
R='c:'/users/'Prologist'/'OneDrive'/c.pl;
  560pathterm(Len,HT,PT):-
  561          length(List,Len),
  562          maplist(pathterm_bind(List),HT),
  563          unify_term('/',List,PT).
  564pathterm_bind(List,Nth1=K):-
  565          nth1(Nth1,List,K)