Laboratorium

Laboratorium 1: Kalkulator dla ONP

Piszemy kalkulator dla odwrotnej notacji polskiej (wystarczy 4 działania + modulo).

Należy zwrócić uwagę na:

  • subtelnosci leksykalne, np zwiazane z liczbami ujemnymi, np
    1 2 -3 ++
    1 2- 3 +
    1 2--3-
  • "lekser" w tym zadaniu powinien być napisany ręcznie
  • możliwe rozszerzenia: liczby zmiennoprzecinkowe, np -6.28e+23, .3E-4, pi; liczby szesnastkowe 0xCafeBabe etc..
  • Porządne komunikaty o błędach

Po ukończeniu kalkulatora można go przerobić tak, żeby zamiast obliczać budował drzewo wyrażenia i wypisywał je w notacji infiksowej (nietrywialne: nawiasy)

Laboratorium 2: generatory analizatorów leksykalnych

Poznajemy generator analizatorów leksykalnych dla naszego języka programowania. Może to obejmować Flex (C/C++), Alex (Haskell), ewentualnie JFlex (Java) i inne generatory.

W programie napisanym na poprzednim laboratorium, analizator leksykalny zamieniamy na wygenerowany przy pomocy odpowiedniego generatora.

Flex

Omawiamy przykład analizatora stworzonego przy uzyciu Flexa, np.

%{
// #include "exp.tab.h" /* Definiuje leksemy, np. NUM */
#define NUM '9'
int yylval;
%}
%option noyywrap
%%
[0-9]+  {
         yylval = atoi( yytext ) ;
         return (int)NUM;
       }
.  { return (int)(yytext[0]); }
\n  { return (int)'\n'; }
%%
int main() { int lexem; while(lexem=yylex()) { ... } 
 return 0;
}

Uruchamianie:
flex -o lexer.c lexer.l

Wygenerowany plik (tu: lexer.c) zawiera funkcję yylex(), której kolejne wywołania dają kolejne leksemy (0 dla EOF jeśli nie ma innych wytycznych)

JFlex

Omawiamy przykład, np.

%%
%class Scanner
%type Symbol
%unicode
%line 
 
%{
  StringBuffer string = new StringBuffer();
  // Leksemy są klasy Symbol, zdefiniowanej poza tym plikiem
  private Symbol symbol(int type) {
    return new Symbol(type, yyline, -1);
  }
  private Symbol symbol(int type, Object value) {
    return new Symbol(type, yyline, -1, value);
  }
%}
 
WhiteSpace     = (LineTerminator | [ \t\f])
DecIntLiteral = 0 | [1-9][0-9]*
 
%%
(0|[1-9][0-9]*) 	{ return symbol(sym.NUM, new Integer(yytext())); }
{WhiteSpace}		{ }
.		{ System.out.println("Unexpected character:"+yytext());}

Z tej specyfikacji JFlex wygeneruje klasę (tu: Scanner) zawierającą kod leksera. Konstruktor tej klasy bierze jako argument klasy java.io.Reader reprezentujący strumień wejściowy. Kolejne wywołania metody yylex() z tej klasy dają kolejne leksemy (null dla EOF w tym wypadku)

Alex

Omawiamy przykład, np.

{
module CalcLex(alexScanTokens) where
import CalcToken(Token(..))
}
%wrapper "basic"
$digit = 0-9                    
tokens :-
  $white+                        ; -- whitespace
  "--".*                            ; -- comment
  $digit+                        {\s -> Int (read s)}
  [\=\+\-\*\/\(\)]               {\s -> Sym (head s)}

Przykład uzycia:

$ alex CalcLex.x
$ ghci CalcLex.hs
GHCi, version 6.12.1...
Ok, modules loaded: CalcLex, CalcTokens.
*CalcLex> alexScanTokens "let x = 1 in x +x"
[Let,Var "x",Sym '=',Int 1,In,Var "x",Sym '+',Var "x"]

Laboratorium 3-4: kalkulator dla notacji infiksowej metodą LL(1)

Na poprzednich zajęciach pisaliśmy kalkulator dla notacji postfiksowej (ONP). Tym razem piszemy kalkulator dla notacji infiksowej (czyli "zwykłej"). W sumie przeznaczamy na ten temat dwa zajęcia: na pierwszych tworzymy tylko parser, który sprawdza poprawność wejścia, na drugich rozszerzamy go o budowę i interpretację drzewa struktury.

Wychodzimy od gramatyki

\[ E \to E + E \mid E - E \mid E * E \mid E / E \mid (E) \mid n \]

Przekształcamy ją do gramatyki jednoznacznej, a potem dla postaci LL(1)

Piszemy parser metodą zejść rekurencyjnych.

Laboratorium 5: generatory parserów

Bison

Omawiamy przykład, np. kalkulator dla ONP

%{
#define YYDEBUG 1
#include <stdio.h>
 double atof(const char *s);
int yylex();
void yyerror(const char *s);
#define YYSTYPE double
%}
%token NUM
%% 
input:    /* empty */
        | input line 
        ;
line:     '\n'
        | exp '\n' { printf("\t%.10g\n", $1);}
        ;
exp:    NUM           { $$ = $1;      }
        | exp exp '+' { $$ = $1 + $2; }
        | exp exp '-' { $$ = $1 - $2; }
        | exp exp '*' { $$ = $1 * $2; }
        | exp exp '/' { $$ = $1 / $2; }
%%
void yyerror(const char * s) { puts(s); }
int main() {
   yydebug=0; /* 1 for debugging */
  yyparse();
}

Java CUP

Omwiamy przykład, np.

import java_cup.runtime.*;
 
terminal Integer NUM;
terminal SEMI, PLUS, STAR;
 
non terminal prog;
non terminal Integer exp;
 
prog ::= exp:e
	{: System.out.println("value = " + e); :} 
	SEMI
	;
 
exp ::= NUM:n
	{: RESULT = n; :}
	| exp:e1 exp:e2 PLUS
	{: RESULT = new Integer(e1.intValue() + e2.intValue()); :} 
	| exp:e1 exp:e2 STAR
	{: RESULT = new Integer(e1.intValue() * e2.intValue()); :} 
	;

Happy

Omawiamy przykład np.

{
module Main where
import Data.Char
}
 
%name calc
%tokentype { Token }
%error { parseError }
 
%token 
      int             { TokenInt $$ }
      '+'             { TokenPlus }
      '*'             { TokenTimes }
%%
Exp : Exp Exp '+' { $1 + $2 }
    | Exp Exp '*' { $1 * $2 }
| int  { $1 }
    ;
{
 
parseError :: [Token] -> a
parseError _ = error "Parse error"
 
data Token 
      = TokenInt Int
      | TokenPlus
      | TokenTimes
 deriving Show
 
lexer :: String -> [Token]
lexer [] = []
lexer (c:cs) 
      | isSpace c = lexer cs
      | isDigit c = lexNum (c:cs)
lexer ('+':cs) = TokenPlus : lexer cs
lexer ('*':cs) = TokenTimes : lexer cs
 
lexNum cs = TokenInt (read num) : lexer rest
      where (num,rest) = span isDigit cs
 
main = getContents >>= print . calc . lexer
}

Zadania

  1. Uruchomić powyższy przykład
  2. Zmodyfikować przykład tak aby zamiast obliczać wartośc wyrażenia budował drzewo struktury i wypisywał je (np. w notacji infiksowej, albo obnawiasowanej prefiksowej.
  3. Napisać przy użyciu generatora parserów kalkulator dla notacji infiksowej (priorytety i łączność operatorów na razie rozwiązujemy przy użyciu klasycznej gramatyki
    E -> E + T  |  T ...

    Laboratorium 6: generatory parserów: priorytety i obsługa błędów

    Bison

    Omawiamy przykład priorytetów, n.p.

    %token NUM
    %left '-' '+'
    %left '*' '/'
    %left NEG     /* leksem-widmo: minus unarny */
    %right '^'    /* potęgowanie        */
    %%
    exp:      NUM                { $$ = $1;         }
            | exp '+' exp        { $$ = $1 + $3;    }
            | exp '-' exp        { $$ = $1 - $3;    }
            | exp '*' exp        { $$ = $1 * $3;    }
            | exp '/' exp        { $$ = $1 / $3;    }
            | '-' exp  %prec NEG { $$ = -$2;        }
            | exp '^' exp        { $$ = pow ($1,$3);}
            | '(' exp ')'        { $$ = $2;         }
    ;
    %%

    Omawiamy przykład obsługi błędów, n.p.

    exp:      NUM                { $$ = $1;         }
            | exp '+' exp        { $$ = $1 + $3;    }
            | exp '-' exp        { $$ = $1 - $3;    }
            | exp '*' exp        { $$ = $1 * $3;    }
            | exp '/' exp        { $$ = $1 / $3;    }
            | '-' exp  %prec NEG { $$ = -$2;        }
            | exp '^' exp        { $$ = pow ($1,$3);}
            | '(' exp ')'        { $$ = $2;         }
            | '(' error ')' 
            { printf("Error in expression\n");$$ = 0;}
    ;

    Studenci powinni zaimplementować powyzsze przykłady w swoich programach, poza tym piszą parser dla Javalette.

    Java Cup

    Priorytety:

    precedence left PLUS, MINUS;
    precedence left TIMES, DIVIDE, MOD;
    precedence left UMINUS;
     
    	expr ::=  MINUS expr:e             
    	          {: RESULT = new Integer(0 - e.intValue()); :} 
    	          %prec UMINUS

    Obsługa błędów:

     stmt ::= expr SEMI | while_stmt SEMI | if_stmt SEMI | ... |
    	     error SEMI
    	     ;

    Happy

    Tak samo jak Bison, np.

    %left '+' '-'
    %left '*' '/'
    %left NEG
    %%
     
    Exp   :
          | Exp '+' Exp             { Plus $1 $3 }
          | Exp '-' Exp             { Minus $1 $3 }
          | Exp '*' Exp             { Times $1 $3 }
          | Exp '/' Exp             { Div $1 $3 }
          | '(' Exp ')'             { Brack $2 }
          | '-' Exp %prec NEG       { Negate $2 }
          | int                     { Int $1 }

    BNFC

    Omawiamy przykład, np.

    entrypoints Exp;
     
    EAdd.  Exp  ::= Exp "+" Exp1 ;
    EMul.  Exp1 ::= Exp1 "*" Exp2 ;
    ENum.  Exp2 ::= Integer ;
    coercions Exp 2;

    Studenci powinni

    • skompilować i uruchomić ten przykład w swoim języku programowania
    • przeanalizować kod wygenerowany przez BNFC
    • rozszerzyć powyższy przykład o operatorym nawiasy, etc.
    • ręcznie zmodyfikować wygenerowany przez BNFC parser

    Laboratorium 7: maszyna wirtualna JVM; Jasmin

    Omawiamy przykład kodu JVM, np.

    .class  public Hello
    .super  java/lang/Object
     
    ; standard initializer
    .method public <init>()V
       aload_0
       invokespecial java/lang/Object/<init>()V
       return
    .end method
     
    .method public static main([Ljava/lang/String;)V
    .limit stack 2
      getstatic  java/lang/System/out Ljava/io/PrintStream;
      ldc "Hello"
      invokevirtual  java/io/PrintStream/println(Ljava/lang/String;)V
      return
    .end method

    Kompilujemy prostą klasę np.

    public class Inc  {
        public static void main(String[] args) {
    	System.out.println(test1(41));
        }
        static int test1(int i) {
    	return i+1;
        }
    }

    Następnie analizujemy kod przy pomocy javap -c, po czym zapisujemy go w formacie asemblera Jasmin.

    Rozszerzyć kalkulator z poprzednich laboratoriów o generowanie kodu Jasmin.

    Laboratorium 8: LLVM

    Low Level Virtual Machine, http://llvm.org/

    • maszyna rejestrowa, nieograniczona ilość rejestrów
    • generacja kodu na rzeczywisty procesor prez alokację rejestrów
    • biblioteka C++, ale także format tekstowy (na laboratorium zajmujemy się tylko tym ostatnim)
    • kod czwórkowy:
      %t2 = add i32 %t0, %t1
    • instrukcje są silnie typowane:
      %t5 = add double %t4, %t3
      store i32 %t2, i32* %loc_r
    • nowy rejestr dla każdego wyniku (SSA - Static Single Assignment)

      Prosty przykład

      declare void @printInt(i32) ;  w innym module
      define i32 @main() {
             %i1 = add i32 2, 2
             call void @printInt(i32 %i1)
             ret i32 0
      }

      Uruchomienie

      Narzędzia dla LLVM są w katalogu PUBLIC/MRJP/Llvm (w tym pliki runtime.{ll,bc}

      $ llvm-as t2.ll
      $ llvm-link -o out.bc t2.bc runtime.bc
      $ lli out.bc
      4

      Silnia, rekurencyjnie

      define i32 @fact(i32 %n) {
              %c0 = icmp eq i32 %n, 0
              br i1 %c0, label %L0, label %L1
      L0:
              ret i32 1
      L1:
              %i1 = sub i32 %n, 1
              %i2 = call i32 @fact(i32 %i1)
              %i3 = mul i32 %n, %i2
              ret i32 %i3 
      }

      Uwaga:

      • argumenty funkcji są deklarowane
      • wszystko jest typowane, nawet warunki skoków
      • skoki warunkowe tylko z "else"

      Silnia, iteracyjnie

      Używając zmiennych lokalnych w pamięci

      declare void @printInt(i32)
      define i32 @main() {
      entry: 
      	%i1=call i32 @fact(i32 5)
      	call void @printInt(i32 %i1)
      	ret i32 0
      }
       
      ; r = 1
      ; i = n
      ; while (i > 1):
      ;   r = r * i
      ;   i = i -1
      ; return r
      ;;
       
      define i32 @fact(i32 %n) {
      entry: 
      ; local variables:
              %loc_r = alloca i32
      	%loc_i = alloca i32
      ; r = 1
      	store i32 1, i32* %loc_r
      ; i = n
              store i32 %n, i32* %loc_i
      	br label %L1
      ; while i > 1:
      L1:
       	%tmp_i1 = load i32* %loc_i
      	%c0 = icmp sle i32 %tmp_i1, 1
      	br i1 %c0, label %L3, label %L2
      ; loop body
      L2:
      ; r = r * i
              %tmp_i2 = load i32* %loc_r
      	%tmp_i3 = load i32* %loc_i
      	%tmp_i4 = mul i32 %tmp_i2, %tmp_i3
      	store i32 %tmp_i4, i32* %loc_r 
      ; i = i-1
      	%tmp_i5 = load i32* %loc_i
      	%tmp_i6 = sub i32 %tmp_i5, 1
      	store i32 %tmp_i6, i32* %loc_i
      	br label %L1
      L3:
      	%tmp_i8 = load i32* %loc_r
      	ret i32 %tmp_i8

      Używając rejestrów, w wersji SSA

      declare void @printInt(i32)
      define i32 @main() {
      entry: 
      	%i1=call i32 @fact(i32 5)
      	call void @printInt(i32 %i1)
      	ret i32 0
      }
       
      ; r = 1
      ; i = n
      ; while (i > 1):
      ;   r = r * i
      ;   i = i -1
       
      define i32 @fact(i32 %n) {
      entry: br label %L1 
      L1: 
      	%i.1 = phi i32 [%n, %entry], [%i.2, %L2]
      	%r.1 = phi i32 [1, %entry], [%r.2, %L2]
      	%c0 = icmp sle i32 %i.1, 1
      	br i1 %c0, label %L3, label %L2
      L2:
      	%r.2 = mul i32 %r.1, %i.1
      	%i.2 = sub i32 %i.1, 1
      	br label %L1
      L3:
      	ret i32 %r.1
      }

      Zadanie

      Rozszerz kalkulator o generowanie kodu dla LLVM

      Napisy w LLVM

      @hellostr = internal constant [6 x i8] c"Hello\00"
       
      declare void @printString(i8*)
      define i32 @main() {
      entry: 
             %t0 = bitcast [6 x i8]* @hellostr to i8* ; można też uzyć getelementptr
             call void @printString(i8* %t0)
             ret i32 0
      }

    Laboratorium 9: asembler x86

    Kompilujemy i uruchamiamy programy napisane na ćwiczeniach.

    Najprostsza metoda zbudowania programu zawierającego funkcję w asemblerze:

    gcc -o f f.s main.c

    gdzie f.s jest plikiem zawierającym kod funkcji w asemblerze

    main.c plik zwierający program główny w C, np.

    int f(int);
    int printf(char*,...);
    int main() {
      printf("%d\n",f(5));
    }

    Uwaga: przy uruchamianiu na komputerze 32-bitowym potrzebna jeszcze będzie funkcja dostosowująca protokół wywołania i386 do omawianego na ćwiczeniach, np.

    .globl fad
    fad:	push %ebp
    	mov %esp,%ebp
    	//   In 32 bit ABI %edi and %esi are callee-save
    	push %edi
    	push %esi
    	mov 8(%ebp), %edi
    	mov 12(%ebp), %esi
    	mov 16(%ebp), %edx
    	mov 20(%ebp), %ecx
    	call f
    	pop %esi
    	pop %edi
    	pop %ebp
    	ret

    Lab 1 (English): RPN calculator

    Write a calculator for the Reverse Polish Notation (aka postfix notation).

    Pay careful attention to:

    • lexical subtleties, e.g. ones related to negative numbers:
      1 2 -3 ++
      1 2- 3 + 
      1 2--3-
    • the "lexer" in this task should be written by hand
    • possible extensions: floating point numbers e.g. -6.28e+23, .3E-4, pi; hexadecimal numbers, e.g. 0xCafeBabe etc..
    • decent error reporting
      When you're done, you can rewrite your program so that instead of computing the value of an expression it will build its tree and output it in infix notation (non-trivial: parentheses).

    Lab 2 (en): lexer generators

    Learn a lexer generator for your programming language. This can include Flex (C/C++), Alex (Haskell), possibly also JFlex (Java) and other generators.

    In the program written in the previous session, replace the handwritten lexer by a generated one.

    Flex

    Discuss an example of a Flex analyser, e.g.

    %{
    #include "exp.tab.h" /* Defines lexems, like NUM etc. */
    %}
    %option noyywrap
    %%
    [[:digit:]]+  {
             yylval = atoi( yytext ) ;
             return (int)NUM;
           }
    .  { return (int)(yytext[0]); }
    \n  { return (int)'\n'; }
    %%

    Running Flex:

    flex -o lexer.c lexer.l

    The generated file will contain a function yylex() which will return one lexem at a time.

    JFlex

    Discuss an example, e.g.

    %class Scanner
    %unicode
    %cup
    %line 
     
    %{
      StringBuffer string = new StringBuffer();
      // Leksemy są klasy Symbol, zdefiniowanej poza tym plikiem
      private Symbol symbol(int type) {
        return new Symbol(type, yyline, -1);
      }
      private Symbol symbol(int type, Object value) {
        return new Symbol(type, yyline, -1, value);
      }
    %}
     
    WhiteSpace     = (LineTerminator | [ \t\f])
    DecIntLiteral = 0 | [1-9][0-9]*
     
    %%
    (0|[1-9][0-9]*) 	{ return symbol(sym.NUM, new Integer(yytext())); }
    [\r\n\t\f ]		{ }
    .		{ System.out.println("Unexpected character:"+yytext());}

    From this specification JFlex generates a .java file with one class (for the above example: Scanner) that contains code for the scanner. The class will have a constructor taking a java.io.Reader from which the input is read. The class will also have a function yylex() returning the subsequent lexeme each time it is called.

    Alex

    Discuss an example, e.g.

    {
    module CalcLex(alexScanTokens) where
    import CalcToken(Token(..))
    }
    %wrapper "basic"
    $digit = 0-9                    
    $alpha = [a-zA-Z]               
    tokens :-
      $white+                        ; -- whitespace
      "--".*                         ; -- comment
      let                            { \s -> Let }
      in                             { \s -> In }
      $digit+                        {\s -> Int (read s)}
      [\=\+\-\*\/\(\)]               {\s -> Sym (head s)}
      $alpha [$alpha $digit \_ \']*  { \s -> Var s }

    Running Alex:

    ben@sowa$ alex CalcLex.x
    ben@sowa$ ghci CalcLex.hs
    GHCi, version 6.12.1...
    Ok, modules loaded: CalcLex, CalcTokens.
    *CalcLex> alexScanTokens "let x = 1 in x +x"
    Loading package array-0.3.0.0 ... linking ... done.
    [Let,Var "x",Sym '=',Int 1,In,Var "x",Sym '+',Var "x"]

    Lab 3-4 (en): recursive descent parsing

    The previous lab involved writing a calculator for the postfix notation (RPN). This time we wrtie a calculator for the infix (i.e. ordinary) notation.
    In the first sessions we write a correctness-checking parser, then extend it to build and iterpret a parse tree.

    Starting with the expression grammar

    \[ E \to E + E \mid E - E \mid E * E \mid E / E \mid (E) \mid n \]

    Transform it first to unambiguous form, then to LL(1).

    Then write a recursive descent parser.

    Lab 5 (en): parser generators

    Bison

    Discuss an example, e.g. RPN calculator

    %{
    #define YYDEBUG 1
    #include <stdio.h>
     double atof(const char *s);
    int yylex();
    void yyerror(const char *s);
    #define YYSTYPE double
    %}
    %token NUM
    %% 
    input:    /* empty */
            | input line 
            ;
    line:     '\n'
            | exp '\n' { printf("\t%.10g\n", $1);}
            ;
    exp:    NUM           { $$ = $1;      }
            | exp exp '+' { $$ = $1 + $2; }
            | exp exp '-' { $$ = $1 - $2; }
            | exp exp '*' { $$ = $1 * $2; }
            | exp exp '/' { $$ = $1 / $2; }
    %%
    void yyerror(const char * s) { puts(s); }
    int main() {
       yydebug=0; /* 1 for debugging */
      yyparse();
    }

    Java CUP

    Discuss an example, e.g.

    import java_cup.runtime.*;
     
    terminal Integer NUM;
    terminal SEMI, PLUS, STAR;
     
    non terminal prog;
    non terminal Integer exp;
     
    prog ::= exp:e
    	{: System.out.println("value = " + e); :} 
    	SEMI
    	;
     
    exp ::= NUM:n
    	{: RESULT = n; :}
    	| exp:e1 exp:e2 PLUS
    	{: RESULT = new Integer(e1.intValue() + e2.intValue()); :} 
    	| exp:e1 exp:e2 STAR
    	{: RESULT = new Integer(e1.intValue() * e2.intValue()); :} 
    	;

    Happy

    Discuss an example, e.g.

    {
    module Main where
    import Data.Char
    }
     
    %name calc
    %tokentype { Token }
    %error { parseError }
     
    %token 
          int             { TokenInt $$ }
          '+'             { TokenPlus }
          '*'             { TokenTimes }
    %%
    Exp : Exp Exp '+' { $1 + $2 }
        | Exp Exp '*' { $1 * $2 }
    | int  { $1 }
        ;
    {
     
    parseError :: [Token] -> a
    parseError _ = error "Parse error"
     
    data Token 
          = TokenInt Int
          | TokenPlus
          | TokenTimes
     deriving Show
     
    lexer :: String -> [Token]
    lexer [] = []
    lexer (c:cs) 
          | isSpace c = lexer cs
          | isDigit c = lexNum (c:cs)
    lexer ('+':cs) = TokenPlus : lexer cs
    lexer ('*':cs) = TokenTimes : lexer cs
     
    lexNum cs = TokenInt (read num) : lexer rest
          where (num,rest) = span isDigit cs
     
    main = getContents >>= print . calc . lexer
    }

    Zadania

    1. Compile a run an example in your chosen language
    2. Modify it to build a parse tree and write it out (e.g. in infix form, or parenthesised prefix form
    3. Using a parser generator, write a calculator for the infix notation; for now, problems with operator precedence and binding direction are to be solved using the usual grammar
      E -> E + T  |  T ...

      Lab 6 (en): parser generators - priorities, error handling, BNF Converter

      Bison

      Discuss an example of handling operator priorities e.g.

      %token NUM
      %left '-' '+'
      %left '*' '/'
      %left NEG     /* phantom lexeme: unary minus */
      %right '^'    /* exponentiation       */
      %%
      exp:      NUM                { $$ = $1;         }
              | exp '+' exp        { $$ = $1 + $3;    }
              | exp '-' exp        { $$ = $1 - $3;    }
              | exp '*' exp        { $$ = $1 * $3;    }
              | exp '/' exp        { $$ = $1 / $3;    }
              | '-' exp  %prec NEG { $$ = -$2;        }
              | exp '^' exp        { $$ = pow ($1,$3);}
              | '(' exp ')'        { $$ = $2;         }
      ;
      %%

      Discuss an example of error handling, e.g.

      exp:      NUM                { $$ = $1;         }
              | exp '+' exp        { $$ = $1 + $3;    }
              | exp '-' exp        { $$ = $1 - $3;    }
              | exp '*' exp        { $$ = $1 * $3;    }
              | exp '/' exp        { $$ = $1 / $3;    }
              | '-' exp  %prec NEG { $$ = -$2;        }
              | exp '^' exp        { $$ = pow ($1,$3);}
              | '(' exp ')'        { $$ = $2;         }
              | '(' error ')' 
              { printf("Error in expression\n");$$ = 0;}
      ;

      The students should implement above examples in their code; apart from that thay write their Latte parsers.

      Java Cup

      Priorities:

      precedence left PLUS, MINUS;
      precedence left TIMES, DIVIDE, MOD;
      precedence left UMINUS;
       
      	expr ::=  MINUS expr:e             
      	          {: RESULT = new Integer(0 - e.intValue()); :} 
      	          %prec UMINUS

      Error handling:

       stmt ::= expr SEMI | while_stmt SEMI | if_stmt SEMI | ... |
      	     error SEMI
      	     ;

      Happy

      Similar to Bison, e.g.

      %left '+' '-'
      %left '*' '/'
      %left NEG
      %%
       
      Exp   :
            | Exp '+' Exp             { Plus $1 $3 }
            | Exp '-' Exp             { Minus $1 $3 }
            | Exp '*' Exp             { Times $1 $3 }
            | Exp '/' Exp             { Div $1 $3 }
            | '(' Exp ')'             { Brack $2 }
            | '-' Exp %prec NEG       { Negate $2 }
            | int                     { Int $1 }

      BNFC

      Discuss an example, e.g.

      entrypoints Exp;
       
      EAdd.  Exp  ::= Exp "+" Exp1 ;
      EMul.  Exp1 ::= Exp1 "*" Exp2 ;
      ENum.  Exp2 ::= Integer ;
      coercions Exp 2;

      Students should

      • compile and run this example in the chosen programming language
      • analyse the BNFC-generated code
      • extend the example with more operatros, parentheses, etc..
      • try to modify the generated parser