Computer Science 3 - 2001

Programming Language Translation


Practical for Week 20, beginning 3 September 2001

ALL GROUPS must hand in their submissions for this practical before lunch time on Thursday 20 September, correctly packaged in a transparent folder with the "cover sheet". Since the practical will have been done on a group basis, please hand in one copy of the cover sheet for each member of the group. These will be returned to you in due course, signed by the marker, and you will be asked to sign to acknowledge that you have received your own copy.

Note the hand in date carefully. The reason for requiring all submissions by that date is that Practical 21 builds on this one, and the prac kit for Practical 21 will effectively provide solutions for large parts of Practical 20.


Objectives

The objectives of this prac are to familiarise yourself with CS301-1 (a little Clang-like language), to extend it syntactically to derive CS301-2 so as to make it more usable, and to develop a pretty printer so that CS301-2 programs typed in an arbitrary mishmash layout can be rearranged neatly.

You are advised to bring your copy of the CS301-1 Report to this prac.

If you have lost it, you will be able to refer to the online copy on the Web pages, of course.


To hand in:

This week you are required to hand in, besides the cover sheet:

I do NOT require listings of any C++ code produced by Coco/R.

Keep the prac sheet and your solutions until the end of the semester. Check carefully that your mark has been entered into the Departmental Records.

You are referred to the rules for practical submission which are clearly stated on page 13 of our Departmental Handbook. However, for this course pracs must be posted in the "hand-in" box in the secretary's office for collection by Pat Terry.

A rule not stated there, but which should be obvious, is that you are not allowed to hand in another student's work as your own. Attempts to do this will result in (at best) a mark of zero and (at worst) severe disciplinary action and the loss of your DP. You are allowed - even encouraged - to work and study with other students, but if you do this you are asked to acknowledge that you have done so.


Task 1 Buy the kit (still free, while stocks last!)

In the kit PRAC20.ZIP you will find the usual treasure trove. In particular


Task 2 Do you really think you know the language?

Suppose that next year we were to decide to use CS301-1 as our First Year Programming Language, and that as an Honours student (which, of course you will be by then), you were asked to be a demonstrator. First years ask the quaintest questions. So do second years, and so, of course do ... Suppose someone came to you with the following mess and asked you the questions indicated. Which of them could you answer (a) by referring only to the EBNF for CS301-1 (b) by referring to the English descriptions in the CS301-1 report or (c) by by submitting the mess to the compiler and seeing what happened?

To submit your solution, copy the file QUERY.CS3, and edit in your answers.

In principle you should, of course, be able simply to write the answer, followed by (a) or (b) next to each one, quoting the relevant section in the EBNF or of the CS301-1 report. But in practice the manual may be deficient. And don't simply hope you can submit the lot to the CS301-1 compiler (COMPILE.EXE) or parser - the error recovery may not be very good, and you might be confused at what it tells you!

  PROGRAM Query;
    CONST
      Header = 'Title';  { Can I declare a string constant? }
    INT
      X, Y,              { Some easy ones }
      L1[10], L2[10],    { Are these the same size? }
      L3[20], I, Query,  { Can I reuse the program name as a variable? }
      Header,            { Can I reuse a constant name as a variable name? }
      L3[15];            { What happens if I use a variable name again? }
    CONST                { Can I declare constants after variables? }
      Max = 1000;
      Min = -89;         { Can I define negative constants? }
      MaxPlus3 = Max+3;  { Can I define constants in terms of others? }
      XX = X;            { Can I give one variable X two names like this? }
      UNTRUE = NOT TRUE; { Can I define Boolean constants }
    INT                  { Can I have another variable section? }
      BigList[Max];      { Can I use named constants to set array sizes? }
    BEGIN
      Write(Header)      { Can I write constants? }
      L1[10] := 34;      { Does L1[10] exist? }
      L1 := L2;          { Can I copy complete arrays? }
      Write(L3);         { Can I write complete arrays? }
      ;; X := Query;;;   { What about spurious semicolons? }
      IF (X) THEN        { Can I have a single variable as a "condition"? }
        BEGIN END;       { Can I write BEGIN END as a valid construction? }
      WHILE (X = 7) DO;  { Is this a valid loop? }
      X := X * -5;       { Can I do this? }
      BEGIN END;         { Can I do this as a stand alone statement? }
      X := L1[1];        { Presumably this is okay? }
      L1 := X;           { Can I do this? Does it mean anything? }
      X := TRUE + 5;     { Can I do this? Does it mean anything? }
      X := 5 AND NOT 6;  { Can I do this? Does it mean anything? }
      X := X - - + Y;    { Can I do this? Does it mean anything? }
    END.


Interlude - If the language is unsuitable, fix it

CS301-1 was designed as a language for a compiler/languages course, with deliberate omissions that can provide hours of fun in the small hours of the morning as you fill them in. Here is a selection of suggestions for deriving Pat's Gift To Civilisation (otherwise known as CSC301-2), all of which can be taken up with a little judicious alteration of the CS3.ATG grammar file that, just by chance, happens to be part of this week's prac kit.

Hang on - don't actually edit that file!!! As a later task we shall be modifying an attributed grammar that produces a pretty printer. But because that grammar may be a bit confusing at first reading, especially if you are one of the (too many) students who has missed (too many) lectures, think out your solutions to the next few tasks on paper, and then merge them with the grammar from Task 9 to make the grammar for Task 10.

Hang on!!!! What you are asked to do, of course, is almost entirely syntactic. Although you will probably by now have a good idea of what a CS301-1 program should "do", we are not writing a full-on compiler - yet.


Task 3 Better ways of declaring arrays and constants

Suppose we wished to extend CS301-2 to allow declarations to be made in terms of predeclared constants, for example

    CONST
      Max = 100;
      MaxPlus10 = Max + 10;
    INT
      List[Max];
      LongList[2 * Max + 100];
      BigList[MaxPlus10];

How would this be achieved?


Task 4 Statement sequences

Modify the grammar to give one for CS301-2 where statement sequences and a terminating END are used in IF and WHILE statements. (See TASK4.CS3) Of course, if you do this, the need for a compound statement (other than for the program "block") will fall away, so fix that too while you are at it.


Task 5 Better control over your output

The CS301-1 WRITE statement always follows its output with a line mark. Introduce a NEWLINE statement as a variation, so that WRITE does not append a line mark, but NEWLINE will do so.

The CS301-1 output statements are also a bit restricted, in that they do not allow a user to do nice "formatting". Extend the language to adopt an idea used in Pascal, where a statement like

      Write(X : 5, X + A : 12, X - Y : 2 * N)

will write the values of X, X+A and X-Y in fields of widths 5, 12 and 2*N respectively.


Task 6 More power to the arms of the IF statement

Extend the syntax for IF statements to allow an optional ELSE clause. You should remember that the IF - THEN - ELSE statement can cause nasty LL(1) problems. Do these happen here too? If not, why not? (A sample program with some extended IF statements appears in the kit as TASK6.CS3).


Task 7 Why does nobody use CS301-1?

Not surprising. It does not have all those cute little assignment operators like += -= *= ++ -- and so on. Well, give the people what they want - add them.

Not so fast. We must also allow statements like LIST[I] += 4. Does your extended grammar allow such things? And, just for fun, people are bound to confuse := and = as operators. How can we best handle this predictable silliness, recovering from it as nicely as possible?

It will suffice to use the ++ and -- operators in complete statements only; don't bother to add them as operators within expressions.


Task 8 And still nobody uses CS301-1?

Well, would you use a language that did not have a CASE or SWITCH statement? No, I thought not. So let's add that as well, on the lines of that found in Modula-2, discussed last week and exemplified in TASK8.CS3.


Task 9 A pretty printer for CS301-1

In case you have not met this concept before (missed that lecture?), a pretty printer is a "compiler" that takes a source program and "translates" the source into the same language. That probably does not sound very useful! However, the "object code" is formatted neatly, according to some simple conventions. For example, given a program that originally reads like this (don't laugh; I have seen this sort of thing!):

        PROGRAM Backwards; INT Terminator;

        PROCEDURE Start(INT Local1,Local2);
            FUNCTION ABS (x); BEGIN IF x < 0 THEN ABS := - x ELSE ABS := x END;

            PROCEDURE Reverse;
              INT Number;
              BEGIN READ(Number);IF Local1<>ABS(Number) THEN BEGIN Reverse; WRITE(Number)END
              END;

            BEGIN
                  Local1:=Terminator;Reverse
                     END;

          BEGIN
      Terminator         :=       9;Start END.

A pretty printer might produce something like this (the exact layout is a matter of taste:

        PROGRAM Backwards;
          INT
            Terminator;

          PROCEDURE Start (INT Local1, Local2);

            FUNCTION ABS (x);
              BEGIN
                IF x < 0 THEN
                  ABS := - x
                ELSE
                  ABS := x
              END;

            PROCEDURE Reverse;
              INT
                Number;
              BEGIN
                READ(Number);
                IF Local1 <> ABS(Number) THEN
                  BEGIN
                    Reverse;
                    WRITE(Number)
                  END;
              END;

     ... and so on

In the prac kit is an alternative grammar for CS301-1 level 1 in the file CS301.ATG that defines how such a pretty printer operates. Essentially it does this by adding "actions" to the grammar within meta-brackets (. ... .), as shown in the following extract:

            CompoundStatement =
              "BEGIN"                (. Append("BEGIN"); IndentNewLine(); .)
                 Statement
                   { ";"             (. Append(";"); NewLine(); .)
                     Statement }
              "END"                  (. ExdentNewLine(); Append("END"); .)   .

Study the grammar carefully, and you should start to appreciate how powerful a tool like Coco/R can become.

Generate the usual make file, construct a CS301-1 pretty printer and try it out on the file AWFUL.CS3, which is in the "old" CS301-1 syntax. Note that the output appears in stdout - redirect it as usual to a new file.

The actions incorporate calls to an auxiliary module, which you will also find in the kit, and which has the interface shown below. You can incorporate these routines into your parser by adding a #include "prettypr.hpp" line into your attribute grammar.


Task 10 A pretty printer for the new, improved CS301-2

At last! Incorporate all your great ideas from the earlier tasks and modify the attribute grammar so that it can parse and pretty-print programs written in your extended CS301-2 language.

You may have to edit the CS301.FRM file if you have added any of your own error messages.

You should be able to test your system by pretty printing the various sample programs suggested in this handout. Feel free to invent a few more.

For a bonus and for the more adventurous among you: since the CS301-2 grammar specifies a syntax for comments that are simply ignored by the parser, the pretty printer as derived from CS301.ATG will simply remove them! Can you think of a way around this - so that the comments are copied to the reformatted output as well? (Hint: study the text book, in particular the section on the PRAGMA directive of Cocol.)


Unattributed CS301-1 grammar

    COMPILER CS3 $XCN  /* generate compiler, C++ */
    /* Simple unattributed grammar for CS301 level 1
       P.D. Terry, Rhodes University, 2001 */

    IGNORE CASE
    IGNORE CHR(9) .. CHR(13)
    COMMENTS FROM "{" TO "}"

    CHARACTERS
      cr         = CHR(13) .
      lf         = CHR(10) .
      letter     = "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz" .
      digit      = "0123456789" .
      instring   = ANY - "'" - cr - lf - CHR(0) .

    TOKENS
      identifier = letter { letter | digit } .
      number     = digit { digit } .
      string     = "'" (instring | "''") { instring | "''" } "'" .

    PRODUCTIONS
      CS3               = "PROGRAM" identifier ";" Block "." .
      Block             = { ConstDeclarations | VarDeclarations } CompoundStatement .
      ConstDeclarations = "CONST" OneConst { OneConst } .
      OneConst          = identifier "=" number ";" .
      VarDeclarations   = ( "INT" | "BOOL" ) OneVar { "," OneVar } ";" .
      OneVar            = identifier [ UpperBound ] .
      UpperBound        = "[" number "]" .
      CompoundStatement = "BEGIN" Statement { ";" Statement } "END" .
      Statement         = [   CompoundStatement | Assignment | ReturnStatement
                            | IfStatement       | WhileStatement
                            | ReadStatement     | WriteStatement ] .
      Assignment        = Variable ":=" Expression .
      Variable          = Designator .
      Designator        = identifier [ "[" Expression "]" ] .
      ReturnStatement   = "RETURN" .
      IfStatement       = "IF" Condition "THEN" Statement .
      WhileStatement    = "WHILE" Condition "DO" Statement .
      Condition         = Expression .
      ReadStatement     = "READ" "(" Variable { "," Variable } ")" .
      WriteStatement    = "WRITE" [ "(" WriteElement { "," WriteElement }  ")" ] .
      WriteElement      = string | Expression .
      Expression        = AndExp { "OR" AndExp } .
      AndExp            = RelExp { "AND" RelExp } .
      RelExp            = AddExp [ RelOp AddExp ] .
      AddExp            = MultExp { AddOp MultExp } .
      MultExp           = UnaryExp { MulOp UnaryExp } .
      UnaryExp          = Factor | UnaryOp UnaryExp .
      Factor            =  Designator | number | "TRUE" | "FALSE" | "(" Expression ")" .
      UnaryOp           = "+" | "-" | "NOT" .
      AddOp             = "+" | "-" .
      MulOp             = "*" | "/" .
      RelOp             = "=" | "<>" | "<" | "<=" | ">" | ">=" .
    END CS3.


The interface to the pretty printing auxiliary routines:

    void Append(char String[]);
    /* Append String to stdout file */

    void IndentNewLine();
    /* Write line mark to stdout file and prepare to indent further lines
       by two spaces more than before */

    void ExdentNewLine();
    /* Write line mark to stdout file and prepare to indent further lines
       by two spaces less */

    void NewLine();
    /* Write line mark to stdout file but leave indentation as before */

    void Indent();
    /* Increment indentation level by 2 */

    void Exdent();
    /* Decrement indentation level by 2 */


Various simple test programs

   PROGRAM Debug;                      PROGRAM Debug;
   { Task 4 Tester }                   { Task 5 Tester }
     INT                                 INT
       I;                                  I;
     BEGIN                               BEGIN
       I := 1;                             I := -5;
       WHILE I <= 10 DO                    WHILE I <= 10 DO
         WRITE(I);                           WRITE(I : 5); WRITE(I + J :3, I : I + 4); NEWLINE;
         WRITE(I * I);                       I := I + 1;
         I := I + 1;;;                     END;
       END;                              END.
       IF I = 11 THEN
         WRITE (' I is now ', I);
         WRITE (' Just as well!')
       END
     END.


   PROGRAM Task6;
   { Task 6 Tester }
     INT
       I;
     BEGIN
       READ(I);
       IF I = 12
         THEN I := 12; WRITE('I Changed to', I : 2);
                   ELSE WRITE('Nothing unusual at all')
       END;
       IF I = 11 THEN
         WRITE (' I is now ', I);
   ELSE IF I = 13 THEN I := 14 ELSE I := 15 END END
     END.


   PROGRAM Debug;              PROGRAM Task8a;
   { Task 7 Tester }           { Demonstrate case statements in CS301-2 }
     BEGIN
       J += A[4];                INT
       I = 4 + 3 * (5 - 12);       I, J, K;
       J -= (2 - 1 * J);
       J *= A[9];                BEGIN
       A[J] += 12;                 Read(I, J, K);
       A[J] := 12;                 IF (I < J) AND (J < K) THEN Write('I < J < K');
       A++;                        CASE I + J OF
       A[J]--;                        1 : J := K; K := I;
     END.                          |  2 : WHILE I < 10 DO I := I + 1;
                                   |  3, 4, 5 .. 12 : { do nothing }
                                     DEFAULT : Read(I, J, K); Write(I * J / K)
                                   END
                                 END.


Home  © P.D. Terry