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