samer@0
|
1 :- module(fileutils, [
|
samer@0
|
2 with_file/2,
|
samer@0
|
3 with_stream/3,
|
samer@0
|
4 read_lines/2,
|
samer@0
|
5 with_output_to_file/2,
|
samer@0
|
6 with_output_to_file/3,
|
samer@0
|
7 with_input_from_file/2,
|
samer@0
|
8 with_input_from_file/3,
|
samer@0
|
9 write_file_with/3,
|
samer@0
|
10 write_file_with/4,
|
samer@0
|
11 with_input_from/2,
|
samer@0
|
12 find_file/3,
|
samer@0
|
13 match_file/2,
|
samer@0
|
14 file_under/4
|
samer@0
|
15 ]).
|
samer@0
|
16
|
samer@0
|
17 :- meta_predicate
|
samer@0
|
18 with_output_to_file(?,0),
|
samer@0
|
19 with_output_to_file(?,0,+),
|
samer@0
|
20 with_input_from_file(?,0),
|
samer@0
|
21 with_input_from_file(?,0,+),
|
samer@0
|
22 write_file_with(?,?,0),
|
samer@0
|
23 write_file_with(?,?,0,?),
|
samer@0
|
24 with_input_from(+,0),
|
samer@0
|
25 with_stream(0,?,0),
|
samer@0
|
26 with_file(?,0).
|
samer@0
|
27
|
samer@0
|
28
|
samer@0
|
29 %% with_stream( :Opener, -Stream, :Goal) is semidet.
|
samer@0
|
30 %
|
samer@0
|
31 % Base predicate for doing things with stream. Opener is a goal which must
|
samer@0
|
32 % prepare the stream, Stream is the variable which will hold the valid
|
samer@0
|
33 % stream handle, and Goal is called with the stream open. The stream is
|
samer@0
|
34 % guaranteed to be closed on exit. Stream will remain unbound on exit.
|
samer@0
|
35 % NB: the idea is that Opener and Goal share the Stream variable, eg:
|
samer@0
|
36 % ==
|
samer@0
|
37 % with_stream( open('out.txt',write,S), S, writeln(S,'Hello!')).
|
samer@0
|
38 % with_stream( open('in.txt',read,S), S, read(S,T)).
|
samer@0
|
39 % ==
|
samer@0
|
40 with_stream(Opener,Stream,Goal) :-
|
samer@0
|
41 copy_term(t(Opener,Stream,Goal),t(O,S,G)),
|
samer@0
|
42 setup_call_cleanup(O,G,close(S)).
|
samer@0
|
43
|
samer@0
|
44
|
samer@0
|
45 %% with_file( :Opener, :Goal) is semidet.
|
samer@0
|
46 %
|
samer@0
|
47 % Call Goal with an open file as specified by Opener, which can be
|
samer@0
|
48 % * open( +Filename, +Mode, @Stream)
|
samer@0
|
49 % * open( +Filename, +Mode, +Options, @Stream)
|
samer@0
|
50 % Opener is used to call open/3 or open/4.
|
samer@0
|
51 %
|
samer@0
|
52 % @deprecated Use with_stream/3 instead.
|
samer@0
|
53 with_file(open(File,Mode,Stream),Goal) :-
|
samer@0
|
54 with_stream(open(File,Mode,Stream),Stream,Goal).
|
samer@0
|
55
|
samer@0
|
56 with_file(open(File,Mode,Stream,Options),Goal) :-
|
samer@0
|
57 with_stream(open(File,Mode,Stream,Options), Stream, Goal).
|
samer@0
|
58
|
samer@0
|
59 %% with_output_to_file( +File, :Goal) is semidet.
|
samer@0
|
60 %% with_output_to_file( +File, :Goal, +Opts) is semidet.
|
samer@0
|
61 %
|
samer@0
|
62 % Call Goal redirecting output to the file File, which is opened as with
|
samer@0
|
63 % open(File,write,Str) or open(File,write,Opts,Str).
|
samer@0
|
64 % However, if the option mode(Mode) is present, it is removed from the
|
samer@0
|
65 % list (leaving Opts1) and the file is opened as with open(File,Mode,Opts1,Str).
|
samer@0
|
66 % The default mode is write.
|
samer@0
|
67 with_output_to_file(File,Goal) :- with_output_to_file(File,Goal,[]).
|
samer@0
|
68 with_output_to_file(File,Goal,Opts) :- write_file_with(File,S,with_output_to(S,Goal),Opts).
|
samer@0
|
69
|
samer@0
|
70
|
samer@0
|
71 %% with_input_from_file( +File, :Goal) is semidet.
|
samer@0
|
72 %% with_input_from_file( +File, :Goal, +Opts) is semidet.
|
samer@0
|
73 %
|
samer@0
|
74 % Call Goal redirecting output to the file File, which is opened as with
|
samer@0
|
75 % open(File,write,Str) or open(File,write,Opts,Str).
|
samer@0
|
76 with_input_from_file(File,Goal) :- with_input_from_file(File,Goal,[]).
|
samer@0
|
77 with_input_from_file(File,Goal,Opts) :-
|
samer@0
|
78 with_stream( open(File,read,S,Opts), S, with_input_from(S,Goal)).
|
samer@0
|
79
|
samer@0
|
80 %% with_input_from( +Source, :Goal) is semidet.
|
samer@0
|
81 %
|
samer@0
|
82 % Temporarily switch current input to object specified by Source while calling Goal as in once/1.
|
samer@0
|
83 % Source is a term like that supplied to with_output_to/2 and can be any of:
|
samer@0
|
84 % * A stream handle or alias.
|
samer@0
|
85 % * atom(+Atom)
|
samer@0
|
86 % * codes(+Codes)
|
samer@0
|
87 % * chars(+Chars)
|
samer@0
|
88 % * string(+String)
|
samer@0
|
89
|
samer@0
|
90 with_input_from(atom(A),G) :- !,
|
samer@0
|
91 setup_call_cleanup(
|
samer@0
|
92 atom_to_memory_file(A,MF),
|
samer@0
|
93 setup_call_cleanup(
|
samer@0
|
94 open_memory_file( MF, read, S),
|
samer@0
|
95 with_input_from(S,G),
|
samer@0
|
96 close(S)
|
samer@0
|
97 ),
|
samer@0
|
98 free_memory_file(MF)
|
samer@0
|
99 ).
|
samer@0
|
100
|
samer@0
|
101 with_input_from(codes(Codes),G) :- !, atom_codes(Atom,Codes), with_input_from(atom(Atom),G).
|
samer@0
|
102 with_input_from(chars(Chars),G) :- !, atom_chars(Atom,Chars), with_input_from(atom(Atom),G).
|
samer@0
|
103 with_input_from(string(Str),G) :- !, string_to_atom(Str,Atom), with_input_from(atom(Atom),G).
|
samer@0
|
104
|
samer@0
|
105 with_input_from(S,G) :- is_stream(S), !,
|
samer@0
|
106 current_input(S0),
|
samer@0
|
107 setup_call_cleanup(set_input(S),once(G),set_input(S0)).
|
samer@0
|
108
|
samer@0
|
109
|
samer@0
|
110 %% write_file_with( +File, @Stream, :Goal, +Options:list) is semidet.
|
samer@0
|
111 %% write_file_with( +File, @Stream, :Goal) is semidet.
|
samer@0
|
112 %
|
samer@0
|
113 % Call Goal after opening the named file and unifying Stream with a
|
samer@0
|
114 % valid stream. The file is guaranteed to be closed and Stream unbound
|
samer@0
|
115 % on exit. Any options are pased to open/4, except for mode(Mode),
|
samer@0
|
116 % which defaults to write and determines whether the file is opened
|
samer@0
|
117 % in write or append mode.
|
samer@0
|
118
|
samer@0
|
119 write_file_with(File,Stream,Goal) :- write_file_with(File,Stream,Goal,[]).
|
samer@0
|
120 write_file_with(File,Stream,Goal,Options) :-
|
samer@0
|
121 select_option(mode(Mode),Options,Options1,write),
|
samer@0
|
122 must_be(oneof([write,append]),Mode),
|
samer@0
|
123 with_stream(
|
samer@0
|
124 open(File,Mode,Stream,Options1),
|
samer@0
|
125 Stream,
|
samer@0
|
126 Goal
|
samer@0
|
127 ).
|
samer@0
|
128
|
samer@0
|
129
|
samer@0
|
130 %% read_lines( +Stream, -Lines:list(list(integer))) is semidet.
|
samer@0
|
131 %
|
samer@0
|
132 % Read all lines from Stream and return a list of lists of character codes.
|
samer@0
|
133 read_lines(Stream,Lines) :-
|
samer@0
|
134 read_line_to_codes(Stream,Line),
|
samer@0
|
135 ( Line=end_of_file
|
samer@0
|
136 -> Lines=[]
|
samer@0
|
137 ; Lines=[Line|Lines1],
|
samer@0
|
138 read_lines(Stream,Lines1)).
|
samer@0
|
139
|
samer@0
|
140
|
samer@0
|
141 %% match_file(+Spec,-File) is nondet.
|
samer@0
|
142 %
|
samer@0
|
143 % Unify File with a filename that matches given spec. Yields
|
samer@0
|
144 % alternative matches on backtracking. Can give relative as
|
samer@0
|
145 % well as absolute paths.
|
samer@0
|
146 match_file(Spec,File) :-
|
samer@0
|
147 expand_file_search_path(Spec,Path),
|
samer@0
|
148 expand_file_name(Path,Files),
|
samer@0
|
149 member(File,Files).
|
samer@0
|
150
|
samer@0
|
151
|
samer@0
|
152 %% file_under( +Root, +Pattern, -File, -Path) is nondet.
|
samer@0
|
153 %
|
samer@0
|
154 % Enumerate all files under directory root whose names match Pattern.
|
samer@0
|
155 % Root can be a unary term as understood by expand_file_search_path/2.
|
samer@0
|
156 % On exit, File is the fully qualified path to the file and path is
|
samer@0
|
157 % a list of directory names represented as atoms.
|
samer@0
|
158 % Returns absolute file paths only.
|
samer@0
|
159
|
samer@0
|
160 file_under(RootSpec,Pattern,File,Path) :-
|
samer@0
|
161 expand_file_search_path(RootSpec,Root),
|
samer@0
|
162 file_under(Root,Pattern,File,Path,[]).
|
samer@0
|
163
|
samer@0
|
164 file_under(Root,Pattern,File) --> {file_in(Root,Pattern,File)}.
|
samer@0
|
165 file_under(Root,Pattern,File) -->
|
samer@0
|
166 { directory_in(Root,Full,Rel) }, [Rel],
|
samer@0
|
167 file_under(Full,Pattern,File).
|
samer@0
|
168
|
samer@0
|
169 file_in(Root,Pattern,File) :-
|
samer@0
|
170 atomic_list_concat([Root,Pattern],'/',Spec),
|
samer@0
|
171 absolute_file_name(Spec,[expand(true),solutions(all)],File).
|
samer@0
|
172
|
samer@0
|
173 directory_in(Root,Dir,DirName) :-
|
samer@0
|
174 atom_concat(Root,'/*',Spec),
|
samer@0
|
175 absolute_file_name(Spec,[file_type(directory),expand(true),solutions(all)],Dir),
|
samer@0
|
176 file_base_name(Dir,DirName).
|
samer@0
|
177
|
samer@0
|
178
|
samer@0
|
179 %% find_file( +FileSpec, +Extensions:list(atom), -File:atom) is nondet.
|
samer@0
|
180 %
|
samer@0
|
181 % Looks for files matching FileSpec ending with one of the given extensions.
|
samer@0
|
182 % FileSpec is initially passed to expand_file_search_path/2 and so can be a unary term.
|
samer@0
|
183 % The resulting atom can include wildcards ('*', '?', '{..}'), environment
|
samer@0
|
184 % variables ('$var') and an optional leading '~' which is equivalent to '$HOME'.
|
samer@0
|
185 % (See expand_file_name/2). This predicate succeeds once for
|
samer@0
|
186 % each readable file matching FileSpec and ending with one of the extensions
|
samer@0
|
187 % in Extensions. NB. no dot is prepended to extensions: if you need '*.blah' then
|
samer@0
|
188 % put '.blah' in Extensions.
|
samer@0
|
189 % Returns ABSOLUTE file paths.
|
samer@0
|
190
|
samer@0
|
191 find_file(Spec,Exts,File) :-
|
samer@0
|
192 match_file(Spec,Path),
|
samer@0
|
193 match_extension(Path,Exts),
|
samer@0
|
194 absolute_file_name(Path,[access(read)],File).
|
samer@0
|
195
|
samer@0
|
196 match_extension(Path,Exts) :-
|
samer@0
|
197 downcase_atom(Path,PathLower), member(Ext,Exts),
|
samer@0
|
198 atom_concat(_,Ext,PathLower).
|
samer@0
|
199
|