Home | History | Annotate | Line # | Download | only in compiler
aslrules.y revision 1.1.1.6
      1 NoEcho('
      2 /******************************************************************************
      3  *
      4  * Module Name: aslrules.y - Main Bison/Yacc production rules
      5  *
      6  *****************************************************************************/
      7 
      8 /*
      9  * Copyright (C) 2000 - 2017, Intel Corp.
     10  * All rights reserved.
     11  *
     12  * Redistribution and use in source and binary forms, with or without
     13  * modification, are permitted provided that the following conditions
     14  * are met:
     15  * 1. Redistributions of source code must retain the above copyright
     16  *    notice, this list of conditions, and the following disclaimer,
     17  *    without modification.
     18  * 2. Redistributions in binary form must reproduce at minimum a disclaimer
     19  *    substantially similar to the "NO WARRANTY" disclaimer below
     20  *    ("Disclaimer") and any redistribution must be conditioned upon
     21  *    including a substantially similar Disclaimer requirement for further
     22  *    binary redistribution.
     23  * 3. Neither the names of the above-listed copyright holders nor the names
     24  *    of any contributors may be used to endorse or promote products derived
     25  *    from this software without specific prior written permission.
     26  *
     27  * Alternatively, this software may be distributed under the terms of the
     28  * GNU General Public License ("GPL") version 2 as published by the Free
     29  * Software Foundation.
     30  *
     31  * NO WARRANTY
     32  * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
     33  * "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
     34  * LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR
     35  * A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
     36  * HOLDERS OR CONTRIBUTORS BE LIABLE FOR SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
     37  * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
     38  * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
     39  * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
     40  * STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING
     41  * IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
     42  * POSSIBILITY OF SUCH DAMAGES.
     43  */
     44 
     45 ')
     46 
     47 /*******************************************************************************
     48  *
     49  * ASL Root and Secondary Terms
     50  *
     51  ******************************************************************************/
     52 
     53 /*
     54  * Root term. Allow multiple #line directives before the definition block
     55  * to handle output from preprocessors
     56  */
     57 AslCode
     58     : DefinitionBlockList           {$<n>$ = TrLinkChildren (
     59                                         TrCreateLeafNode (PARSEOP_ASL_CODE),1, $1);}
     60     | error                         {YYABORT; $$ = NULL;}
     61     ;
     62 
     63 
     64 /*
     65  * Note concerning support for "module-level code".
     66  *
     67  * ACPI 1.0 allowed Type1 and Type2 executable opcodes outside of control
     68  * methods (the so-called module-level code.) This support was explicitly
     69  * removed in ACPI 2.0, but this type of code continues to be created by
     70  * BIOS vendors. In order to support the disassembly and recompilation of
     71  * such code (and the porting of ASL code to iASL), iASL supports this
     72  * code in violation of the current ACPI specification.
     73  *
     74  * The grammar change to support module-level code is to revert the
     75  * {ObjectList} portion of the DefinitionBlockTerm in ACPI 2.0 to the
     76  * original use of {TermList} instead (see below.) This allows the use
     77  * of Type1 and Type2 opcodes at module level.
     78  *
     79  * 04/2016: The module-level code is now allowed in the following terms:
     80  * DeviceTerm, PowerResTerm, ProcessorTerm, ScopeTerm, ThermalZoneTerm.
     81  * The ObjectList term is obsolete and has been removed.
     82  */
     83 DefinitionBlockTerm
     84     : PARSEOP_DEFINITION_BLOCK
     85         PARSEOP_OPEN_PAREN          {$<n>$ = TrCreateLeafNode (PARSEOP_DEFINITION_BLOCK);}
     86         String ','
     87         String ','
     88         ByteConst ','
     89         String ','
     90         String ','
     91         DWordConst
     92         PARSEOP_CLOSE_PAREN         {TrSetEndLineNumber ($<n>3);}
     93             '{' TermList '}'        {$$ = TrLinkChildren ($<n>3,7,
     94                                         $4,$6,$8,$10,$12,$14,$18);}
     95     ;
     96 
     97 DefinitionBlockList
     98     : DefinitionBlockTerm
     99     | DefinitionBlockTerm
    100         DefinitionBlockList         {$$ = TrLinkPeerNodes (2, $1,$2);}
    101     ;
    102 
    103 
    104 /******* Basic ASCII identifiers **************************************************/
    105 
    106 /* Allow IO, DMA, IRQ Resource macro and FOR macro names to also be used as identifiers */
    107 
    108 NameString
    109     : NameSeg                       {}
    110     | PARSEOP_NAMESTRING            {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) $1);}
    111     | PARSEOP_IO                    {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) "IO");}
    112     | PARSEOP_DMA                   {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) "DMA");}
    113     | PARSEOP_IRQ                   {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) "IRQ");}
    114     | PARSEOP_FOR                   {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) "FOR");}
    115     ;
    116 /*
    117 NameSeg
    118     : PARSEOP_NAMESEG               {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESEG, (ACPI_NATIVE_INT)
    119                                         TrNormalizeNameSeg ($1));}
    120     ;
    121 */
    122 
    123 NameSeg
    124     : PARSEOP_NAMESEG               {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESEG,
    125                                         (ACPI_NATIVE_INT) AslCompilerlval.s);}
    126     ;
    127 
    128 
    129 /******* Fundamental argument/statement types ***********************************/
    130 
    131 Term
    132     : Object                        {}
    133     | Type1Opcode                   {}
    134     | Type2Opcode                   {}
    135     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    136     | Type2StringOpcode             {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    137     | Type2BufferOpcode             {}
    138     | Type2BufferOrStringOpcode     {}
    139     | error                         {$$ = AslDoError(); yyclearin;}
    140     ;
    141 
    142 SuperName
    143     : SimpleName                    {}
    144     | DebugTerm                     {}
    145     | Type6Opcode                   {}
    146     ;
    147 
    148 Target
    149     :                               {$$ = TrCreateNullTarget ();} /* Placeholder is a ZeroOp object */
    150     | ','                           {$$ = TrCreateNullTarget ();} /* Placeholder is a ZeroOp object */
    151     | ',' SuperName                 {$$ = TrSetNodeFlags ($2, NODE_IS_TARGET);}
    152     ;
    153 
    154 RequiredTarget
    155     : ',' SuperName                 {$$ = TrSetNodeFlags ($2, NODE_IS_TARGET);}
    156     ;
    157 
    158 TermArg
    159     : SimpleName                    {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    160     | Type2Opcode                   {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    161     | DataObject                    {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    162 /*
    163     | PARSEOP_OPEN_PAREN
    164         TermArg
    165         PARSEOP_CLOSE_PAREN         {}
    166 */
    167     ;
    168 
    169 /*
    170  NOTE: Removed from TermArg due to reduce/reduce conflicts:
    171     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    172     | Type2StringOpcode             {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    173     | Type2BufferOpcode             {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    174     | Type2BufferOrStringOpcode     {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    175 
    176 */
    177 
    178 MethodInvocationTerm
    179     : NameString
    180         PARSEOP_OPEN_PAREN          {TrUpdateNode (PARSEOP_METHODCALL, $1);}
    181         ArgList
    182         PARSEOP_CLOSE_PAREN         {$$ = TrLinkChildNode ($1,$4);}
    183     ;
    184 
    185 /* OptionalCount must appear before ByteList or an incorrect reduction will result */
    186 
    187 OptionalCount
    188     :                               {$$ = TrCreateLeafNode (PARSEOP_ONES);}       /* Placeholder is a OnesOp object */
    189     | ','                           {$$ = TrCreateLeafNode (PARSEOP_ONES);}       /* Placeholder is a OnesOp object */
    190     | ',' TermArg                   {$$ = $2;}
    191     ;
    192 
    193 /*
    194  * Data count for buffers and packages (byte count for buffers,
    195  * element count for packages).
    196  */
    197 OptionalDataCount
    198 
    199         /* Legacy ASL */
    200     :                               {$$ = NULL;}
    201     | PARSEOP_OPEN_PAREN
    202         TermArg
    203         PARSEOP_CLOSE_PAREN         {$$ = $2;}
    204     | PARSEOP_OPEN_PAREN
    205         PARSEOP_CLOSE_PAREN         {$$ = NULL;}
    206 
    207         /* C-style (ASL+) -- adds equals term */
    208 
    209     |  PARSEOP_EXP_EQUALS           {$$ = NULL;}
    210 
    211     | PARSEOP_OPEN_PAREN
    212         TermArg
    213         PARSEOP_CLOSE_PAREN
    214         PARSEOP_EXP_EQUALS          {$$ = $2;}
    215 
    216     | PARSEOP_OPEN_PAREN
    217         PARSEOP_CLOSE_PAREN
    218         String
    219         PARSEOP_EXP_EQUALS          {$$ = NULL;}
    220     ;
    221 
    222 
    223 /******* List Terms **************************************************/
    224 
    225     /* ACPI 3.0 -- allow semicolons between terms */
    226 
    227 TermList
    228     :                               {$$ = NULL;}
    229     | TermList Term                 {$$ = TrLinkPeerNode (
    230                                         TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$2);}
    231     | TermList Term ';'             {$$ = TrLinkPeerNode (
    232                                         TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$2);}
    233     | TermList ';' Term             {$$ = TrLinkPeerNode (
    234                                         TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$3);}
    235     | TermList ';' Term ';'         {$$ = TrLinkPeerNode (
    236                                         TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$3);}
    237     ;
    238 
    239 ArgList
    240     :                               {$$ = NULL;}
    241     | TermArg
    242     | ArgList ','                   /* Allows a trailing comma at list end */
    243     | ArgList ','
    244         TermArg                     {$$ = TrLinkPeerNode ($1,$3);}
    245     ;
    246 
    247 ByteList
    248     :                               {$$ = NULL;}
    249     | ByteConstExpr
    250     | ByteList ','                  /* Allows a trailing comma at list end */
    251     | ByteList ','
    252         ByteConstExpr               {$$ = TrLinkPeerNode ($1,$3);}
    253     ;
    254 
    255 DWordList
    256     :                               {$$ = NULL;}
    257     | DWordConstExpr
    258     | DWordList ','                 /* Allows a trailing comma at list end */
    259     | DWordList ','
    260         DWordConstExpr              {$$ = TrLinkPeerNode ($1,$3);}
    261     ;
    262 
    263 FieldUnitList
    264     :                               {$$ = NULL;}
    265     | FieldUnit
    266     | FieldUnitList ','             /* Allows a trailing comma at list end */
    267     | FieldUnitList ','
    268         FieldUnit                   {$$ = TrLinkPeerNode ($1,$3);}
    269     ;
    270 
    271 FieldUnit
    272     : FieldUnitEntry                {}
    273     | OffsetTerm                    {}
    274     | AccessAsTerm                  {}
    275     | ConnectionTerm                {}
    276     ;
    277 
    278 FieldUnitEntry
    279     : ',' AmlPackageLengthTerm      {$$ = TrCreateNode (PARSEOP_RESERVED_BYTES,1,$2);}
    280     | NameSeg ','
    281         AmlPackageLengthTerm        {$$ = TrLinkChildNode ($1,$3);}
    282     ;
    283 
    284 Object
    285     : CompilerDirective             {}
    286     | NamedObject                   {}
    287     | NameSpaceModifier             {}
    288 //    | StructureTerm                 {}
    289     ;
    290 
    291 PackageList
    292     :                               {$$ = NULL;}
    293     | PackageElement
    294     | PackageList ','               /* Allows a trailing comma at list end */
    295     | PackageList ','
    296         PackageElement              {$$ = TrLinkPeerNode ($1,$3);}
    297     ;
    298 
    299 PackageElement
    300     : DataObject                    {}
    301     | NameString                    {}
    302     ;
    303 
    304     /* Rules for specifying the type of one method argument or return value */
    305 
    306 ParameterTypePackage
    307     :                               {$$ = NULL;}
    308     | ObjectTypeKeyword             {$$ = $1;}
    309     | ParameterTypePackage ','
    310         ObjectTypeKeyword           {$$ = TrLinkPeerNodes (2,$1,$3);}
    311     ;
    312 
    313 ParameterTypePackageList
    314     :                               {$$ = NULL;}
    315     | ObjectTypeKeyword             {$$ = $1;}
    316     | '{' ParameterTypePackage '}'  {$$ = $2;}
    317     ;
    318 
    319 OptionalParameterTypePackage
    320     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
    321     | ',' ParameterTypePackageList  {$$ = TrLinkChildren (
    322                                         TrCreateLeafNode (PARSEOP_DEFAULT_ARG),1,$2);}
    323     ;
    324 
    325     /* Rules for specifying the types for method arguments */
    326 
    327 ParameterTypesPackage
    328     : ParameterTypePackageList      {$$ = $1;}
    329     | ParameterTypesPackage ','
    330         ParameterTypePackageList    {$$ = TrLinkPeerNodes (2,$1,$3);}
    331     ;
    332 
    333 ParameterTypesPackageList
    334     :                               {$$ = NULL;}
    335     | ObjectTypeKeyword             {$$ = $1;}
    336     | '{' ParameterTypesPackage '}' {$$ = $2;}
    337     ;
    338 
    339 OptionalParameterTypesPackage
    340     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
    341     | ',' ParameterTypesPackageList {$$ = TrLinkChildren (
    342                                         TrCreateLeafNode (PARSEOP_DEFAULT_ARG),1,$2);}
    343     ;
    344 
    345 /*
    346  * Case-Default list; allow only one Default term and unlimited Case terms
    347  */
    348 CaseDefaultTermList
    349     :                               {$$ = NULL;}
    350     | CaseTerm                      {}
    351     | DefaultTerm                   {}
    352     | CaseDefaultTermList
    353         CaseTerm                    {$$ = TrLinkPeerNode ($1,$2);}
    354     | CaseDefaultTermList
    355         DefaultTerm                 {$$ = TrLinkPeerNode ($1,$2);}
    356 
    357 /* Original - attempts to force zero or one default term within the switch */
    358 
    359 /*
    360 CaseDefaultTermList
    361     :                               {$$ = NULL;}
    362     | CaseTermList
    363         DefaultTerm
    364         CaseTermList                {$$ = TrLinkPeerNode ($1,TrLinkPeerNode ($2, $3));}
    365     | CaseTermList
    366         CaseTerm                    {$$ = TrLinkPeerNode ($1,$2);}
    367     ;
    368 
    369 CaseTermList
    370     :                               {$$ = NULL;}
    371     | CaseTerm                      {}
    372     | CaseTermList
    373         CaseTerm                    {$$ = TrLinkPeerNode ($1,$2);}
    374     ;
    375 */
    376 
    377 
    378 /*******************************************************************************
    379  *
    380  * ASL Data and Constant Terms
    381  *
    382  ******************************************************************************/
    383 
    384 DataObject
    385     : BufferData                    {}
    386     | PackageData                   {}
    387     | IntegerData                   {}
    388     | StringData                    {}
    389     ;
    390 
    391 BufferData
    392     : Type5Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    393     | Type2BufferOrStringOpcode     {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    394     | Type2BufferOpcode             {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    395     | BufferTerm                    {}
    396     ;
    397 
    398 PackageData
    399     : PackageTerm                   {}
    400     ;
    401 
    402 IntegerData
    403     : Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    404     | Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    405     | Integer                       {}
    406     | ConstTerm                     {}
    407     ;
    408 
    409 StringData
    410     : Type2StringOpcode             {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    411     | String                        {}
    412     ;
    413 
    414 ByteConst
    415     : Integer                       {$$ = TrUpdateNode (PARSEOP_BYTECONST, $1);}
    416     ;
    417 
    418 WordConst
    419     : Integer                       {$$ = TrUpdateNode (PARSEOP_WORDCONST, $1);}
    420     ;
    421 
    422 DWordConst
    423     : Integer                       {$$ = TrUpdateNode (PARSEOP_DWORDCONST, $1);}
    424     ;
    425 
    426 QWordConst
    427     : Integer                       {$$ = TrUpdateNode (PARSEOP_QWORDCONST, $1);}
    428     ;
    429 
    430 /*
    431  * The NODE_COMPILE_TIME_CONST flag in the following constant expressions
    432  * enables compile-time constant folding to reduce the Type3Opcodes/Type2IntegerOpcodes
    433  * to simple integers. It is an error if these types of expressions cannot be
    434  * reduced, since the AML grammar for ****ConstExpr requires a simple constant.
    435  * Note: The required byte length of the constant is passed through to the
    436  * constant folding code in the node AmlLength field.
    437  */
    438 ByteConstExpr
    439     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    440                                         TrSetNodeAmlLength ($1, 1);}
    441     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    442                                         TrSetNodeAmlLength ($1, 1);}
    443     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_BYTECONST, $1);}
    444     | ByteConst                     {}
    445     ;
    446 
    447 WordConstExpr
    448     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    449                                         TrSetNodeAmlLength ($1, 2);}
    450     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    451                                         TrSetNodeAmlLength ($1, 2);}
    452     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_WORDCONST, $1);}
    453     | WordConst                     {}
    454     ;
    455 
    456 DWordConstExpr
    457     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    458                                         TrSetNodeAmlLength ($1, 4);}
    459     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    460                                         TrSetNodeAmlLength ($1, 4);}
    461     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_DWORDCONST, $1);}
    462     | DWordConst                    {}
    463     ;
    464 
    465 QWordConstExpr
    466     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    467                                         TrSetNodeAmlLength ($1, 8);}
    468     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    469                                         TrSetNodeAmlLength ($1, 8);}
    470     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_QWORDCONST, $1);}
    471     | QWordConst                    {}
    472     ;
    473 
    474 ConstTerm
    475     : ConstExprTerm                 {}
    476     | PARSEOP_REVISION              {$$ = TrCreateLeafNode (PARSEOP_REVISION);}
    477     ;
    478 
    479 ConstExprTerm
    480     : PARSEOP_ZERO                  {$$ = TrCreateValuedLeafNode (PARSEOP_ZERO, 0);}
    481     | PARSEOP_ONE                   {$$ = TrCreateValuedLeafNode (PARSEOP_ONE, 1);}
    482     | PARSEOP_ONES                  {$$ = TrCreateValuedLeafNode (PARSEOP_ONES, ACPI_UINT64_MAX);}
    483     | PARSEOP___DATE__              {$$ = TrCreateConstantLeafNode (PARSEOP___DATE__);}
    484     | PARSEOP___FILE__              {$$ = TrCreateConstantLeafNode (PARSEOP___FILE__);}
    485     | PARSEOP___LINE__              {$$ = TrCreateConstantLeafNode (PARSEOP___LINE__);}
    486     | PARSEOP___PATH__              {$$ = TrCreateConstantLeafNode (PARSEOP___PATH__);}
    487     ;
    488 
    489 Integer
    490     : PARSEOP_INTEGER               {$$ = TrCreateValuedLeafNode (PARSEOP_INTEGER,
    491                                         AslCompilerlval.i);}
    492     ;
    493 
    494 String
    495     : PARSEOP_STRING_LITERAL        {$$ = TrCreateValuedLeafNode (PARSEOP_STRING_LITERAL,
    496                                         (ACPI_NATIVE_INT) AslCompilerlval.s);}
    497     ;
    498 
    499 
    500 /*******************************************************************************
    501  *
    502  * ASL Opcode Terms
    503  *
    504  ******************************************************************************/
    505 
    506 CompilerDirective
    507     : IncludeTerm                   {}
    508     | IncludeEndTerm                {}
    509     | ExternalTerm                  {}
    510     ;
    511 
    512 NamedObject
    513     : BankFieldTerm                 {}
    514     | CreateBitFieldTerm            {}
    515     | CreateByteFieldTerm           {}
    516     | CreateDWordFieldTerm          {}
    517     | CreateFieldTerm               {}
    518     | CreateQWordFieldTerm          {}
    519     | CreateWordFieldTerm           {}
    520     | DataRegionTerm                {}
    521     | DeviceTerm                    {}
    522     | EventTerm                     {}
    523     | FieldTerm                     {}
    524     | FunctionTerm                  {}
    525     | IndexFieldTerm                {}
    526     | MethodTerm                    {}
    527     | MutexTerm                     {}
    528     | OpRegionTerm                  {}
    529     | PowerResTerm                  {}
    530     | ProcessorTerm                 {}
    531     | ThermalZoneTerm               {}
    532     ;
    533 
    534 NameSpaceModifier
    535     : AliasTerm                     {}
    536     | NameTerm                      {}
    537 //    | NameTermAslPlus               {}
    538     | ScopeTerm                     {}
    539     ;
    540 
    541 SimpleName
    542     : NameString                    {}
    543     | LocalTerm                     {}
    544     | ArgTerm                       {}
    545     ;
    546 
    547 /* For ObjectType(), SuperName except for MethodInvocationTerm */
    548 
    549 ObjectTypeSource
    550     : SimpleName                    {}
    551     | DebugTerm                     {}
    552     | RefOfTerm                     {}
    553     | DerefOfTerm                   {}
    554     | IndexTerm                     {}
    555     | IndexExpTerm                  {}
    556     ;
    557 
    558 /* For DeRefOf(), SuperName except for DerefOf and Debug */
    559 
    560 DerefOfSource
    561     : SimpleName                    {}
    562     | RefOfTerm                     {}
    563     | DerefOfTerm                   {}
    564     | IndexTerm                     {}
    565     | IndexExpTerm                  {}
    566     | StoreTerm                     {}
    567     | EqualsTerm                    {}
    568     | MethodInvocationTerm          {}
    569     ;
    570 
    571 /* For RefOf(), SuperName except for RefOf and MethodInvocationTerm */
    572 
    573 RefOfSource
    574     : SimpleName                    {}
    575     | DebugTerm                     {}
    576     | DerefOfTerm                   {}
    577     | IndexTerm                     {}
    578     | IndexExpTerm                  {}
    579     ;
    580 
    581 /* For CondRefOf(), SuperName except for RefOf and MethodInvocationTerm */
    582 
    583 CondRefOfSource
    584     : SimpleName                    {}
    585     | DebugTerm                     {}
    586     | DerefOfTerm                   {}
    587     | IndexTerm                     {}
    588     | IndexExpTerm                  {}
    589     ;
    590 
    591 /*
    592  * Opcode types, as defined in the ACPI specification
    593  */
    594 Type1Opcode
    595     : BreakTerm                     {}
    596     | BreakPointTerm                {}
    597     | ContinueTerm                  {}
    598     | FatalTerm                     {}
    599     | ForTerm                       {}
    600     | ElseIfTerm                    {}
    601     | LoadTerm                      {}
    602     | NoOpTerm                      {}
    603     | NotifyTerm                    {}
    604     | ReleaseTerm                   {}
    605     | ResetTerm                     {}
    606     | ReturnTerm                    {}
    607     | SignalTerm                    {}
    608     | SleepTerm                     {}
    609     | StallTerm                     {}
    610     | SwitchTerm                    {}
    611     | UnloadTerm                    {}
    612     | WhileTerm                     {}
    613     ;
    614 
    615 Type2Opcode
    616     : AcquireTerm                   {}
    617     | CondRefOfTerm                 {}
    618     | CopyObjectTerm                {}
    619     | DerefOfTerm                   {}
    620     | ObjectTypeTerm                {}
    621     | RefOfTerm                     {}
    622     | SizeOfTerm                    {}
    623     | StoreTerm                     {}
    624     | EqualsTerm                    {}
    625     | TimerTerm                     {}
    626     | WaitTerm                      {}
    627     | MethodInvocationTerm          {}
    628     ;
    629 
    630 /*
    631  * Type 3/4/5 opcodes
    632  */
    633 Type2IntegerOpcode                  /* "Type3" opcodes */
    634     : Expression                    {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    635     | AddTerm                       {}
    636     | AndTerm                       {}
    637     | DecTerm                       {}
    638     | DivideTerm                    {}
    639     | FindSetLeftBitTerm            {}
    640     | FindSetRightBitTerm           {}
    641     | FromBCDTerm                   {}
    642     | IncTerm                       {}
    643     | IndexTerm                     {}
    644 //    | StructureIndexTerm            {}
    645 //    | StructurePointerTerm          {}
    646     | LAndTerm                      {}
    647     | LEqualTerm                    {}
    648     | LGreaterTerm                  {}
    649     | LGreaterEqualTerm             {}
    650     | LLessTerm                     {}
    651     | LLessEqualTerm                {}
    652     | LNotTerm                      {}
    653     | LNotEqualTerm                 {}
    654     | LoadTableTerm                 {}
    655     | LOrTerm                       {}
    656     | MatchTerm                     {}
    657     | ModTerm                       {}
    658     | MultiplyTerm                  {}
    659     | NAndTerm                      {}
    660     | NOrTerm                       {}
    661     | NotTerm                       {}
    662     | OrTerm                        {}
    663     | ShiftLeftTerm                 {}
    664     | ShiftRightTerm                {}
    665     | SubtractTerm                  {}
    666     | ToBCDTerm                     {}
    667     | ToIntegerTerm                 {}
    668     | XOrTerm                       {}
    669     ;
    670 
    671 Type2StringOpcode                   /* "Type4" Opcodes */
    672     : ToDecimalStringTerm           {}
    673     | ToHexStringTerm               {}
    674     | ToStringTerm                  {}
    675     ;
    676 
    677 Type2BufferOpcode                   /* "Type5" Opcodes */
    678     : ToBufferTerm                  {}
    679     | ConcatResTerm                 {}
    680     ;
    681 
    682 Type2BufferOrStringOpcode
    683     : ConcatTerm                    {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    684     | PrintfTerm                    {}
    685     | FprintfTerm                   {}
    686     | MidTerm                       {}
    687     ;
    688 
    689 /*
    690  * A type 3 opcode evaluates to an Integer and cannot have a destination operand
    691  */
    692 Type3Opcode
    693     : EISAIDTerm                    {}
    694     ;
    695 
    696 /* Obsolete
    697 Type4Opcode
    698     : ConcatTerm                    {}
    699     | ToDecimalStringTerm           {}
    700     | ToHexStringTerm               {}
    701     | MidTerm                       {}
    702     | ToStringTerm                  {}
    703     ;
    704 */
    705 
    706 /* Type 5 opcodes are a subset of Type2 opcodes, and return a constant */
    707 
    708 Type5Opcode
    709     : ResourceTemplateTerm          {}
    710     | UnicodeTerm                   {}
    711     | ToPLDTerm                     {}
    712     | ToUUIDTerm                    {}
    713     ;
    714 
    715 Type6Opcode
    716     : RefOfTerm                     {}
    717     | DerefOfTerm                   {}
    718     | IndexTerm                     {}
    719     | IndexExpTerm                  {}
    720 //    | StructureIndexTerm            {}
    721 //    | StructurePointerTerm          {}
    722     | MethodInvocationTerm          {}
    723     ;
    724 
    725 
    726 /*******************************************************************************
    727  *
    728  * ASL Helper Terms
    729  *
    730  ******************************************************************************/
    731 
    732 AmlPackageLengthTerm
    733     : Integer                       {$$ = TrUpdateNode (PARSEOP_PACKAGE_LENGTH,
    734                                         (ACPI_PARSE_OBJECT *) $1);}
    735     ;
    736 
    737 NameStringItem
    738     : ',' NameString                {$$ = $2;}
    739     | ',' error                     {$$ = AslDoError (); yyclearin;}
    740     ;
    741 
    742 TermArgItem
    743     : ',' TermArg                   {$$ = $2;}
    744     | ',' error                     {$$ = AslDoError (); yyclearin;}
    745     ;
    746 
    747 OptionalReference
    748     :                               {$$ = TrCreateLeafNode (PARSEOP_ZERO);}       /* Placeholder is a ZeroOp object */
    749     | ','                           {$$ = TrCreateLeafNode (PARSEOP_ZERO);}       /* Placeholder is a ZeroOp object */
    750     | ',' TermArg                   {$$ = $2;}
    751     ;
    752 
    753 OptionalReturnArg
    754     :                               {$$ = TrSetNodeFlags (TrCreateLeafNode (PARSEOP_ZERO),
    755                                             NODE_IS_NULL_RETURN);}       /* Placeholder is a ZeroOp object */
    756     | TermArg                       {$$ = $1;}
    757     ;
    758 
    759 OptionalSerializeRuleKeyword
    760     :                               {$$ = NULL;}
    761     | ','                           {$$ = NULL;}
    762     | ',' SerializeRuleKeyword      {$$ = $2;}
    763     ;
    764 
    765 OptionalTermArg
    766     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
    767     | TermArg                       {$$ = $1;}
    768     ;
    769 
    770 OptionalWordConst
    771     :                               {$$ = NULL;}
    772     | WordConst                     {$$ = $1;}
    773     ;
    774