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