
/* Complete interpreter --- scanner, parser, interpreter --- for an
   arithmetic language with variables.   (In this prototype,
   all variables have value 0.)

   Example use:

   ?- run.
   Type program as a string followed by a period:
   |: "( 2  +  ( xy + 34 ) )".
   Scanned program: ( 2 + ( xy + 34 ) ) 
   Parse tree: add(num(2), add(iden([120, 121]), num(34)))
   Program evaluates to: 36
   true 

   (Notice that "xy" displays as the two-ASCII-char list, [120, 121].)
*/


/* Driver code:  *******************************************************/
 
run :- write('Type program as a string followed by a period:'),
       nl,
       read(InputText),
       scan(InputText, "", [], WordList),
       write('Scanned program: '), writeWords(WordList),
       parseExpr(WordList, ExprTree),
       write('Parse tree: '), write(ExprTree), nl,
       evalExpr(ExprTree, Answer),
       write('Program evaluates to: '), write(Answer), nl, !.


/****************************************************************************
  Scanner:  this part divides a string into a list of words. 

  scan(InputText, CurrentWordBeingAssembled,  WordsCollectedSoFar, FinalAnswer)
        where  InputText  is the string to be broken into words
               CurrentWordBeingAssembled  is the next word to be added to
                 to the  WordsCollectedSoFar
               WordsCollectedSoFar  are the words extracted so far from the
                 input text
               FinalAnswer  will hold the final value of  WordsCollectedSoFar 
                 It will be returned as the definition's answer

  IMPORTANT: all words must be separated by 1+ blanks!

  Example:  ?- scan("( 2 + ( x + 3 ) )", "", [], AnsList)
            AnsList = ["(", "2", "+", "(", "x", "+", "3", ")", ")"]
*/

/* cases when we have processed all the input text: */
scan([], [], Words, Words).
scan([], CurrentWord, Words, Ans) :- append(Words, [CurrentWord], Ans).

/* cases when there are more input characters to read:  */
scan([Char|Rest], CurrentWord, Words, Ans) :- notBlank(Char),
                       append(CurrentWord, [Char], NewWord),
                       scan(Rest, NewWord, Words, Ans).

scan([Char|Rest], CurrentWord, Words, Ans) :- isBlank(Char),
                       flushCurrentWord(CurrentWord, Words, NewWords),
                       scan(Rest, "", NewWords, Ans).

/* helper function that moves a completely assembled current word to the
     list of words collected so far:  */
flushCurrentWord("", Words, Words).
flushCurrentWord(Word, Words, NewWords) :- append(Words, [Word], NewWords).
/* a blank space is  Ascii code  32:  */
notBlank(C) :- C \= 32.
isBlank(32).

/* How to write a list of words to the output screen: */
writeWords([]) :- nl.
writeWords([H|T]) :- writeWord(H), writeWords(T).

writeWord([]) :- put(32).
writeWord([L|Rest]) :- put(L), writeWord(Rest).


/****************************************************************************
   Parser:  This part converts a list of words to a parse tree 
     (an operator tree).   Here is the input syntax it enforces:

   E : Expression        N : Numeral        I : Identifier

   E ::=  N  |  I  |  ( E1 + E2 )
   N  is a string of digits
   I  is a string of lower-case letters

   The parser's output are operator trees of these functor forms:

   ETREE ::=  num(n)  |  iden(i)  |  add( ETREE1, ETREE2 ) 
   where  n  is an integer
          i  is a string of lower-case letters

   (Comment: if we were writing this in Python, which lacks functors,
             we would make the operator trees look like this:
             ["num", n}  |  ["iden", i]  |  ["add", ETREE1, ETREE2]
   )

   The definition of the parser is

   parseExpr(WordList, ETree)
      where  WordList  is the input list of words to be parsed
             Etree  is the output parse tree built from  WordList

   Example: ?- parseExpr(["(", "2", "+", "(", "x", "+", "3", ")", ")"], Tree)
            Tree = add(num(2), add(iden("x"), num(3)))
*/

parseExpr([], Tree) :- write('Parse error: no input left').

parseExpr([Word], num(Num)) :- isNum(Word), toInt(Word, F, Num). /* see below */

parseExpr([Word], iden(Word)) :- isIden(Word).  /* see below */

/* this next one is cool: by trial and error, it splits  Words  into
   the fragments needed to build an addition operator tree: */
parseExpr(Words, add(Tree1, Tree2)) :-  
             /* split up  Words  into  ["("] + E1 + ["+"] + E2 + [")"] :  */
             append(["("], W1, Words),
             append(E1, W2, W1),
             append(["+"], W3, W2),
             append(E2, [")"], W3),
             /* You can write em out to see how  Words  got chopped up: */
             /* write('W1: '), write(W1), nl,
                write('W2: '), write(W2), nl,
                write('W3: '), write(W3), nl, nl,  */
             parseExpr(E1, Tree1),
             parseExpr(E2, Tree2).

/* Defines when a string is a numeral, that is, all digits: */
isNum([H]) :- isdigit(H).
isNum([H|T]) :- isdigit(H), isNum(T).
isdigit(N) :- N >= 48, N =< 57.

/* Converts a string of digits,  NumeralString,   to an int,  AnswerInt:
   Call it like this:
      ?- toInt(NumeralString, F, AnswerInt)
         The  F  is a "local variable" that is not part of the answer. */
toInt([], 1, 0).
toInt([H|T], Factor, Val) :-  toInt(T, Fac, Val0),
                    HVal0 is H - 48,
                    HVal is HVal0 * Fac,
                    Val is HVal + Val0,
                    Factor is Fac * 10.

/* Defines when a string is an identifier, that is, all lower-case letters: */
isIden([H]) :- isLetter(H).
isIden([H|T]) :- isLetter(H), isIden(T).
isLetter(L) :- L >= 97,  L =< 122.  


/***************************************************************************
  Interpreter:  This part computes the meaning of a parse tree.
  Recall these forms of tree:
    ETREE ::=  num(n)  |  iden(i)  |  add( ETREE1, ETREE2 ) 

  All identifiers,  i,  will be treated as having the meaning,  0

  The definition of the interpreter is

   evalExpr(ETREE, Answer)   
      where  ETREE  is as above 
             Answer  is the integer  Answer, the meaning of  ETREE 

  Example usage:  ?- evalExpr( add(num(2), add(iden("x"), num(3))), Ans)
                  Ans = 5
*/

evalExpr(num(N), N).

evalExpr(iden(I), Ans) :- lookup(I, Ans).

evalExpr(add(E1, E2), Ans) :-  evalExpr(E1, Ans1),
                               evalExpr(E2, Ans2),
                               Ans is Ans1 + Ans2.

/* Looks up the value of identifier  I,  returning  Ans */
lookup(I, 0).
/* that's it for now... */

