1;; iso-10303-11:2004
2
3  0 ABS = ’abs’ .
4  1 ABSTRACT = ’abstract’ .
5  2 ACOS = ’acos’ .
6  3 AGGREGATE = ’aggregate’ .
7  4 ALIAS = ’alias’ .
8  5 AND = ’and’ .
9  6 ANDOR = ’andor’ .
10  7 ARRAY = ’array’ .
11  8 AS = ’as’ .
12  9 ASIN = ’asin’ .
13 10 ATAN = ’atan’ .
14 11 BAG = ’bag’ .
15 12 BASED_ON = ’based_on’ .
16 13 BEGIN = ’begin’ .
17 14 BINARY = ’binary’ .
18 15 BLENGTH = ’blength’ .
19 16 BOOLEAN = ’boolean’ .
20 17 BY = ’by’ .
21 18 CASE = ’case’ .
22 19 CONSTANT = ’constant’ .
23 20 CONST_E = ’const_e’ .
24 21 COS = ’cos’ .
25 22 DERIVE = ’derive’ .
26 23 DIV = ’div’ .
27 24 ELSE = ’else’ .
28 25 END = ’end’ .
29 26 END_ALIAS = ’end_alias’ .
30 27 END_CASE = ’end_case’ .
31 28 END_CONSTANT = ’end_constant’ .
32 29 END_ENTITY = ’end_entity’ .
33 30 END_FUNCTION = ’end_function’ .
34 31 END_IF = ’end_if’ .
35 32 END_LOCAL = ’end_local’ .
36 33 END_PROCEDURE = ’end_procedure’ .
37 34 END_REPEAT = ’end_repeat’ .
38 35 END_RULE = ’end_rule’ .
39 36 END_SCHEMA = ’end_schema’ .
40 37 END_SUBTYPE_CONSTRAINT = ’end_subtype_constraint’ .
41 38 END_TYPE = ’end_type’ .
42 39 ENTITY = ’entity’ .
43 40 ENUMERATION = ’enumeration’ .
44 41 ESCAPE = ’escape’ .
45 42 EXISTS = ’exists’ .
46 43 EXTENSIBLE = ’extensible’ .
47 44 EXP = ’exp’ .
48 45 FALSE = ’false’ .
49 46 FIXED = ’fixed’ .
50 47 FOR = ’for’ .
51 48 FORMAT = ’format’ .
52 49 FROM = ’from’ .
53 50 FUNCTION = ’function’ .
54 51 GENERIC = ’generic’ .
55 52 GENERIC_ENTITY = ’generic_entity’ .
56 53 HIBOUND = ’hibound’ .
57 54 HIINDEX = ’hiindex’ .
58 55 IF = ’if’ .
59 56 IN = ’in’ .
60 57 INSERT = ’insert’ .
61 58 INTEGER = ’integer’ .
62 59 INVERSE = ’inverse’ .
63 60 LENGTH = ’length’ .
64 61 LIKE = ’like’ .
65 62 LIST = ’list’ .
66 63 LOBOUND = ’lobound’ .
67 64 LOCAL = ’local’ .
68 65 LOG = ’log’ .
69 66 LOG10 = ’log10’ .
70 67 LOG2 = ’log2’ .
71 68 LOGICAL = ’logical’ .
72 69 LOINDEX = ’loindex’ .
73 70 MOD = ’mod’ .
74 71 NOT = ’not’ .
75 72 NUMBER = ’number’ .
76 73 NVL = ’nvl’ .
77 74 ODD = ’odd’ .
78 75 OF = ’of’ .
79 76 ONEOF = ’oneof’ .
80 77 OPTIONAL = ’optional’ .
81 78 OR = ’or’ .
82 79 OTHERWISE = ’otherwise’ .
83 80 PI = ’pi’ .
84 81 PROCEDURE = ’procedure’ .
85 82 QUERY = ’query’ .
86 83 REAL = ’real’ .
87 84 REFERENCE = ’reference’ .
88 85 REMOVE = ’remove’ .
89 86 RENAMED = ’renamed’ .
90 87 REPEAT = ’repeat’ .
91 88 RETURN = ’return’ .
92 89 ROLESOF = ’rolesof’ .
93 90 RULE = ’rule’ .
94 91 SCHEMA = ’schema’ .
95 92 SELECT = ’select’ .
96 93 SELF = ’self’ .
97 94 SET = ’set’ .
98 95 SIN = ’sin’ .
99 96 SIZEOF = ’sizeof’ .
100 97 SKIP = ’skip’ .
101 98 SQRT = ’sqrt’ .
102 99 STRING = ’string’ .
103100 SUBTYPE = ’subtype’ .
104101 SUBTYPE_CONSTRAINT = ’subtype_constraint’ .
105102 SUPERTYPE = ’supertype’ .
106103 TAN = ’tan’ .
107104 THEN = ’then’ .
108105 TO = ’to’ .
109106 TOTAL_OVER = ’total_over’ .
110107 TRUE = ’true’ .
111108 TYPE = ’type’ .
112109 TYPEOF = ’typeof’ .
113110 UNIQUE = ’unique’ .
114111 UNKNOWN = ’unknown’ .
115112 UNTIL = ’until’ .
116113 USE = ’use’ .
117114 USEDIN = ’usedin’ .
118115 VALUE = ’value’ .
119116 VALUE_IN = ’value_in’ .
120117 VALUE_UNIQUE = ’value_unique’ .
121118 VAR = ’var’ .
122119 WHERE = ’where’ .
123120 WHILE = ’while’ .
124121 WITH = ’with’ .
125122 XOR = ’xor’ .
126123 bit = ’0’ | ’1’ .
127124 digit = ’0’ | ’1’ | ’2’ | ’3’ | ’4’ | ’5’ | ’6’ | ’7’ | ’8’ | ’9’ .
128125 digits = digit { digit } .
129126 encoded_character = octet octet octet octet .
130127 hex_digit = digit | ’a’ | ’b’ | ’c’ | ’d’ | ’e’ | ’f’ .
131128 letter = ’a’ | ’b’ | ’c’ | ’d’ | ’e’ | ’f’ | ’g’ | ’h’ | ’i’ | ’j’ | ’k’ | ’l’ | ’m’ | ’n’ | ’o’ | ’p’ | ’q’ | ’r’ | ’s’ | ’t’ | ’u’ | ’v’ | ’w’ | ’x’ | ’y’ | ’z’ .
132129 lparen_then_not_lparen_star = ’(’ { ’(’ } not_lparen_star { not_lparen_star } .
133130 not_lparen_star = not_paren_star | ’)’ .
134131 not_paren_star = letter | digit | not_paren_star_special .
135132 not_paren_star_quote_special = ’!’ | ’"’ | ’#’ | ’$’ | ’%’ | ’&’ | ’+’ | ’,’ | ’-’ | ’.’ | ’/’ | ’:’ | ’;’ | ’<’ | ’=’ | ’>’ | ’?’ | ’@’ | ’[’ | ’\’ | ’]’ | ’^’ | ’_’ | ’‘’ | ’{’ | ’|’ | ’}’ | ’~’ .
136133 not_paren_star_special = not_paren_star_quote_special | ’’’’ .
137134 not_quote = not_paren_star_quote_special | letter | digit | ’(’ | ’)’ | ’*’ .
138135 not_rparen_star = not_paren_star | ’(’ .
139136 octet = hex_digit hex_digit .
140137 special = not_paren_star_quote_special | ’(’ | ’)’ | ’*’ | ’’’’ .
141138 not_rparen_star_then_rparen = not_rparen_star { not_rparen_star } ’)’ { ’)’ } .
142139 binary_literal = ’%’ bit { bit } .
143140 encoded_string_literal = ’"’ encoded_character { encoded_character } ’"’ .
144141 integer_literal = digits .
145142 real_literal = integer_literal | ( digits ’.’ [ digits ] [ ’e’ [ sign ] digits ] ) .
146143 simple_id = letter { letter | digit | ’_’ } .
147144 simple_string_literal = \q { ( \q \q ) | not_quote | \s | \x8 | \x9 | \xA | \xB | \xC | \xD } \q .
148145 embedded_remark = ’(*’ [ remark_tag ] { ( not_paren_star { not_paren_star } ) | lparen_then_not_lparen_star | ( ’*’ { ’*’ } ) | not_rparen_star_then_rparen | embedded_remark } ’*)’ .
149146 remark = embedded_remark | tail_remark .
150147 remark_tag = ’"’ remark_ref { ’.’ remark_ref } ’"’ .
151148 remark_ref = attribute_ref | constant_ref | entity_ref | enumeration_ref | function_ref | parameter_ref | procedure_ref | rule_label_ref | rule_ref | schema_ref | subtype_constraint_ref | type_label_ref | type_ref | variable_ref .
152149 tail_remark = ’--’ [ remark_tag ] { \a | \s | \x8 | \x9 | \xA | \xB | \xC | \xD } \n .
153150 attribute_ref = attribute_id .
154151 constant_ref = constant_id .
155152 entity_ref = entity_id .
156153 enumeration_ref = enumeration_id .
157154 function_ref = function_id .
158155 parameter_ref = parameter_id .
159156 procedure_ref = procedure_id .
160157 rule_label_ref = rule_label_id .
161158 rule_ref = rule_id .
162159 schema_ref = schema_id .
163160 subtype_constraint_ref = subtype_constraint_id .
164161 type_label_ref = type_label_id .
165162 type_ref = type_id .
166163 variable_ref = variable_id .
167164 abstract_entity_declaration = ABSTRACT .
168165 abstract_supertype = ABSTRACT SUPERTYPE ’;’ .
169166 abstract_supertype_declaration = ABSTRACT SUPERTYPE [ subtype_constraint ] .
170167 actual_parameter_list = ’(’ parameter { ’,’ parameter } ’)’ .
171168 add_like_op = ’+’ | ’-’ | OR | XOR .
172169 aggregate_initializer = ’[’ [ element { ’,’ element } ] ’]’ .
173170 aggregate_source = simple_expression .
174171 aggregate_type = AGGREGATE [ ’:’ type_label ] OF parameter_type .
175172 aggregation_types = array_type | bag_type | list_type | set_type .
176173 algorithm_head = { declaration } [ constant_decl ] [ local_decl ] .
177174 alias_stmt = ALIAS variable_id FOR general_ref { qualifier } ’;’ stmt { stmt } END_ALIAS ’;’ .
178175 array_type = ARRAY bound_spec OF [ OPTIONAL ] [ UNIQUE ] instantiable_type .
179176 assignment_stmt = general_ref { qualifier } ’:=’ expression ’;’ .
180177 attribute_decl = attribute_id | redeclared_attribute .
181178 attribute_id = simple_id .
182179 attribute_qualifier = ’.’ attribute_ref .
183180 bag_type = BAG [ bound_spec ] OF instantiable_type .
184181 binary_type = BINARY [ width_spec ] .
185182 boolean_type = BOOLEAN .
186183 bound_1 = numeric_expression .
187184 bound_2 = numeric_expression .
188185 bound_spec = ’[’ bound_1 ’:’ bound_2 ’]’ .
189186 built_in_constant = CONST_E | PI | SELF | ’?’ .
190187 built_in_function = ABS | ACOS | ASIN | ATAN | BLENGTH | COS | EXISTS | EXP | FORMAT | HIBOUND | HIINDEX | LENGTH | LOBOUND | LOINDEX | LOG | LOG2 | LOG10 | NVL | ODD | ROLESOF | SIN | SIZEOF | SQRT | TAN | TYPEOF | USEDIN | VALUE | VALUE_IN | VALUE_UNIQUE .
191188 built_in_procedure = INSERT | REMOVE .
192189 case_action = case_label { ’,’ case_label } ’:’ stmt .
193190 case_label = expression .
194191 case_stmt = CASE selector OF { case_action } [ OTHERWISE ’:’ stmt ] END_CASE ’;’ .
195192 compound_stmt = BEGIN stmt { stmt } END ’;’ .
196193 concrete_types = aggregation_types | simple_types | type_ref .
197194 constant_body = constant_id ’:’ instantiable_type ’:=’ expression ’;’ .
198195 constant_decl = CONSTANT constant_body { constant_body } END_CONSTANT ’;’ .
199196 constant_factor = built_in_constant | constant_ref .
200197 constant_id = simple_id .
201198 constructed_types = enumeration_type | select_type .
202199 declaration = entity_decl | function_decl | procedure_decl | subtype_constraint_decl | type_decl .
203200 derived_attr = attribute_decl ’:’ parameter_type ’:=’ expression ’;’ .
204201 derive_clause = DERIVE derived_attr { derived_attr } .
205202 domain_rule = [ rule_label_id ’:’ ] expression .
206203 element = expression [ ’:’ repetition ] .
207204 entity_body = { explicit_attr } [ derive_clause ] [ inverse_clause ] [ unique_clause ] [ where_clause ] .
208205 entity_constructor = entity_ref ’(’ [ expression { ’,’ expression } ] ’)’ .
209206 entity_decl = entity_head entity_body END_ENTITY ’;’ .
210207 entity_head = ENTITY entity_id subsuper ’;’ .
211208 entity_id = simple_id .
212209 enumeration_extension = BASED_ON type_ref [ WITH enumeration_items ] .
213210 enumeration_id = simple_id .
214211 enumeration_items = ’(’ enumeration_id { ’,’ enumeration_id } ’)’ .
215212 enumeration_reference = [ type_ref ’.’ ] enumeration_ref .
216213 enumeration_type = [ EXTENSIBLE ] ENUMERATION [ ( OF enumeration_items ) | enumeration_extension ] .
217214 escape_stmt = ESCAPE ’;’ .
218215 explicit_attr = attribute_decl { ’,’ attribute_decl } ’:’ [ OPTIONAL ] parameter_type ’;’ .
219216 expression = simple_expression [ rel_op_extended simple_expression ] .
220217 factor = simple_factor [ ’**’ simple_factor ] .
221218 formal_parameter = parameter_id { ’,’ parameter_id } ’:’ parameter_type .
222219 function_call = ( built_in_function | function_ref ) [ actual_parameter_list ] .
223220 function_decl = function_head algorithm_head stmt { stmt } END_FUNCTION ’;’ .
224221 function_head = FUNCTION function_id [ ’(’ formal_parameter { ’;’ formal_parameter } ’)’ ] ’:’ parameter_type ’;’ .
225222 function_id = simple_id .
226223 generalized_types = aggregate_type | general_aggregation_types | generic_entity_type | generic_type .
227224 general_aggregation_types = general_array_type | general_bag_type | general_list_type | general_set_type .
228225 general_array_type = ARRAY [ bound_spec ] OF [ OPTIONAL ] [ UNIQUE ] parameter_type .
229226 general_bag_type = BAG [ bound_spec ] OF parameter_type .
230227 general_list_type = LIST [ bound_spec ] OF [ UNIQUE ] parameter_type .
231228 general_ref = parameter_ref | variable_ref .
232229 general_set_type = SET [ bound_spec ] OF parameter_type .
233230 generic_entity_type = GENERIC_ENTITY [ ’:’ type_label ] .
234231 generic_type = GENERIC [ ’:’ type_label ] .
235232 group_qualifier = ’\’ entity_ref .
236233 if_stmt = IF logical_expression THEN stmt { stmt } [ ELSE stmt { stmt } ] END_IF ’;’ .
237234 increment = numeric_expression .
238235 increment_control = variable_id ’:=’ bound_1 TO bound_2 [ BY increment ] .
239236 index = numeric_expression .
240237 index_1 = index .
241238 index_2 = index .
242239 index_qualifier = ’[’ index_1 [ ’:’ index_2 ] ’]’ .
243240 instantiable_type = concrete_types | entity_ref .
244241 integer_type = INTEGER .
245242 interface_specification = reference_clause | use_clause .
246243 interval = ’{’ interval_low interval_op interval_item interval_op interval_high ’}’ .
247244 interval_high = simple_expression .
248245 interval_item = simple_expression .
249246 interval_low = simple_expression .
250247 interval_op = ’<’ | ’<=’ .
251248 inverse_attr = attribute_decl ’:’ [ ( SET | BAG ) [ bound_spec ] OF ] entity_ref FOR [ entity_ref ’.’ ] attribute_ref ’;’ .
252249 inverse_clause = INVERSE inverse_attr { inverse_attr } .
253250 list_type = LIST [ bound_spec ] OF [ UNIQUE ] instantiable_type .
254251 literal = binary_literal | logical_literal | real_literal | string_literal .
255252 local_decl = LOCAL local_variable { local_variable } END_LOCAL ’;’ .
256253 local_variable = variable_id { ’,’ variable_id } ’:’ parameter_type [ ’:=’ expression ] ’;’ .
257254 logical_expression = expression .
258255 logical_literal = FALSE | TRUE | UNKNOWN .
259256 logical_type = LOGICAL .
260257 multiplication_like_op = ’*’ | ’/’ | DIV | MOD | AND | ’||’ .
261258 named_types = entity_ref | type_ref .
262259 named_type_or_rename = named_types [ AS ( entity_id | type_id ) ] .
263260 null_stmt = ’;’ .
264261 number_type = NUMBER .
265262 numeric_expression = simple_expression .
266263 one_of = ONEOF ’(’ supertype_expression { ’,’ supertype_expression } ’)’ .
267264 parameter = expression .
268265 parameter_id = simple_id .
269266 parameter_type = generalized_types | named_types | simple_types .
270267 population = entity_ref .
271268 precision_spec = numeric_expression .
272269 primary = literal | ( qualifiable_factor { qualifier } ) .
273270 procedure_call_stmt = ( built_in_procedure | procedure_ref ) [ actual_parameter_list ] ’;’ .
274271 procedure_decl = procedure_head algorithm_head { stmt } END_PROCEDURE ’;’ .
275272 procedure_head = PROCEDURE procedure_id [ ’(’ [ VAR ] formal_parameter { ’;’ [ VAR ] formal_parameter } ’)’ ] ’;’ .
276273 procedure_id = simple_id .
277274 qualifiable_factor = attribute_ref | constant_factor | function_call | general_ref | population .
278275 qualified_attribute = SELF group_qualifier attribute_qualifier .
279276 qualifier = attribute_qualifier | group_qualifier | index_qualifier .
280277 query_expression = QUERY ’(’ variable_id ’<*’ aggregate_source ’|’ logical_expression ’)’ .
281278 real_type = REAL [ ’(’ precision_spec ’)’ ] .
282279 redeclared_attribute = qualified_attribute [ RENAMED attribute_id ] .
283280 referenced_attribute = attribute_ref | qualified_attribute .
284281 reference_clause = REFERENCE FROM schema_ref [ ’(’ resource_or_rename { ’,’ resource_or_rename } ’)’ ] ’;’ .
285282 rel_op = ’<’ | ’>’ | ’<=’ | ’>=’ | ’<>’ | ’=’ | ’:<>:’ | ’:=:’ .
286283 rel_op_extended = rel_op | IN | LIKE .
287284 rename_id = constant_id | entity_id | function_id | procedure_id | type_id .
288285 repeat_control = [ increment_control ] [ while_control ] [ until_control ] .
289286 repeat_stmt = REPEAT repeat_control ’;’ stmt { stmt } END_REPEAT ’;’ .
290287 repetition = numeric_expression .
291288 resource_or_rename = resource_ref [ AS rename_id ] .
292289 resource_ref = constant_ref | entity_ref | function_ref | procedure_ref | type_ref .
293290 return_stmt = RETURN [ ’(’ expression ’)’ ] ’;’ .
294291 rule_decl = rule_head algorithm_head { stmt } where_clause END_RULE ’;’ .
295292 rule_head = RULE rule_id FOR ’(’ entity_ref { ’,’ entity_ref } ’)’ ’;’ .
296293 rule_id = simple_id .
297294 rule_label_id = simple_id .
298295 schema_body = { interface_specification } [ constant_decl ] { declaration | rule_decl } .
299296 schema_decl = SCHEMA schema_id [ schema_version_id ] ’;’ schema_body END_SCHEMA ’;’ .
300297 schema_id = simple_id .
301298 schema_version_id = string_literal .
302299 selector = expression .
303300 select_extension = BASED_ON type_ref [ WITH select_list ] .
304301 select_list = ’(’ named_types { ’,’ named_types } ’)’ .
305302 select_type = [ EXTENSIBLE [ GENERIC_ENTITY ] ] SELECT [ select_list | select_extension ] .
306303 set_type = SET [ bound_spec ] OF instantiable_type .
307304 sign = ’+’ | ’-’ .
308305 simple_expression = term { add_like_op term } .
309306 simple_factor = aggregate_initializer | entity_constructor | enumeration_reference | interval | query_expression | ( [ unary_op ] ( ’(’ expression ’)’ | primary ) ) .
310307 simple_types = binary_type | boolean_type | integer_type | logical_type | number_type | real_type | string_type .
311308 skip_stmt = SKIP ’;’ .
312309 stmt = alias_stmt | assignment_stmt | case_stmt | compound_stmt | escape_stmt | if_stmt | null_stmt | procedure_call_stmt | repeat_stmt | return_stmt | skip_stmt .
313310 string_literal = simple_string_literal | encoded_string_literal .
314311 string_type = STRING [ width_spec ] .
315312 subsuper = [ supertype_constraint ] [ subtype_declaration ] .
316313 subtype_constraint = OF ’(’ supertype_expression ’)’ .
317314 subtype_constraint_body = [ abstract_supertype ] [ total_over ] [ supertype_expression ’;’ ] .
318315 subtype_constraint_decl = subtype_constraint_head subtype_constraint_body END_SUBTYPE_CONSTRAINT ’;’ .
319316 subtype_constraint_head = SUBTYPE_CONSTRAINT subtype_constraint_id FOR entity_ref ’;’ .
320317 subtype_constraint_id = simple_id .
321318 subtype_declaration = SUBTYPE OF ’(’ entity_ref { ’,’ entity_ref } ’)’ .
322319 supertype_constraint = abstract_entity_declaration | abstract_supertype_declaration | supertype_rule .
323320 supertype_expression = supertype_factor { ANDOR supertype_factor } .
324321 supertype_factor = supertype_term { AND supertype_term } .
325322 supertype_rule = SUPERTYPE subtype_constraint .
326323 supertype_term = entity_ref | one_of | ’(’ supertype_expression ’)’ .
327324 syntax = schema_decl { schema_decl } .
328325 term = factor { multiplication_like_op factor } .
329326 total_over = TOTAL_OVER ’(’ entity_ref { ’,’ entity_ref } ’)’ ’;’ .
330327 type_decl = TYPE type_id ’=’ underlying_type ’;’ [ where_clause ] END_TYPE ’;’ .
331328 type_id = simple_id .
332329 type_label = type_label_id | type_label_ref .
333330 type_label_id = simple_id .
334331 unary_op = ’+’ | ’-’ | NOT .
335332 underlying_type = concrete_types | constructed_types .
336333 unique_clause = UNIQUE unique_rule ’;’ { unique_rule ’;’ } .
337334 unique_rule = [ rule_label_id ’:’ ] referenced_attribute { ’,’ referenced_attribute } .
338335 until_control = UNTIL logical_expression .
339336 use_clause = USE FROM schema_ref [ ’(’ named_type_or_rename { ’,’ named_type_or_rename } ’)’ ] ’;’ .
340337 variable_id = simple_id .
341338 where_clause = WHERE domain_rule ’;’ { domain_rule ’;’ } .
342339 while_control = WHILE logical_expression .
343340 width = numeric_expression .
344341 width_spec = ’(’ width ’)’ [ FIXED ] .
345