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
   28:- dynamic flag/1.   29
   30read_file(File, List) :- system:seeing(Old), system:see(File), read_line(List), system:seen, system:see(Old).
   31
   32read_line(Words) :- get0(C),
   33                    read_rest(C,Words).
   34          
   35/* Ends the input. */
   36read_rest(-1,[]) :- !.
   37
   38/* Spaces, tabs and newlines between words are ignored. */
   39read_rest(C,Words) :- ( C=32 ; C=10 ; C=9 ; C=13 ; C=92 ) , !,
   40                     get0(C1),
   41                     read_rest(C1,Words).
   42
   43/* Brackets, comma, period or question marks are treated as separed words */
   44read_rest(C, [Char|Words]) :- ( C=40 ; C=41 ; C=44 ; C=45 ; C=46 ; C=63 ; C=58 ; C=60 ; C=62) , name(Char, [C]), !,
   45			get0(C1),
   46			read_rest(C1, Words).
   47
   48
   49/* Read comments to the end of line */
   50read_rest(59, Words) :- get0(Next), !, 
   51			      read_comment(Next, Last),
   52			      read_rest(Last, Words).
   53
   54/* Otherwise get all of the next word. */
   55read_rest(C,[Word|Words]) :- read_word(C,Chars,Next),
   57                             atom_codes(Word,Chars),
   58                             read_rest(Next,Words)
   58.
   59
   64/* Space, comma, newline, period, end-of-file or question mark separate words. */
   65read_word(C,[],C) :- ( C=32 ; C=44 ; C=10 ; C=9 ; C=13 ;
   66                         C=46 ; C=63 ; C=40 ; C=41 ; C=58 ; C=60 ; C=62 ; C= -1 ) , !.
   67
   68/* Otherwise, get characters and convert to lower case. */
   69read_word(C,[LC|Chars],Last) :- not(flag(lower_case)),
   70	atom_codes(Atom,[C]),
   72				check_letter(C, LC),
   73				get0(Next),
   74                                read_word(Next,Chars,Last)
   74.
   75
   76read_word(C,[LC|Chars],Last) :- flag(lower_case),
   77	atom_codes(Atom,[C]),
   79				lower_case(C, LC),
   80				get0(Next),
   81                                read_word(Next,Chars,Last)
   81.
   82
   83/* Convert to lower case if necessary. */
   84check_letter(C,C) :- ( C <  65 ; C > 90 ) , !.
   85check_letter(C,C) :- ( C <  97 ; C > 122 ) , !.
   86
   87/* Convert to lower case if necessary. */
   88lower_case(C,C) :- ( C <  65 ; C > 90 ) , !.
   89lower_case(C,LC) :- LC is C + 32.
   90
   91
   92/* Keep reading as long you dont find end-of-line or end-of-file */
   93read_comment(10, 10) :- !.
   94read_comment(-1, -1) :- !.
   95read_comment(_, Last) :- get0(Next),
   96			 read_comment(Next, Last).
   97
   98/* for reference ... 
   99newline(10).
  100comma(44).
  101space(32).
  102period(46).
  103question_mark(63).
  104*/