1:- module(path, [file_stream/4, build_path/2, parent_path/2, make_parent/1,
2 file_format/2, nth_parent_dir/3, walk/2, walk/3, list_files/2]). 3
4:- use_module(library(clpfd)). 5:- use_module(library(filesex)). 6
7file_stream(File, Mode, Stream, Pred) :-
8 setup_call_cleanup(
9 open(File, Mode, Stream),
10 call(Pred),
11 close(Stream)).
12
13build_path(Paths, Path) :-
14 reverse(Paths, RevPaths), 15 foldl(directory_file_path, RevPaths, '', Path).
16
17parent_path(Path, Parent) :-
18 atom_concat(NoTrailingSlash, '/', Path) -> directory_file_path(Parent, _, NoTrailingSlash);
19 directory_file_path(Parent, _, Path).
20
21make_parent(Path) :-
22 parent_path(Path, Parent),
23 make_directory_path(Parent).
24
25file_format(Path, Format) :-
26 file_name_extension(_, Ext, Path),
27 downcase_atom(Ext, Format).
28
29nth_parent_dir(0, Path, Path).
30nth_parent_dir(N, Path, Parent) :-
31 N #> 0,
32 absolute_file_name(Path, AbsPath),
33 file_directory_name(AbsPath, TempParent),
34 N1 #= N - 1,
35 nth_parent_dir(N1, TempParent, Parent).
36
37walk(Path, Result) :- walk(Path, always, Result).
38
39walk(Path, Pred, Result) :-
40 call(Pred, Path),
41 exists_directory(Path),
42 directory_files(Path, Files),
43 member(Temp, Files),
44 not(Temp = '.'),
45 not(Temp = '..'),
46 directory_file_path(Path, Temp, File),
47 call(Pred, File),
48 (
49 Result = File;
50
51 exists_directory(File),
52 walk(File, Pred, Result)
53 ).
54walk(Path, Pred, Path) :- call(Pred, Path), exists_file(Path).
55
56list_files(Path, Files) :-
57 directory_file_path(Path, '*', Wildcard),
58 expand_file_name(Wildcard, Files)