[net.sources] LALR grammar for revised Ada

david@ssc-vax.UUCP (David Norris) (12/02/83)

   This is an LALR(1) grammar for ANSI standard Ada, acceptable by the
Yacc compiler-compiler under Unix.  It is based on a grammar for preliminary
Ada from an article in the ACM Sigplan Notices (see below), and updated by
me to conform to the new standard.  I am submitting it to the net for public
use; any comments or suggestions (or mistakes) would be appreciated.  I have
a lexical analyzer (also in C) which accompanies the parser generated by this
grammar, if anyone is interested.  The addition of error-recovery routines
would make this a good Ada syntax-checker or the start of a full compiler.

	-- Dave Norris
	-- ..!uw-beaver!ssc-vax!david

/*
         An LALR(1) Grammar for (Revised) MIL-STD-1815A Ada

         original work done by
                  Persch, Winterstein, Drossopoulou, and Dausmann
                  Universitat Karlsruhe, D-7500 Karlsruhe 1

         adapted to MIL-STD-1815A by
                  David C. Norris
                  October, 1983

         From an original paper in the ACM Sigplan Notices
         Volume 16, Number 3, March 1981, Page 85

         The following is an LALR(1) grammar for the ANSI standard
         Ada language, acceptable to the YACC compiler-compiler
         under the UNIX operating system.  The grammar produces
         one shift-reduce conflict (attribute) which is properly
         resolved by Yacc's disambiguating rules (shifted).
         The tokens accepted by the parser are those which a
         typical lexical analyzer might produce.
*/
%start compilation 

/* Define as tokens the literals */

%token IDENTIFIER NUMERIC_LITERAL STRING_LITERAL CHARACTER_LITERAL

/* Define as tokens the Ada keywords */

%token ABORT ABS ACCEPT ACCESS ALL AND ARRAY AT
%token BEGIN BODY
%token CASE CONSTANT
%token DECLARE DELAY DELTA DIGITS DO
%token ELSE ELSIF END ENTRY EXCEPTION EXIT
%token FOR FUNCTION
%token GENERIC GOTO
%token IF IN IS
%token LIMITED LOOP
%token MOD
%token NEW NOT NULL
%token OF OR OTHERS OUT
%token PACKAGE PRAGMA PRIVATE PROCEDURE
%token RAISE RANGE RECORD REM RENAMES RETURN REVERSE
%token SELECT SEPARATE SUBTYPE
%token TASK TERMINATE THEN TYPE
%token USE
%token WHEN WHILE WITH
%token XOR

/* Define as tokens the special symbols */

%token ELLIPSIS LEFT_PAREN RIGHT_PAREN COMMA COLON SEMICOLON
%token BOX PERIOD QUOTE EQUAL_TO NOT_EQUAL_TO GREATER_THAN
%token GREATER_EQUAL LESS_THAN LESS_EQUAL PLUS MINUS AMPERSAND SPLAT
%token SLASH DOUBLE_STAR LEFT_LABEL RIGHT_LABEL REPLACEMENT ARROW BAR

%%

pragma : PRAGMA IDENTIFIER SEMICOLON
       | PRAGMA IDENTIFIER LEFT_PAREN argument_list RIGHT_PAREN SEMICOLON ;

argument_list : argument
              | argument_list COMMA argument ;

/* expression can also be a name */
argument : expression
         | IDENTIFIER ARROW expression ;

/* pragmas allowed in declarationive part */
basic_declaration :
     object_declaration      | number_declaration
  |  type_declaration        | subtype_declaration
  |  subprogram_declaration  | package_declaration
  |  task_declaration        | generic_declaration
  |  exception_declaration   | generic_instantiation
  |  renaming_declaration    | pragma ;

/* deferred_constant_declaration is in here */
object_declaration :
    IDENTIFIER       COLON          subtype_indication
                                        initialization_option SEMICOLON
  | IDENTIFIER       COLON CONSTANT subtype_indication
                                        initialization_option SEMICOLON
  | IDENTIFIER       COLON          constrained_array_definition
                                        initialization_option SEMICOLON
  | IDENTIFIER       COLON CONSTANT constrained_array_definition
                                        initialization_option SEMICOLON
  | identifier_list2 COLON          subtype_indication
                                        initialization_option SEMICOLON
  | identifier_list2 COLON CONSTANT subtype_indication
                                        initialization_option SEMICOLON
  | identifier_list2 COLON          constrained_array_definition
                                        initialization_option SEMICOLON
  | identifier_list2 COLON CONSTANT constrained_array_definition
                                        initialization_option SEMICOLON ;

initialization_option : | REPLACEMENT expression ;

number_declaration :
    IDENTIFIER       COLON CONSTANT REPLACEMENT expression SEMICOLON
  | identifier_list2 COLON CONSTANT REPLACEMENT expression SEMICOLON ;

identifier_list2 : IDENTIFIER COMMA IDENTIFIER
                  | identifier_list2 COMMA IDENTIFIER ;

/* type_definition includes private_type */
type_declaration :
     TYPE IDENTIFIER discriminant_part_option IS type_definition SEMICOLON
   | incomplete_type_declaration ;

discriminant_part_option : | discriminant_part ;

type_definition : enumeration_type_definition | integer_type_definition
                | real_type_definition        | array_type_definition
                | record_type_definition      | access_type_definition
                | derived_type_definition     | private_type_definition ;

subtype_declaration : SUBTYPE IDENTIFIER IS subtype_indication SEMICOLON ;

subtype_indication : name | subtype_indication_with_constraint ;

/* index_constraint, discriminant_constraint are in name */
subtype_indication_with_constraint : name range_constraint
                                   | name floating_point_constraint
                                   | name fixed_point_constraint ;

derived_type_definition : NEW subtype_indication ;

range_constraint : RANGE range ;

range : simple_expression ELLIPSIS simple_expression
      | name QUOTE RANGE
      | name QUOTE RANGE LEFT_PAREN expression RIGHT_PAREN ;

enumeration_type_definition : LEFT_PAREN enumeration_literal_list RIGHT_PAREN ;

enumeration_literal_list : enumeration_literal
                         | enumeration_literal_list COMMA enumeration_literal ;

enumeration_literal : IDENTIFIER | CHARACTER_LITERAL ;

integer_type_definition : range_constraint ;

real_type_definition : floating_point_constraint | fixed_point_constraint ;

floating_point_constraint : DIGITS simple_expression range_constraint_option ;

range_constraint_option : | range_constraint ;

fixed_point_constraint : DELTA simple_expression range_constraint_option ;

array_type_definition : unconstrained_array_definition
                      | constrained_array_definition ;

unconstrained_array_definition :
        ARRAY LEFT_PAREN index_list RIGHT_PAREN OF subtype_indication

constrained_array_definition :
        ARRAY index_constraint OF subtype_indication

index_list : index_subtype_definition
           | index_list COMMA index_subtype_definition ;

index_subtype_definition : name RANGE BOX ;

index_constraint : LEFT_PAREN discrete_range_list RIGHT_PAREN ;

discrete_range_list : discrete_range
                    | discrete_range_list COMMA discrete_range ;

discrete_range : subtype_indication | range ;

record_type_definition : RECORD component_list END RECORD ;

component_list : component_declaration_list0 component_declaration
               | component_declaration_list0 variant_part
               | NULL ;

component_declaration_list0 :
   | component_declaration_list0 component_declaration ;

component_declaration :
    IDENTIFIER       COLON subtype_indication initialization_option SEMICOLON
  | identifier_list2 COLON subtype_indication initialization_option SEMICOLON ;

discriminant_part : LEFT_PAREN discriminant_specification_list RIGHT_PAREN ;

discriminant_specification_list :
      discriminant_specification
    | discriminant_specification_list SEMICOLON discriminant_specification ;

discriminant_specification : 
         IDENTIFIER       COLON name initialization_option
       | identifier_list2 COLON name initialization_option ;

variant_part : CASE IDENTIFIER IS variant_list1 END CASE SEMICOLON ;

variant_list1 :               WHEN choice_list ARROW component_list
              | variant_list1 WHEN choice_list ARROW component_list ;

/* simple_expression can be simple_name */
/* "name range_constraint" and "range" substitutes for discrete_range */
/* choice OTHERS must stand by itself, so is not included in choice_list */
choice : simple_expression | name range_constraint | range ;

choice_list : OTHERS
            | choice_list1 ;

choice_list1 : choice | choice_list BAR choice ;

access_type_definition : ACCESS subtype_indication ;

incomplete_type_declaration :
                TYPE IDENTIFIER discriminant_part_option SEMICOLON ;

/* "body" separates basic_items from later_items */
declarative_part :
    basic_declarative_item_list0
  | basic_declarative_item_list0 body later_declarative_item_list0 ;

basic_declarative_item_list0 :
         | basic_declarative_item_list0 basic_declaration
         | basic_declarative_item_list0 representation_clause
         | basic_declarative_item_list0 use_clause ;

body : proper_body | body_stub ;

later_declarative_item_list0 :
        | later_declarative_item_list0 body
        | later_declarative_item_list0 subprogram_declaration
        | later_declarative_item_list0 package_declaration
        | later_declarative_item_list0 task_declaration
        | later_declarative_item_list0 generic_declaration
        | later_declarative_item_list0 use_clause
        | later_declarative_item_list0 generic_instantiation ;

proper_body : subprogram_body | package_body | task_body ;

/* "indexed_component" substitutes for slice */
/* operator_symbol substitutes for string_literal in primary */
name : IDENTIFIER        | CHARACTER_LITERAL  | operator_symbol
     | indexed_component | selected_component | attribute ;

/* "indexed_component" covers:
                           indexed_components
                           slices
                           function_calls
                           name index_constraint (in subtype_indication)
                           name discriminant_constraint (in subtype_indication)
                           procedure_calls
                           type_conversion
                           subtype_indication (in allocator)
*/

indexed_component : name LEFT_PAREN generalized_expression_list RIGHT_PAREN ;

generalized_expression_list :
     generalized_expression
   | generalized_expression_list COMMA generalized_expression ;

generalized_expression : expression
                       | range
                       | subtype_indication_with_constraint
                       | choice_list ARROW expression
                       | choice_list ARROW subtype_indication_with_constraint ;

selected_component : name PERIOD IDENTIFIER
                   | name PERIOD ALL
                   | name PERIOD operator_symbol
                   | name PERIOD CHARACTER_LITERAL ;

/* shift-reduce conflict here properly resolved (shifted) */
attribute : name QUOTE IDENTIFIER
          | name QUOTE DELTA
          | name QUOTE DIGITS
          | name QUOTE IDENTIFIER LEFT_PAREN expression RIGHT_PAREN ;

/* aggregate must have 2 component associations or have choices
   with an arrow to distinguish from "(expression)"             */
aggregate : LEFT_PAREN component_association_list2  RIGHT_PAREN
          | LEFT_PAREN choice_list ARROW expression RIGHT_PAREN ;

component_association_list2 :
           component_association       COMMA component_association
         | component_association_list2 COMMA component_association ;

component_association : expression | choice_list ARROW expression ;

expression : relation
           | and_expression
           | or_expression
           | xor_expression
           | andthen_expression
           | orelse_expression ;

and_expression : relation AND relation
               | and_expression AND relation ;

or_expression : relation OR relation
              | or_expression OR relation ;

xor_expression : relation XOR relation
               | xor_expression XOR relation ;

andthen_expression : relation AND THEN relation
                   | andthen_expression AND THEN relation ;

orelse_expression : relation OR ELSE relation
                  | orelse_expression OR ELSE relation ;

relation : simple_expression
         | simple_expression relational_operator simple_expression
         | simple_expression membership_operator range
         | simple_expression membership_operator name ;

membership_operator : IN | NOT IN ;

simple_expression : term_list
                  | unary_adding_operator term_list ;

term_list : term
          | term_list binary_adding_operator term ;

term : factor
     | term multiplying_operator factor ;

factor : primary
       | primary DOUBLE_STAR primary
       | ABS primary
       | NOT primary ;

/* string_literal can be name (operator_symbol) */
/* function_call is name (indexed_component) */
/* type_conversion is name (indexed_component) */
primary : NUMERIC_LITERAL | NULL | aggregate
        | name | allocator | qualified_expression
        | LEFT_PAREN expression RIGHT_PAREN ;

relational_operator : EQUAL_TO | NOT_EQUAL_TO
                    | GREATER_THAN | GREATER_EQUAL
                    | LESS_THAN | LESS_EQUAL ;

binary_adding_operator : PLUS | MINUS | AMPERSAND ;

unary_adding_operator : PLUS | MINUS ;

multiplying_operator : SPLAT | SLASH | MOD | REM ;

qualified_expression : name QUOTE LEFT_PAREN expression RIGHT_PAREN
                     | name QUOTE aggregate ;

/* name can be subtype_indication (indexed_component) */
allocator : NEW name | NEW qualified_expression ;

sequence_of_statements : statement | sequence_of_statements statement ;

statement : label_list simple_statement | label_list compound_statement ;

label_list : | label_list label ;

simple_statement : null_statement  | assignment_statement
                 | exit_statement  | return_statement
                 | goto_statement  | procedure_call_statement
                 | delay_statement | abort_statement
                 | raise_statement | code_statement ;

compound_statement : if_statement     | case_statement
                   | loop_statement   | block_statement
                   | accept_statement | select_statement ;

label : LEFT_LABEL IDENTIFIER RIGHT_LABEL ;

null_statement : NULL SEMICOLON ;

assignment_statement : name REPLACEMENT expression SEMICOLON ;

if_statement : IF condition THEN
                   sequence_of_statements
               elsif_list0
               else_option
               END IF SEMICOLON ;

elsif_list0 : | elsif_list0 ELSIF condition THEN sequence_of_statements ;

else_option : | ELSE sequence_of_statements ;

condition : expression ;

case_statement : CASE expression IS
                    alternative_list1
                 END CASE SEMICOLON ;

alternative_list1 :
     WHEN choice_list ARROW sequence_of_statements
   | alternative_list1 WHEN choice_list ARROW sequence_of_statements ;

loop_statement :
     iteration_clause_option basic_loop SEMICOLON
   | IDENTIFIER COLON iteration_clause_option basic_loop IDENTIFIER SEMICOLON ;

basic_loop : LOOP sequence_of_statements END LOOP ;

iteration_clause_option : FOR IDENTIFIER IN         discrete_range
                        | FOR IDENTIFIER IN REVERSE discrete_range
                        | WHILE condition ;

block_statement : declare_part_option
                  BEGIN
                      sequence_of_statements
                      exception_option
                  END SEMICOLON
                | IDENTIFIER COLON
                  declare_part_option
                  BEGIN
                      sequence_of_statements
                      exception_option
                  END IDENTIFIER SEMICOLON ;

declare_part_option : | DECLARE declarative_part ;

exception_option : | EXCEPTION exception_handler_list1 ;

exception_handler_list1 : exception_handler
                        | exception_handler_list1 exception_handler ;

exit_statement : EXIT name_option when_option SEMICOLON ;

name_option : | name ;

when_option : | WHEN condition ;

return_statement : RETURN SEMICOLON | RETURN expression SEMICOLON ;

goto_statement : GOTO name SEMICOLON ;

subprogram_declaration : subprogram_specification SEMICOLON ;

subprogram_specification :
     PROCEDURE IDENTIFIER formal_part_option
   | FUNCTION  designator formal_part_option RETURN name ;

subprogram_specification_is :
     PROCEDURE IDENTIFIER IS
   | FUNCTION  designator formal_part_option RETURN name IS ;

designator : IDENTIFIER | operator_symbol ;

operator_symbol : STRING_LITERAL ;

formal_part : LEFT_PAREN parameter_specification_list RIGHT_PAREN ;

formal_part_option : | formal_part ;

parameter_specification_list :
    parameter_specification
  | parameter_specification_list SEMICOLON parameter_specification ;

parameter_specification :
    IDENTIFIER       COLON mode name initialization_option
  | identifier_list2 COLON mode name initialization_option ;

mode : | IN | OUT | IN OUT ;

subprogram_body : subprogram_specification_is
                      declarative_part
                  BEGIN
                      sequence_of_statements
                  exception_option
                  END designator_option SEMICOLON ;

designator_option : | designator ;

procedure_call_statement : name SEMICOLON ;

package_declaration : package_specification SEMICOLON ;

package_specification : PACKAGE IDENTIFIER IS
                            basic_declarative_item_list0
                        private_part_option
                        END identifier_option ;

private_part_option : | PRIVATE basic_declarative_item_list0 ;

identifier_option : | IDENTIFIER ;

package_body : PACKAGE BODY IDENTIFIER IS
                   declarative_part
                   statements_option
               END identifier_option SEMICOLON ;

statements_option : | BEGIN sequence_of_statements exception_option ;

private_type_definition : LIMITED PRIVATE | PRIVATE ;

use_clause : USE name_list SEMICOLON ;

name_list : name | name_list COMMA name ;

renaming_declaration : IDENTIFIER COLON name      RENAMES name SEMICOLON
                     | IDENTIFIER COLON EXCEPTION RENAMES name SEMICOLON
                     | PACKAGE IDENTIFIER         RENAMES name SEMICOLON
                     | subprogram_specification   RENAMES name SEMICOLON ;

task_declaration : task_specification SEMICOLON ;

task_specification : TASK IDENTIFIER      task_specifier
                   | TASK TYPE IDENTIFIER task_specifier ;

task_specifier :
               | IS
                     entry_declaration_list0
                     representation_clause_list0
                 END identifier_option SEMICOLON ;

representation_clause_list0 :
                          | representation_clause_list0 representation_clause ;

entry_declaration_list0 : | entry_declaration_list0 entry_declaration ;

task_body : TASK BODY IDENTIFIER IS
                declarative_part
            BEGIN
                sequence_of_statements
            exception_option
            END identifier_option SEMICOLON ;

entry_declaration : ENTRY IDENTIFIER formal_part_option SEMICOLON
                  | ENTRY IDENTIFIER LEFT_PAREN discrete_range RIGHT_PAREN
                                     formal_part_option SEMICOLON ;

/* identical syntax as procedure_call */
entry_call_statement : procedure_call_statement ;

accept_statement :
        ACCEPT IDENTIFIER formal_part_option SEMICOLON
      | ACCEPT IDENTIFIER LEFT_PAREN expression RIGHT_PAREN formal_part_option
        SEMICOLON
      | ACCEPT IDENTIFIER formal_part_option DO
           sequence_of_statements
        END identifier_option SEMICOLON
      | ACCEPT IDENTIFIER LEFT_PAREN expression RIGHT_PAREN formal_part_option
           DO
                sequence_of_statements
           END identifier_option SEMICOLON ;

delay_statement : DELAY simple_expression SEMICOLON ;

select_statement : selective_wait | conditional_entry_call | timed_entry_call ;

selective_wait : SELECT
                     condition_option
                         select_alternative
                 select_alternative_list0
                 else_option
                 END SELECT SEMICOLON ;

select_alternative_list0 : | select_alternative_list0
                             OR condition_option select_alternative ;

condition_option : | WHEN condition ARROW ;

select_alternative : accept_statement sequence_of_statements_option
                   | delay_statement sequence_of_statements_option
                   | TERMINATE SEMICOLON ;

sequence_of_statements_option : | sequence_of_statements ;

conditional_entry_call : SELECT
                             entry_call_statement sequence_of_statements_option
                         ELSE
                             sequence_of_statements
                         END SELECT SEMICOLON ;

timed_entry_call : SELECT
                       entry_call_statement sequence_of_statements_option
                   OR
                       delay_statement sequence_of_statements_option
                   END SELECT SEMICOLON ;

abort_statement : ABORT name_list SEMICOLON ;

compilation : compilation_list ;

compilation_list : pragma_list0 compilation_unit
                 | compilation_list pragma_list0 compilation_unit ;

pragma_list0 : | pragma_list0 pragma ;

compilation_unit : context_clause subprogram_declaration
                 | context_clause subprogram_body
                 | context_clause package_declaration
                 | context_clause package_body
                 | context_clause generic_declaration
                 | context_clause generic_instantiation
                 | context_clause subunit ;

context_clause : | context_clause with_clause use_clause_option ;

use_clause_option : | use_clause ;

with_clause : WITH name_list SEMICOLON ;

subunit : SEPARATE LEFT_PAREN name RIGHT_PAREN proper_body ;

body_stub : subprogram_specification_is SEPARATE SEMICOLON
          | PACKAGE BODY IDENTIFIER IS  SEPARATE SEMICOLON
          | TASK BODY IDENTIFIER IS     SEPARATE SEMICOLON ;

exception_declaration : IDENTIFIER       COLON EXCEPTION SEMICOLON
                      | identifier_list2 COLON EXCEPTION SEMICOLON ;

exception_handler : WHEN exception_choice_list ARROW sequence_of_statements ;

exception_choice_list : OTHERS
                      | exception_choice_list1 ;

exception_choice_list1 : name | exception_choice_list1 BAR name ;

raise_statement : RAISE name_option SEMICOLON ;

generic_declaration : generic_specification SEMICOLON ;

generic_specification : generic_formal_part subprogram_specification
                      | generic_formal_part package_specification ;

generic_formal_part : GENERIC
                    | generic_formal_part generic_parameter_declaration ;

/* generic_type_definition includes private_type_definition */
generic_parameter_declaration :
                  parameter_specification                    SEMICOLON
                | TYPE IDENTIFIER IS generic_type_definition SEMICOLON
                | WITH subprogram_specification              SEMICOLON
                | WITH subprogram_specification_is name      SEMICOLON
                | WITH subprogram_specification_is BOX       SEMICOLON ;

generic_type_definition : LEFT_PAREN BOX RIGHT_PAREN
                        | RANGE BOX
                        | DELTA BOX
                        | DIGITS BOX
                        | array_type_definition
                        | access_type_definition
                        | private_type_definition ;

generic_instantiation :
               PACKAGE   IDENTIFIER IS NEW name SEMICOLON
             | PROCEDURE IDENTIFIER IS NEW name SEMICOLON
             | FUNCTION  designator IS NEW name SEMICOLON ;

representation_clause : type_representation_clause | address_clause ;

type_representation_clause : length_clause
                           | enumeration_representation_clause
                           | record_representation_clause ;

length_clause : FOR attribute USE simple_expression SEMICOLON ;

enumeration_representation_clause : FOR IDENTIFIER USE aggregate SEMICOLON ;

record_representation_clause : FOR IDENTIFIER USE
                                 RECORD alignment_clause_option
                                     component_clause0
                                 END RECORD SEMICOLON ;

component_clause0 :
      | component_clause0 name AT simple_expression RANGE range SEMICOLON ;

alignment_clause_option : | AT MOD simple_expression SEMICOLON ;

address_clause : FOR IDENTIFIER USE AT simple_expression SEMICOLON ;

code_statement : name QUOTE aggregate SEMICOLON ;