1%{
2/*
3 * Copyright (c) 2010 Apple Inc. All rights reserved.
4 *
5 * @APPLE_LICENSE_HEADER_START@
6 *
7 * Redistribution and use in source and binary forms, with or without
8 * modification, are permitted provided that the following conditions
9 * are met:
10 *
11 * 1.  Redistributions of source code must retain the above copyright
12 *     notice, this list of conditions and the following disclaimer.
13 * 2.  Redistributions in binary form must reproduce the above copyright
14 *     notice, this list of conditions and the following disclaimer in the
15 *     documentation and/or other materials provided with the distribution.
16 * 3.  Neither the name of Apple Inc. ("Apple") nor the names of its
17 *     contributors may be used to endorse or promote products derived from
18 *     this software without specific prior written permission.
19 *
20 * THIS SOFTWARE IS PROVIDED BY APPLE AND ITS CONTRIBUTORS "AS IS" AND ANY
21 * EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
22 * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
23 * DISCLAIMED. IN NO EVENT SHALL APPLE OR ITS CONTRIBUTORS BE LIABLE FOR ANY
24 * DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
25 * (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
26 * LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND
27 * ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
28 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
29 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
30 *
31 * Portions of this software have been released under the following terms:
32 *
33 * (c) Copyright 1989-1993 OPEN SOFTWARE FOUNDATION, INC.
34 * (c) Copyright 1989-1993 HEWLETT-PACKARD COMPANY
35 * (c) Copyright 1989-1993 DIGITAL EQUIPMENT CORPORATION
36 *
37 * To anyone who acknowledges that this file is provided "AS IS"
38 * without any express or implied warranty:
39 * permission to use, copy, modify, and distribute this file for any
40 * purpose is hereby granted without fee, provided that the above
41 * copyright notices and this notice appears in all source code copies,
42 * and that none of the names of Open Software Foundation, Inc., Hewlett-
43 * Packard Company or Digital Equipment Corporation be used
44 * in advertising or publicity pertaining to distribution of the software
45 * without specific, written prior permission.  Neither Open Software
46 * Foundation, Inc., Hewlett-Packard Company nor Digital
47 * Equipment Corporation makes any representations about the suitability
48 * of this software for any purpose.
49 *
50 * Copyright (c) 2007, Novell, Inc. All rights reserved.
51 * Redistribution and use in source and binary forms, with or without
52 * modification, are permitted provided that the following conditions
53 * are met:
54 *
55 * 1.  Redistributions of source code must retain the above copyright
56 *     notice, this list of conditions and the following disclaimer.
57 * 2.  Redistributions in binary form must reproduce the above copyright
58 *     notice, this list of conditions and the following disclaimer in the
59 *     documentation and/or other materials provided with the distribution.
60 * 3.  Neither the name of Novell Inc. nor the names of its contributors
61 *     may be used to endorse or promote products derived from this
62 *     this software without specific prior written permission.
63 *
64 * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY
65 * EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
66 * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
67 * DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDERS OR CONTRIBUTORS BE LIABLE FOR ANY
68 * DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
69 * (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
70 * LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND
71 * ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
72 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
73 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
74 *
75 * @APPLE_LICENSE_HEADER_END@
76 */
77
78/*
79**
80**  NAME:
81**
82**      IDL.Y
83**
84**  FACILITY:
85**
86**      Interface Definition Language (IDL) Compiler
87**
88**  ABSTRACT:
89**
90**      This module defines the main IDL grammar accepted
91**      by the IDL compiler.
92**
93**  VERSION: DCE 1.0
94**
95*/
96
97#include <sys/types.h>
98
99#include <nidl.h>
100#include <nametbl.h>
101#include <errors.h>
102#include <ast.h>
103#include <astp.h>
104#include <frontend.h>
105
106#define YYDEBUG 1
107
108extern boolean search_attributes_table ;
109
110/*
111**  Local cells used for inter-production communication
112*/
113static ASTP_attr_k_t       ASTP_bound_type;    /* Array bound attribute */
114
115/* An opaque pointer. */
116#ifndef YY_TYPEDEF_YY_SCANNER_T
117#define YY_TYPEDEF_YY_SCANNER_T
118typedef void* yyscan_t;
119#endif
120
121typedef struct nidl_parser_state_t
122{
123   yyscan_t     nidl_yyscanner;
124   unsigned     nidl_yynerrs;
125   parser_location_t nidl_location;
126} nidl_parser_state_t;
127
128static void nidl_yyerror (YYLTYPE *, nidl_parser_p, char const *);
129
130%}
131
132%locations
133%defines
134%error-verbose
135%pure-parser
136%name-prefix="nidl_yy"
137
138/* Tell Bison that the Flexer takes a yyscan_t parameter. */
139%lex-param { void * lexxer }
140/* Tell Bison that we will pass the yyscan_t scanner into yyparse. */
141%parse-param { nidl_parser_state_t * nidl }
142
143/* Tell Bison how to get the lexxer argument from the parser state. */
144%{
145#define lexxer nidl->nidl_yyscanner
146%}
147
148        /*   Declaration of yylval, yyval                   */
149%union
150{
151	 NAMETABLE_id_t         y_id ;          /* Identifier           */
152	 long                   y_ptrlevels;	/* levels of * for pointers */
153	 long					y_ptrclass;		/* class of pointer */
154	 STRTAB_str_t           y_string ;      /* String               */
155	 STRTAB_str_t           y_float ;       /* Float constant       */
156	 AST_export_n_t*        y_export ;      /* an export node       */
157	 AST_import_n_t*        y_import ;      /* Import node          */
158	 AST_exception_n_t*     y_exception ;   /* Exception node       */
159	 AST_constant_n_t*      y_constant;     /* Constant node        */
160	 AST_parameter_n_t*     y_parameter ;   /* Parameter node       */
161	 AST_type_n_t*          y_type ;        /* Type node            */
162	 AST_type_p_n_t*        y_type_ptr ;    /* Type pointer node    */
163	 AST_field_n_t*         y_field ;       /* Field node           */
164	 AST_arm_n_t*           y_arm ;         /* Union variant arm    */
165	 AST_operation_n_t*     y_operation ;   /* Routine node         */
166	 AST_interface_n_t*     y_interface ;   /* Interface node       */
167	 AST_case_label_n_t*    y_label ;       /* Union tags           */
168	 ASTP_declarator_n_t*   y_declarator ;  /* Declarator info      */
169	 ASTP_array_index_n_t*  y_index ;       /* Array index info     */
170	 nidl_uuid_t            y_uuid ;        /* Universal UID        */
171	 char                   y_char;         /* character constant   */
172	 ASTP_attributes_t      y_attributes;   /* attributes flags     */
173
174     	 AST_cpp_quote_n_t*     y_cpp_quote;    /* Quoted C within interface treated as one 'kind' of export node + quote outside interfaces */
175
176	 struct {
177		  long            int_val ;        /* Integer constant     */
178		  AST_type_k_t    int_size;
179		  int             int_signed;
180	 }                  y_int_info;     /* int size and signedness */
181	 AST_exp_n_t           * y_exp;          /* constant expression info */
182}
183
184%{
185#include <nidl_l.h>
186%}
187
188/********************************************************************/
189/*                                                                  */
190/*          Tokens used by the IDL parser.                          */
191/*                                                                  */
192/********************************************************************/
193
194/* Keywords                 */
195%token ALIGN_KW
196%token BYTE_KW
197%token CHAR_KW
198%token CONST_KW
199%token DEFAULT_KW
200%token ENUM_KW
201%token EXCEPTIONS_KW
202%token FLOAT_KW
203%token HYPER_KW
204%token INT_KW
205%token INTERFACE_KW
206%token IMPORT_KW
207%token LIBRARY_KW
208%token LONG_KW
209%token PIPE_KW
210%token REF_KW
211%token SMALL_KW
212%token STRUCT_KW
213%token TYPEDEF_KW
214%token UNION_KW
215%token UNSIGNED_KW
216%token SHORT_KW
217%token VOID_KW
218%token DOUBLE_KW
219%token BOOLEAN_KW
220%token CASE_KW
221%token SWITCH_KW
222%token HANDLE_T_KW
223%token TRUE_KW
224%token FALSE_KW
225%token NULL_KW
226%token BROADCAST_KW
227%token COMM_STATUS_KW
228%token CONTEXT_HANDLE_KW
229%token FIRST_IS_KW
230%token HANDLE_KW
231%token IDEMPOTENT_KW
232%token IGNORE_KW
233%token CALL_AS_KW
234%token IID_IS_KW
235%token IMPLICIT_HANDLE_KW
236%token IN_KW
237%token LAST_IS_KW
238%token LENGTH_IS_KW
239%token LOCAL_KW
240%token MAX_IS_KW
241%token MAYBE_KW
242%token MIN_IS_KW
243%token MUTABLE_KW
244%token OUT_KW
245%token OBJECT_KW
246%token POINTER_DEFAULT_KW
247%token ENDPOINT_KW
248%token PTR_KW
249%token RANGE_KW
250%token REFLECT_DELETIONS_KW
251%token REMOTE_KW
252%token SECURE_KW
253%token SHAPE_KW
254%token SIZE_IS_KW
255%token STRING_KW
256%token SWITCH_IS_KW
257%token SWITCH_TYPE_KW
258%token TRANSMIT_AS_KW
259%token UNIQUE_KW
260%token UUID_KW
261%token VERSION_KW
262%token V1_ARRAY_KW
263%token V1_STRING_KW
264%token V1_ENUM_KW
265%token V1_STRUCT_KW
266
267/* Added by Centeris */
268
269%token CPP_QUOTE_KW
270
271/*  Non-keyword tokens      */
272
273%token UUID_REP
274
275/*  Punctuation             */
276
277%token COLON
278%token COMMA
279%token DOTDOT
280%token EQUAL
281%token LBRACE
282%token LBRACKET
283%token LPAREN
284%token RBRACE
285%token RBRACKET
286%token RPAREN
287%token SEMI
288%token STAR
289%token QUESTION
290%token BAR
291%token BARBAR
292%token LANGLE
293%token LANGLEANGLE
294%token RANGLE
295%token RANGLEANGLE
296%token AMP
297%token AMPAMP
298%token LESSEQUAL
299%token GREATEREQUAL
300%token EQUALEQUAL
301%token CARET
302%token PLUS
303%token MINUS
304%token NOT
305%token NOTEQUAL
306%token SLASH
307%token PERCENT
308%token TILDE
309%token POUND
310%token UNKNOWN  /* Something that doesn't fit in any other token class */
311
312/*  Tokens setting yylval   */
313
314%token <y_id>      		IDENTIFIER
315%token <y_string>  		STRING
316%token <y_int_info>		INTEGER_NUMERIC
317%token <y_char>			CHAR
318%token <y_float>		FLOAT_NUMERIC
319%start grammar_start
320
321%%
322
323/********************************************************************/
324/*                                                                  */
325/*          Syntax description and actions for IDL                  */
326/*                                                                  */
327/********************************************************************/
328
329grammar_start:     	interfaces cpp_quotes
330			{
331				global_cppquotes_post = (AST_cpp_quote_n_t*)AST_concat_element(
332					(ASTP_node_t*)global_cppquotes_post, (ASTP_node_t*)$<y_cpp_quote>2);
333			}
334			|
335			optional_imports_cppquotes
336			|
337        		{
338            			$<y_import>$ = (AST_import_n_t *)NULL;
339		        }
340
341			/*{
342#if 0
343	 			global_imports = (AST_import_n_t*)AST_concat_element(
344	 				 (ASTP_node_t*)global_imports, (ASTP_node_t*)$<y_import>1);
345#endif
346				global_cppquotes_post = (AST_cpp_quote_n_t*)AST_concat_element(
347					(ASTP_node_t*)global_cppquotes_post, (ASTP_node_t*)$<y_cpp_quote>2);
348			}*/
349		;
350
351interfaces:
352	interfaces interface_plus
353	|
354	interface_plus
355	;
356
357/*Centeris wfu*/
358cpp_quotes:
359	cpp_quote cpp_quotes
360	{
361		$<y_cpp_quote>$ = (AST_cpp_quote_n_t *) AST_concat_element(
362                                                (ASTP_node_t *) $<y_cpp_quote>1,
363                                                (ASTP_node_t *) $<y_cpp_quote>2);
364        }
365	| /*Nothing*/
366	{	$<y_cpp_quote>$ = (AST_cpp_quote_n_t *)NULL;
367	}
368	;
369
370interface_plus:
371	cpp_quotes interface
372	{
373		global_cppquotes = (AST_cpp_quote_n_t*)AST_concat_element(
374			(ASTP_node_t*)global_cppquotes, (ASTP_node_t*)$<y_cpp_quote>1);
375	}
376	;
377
378interface:
379        interface_init interface_start interface_ancestor interface_tail
380        {
381            AST_finish_interface_node(nidl_location(nidl), the_interface);
382        }
383	;
384
385interface_start:
386        interface_attributes INTERFACE_KW IDENTIFIER
387        {
388	    AST_type_n_t * interface_type =
389          AST_type_node(nidl_location(nidl), AST_interface_k);
390	    interface_type->type_structure.interface = the_interface;
391	    interface_type->name = $<y_id>3;
392            the_interface->name = $<y_id>3;
393            ASTP_add_name_binding (nidl_location(nidl), the_interface->name, interface_type);
394        }
395    ;
396
397interface_ancestor:
398	/* Nothing */
399	{
400		 the_interface->inherited_interface_name = NAMETABLE_NIL_ID;
401	}
402	 | COLON IDENTIFIER
403	{
404		 the_interface->inherited_interface_name = $<y_id>2;
405	}
406	;
407
408interface_init:
409        /* Always create the interface node and auto-import the system idl */
410        {
411            STRTAB_str_t nidl_idl_str;
412            nidl_idl_str = STRTAB_add_string (AUTO_IMPORT_FILE);
413            AST_interface_n_t* old = the_interface;
414
415	         the_interface = AST_interface_node(nidl_location(nidl));
416            the_interface->prev = old;
417	         the_interface->exports = NULL;
418            the_interface->imports =
419               AST_import_node(nidl_location(nidl), nidl_idl_str);
420            the_interface->imports->interface = FE_parse_import (nidl_idl_str);
421            if (the_interface->imports->interface != NULL)
422            {
423                AST_CLR_OUT_OF_LINE(the_interface->imports->interface);
424                AST_SET_IN_LINE(the_interface->imports->interface);
425            }
426        }
427    ;
428
429interface_tail:
430        LBRACE interface_body RBRACE
431        { $<y_interface>$ = $<y_interface>2; }
432    |   error
433        {
434            $<y_interface>$ = NULL;
435            log_error(nidl_yylineno(nidl),NIDL_MISSONINTER, NULL);
436        }
437    |   error RBRACE
438        {
439            $<y_interface>$ = NULL;
440        }
441    ;
442
443interface_body:
444        optional_imports exports extraneous_semi
445        {
446            /* May already be an import of nbase, so concat */
447            the_interface->imports = (AST_import_n_t *) AST_concat_element(
448                                        (ASTP_node_t *) the_interface->imports,
449                                        (ASTP_node_t *) $<y_import>1);
450            the_interface->exports = (AST_export_n_t*)AST_concat_element(
451			(ASTP_node_t*)the_interface->exports,
452			(ASTP_node_t*)$<y_export>2);
453        }
454  ;
455
456optional_imports:
457        imports
458    |   /* Nothing */
459        {
460            $<y_import>$ = (AST_import_n_t *)NULL;
461        }
462    ;
463
464optional_imports_cppquotes:
465        imports cpp_quotes
466	{
467#if 0
468	 			global_imports = (AST_import_n_t*)AST_concat_element(
469	 				 (ASTP_node_t*)global_imports, (ASTP_node_t*)$<y_import>1);
470#endif
471
472				global_cppquotes_post = (AST_cpp_quote_n_t*)AST_concat_element(
473					(ASTP_node_t*)global_cppquotes_post, (ASTP_node_t*)$<y_cpp_quote>2);
474	}
475
476    ;
477
478imports:
479        import
480    |   imports import
481        {
482                $<y_import>$ = (AST_import_n_t *) AST_concat_element(
483                                                (ASTP_node_t *) $<y_import>1,
484                                                (ASTP_node_t *) $<y_import>2);
485        }
486    ;
487
488import:
489        IMPORT_KW error
490        {
491            $<y_import>$ = (AST_import_n_t *)NULL;
492        }
493    |   IMPORT_KW error SEMI
494        {
495            $<y_import>$ = (AST_import_n_t *)NULL;
496        }
497    |   IMPORT_KW import_files SEMI
498        {
499            $<y_import>$ = $<y_import>2;
500        }
501    ;
502
503import_files:
504        import_file
505    |   import_files COMMA import_file
506        {
507                $<y_import>$ = (AST_import_n_t *) AST_concat_element(
508                                                (ASTP_node_t *) $<y_import>1,
509                                                (ASTP_node_t *) $<y_import>3);
510        }
511    ;
512
513import_file:
514        STRING
515        {
516            AST_interface_n_t  *int_p;
517            int_p = FE_parse_import ($<y_string>1);
518            if (int_p != (AST_interface_n_t *)NULL)
519            {
520                $<y_import>$ = AST_import_node(nidl_location(nidl), $<y_string>1);
521                $<y_import>$->interface = int_p;
522            }
523            else
524                $<y_import>$ = (AST_import_n_t *)NULL;
525        }
526    ;
527
528exports:
529        export
530    |   exports extraneous_semi export
531        {
532                $<y_export>$ = (AST_export_n_t *) AST_concat_element(
533                                            (ASTP_node_t *) $<y_export>1,
534                                            (ASTP_node_t *) $<y_export>3) ;
535        }
536    ;
537
538export:
539        type_dcl      SEMI
540        {
541                $<y_export>$ = AST_types_to_exports (nidl_location(nidl),
542                                             $<y_type_ptr>1);
543        }
544    |   const_dcl     SEMI
545        {
546                $<y_export>$ = AST_export_node (
547                        nidl_location(nidl),
548                        (ASTP_node_t *) $<y_constant>1, AST_constant_k);
549        }
550    |   operation_dcl SEMI
551        {
552            if (ASTP_parsing_main_idl)
553                $<y_export>$ = AST_export_node (
554                        nidl_location(nidl),
555                        (ASTP_node_t *) $<y_operation>1, AST_operation_k);
556        }
557    |   cpp_quote
558        {
559            $<y_export>$ = AST_export_node (
560                     nidl_location(nidl),
561                (ASTP_node_t *) $<y_cpp_quote>1, AST_cpp_quote_k);
562        }
563    |   error SEMI
564        {
565            $<y_export>$ = (AST_export_n_t *)NULL;
566        }
567    ;
568
569cpp_quote:
570        CPP_QUOTE_KW LPAREN STRING RPAREN
571        {
572            $<y_cpp_quote>$ =
573               AST_cpp_quote_node(nidl_location(nidl), $<y_string>3);
574
575        }
576	;
577
578const_dcl:
579        CONST_KW type_spec declarator EQUAL const_exp
580
581        {
582           $<y_constant>$ = AST_finish_constant_node (nidl_location(nidl),
583                     $<y_constant>5, $<y_declarator>3, $<y_type>2);
584        }
585    ;
586
587const_exp:  expression
588        {
589				$<y_constant>$ = AST_constant_from_exp(nidl_location(nidl),
590                                    $<y_exp>1);
591				if ($<y_constant>$ == NULL)	{
592					 log_error(nidl_yylineno(nidl), NIDL_EXPNOTCONST, NULL);
593				}
594        }
595    ;
596
597type_dcl:
598        TYPEDEF_KW type_declarator
599        {
600            $<y_type_ptr>$ = $<y_type_ptr>2;
601        }
602    ;
603
604type_declarator:
605        attributes type_spec declarators extraneous_comma
606        {
607            $<y_type_ptr>$  = AST_declarators_to_types(nidl_location(nidl),
608                  the_interface, $<y_type>2, $<y_declarator>3, &$<y_attributes>1) ;
609            ASTP_free_simple_list((ASTP_node_t *)$<y_attributes>1.bounds);
610        }
611    ;
612
613type_spec:
614        simple_type_spec
615    |   constructed_type_spec
616    ;
617
618simple_type_spec:
619        floating_point_type_spec
620    |   integer_type_spec
621    |   char_type_spec
622    |   boolean_type_spec
623    |   byte_type_spec
624    |   void_type_spec
625    |   named_type_spec
626    |   handle_type_spec
627    ;
628
629constructed_type_spec:
630        struct_type_spec
631    |   union_type_spec
632    |   enum_type_spec
633    |   pipe_type_spec
634    ;
635
636named_type_spec:
637        IDENTIFIER
638        {
639            $<y_type>$ = AST_lookup_named_type(nidl_location(nidl), $<y_id>1);
640        }
641    ;
642
643floating_point_type_spec:
644        FLOAT_KW
645        {
646            $<y_type>$ = AST_lookup_type_node(AST_short_float_k);
647        }
648    |   DOUBLE_KW
649        {
650            $<y_type>$ = AST_lookup_type_node(AST_long_float_k);
651        }
652    ;
653
654extraneous_comma:
655        /* Nothing */
656    |   COMMA
657        { log_warning(nidl_yylineno(nidl), NIDL_EXTRAPUNCT, ",", NULL);}
658    ;
659
660extraneous_semi:
661        /* Nothing */
662    |   SEMI
663        { log_warning(nidl_yylineno(nidl), NIDL_EXTRAPUNCT, ";", NULL);}
664    ;
665
666optional_unsigned_kw:
667        UNSIGNED_KW     { $<y_int_info>$.int_signed = false; }
668    |   /* Nothing */   { $<y_int_info>$.int_signed = true; }
669    ;
670
671integer_size_spec:
672        SMALL_KW
673        {
674            $<y_int_info>$.int_size = AST_small_integer_k;
675            $<y_int_info>$.int_signed = true;
676        }
677    |   SHORT_KW
678        {
679            $<y_int_info>$.int_size = AST_short_integer_k;
680            $<y_int_info>$.int_signed = true;
681        }
682    |   LONG_KW
683        {
684            $<y_int_info>$.int_size = AST_long_integer_k;
685            $<y_int_info>$.int_signed = true;
686        }
687    |   HYPER_KW
688        {
689            $<y_int_info>$.int_size = AST_hyper_integer_k;
690            $<y_int_info>$.int_signed = true;
691        }
692    ;
693
694integer_modifiers:
695        integer_size_spec
696        { $<y_int_info>$ = $<y_int_info>1; }
697    |   UNSIGNED_KW integer_size_spec
698        {
699            $<y_int_info>$.int_size = $<y_int_info>2.int_size;
700            $<y_int_info>$.int_signed = false;
701        }
702    |   integer_size_spec UNSIGNED_KW
703        {
704            $<y_int_info>$.int_size = $<y_int_info>1.int_size;
705            $<y_int_info>$.int_signed = false;
706        }
707    ;
708
709integer_type_spec:
710        integer_modifiers
711        { $<y_type>$ = AST_lookup_integer_type_node($<y_int_info>1.int_size,$<y_int_info>1.int_signed); }
712    |   integer_modifiers INT_KW
713        { $<y_type>$ = AST_lookup_integer_type_node($<y_int_info>1.int_size,$<y_int_info>1.int_signed); }
714    |   optional_unsigned_kw INT_KW
715        {
716            log_warning(nidl_yylineno(nidl),NIDL_INTSIZEREQ, NULL);
717            $<y_type>$ = AST_lookup_integer_type_node(AST_long_integer_k,$<y_int_info>1.int_signed);
718        }
719    ;
720
721char_type_spec:
722        optional_unsigned_kw CHAR_KW
723        { $<y_type>$ = AST_lookup_type_node(AST_character_k); }
724    ;
725
726boolean_type_spec:
727        BOOLEAN_KW
728        { $<y_type>$ = AST_lookup_type_node(AST_boolean_k); }
729    ;
730
731byte_type_spec:
732        BYTE_KW
733        { $<y_type>$ = AST_lookup_type_node(AST_byte_k); }
734    ;
735
736void_type_spec:
737        VOID_KW
738        { $<y_type>$ = AST_lookup_type_node(AST_void_k); }
739    ;
740
741handle_type_spec:
742       HANDLE_T_KW
743        { $<y_type>$ = AST_lookup_type_node(AST_handle_k); }
744    ;
745
746push_name_space:
747        LBRACE
748        {
749            NAMETABLE_push_level ();
750        }
751    ;
752
753pop_name_space:
754        RBRACE
755        {
756            ASTP_patch_field_reference (nidl_location(nidl));
757            NAMETABLE_pop_level ();
758        }
759    ;
760
761union_type_spec:
762        UNION_KW ne_union_body
763        {
764        $<y_type>$ = AST_disc_union_node(
765                         nidl_location(nidl),
766                         NAMETABLE_NIL_ID,      /* tag name          */
767                         NAMETABLE_NIL_ID,      /* union name        */
768                         NAMETABLE_NIL_ID,      /* discriminant name */
769                         NULL,                  /* discriminant type */
770                         $<y_arm>2 );           /* the arm list      */
771        }
772    |
773        UNION_KW SWITCH_KW LPAREN simple_type_spec IDENTIFIER RPAREN union_body
774        {
775        $<y_type>$ = AST_disc_union_node(
776                         nidl_location(nidl),
777                         NAMETABLE_NIL_ID,      /* tag name          */
778                         ASTP_tagged_union_id,  /* union name        */
779                         $<y_id>5,              /* discriminant name */
780                         $<y_type>4,            /* discriminant type */
781                         $<y_arm>7 );           /* the arm list      */
782        }
783    |   UNION_KW IDENTIFIER ne_union_body
784        {
785        $<y_type>$ = AST_disc_union_node(
786                         nidl_location(nidl),
787                         $<y_id>2,              /* tag name          */
788                         NAMETABLE_NIL_ID,      /* union name        */
789                         NAMETABLE_NIL_ID,      /* discriminant name */
790                         NULL,                  /* discriminant type */
791                         $<y_arm>3 );           /* the arm list      */
792        }
793    |   UNION_KW SWITCH_KW LPAREN simple_type_spec IDENTIFIER RPAREN IDENTIFIER union_body
794        {
795        $<y_type>$ = AST_disc_union_node(
796                         nidl_location(nidl),
797                         NAMETABLE_NIL_ID,      /* tag name          */
798                         $<y_id>7,              /* union name        */
799                         $<y_id>5,              /* discriminant name */
800                         $<y_type>4,            /* discriminant type */
801                         $<y_arm>8 );           /* the arm list      */
802        }
803    |   UNION_KW IDENTIFIER SWITCH_KW LPAREN simple_type_spec IDENTIFIER RPAREN union_body
804        {
805        $<y_type>$ = AST_disc_union_node(
806                         nidl_location(nidl),
807                         $<y_id>2,              /* tag name          */
808                         ASTP_tagged_union_id,  /* union name        */
809                         $<y_id>6,              /* discriminant name */
810                         $<y_type>5,            /* discriminant type */
811                         $<y_arm>8 );           /* the arm list      */
812        }
813    |   UNION_KW IDENTIFIER SWITCH_KW LPAREN simple_type_spec IDENTIFIER RPAREN IDENTIFIER union_body
814        {
815        $<y_type>$ = AST_disc_union_node(
816                         nidl_location(nidl),
817                         $<y_id>2,              /* tag name          */
818                         $<y_id>8,              /* union name        */
819                         $<y_id>6,              /* discriminant name */
820                         $<y_type>5,            /* discriminant type */
821                         $<y_arm>9 );           /* the arm list      */
822        }
823    |   UNION_KW IDENTIFIER
824        {
825            $<y_type>$ = AST_type_from_tag (nidl_location(nidl),
826                              AST_disc_union_k, $<y_id>2);
827        }
828    ;
829
830ne_union_body:
831        push_name_space ne_union_cases pop_name_space
832        {
833                $<y_arm>$ = $<y_arm>2;
834        }
835    ;
836union_body:
837        push_name_space union_cases pop_name_space
838        {
839                $<y_arm>$ = $<y_arm>2;
840        }
841    ;
842
843ne_union_cases:
844        ne_union_case
845    |   ne_union_cases extraneous_semi ne_union_case
846        {
847            $<y_arm>$ = (AST_arm_n_t *) AST_concat_element(
848                                        (ASTP_node_t *) $<y_arm>1,
849                                        (ASTP_node_t *) $<y_arm>3);
850        }
851    ;
852union_cases:
853        union_case
854    |   union_cases extraneous_semi union_case
855        {
856            $<y_arm>$ = (AST_arm_n_t *) AST_concat_element(
857                                        (ASTP_node_t *) $<y_arm>1,
858                                        (ASTP_node_t *) $<y_arm>3);
859        }
860    ;
861
862ne_union_case:
863        ne_union_member
864        {
865            $<y_arm>$ = $<y_arm>1;
866        }
867    ;
868union_case:
869        union_case_list union_member
870        {
871            $<y_arm>$ = AST_label_arm($<y_arm>2, $<y_label>1) ;
872        }
873    ;
874
875ne_union_case_list:
876        ne_union_case_label
877    |   ne_union_case_list COMMA ne_union_case_label
878        {
879            $<y_label>$ = (AST_case_label_n_t *) AST_concat_element(
880                                        (ASTP_node_t *) $<y_label>1,
881                                        (ASTP_node_t *) $<y_label>3);
882        }
883    ;
884union_case_list:
885        union_case_label
886    |   union_case_list union_case_label
887        {
888            $<y_label>$ = (AST_case_label_n_t *) AST_concat_element(
889                                        (ASTP_node_t *) $<y_label>1,
890                                        (ASTP_node_t *) $<y_label>2);
891        }
892    ;
893
894ne_union_case_label:
895        const_exp
896        {
897            $<y_label>$ = AST_case_label_node(
898                              nidl_location(nidl), $<y_constant>1);
899        }
900    ;
901union_case_label:
902        CASE_KW const_exp COLON
903        {
904            $<y_label>$ = AST_case_label_node(
905                              nidl_location(nidl), $<y_constant>2);
906        }
907    |   DEFAULT_KW COLON
908        {
909            $<y_label>$ = AST_default_case_label_node(
910                              nidl_location(nidl));
911        }
912    ;
913
914ne_union_member:
915        attribute_opener rest_of_attribute_list SEMI
916        {
917            $<y_arm>$ = AST_declarator_to_arm(nidl_location(nidl),
918                  NULL, NULL, &$<y_attributes>2);
919            ASTP_free_simple_list((ASTP_node_t *)$<y_attributes>2.bounds);
920        }
921    |   attribute_opener rest_of_attribute_list type_spec declarator SEMI
922        {
923            $<y_arm>$ = AST_declarator_to_arm(nidl_location(nidl),
924                  $<y_type>3, $<y_declarator>4, &$<y_attributes>2);
925            ASTP_free_simple_list((ASTP_node_t *)$<y_attributes>2.bounds);
926        }
927    ;
928union_member:
929        /* nothing */ SEMI
930        {
931            $<y_arm>$ = AST_arm_node(nidl_location(nidl),
932                              NAMETABLE_NIL_ID,NULL,NULL);
933        }
934    |   attributes type_spec declarator SEMI
935        {
936            if (ASTP_TEST_ATTR(&$<y_attributes>1, ASTP_CASE))
937            {
938                ASTP_attr_flag_t attr1 = ASTP_CASE;
939                log_error(nidl_yylineno(nidl), NIDL_EUMEMATTR,
940                      KEYWORDS_lookup_text(AST_attribute_to_token(&attr1)),
941		      NULL);
942            }
943            if (ASTP_TEST_ATTR(&$<y_attributes>1, ASTP_DEFAULT))
944            {
945                ASTP_attr_flag_t attr1 = ASTP_DEFAULT;
946                log_error(nidl_yylineno(nidl), NIDL_EUMEMATTR,
947                      KEYWORDS_lookup_text(AST_attribute_to_token(&attr1)),
948		      NULL);
949            }
950            $<y_arm>$ = AST_declarator_to_arm(nidl_location(nidl),
951                  $<y_type>2, $<y_declarator>3, &$<y_attributes>1);
952            ASTP_free_simple_list((ASTP_node_t *)$<y_attributes>1.bounds);
953        }
954    ;
955
956struct_type_spec:
957        STRUCT_KW push_name_space member_list pop_name_space
958        {
959            $<y_type>$ = AST_structure_node(nidl_location(nidl),
960                           $<y_field>3, NAMETABLE_NIL_ID) ;
961        }
962    |   STRUCT_KW IDENTIFIER push_name_space member_list pop_name_space
963        {
964            $<y_type>$ = AST_structure_node(nidl_location(nidl),
965                           $<y_field>4, $<y_id>2) ;
966        }
967    |   STRUCT_KW IDENTIFIER
968        {
969            $<y_type>$ = AST_type_from_tag (nidl_location(nidl),
970                              AST_structure_k, $<y_id>2);
971        }
972    ;
973
974member_list:
975        member
976    |   member_list extraneous_semi member
977        {
978            $<y_field>$ = (AST_field_n_t *)AST_concat_element(
979                                    (ASTP_node_t *) $<y_field>1,
980                                    (ASTP_node_t *) $<y_field>3) ;
981        }
982    ;
983
984member:
985        attributes type_spec old_attribute_syntax declarators SEMI
986        {
987            $<y_field>$ = AST_declarators_to_fields(nidl_location(nidl),
988                                                    $<y_declarator>4,
989                                                    $<y_type>2,
990                                                    &$<y_attributes>1);
991            ASTP_free_simple_list((ASTP_node_t *)$<y_attributes>1.bounds);
992        }
993    ;
994
995enum_type_spec:
996        ENUM_KW optional_tag enum_body
997        {
998             $<y_type>$ = AST_enumerator_node(nidl_location(nidl),
999                              $<y_constant>3, AST_short_integer_k);
1000        }
1001    ;
1002
1003optional_tag:
1004	IDENTIFIER
1005		{
1006		}
1007	| /* Nothing */
1008	;
1009
1010enum_body:
1011        LBRACE enum_ids extraneous_comma RBRACE
1012        {
1013            $<y_constant>$ = $<y_constant>2 ;
1014        }
1015    ;
1016
1017enum_ids:
1018        enum_id
1019    |   enum_ids COMMA enum_id
1020        {
1021            $<y_constant>$ = (AST_constant_n_t *) AST_concat_element(
1022                                    (ASTP_node_t *) $<y_constant>1,
1023                                    (ASTP_node_t *) $<y_constant>3) ;
1024        }
1025    ;
1026
1027enum_id:
1028        IDENTIFIER optional_value
1029        {
1030            $<y_constant>$ = AST_enum_constant(nidl_location(nidl),
1031                              $<y_id>1, $<y_exp>2) ;
1032        }
1033    ;
1034
1035pipe_type_spec:
1036        PIPE_KW type_spec
1037        {
1038            $<y_type>$ = AST_pipe_node (nidl_location(nidl), $<y_type>2);
1039        }
1040    ;
1041
1042optional_value:
1043	/* Nothing */
1044		{
1045			 $<y_exp>$ = AST_exp_integer_constant(nidl_location(nidl),
1046                                 0, true);
1047		}
1048	| EQUAL expression
1049		{
1050          ASTP_validate_integer(nidl_location(nidl), $<y_exp>2);
1051			 $<y_exp>$ = $<y_exp>2;
1052		}
1053	;
1054
1055declarators:
1056        declarator
1057		  {
1058				$<y_declarator>$ =  $<y_declarator>1;
1059		  }
1060    |   declarators COMMA declarator
1061        {
1062            $<y_declarator>$ = (ASTP_declarator_n_t *) AST_concat_element(
1063                                            (ASTP_node_t *) $<y_declarator>1,
1064                                            (ASTP_node_t *) $<y_declarator>3) ;
1065        }
1066    ;
1067
1068declarator:
1069	declarator1
1070		{ $<y_declarator>$ = $<y_declarator>1; }
1071		;
1072
1073declarator1:
1074        direct_declarator
1075            { $<y_declarator>$ = $<y_declarator>1; }
1076       |    pointer direct_declarator
1077            {
1078                $<y_declarator>$ = $<y_declarator>2;
1079                AST_declarator_operation($<y_declarator>$, AST_pointer_k,
1080                        (ASTP_node_t *)NULL, $<y_ptrlevels>1 );
1081            };
1082
1083pointer :
1084            STAR
1085            { $<y_ptrlevels>$ = 1;}
1086       |    STAR pointer
1087            { $<y_ptrlevels>$ = $<y_ptrlevels>2 + 1; };
1088
1089direct_declarator:
1090            IDENTIFIER
1091            { $<y_declarator>$ = AST_declarator_node ( $<y_id>1 ); }
1092       |        direct_declarator array_bounds
1093            {
1094                $<y_declarator>$ = $<y_declarator>$;
1095                AST_declarator_operation($<y_declarator>$, AST_array_k,
1096                        (ASTP_node_t *) $<y_index>2, 0 );
1097            }
1098       |   LPAREN declarator RPAREN
1099            {
1100            $<y_declarator>$ = $<y_declarator>2;
1101            }
1102       |        direct_declarator parameter_dcls
1103            {
1104                $<y_declarator>$ = $<y_declarator>$;
1105                AST_declarator_operation($<y_declarator>$, AST_function_k,
1106                        (ASTP_node_t *) $<y_parameter>2, 0 );
1107            }
1108       ;
1109
1110    /*
1111     * The following productions use an AST routine with the signature:
1112     *
1113     *   ASTP_array_index_node( AST_constant_n_t * lower_bound,
1114     *                          ASTP_bound_t lower_bound_type,
1115     *                          AST_constant_n_t * upper_bound,
1116     *                          ASTP_bound_t upper_bound_type);
1117     *
1118     * The type ASTP_bound_t is defined as:
1119     *
1120     *   typedef enum {ASTP_constant_bound,
1121     *                 ASTP_default_bound,
1122     *                 ASTP_open_bound} ASTP_bound_t;
1123     *
1124     * The bound value passed is only used if the associated bound type is
1125     * ASTP_constant_bound.
1126     */
1127
1128array_bounds:
1129        LBRACKET RBRACKET
1130        {
1131            $<y_index>$ = ASTP_array_index_node (nidl_location(nidl),
1132                                                 NULL, ASTP_default_bound,
1133                                                 NULL, ASTP_open_bound);
1134        }
1135    |   LBRACKET STAR RBRACKET
1136        {
1137            $<y_index>$ = ASTP_array_index_node  (nidl_location(nidl),
1138                                                 NULL, ASTP_default_bound,
1139                                                 NULL, ASTP_open_bound);
1140        }
1141    |   LBRACKET const_exp RBRACKET
1142        {
1143            $<y_index>$ = ASTP_array_index_node  (nidl_location(nidl),
1144                                                 NULL, ASTP_default_bound,
1145                                                 $<y_constant>2, ASTP_constant_bound);
1146        }
1147    |   LBRACKET STAR DOTDOT STAR RBRACKET
1148        {
1149            $<y_index>$ = ASTP_array_index_node  (nidl_location(nidl),
1150                                                 NULL, ASTP_open_bound,
1151                                                 NULL, ASTP_open_bound);
1152        }
1153    |   LBRACKET STAR DOTDOT const_exp RBRACKET
1154        {
1155            $<y_index>$ = ASTP_array_index_node  (nidl_location(nidl),
1156                                                 NULL, ASTP_open_bound,
1157                                                 $<y_constant>4,
1158                                                 ASTP_constant_bound);
1159        }
1160    |   LBRACKET const_exp DOTDOT STAR RBRACKET
1161        {
1162            $<y_index>$ = ASTP_array_index_node  (nidl_location(nidl),
1163                                                 $<y_constant>2,
1164                                                 ASTP_constant_bound,
1165                                                 NULL, ASTP_open_bound);
1166        }
1167    |   LBRACKET const_exp DOTDOT const_exp RBRACKET
1168        {
1169            $<y_index>$ = ASTP_array_index_node  (nidl_location(nidl),
1170                                                 $<y_constant>2, ASTP_constant_bound,
1171                                                 $<y_constant>4, ASTP_constant_bound);
1172        }
1173    ;
1174
1175operation_dcl:
1176        attributes type_spec declarators extraneous_comma
1177        {
1178            if (ASTP_parsing_main_idl)
1179                $<y_operation>$ = AST_operation_node (
1180                                    nidl_location(nidl),
1181                                    $<y_type>2,         /*The type node*/
1182                                    $<y_declarator>3,   /* Declarator list */
1183                                   &$<y_attributes>1);  /* attributes */
1184            ASTP_free_simple_list((ASTP_node_t *)$<y_attributes>1.bounds);
1185        }
1186    | error declarators
1187        {
1188        log_error(nidl_yylineno(nidl),NIDL_MISSONOP, NULL);
1189        $<y_operation>$ = NULL;
1190        }
1191    ;
1192
1193parameter_dcls:
1194        param_names param_list extraneous_comma end_param_names
1195        {
1196            $<y_parameter>$ = $<y_parameter>2;
1197        }
1198    ;
1199
1200param_names:
1201        LPAREN
1202        {
1203        NAMETABLE_push_level ();
1204        }
1205    ;
1206
1207end_param_names:
1208        RPAREN
1209        {
1210        ASTP_patch_field_reference (nidl_location(nidl));
1211        NAMETABLE_pop_level ();
1212        }
1213    ;
1214
1215param_list:
1216        param_dcl
1217    |   param_list COMMA param_dcl
1218        {
1219            if (ASTP_parsing_main_idl)
1220                $<y_parameter>$ = (AST_parameter_n_t *) AST_concat_element(
1221                                    (ASTP_node_t *) $<y_parameter>1,
1222                                    (ASTP_node_t *) $<y_parameter>3);
1223        }
1224    |   /* nothing */
1225        {
1226            $<y_parameter>$ = (AST_parameter_n_t *)NULL;
1227        }
1228    ;
1229
1230param_dcl:
1231        attributes type_spec old_attribute_syntax declarator_or_null
1232        {
1233            /*
1234             * We have to use special code here to allow (void) as a parameter
1235             * specification.  If there are no declarators, then we need to
1236             * make sure that the type is void and that there are no attributes .
1237             */
1238            if ($<y_declarator>4 == NULL)
1239            {
1240                /*
1241                 * If the type is not void or some attribute is specified,
1242                 * there is a syntax error.  Force a yacc error, so that
1243                 * we can safely recover from the lack of a declarator.
1244                 */
1245                if (($<y_type>2->kind != AST_void_k) ||
1246                   ($<y_attributes>1.bounds != NULL) ||
1247                   ($<y_attributes>1.attr_flags != 0))
1248                {
1249                    yywhere(nidl_location(nidl));  /* Issue a syntax error for this line */
1250                    YYERROR;    /* Allow natural error recovery */
1251                }
1252
1253                $<y_parameter>$ = (AST_parameter_n_t *)NULL;
1254            }
1255            else
1256            {
1257                if (ASTP_parsing_main_idl)
1258                    $<y_parameter>$ = AST_declarator_to_param(
1259                                            nidl_location(nidl),
1260                                            &$<y_attributes>1,
1261                                            $<y_type>2,
1262                                            $<y_declarator>4);
1263            }
1264            ASTP_free_simple_list((ASTP_node_t *)$<y_attributes>1.bounds);
1265        }
1266    |    error old_attribute_syntax declarator_or_null
1267        {
1268            log_error(nidl_yylineno(nidl), NIDL_MISSONPARAM, NULL);
1269            $<y_parameter>$ = (AST_parameter_n_t *)NULL;
1270        }
1271    ;
1272
1273declarator_or_null:
1274        declarator
1275        { $<y_declarator>$ = $<y_declarator>1; }
1276    |   /* nothing */
1277        { $<y_declarator>$ = NULL; }
1278    ;
1279
1280/*
1281 * Attribute definitions
1282 *
1283 * Attributes may appear on types, fields, parameters, operations and
1284 * interfaces.  Thes productions must be used around attributes in order
1285 * for LEX to recognize attribute names as keywords instead of identifiers.
1286 * The bounds productions are used in attribute options (such
1287 * as size_is) because variable names the may look like attribute names
1288 * should be allowed.
1289 */
1290
1291attribute_opener:
1292        LBRACKET
1293        {
1294            search_attributes_table = true;
1295        }
1296    ;
1297
1298attribute_closer:
1299        RBRACKET
1300        {
1301            search_attributes_table = false;
1302        }
1303    ;
1304
1305bounds_opener:
1306        LPAREN
1307        {
1308            search_attributes_table = false;
1309        }
1310    ;
1311
1312bounds_closer:
1313        RPAREN
1314        {
1315            search_attributes_table = true;
1316        }
1317    ;
1318
1319/*
1320 * Production to accept attributes in the old location, and issue a clear error that
1321 * the translator should be used.
1322 */
1323old_attribute_syntax:
1324        attributes
1325        {
1326            /* Give an error on notranslated sources */
1327            if (($<y_attributes>1.bounds != NULL) ||
1328               ($<y_attributes>1.attr_flags != 0))
1329            {
1330                log_error(nidl_yylineno(nidl),NIDL_ATTRTRANS, NULL);
1331                ASTP_free_simple_list((ASTP_node_t *)$<y_attributes>1.bounds);
1332            }
1333        }
1334    ;
1335
1336/*
1337 * Interface Attributes
1338 *
1339 * Interface attributes are special--there is no cross between interface
1340 * attributes and other attributes (for instance on fields or types.
1341 */
1342interface_attributes:
1343        attribute_opener interface_attr_list extraneous_comma attribute_closer
1344    |   attribute_opener error attribute_closer
1345        {
1346            log_error(nidl_yylineno(nidl),NIDL_ERRINATTR, NULL);
1347        }
1348
1349    |   /* Nothing */
1350    ;
1351
1352interface_attr_list:
1353        interface_attr
1354    |   interface_attr_list COMMA interface_attr
1355    |   /* nothing */
1356    ;
1357
1358interface_attr:
1359        UUID_KW error
1360        {
1361            log_error(nidl_yylineno(nidl),NIDL_SYNTAXUUID, NULL);
1362        }
1363    |   UUID_KW UUID_REP
1364        {
1365            {
1366                if (ASTP_IF_AF_SET(the_interface,ASTP_IF_UUID))
1367                        log_error(nidl_yylineno(nidl), NIDL_ATTRUSEMULT, NULL);
1368                ASTP_SET_IF_AF(the_interface,ASTP_IF_UUID);
1369                the_interface->uuid = $<y_uuid>2;
1370            }
1371        }
1372    |   ENDPOINT_KW LPAREN port_list extraneous_comma RPAREN
1373        {
1374            if (ASTP_IF_AF_SET(the_interface,ASTP_IF_PORT))
1375                    log_error(nidl_yylineno(nidl), NIDL_ATTRUSEMULT, NULL);
1376            ASTP_SET_IF_AF(the_interface,ASTP_IF_PORT);
1377        }
1378    |   EXCEPTIONS_KW LPAREN excep_list extraneous_comma RPAREN
1379        {
1380            if (ASTP_IF_AF_SET(the_interface, ASTP_IF_EXCEPTIONS))
1381                log_error(nidl_yylineno(nidl), NIDL_ATTRUSEMULT, NULL);
1382            ASTP_SET_IF_AF(the_interface, ASTP_IF_EXCEPTIONS);
1383        }
1384    |   VERSION_KW LPAREN version_number RPAREN
1385        {
1386            {
1387                if (ASTP_IF_AF_SET(the_interface,ASTP_IF_VERSION))
1388                        log_error(nidl_yylineno(nidl), NIDL_ATTRUSEMULT, NULL);
1389                ASTP_SET_IF_AF(the_interface,ASTP_IF_VERSION);
1390            }
1391
1392        }
1393    |   LOCAL_KW
1394        {
1395            {
1396                if (AST_LOCAL_SET(the_interface))
1397                        log_warning(nidl_yylineno(nidl), NIDL_MULATTRDEF, NULL);
1398                AST_SET_LOCAL(the_interface);
1399            }
1400        }
1401    |   POINTER_DEFAULT_KW LPAREN pointer_class RPAREN
1402        {
1403            if (the_interface->pointer_default != 0)
1404                    log_error(nidl_yylineno(nidl), NIDL_ATTRUSEMULT, NULL);
1405            the_interface->pointer_default = $<y_ptrclass>3;
1406        }
1407	 /* extensions to osf */
1408	 |	  OBJECT_KW
1409	 		{
1410				if (AST_OBJECT_SET(the_interface))
1411					 log_warning(nidl_yylineno(nidl), NIDL_MULATTRDEF, NULL);
1412				AST_SET_OBJECT(the_interface);
1413			}
1414	 |		acf_interface_attr
1415	 		{
1416				/* complain about compat here */
1417			}
1418    ;
1419
1420acf_interface_attr:
1421	IMPLICIT_HANDLE_KW LPAREN HANDLE_T_KW IDENTIFIER RPAREN
1422	{
1423		if (the_interface->implicit_handle_name != NAMETABLE_NIL_ID)
1424			 log_error(nidl_yylineno(nidl), NIDL_ATTRUSEMULT, NULL);
1425
1426		ASTP_set_implicit_handle(the_interface, NAMETABLE_NIL_ID, $<y_id>4);
1427	}
1428	|
1429	IMPLICIT_HANDLE_KW LPAREN IDENTIFIER IDENTIFIER RPAREN
1430	{
1431		if (the_interface->implicit_handle_name != NAMETABLE_NIL_ID)
1432			log_error(nidl_yylineno(nidl), NIDL_ATTRUSEMULT, NULL);
1433
1434		ASTP_set_implicit_handle(the_interface, $<y_id>3, $<y_id>4);
1435	}
1436	;
1437
1438pointer_class:
1439        REF_KW { $<y_ptrclass>$ = ASTP_REF; }
1440    |   PTR_KW { $<y_ptrclass>$ = ASTP_PTR; }
1441    |   UNIQUE_KW { $<y_ptrclass>$ = ASTP_UNIQUE; }
1442    ;
1443
1444version_number:
1445        INTEGER_NUMERIC
1446        {
1447            the_interface->version = $<y_int_info>1.int_val;
1448            if (the_interface->version > /*(unsigned int)*/ASTP_C_USHORT_MAX)
1449                log_error(nidl_yylineno(nidl), NIDL_MAJORTOOLARGE,
1450			  ASTP_C_USHORT_MAX, NULL);
1451        }
1452   |    FLOAT_NUMERIC
1453        {
1454            char const *float_text;
1455            unsigned int            major_version,minor_version;
1456            STRTAB_str_to_string($<y_string>1, &float_text);
1457            sscanf(float_text,"%d.%d",&major_version,&minor_version);
1458            if (major_version > (unsigned int)ASTP_C_USHORT_MAX)
1459                log_error(nidl_yylineno(nidl), NIDL_MAJORTOOLARGE,
1460			  ASTP_C_USHORT_MAX, NULL);
1461            if (minor_version > (unsigned int)ASTP_C_USHORT_MAX)
1462                log_error(nidl_yylineno(nidl), NIDL_MINORTOOLARGE,
1463			  ASTP_C_USHORT_MAX, NULL);
1464            the_interface->version = (minor_version * 65536) + major_version;
1465        }
1466    ;
1467
1468port_list:
1469        port_spec
1470    |   port_list COMMA port_spec
1471    ;
1472
1473excep_list:
1474        excep_spec
1475        {
1476            the_interface->exceptions = $<y_exception>1;
1477        }
1478    |   excep_list COMMA excep_spec
1479        {
1480            $<y_exception>$ = (AST_exception_n_t *) AST_concat_element(
1481                                (ASTP_node_t *) the_interface->exceptions,
1482                                (ASTP_node_t *) $<y_exception>3 );
1483        }
1484    ;
1485
1486port_spec:
1487        STRING
1488        {
1489            ASTP_parse_port(the_interface,$<y_string>1);
1490        }
1491    ;
1492
1493excep_spec:
1494        IDENTIFIER
1495        {
1496            if (ASTP_parsing_main_idl)
1497            {
1498                $<y_exception>$ =
1499                   AST_exception_node(nidl_location(nidl), $<y_id>1);
1500            }
1501            else
1502            {
1503                $<y_exception>$ = NULL;
1504            }
1505        }
1506    ;
1507
1508/*
1509 * Attributes that can appear on fields or parameters. These are the array
1510 * bounds attributes, i.e., last_is and friends. They are handled differently
1511 * from any other attributes.
1512 */
1513fp_attribute:
1514        array_bound_type bounds_opener array_bound_id_list bounds_closer
1515        {
1516            $<y_attributes>$.bounds = $<y_attributes>3.bounds;
1517            $<y_attributes>$.attr_flags = 0;
1518        }
1519    |   neu_switch_type bounds_opener neu_switch_id bounds_closer
1520        {
1521            $<y_attributes>$.bounds = $<y_attributes>3.bounds;
1522            $<y_attributes>$.attr_flags = 0;
1523        }
1524    ;
1525
1526array_bound_type:
1527        FIRST_IS_KW
1528        {
1529            ASTP_bound_type = first_is_k;
1530        }
1531    |   LAST_IS_KW
1532        {
1533            ASTP_bound_type = last_is_k;
1534        }
1535    |   LENGTH_IS_KW
1536        {
1537            ASTP_bound_type = length_is_k;
1538        }
1539    |   MAX_IS_KW
1540        {
1541            ASTP_bound_type = max_is_k;
1542        }
1543    |   MIN_IS_KW
1544        {
1545            ASTP_bound_type = min_is_k;
1546        }
1547    |   SIZE_IS_KW
1548        {
1549            ASTP_bound_type = size_is_k;
1550        }
1551    ;
1552
1553array_bound_id_list:
1554        array_bound_id
1555    |   array_bound_id_list COMMA array_bound_id
1556        {
1557        $<y_attributes>$.bounds = (ASTP_type_attr_n_t *) AST_concat_element (
1558                                (ASTP_node_t*) $<y_attributes>1.bounds,
1559                                (ASTP_node_t*) $<y_attributes>3.bounds);
1560        }
1561    ;
1562
1563/* expression conflicts with identifier here */
1564array_bound_id:
1565	  expression
1566			{
1567				 $<y_attributes>$.bounds =
1568                AST_array_bound_from_expr(nidl_location(nidl),
1569                        $<y_exp>1, ASTP_bound_type);
1570			}
1571    |   /* nothing */
1572        {
1573        $<y_attributes>$.bounds = AST_array_bound_info (nidl_location(nidl),
1574                        NAMETABLE_NIL_ID, ASTP_bound_type, FALSE);
1575        }
1576    ;
1577
1578neu_switch_type:
1579        SWITCH_IS_KW
1580        {
1581            ASTP_bound_type = switch_is_k;
1582        }
1583    ;
1584
1585neu_switch_id:
1586        IDENTIFIER
1587        {
1588        $<y_attributes>$.bounds = AST_array_bound_info(nidl_location(nidl),
1589                        $<y_id>1, ASTP_bound_type, FALSE);
1590        }
1591    |   STAR IDENTIFIER
1592        {
1593        $<y_attributes>$.bounds = AST_array_bound_info(nidl_location(nidl),
1594                        $<y_id>2, ASTP_bound_type, TRUE);
1595        }
1596    ;
1597
1598/*
1599 * Generalized Attribute processing
1600 */
1601attributes:
1602        attribute_opener rest_of_attribute_list
1603        { $<y_attributes>$ = $<y_attributes>2; }
1604     |
1605        /* nothing */
1606        {
1607        $<y_attributes>$.bounds = NULL;
1608        $<y_attributes>$.attr_flags = 0;
1609        }
1610     ;
1611
1612rest_of_attribute_list:
1613        attribute_list extraneous_comma attribute_closer
1614     |  error attribute_closer
1615        {
1616        /*
1617         * Can't tell if we had any valid attributes in the list, so return
1618         * none.
1619         */
1620        $<y_attributes>$.bounds = NULL;
1621        $<y_attributes>$.attr_flags = 0;
1622        log_error(nidl_yylineno(nidl), NIDL_ERRINATTR, NULL);
1623        }
1624     |  error SEMI
1625        {
1626        /*
1627         * No closer to the attribute, so give a different message.
1628         */
1629        $<y_attributes>$.bounds = NULL;
1630        $<y_attributes>$.attr_flags = 0;
1631        log_error(nidl_yylineno(nidl), NIDL_MISSONATTR, NULL);
1632        search_attributes_table = false;
1633        }
1634     ;
1635
1636attribute_list:
1637        attribute
1638        { $<y_attributes>$ = $<y_attributes>1; }
1639     |
1640        attribute_list COMMA attribute
1641        {
1642          /*
1643           * If the same bit has been specified more than once, then issue
1644           * a message.
1645           */
1646          if (($<y_attributes>1.attr_flags & $<y_attributes>3.attr_flags) != 0)
1647                log_warning(nidl_yylineno(nidl), NIDL_MULATTRDEF, NULL);
1648          $<y_attributes>$.attr_flags = $<y_attributes>1.attr_flags |
1649                                        $<y_attributes>3.attr_flags;
1650          $<y_attributes>$.bounds = (ASTP_type_attr_n_t *) AST_concat_element (
1651                                (ASTP_node_t*) $<y_attributes>1.bounds,
1652                                (ASTP_node_t*) $<y_attributes>3.bounds);
1653        }
1654     ;
1655
1656attribute:
1657        /* bound attributes */
1658        fp_attribute            { $<y_attributes>$ = $<y_attributes>1; }
1659
1660        /* Operation Attributes */
1661    |   BROADCAST_KW            { $<y_attributes>$.attr_flags = ASTP_BROADCAST;
1662                                  $<y_attributes>$.bounds = NULL;       }
1663    |   MAYBE_KW                { $<y_attributes>$.attr_flags = ASTP_MAYBE;
1664                                  $<y_attributes>$.bounds = NULL;       }
1665    |   IDEMPOTENT_KW           { $<y_attributes>$.attr_flags = ASTP_IDEMPOTENT;
1666                                  $<y_attributes>$.bounds = NULL;       }
1667    |   REFLECT_DELETIONS_KW    { $<y_attributes>$.attr_flags = ASTP_REFLECT_DELETIONS;
1668                                  $<y_attributes>$.bounds = NULL;       }
1669	 |   LOCAL_KW                { $<y_attributes>$.attr_flags = ASTP_LOCAL;
1670	                               $<y_attributes>$.bounds = NULL;       }
1671	 |   CALL_AS_KW LPAREN IDENTIFIER RPAREN	{	}
1672
1673        /* Parameter-only Attributes */
1674    |   PTR_KW                  { $<y_attributes>$.attr_flags = ASTP_PTR;
1675                                  $<y_attributes>$.bounds = NULL;       }
1676    |   IN_KW                   { $<y_attributes>$.attr_flags = ASTP_IN;
1677                                  $<y_attributes>$.bounds = NULL;       }
1678    |   IN_KW LPAREN SHAPE_KW RPAREN
1679                                { $<y_attributes>$.attr_flags =
1680                                        ASTP_IN | ASTP_IN_SHAPE;
1681                                  $<y_attributes>$.bounds = NULL;       }
1682    |   OUT_KW                  { $<y_attributes>$.attr_flags = ASTP_OUT;
1683                                  $<y_attributes>$.bounds = NULL;       }
1684    |   OUT_KW LPAREN SHAPE_KW RPAREN
1685                                { $<y_attributes>$.attr_flags =
1686                                        ASTP_OUT | ASTP_OUT_SHAPE;
1687                                  $<y_attributes>$.bounds = NULL;       }
1688	 |	  IID_IS_KW LPAREN IDENTIFIER RPAREN
1689											{ $<y_attributes>$.iid_is_name = $<y_id>3;
1690                                   $<y_attributes>$.bounds = NULL;
1691                                   $<y_attributes>$.attr_flags = 0;
1692											}
1693	 |	  IID_IS_KW LPAREN STAR IDENTIFIER RPAREN /* MIDL extension */
1694											{ $<y_attributes>$.iid_is_name = $<y_id>4;
1695                                   $<y_attributes>$.bounds = NULL;
1696                                   $<y_attributes>$.attr_flags = 0;
1697											}
1698
1699        /* Type, Field, Parameter Attributes */
1700    |   V1_ARRAY_KW             { $<y_attributes>$.attr_flags = ASTP_SMALL;
1701                                  $<y_attributes>$.bounds = NULL;       }
1702    |   STRING_KW               { $<y_attributes>$.attr_flags = ASTP_STRING;
1703                                  $<y_attributes>$.bounds = NULL;       }
1704    |   V1_STRING_KW            { $<y_attributes>$.attr_flags = ASTP_STRING0;
1705                                  $<y_attributes>$.bounds = NULL;       }
1706    |   UNIQUE_KW               { $<y_attributes>$.attr_flags = ASTP_UNIQUE;
1707                                  $<y_attributes>$.bounds = NULL;       }
1708    |   REF_KW                  { $<y_attributes>$.attr_flags = ASTP_REF;
1709                                  $<y_attributes>$.bounds = NULL;       }
1710    |   IGNORE_KW               { $<y_attributes>$.attr_flags = ASTP_IGNORE;
1711                                  $<y_attributes>$.bounds = NULL;       }
1712    |   CONTEXT_HANDLE_KW       { $<y_attributes>$.attr_flags = ASTP_CONTEXT;
1713                                  $<y_attributes>$.bounds = NULL;       }
1714    |   RANGE_KW LPAREN expression COMMA expression RPAREN /* MIDL extension */
1715                                { $<y_attributes>$.attr_flags = ASTP_RANGE;
1716                                  $<y_attributes>$.bounds =
1717                                     AST_range_from_expr(nidl_location(nidl),
1718                                           $<y_exp>3, $<y_exp>5);
1719                                }
1720
1721        /* Type-only Attribute(s) */
1722    |   V1_STRUCT_KW            { $<y_attributes>$.attr_flags = ASTP_UNALIGN;
1723                                  $<y_attributes>$.bounds = NULL;       }
1724    |   V1_ENUM_KW              { $<y_attributes>$.attr_flags = ASTP_V1_ENUM;
1725                                  $<y_attributes>$.bounds = NULL;       }
1726    |   ALIGN_KW LPAREN SMALL_KW RPAREN
1727                                { $<y_attributes>$.attr_flags = ASTP_ALIGN_SMALL;
1728                                  $<y_attributes>$.bounds = NULL;       }
1729    |   ALIGN_KW LPAREN SHORT_KW RPAREN
1730                                { $<y_attributes>$.attr_flags = ASTP_ALIGN_SHORT;
1731                                  $<y_attributes>$.bounds = NULL;       }
1732    |   ALIGN_KW LPAREN LONG_KW RPAREN
1733                                { $<y_attributes>$.attr_flags = ASTP_ALIGN_LONG;
1734                                  $<y_attributes>$.bounds = NULL;       }
1735    |   ALIGN_KW LPAREN HYPER_KW RPAREN
1736                                { $<y_attributes>$.attr_flags = ASTP_ALIGN_HYPER;
1737                                  $<y_attributes>$.bounds = NULL;       }
1738    |   HANDLE_KW               { $<y_attributes>$.attr_flags = ASTP_HANDLE;
1739                                  $<y_attributes>$.bounds = NULL;       }
1740    |   TRANSMIT_AS_KW LPAREN simple_type_spec RPAREN
1741                                { $<y_attributes>$.attr_flags = ASTP_TRANSMIT_AS;
1742                                  $<y_attributes>$.bounds = NULL;
1743                                  ASTP_transmit_as_type = $<y_type>3;
1744                                }
1745    |   SWITCH_TYPE_KW LPAREN simple_type_spec RPAREN
1746                                { $<y_attributes>$.attr_flags = ASTP_SWITCH_TYPE;
1747                                  $<y_attributes>$.bounds = NULL;
1748                                  ASTP_switch_type = $<y_type>3;
1749                                }
1750
1751        /* Arm-only Attribute(s) */
1752    |   CASE_KW LPAREN ne_union_case_list RPAREN
1753                                { $<y_attributes>$.attr_flags = ASTP_CASE;
1754                                  $<y_attributes>$.bounds = NULL;
1755                                  ASTP_case = $<y_label>3;
1756                                }
1757    |   DEFAULT_KW              { $<y_attributes>$.attr_flags = ASTP_DEFAULT;
1758                                  $<y_attributes>$.bounds = NULL;
1759                                }
1760    |   IDENTIFIER      /* Not an attribute, so give an error */
1761        {
1762                char const *identifier; /* place to receive the identifier text */
1763                NAMETABLE_id_to_string ($<y_id>1, &identifier);
1764                log_error (nidl_yylineno(nidl), NIDL_UNKNOWNATTR, identifier, NULL);
1765                $<y_attributes>$.attr_flags = 0;
1766                $<y_attributes>$.bounds = NULL;
1767        }
1768    ;
1769
1770/********************************************************************/
1771/*                                                                  */
1772/*          Compiletime Integer expression evaluation               */
1773/*                                                                  */
1774/********************************************************************/
1775expression: conditional_expression
1776        {$<y_exp>$ = $<y_exp>1;}
1777   ;
1778
1779conditional_expression:
1780        logical_OR_expression
1781        {$<y_exp>$ = $<y_exp>1;}
1782   |    logical_OR_expression QUESTION expression COLON conditional_expression
1783        {
1784            $<y_exp>$ = AST_expression(nidl_location(nidl),
1785                     AST_EXP_TERNARY_OP, $<y_exp>1, $<y_exp>3, $<y_exp>5);
1786        }
1787   ;
1788
1789logical_OR_expression:
1790        logical_AND_expression
1791        {$<y_exp>$ = $<y_exp>1;}
1792   |    logical_OR_expression BARBAR logical_AND_expression
1793        {
1794            $<y_exp>$ = AST_expression(nidl_location(nidl),
1795                  AST_EXP_BINARY_LOG_OR, $<y_exp>1, $<y_exp>3, NULL);
1796        }
1797   ;
1798
1799logical_AND_expression:
1800        inclusive_OR_expression
1801        {$<y_exp>$ = $<y_exp>1;}
1802   |    logical_AND_expression AMPAMP inclusive_OR_expression
1803        {
1804				$<y_exp>$ = AST_expression(nidl_location(nidl),
1805                  AST_EXP_BINARY_LOG_AND, $<y_exp>1, $<y_exp>3, NULL);
1806        }
1807   ;
1808
1809inclusive_OR_expression:
1810        exclusive_OR_expression
1811        {$<y_exp>$ = $<y_exp>1;}
1812   |    inclusive_OR_expression BAR exclusive_OR_expression
1813        {
1814				$<y_exp>$ = AST_expression(nidl_location(nidl),
1815                  AST_EXP_BINARY_OR, $<y_exp>1, $<y_exp>3, NULL);
1816        }
1817   ;
1818
1819exclusive_OR_expression:
1820        AND_expression
1821        {$<y_exp>$ = $<y_exp>1;}
1822   |    exclusive_OR_expression CARET AND_expression
1823        {
1824				$<y_exp>$ = AST_expression(nidl_location(nidl),
1825                  AST_EXP_BINARY_XOR, $<y_exp>1, $<y_exp>3, NULL);
1826        }
1827   ;
1828
1829AND_expression:
1830        equality_expression
1831        {$<y_exp>$ = $<y_exp>1;}
1832   |    AND_expression AMP equality_expression
1833        {
1834				$<y_exp>$ = AST_expression(nidl_location(nidl),
1835                  AST_EXP_BINARY_AND, $<y_exp>1, $<y_exp>3, NULL);
1836        }
1837   ;
1838
1839equality_expression:
1840        relational_expression
1841        {$<y_exp>$ = $<y_exp>1;}
1842   |    equality_expression EQUALEQUAL relational_expression
1843        {
1844				$<y_exp>$ = AST_expression(nidl_location(nidl),
1845                  AST_EXP_BINARY_EQUAL, $<y_exp>1, $<y_exp>3, NULL);
1846        }
1847   |    equality_expression NOTEQUAL relational_expression
1848        {
1849				$<y_exp>$ = AST_expression(nidl_location(nidl),
1850                  AST_EXP_BINARY_NE, $<y_exp>1, $<y_exp>3, NULL);
1851
1852        }
1853   ;
1854
1855relational_expression:
1856        shift_expression
1857        {$<y_exp>$ = $<y_exp>1;}
1858   |    relational_expression LANGLE shift_expression
1859        {
1860				$<y_exp>$ = AST_expression(nidl_location(nidl),
1861                  AST_EXP_BINARY_LT, $<y_exp>1, $<y_exp>3, NULL);
1862        }
1863   |    relational_expression RANGLE shift_expression
1864        {
1865				$<y_exp>$ = AST_expression(nidl_location(nidl),
1866                  AST_EXP_BINARY_GT, $<y_exp>1, $<y_exp>3, NULL);
1867        }
1868   |    relational_expression LESSEQUAL shift_expression
1869        {
1870				$<y_exp>$ = AST_expression(nidl_location(nidl),
1871                  AST_EXP_BINARY_LE, $<y_exp>1, $<y_exp>3, NULL);
1872        }
1873   |    relational_expression GREATEREQUAL shift_expression
1874        {
1875				$<y_exp>$ = AST_expression(nidl_location(nidl),
1876                  AST_EXP_BINARY_GE, $<y_exp>1, $<y_exp>3, NULL);
1877
1878        }
1879   ;
1880
1881shift_expression:
1882        additive_expression
1883        {$<y_exp>$ = $<y_exp>1;}
1884   |    shift_expression LANGLEANGLE additive_expression
1885        {
1886				$<y_exp>$ = AST_expression(nidl_location(nidl),
1887                  AST_EXP_BINARY_LSHIFT, $<y_exp>1, $<y_exp>3, NULL);
1888        }
1889   |    shift_expression RANGLEANGLE additive_expression
1890        {
1891				$<y_exp>$ = AST_expression(nidl_location(nidl),
1892                  AST_EXP_BINARY_RSHIFT, $<y_exp>1, $<y_exp>3, NULL);
1893
1894        }
1895   ;
1896
1897additive_expression:
1898        multiplicative_expression
1899        {$<y_exp>$ = $<y_exp>1;}
1900   |    additive_expression PLUS multiplicative_expression
1901        {
1902				$<y_exp>$ = AST_expression(nidl_location(nidl),
1903                  AST_EXP_BINARY_PLUS, $<y_exp>1, $<y_exp>3, NULL);
1904
1905        }
1906   |    additive_expression MINUS multiplicative_expression
1907        {
1908				$<y_exp>$ = AST_expression(nidl_location(nidl),
1909                  AST_EXP_BINARY_MINUS, $<y_exp>1, $<y_exp>3, NULL);
1910        }
1911   ;
1912
1913multiplicative_expression:
1914        cast_expression
1915        {$<y_exp>$ = $<y_exp>1;}
1916   |    multiplicative_expression STAR cast_expression
1917        {
1918				$<y_exp>$ = AST_expression(nidl_location(nidl),
1919                  AST_EXP_BINARY_STAR, $<y_exp>1, $<y_exp>3, NULL);
1920				/*
1921            if (($<y_exp>$.exp.constant.val.integer < $<y_exp>1.exp.constant.val.integer) &&
1922                ($<y_exp>$.exp.constant.val.integer < $<y_exp>3.exp.constant.val.integer))
1923                log_error (nidl_yylineno(nidl), NIDL_INTOVERFLOW,
1924			   KEYWORDS_lookup_text(LONG_KW), NULL);
1925					*/
1926        }
1927   |    multiplicative_expression SLASH cast_expression
1928        {
1929				$<y_exp>$ = AST_expression(nidl_location(nidl),
1930                  AST_EXP_BINARY_SLASH, $<y_exp>1, $<y_exp>3, NULL);
1931        }
1932   |    multiplicative_expression PERCENT cast_expression
1933        {
1934				$<y_exp>$ = AST_expression(nidl_location(nidl),
1935                  AST_EXP_BINARY_PERCENT, $<y_exp>1, $<y_exp>3, NULL);
1936            /*    log_error (nidl_yylineno(nidl), NIDL_INTDIVBY0, NULL); */
1937        }
1938   ;
1939
1940cast_expression: unary_expression
1941        {$<y_exp>$ = $<y_exp>1;}
1942    ;
1943
1944unary_expression:
1945        primary_expression
1946        {$<y_exp>$ = $<y_exp>1;}
1947   |    PLUS primary_expression
1948        {
1949				$<y_exp>$ = AST_expression(nidl_location(nidl),
1950                  AST_EXP_UNARY_PLUS, $<y_exp>2, NULL, NULL);
1951		  }
1952   |    MINUS primary_expression
1953        {
1954				$<y_exp>$ = AST_expression(nidl_location(nidl),
1955                  AST_EXP_UNARY_MINUS, $<y_exp>2, NULL, NULL);
1956        }
1957   |    TILDE primary_expression
1958        {
1959				$<y_exp>$ = AST_expression(nidl_location(nidl),
1960                  AST_EXP_UNARY_TILDE, $<y_exp>2, NULL, NULL);
1961        }
1962   |    NOT primary_expression
1963        {
1964				$<y_exp>$ = AST_expression(nidl_location(nidl),
1965                  AST_EXP_UNARY_NOT, $<y_exp>2, NULL, NULL);
1966        }
1967	|	  STAR primary_expression
1968		  {
1969			  $<y_exp>$ = AST_expression(nidl_location(nidl),
1970                 AST_EXP_UNARY_STAR, $<y_exp>2, NULL, NULL);
1971		  }
1972   ;
1973
1974primary_expression:
1975        LPAREN expression RPAREN
1976        { $<y_exp>$ = $<y_exp>2; }
1977    |   INTEGER_NUMERIC
1978        {
1979				$<y_exp>$ = AST_exp_integer_constant(
1980               nidl_location(nidl),
1981					$<y_int_info>1.int_val,
1982					$<y_int_info>1.int_signed);
1983        }
1984    |   CHAR
1985        {
1986				$<y_exp>$ = AST_exp_char_constant(nidl_location(nidl), $<y_char>1);
1987        }
1988    |   IDENTIFIER
1989        {
1990            $<y_exp>$ = AST_exp_identifier(nidl_location(nidl), $<y_id>1);
1991        }
1992    |   STRING
1993        {
1994            $<y_exp>$ = AST_exp_string_constant(
1995                  nidl_location(nidl), $<y_string>1);
1996        }
1997    |   NULL_KW
1998        {
1999            $<y_exp>$ = AST_exp_null_constant(nidl_location(nidl));
2000        }
2001
2002    |   TRUE_KW
2003        {
2004            $<y_exp>$ = AST_exp_boolean_constant(nidl_location(nidl), true);
2005        }
2006
2007    |   FALSE_KW
2008        {
2009            $<y_exp>$ = AST_exp_boolean_constant(nidl_location(nidl), false);
2010        }
2011   |    FLOAT_NUMERIC
2012        {
2013				$<y_exp>$ = AST_exp_integer_constant(nidl_location(nidl), 0,0);
2014            log_error(nidl_yylineno(nidl), NIDL_FLOATCONSTNOSUP, NULL);
2015        }
2016   ;
2017%%
2018
2019nidl_parser_p nidl_parser_alloc
2020(
2021    boolean     *cmd_opt_arr,   /* [in] Array of command option flags */
2022    void        **cmd_val_arr,  /* [in] Array of command option values */
2023    char        *nidl_file       /* [in] ACF file name */
2024)
2025{
2026   nidl_parser_state_t * nidl;
2027
2028   nidl = NEW(nidl_parser_state_t);
2029
2030   /* Set global (STRTAB_str_t error_file_name_id) for error processing. */
2031   set_name_for_errors(nidl_file);
2032   nidl->nidl_location.fileid = STRTAB_add_string(nidl_file);
2033
2034   // XXX save file name ID in parser state
2035
2036   return nidl;
2037}
2038
2039void nidl_parser_destroy
2040(
2041   nidl_parser_p nidl
2042)
2043{
2044   FREE(nidl);
2045   yyin_p = NULL;
2046   yylineno_p = NULL;
2047}
2048
2049void nidl_parser_input
2050(
2051    nidl_parser_p nidl,
2052    FILE * in
2053)
2054{
2055    assert(nidl->nidl_yyscanner == NULL);
2056
2057    nidl_yylex_init(&nidl->nidl_yyscanner);
2058    nidl_yyset_in(in, nidl->nidl_yyscanner);
2059
2060    yyin_p = in;
2061    yylineno_p = &nidl->nidl_location.lineno;
2062}
2063
2064const parser_location_t * nidl_location
2065(
2066   nidl_parser_p nidl
2067)
2068{
2069    /* Update the current location before handing it back ... */
2070    nidl->nidl_location.lineno = nidl_yylineno(nidl);
2071    nidl->nidl_location.location = *nidl_yyget_lloc(nidl->nidl_yyscanner);
2072    nidl->nidl_location.text = nidl_yyget_text(nidl->nidl_yyscanner);
2073
2074    return &nidl->nidl_location;
2075}
2076
2077unsigned nidl_yylineno
2078(
2079   nidl_parser_p nidl
2080)
2081{
2082   return nidl_yyget_lineno(nidl->nidl_yyscanner);
2083}
2084
2085unsigned nidl_errcount
2086(
2087   nidl_parser_p nidl
2088)
2089{
2090   return nidl->nidl_yynerrs;
2091}
2092
2093static void nidl_yyerror
2094(
2095    YYLTYPE * yylloc ATTRIBUTE_UNUSED,
2096    nidl_parser_p nidl,
2097    char const * message
2098)
2099{
2100    const struct parser_location_t * loc;
2101    loc = nidl_location(nidl);
2102    idl_yyerror(loc, message);
2103}
2104
2105/* preserve coding style vim: set tw=78 sw=3 ts=3 et : */
2106