22

I'd like to read a plain text file and apply a predicate to each line (the predicates contain write which does the output). How would I do that?

false
  • 10,264
  • 13
  • 101
  • 209
Igor Marvinsky
  • 387
  • 1
  • 4
  • 17

5 Answers5

25

You can use read to read the stream. Remember to invoke at_end_of_stream to ensure no syntax errors.

Example:

readFile.pl

main :-
    open('myFile.txt', read, Str),
    read_file(Str,Lines),
    close(Str),
    write(Lines), nl.

read_file(Stream,[]) :-
    at_end_of_stream(Stream).

read_file(Stream,[X|L]) :-
    \+ at_end_of_stream(Stream),
    read(Stream,X),
    read_file(Stream,L).

myFile.txt

'line 0'.
'line 1'.
'line 2'.
'line 3'.
'line 4'.
'line 5'.
'line 6'.
'line 7'.
'line 8'.
'line 9'.

Thus by invoking main you will recieve the output:

?- main.
[line 0,line 1,line 2,line 3,line 4,line 5,line 6,line 7,line 8,line 9]
true 

Just configure main. The output here is an example by using write, of course. Configure to match your request.

I assume that this principle can be applied to answer your question. Good luck.

Ishq
  • 1,189
  • 1
  • 8
  • 10
  • Some time later, but i get an error with this code: 'uncaught exception: error(existence_error(procedure,main/0),top_level/0)'. Know what this means? – RK_97 Nov 29 '20 at 14:35
18

In SWI-Prolog, the cleanest solution is to write a DCG that describes what a "line" is, then call a predicate for each line. Use library(pio) to apply the DCG to a file.

EDIT: As requested, consider:

:- use_module(library(pio)).

lines([])           --> call(eos), !.
lines([Line|Lines]) --> line(Line), lines(Lines).

eos([], []).

line([])     --> ( "\n" ; call(eos) ), !.
line([L|Ls]) --> [L], line(Ls).

Sample usage: ?- phrase_from_file(lines(Ls), 'your_file.txt').

mat
  • 40,498
  • 3
  • 51
  • 78
  • 2
    I know it's been a long time, but I'm trying this method and it seems to take an absurdly long time. Could you provide an example of some performant code using DCGs and library(pio) that will read in a file by lines? Thanks! – Shon Oct 22 '14 at 03:21
  • 1
    Thanks so much! I see my error before was using the example in the SWI-Prolog library(pio) documentation for my model. It uses `findall/3` to get all instances of a certain pattern, but I see you just use a dcg that parses the whole file. Out of curiosity, why must we use `call(eos)` instead of a dcg rule? – Shon Oct 24 '14 at 02:58
  • 7
    `call//1` (and then, `eos/2`) is used to portably refer to the *entire* implicit DCG arguments from within a DCG rule. You cannot use a DCG rule instead, because DCG rules are subject to translation rules that let them only refer to certain parts of these arguments. "Portable" means that this is independent of how any particular Prolog system actually translates DCG rules to Prolog rules, so that it works in all systems that support DCGs as currently being drafted by ISO. – mat Oct 24 '14 at 07:52
  • Thanks again! I reworked the problem I was attempting with the help of your example, and it ended up in a fairly elegant solution. More importantly, you've helped me bump up my understanding of DCGs to the next level. (I've been studying them casually, off and on, for more than a year, and I still feel like I have a limited grasp. It is such a simple concept, and yet... maybe it's not so simple?). – Shon Oct 26 '14 at 01:45
3

There are kind of more possible in number and more reasonable in performance solutions, to get uninterpreted i.e plain text lines from a file:

SWI-Prolog:

read_line(S, X) :- 
   read_line_to_codes(S, L), 
   read_line2(L, X).

read_line2(end_of_file, _) :- !, fail.
read_line2(L, X) :-
   atom_codes(X, L).

Jekejeke Prolog:

:- use_module(library(stream/console)).

Here are some timings, reading a file of 655 lines:

test :-
   open('<path>', read, Stream),
   test(Stream),
   close(Stream).

test(Stream) :-
   read_line(Stream, _), !,
   test(Stream).
test(_).

SWI-Prolog:

̀?- time((between(1,100,_), test, fail; true)).
% 328,300 inferences, 0.125 CPU in 0.143 seconds (88% CPU, 2626400 Lips)
true.

Jekejeke Prolog:

?- time((between(1,100,_), test, fail; true)).
% Up 121 ms, GC 2 ms, Thread Cpu 94 ms (Current 05/07/19 17:19:05)
Yes

I guess a SWI-Prolog solution that reads into a string instead into an atom could be faster. But in the above we compare atom against atom reading.

1

There is a nice example in de SWI-Prolog documentation:

file_line(File, Line) :-
    setup_call_cleanup(open(File, read, In),
        stream_line(In, Line),
        close(In)).

stream_line(In, Line) :-
    repeat,
    (   read_line_to_string(In, Line0),
        Line0 \== end_of_file
    ->  Line0 = Line
    ;   !,
        fail
    ).

source: https://www.swi-prolog.org/pldoc/man?predicate=read_string/5

César Alforde
  • 2,028
  • 2
  • 15
  • 17
0

Given the responses here I created this, which more like python "with" :

?- read_file('test.txt', tokenize,5,L). %first 5 lines
?- read_file('test.txt', tokenize,L). %the whole file
?- read_file('test.txt', split,5,L). %just split
?- open('test.txt',read,S), read_lines(S,split,5,L), close(S).

code :

:- module(files,[read_line/3, read_file/3,  read_file/4, read_lines/3, read_lines/4, split/2, split/3, split/4]).

:- use_module(library(pcre)).

string2atoms(Strings, Atoms) :- maplist(atom_string, Atoms, Strings).
split(Str, Lst) :- split_string(Str, " ", "", Lst).
split(Str, Separator, Lst) :- split_string(Str, Separator, "", Lst).
split(Str, Separator, Pad, Lst) :- split_string(Str, Separator, Pad, Lst).
is_empty(Str) :- re_match(Str, '^\s*$').
non_empty(Str) :- ( is_empty(Str) -> false ; true).

tokenize(String,Tokens) :- split(String,Lst), string2atoms(Lst,Tokens).

%read a line and execute a Goal on it
read_line(Stream,Goal,Args) :- 
    \+ at_end_of_stream(Stream), read_line_to_string(Stream,Str),
    %% \+ isempty(Str), call(Goal,Str,Args). 
    ( is_empty(Str) -> true ; call(Goal,Str,Args)). 

% given Stream execute Goal on every line. with the option to process only N lines
read_lines(Stream, _, _,_) :- at_end_of_stream(Stream), !. %is EOF
read_lines(_, _, 0,_) :- !. % only N lines
read_lines(Stream, Goal, N, [Res|T]) :-
    N0 is N - 1, read_line(Stream, Goal, Res), writeln(Res),
    read_lines(Stream, Goal, N0, T).

%read the whole file
read_lines(Stream, Goal, LoL) :- read_lines(Stream, Goal, 1000000, LoL).

%given file name execute Goal on every line
read_file(File, Goal, N, Res) :-
    open(File, read, Stream), read_lines(Stream, Goal, N, Res), close(Stream).
read_file(File, Goal, Res) :- read_file(File, Goal, 1000000, Res).
sten
  • 7,028
  • 9
  • 41
  • 63