Home | History | Annotate | Line # | Download | only in compiler
aslrules.y revision 1.1.1.4
      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 (TrCreateLeafNode (PARSEOP_ASL_CODE),1, $1);}
     59     | error                         {YYABORT; $$ = NULL;}
     60     ;
     61 
     62 
     63 /*
     64  * Note concerning support for "module-level code".
     65  *
     66  * ACPI 1.0 allowed Type1 and Type2 executable opcodes outside of control
     67  * methods (the so-called module-level code.) This support was explicitly
     68  * removed in ACPI 2.0, but this type of code continues to be created by
     69  * BIOS vendors. In order to support the disassembly and recompilation of
     70  * such code (and the porting of ASL code to iASL), iASL supports this
     71  * code in violation of the current ACPI specification.
     72  *
     73  * The grammar change to support module-level code is to revert the
     74  * {ObjectList} portion of the DefinitionBlockTerm in ACPI 2.0 to the
     75  * original use of {TermList} instead (see below.) This allows the use
     76  * of Type1 and Type2 opcodes at module level.
     77  *
     78  * 04/2016: The module-level code is now allowed in the following terms:
     79  * DeviceTerm, PowerResTerm, ProcessorTerm, ScopeTerm, ThermalZoneTerm.
     80  * The ObjectList term is obsolete and has been removed.
     81  */
     82 DefinitionBlockTerm
     83     : PARSEOP_DEFINITION_BLOCK '('  {$<n>$ = TrCreateLeafNode (PARSEOP_DEFINITION_BLOCK);}
     84         String ','
     85         String ','
     86         ByteConst ','
     87         String ','
     88         String ','
     89         DWordConst
     90         ')'                         {TrSetEndLineNumber ($<n>3);}
     91             '{' TermList '}'        {$$ = TrLinkChildren ($<n>3,7,$4,$6,$8,$10,$12,$14,$18);}
     92     ;
     93 
     94 DefinitionBlockList
     95     : DefinitionBlockTerm
     96     | DefinitionBlockTerm
     97         DefinitionBlockList         {$$ = TrLinkPeerNodes (2, $1,$2);}
     98     ;
     99 
    100 SuperName
    101     : NameString                    {}
    102     | ArgTerm                       {}
    103     | LocalTerm                     {}
    104     | DebugTerm                     {}
    105     | Type6Opcode                   {}
    106 
    107 Target
    108     :                               {$$ = TrCreateNullTarget ();} /* Placeholder is a ZeroOp object */
    109     | ','                           {$$ = TrCreateNullTarget ();} /* Placeholder is a ZeroOp object */
    110     | ',' SuperName                 {$$ = TrSetNodeFlags ($2, NODE_IS_TARGET);}
    111     ;
    112 
    113 TermArg
    114     : Type2Opcode                   {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    115     | DataObject                    {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    116     | NameString                    {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    117     | ArgTerm                       {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    118     | LocalTerm                     {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    119     ;
    120 
    121 /*
    122  NOTE: Removed from TermArg due to reduce/reduce conflicts:
    123     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    124     | Type2StringOpcode             {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    125     | Type2BufferOpcode             {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    126     | Type2BufferOrStringOpcode     {$$ = TrSetNodeFlags ($1, NODE_IS_TERM_ARG);}
    127 
    128 */
    129 
    130 MethodInvocationTerm
    131     : NameString '('                {TrUpdateNode (PARSEOP_METHODCALL, $1);}
    132         ArgList ')'                 {$$ = TrLinkChildNode ($1,$4);}
    133     ;
    134 
    135 /* OptionalCount must appear before ByteList or an incorrect reduction will result */
    136 
    137 OptionalCount
    138     :                               {$$ = TrCreateLeafNode (PARSEOP_ONES);}       /* Placeholder is a OnesOp object */
    139     | ','                           {$$ = TrCreateLeafNode (PARSEOP_ONES);}       /* Placeholder is a OnesOp object */
    140     | ',' TermArg                   {$$ = $2;}
    141     ;
    142 
    143 VarPackageLengthTerm
    144     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
    145     | TermArg                       {$$ = $1;}
    146     ;
    147 
    148 
    149 /******* List Terms **************************************************/
    150 
    151 ArgList
    152     :                               {$$ = NULL;}
    153     | TermArg
    154     | ArgList ','                   /* Allows a trailing comma at list end */
    155     | ArgList ','
    156         TermArg                     {$$ = TrLinkPeerNode ($1,$3);}
    157     ;
    158 
    159 ByteList
    160     :                               {$$ = NULL;}
    161     | ByteConstExpr
    162     | ByteList ','                  /* Allows a trailing comma at list end */
    163     | ByteList ','
    164         ByteConstExpr               {$$ = TrLinkPeerNode ($1,$3);}
    165     ;
    166 
    167 DWordList
    168     :                               {$$ = NULL;}
    169     | DWordConstExpr
    170     | DWordList ','                 /* Allows a trailing comma at list end */
    171     | DWordList ','
    172         DWordConstExpr              {$$ = TrLinkPeerNode ($1,$3);}
    173     ;
    174 
    175 FieldUnitList
    176     :                               {$$ = NULL;}
    177     | FieldUnit
    178     | FieldUnitList ','             /* Allows a trailing comma at list end */
    179     | FieldUnitList ','
    180         FieldUnit                   {$$ = TrLinkPeerNode ($1,$3);}
    181     ;
    182 
    183 FieldUnit
    184     : FieldUnitEntry                {}
    185     | OffsetTerm                    {}
    186     | AccessAsTerm                  {}
    187     | ConnectionTerm                {}
    188     ;
    189 
    190 FieldUnitEntry
    191     : ',' AmlPackageLengthTerm      {$$ = TrCreateNode (PARSEOP_RESERVED_BYTES,1,$2);}
    192     | NameSeg ','
    193         AmlPackageLengthTerm        {$$ = TrLinkChildNode ($1,$3);}
    194     ;
    195 
    196 Object
    197     : CompilerDirective             {}
    198     | NamedObject                   {}
    199     | NameSpaceModifier             {}
    200     ;
    201 
    202 PackageList
    203     :                               {$$ = NULL;}
    204     | PackageElement
    205     | PackageList ','               /* Allows a trailing comma at list end */
    206     | PackageList ','
    207         PackageElement              {$$ = TrLinkPeerNode ($1,$3);}
    208     ;
    209 
    210 PackageElement
    211     : DataObject                    {}
    212     | NameString                    {}
    213     ;
    214 
    215     /* Rules for specifying the type of one method argument or return value */
    216 
    217 ParameterTypePackage
    218     :                               {$$ = NULL;}
    219     | ObjectTypeKeyword             {$$ = $1;}
    220     | ParameterTypePackage ','
    221         ObjectTypeKeyword           {$$ = TrLinkPeerNodes (2,$1,$3);}
    222     ;
    223 
    224 ParameterTypePackageList
    225     :                               {$$ = NULL;}
    226     | ObjectTypeKeyword             {$$ = $1;}
    227     | '{' ParameterTypePackage '}'  {$$ = $2;}
    228     ;
    229 
    230 OptionalParameterTypePackage
    231     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
    232     | ',' ParameterTypePackageList  {$$ = TrLinkChildren (TrCreateLeafNode (PARSEOP_DEFAULT_ARG),1,$2);}
    233     ;
    234 
    235     /* Rules for specifying the types for method arguments */
    236 
    237 ParameterTypesPackage
    238     : ParameterTypePackageList      {$$ = $1;}
    239     | ParameterTypesPackage ','
    240         ParameterTypePackageList    {$$ = TrLinkPeerNodes (2,$1,$3);}
    241     ;
    242 
    243 ParameterTypesPackageList
    244     :                               {$$ = NULL;}
    245     | ObjectTypeKeyword             {$$ = $1;}
    246     | '{' ParameterTypesPackage '}' {$$ = $2;}
    247     ;
    248 
    249 OptionalParameterTypesPackage
    250     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
    251     | ',' ParameterTypesPackageList {$$ = TrLinkChildren (TrCreateLeafNode (PARSEOP_DEFAULT_ARG),1,$2);}
    252     ;
    253 
    254     /* ACPI 3.0 -- allow semicolons between terms */
    255 
    256 TermList
    257     :                               {$$ = NULL;}
    258     | TermList Term                 {$$ = TrLinkPeerNode (TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$2);}
    259     | TermList Term ';'             {$$ = TrLinkPeerNode (TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$2);}
    260     | TermList ';' Term             {$$ = TrLinkPeerNode (TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$3);}
    261     | TermList ';' Term ';'         {$$ = TrLinkPeerNode (TrSetNodeFlags ($1, NODE_RESULT_NOT_USED),$3);}
    262     ;
    263 
    264 Term
    265     : Object                        {}
    266     | Type1Opcode                   {}
    267     | Type2Opcode                   {}
    268     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    269     | Type2StringOpcode             {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    270     | Type2BufferOpcode             {}
    271     | Type2BufferOrStringOpcode     {}
    272     | error                         {$$ = AslDoError(); yyclearin;}
    273     ;
    274 
    275 /*
    276  * Case-Default list; allow only one Default term and unlimited Case terms
    277  */
    278 CaseDefaultTermList
    279     :                               {$$ = NULL;}
    280     | CaseTerm  {}
    281     | DefaultTerm   {}
    282     | CaseDefaultTermList
    283         CaseTerm                    {$$ = TrLinkPeerNode ($1,$2);}
    284     | CaseDefaultTermList
    285         DefaultTerm                 {$$ = TrLinkPeerNode ($1,$2);}
    286 
    287 /* Original - attempts to force zero or one default term within the switch */
    288 
    289 /*
    290 CaseDefaultTermList
    291     :                               {$$ = NULL;}
    292     | CaseTermList
    293         DefaultTerm
    294         CaseTermList                {$$ = TrLinkPeerNode ($1,TrLinkPeerNode ($2, $3));}
    295     | CaseTermList
    296         CaseTerm                    {$$ = TrLinkPeerNode ($1,$2);}
    297     ;
    298 
    299 CaseTermList
    300     :                               {$$ = NULL;}
    301     | CaseTerm                      {}
    302     | CaseTermList
    303         CaseTerm                    {$$ = TrLinkPeerNode ($1,$2);}
    304     ;
    305 */
    306 
    307 
    308 /*******************************************************************************
    309  *
    310  * ASL Data and Constant Terms
    311  *
    312  ******************************************************************************/
    313 
    314 DataObject
    315     : BufferData                    {}
    316     | PackageData                   {}
    317     | IntegerData                   {}
    318     | StringData                    {}
    319     ;
    320 
    321 BufferData
    322     : Type5Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    323     | Type2BufferOrStringOpcode     {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    324     | Type2BufferOpcode             {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    325     | BufferTerm                    {}
    326     ;
    327 
    328 PackageData
    329     : PackageTerm                   {}
    330     ;
    331 
    332 IntegerData
    333     : Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    334     | Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    335     | Integer                       {}
    336     | ConstTerm                     {}
    337     ;
    338 
    339 StringData
    340     : Type2StringOpcode             {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    341     | String                        {}
    342     ;
    343 
    344 ByteConst
    345     : Integer                       {$$ = TrUpdateNode (PARSEOP_BYTECONST, $1);}
    346     ;
    347 
    348 WordConst
    349     : Integer                       {$$ = TrUpdateNode (PARSEOP_WORDCONST, $1);}
    350     ;
    351 
    352 DWordConst
    353     : Integer                       {$$ = TrUpdateNode (PARSEOP_DWORDCONST, $1);}
    354     ;
    355 
    356 QWordConst
    357     : Integer                       {$$ = TrUpdateNode (PARSEOP_QWORDCONST, $1);}
    358     ;
    359 
    360 /*
    361  * The NODE_COMPILE_TIME_CONST flag in the following constant expressions
    362  * enables compile-time constant folding to reduce the Type3Opcodes/Type2IntegerOpcodes
    363  * to simple integers. It is an error if these types of expressions cannot be
    364  * reduced, since the AML grammar for ****ConstExpr requires a simple constant.
    365  * Note: The required byte length of the constant is passed through to the
    366  * constant folding code in the node AmlLength field.
    367  */
    368 ByteConstExpr
    369     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST); TrSetNodeAmlLength ($1, 1);}
    370     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST); TrSetNodeAmlLength ($1, 1);}
    371     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_BYTECONST, $1);}
    372     | ByteConst                     {}
    373     ;
    374 
    375 WordConstExpr
    376     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST); TrSetNodeAmlLength ($1, 2);}
    377     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST); TrSetNodeAmlLength ($1, 2);}
    378     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_WORDCONST, $1);}
    379     | WordConst                     {}
    380     ;
    381 
    382 DWordConstExpr
    383     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST); TrSetNodeAmlLength ($1, 4);}
    384     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST); TrSetNodeAmlLength ($1, 4);}
    385     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_DWORDCONST, $1);}
    386     | DWordConst                    {}
    387     ;
    388 
    389 QWordConstExpr
    390     : Type3Opcode                   {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST); TrSetNodeAmlLength ($1, 8);}
    391     | Type2IntegerOpcode            {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST); TrSetNodeAmlLength ($1, 8);}
    392     | ConstExprTerm                 {$$ = TrUpdateNode (PARSEOP_QWORDCONST, $1);}
    393     | QWordConst                    {}
    394     ;
    395 
    396 ConstTerm
    397     : ConstExprTerm                 {}
    398     | PARSEOP_REVISION              {$$ = TrCreateLeafNode (PARSEOP_REVISION);}
    399     ;
    400 
    401 ConstExprTerm
    402     : PARSEOP_ZERO                  {$$ = TrCreateValuedLeafNode (PARSEOP_ZERO, 0);}
    403     | PARSEOP_ONE                   {$$ = TrCreateValuedLeafNode (PARSEOP_ONE, 1);}
    404     | PARSEOP_ONES                  {$$ = TrCreateValuedLeafNode (PARSEOP_ONES, ACPI_UINT64_MAX);}
    405     | PARSEOP___DATE__              {$$ = TrCreateConstantLeafNode (PARSEOP___DATE__);}
    406     | PARSEOP___FILE__              {$$ = TrCreateConstantLeafNode (PARSEOP___FILE__);}
    407     | PARSEOP___LINE__              {$$ = TrCreateConstantLeafNode (PARSEOP___LINE__);}
    408     | PARSEOP___PATH__              {$$ = TrCreateConstantLeafNode (PARSEOP___PATH__);}
    409     ;
    410 
    411 Integer
    412     : PARSEOP_INTEGER               {$$ = TrCreateValuedLeafNode (PARSEOP_INTEGER, AslCompilerlval.i);}
    413     ;
    414 
    415 String
    416     : PARSEOP_STRING_LITERAL        {$$ = TrCreateValuedLeafNode (PARSEOP_STRING_LITERAL, (ACPI_NATIVE_INT) AslCompilerlval.s);}
    417     ;
    418 
    419 
    420 /*******************************************************************************
    421  *
    422  * ASL Opcode Terms
    423  *
    424  ******************************************************************************/
    425 
    426 CompilerDirective
    427     : IncludeTerm                   {}
    428     | IncludeEndTerm                {}
    429     | ExternalTerm                  {}
    430     ;
    431 
    432 NamedObject
    433     : BankFieldTerm                 {}
    434     | CreateBitFieldTerm            {}
    435     | CreateByteFieldTerm           {}
    436     | CreateDWordFieldTerm          {}
    437     | CreateFieldTerm               {}
    438     | CreateQWordFieldTerm          {}
    439     | CreateWordFieldTerm           {}
    440     | DataRegionTerm                {}
    441     | DeviceTerm                    {}
    442     | EventTerm                     {}
    443     | FieldTerm                     {}
    444     | FunctionTerm                  {}
    445     | IndexFieldTerm                {}
    446     | MethodTerm                    {}
    447     | MutexTerm                     {}
    448     | OpRegionTerm                  {}
    449     | PowerResTerm                  {}
    450     | ProcessorTerm                 {}
    451     | ThermalZoneTerm               {}
    452     ;
    453 
    454 NameSpaceModifier
    455     : AliasTerm                     {}
    456     | NameTerm                      {}
    457     | ScopeTerm                     {}
    458     ;
    459 
    460 /* For ObjectType: SuperName except for MethodInvocationTerm */
    461 
    462 ObjectTypeName
    463     : NameString                    {}
    464     | ArgTerm                       {}
    465     | LocalTerm                     {}
    466     | DebugTerm                     {}
    467     | RefOfTerm                     {}
    468     | DerefOfTerm                   {}
    469     | IndexTerm                     {}
    470 /*    | MethodInvocationTerm          {} */  /* Caused reduce/reduce with Type6Opcode->MethodInvocationTerm */
    471     ;
    472 
    473 RequiredTarget
    474     : ',' SuperName                 {$$ = TrSetNodeFlags ($2, NODE_IS_TARGET);}
    475     ;
    476 
    477 SimpleTarget
    478     : NameString                    {}
    479     | LocalTerm                     {}
    480     | ArgTerm                       {}
    481     ;
    482 
    483 /* Opcode types */
    484 
    485 Type1Opcode
    486     : BreakTerm                     {}
    487     | BreakPointTerm                {}
    488     | ContinueTerm                  {}
    489     | FatalTerm                     {}
    490     | ForTerm                       {}
    491     | ElseIfTerm                    {}
    492     | LoadTerm                      {}
    493     | NoOpTerm                      {}
    494     | NotifyTerm                    {}
    495     | ReleaseTerm                   {}
    496     | ResetTerm                     {}
    497     | ReturnTerm                    {}
    498     | SignalTerm                    {}
    499     | SleepTerm                     {}
    500     | StallTerm                     {}
    501     | SwitchTerm                    {}
    502     | UnloadTerm                    {}
    503     | WhileTerm                     {}
    504     ;
    505 
    506 Type2Opcode
    507     : AcquireTerm                   {}
    508     | CondRefOfTerm                 {}
    509     | CopyObjectTerm                {}
    510     | DerefOfTerm                   {}
    511     | ObjectTypeTerm                {}
    512     | RefOfTerm                     {}
    513     | SizeOfTerm                    {}
    514     | StoreTerm                     {}
    515     | EqualsTerm                    {}
    516     | TimerTerm                     {}
    517     | WaitTerm                      {}
    518     | MethodInvocationTerm          {}
    519     ;
    520 
    521 /*
    522  * Type 3/4/5 opcodes
    523  */
    524 Type2IntegerOpcode                  /* "Type3" opcodes */
    525     : Expression                    {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    526     | AddTerm                       {}
    527     | AndTerm                       {}
    528     | DecTerm                       {}
    529     | DivideTerm                    {}
    530     | FindSetLeftBitTerm            {}
    531     | FindSetRightBitTerm           {}
    532     | FromBCDTerm                   {}
    533     | IncTerm                       {}
    534     | IndexTerm                     {}
    535     | LAndTerm                      {}
    536     | LEqualTerm                    {}
    537     | LGreaterTerm                  {}
    538     | LGreaterEqualTerm             {}
    539     | LLessTerm                     {}
    540     | LLessEqualTerm                {}
    541     | LNotTerm                      {}
    542     | LNotEqualTerm                 {}
    543     | LoadTableTerm                 {}
    544     | LOrTerm                       {}
    545     | MatchTerm                     {}
    546     | ModTerm                       {}
    547     | MultiplyTerm                  {}
    548     | NAndTerm                      {}
    549     | NOrTerm                       {}
    550     | NotTerm                       {}
    551     | OrTerm                        {}
    552     | ShiftLeftTerm                 {}
    553     | ShiftRightTerm                {}
    554     | SubtractTerm                  {}
    555     | ToBCDTerm                     {}
    556     | ToIntegerTerm                 {}
    557     | XOrTerm                       {}
    558     ;
    559 
    560 Type2StringOpcode                   /* "Type4" Opcodes */
    561     : ToDecimalStringTerm           {}
    562     | ToHexStringTerm               {}
    563     | ToStringTerm                  {}
    564     ;
    565 
    566 Type2BufferOpcode                   /* "Type5" Opcodes */
    567     : ToBufferTerm                  {}
    568     | ConcatResTerm                 {}
    569     ;
    570 
    571 Type2BufferOrStringOpcode
    572     : ConcatTerm                    {$$ = TrSetNodeFlags ($1, NODE_COMPILE_TIME_CONST);}
    573     | PrintfTerm                    {}
    574     | FprintfTerm                   {}
    575     | MidTerm                       {}
    576     ;
    577 
    578 /*
    579  * A type 3 opcode evaluates to an Integer and cannot have a destination operand
    580  */
    581 Type3Opcode
    582     : EISAIDTerm                    {}
    583     ;
    584 
    585 /* Obsolete
    586 Type4Opcode
    587     : ConcatTerm                    {}
    588     | ToDecimalStringTerm           {}
    589     | ToHexStringTerm               {}
    590     | MidTerm                       {}
    591     | ToStringTerm                  {}
    592     ;
    593 */
    594 
    595 Type5Opcode
    596     : ResourceTemplateTerm          {}
    597     | UnicodeTerm                   {}
    598     | ToPLDTerm                     {}
    599     | ToUUIDTerm                    {}
    600     ;
    601 
    602 Type6Opcode
    603     : RefOfTerm                     {}
    604     | DerefOfTerm                   {}
    605     | IndexTerm                     {}
    606     | IndexExpTerm                  {}
    607     | MethodInvocationTerm          {}
    608     ;
    609 
    610 
    611 /*******************************************************************************
    612  *
    613  * ASL Primary Terms
    614  *
    615  ******************************************************************************/
    616 
    617 AccessAsTerm
    618     : PARSEOP_ACCESSAS '('
    619         AccessTypeKeyword
    620         OptionalAccessAttribTerm
    621         ')'                         {$$ = TrCreateNode (PARSEOP_ACCESSAS,2,$3,$4);}
    622     | PARSEOP_ACCESSAS '('
    623         error ')'                   {$$ = AslDoError(); yyclearin;}
    624     ;
    625 
    626 AcquireTerm
    627     : PARSEOP_ACQUIRE '('           {$<n>$ = TrCreateLeafNode (PARSEOP_ACQUIRE);}
    628         SuperName
    629         ',' WordConstExpr
    630         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$6);}
    631     | PARSEOP_ACQUIRE '('
    632         error ')'                   {$$ = AslDoError(); yyclearin;}
    633     ;
    634 
    635 AddTerm
    636     : PARSEOP_ADD '('               {$<n>$ = TrCreateLeafNode (PARSEOP_ADD);}
    637         TermArg
    638         TermArgItem
    639         Target
    640         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
    641     | PARSEOP_ADD '('
    642         error ')'                   {$$ = AslDoError(); yyclearin;}
    643     ;
    644 
    645 AliasTerm
    646     : PARSEOP_ALIAS '('             {$<n>$ = TrCreateLeafNode (PARSEOP_ALIAS);}
    647         NameString
    648         NameStringItem
    649         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,
    650                                         TrSetNodeFlags ($5, NODE_IS_NAME_DECLARATION));}
    651     | PARSEOP_ALIAS '('
    652         error ')'                   {$$ = AslDoError(); yyclearin;}
    653     ;
    654 
    655 AndTerm
    656     : PARSEOP_AND '('               {$<n>$ = TrCreateLeafNode (PARSEOP_AND);}
    657         TermArg
    658         TermArgItem
    659         Target
    660         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
    661     | PARSEOP_AND '('
    662         error ')'                   {$$ = AslDoError(); yyclearin;}
    663     ;
    664 
    665 ArgTerm
    666     : PARSEOP_ARG0                  {$$ = TrCreateLeafNode (PARSEOP_ARG0);}
    667     | PARSEOP_ARG1                  {$$ = TrCreateLeafNode (PARSEOP_ARG1);}
    668     | PARSEOP_ARG2                  {$$ = TrCreateLeafNode (PARSEOP_ARG2);}
    669     | PARSEOP_ARG3                  {$$ = TrCreateLeafNode (PARSEOP_ARG3);}
    670     | PARSEOP_ARG4                  {$$ = TrCreateLeafNode (PARSEOP_ARG4);}
    671     | PARSEOP_ARG5                  {$$ = TrCreateLeafNode (PARSEOP_ARG5);}
    672     | PARSEOP_ARG6                  {$$ = TrCreateLeafNode (PARSEOP_ARG6);}
    673     ;
    674 
    675 BankFieldTerm
    676     : PARSEOP_BANKFIELD '('         {$<n>$ = TrCreateLeafNode (PARSEOP_BANKFIELD);}
    677         NameString
    678         NameStringItem
    679         TermArgItem
    680         ',' AccessTypeKeyword
    681         ',' LockRuleKeyword
    682         ',' UpdateRuleKeyword
    683         ')' '{'
    684             FieldUnitList '}'       {$$ = TrLinkChildren ($<n>3,7,$4,$5,$6,$8,$10,$12,$15);}
    685     | PARSEOP_BANKFIELD '('
    686         error ')' '{' error '}'     {$$ = AslDoError(); yyclearin;}
    687     ;
    688 
    689 BreakTerm
    690     : PARSEOP_BREAK                 {$$ = TrCreateNode (PARSEOP_BREAK, 0);}
    691     ;
    692 
    693 BreakPointTerm
    694     : PARSEOP_BREAKPOINT            {$$ = TrCreateNode (PARSEOP_BREAKPOINT, 0);}
    695     ;
    696 
    697 BufferTerm
    698     : PARSEOP_BUFFER '('            {$<n>$ = TrCreateLeafNode (PARSEOP_BUFFER);}
    699         OptionalBufferLength
    700         ')' '{'
    701             BufferTermData '}'      {$$ = TrLinkChildren ($<n>3,2,$4,$7);}
    702     | PARSEOP_BUFFER '('
    703         error ')'                   {$$ = AslDoError(); yyclearin;}
    704     ;
    705 
    706 BufferTermData
    707     : ByteList                      {}
    708     | StringData                    {}
    709     ;
    710 
    711 CaseTerm
    712     : PARSEOP_CASE '('              {$<n>$ = TrCreateLeafNode (PARSEOP_CASE);}
    713         DataObject
    714         ')' '{'
    715             TermList '}'            {$$ = TrLinkChildren ($<n>3,2,$4,$7);}
    716     | PARSEOP_CASE '('
    717         error ')'                   {$$ = AslDoError(); yyclearin;}
    718     ;
    719 
    720 ConcatTerm
    721     : PARSEOP_CONCATENATE '('       {$<n>$ = TrCreateLeafNode (PARSEOP_CONCATENATE);}
    722         TermArg
    723         TermArgItem
    724         Target
    725         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
    726     | PARSEOP_CONCATENATE '('
    727         error ')'                   {$$ = AslDoError(); yyclearin;}
    728     ;
    729 
    730 ConcatResTerm
    731     : PARSEOP_CONCATENATERESTEMPLATE '('    {$<n>$ = TrCreateLeafNode (PARSEOP_CONCATENATERESTEMPLATE);}
    732         TermArg
    733         TermArgItem
    734         Target
    735         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
    736     | PARSEOP_CONCATENATERESTEMPLATE '('
    737         error ')'                   {$$ = AslDoError(); yyclearin;}
    738     ;
    739 
    740 ConnectionTerm
    741     : PARSEOP_CONNECTION '('
    742         NameString
    743         ')'                         {$$ = TrCreateNode (PARSEOP_CONNECTION,1,$3);}
    744     | PARSEOP_CONNECTION '('        {$<n>$ = TrCreateLeafNode (PARSEOP_CONNECTION);}
    745         ResourceMacroTerm
    746         ')'                         {$$ = TrLinkChildren ($<n>3, 1,
    747                                             TrLinkChildren (TrCreateLeafNode (PARSEOP_RESOURCETEMPLATE), 3,
    748                                                 TrCreateLeafNode (PARSEOP_DEFAULT_ARG),
    749                                                 TrCreateLeafNode (PARSEOP_DEFAULT_ARG),
    750                                                 $4));}
    751     | PARSEOP_CONNECTION '('
    752         error ')'                   {$$ = AslDoError(); yyclearin;}
    753     ;
    754 
    755 CondRefOfTerm
    756     : PARSEOP_CONDREFOF '('         {$<n>$ = TrCreateLeafNode (PARSEOP_CONDREFOF);}
    757         SuperName
    758         Target
    759         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
    760     | PARSEOP_CONDREFOF '('
    761         error ')'                   {$$ = AslDoError(); yyclearin;}
    762     ;
    763 
    764 ContinueTerm
    765     : PARSEOP_CONTINUE              {$$ = TrCreateNode (PARSEOP_CONTINUE, 0);}
    766     ;
    767 
    768 CopyObjectTerm
    769     : PARSEOP_COPYOBJECT '('        {$<n>$ = TrCreateLeafNode (PARSEOP_COPYOBJECT);}
    770         TermArg
    771         ',' SimpleTarget
    772         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,TrSetNodeFlags ($6, NODE_IS_TARGET));}
    773     | PARSEOP_COPYOBJECT '('
    774         error ')'                   {$$ = AslDoError(); yyclearin;}
    775     ;
    776 
    777 CreateBitFieldTerm
    778     : PARSEOP_CREATEBITFIELD '('    {$<n>$ = TrCreateLeafNode (PARSEOP_CREATEBITFIELD);}
    779         TermArg
    780         TermArgItem
    781         NameStringItem
    782         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,TrSetNodeFlags ($6, NODE_IS_NAME_DECLARATION));}
    783     | PARSEOP_CREATEBITFIELD '('
    784         error ')'                   {$$ = AslDoError(); yyclearin;}
    785     ;
    786 
    787 CreateByteFieldTerm
    788     : PARSEOP_CREATEBYTEFIELD '('   {$<n>$ = TrCreateLeafNode (PARSEOP_CREATEBYTEFIELD);}
    789         TermArg
    790         TermArgItem
    791         NameStringItem
    792         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,TrSetNodeFlags ($6, NODE_IS_NAME_DECLARATION));}
    793     | PARSEOP_CREATEBYTEFIELD '('
    794         error ')'                   {$$ = AslDoError(); yyclearin;}
    795     ;
    796 
    797 CreateDWordFieldTerm
    798     : PARSEOP_CREATEDWORDFIELD '('  {$<n>$ = TrCreateLeafNode (PARSEOP_CREATEDWORDFIELD);}
    799         TermArg
    800         TermArgItem
    801         NameStringItem
    802         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,TrSetNodeFlags ($6, NODE_IS_NAME_DECLARATION));}
    803     | PARSEOP_CREATEDWORDFIELD '('
    804         error ')'                   {$$ = AslDoError(); yyclearin;}
    805     ;
    806 
    807 CreateFieldTerm
    808     : PARSEOP_CREATEFIELD '('       {$<n>$ = TrCreateLeafNode (PARSEOP_CREATEFIELD);}
    809         TermArg
    810         TermArgItem
    811         TermArgItem
    812         NameStringItem
    813         ')'                         {$$ = TrLinkChildren ($<n>3,4,$4,$5,$6,TrSetNodeFlags ($7, NODE_IS_NAME_DECLARATION));}
    814     | PARSEOP_CREATEFIELD '('
    815         error ')'                   {$$ = AslDoError(); yyclearin;}
    816     ;
    817 
    818 CreateQWordFieldTerm
    819     : PARSEOP_CREATEQWORDFIELD '('  {$<n>$ = TrCreateLeafNode (PARSEOP_CREATEQWORDFIELD);}
    820         TermArg
    821         TermArgItem
    822         NameStringItem
    823         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,TrSetNodeFlags ($6, NODE_IS_NAME_DECLARATION));}
    824     | PARSEOP_CREATEQWORDFIELD '('
    825         error ')'                   {$$ = AslDoError(); yyclearin;}
    826     ;
    827 
    828 CreateWordFieldTerm
    829     : PARSEOP_CREATEWORDFIELD '('   {$<n>$ = TrCreateLeafNode (PARSEOP_CREATEWORDFIELD);}
    830         TermArg
    831         TermArgItem
    832         NameStringItem
    833         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,TrSetNodeFlags ($6, NODE_IS_NAME_DECLARATION));}
    834     | PARSEOP_CREATEWORDFIELD '('
    835         error ')'                   {$$ = AslDoError(); yyclearin;}
    836     ;
    837 
    838 DataRegionTerm
    839     : PARSEOP_DATATABLEREGION '('   {$<n>$ = TrCreateLeafNode (PARSEOP_DATATABLEREGION);}
    840         NameString
    841         TermArgItem
    842         TermArgItem
    843         TermArgItem
    844         ')'                         {$$ = TrLinkChildren ($<n>3,4,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$5,$6,$7);}
    845     | PARSEOP_DATATABLEREGION '('
    846         error ')'                   {$$ = AslDoError(); yyclearin;}
    847     ;
    848 
    849 DebugTerm
    850     : PARSEOP_DEBUG                 {$$ = TrCreateLeafNode (PARSEOP_DEBUG);}
    851     ;
    852 
    853 DecTerm
    854     : PARSEOP_DECREMENT '('         {$<n>$ = TrCreateLeafNode (PARSEOP_DECREMENT);}
    855         SuperName
    856         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
    857     | PARSEOP_DECREMENT '('
    858         error ')'                   {$$ = AslDoError(); yyclearin;}
    859     ;
    860 
    861 DefaultTerm
    862     : PARSEOP_DEFAULT '{'           {$<n>$ = TrCreateLeafNode (PARSEOP_DEFAULT);}
    863         TermList '}'                {$$ = TrLinkChildren ($<n>3,1,$4);}
    864     | PARSEOP_DEFAULT '{'
    865         error '}'                   {$$ = AslDoError(); yyclearin;}
    866     ;
    867 
    868 DerefOfTerm
    869     : PARSEOP_DEREFOF '('           {$<n>$ = TrCreateLeafNode (PARSEOP_DEREFOF);}
    870         TermArg
    871         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
    872     | PARSEOP_DEREFOF '('
    873         error ')'                   {$$ = AslDoError(); yyclearin;}
    874     ;
    875 
    876 DeviceTerm
    877     : PARSEOP_DEVICE '('            {$<n>$ = TrCreateLeafNode (PARSEOP_DEVICE);}
    878         NameString
    879         ')' '{'
    880             TermList '}'            {$$ = TrLinkChildren ($<n>3,2,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$7);}
    881     | PARSEOP_DEVICE '('
    882         error ')'                   {$$ = AslDoError(); yyclearin;}
    883     ;
    884 
    885 DivideTerm
    886     : PARSEOP_DIVIDE '('            {$<n>$ = TrCreateLeafNode (PARSEOP_DIVIDE);}
    887         TermArg
    888         TermArgItem
    889         Target
    890         Target
    891         ')'                         {$$ = TrLinkChildren ($<n>3,4,$4,$5,$6,$7);}
    892     | PARSEOP_DIVIDE '('
    893         error ')'                   {$$ = AslDoError(); yyclearin;}
    894     ;
    895 
    896 EISAIDTerm
    897     : PARSEOP_EISAID '('
    898         StringData ')'              {$$ = TrUpdateNode (PARSEOP_EISAID, $3);}
    899     | PARSEOP_EISAID '('
    900         error ')'                   {$$ = AslDoError(); yyclearin;}
    901     ;
    902 
    903 ElseIfTerm
    904     : IfTerm ElseTerm               {$$ = TrLinkPeerNode ($1,$2);}
    905     ;
    906 
    907 ElseTerm
    908     :                               {$$ = NULL;}
    909     | PARSEOP_ELSE '{'              {$<n>$ = TrCreateLeafNode (PARSEOP_ELSE);}
    910         TermList '}'                {$$ = TrLinkChildren ($<n>3,1,$4);}
    911 
    912     | PARSEOP_ELSE '{'
    913         error '}'                   {$$ = AslDoError(); yyclearin;}
    914 
    915     | PARSEOP_ELSE
    916         error                       {$$ = AslDoError(); yyclearin;}
    917 
    918     | PARSEOP_ELSEIF '('            {$<n>$ = TrCreateLeafNode (PARSEOP_ELSE);}
    919         TermArg                     {$<n>$ = TrCreateLeafNode (PARSEOP_IF);}
    920         ')' '{'
    921             TermList '}'            {TrLinkChildren ($<n>5,2,$4,$8);}
    922         ElseTerm                    {TrLinkPeerNode ($<n>5,$11);}
    923                                     {$$ = TrLinkChildren ($<n>3,1,$<n>5);}
    924 
    925     | PARSEOP_ELSEIF '('
    926         error ')'                   {$$ = AslDoError(); yyclearin;}
    927 
    928     | PARSEOP_ELSEIF
    929         error                       {$$ = AslDoError(); yyclearin;}
    930     ;
    931 
    932 EventTerm
    933     : PARSEOP_EVENT '('             {$<n>$ = TrCreateLeafNode (PARSEOP_EVENT);}
    934         NameString
    935         ')'                         {$$ = TrLinkChildren ($<n>3,1,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION));}
    936     | PARSEOP_EVENT '('
    937         error ')'                   {$$ = AslDoError(); yyclearin;}
    938     ;
    939 
    940 ExternalTerm
    941     : PARSEOP_EXTERNAL '('
    942         NameString
    943         OptionalObjectTypeKeyword
    944         OptionalParameterTypePackage
    945         OptionalParameterTypesPackage
    946         ')'                         {$$ = TrCreateNode (PARSEOP_EXTERNAL,4,$3,$4,$5,$6);}
    947     | PARSEOP_EXTERNAL '('
    948         error ')'                   {$$ = AslDoError(); yyclearin;}
    949     ;
    950 
    951 FatalTerm
    952     : PARSEOP_FATAL '('             {$<n>$ = TrCreateLeafNode (PARSEOP_FATAL);}
    953         ByteConstExpr
    954         ',' DWordConstExpr
    955         TermArgItem
    956         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$6,$7);}
    957     | PARSEOP_FATAL '('
    958         error ')'                   {$$ = AslDoError(); yyclearin;}
    959     ;
    960 
    961 FieldTerm
    962     : PARSEOP_FIELD '('             {$<n>$ = TrCreateLeafNode (PARSEOP_FIELD);}
    963         NameString
    964         ',' AccessTypeKeyword
    965         ',' LockRuleKeyword
    966         ',' UpdateRuleKeyword
    967         ')' '{'
    968             FieldUnitList '}'       {$$ = TrLinkChildren ($<n>3,5,$4,$6,$8,$10,$13);}
    969     | PARSEOP_FIELD '('
    970         error ')' '{' error '}'     {$$ = AslDoError(); yyclearin;}
    971     ;
    972 
    973 FindSetLeftBitTerm
    974     : PARSEOP_FINDSETLEFTBIT '('    {$<n>$ = TrCreateLeafNode (PARSEOP_FINDSETLEFTBIT);}
    975         TermArg
    976         Target
    977         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
    978     | PARSEOP_FINDSETLEFTBIT '('
    979         error ')'                   {$$ = AslDoError(); yyclearin;}
    980     ;
    981 
    982 FindSetRightBitTerm
    983     : PARSEOP_FINDSETRIGHTBIT '('   {$<n>$ = TrCreateLeafNode (PARSEOP_FINDSETRIGHTBIT);}
    984         TermArg
    985         Target
    986         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
    987     | PARSEOP_FINDSETRIGHTBIT '('
    988         error ')'                   {$$ = AslDoError(); yyclearin;}
    989     ;
    990 
    991     /* Convert a For() loop to a While() loop */
    992 ForTerm
    993     : PARSEOP_FOR '('               {$<n>$ = TrCreateLeafNode (PARSEOP_WHILE);}
    994         OptionalTermArg ','         {}
    995         OptionalPredicate ','
    996         OptionalTermArg             {$<n>$ = TrLinkPeerNode ($4,$<n>3);
    997                                         TrSetParent ($9,$<n>3);}                /* New parent is WHILE */
    998         ')' '{' TermList '}'        {$<n>$ = TrLinkChildren ($<n>3,2,$7,$13);}
    999                                     {$<n>$ = TrLinkPeerNode ($13,$9);
   1000                                         $$ = $<n>10;}
   1001     ;
   1002 
   1003 OptionalPredicate
   1004     :                               {$$ = TrCreateValuedLeafNode (PARSEOP_INTEGER, 1);}
   1005     | TermArg                       {$$ = $1;}
   1006     ;
   1007 
   1008 FprintfTerm
   1009     : PARSEOP_FPRINTF '('            {$<n>$ = TrCreateLeafNode (PARSEOP_FPRINTF);}
   1010         TermArg ','
   1011         StringData
   1012         PrintfArgList
   1013         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$6,$7);}
   1014     | PARSEOP_FPRINTF '('
   1015         error ')'                   {$$ = AslDoError(); yyclearin;}
   1016     ;
   1017 
   1018 FromBCDTerm
   1019     : PARSEOP_FROMBCD '('           {$<n>$ = TrCreateLeafNode (PARSEOP_FROMBCD);}
   1020         TermArg
   1021         Target
   1022         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1023     | PARSEOP_FROMBCD '('
   1024         error ')'                   {$$ = AslDoError(); yyclearin;}
   1025     ;
   1026 
   1027 FunctionTerm
   1028     : PARSEOP_FUNCTION '('          {$<n>$ = TrCreateLeafNode (PARSEOP_METHOD);}
   1029         NameString
   1030         OptionalParameterTypePackage
   1031         OptionalParameterTypesPackage
   1032         ')' '{'
   1033             TermList '}'            {$$ = TrLinkChildren ($<n>3,7,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),
   1034                                         TrCreateValuedLeafNode (PARSEOP_BYTECONST, 0),
   1035                                         TrCreateLeafNode (PARSEOP_SERIALIZERULE_NOTSERIAL),
   1036                                         TrCreateValuedLeafNode (PARSEOP_BYTECONST, 0),$5,$6,$9);}
   1037     | PARSEOP_FUNCTION '('
   1038         error ')'                   {$$ = AslDoError(); yyclearin;}
   1039     ;
   1040 
   1041 IfTerm
   1042     : PARSEOP_IF '('                {$<n>$ = TrCreateLeafNode (PARSEOP_IF);}
   1043         TermArg
   1044         ')' '{'
   1045             TermList '}'            {$$ = TrLinkChildren ($<n>3,2,$4,$7);}
   1046 
   1047     | PARSEOP_IF '('
   1048         error ')'                   {$$ = AslDoError(); yyclearin;}
   1049     ;
   1050 
   1051 IncludeTerm
   1052     : PARSEOP_INCLUDE '('
   1053         String  ')'                 {$$ = TrUpdateNode (PARSEOP_INCLUDE, $3);
   1054                                         FlOpenIncludeFile ($3);}
   1055     ;
   1056 
   1057 IncludeEndTerm
   1058     : PARSEOP_INCLUDE_END           {$<n>$ = TrCreateLeafNode (PARSEOP_INCLUDE_END); TrSetCurrentFilename ($$);}
   1059     ;
   1060 
   1061 IncTerm
   1062     : PARSEOP_INCREMENT '('         {$<n>$ = TrCreateLeafNode (PARSEOP_INCREMENT);}
   1063         SuperName
   1064         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1065     | PARSEOP_INCREMENT '('
   1066         error ')'                   {$$ = AslDoError(); yyclearin;}
   1067     ;
   1068 
   1069 IndexFieldTerm
   1070     : PARSEOP_INDEXFIELD '('        {$<n>$ = TrCreateLeafNode (PARSEOP_INDEXFIELD);}
   1071         NameString
   1072         NameStringItem
   1073         ',' AccessTypeKeyword
   1074         ',' LockRuleKeyword
   1075         ',' UpdateRuleKeyword
   1076         ')' '{'
   1077             FieldUnitList '}'       {$$ = TrLinkChildren ($<n>3,6,$4,$5,$7,$9,$11,$14);}
   1078     | PARSEOP_INDEXFIELD '('
   1079         error ')' '{' error '}'     {$$ = AslDoError(); yyclearin;}
   1080     ;
   1081 
   1082 IndexTerm
   1083     : PARSEOP_INDEX '('             {$<n>$ = TrCreateLeafNode (PARSEOP_INDEX);}
   1084         TermArg
   1085         TermArgItem
   1086         Target
   1087         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1088     | PARSEOP_INDEX '('
   1089         error ')'                   {$$ = AslDoError(); yyclearin;}
   1090     ;
   1091 
   1092 LAndTerm
   1093     : PARSEOP_LAND '('              {$<n>$ = TrCreateLeafNode (PARSEOP_LAND);}
   1094         TermArg
   1095         TermArgItem
   1096         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1097     | PARSEOP_LAND '('
   1098         error ')'                   {$$ = AslDoError(); yyclearin;}
   1099     ;
   1100 
   1101 LEqualTerm
   1102     : PARSEOP_LEQUAL '('            {$<n>$ = TrCreateLeafNode (PARSEOP_LEQUAL);}
   1103         TermArg
   1104         TermArgItem
   1105         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1106     | PARSEOP_LEQUAL '('
   1107         error ')'                   {$$ = AslDoError(); yyclearin;}
   1108     ;
   1109 
   1110 LGreaterEqualTerm
   1111     : PARSEOP_LGREATEREQUAL '('     {$<n>$ = TrCreateLeafNode (PARSEOP_LLESS);}
   1112         TermArg
   1113         TermArgItem
   1114         ')'                         {$$ = TrCreateNode (PARSEOP_LNOT, 1, TrLinkChildren ($<n>3,2,$4,$5));}
   1115     | PARSEOP_LGREATEREQUAL '('
   1116         error ')'                   {$$ = AslDoError(); yyclearin;}
   1117     ;
   1118 
   1119 LGreaterTerm
   1120     : PARSEOP_LGREATER '('          {$<n>$ = TrCreateLeafNode (PARSEOP_LGREATER);}
   1121         TermArg
   1122         TermArgItem
   1123         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1124     | PARSEOP_LGREATER '('
   1125         error ')'                   {$$ = AslDoError(); yyclearin;}
   1126     ;
   1127 
   1128 LLessEqualTerm
   1129     : PARSEOP_LLESSEQUAL '('        {$<n>$ = TrCreateLeafNode (PARSEOP_LGREATER);}
   1130         TermArg
   1131         TermArgItem
   1132         ')'                         {$$ = TrCreateNode (PARSEOP_LNOT, 1, TrLinkChildren ($<n>3,2,$4,$5));}
   1133     | PARSEOP_LLESSEQUAL '('
   1134         error ')'                   {$$ = AslDoError(); yyclearin;}
   1135     ;
   1136 
   1137 LLessTerm
   1138     : PARSEOP_LLESS '('             {$<n>$ = TrCreateLeafNode (PARSEOP_LLESS);}
   1139         TermArg
   1140         TermArgItem
   1141         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1142     | PARSEOP_LLESS '('
   1143         error ')'                   {$$ = AslDoError(); yyclearin;}
   1144     ;
   1145 
   1146 LNotEqualTerm
   1147     : PARSEOP_LNOTEQUAL '('         {$<n>$ = TrCreateLeafNode (PARSEOP_LEQUAL);}
   1148         TermArg
   1149         TermArgItem
   1150         ')'                         {$$ = TrCreateNode (PARSEOP_LNOT, 1, TrLinkChildren ($<n>3,2,$4,$5));}
   1151     | PARSEOP_LNOTEQUAL '('
   1152         error ')'                   {$$ = AslDoError(); yyclearin;}
   1153     ;
   1154 
   1155 LNotTerm
   1156     : PARSEOP_LNOT '('              {$<n>$ = TrCreateLeafNode (PARSEOP_LNOT);}
   1157         TermArg
   1158         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1159     | PARSEOP_LNOT '('
   1160         error ')'                   {$$ = AslDoError(); yyclearin;}
   1161     ;
   1162 
   1163 LoadTableTerm
   1164     : PARSEOP_LOADTABLE '('         {$<n>$ = TrCreateLeafNode (PARSEOP_LOADTABLE);}
   1165         TermArg
   1166         TermArgItem
   1167         TermArgItem
   1168         OptionalListString
   1169         OptionalListString
   1170         OptionalReference
   1171         ')'                         {$$ = TrLinkChildren ($<n>3,6,$4,$5,$6,$7,$8,$9);}
   1172     | PARSEOP_LOADTABLE '('
   1173         error ')'                   {$$ = AslDoError(); yyclearin;}
   1174     ;
   1175 
   1176 LoadTerm
   1177     : PARSEOP_LOAD '('              {$<n>$ = TrCreateLeafNode (PARSEOP_LOAD);}
   1178         NameString
   1179         RequiredTarget
   1180         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1181     | PARSEOP_LOAD '('
   1182         error ')'                   {$$ = AslDoError(); yyclearin;}
   1183     ;
   1184 
   1185 LocalTerm
   1186     : PARSEOP_LOCAL0                {$$ = TrCreateLeafNode (PARSEOP_LOCAL0);}
   1187     | PARSEOP_LOCAL1                {$$ = TrCreateLeafNode (PARSEOP_LOCAL1);}
   1188     | PARSEOP_LOCAL2                {$$ = TrCreateLeafNode (PARSEOP_LOCAL2);}
   1189     | PARSEOP_LOCAL3                {$$ = TrCreateLeafNode (PARSEOP_LOCAL3);}
   1190     | PARSEOP_LOCAL4                {$$ = TrCreateLeafNode (PARSEOP_LOCAL4);}
   1191     | PARSEOP_LOCAL5                {$$ = TrCreateLeafNode (PARSEOP_LOCAL5);}
   1192     | PARSEOP_LOCAL6                {$$ = TrCreateLeafNode (PARSEOP_LOCAL6);}
   1193     | PARSEOP_LOCAL7                {$$ = TrCreateLeafNode (PARSEOP_LOCAL7);}
   1194     ;
   1195 
   1196 LOrTerm
   1197     : PARSEOP_LOR '('               {$<n>$ = TrCreateLeafNode (PARSEOP_LOR);}
   1198         TermArg
   1199         TermArgItem
   1200         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1201     | PARSEOP_LOR '('
   1202         error ')'                   {$$ = AslDoError(); yyclearin;}
   1203     ;
   1204 
   1205 MatchTerm
   1206     : PARSEOP_MATCH '('             {$<n>$ = TrCreateLeafNode (PARSEOP_MATCH);}
   1207         TermArg
   1208         ',' MatchOpKeyword
   1209         TermArgItem
   1210         ',' MatchOpKeyword
   1211         TermArgItem
   1212         TermArgItem
   1213         ')'                         {$$ = TrLinkChildren ($<n>3,6,$4,$6,$7,$9,$10,$11);}
   1214     | PARSEOP_MATCH '('
   1215         error ')'                   {$$ = AslDoError(); yyclearin;}
   1216     ;
   1217 
   1218 MethodTerm
   1219     : PARSEOP_METHOD  '('           {$<n>$ = TrCreateLeafNode (PARSEOP_METHOD);}
   1220         NameString
   1221         OptionalByteConstExpr       {UtCheckIntegerRange ($5, 0, 7);}
   1222         OptionalSerializeRuleKeyword
   1223         OptionalByteConstExpr
   1224         OptionalParameterTypePackage
   1225         OptionalParameterTypesPackage
   1226         ')' '{'
   1227             TermList '}'            {$$ = TrLinkChildren ($<n>3,7,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$5,$7,$8,$9,$10,$13);}
   1228     | PARSEOP_METHOD '('
   1229         error ')'                   {$$ = AslDoError(); yyclearin;}
   1230     ;
   1231 
   1232 MidTerm
   1233     : PARSEOP_MID '('               {$<n>$ = TrCreateLeafNode (PARSEOP_MID);}
   1234         TermArg
   1235         TermArgItem
   1236         TermArgItem
   1237         Target
   1238         ')'                         {$$ = TrLinkChildren ($<n>3,4,$4,$5,$6,$7);}
   1239     | PARSEOP_MID '('
   1240         error ')'                   {$$ = AslDoError(); yyclearin;}
   1241     ;
   1242 
   1243 ModTerm
   1244     : PARSEOP_MOD '('               {$<n>$ = TrCreateLeafNode (PARSEOP_MOD);}
   1245         TermArg
   1246         TermArgItem
   1247         Target
   1248         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1249     | PARSEOP_MOD '('
   1250         error ')'                   {$$ = AslDoError(); yyclearin;}
   1251     ;
   1252 
   1253 MultiplyTerm
   1254     : PARSEOP_MULTIPLY '('          {$<n>$ = TrCreateLeafNode (PARSEOP_MULTIPLY);}
   1255         TermArg
   1256         TermArgItem
   1257         Target
   1258         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1259     | PARSEOP_MULTIPLY '('
   1260         error ')'                   {$$ = AslDoError(); yyclearin;}
   1261     ;
   1262 
   1263 MutexTerm
   1264     : PARSEOP_MUTEX '('             {$<n>$ = TrCreateLeafNode (PARSEOP_MUTEX);}
   1265         NameString
   1266         ',' ByteConstExpr
   1267         ')'                         {$$ = TrLinkChildren ($<n>3,2,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$6);}
   1268     | PARSEOP_MUTEX '('
   1269         error ')'                   {$$ = AslDoError(); yyclearin;}
   1270     ;
   1271 
   1272 NameTerm
   1273     : PARSEOP_NAME '('              {$<n>$ = TrCreateLeafNode (PARSEOP_NAME);}
   1274         NameString
   1275         ',' DataObject
   1276         ')'                         {$$ = TrLinkChildren ($<n>3,2,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$6);}
   1277     | PARSEOP_NAME '('
   1278         error ')'                   {$$ = AslDoError(); yyclearin;}
   1279     ;
   1280 
   1281 NAndTerm
   1282     : PARSEOP_NAND '('              {$<n>$ = TrCreateLeafNode (PARSEOP_NAND);}
   1283         TermArg
   1284         TermArgItem
   1285         Target
   1286         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1287     | PARSEOP_NAND '('
   1288         error ')'                   {$$ = AslDoError(); yyclearin;}
   1289     ;
   1290 
   1291 NoOpTerm
   1292     : PARSEOP_NOOP                  {$$ = TrCreateNode (PARSEOP_NOOP, 0);}
   1293     ;
   1294 
   1295 NOrTerm
   1296     : PARSEOP_NOR '('               {$<n>$ = TrCreateLeafNode (PARSEOP_NOR);}
   1297         TermArg
   1298         TermArgItem
   1299         Target
   1300         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1301     | PARSEOP_NOR '('
   1302         error ')'                   {$$ = AslDoError(); yyclearin;}
   1303     ;
   1304 
   1305 NotifyTerm
   1306     : PARSEOP_NOTIFY '('            {$<n>$ = TrCreateLeafNode (PARSEOP_NOTIFY);}
   1307         SuperName
   1308         TermArgItem
   1309         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1310     | PARSEOP_NOTIFY '('
   1311         error ')'                   {$$ = AslDoError(); yyclearin;}
   1312     ;
   1313 
   1314 NotTerm
   1315     : PARSEOP_NOT '('               {$<n>$ = TrCreateLeafNode (PARSEOP_NOT);}
   1316         TermArg
   1317         Target
   1318         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1319     | PARSEOP_NOT '('
   1320         error ')'                   {$$ = AslDoError(); yyclearin;}
   1321     ;
   1322 
   1323 ObjectTypeTerm
   1324     : PARSEOP_OBJECTTYPE '('        {$<n>$ = TrCreateLeafNode (PARSEOP_OBJECTTYPE);}
   1325         ObjectTypeName
   1326         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1327     | PARSEOP_OBJECTTYPE '('
   1328         error ')'                   {$$ = AslDoError(); yyclearin;}
   1329     ;
   1330 
   1331 OffsetTerm
   1332     : PARSEOP_OFFSET '('
   1333         AmlPackageLengthTerm
   1334         ')'                         {$$ = TrCreateNode (PARSEOP_OFFSET,1,$3);}
   1335     | PARSEOP_OFFSET '('
   1336         error ')'                   {$$ = AslDoError(); yyclearin;}
   1337     ;
   1338 
   1339 OpRegionTerm
   1340     : PARSEOP_OPERATIONREGION '('   {$<n>$ = TrCreateLeafNode (PARSEOP_OPERATIONREGION);}
   1341         NameString
   1342         ',' OpRegionSpaceIdTerm
   1343         TermArgItem
   1344         TermArgItem
   1345         ')'                         {$$ = TrLinkChildren ($<n>3,4,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$6,$7,$8);}
   1346     | PARSEOP_OPERATIONREGION '('
   1347         error ')'                   {$$ = AslDoError(); yyclearin;}
   1348     ;
   1349 
   1350 OpRegionSpaceIdTerm
   1351     : RegionSpaceKeyword            {}
   1352     | ByteConst                     {$$ = UtCheckIntegerRange ($1, 0x80, 0xFF);}
   1353     ;
   1354 
   1355 OrTerm
   1356     : PARSEOP_OR '('                {$<n>$ = TrCreateLeafNode (PARSEOP_OR);}
   1357         TermArg
   1358         TermArgItem
   1359         Target
   1360         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1361     | PARSEOP_OR '('
   1362         error ')'                   {$$ = AslDoError(); yyclearin;}
   1363     ;
   1364 
   1365 PackageTerm
   1366     : PARSEOP_PACKAGE '('           {$<n>$ = TrCreateLeafNode (PARSEOP_VAR_PACKAGE);}
   1367         VarPackageLengthTerm
   1368         ')' '{'
   1369             PackageList '}'         {$$ = TrLinkChildren ($<n>3,2,$4,$7);}
   1370     | PARSEOP_PACKAGE '('
   1371         error ')'                   {$$ = AslDoError(); yyclearin;}
   1372     ;
   1373 
   1374 PowerResTerm
   1375     : PARSEOP_POWERRESOURCE '('     {$<n>$ = TrCreateLeafNode (PARSEOP_POWERRESOURCE);}
   1376         NameString
   1377         ',' ByteConstExpr
   1378         ',' WordConstExpr
   1379         ')' '{'
   1380             TermList '}'            {$$ = TrLinkChildren ($<n>3,4,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$6,$8,$11);}
   1381     | PARSEOP_POWERRESOURCE '('
   1382         error ')'                   {$$ = AslDoError(); yyclearin;}
   1383     ;
   1384 
   1385 PrintfTerm
   1386     : PARSEOP_PRINTF '('            {$<n>$ = TrCreateLeafNode (PARSEOP_PRINTF);}
   1387         StringData
   1388         PrintfArgList
   1389         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1390     | PARSEOP_PRINTF '('
   1391         error ')'                   {$$ = AslDoError(); yyclearin;}
   1392     ;
   1393 
   1394 PrintfArgList
   1395     :                               {$$ = NULL;}
   1396     | TermArg                       {$$ = $1;}
   1397     | PrintfArgList ','
   1398        TermArg                      {$$ = TrLinkPeerNode ($1, $3);}
   1399     ;
   1400 
   1401 ProcessorTerm
   1402     : PARSEOP_PROCESSOR '('         {$<n>$ = TrCreateLeafNode (PARSEOP_PROCESSOR);}
   1403         NameString
   1404         ',' ByteConstExpr
   1405         OptionalDWordConstExpr
   1406         OptionalByteConstExpr
   1407         ')' '{'
   1408             TermList '}'            {$$ = TrLinkChildren ($<n>3,5,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$6,$7,$8,$11);}
   1409     | PARSEOP_PROCESSOR '('
   1410         error ')'                   {$$ = AslDoError(); yyclearin;}
   1411     ;
   1412 
   1413 RawDataBufferTerm
   1414     : PARSEOP_DATABUFFER  '('       {$<n>$ = TrCreateLeafNode (PARSEOP_DATABUFFER);}
   1415         OptionalWordConst
   1416         ')' '{'
   1417             ByteList '}'            {$$ = TrLinkChildren ($<n>3,2,$4,$7);}
   1418     | PARSEOP_DATABUFFER '('
   1419         error ')'                   {$$ = AslDoError(); yyclearin;}
   1420     ;
   1421 
   1422 /*
   1423  * In RefOf, the node isn't really a target, but we can't keep track of it after
   1424  * we've taken a pointer to it. (hard to tell if a local becomes initialized this way.)
   1425  */
   1426 RefOfTerm
   1427     : PARSEOP_REFOF '('             {$<n>$ = TrCreateLeafNode (PARSEOP_REFOF);}
   1428         SuperName
   1429         ')'                         {$$ = TrLinkChildren ($<n>3,1,TrSetNodeFlags ($4, NODE_IS_TARGET));}
   1430     | PARSEOP_REFOF '('
   1431         error ')'                   {$$ = AslDoError(); yyclearin;}
   1432     ;
   1433 
   1434 ReleaseTerm
   1435     : PARSEOP_RELEASE '('           {$<n>$ = TrCreateLeafNode (PARSEOP_RELEASE);}
   1436         SuperName
   1437         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1438     | PARSEOP_RELEASE '('
   1439         error ')'                   {$$ = AslDoError(); yyclearin;}
   1440     ;
   1441 
   1442 ResetTerm
   1443     : PARSEOP_RESET '('             {$<n>$ = TrCreateLeafNode (PARSEOP_RESET);}
   1444         SuperName
   1445         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1446     | PARSEOP_RESET '('
   1447         error ')'                   {$$ = AslDoError(); yyclearin;}
   1448     ;
   1449 
   1450 ReturnTerm
   1451     : PARSEOP_RETURN '('            {$<n>$ = TrCreateLeafNode (PARSEOP_RETURN);}
   1452         OptionalReturnArg
   1453         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1454     | PARSEOP_RETURN                {$$ = TrLinkChildren (TrCreateLeafNode (PARSEOP_RETURN),1,TrSetNodeFlags (TrCreateLeafNode (PARSEOP_ZERO), NODE_IS_NULL_RETURN));}
   1455     | PARSEOP_RETURN '('
   1456         error ')'                   {$$ = AslDoError(); yyclearin;}
   1457     ;
   1458 
   1459 ScopeTerm
   1460     : PARSEOP_SCOPE '('             {$<n>$ = TrCreateLeafNode (PARSEOP_SCOPE);}
   1461         NameString
   1462         ')' '{'
   1463             TermList '}'            {$$ = TrLinkChildren ($<n>3,2,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$7);}
   1464     | PARSEOP_SCOPE '('
   1465         error ')'                   {$$ = AslDoError(); yyclearin;}
   1466     ;
   1467 
   1468 ShiftLeftTerm
   1469     : PARSEOP_SHIFTLEFT '('         {$<n>$ = TrCreateLeafNode (PARSEOP_SHIFTLEFT);}
   1470         TermArg
   1471         TermArgItem
   1472         Target
   1473         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1474     | PARSEOP_SHIFTLEFT '('
   1475         error ')'                   {$$ = AslDoError(); yyclearin;}
   1476     ;
   1477 
   1478 ShiftRightTerm
   1479     : PARSEOP_SHIFTRIGHT '('        {$<n>$ = TrCreateLeafNode (PARSEOP_SHIFTRIGHT);}
   1480         TermArg
   1481         TermArgItem
   1482         Target
   1483         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1484     | PARSEOP_SHIFTRIGHT '('
   1485         error ')'                   {$$ = AslDoError(); yyclearin;}
   1486     ;
   1487 
   1488 SignalTerm
   1489     : PARSEOP_SIGNAL '('            {$<n>$ = TrCreateLeafNode (PARSEOP_SIGNAL);}
   1490         SuperName
   1491         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1492     | PARSEOP_SIGNAL '('
   1493         error ')'                   {$$ = AslDoError(); yyclearin;}
   1494     ;
   1495 
   1496 SizeOfTerm
   1497     : PARSEOP_SIZEOF '('            {$<n>$ = TrCreateLeafNode (PARSEOP_SIZEOF);}
   1498         SuperName
   1499         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1500     | PARSEOP_SIZEOF '('
   1501         error ')'                   {$$ = AslDoError(); yyclearin;}
   1502     ;
   1503 
   1504 SleepTerm
   1505     : PARSEOP_SLEEP '('             {$<n>$ = TrCreateLeafNode (PARSEOP_SLEEP);}
   1506         TermArg
   1507         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1508     | PARSEOP_SLEEP '('
   1509         error ')'                   {$$ = AslDoError(); yyclearin;}
   1510     ;
   1511 
   1512 StallTerm
   1513     : PARSEOP_STALL '('             {$<n>$ = TrCreateLeafNode (PARSEOP_STALL);}
   1514         TermArg
   1515         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1516     | PARSEOP_STALL '('
   1517         error ')'                   {$$ = AslDoError(); yyclearin;}
   1518     ;
   1519 
   1520 StoreTerm
   1521     : PARSEOP_STORE '('             {$<n>$ = TrCreateLeafNode (PARSEOP_STORE);}
   1522         TermArg
   1523         ',' SuperName
   1524         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,TrSetNodeFlags ($6, NODE_IS_TARGET));}
   1525     | PARSEOP_STORE '('
   1526         error ')'                   {$$ = AslDoError(); yyclearin;}
   1527     ;
   1528 
   1529 SubtractTerm
   1530     : PARSEOP_SUBTRACT '('          {$<n>$ = TrCreateLeafNode (PARSEOP_SUBTRACT);}
   1531         TermArg
   1532         TermArgItem
   1533         Target
   1534         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1535     | PARSEOP_SUBTRACT '('
   1536         error ')'                   {$$ = AslDoError(); yyclearin;}
   1537     ;
   1538 SwitchTerm
   1539     : PARSEOP_SWITCH '('            {$<n>$ = TrCreateLeafNode (PARSEOP_SWITCH);}
   1540         TermArg
   1541         ')' '{'
   1542             CaseDefaultTermList '}'
   1543                                     {$$ = TrLinkChildren ($<n>3,2,$4,$7);}
   1544     | PARSEOP_SWITCH '('
   1545         error ')'                   {$$ = AslDoError(); yyclearin;}
   1546     ;
   1547 
   1548 ThermalZoneTerm
   1549     : PARSEOP_THERMALZONE '('       {$<n>$ = TrCreateLeafNode (PARSEOP_THERMALZONE);}
   1550         NameString
   1551         ')' '{'
   1552             TermList '}'            {$$ = TrLinkChildren ($<n>3,2,TrSetNodeFlags ($4, NODE_IS_NAME_DECLARATION),$7);}
   1553     | PARSEOP_THERMALZONE '('
   1554         error ')'                   {$$ = AslDoError(); yyclearin;}
   1555     ;
   1556 
   1557 TimerTerm
   1558     : PARSEOP_TIMER '('             {$<n>$ = TrCreateLeafNode (PARSEOP_TIMER);}
   1559         ')'                         {$$ = TrLinkChildren ($<n>3,0);}
   1560     | PARSEOP_TIMER                 {$$ = TrLinkChildren (TrCreateLeafNode (PARSEOP_TIMER),0);}
   1561     | PARSEOP_TIMER '('
   1562         error ')'                   {$$ = AslDoError(); yyclearin;}
   1563     ;
   1564 
   1565 ToBCDTerm
   1566     : PARSEOP_TOBCD '('             {$<n>$ = TrCreateLeafNode (PARSEOP_TOBCD);}
   1567         TermArg
   1568         Target
   1569         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1570     | PARSEOP_TOBCD '('
   1571         error ')'                   {$$ = AslDoError(); yyclearin;}
   1572     ;
   1573 
   1574 ToBufferTerm
   1575     : PARSEOP_TOBUFFER '('          {$<n>$ = TrCreateLeafNode (PARSEOP_TOBUFFER);}
   1576         TermArg
   1577         Target
   1578         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1579     | PARSEOP_TOBUFFER '('
   1580         error ')'                   {$$ = AslDoError(); yyclearin;}
   1581     ;
   1582 
   1583 ToDecimalStringTerm
   1584     : PARSEOP_TODECIMALSTRING '('   {$<n>$ = TrCreateLeafNode (PARSEOP_TODECIMALSTRING);}
   1585         TermArg
   1586         Target
   1587         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1588     | PARSEOP_TODECIMALSTRING '('
   1589         error ')'                   {$$ = AslDoError(); yyclearin;}
   1590     ;
   1591 
   1592 ToHexStringTerm
   1593     : PARSEOP_TOHEXSTRING '('       {$<n>$ = TrCreateLeafNode (PARSEOP_TOHEXSTRING);}
   1594         TermArg
   1595         Target
   1596         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1597     | PARSEOP_TOHEXSTRING '('
   1598         error ')'                   {$$ = AslDoError(); yyclearin;}
   1599     ;
   1600 
   1601 ToIntegerTerm
   1602     : PARSEOP_TOINTEGER '('         {$<n>$ = TrCreateLeafNode (PARSEOP_TOINTEGER);}
   1603         TermArg
   1604         Target
   1605         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1606     | PARSEOP_TOINTEGER '('
   1607         error ')'                   {$$ = AslDoError(); yyclearin;}
   1608     ;
   1609 
   1610 ToPLDTerm
   1611     : PARSEOP_TOPLD '('             {$<n>$ = TrCreateLeafNode (PARSEOP_TOPLD);}
   1612         PldKeywordList
   1613         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1614     | PARSEOP_TOPLD '('
   1615         error ')'                   {$$ = AslDoError(); yyclearin;}
   1616     ;
   1617 
   1618 PldKeywordList
   1619     :                               {$$ = NULL;}
   1620     | PldKeyword
   1621         PARSEOP_EXP_EQUALS Integer  {$$ = TrLinkChildren ($1,1,$3);}
   1622     | PldKeyword
   1623         PARSEOP_EXP_EQUALS String   {$$ = TrLinkChildren ($1,1,$3);}
   1624     | PldKeywordList ','            /* Allows a trailing comma at list end */
   1625     | PldKeywordList ','
   1626         PldKeyword
   1627         PARSEOP_EXP_EQUALS Integer  {$$ = TrLinkPeerNode ($1,TrLinkChildren ($3,1,$5));}
   1628     | PldKeywordList ','
   1629         PldKeyword
   1630         PARSEOP_EXP_EQUALS String   {$$ = TrLinkPeerNode ($1,TrLinkChildren ($3,1,$5));}
   1631     ;
   1632 
   1633 
   1634 ToStringTerm
   1635     : PARSEOP_TOSTRING '('          {$<n>$ = TrCreateLeafNode (PARSEOP_TOSTRING);}
   1636         TermArg
   1637         OptionalCount
   1638         Target
   1639         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1640     | PARSEOP_TOSTRING '('
   1641         error ')'                   {$$ = AslDoError(); yyclearin;}
   1642     ;
   1643 
   1644 ToUUIDTerm
   1645     : PARSEOP_TOUUID '('
   1646         StringData ')'              {$$ = TrUpdateNode (PARSEOP_TOUUID, $3);}
   1647     | PARSEOP_TOUUID '('
   1648         error ')'                   {$$ = AslDoError(); yyclearin;}
   1649     ;
   1650 
   1651 UnicodeTerm
   1652     : PARSEOP_UNICODE '('           {$<n>$ = TrCreateLeafNode (PARSEOP_UNICODE);}
   1653         StringData
   1654         ')'                         {$$ = TrLinkChildren ($<n>3,2,0,$4);}
   1655     | PARSEOP_UNICODE '('
   1656         error ')'                   {$$ = AslDoError(); yyclearin;}
   1657     ;
   1658 
   1659 UnloadTerm
   1660     : PARSEOP_UNLOAD '('            {$<n>$ = TrCreateLeafNode (PARSEOP_UNLOAD);}
   1661         SuperName
   1662         ')'                         {$$ = TrLinkChildren ($<n>3,1,$4);}
   1663     | PARSEOP_UNLOAD '('
   1664         error ')'                   {$$ = AslDoError(); yyclearin;}
   1665     ;
   1666 
   1667 WaitTerm
   1668     : PARSEOP_WAIT '('              {$<n>$ = TrCreateLeafNode (PARSEOP_WAIT);}
   1669         SuperName
   1670         TermArgItem
   1671         ')'                         {$$ = TrLinkChildren ($<n>3,2,$4,$5);}
   1672     | PARSEOP_WAIT '('
   1673         error ')'                   {$$ = AslDoError(); yyclearin;}
   1674     ;
   1675 
   1676 XOrTerm
   1677     : PARSEOP_XOR '('               {$<n>$ = TrCreateLeafNode (PARSEOP_XOR);}
   1678         TermArg
   1679         TermArgItem
   1680         Target
   1681         ')'                         {$$ = TrLinkChildren ($<n>3,3,$4,$5,$6);}
   1682     | PARSEOP_XOR '('
   1683         error ')'                   {$$ = AslDoError(); yyclearin;}
   1684     ;
   1685 
   1686 WhileTerm
   1687     : PARSEOP_WHILE '('             {$<n>$ = TrCreateLeafNode (PARSEOP_WHILE);}
   1688         TermArg
   1689         ')' '{' TermList '}'
   1690                                     {$$ = TrLinkChildren ($<n>3,2,$4,$7);}
   1691     | PARSEOP_WHILE '('
   1692         error ')'                   {$$ = AslDoError(); yyclearin;}
   1693     ;
   1694 
   1695 
   1696 /*******************************************************************************
   1697  *
   1698  * ASL Helper Terms
   1699  *
   1700  ******************************************************************************/
   1701 
   1702 AmlPackageLengthTerm
   1703     : Integer                       {$$ = TrUpdateNode (PARSEOP_PACKAGE_LENGTH,(ACPI_PARSE_OBJECT *) $1);}
   1704     ;
   1705 
   1706 NameStringItem
   1707     : ',' NameString                {$$ = $2;}
   1708     | ',' error                     {$$ = AslDoError (); yyclearin;}
   1709     ;
   1710 
   1711 TermArgItem
   1712     : ',' TermArg                   {$$ = $2;}
   1713     | ',' error                     {$$ = AslDoError (); yyclearin;}
   1714     ;
   1715 
   1716 OptionalReference
   1717     :                               {$$ = TrCreateLeafNode (PARSEOP_ZERO);}       /* Placeholder is a ZeroOp object */
   1718     | ','                           {$$ = TrCreateLeafNode (PARSEOP_ZERO);}       /* Placeholder is a ZeroOp object */
   1719     | ',' TermArg                   {$$ = $2;}
   1720     ;
   1721 
   1722 OptionalReturnArg
   1723     :                               {$$ = TrSetNodeFlags (TrCreateLeafNode (PARSEOP_ZERO), NODE_IS_NULL_RETURN);}       /* Placeholder is a ZeroOp object */
   1724     | TermArg                       {$$ = $1;}
   1725     ;
   1726 
   1727 OptionalSerializeRuleKeyword
   1728     :                               {$$ = NULL;}
   1729     | ','                           {$$ = NULL;}
   1730     | ',' SerializeRuleKeyword      {$$ = $2;}
   1731     ;
   1732 
   1733 OptionalTermArg
   1734     :                               {$$ = TrCreateLeafNode (PARSEOP_DEFAULT_ARG);}
   1735     | TermArg                       {$$ = $1;}
   1736     ;
   1737 
   1738 OptionalBufferLength
   1739     :                               {$$ = NULL;}
   1740     | TermArg                       {$$ = $1;}
   1741     ;
   1742 
   1743 OptionalWordConst
   1744     :                               {$$ = NULL;}
   1745     | WordConst                     {$$ = $1;}
   1746     ;
   1747