
% run a shell command and capture the output
% e.g.  run("ls", ["-l", "foo.txt"], Output).

run(Cmd, ArgList, LinesOfOutput) :- setup_call_cleanup(
     process_create(path(Cmd), ArgList, [ stdout(pipe(OutputPipe)) ]),
     readFromPipe(OutputPipe, LinesOfOutput), close(OutputPipe)).

% note the setup_call_cleanup regards its first argument as the setup,
%    to be run once (i.e. the process_create), the second argument as
%    the goal to be run if the setup succeeds (i.e. readFromPipe), and
%    the third argument as the cleanup step to be carried out afterward
%    (i.e. close the pipe)

% read lines of output from a pipe into a list
readFromPipe(OutputPipe, LinesOfOutput) :-
   read_line_to_codes(OutputPipe, LineAsCodes),
   readFromPipe(LineAsCodes, OutputPipe, LinesOfOutput).

% quit at end of file
readFromPipe(end_of_file, _, []) :- !.

% convert code to text
readFromPipe(LineOfCodes, OutputPipe, [CurLine|RestOfLines]) :-
   atom_codes(CurLine, LineOfCodes),
   read_line_to_codes(OutputPipe, NextLineCodes),
   readFromPipe(NextLineCodes, OutputPipe, RestOfLines).

