samer@0: :- module(fileutils, [ samer@0: with_file/2, samer@0: with_stream/3, samer@0: read_lines/2, samer@0: with_output_to_file/2, samer@0: with_output_to_file/3, samer@0: with_input_from_file/2, samer@0: with_input_from_file/3, samer@0: write_file_with/3, samer@0: write_file_with/4, samer@0: with_input_from/2, samer@0: find_file/3, samer@0: match_file/2, samer@0: file_under/4 samer@0: ]). samer@0: samer@0: :- meta_predicate samer@0: with_output_to_file(?,0), samer@0: with_output_to_file(?,0,+), samer@0: with_input_from_file(?,0), samer@0: with_input_from_file(?,0,+), samer@0: write_file_with(?,?,0), samer@0: write_file_with(?,?,0,?), samer@0: with_input_from(+,0), samer@0: with_stream(0,?,0), samer@0: with_file(?,0). samer@0: samer@0: samer@0: %% with_stream( :Opener, -Stream, :Goal) is semidet. samer@0: % samer@0: % Base predicate for doing things with stream. Opener is a goal which must samer@0: % prepare the stream, Stream is the variable which will hold the valid samer@0: % stream handle, and Goal is called with the stream open. The stream is samer@0: % guaranteed to be closed on exit. Stream will remain unbound on exit. samer@0: % NB: the idea is that Opener and Goal share the Stream variable, eg: samer@0: % == samer@0: % with_stream( open('out.txt',write,S), S, writeln(S,'Hello!')). samer@0: % with_stream( open('in.txt',read,S), S, read(S,T)). samer@0: % == samer@0: with_stream(Opener,Stream,Goal) :- samer@0: copy_term(t(Opener,Stream,Goal),t(O,S,G)), samer@0: setup_call_cleanup(O,G,close(S)). samer@0: samer@0: samer@0: %% with_file( :Opener, :Goal) is semidet. samer@0: % samer@0: % Call Goal with an open file as specified by Opener, which can be samer@0: % * open( +Filename, +Mode, @Stream) samer@0: % * open( +Filename, +Mode, +Options, @Stream) samer@0: % Opener is used to call open/3 or open/4. samer@0: % samer@0: % @deprecated Use with_stream/3 instead. samer@0: with_file(open(File,Mode,Stream),Goal) :- samer@0: with_stream(open(File,Mode,Stream),Stream,Goal). samer@0: samer@0: with_file(open(File,Mode,Stream,Options),Goal) :- samer@0: with_stream(open(File,Mode,Stream,Options), Stream, Goal). samer@0: samer@0: %% with_output_to_file( +File, :Goal) is semidet. samer@0: %% with_output_to_file( +File, :Goal, +Opts) is semidet. samer@0: % samer@0: % Call Goal redirecting output to the file File, which is opened as with samer@0: % open(File,write,Str) or open(File,write,Opts,Str). samer@0: % However, if the option mode(Mode) is present, it is removed from the samer@0: % list (leaving Opts1) and the file is opened as with open(File,Mode,Opts1,Str). samer@0: % The default mode is write. samer@0: with_output_to_file(File,Goal) :- with_output_to_file(File,Goal,[]). samer@0: with_output_to_file(File,Goal,Opts) :- write_file_with(File,S,with_output_to(S,Goal),Opts). samer@0: samer@0: samer@0: %% with_input_from_file( +File, :Goal) is semidet. samer@0: %% with_input_from_file( +File, :Goal, +Opts) is semidet. samer@0: % samer@0: % Call Goal redirecting output to the file File, which is opened as with samer@0: % open(File,write,Str) or open(File,write,Opts,Str). samer@0: with_input_from_file(File,Goal) :- with_input_from_file(File,Goal,[]). samer@0: with_input_from_file(File,Goal,Opts) :- samer@0: with_stream( open(File,read,S,Opts), S, with_input_from(S,Goal)). samer@0: samer@0: %% with_input_from( +Source, :Goal) is semidet. samer@0: % samer@0: % Temporarily switch current input to object specified by Source while calling Goal as in once/1. samer@0: % Source is a term like that supplied to with_output_to/2 and can be any of: samer@0: % * A stream handle or alias. samer@0: % * atom(+Atom) samer@0: % * codes(+Codes) samer@0: % * chars(+Chars) samer@0: % * string(+String) samer@0: samer@0: with_input_from(atom(A),G) :- !, samer@0: setup_call_cleanup( samer@0: atom_to_memory_file(A,MF), samer@0: setup_call_cleanup( samer@0: open_memory_file( MF, read, S), samer@0: with_input_from(S,G), samer@0: close(S) samer@0: ), samer@0: free_memory_file(MF) samer@0: ). samer@0: samer@0: with_input_from(codes(Codes),G) :- !, atom_codes(Atom,Codes), with_input_from(atom(Atom),G). samer@0: with_input_from(chars(Chars),G) :- !, atom_chars(Atom,Chars), with_input_from(atom(Atom),G). samer@0: with_input_from(string(Str),G) :- !, string_to_atom(Str,Atom), with_input_from(atom(Atom),G). samer@0: samer@0: with_input_from(S,G) :- is_stream(S), !, samer@0: current_input(S0), samer@0: setup_call_cleanup(set_input(S),once(G),set_input(S0)). samer@0: samer@0: samer@0: %% write_file_with( +File, @Stream, :Goal, +Options:list) is semidet. samer@0: %% write_file_with( +File, @Stream, :Goal) is semidet. samer@0: % samer@0: % Call Goal after opening the named file and unifying Stream with a samer@0: % valid stream. The file is guaranteed to be closed and Stream unbound samer@0: % on exit. Any options are pased to open/4, except for mode(Mode), samer@0: % which defaults to write and determines whether the file is opened samer@0: % in write or append mode. samer@0: samer@0: write_file_with(File,Stream,Goal) :- write_file_with(File,Stream,Goal,[]). samer@0: write_file_with(File,Stream,Goal,Options) :- samer@0: select_option(mode(Mode),Options,Options1,write), samer@0: must_be(oneof([write,append]),Mode), samer@0: with_stream( samer@0: open(File,Mode,Stream,Options1), samer@0: Stream, samer@0: Goal samer@0: ). samer@0: samer@0: samer@0: %% read_lines( +Stream, -Lines:list(list(integer))) is semidet. samer@0: % samer@0: % Read all lines from Stream and return a list of lists of character codes. samer@0: read_lines(Stream,Lines) :- samer@0: read_line_to_codes(Stream,Line), samer@0: ( Line=end_of_file samer@0: -> Lines=[] samer@0: ; Lines=[Line|Lines1], samer@0: read_lines(Stream,Lines1)). samer@0: samer@0: samer@0: %% match_file(+Spec,-File) is nondet. samer@0: % samer@0: % Unify File with a filename that matches given spec. Yields samer@0: % alternative matches on backtracking. Can give relative as samer@0: % well as absolute paths. samer@0: match_file(Spec,File) :- samer@0: expand_file_search_path(Spec,Path), samer@0: expand_file_name(Path,Files), samer@0: member(File,Files). samer@0: samer@0: samer@0: %% file_under( +Root, +Pattern, -File, -Path) is nondet. samer@0: % samer@0: % Enumerate all files under directory root whose names match Pattern. samer@0: % Root can be a unary term as understood by expand_file_search_path/2. samer@0: % On exit, File is the fully qualified path to the file and path is samer@0: % a list of directory names represented as atoms. samer@0: % Returns absolute file paths only. samer@0: samer@0: file_under(RootSpec,Pattern,File,Path) :- samer@0: expand_file_search_path(RootSpec,Root), samer@0: file_under(Root,Pattern,File,Path,[]). samer@0: samer@0: file_under(Root,Pattern,File) --> {file_in(Root,Pattern,File)}. samer@0: file_under(Root,Pattern,File) --> samer@0: { directory_in(Root,Full,Rel) }, [Rel], samer@0: file_under(Full,Pattern,File). samer@0: samer@0: file_in(Root,Pattern,File) :- samer@0: atomic_list_concat([Root,Pattern],'/',Spec), samer@0: absolute_file_name(Spec,[expand(true),solutions(all)],File). samer@0: samer@0: directory_in(Root,Dir,DirName) :- samer@0: atom_concat(Root,'/*',Spec), samer@0: absolute_file_name(Spec,[file_type(directory),expand(true),solutions(all)],Dir), samer@0: file_base_name(Dir,DirName). samer@0: samer@0: samer@0: %% find_file( +FileSpec, +Extensions:list(atom), -File:atom) is nondet. samer@0: % samer@0: % Looks for files matching FileSpec ending with one of the given extensions. samer@0: % FileSpec is initially passed to expand_file_search_path/2 and so can be a unary term. samer@0: % The resulting atom can include wildcards ('*', '?', '{..}'), environment samer@0: % variables ('$var') and an optional leading '~' which is equivalent to '$HOME'. samer@0: % (See expand_file_name/2). This predicate succeeds once for samer@0: % each readable file matching FileSpec and ending with one of the extensions samer@0: % in Extensions. NB. no dot is prepended to extensions: if you need '*.blah' then samer@0: % put '.blah' in Extensions. samer@0: % Returns ABSOLUTE file paths. samer@0: samer@0: find_file(Spec,Exts,File) :- samer@0: match_file(Spec,Path), samer@0: match_extension(Path,Exts), samer@0: absolute_file_name(Path,[access(read)],File). samer@0: samer@0: match_extension(Path,Exts) :- samer@0: downcase_atom(Path,PathLower), member(Ext,Exts), samer@0: atom_concat(_,Ext,PathLower). samer@0: