Home | History | Annotate | Line # | Download | only in compiler
aslrules.y revision 1.1.1.5
      1 NoEcho('
      2 /******************************************************************************
      3  *
      4  * Module Name: aslrules.y - Main Bison/Yacc production rules
      5  *
      6  *****************************************************************************/
      7 
      8 /*
      9  * Copyright (C) 2000 - 2016, 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 '('  {$<n>$ = TrCreateLeafNode (PARSEOP_DEFINITION_BLOCK);}
     85         String ','
     86         String ','
     87         ByteConst ','
     88         String ','
     89         String ','
     90         DWordConst
     91         ')'                         {TrSetEndLineNumber ($<n>3);}
     92             '{' TermList '}'        {$$ = TrLinkChildren ($<n>3,7,
     93                                         $4,$6,$8,$10,$12,$14,$18);}
     94     ;
     95 
     96 DefinitionBlockList
     97     : DefinitionBlockTerm
     98     | DefinitionBlockTerm
     99         DefinitionBlockList         {$$ = TrLinkPeerNodes (2, $1,$2);}
    100     ;
    101 
    102 /* Allow IO, DMA, IRQ Resource macro and FOR macro names to also be used as identifiers */
    103 
    104 NameString
    105     : NameSeg                       {}
    106     | PARSEOP_NAMESTRING            {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) $1);}
    107     | PARSEOP_IO                    {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) "IO");}
    108     | PARSEOP_DMA                   {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) "DMA");}
    109     | PARSEOP_IRQ                   {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) "IRQ");}
    110     | PARSEOP_FOR                   {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESTRING, (ACPI_NATIVE_INT) "FOR");}
    111     ;
    112 /*
    113 NameSeg
    114     : PARSEOP_NAMESEG               {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESEG, (ACPI_NATIVE_INT)
    115                                             TrNormalizeNameSeg ($1));}
    116     ;
    117 */
    118 
    119 NameSeg
    120     : PARSEOP_NAMESEG               {$$ = TrCreateValuedLeafNode (PARSEOP_NAMESEG,
    121                                             (ACPI_NATIVE_INT) AslCompilerlval.s);}
    122     ;
    123 
    124 
    125 SuperName
    126     : NameString                    {}
    127     | ArgTerm                       {}
    128     | LocalTerm                     {}
    129     | DebugTerm                     {}
    130     | Type6Opcode                   {}
    131     ;
    132 
    133 Target
    134     :                               {$$ = TrCreateNullTarget ();} /* Placeholder is a ZeroOp object */
    135     | ','                           {$$ = TrCreateNullTarget ();} /* Placeholder is a ZeroOp object */
    136     | ',' SuperName                 {$$ = TrSetNodeFlags ($2, NODE_IS_TARGET);}
    137     ;
    138 
    139 TermArg
    140     : Type2Opcode                   {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    141     | DataObject                    {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    142     | NameString                    {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    143     | ArgTerm                       {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    144     | LocalTerm                     {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    145 
    146 
    147     ;
    148 
    149 /*
    150  NOTE: Removed from TermArg due to reduce/reduce conflicts:
    151     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    152     | Type2StringOpcode             {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    153     | Type2BufferOpcode             {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    154     | Type2BufferOrStringOpcode     {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    155 
    156 */
    157 
    158 MethodInvocationTerm
    159     : NameString '('                {TrUpdateNode (PARSEOP_METHODCALL, $1);}
    160         ArgList ')'                 {$$ = TrLinkChildNode ($1,$4);}
    161     ;
    162 
    163 /* OptionalCount must appear before ByteList or an incorrect reduction will result */
    164 
    165 OptionalCount
    166     :                               {$$ = TrCreateLeafNode (PARSEOP_ONES);}       /* Placeholder is a OnesOp object */
    167     | ','                           {$$ = TrCreateLeafNode (PARSEOP_ONES);}       /* Placeholder is a OnesOp object */
    168     | ',' TermArg                   {$$ = $2;}
    169     ;
    170 
    171 /*
    172  * Data count for buffers and packages (byte count for buffers,
    173  * element count for packages).
    174  */
    175 OptionalDataCount
    176 
    177         /* Legacy ASL */
    178     :                               {$$ = NULL;}
    179     | '(' TermArg ')'               {$$ = $2;}
    180     | '('  ')'                      {$$ = NULL;}
    181 
    182         /* C-style (ASL+) -- adds equals term */
    183 
    184     |  PARSEOP_EXP_EQUALS           {$$ = NULL;}
    185 
    186     | '(' TermArg ')'
    187         PARSEOP_EXP_EQUALS          {$$ = $2;}
    188 
    189     | '('  ')' String
    190         PARSEOP_EXP_EQUALS          {$$ = NULL;}
    191     ;
    192 
    193 
    194 /******* List Terms **************************************************/
    195 
    196 ArgList
    197     :                               {$$ = NULL;}
    198     | TermArg
    199     | ArgList ','                   /* Allows a trailing comma at list end */
    200     | ArgList ','
    201         TermArg                     {$$ = TrLinkPeerNode ($1,$3);}
    202     ;
    203 
    204 ByteList
    205     :                               {$$ = NULL;}
    206     | ByteConstExpr
    207     | ByteList ','                  /* Allows a trailing comma at list end */
    208     | ByteList ','
    209         ByteConstExpr               {$$ = TrLinkPeerNode ($1,$3);}
    210     ;
    211 
    212 DWordList
    213     :                               {$$ = NULL;}
    214     | DWordConstExpr
    215     | DWordList ','                 /* Allows a trailing comma at list end */
    216     | DWordList ','
    217         DWordConstExpr              {$$ = TrLinkPeerNode ($1,$3);}
    218     ;
    219 
    220 FieldUnitList
    221     :                               {$$ = NULL;}
    222     | FieldUnit
    223     | FieldUnitList ','             /* Allows a trailing comma at list end */
    224     | FieldUnitList ','
    225         FieldUnit                   {$$ = TrLinkPeerNode ($1,$3);}
    226     ;
    227 
    228 FieldUnit
    229     : FieldUnitEntry                {}
    230     | OffsetTerm                    {}
    231     | AccessAsTerm                  {}
    232     | ConnectionTerm                {}
    233     ;
    234 
    235 FieldUnitEntry
    236     : ',' AmlPackageLengthTerm      {$$ = TrCreateNode (PARSEOP_RESERVED_BYTES,1,$2);}
    237     | NameSeg ','
    238         AmlPackageLengthTerm        {$$ = TrLinkChildNode ($1,$3);}
    239     ;
    240 
    241 Object
    242     : CompilerDirective             {}
    243     | NamedObject                   {}
    244     | NameSpaceModifier             {}
    245 //    | StructureTerm                 {}
    246     ;
    247 
    248 PackageList
    249     :                               {$$ = NULL;}
    250     | PackageElement
    251     | PackageList ','               /* Allows a trailing comma at list end */
    252     | PackageList ','
    253         PackageElement              {$$ = TrLinkPeerNode ($1,$3);}
    254     ;
    255 
    256 PackageElement
    257     : DataObject                    {}
    258     | NameString                    {}
    259     ;
    260 
    261     /* Rules for specifying the type of one method argument or return value */
    262 
    263 ParameterTypePackage
    264     :                               {$$ = NULL;}
    265     | ObjectTypeKeyword             {$$ = $1;}
    266     | ParameterTypePackage ','
    267         ObjectTypeKeyword           {$$ = TrLinkPeerNodes (2,$1,$3);}
    268     ;
    269 
    270 ParameterTypePackageList
    271     :                               {$$ = NULL;}
    272     | ObjectTypeKeyword             {$$ = $1;}
    273     | '{' ParameterTypePackage '}'  {$$ = $2;}
    274     ;
    275 
    276 OptionalParameterTypePackage
    277     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
    278     | ',' ParameterTypePackageList  {$$ = TrLinkChildren (
    279                                         TrCreateLeafNode (PARSEOP_DEFAULT_ARG),1,$2);}
    280     ;
    281 
    282     /* Rules for specifying the types for method arguments */
    283 
    284 ParameterTypesPackage
    285     : ParameterTypePackageList      {$$ = $1;}
    286     | ParameterTypesPackage ','
    287         ParameterTypePackageList    {$$ = TrLinkPeerNodes (2,$1,$3);}
    288     ;
    289 
    290 ParameterTypesPackageList
    291     :                               {$$ = NULL;}
    292     | ObjectTypeKeyword             {$$ = $1;}
    293     | '{' ParameterTypesPackage '}' {$$ = $2;}
    294     ;
    295 
    296 OptionalParameterTypesPackage
    297     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
    298     | ',' ParameterTypesPackageList {$$ = TrLinkChildren (
    299                                         TrCreateLeafNode (PARSEOP_DEFAULT_ARG),1,$2);}
    300     ;
    301 
    302     /* ACPI 3.0 -- allow semicolons between terms */
    303 
    304 TermList
    305     :                               {$$ = NULL;}
    306     | TermList Term                 {$$ = TrLinkPeerNode (
    307                                         TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$2);}
    308     | TermList Term ';'             {$$ = TrLinkPeerNode (
    309                                         TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$2);}
    310     | TermList ';' Term             {$$ = TrLinkPeerNode (
    311                                         TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$3);}
    312     | TermList ';' Term ';'         {$$ = TrLinkPeerNode (
    313                                         TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$3);}
    314     ;
    315 
    316 Term
    317     : Object                        {}
    318     | Type1Opcode                   {}
    319     | Type2Opcode                   {}
    320     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    321     | Type2StringOpcode             {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    322     | Type2BufferOpcode             {}
    323     | Type2BufferOrStringOpcode     {}
    324     | error                         {$$ = AslDoError(); yyclearin;}
    325     ;
    326 
    327 /*
    328  * Case-Default list; allow only one Default term and unlimited Case terms
    329  */
    330 CaseDefaultTermList
    331     :                               {$$ = NULL;}
    332     | CaseTerm  {}
    333     | DefaultTerm   {}
    334     | CaseDefaultTermList
    335         CaseTerm                    {$$ = TrLinkPeerNode ($1,$2);}
    336     | CaseDefaultTermList
    337         DefaultTerm                 {$$ = TrLinkPeerNode ($1,$2);}
    338 
    339 /* Original - attempts to force zero or one default term within the switch */
    340 
    341 /*
    342 CaseDefaultTermList
    343     :                               {$$ = NULL;}
    344     | CaseTermList
    345         DefaultTerm
    346         CaseTermList                {$$ = TrLinkPeerNode ($1,TrLinkPeerNode ($2, $3));}
    347     | CaseTermList
    348         CaseTerm                    {$$ = TrLinkPeerNode ($1,$2);}
    349     ;
    350 
    351 CaseTermList
    352     :                               {$$ = NULL;}
    353     | CaseTerm                      {}
    354     | CaseTermList
    355         CaseTerm                    {$$ = TrLinkPeerNode ($1,$2);}
    356     ;
    357 */
    358 
    359 
    360 /*******************************************************************************
    361  *
    362  * ASL Data and Constant Terms
    363  *
    364  ******************************************************************************/
    365 
    366 DataObject
    367     : BufferData                    {}
    368     | PackageData                   {}
    369     | IntegerData                   {}
    370     | StringData                    {}
    371     ;
    372 
    373 BufferData
    374     : Type5Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    375     | Type2BufferOrStringOpcode     {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    376     | Type2BufferOpcode             {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    377     | BufferTerm                    {}
    378     ;
    379 
    380 PackageData
    381     : PackageTerm                   {}
    382     ;
    383 
    384 IntegerData
    385     : Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    386     | Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    387     | Integer                       {}
    388     | ConstTerm                     {}
    389     ;
    390 
    391 StringData
    392     : Type2StringOpcode             {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    393     | String                        {}
    394     ;
    395 
    396 ByteConst
    397     : Integer                       {$$ = TrUpdateNode (PARSEOP_BYTECONST, $1);}
    398     ;
    399 
    400 WordConst
    401     : Integer                       {$$ = TrUpdateNode (PARSEOP_WORDCONST, $1);}
    402     ;
    403 
    404 DWordConst
    405     : Integer                       {$$ = TrUpdateNode (PARSEOP_DWORDCONST, $1);}
    406     ;
    407 
    408 QWordConst
    409     : Integer                       {$$ = TrUpdateNode (PARSEOP_QWORDCONST, $1);}
    410     ;
    411 
    412 /*
    413  * The NODE_COMPILE_TIME_CONST flag in the following constant expressions
    414  * enables compile-time constant folding to reduce the Type3Opcodes/Type2IntegerOpcodes
    415  * to simple integers. It is an error if these types of expressions cannot be
    416  * reduced, since the AML grammar for ****ConstExpr requires a simple constant.
    417  * Note: The required byte length of the constant is passed through to the
    418  * constant folding code in the node AmlLength field.
    419  */
    420 ByteConstExpr
    421     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    422                                         TrSetNodeAmlLength ($1, 1);}
    423     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    424                                         TrSetNodeAmlLength ($1, 1);}
    425     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_BYTECONST, $1);}
    426     | ByteConst                     {}
    427     ;
    428 
    429 WordConstExpr
    430     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    431                                         TrSetNodeAmlLength ($1, 2);}
    432     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    433                                         TrSetNodeAmlLength ($1, 2);}
    434     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_WORDCONST, $1);}
    435     | WordConst                     {}
    436     ;
    437 
    438 DWordConstExpr
    439     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    440                                         TrSetNodeAmlLength ($1, 4);}
    441     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    442                                         TrSetNodeAmlLength ($1, 4);}
    443     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_DWORDCONST, $1);}
    444     | DWordConst                    {}
    445     ;
    446 
    447 QWordConstExpr
    448     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    449                                         TrSetNodeAmlLength ($1, 8);}
    450     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);
    451                                         TrSetNodeAmlLength ($1, 8);}
    452     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_QWORDCONST, $1);}
    453     | QWordConst                    {}
    454     ;
    455 
    456 ConstTerm
    457     : ConstExprTerm                 {}
    458     | PARSEOP_REVISION              {$$ = TrCreateLeafNode (PARSEOP_REVISION);}
    459     ;
    460 
    461 ConstExprTerm
    462     : PARSEOP_ZERO                  {$$ = TrCreateValuedLeafNode (PARSEOP_ZERO, 0);}
    463     | PARSEOP_ONE                   {$$ = TrCreateValuedLeafNode (PARSEOP_ONE, 1);}
    464     | PARSEOP_ONES                  {$$ = TrCreateValuedLeafNode (PARSEOP_ONES, ACPI_UINT64_MAX);}
    465     | PARSEOP___DATE__              {$$ = TrCreateConstantLeafNode (PARSEOP___DATE__);}
    466     | PARSEOP___FILE__              {$$ = TrCreateConstantLeafNode (PARSEOP___FILE__);}
    467     | PARSEOP___LINE__              {$$ = TrCreateConstantLeafNode (PARSEOP___LINE__);}
    468     | PARSEOP___PATH__              {$$ = TrCreateConstantLeafNode (PARSEOP___PATH__);}
    469     ;
    470 
    471 Integer
    472     : PARSEOP_INTEGER               {$$ = TrCreateValuedLeafNode (PARSEOP_INTEGER,
    473                                         AslCompilerlval.i);}
    474     ;
    475 
    476 String
    477     : PARSEOP_STRING_LITERAL        {$$ = TrCreateValuedLeafNode (PARSEOP_STRING_LITERAL,
    478                                         (ACPI_NATIVE_INT) AslCompilerlval.s);}
    479     ;
    480 
    481 
    482 /*******************************************************************************
    483  *
    484  * ASL Opcode Terms
    485  *
    486  ******************************************************************************/
    487 
    488 CompilerDirective
    489     : IncludeTerm                   {}
    490     | IncludeEndTerm                {}
    491     | ExternalTerm                  {}
    492     ;
    493 
    494 NamedObject
    495     : BankFieldTerm                 {}
    496     | CreateBitFieldTerm            {}
    497     | CreateByteFieldTerm           {}
    498     | CreateDWordFieldTerm          {}
    499     | CreateFieldTerm               {}
    500     | CreateQWordFieldTerm          {}
    501     | CreateWordFieldTerm           {}
    502     | DataRegionTerm                {}
    503     | DeviceTerm                    {}
    504     | EventTerm                     {}
    505     | FieldTerm                     {}
    506     | FunctionTerm                  {}
    507     | IndexFieldTerm                {}
    508     | MethodTerm                    {}
    509     | MutexTerm                     {}
    510     | OpRegionTerm                  {}
    511     | PowerResTerm                  {}
    512     | ProcessorTerm                 {}
    513     | ThermalZoneTerm               {}
    514     ;
    515 
    516 NameSpaceModifier
    517     : AliasTerm                     {}
    518     | NameTerm                      {}
    519 //    | NameTermAslPlus               {}
    520     | ScopeTerm                     {}
    521     ;
    522 
    523 /* For ObjectType: SuperName except for MethodInvocationTerm */
    524 
    525 ObjectTypeName
    526     : NameString                    {}
    527     | ArgTerm                       {}
    528     | LocalTerm                     {}
    529     | DebugTerm                     {}
    530     | RefOfTerm                     {}
    531     | DerefOfTerm                   {}
    532     | IndexTerm                     {}
    533     | IndexExpTerm                  {}
    534 /*    | MethodInvocationTerm          {} */  /* Caused reduce/reduce with Type6Opcode->MethodInvocationTerm */
    535     ;
    536 
    537 RequiredTarget
    538     : ',' SuperName                 {$$ = TrSetNodeFlags ($2, NODE_IS_TARGET);}
    539     ;
    540 
    541 SimpleTarget
    542     : NameString                    {}
    543     | LocalTerm                     {}
    544     | ArgTerm                       {}
    545     ;
    546 
    547 /* Opcode types */
    548 
    549 Type1Opcode
    550     : BreakTerm                     {}
    551     | BreakPointTerm                {}
    552     | ContinueTerm                  {}
    553     | FatalTerm                     {}
    554     | ForTerm                       {}
    555     | ElseIfTerm                    {}
    556     | LoadTerm                      {}
    557     | NoOpTerm                      {}
    558     | NotifyTerm                    {}
    559     | ReleaseTerm                   {}
    560     | ResetTerm                     {}
    561     | ReturnTerm                    {}
    562     | SignalTerm                    {}
    563     | SleepTerm                     {}
    564     | StallTerm                     {}
    565     | SwitchTerm                    {}
    566     | UnloadTerm                    {}
    567     | WhileTerm                     {}
    568     ;
    569 
    570 Type2Opcode
    571     : AcquireTerm                   {}
    572     | CondRefOfTerm                 {}
    573     | CopyObjectTerm                {}
    574     | DerefOfTerm                   {}
    575     | ObjectTypeTerm                {}
    576     | RefOfTerm                     {}
    577     | SizeOfTerm                    {}
    578     | StoreTerm                     {}
    579     | EqualsTerm                    {}
    580     | TimerTerm                     {}
    581     | WaitTerm                      {}
    582     | MethodInvocationTerm          {}
    583     ;
    584 
    585 /*
    586  * Type 3/4/5 opcodes
    587  */
    588 Type2IntegerOpcode                  /* "Type3" opcodes */
    589     : Expression                    {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    590     | AddTerm                       {}
    591     | AndTerm                       {}
    592     | DecTerm                       {}
    593     | DivideTerm                    {}
    594     | FindSetLeftBitTerm            {}
    595     | FindSetRightBitTerm           {}
    596     | FromBCDTerm                   {}
    597     | IncTerm                       {}
    598     | IndexTerm                     {}
    599 //    | StructureIndexTerm            {}
    600 //    | StructurePointerTerm          {}
    601     | LAndTerm                      {}
    602     | LEqualTerm                    {}
    603     | LGreaterTerm                  {}
    604     | LGreaterEqualTerm             {}
    605     | LLessTerm                     {}
    606     | LLessEqualTerm                {}
    607     | LNotTerm                      {}
    608     | LNotEqualTerm                 {}
    609     | LoadTableTerm                 {}
    610     | LOrTerm                       {}
    611     | MatchTerm                     {}
    612     | ModTerm                       {}
    613     | MultiplyTerm                  {}
    614     | NAndTerm                      {}
    615     | NOrTerm                       {}
    616     | NotTerm                       {}
    617     | OrTerm                        {}
    618     | ShiftLeftTerm                 {}
    619     | ShiftRightTerm                {}
    620     | SubtractTerm                  {}
    621     | ToBCDTerm                     {}
    622     | ToIntegerTerm                 {}
    623     | XOrTerm                       {}
    624     ;
    625 
    626 Type2StringOpcode                   /* "Type4" Opcodes */
    627     : ToDecimalStringTerm           {}
    628     | ToHexStringTerm               {}
    629     | ToStringTerm                  {}
    630     ;
    631 
    632 Type2BufferOpcode                   /* "Type5" Opcodes */
    633     : ToBufferTerm                  {}
    634     | ConcatResTerm                 {}
    635     ;
    636 
    637 Type2BufferOrStringOpcode
    638     : ConcatTerm                    {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    639     | PrintfTerm                    {}
    640     | FprintfTerm                   {}
    641     | MidTerm                       {}
    642     ;
    643 
    644 /*
    645  * A type 3 opcode evaluates to an Integer and cannot have a destination operand
    646  */
    647 Type3Opcode
    648     : EISAIDTerm                    {}
    649     ;
    650 
    651 /* Obsolete
    652 Type4Opcode
    653     : ConcatTerm                    {}
    654     | ToDecimalStringTerm           {}
    655     | ToHexStringTerm               {}
    656     | MidTerm                       {}
    657     | ToStringTerm                  {}
    658     ;
    659 */
    660 
    661 /* Type 5 opcodes are a subset of Type2 opcodes, and return a constant */
    662 
    663 Type5Opcode
    664     : ResourceTemplateTerm          {}
    665     | UnicodeTerm                   {}
    666     | ToPLDTerm                     {}
    667     | ToUUIDTerm                    {}
    668     ;
    669 
    670 Type6Opcode
    671     : RefOfTerm                     {}
    672     | DerefOfTerm                   {}
    673     | IndexTerm                     {}
    674     | IndexExpTerm                  {}
    675 //    | StructureIndexTerm            {}
    676 //    | StructurePointerTerm          {}
    677     | MethodInvocationTerm          {}
    678     ;
    679 
    680 
    681 /*******************************************************************************
    682  *
    683  * ASL Helper Terms
    684  *
    685  ******************************************************************************/
    686 
    687 AmlPackageLengthTerm
    688     : Integer                       {$$ = TrUpdateNode (PARSEOP_PACKAGE_LENGTH,
    689                                         (ACPI_PARSE_OBJECT *) $1);}
    690     ;
    691 
    692 NameStringItem
    693     : ',' NameString                {$$ = $2;}
    694     | ',' error                     {$$ = AslDoError (); yyclearin;}
    695     ;
    696 
    697 TermArgItem
    698     : ',' TermArg                   {$$ = $2;}
    699     | ',' error                     {$$ = AslDoError (); yyclearin;}
    700     ;
    701 
    702 OptionalReference
    703     :                               {$$ = TrCreateLeafNode (PARSEOP_ZERO);}       /* Placeholder is a ZeroOp object */
    704     | ','                           {$$ = TrCreateLeafNode (PARSEOP_ZERO);}       /* Placeholder is a ZeroOp object */
    705     | ',' TermArg                   {$$ = $2;}
    706     ;
    707 
    708 OptionalReturnArg
    709     :                               {$$ = TrSetNodeFlags (TrCreateLeafNode (PARSEOP_ZERO),
    710                                             NODE_IS_NULL_RETURN);}       /* Placeholder is a ZeroOp object */
    711     | TermArg                       {$$ = $1;}
    712     ;
    713 
    714 OptionalSerializeRuleKeyword
    715     :                               {$$ = NULL;}
    716     | ','                           {$$ = NULL;}
    717     | ',' SerializeRuleKeyword      {$$ = $2;}
    718     ;
    719 
    720 OptionalTermArg
    721     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
    722     | TermArg                       {$$ = $1;}
    723     ;
    724 
    725 OptionalWordConst
    726     :                               {$$ = NULL;}
    727     | WordConst                     {$$ = $1;}
    728     ;
    729