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