1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%%%  read_line
    3%%%  This is a modified version for parsing pddl files.
    4%%%  Read the input file character by character and parse it
    5%%%  into a list. Brackets, comma, period and question marks
    6%%%  are treated as separate words. White spaces separed 
    7%%%  words. 
    8%%%
    9%%%  Similar to read_sent in Pereira and Shieber, Prolog and
   10%%%        Natural Language Analysis, CSLI, 1987.
   11%%%
   12%%%  Examples:
   13%%%           :- read_line('input.txt', L).
   14%%%           input.txt> The sky was blue, after the rain.
   15%%%           L = [the, sky, was, blue, (','), after, the, rain, '.']
   16%%%
   17%%%           :- read_line('domain.pddl', L).
   18%%%           domain.pddl>
   19%%%           (define (domain BLOCKS)
   20%%%             (:requirements :strips :typing :action-costs)
   21%%%             (:types block)
   22%%%             (:predicates (on ?x - block ?y - block)
   23%%%           ...
   24%%%           L = ['(', define, '(', domain, blocks, ')', '(', :, requirements|...].
   25%
   26%read_file(+File, -List).
   27%% read_file(File, List) :- seeing(Old), see(File), read_line(List), seen, see(Old).
   28read_file(File, List) :-
   29	seeing(Old),
   31	system:see(File),
   33	read_line(List),
   35	seen,
   36	system:see(Old),
   38	true
   38.
   39
   40read_line(Words) :- get0(C),
   41                    read_rest(C,Words).
   42          
   43/* Ends the input. */
   44read_rest(-1,[]) :- !.
   45
   46/* Spaces, tabs and newlines between words are ignored. */
   47read_rest(C,Words) :- ( C=32 ; C=10 ; C=9 ; C=13 ; C=92 ) , !,
   48                     get0(C1),
   49                     read_rest(C1,Words).
   56/* Brackets, comma, period or question marks are treated as separed words */
   57read_rest(C, [Char|Words]) :- ( C=40 ; C=41 ; C=44 ; C=45 ; C=46 ; C=63 ; C=58 ) , name(Char, [C]), !,
   58			get0(C1),
   59			read_rest(C1, Words).
   60
   61
   62/* Read comments to the end of line */
   63read_rest(59, Words) :- get0(Next), !, 
   64			      read_comment(Next, Last),
   65			      read_rest(Last, Words).
   66
   67/* Otherwise get all of the next word. */
   68read_rest(C,[Word|Words]) :- read_word(C,Chars,Next),
   69                             name(Word,Chars),
   70                             read_rest(Next,Words).
   76/* Space, comma, newline, period, end-of-file or question mark separate words. */
   77read_word(C,[],C) :- ( C=32 ; C=44 ; C=10 ; C=9 ; C=13 ;
   78                         C=46 ; C=63 ; C=40 ; C=41 ; C=58 ; C= -1 ) , !.
   79
   80
   81/* Otherwise, get characters and convert to lower case. */
   82read_word(C,[LC|Chars],Last) :- lower_case(C, LC),
   83				get0(Next),
   84                                read_word(Next,Chars,Last).
   85
   86/* Convert to lower case if necessary. */
   87lower_case(C,C) :- ( C <  65 ; C > 90 ) , !.
   88lower_case(C,LC) :- LC is C + 32.
   89
   90
   91/* Keep reading as long you dont find end-of-line or end-of-file */
   92read_comment(10, 10) :- !.
   93read_comment(-1, -1) :- !.
   94read_comment(_, Last) :- get0(Next),
   95			 read_comment(Next, Last).
   96
   97/* for reference ... 
   98newline(10).
   99comma(44).
  100space(32).
  101period(46).
  102question_mark(63).
  103*/