-- File generated by the BNF Converter. -- Parser definition for use with Happy. { {-# OPTIONS_GHC -fno-warn-incomplete-patterns -fno-warn-overlapping-patterns #-} {-# LANGUAGE PatternSynonyms #-} module ParC ( happyError , myLexer , pProgram , pListExternal_declaration , pExternal_declaration , pFunction_def , pDec , pListDec , pListDeclaration_specifier , pDeclaration_specifier , pListInit_declarator , pInit_declarator , pType_specifier , pStorage_class_specifier , pType_qualifier , pStruct_or_union_spec , pStruct_or_union , pListStruct_dec , pStruct_dec , pListSpec_qual , pSpec_qual , pListStruct_declarator , pStruct_declarator , pEnum_specifier , pListEnumerator , pEnumerator , pDeclarator , pDirect_declarator , pPointer , pListType_qualifier , pParameter_type , pParameter_declarations , pParameter_declaration , pListIdent , pInitializer , pInitializers , pType_name , pAbstract_declarator , pDir_abs_dec , pStm , pLabeled_stm , pCompound_stm , pExpression_stm , pSelection_stm , pIter_stm , pJump_stm , pListStm , pExp , pExp2 , pExp3 , pExp4 , pExp5 , pExp6 , pExp7 , pExp8 , pExp9 , pExp10 , pExp11 , pExp12 , pExp13 , pExp14 , pExp15 , pExp16 , pExp17 , pConstant , pConstant_expression , pUnary_operator , pListExp2 , pAssignment_op ) where import Prelude import qualified AbsC import LexC } %name pProgram Program %name pListExternal_declaration ListExternal_declaration %name pExternal_declaration External_declaration %name pFunction_def Function_def %name pDec Dec %name pListDec ListDec %name pListDeclaration_specifier ListDeclaration_specifier %name pDeclaration_specifier Declaration_specifier %name pListInit_declarator ListInit_declarator %name pInit_declarator Init_declarator %name pType_specifier Type_specifier %name pStorage_class_specifier Storage_class_specifier %name pType_qualifier Type_qualifier %name pStruct_or_union_spec Struct_or_union_spec %name pStruct_or_union Struct_or_union %name pListStruct_dec ListStruct_dec %name pStruct_dec Struct_dec %name pListSpec_qual ListSpec_qual %name pSpec_qual Spec_qual %name pListStruct_declarator ListStruct_declarator %name pStruct_declarator Struct_declarator %name pEnum_specifier Enum_specifier %name pListEnumerator ListEnumerator %name pEnumerator Enumerator %name pDeclarator Declarator %name pDirect_declarator Direct_declarator %name pPointer Pointer %name pListType_qualifier ListType_qualifier %name pParameter_type Parameter_type %name pParameter_declarations Parameter_declarations %name pParameter_declaration Parameter_declaration %name pListIdent ListIdent %name pInitializer Initializer %name pInitializers Initializers %name pType_name Type_name %name pAbstract_declarator Abstract_declarator %name pDir_abs_dec Dir_abs_dec %name pStm Stm %name pLabeled_stm Labeled_stm %name pCompound_stm Compound_stm %name pExpression_stm Expression_stm %name pSelection_stm Selection_stm %name pIter_stm Iter_stm %name pJump_stm Jump_stm %name pListStm ListStm %name pExp Exp %name pExp2 Exp2 %name pExp3 Exp3 %name pExp4 Exp4 %name pExp5 Exp5 %name pExp6 Exp6 %name pExp7 Exp7 %name pExp8 Exp8 %name pExp9 Exp9 %name pExp10 Exp10 %name pExp11 Exp11 %name pExp12 Exp12 %name pExp13 Exp13 %name pExp14 Exp14 %name pExp15 Exp15 %name pExp16 Exp16 %name pExp17 Exp17 %name pConstant Constant %name pConstant_expression Constant_expression %name pUnary_operator Unary_operator %name pListExp2 ListExp2 %name pAssignment_op Assignment_op %monad { Err } { (>>=) } { return } %tokentype {Token} %token '!' { PT _ (TS _ 1) } '!=' { PT _ (TS _ 2) } '%' { PT _ (TS _ 3) } '%=' { PT _ (TS _ 4) } '&' { PT _ (TS _ 5) } '&&' { PT _ (TS _ 6) } '&=' { PT _ (TS _ 7) } '(' { PT _ (TS _ 8) } ')' { PT _ (TS _ 9) } '*' { PT _ (TS _ 10) } '*=' { PT _ (TS _ 11) } '+' { PT _ (TS _ 12) } '++' { PT _ (TS _ 13) } '+=' { PT _ (TS _ 14) } ',' { PT _ (TS _ 15) } '-' { PT _ (TS _ 16) } '--' { PT _ (TS _ 17) } '-=' { PT _ (TS _ 18) } '->' { PT _ (TS _ 19) } '.' { PT _ (TS _ 20) } '...' { PT _ (TS _ 21) } '/' { PT _ (TS _ 22) } '/=' { PT _ (TS _ 23) } ':' { PT _ (TS _ 24) } ';' { PT _ (TS _ 25) } '<' { PT _ (TS _ 26) } '<<' { PT _ (TS _ 27) } '<<=' { PT _ (TS _ 28) } '<=' { PT _ (TS _ 29) } '=' { PT _ (TS _ 30) } '==' { PT _ (TS _ 31) } '>' { PT _ (TS _ 32) } '>=' { PT _ (TS _ 33) } '>>' { PT _ (TS _ 34) } '>>=' { PT _ (TS _ 35) } '?' { PT _ (TS _ 36) } 'Typedef_name' { PT _ (TS _ 37) } '[' { PT _ (TS _ 38) } ']' { PT _ (TS _ 39) } '^' { PT _ (TS _ 40) } '^=' { PT _ (TS _ 41) } 'auto' { PT _ (TS _ 42) } 'break' { PT _ (TS _ 43) } 'case' { PT _ (TS _ 44) } 'char' { PT _ (TS _ 45) } 'const' { PT _ (TS _ 46) } 'continue' { PT _ (TS _ 47) } 'default' { PT _ (TS _ 48) } 'do' { PT _ (TS _ 49) } 'double' { PT _ (TS _ 50) } 'else' { PT _ (TS _ 51) } 'enum' { PT _ (TS _ 52) } 'extern' { PT _ (TS _ 53) } 'float' { PT _ (TS _ 54) } 'for' { PT _ (TS _ 55) } 'goto' { PT _ (TS _ 56) } 'if' { PT _ (TS _ 57) } 'int' { PT _ (TS _ 58) } 'long' { PT _ (TS _ 59) } 'register' { PT _ (TS _ 60) } 'return' { PT _ (TS _ 61) } 'short' { PT _ (TS _ 62) } 'signed' { PT _ (TS _ 63) } 'sizeof' { PT _ (TS _ 64) } 'static' { PT _ (TS _ 65) } 'struct' { PT _ (TS _ 66) } 'switch' { PT _ (TS _ 67) } 'typedef' { PT _ (TS _ 68) } 'union' { PT _ (TS _ 69) } 'unsigned' { PT _ (TS _ 70) } 'void' { PT _ (TS _ 71) } 'volatile' { PT _ (TS _ 72) } 'while' { PT _ (TS _ 73) } '{' { PT _ (TS _ 74) } '|' { PT _ (TS _ 75) } '|=' { PT _ (TS _ 76) } '||' { PT _ (TS _ 77) } '}' { PT _ (TS _ 78) } '~' { PT _ (TS _ 79) } L_Ident { PT _ (TV $$) } L_charac { PT _ (TC $$) } L_doubl { PT _ (TD $$) } L_integ { PT _ (TI $$) } L_quoted { PT _ (TL $$) } L_Unsigned { PT _ (T_Unsigned $$) } L_Long { PT _ (T_Long $$) } L_UnsignedLong { PT _ (T_UnsignedLong $$) } L_Hexadecimal { PT _ (T_Hexadecimal $$) } L_HexUnsigned { PT _ (T_HexUnsigned $$) } L_HexLong { PT _ (T_HexLong $$) } L_HexUnsLong { PT _ (T_HexUnsLong $$) } L_Octal { PT _ (T_Octal $$) } L_OctalUnsigned { PT _ (T_OctalUnsigned $$) } L_OctalLong { PT _ (T_OctalLong $$) } L_OctalUnsLong { PT _ (T_OctalUnsLong $$) } L_CDouble { PT _ (T_CDouble $$) } L_CFloat { PT _ (T_CFloat $$) } L_CLongDouble { PT _ (T_CLongDouble $$) } %% Ident :: { AbsC.Ident } Ident : L_Ident { AbsC.Ident $1 } Char :: { Char } Char : L_charac { (read $1 ) :: Char } Double :: { Double } Double : L_doubl { (read $1 ) :: Double } Integer :: { Integer } Integer : L_integ { (read $1 ) :: Integer } String :: { String } String : L_quoted { $1 } Unsigned :: { AbsC.Unsigned } Unsigned : L_Unsigned { AbsC.Unsigned $1 } Long :: { AbsC.Long } Long : L_Long { AbsC.Long $1 } UnsignedLong :: { AbsC.UnsignedLong } UnsignedLong : L_UnsignedLong { AbsC.UnsignedLong $1 } Hexadecimal :: { AbsC.Hexadecimal } Hexadecimal : L_Hexadecimal { AbsC.Hexadecimal $1 } HexUnsigned :: { AbsC.HexUnsigned } HexUnsigned : L_HexUnsigned { AbsC.HexUnsigned $1 } HexLong :: { AbsC.HexLong } HexLong : L_HexLong { AbsC.HexLong $1 } HexUnsLong :: { AbsC.HexUnsLong } HexUnsLong : L_HexUnsLong { AbsC.HexUnsLong $1 } Octal :: { AbsC.Octal } Octal : L_Octal { AbsC.Octal $1 } OctalUnsigned :: { AbsC.OctalUnsigned } OctalUnsigned : L_OctalUnsigned { AbsC.OctalUnsigned $1 } OctalLong :: { AbsC.OctalLong } OctalLong : L_OctalLong { AbsC.OctalLong $1 } OctalUnsLong :: { AbsC.OctalUnsLong } OctalUnsLong : L_OctalUnsLong { AbsC.OctalUnsLong $1 } CDouble :: { AbsC.CDouble } CDouble : L_CDouble { AbsC.CDouble $1 } CFloat :: { AbsC.CFloat } CFloat : L_CFloat { AbsC.CFloat $1 } CLongDouble :: { AbsC.CLongDouble } CLongDouble : L_CLongDouble { AbsC.CLongDouble $1 } Program :: { AbsC.Program } Program : ListExternal_declaration { AbsC.Progr $1 } ListExternal_declaration :: { [AbsC.External_declaration] } ListExternal_declaration : External_declaration { (:[]) $1 } | External_declaration ListExternal_declaration { (:) $1 $2 } External_declaration :: { AbsC.External_declaration } External_declaration : Dec { AbsC.Global $1 } | Function_def { AbsC.Afunc $1 } Function_def :: { AbsC.Function_def } Function_def : Declarator Compound_stm { AbsC.NewFuncInt $1 $2 } | Declarator ListDec Compound_stm { AbsC.OldFuncInt $1 $2 $3 } | ListDeclaration_specifier Declarator Compound_stm { AbsC.NewFunc $1 $2 $3 } | ListDeclaration_specifier Declarator ListDec Compound_stm { AbsC.OldFunc $1 $2 $3 $4 } Dec :: { AbsC.Dec } Dec : ListDeclaration_specifier ';' { AbsC.NoDeclarator $1 } | ListDeclaration_specifier ListInit_declarator ';' { AbsC.Declarators $1 $2 } ListDec :: { [AbsC.Dec] } ListDec : Dec { (:[]) $1 } | Dec ListDec { (:) $1 $2 } ListDeclaration_specifier :: { [AbsC.Declaration_specifier] } ListDeclaration_specifier : Declaration_specifier { (:[]) $1 } | Declaration_specifier ListDeclaration_specifier { (:) $1 $2 } Declaration_specifier :: { AbsC.Declaration_specifier } Declaration_specifier : Storage_class_specifier { AbsC.Storage $1 } | Type_qualifier { AbsC.SpecProp $1 } | Type_specifier { AbsC.Type $1 } ListInit_declarator :: { [AbsC.Init_declarator] } ListInit_declarator : Init_declarator { (:[]) $1 } | Init_declarator ',' ListInit_declarator { (:) $1 $3 } Init_declarator :: { AbsC.Init_declarator } Init_declarator : Declarator { AbsC.OnlyDecl $1 } | Declarator '=' Initializer { AbsC.InitDecl $1 $3 } Type_specifier :: { AbsC.Type_specifier } Type_specifier : 'Typedef_name' { AbsC.Tname } | 'char' { AbsC.Tchar } | 'double' { AbsC.Tdouble } | 'float' { AbsC.Tfloat } | 'int' { AbsC.Tint } | 'long' { AbsC.Tlong } | 'short' { AbsC.Tshort } | 'signed' { AbsC.Tsigned } | 'unsigned' { AbsC.Tunsigned } | 'void' { AbsC.Tvoid } | Enum_specifier { AbsC.Tenum $1 } | Struct_or_union_spec { AbsC.Tstruct $1 } Storage_class_specifier :: { AbsC.Storage_class_specifier } Storage_class_specifier : 'auto' { AbsC.LocalBlock } | 'extern' { AbsC.GlobalPrograms } | 'register' { AbsC.LocalReg } | 'static' { AbsC.LocalProgram } | 'typedef' { AbsC.MyType } Type_qualifier :: { AbsC.Type_qualifier } Type_qualifier : 'const' { AbsC.Const } | 'volatile' { AbsC.NoOptim } Struct_or_union_spec :: { AbsC.Struct_or_union_spec } Struct_or_union_spec : Struct_or_union '{' ListStruct_dec '}' { AbsC.Unique $1 $3 } | Struct_or_union Ident { AbsC.TagType $1 $2 } | Struct_or_union Ident '{' ListStruct_dec '}' { AbsC.Tag $1 $2 $4 } Struct_or_union :: { AbsC.Struct_or_union } Struct_or_union : 'struct' { AbsC.Struct } | 'union' { AbsC.Union } ListStruct_dec :: { [AbsC.Struct_dec] } ListStruct_dec : Struct_dec { (:[]) $1 } | Struct_dec ListStruct_dec { (:) $1 $2 } Struct_dec :: { AbsC.Struct_dec } Struct_dec : ListSpec_qual ListStruct_declarator ';' { AbsC.Structen $1 $2 } ListSpec_qual :: { [AbsC.Spec_qual] } ListSpec_qual : Spec_qual { (:[]) $1 } | Spec_qual ListSpec_qual { (:) $1 $2 } Spec_qual :: { AbsC.Spec_qual } Spec_qual : Type_qualifier { AbsC.QualSpec $1 } | Type_specifier { AbsC.TypeSpec $1 } ListStruct_declarator :: { [AbsC.Struct_declarator] } ListStruct_declarator : Struct_declarator { (:[]) $1 } | Struct_declarator ',' ListStruct_declarator { (:) $1 $3 } Struct_declarator :: { AbsC.Struct_declarator } Struct_declarator : ':' Constant_expression { AbsC.Field $2 } | Declarator { AbsC.Decl $1 } | Declarator ':' Constant_expression { AbsC.DecField $1 $3 } Enum_specifier :: { AbsC.Enum_specifier } Enum_specifier : 'enum' '{' ListEnumerator '}' { AbsC.EnumDec $3 } | 'enum' Ident { AbsC.EnumVar $2 } | 'enum' Ident '{' ListEnumerator '}' { AbsC.EnumName $2 $4 } ListEnumerator :: { [AbsC.Enumerator] } ListEnumerator : Enumerator { (:[]) $1 } | Enumerator ',' ListEnumerator { (:) $1 $3 } Enumerator :: { AbsC.Enumerator } Enumerator : Ident { AbsC.Plain $1 } | Ident '=' Constant_expression { AbsC.EnumInit $1 $3 } Declarator :: { AbsC.Declarator } Declarator : Direct_declarator { AbsC.NoPointer $1 } | Pointer Direct_declarator { AbsC.BeginPointer $1 $2 } Direct_declarator :: { AbsC.Direct_declarator } Direct_declarator : '(' Declarator ')' { AbsC.ParenDecl $2 } | Ident { AbsC.Name $1 } | Direct_declarator '(' ')' { AbsC.OldFuncDec $1 } | Direct_declarator '(' Parameter_type ')' { AbsC.NewFuncDec $1 $3 } | Direct_declarator '(' ListIdent ')' { AbsC.OldFuncDef $1 $3 } | Direct_declarator '[' ']' { AbsC.Incomplete $1 } | Direct_declarator '[' Constant_expression ']' { AbsC.InnitArray $1 $3 } Pointer :: { AbsC.Pointer } Pointer : '*' { AbsC.Point } | '*' Pointer { AbsC.PointPoint $2 } | '*' ListType_qualifier { AbsC.PointQual $2 } | '*' ListType_qualifier Pointer { AbsC.PointQualPoint $2 $3 } ListType_qualifier :: { [AbsC.Type_qualifier] } ListType_qualifier : Type_qualifier { (:[]) $1 } | Type_qualifier ListType_qualifier { (:) $1 $2 } Parameter_type :: { AbsC.Parameter_type } Parameter_type : Parameter_declarations { AbsC.AllSpec $1 } | Parameter_declarations ',' '...' { AbsC.More $1 } Parameter_declarations :: { AbsC.Parameter_declarations } Parameter_declarations : Parameter_declaration { AbsC.ParamDec $1 } | Parameter_declarations ',' Parameter_declaration { AbsC.MoreParamDec $1 $3 } Parameter_declaration :: { AbsC.Parameter_declaration } Parameter_declaration : ListDeclaration_specifier { AbsC.OnlyType $1 } | ListDeclaration_specifier Abstract_declarator { AbsC.Abstract $1 $2 } | ListDeclaration_specifier Declarator { AbsC.TypeAndParam $1 $2 } ListIdent :: { [AbsC.Ident] } ListIdent : Ident { (:[]) $1 } | Ident ',' ListIdent { (:) $1 $3 } Initializer :: { AbsC.Initializer } Initializer : '{' Initializers ',' '}' { AbsC.InitListTwo $2 } | '{' Initializers '}' { AbsC.InitListOne $2 } | Exp2 { AbsC.InitExpr $1 } Initializers :: { AbsC.Initializers } Initializers : Initializer { AbsC.AnInit $1 } | Initializers ',' Initializer { AbsC.MoreInit $1 $3 } Type_name :: { AbsC.Type_name } Type_name : ListSpec_qual { AbsC.PlainType $1 } | ListSpec_qual Abstract_declarator { AbsC.ExtendedType $1 $2 } Abstract_declarator :: { AbsC.Abstract_declarator } Abstract_declarator : Dir_abs_dec { AbsC.Advanced $1 } | Pointer { AbsC.PointerStart $1 } | Pointer Dir_abs_dec { AbsC.PointAdvanced $1 $2 } Dir_abs_dec :: { AbsC.Dir_abs_dec } Dir_abs_dec : '(' ')' { AbsC.OldFunction } | '(' Abstract_declarator ')' { AbsC.WithinParentes $2 } | '(' Parameter_type ')' { AbsC.NewFunction $2 } | '[' ']' { AbsC.Array } | '[' Constant_expression ']' { AbsC.InitiatedArray $2 } | Dir_abs_dec '(' ')' { AbsC.OldFuncExpr $1 } | Dir_abs_dec '(' Parameter_type ')' { AbsC.NewFuncExpr $1 $3 } | Dir_abs_dec '[' ']' { AbsC.UnInitiated $1 } | Dir_abs_dec '[' Constant_expression ']' { AbsC.Initiated $1 $3 } Stm :: { AbsC.Stm } Stm : Compound_stm { AbsC.CompS $1 } | Expression_stm { AbsC.ExprS $1 } | Iter_stm { AbsC.IterS $1 } | Jump_stm { AbsC.JumpS $1 } | Labeled_stm { AbsC.LabelS $1 } | Selection_stm { AbsC.SelS $1 } Labeled_stm :: { AbsC.Labeled_stm } Labeled_stm : 'case' Constant_expression ':' Stm { AbsC.SlabelTwo $2 $4 } | 'default' ':' Stm { AbsC.SlabelThree $3 } | Ident ':' Stm { AbsC.SlabelOne $1 $3 } Compound_stm :: { AbsC.Compound_stm } Compound_stm : '{' '}' { AbsC.ScompOne } | '{' ListDec '}' { AbsC.ScompThree $2 } | '{' ListDec ListStm '}' { AbsC.ScompFour $2 $3 } | '{' ListStm '}' { AbsC.ScompTwo $2 } Expression_stm :: { AbsC.Expression_stm } Expression_stm : ';' { AbsC.SexprOne } | Exp ';' { AbsC.SexprTwo $1 } Selection_stm :: { AbsC.Selection_stm } Selection_stm : 'if' '(' Exp ')' Stm { AbsC.SselOne $3 $5 } | 'if' '(' Exp ')' Stm 'else' Stm { AbsC.SselTwo $3 $5 $7 } | 'switch' '(' Exp ')' Stm { AbsC.SselThree $3 $5 } Iter_stm :: { AbsC.Iter_stm } Iter_stm : 'do' Stm 'while' '(' Exp ')' ';' { AbsC.SiterTwo $2 $5 } | 'for' '(' Expression_stm Expression_stm ')' Stm { AbsC.SiterThree $3 $4 $6 } | 'for' '(' Expression_stm Expression_stm Exp ')' Stm { AbsC.SiterFour $3 $4 $5 $7 } | 'while' '(' Exp ')' Stm { AbsC.SiterOne $3 $5 } Jump_stm :: { AbsC.Jump_stm } Jump_stm : 'break' ';' { AbsC.SjumpThree } | 'continue' ';' { AbsC.SjumpTwo } | 'goto' Ident ';' { AbsC.SjumpOne $2 } | 'return' ';' { AbsC.SjumpFour } | 'return' Exp ';' { AbsC.SjumpFive $2 } ListStm :: { [AbsC.Stm] } ListStm : Stm { (:[]) $1 } | Stm ListStm { (:) $1 $2 } Exp :: { AbsC.Exp } Exp : Exp ',' Exp2 { AbsC.Ecomma $1 $3 } | Exp2 { $1 } Exp2 :: { AbsC.Exp } Exp2 : Exp3 { $1 } | Exp15 Assignment_op Exp2 { AbsC.Eassign $1 $2 $3 } Exp3 :: { AbsC.Exp } Exp3 : Exp4 { $1 } | Exp4 '?' Exp ':' Exp3 { AbsC.Econdition $1 $3 $5 } Exp4 :: { AbsC.Exp } Exp4 : Exp4 '||' Exp5 { AbsC.Elor $1 $3 } | Exp5 { $1 } Exp5 :: { AbsC.Exp } Exp5 : Exp5 '&&' Exp6 { AbsC.Eland $1 $3 } | Exp6 { $1 } Exp6 :: { AbsC.Exp } Exp6 : Exp6 '|' Exp7 { AbsC.Ebitor $1 $3 } | Exp7 { $1 } Exp7 :: { AbsC.Exp } Exp7 : Exp7 '^' Exp8 { AbsC.Ebitexor $1 $3 } | Exp8 { $1 } Exp8 :: { AbsC.Exp } Exp8 : Exp8 '&' Exp9 { AbsC.Ebitand $1 $3 } | Exp9 { $1 } Exp9 :: { AbsC.Exp } Exp9 : Exp9 '!=' Exp10 { AbsC.Eneq $1 $3 } | Exp9 '==' Exp10 { AbsC.Eeq $1 $3 } | Exp10 { $1 } Exp10 :: { AbsC.Exp } Exp10 : Exp10 '<' Exp11 { AbsC.Elthen $1 $3 } | Exp10 '<=' Exp11 { AbsC.Ele $1 $3 } | Exp10 '>' Exp11 { AbsC.Egrthen $1 $3 } | Exp10 '>=' Exp11 { AbsC.Ege $1 $3 } | Exp11 { $1 } Exp11 :: { AbsC.Exp } Exp11 : Exp11 '<<' Exp12 { AbsC.Eleft $1 $3 } | Exp11 '>>' Exp12 { AbsC.Eright $1 $3 } | Exp12 { $1 } Exp12 :: { AbsC.Exp } Exp12 : Exp12 '+' Exp13 { AbsC.Eplus $1 $3 } | Exp12 '-' Exp13 { AbsC.Eminus $1 $3 } | Exp13 { $1 } Exp13 :: { AbsC.Exp } Exp13 : Exp13 '%' Exp14 { AbsC.Emod $1 $3 } | Exp13 '*' Exp14 { AbsC.Etimes $1 $3 } | Exp13 '/' Exp14 { AbsC.Ediv $1 $3 } | Exp14 { $1 } Exp14 :: { AbsC.Exp } Exp14 : '(' Type_name ')' Exp14 { AbsC.Etypeconv $2 $4 } | Exp15 { $1 } Exp15 :: { AbsC.Exp } Exp15 : '++' Exp15 { AbsC.Epreinc $2 } | '--' Exp15 { AbsC.Epredec $2 } | 'sizeof' '(' Type_name ')' { AbsC.Ebytestype $3 } | 'sizeof' Exp15 { AbsC.Ebytesexpr $2 } | Unary_operator Exp14 { AbsC.Epreop $1 $2 } | Exp16 { $1 } Exp16 :: { AbsC.Exp } Exp16 : Exp16 '(' ')' { AbsC.Efunk $1 } | Exp16 '(' ListExp2 ')' { AbsC.Efunkpar $1 $3 } | Exp16 '++' { AbsC.Epostinc $1 } | Exp16 '--' { AbsC.Epostdec $1 } | Exp16 '->' Ident { AbsC.Epoint $1 $3 } | Exp16 '.' Ident { AbsC.Eselect $1 $3 } | Exp16 '[' Exp ']' { AbsC.Earray $1 $3 } | Exp17 { $1 } Exp17 :: { AbsC.Exp } Exp17 : '(' Exp ')' { $2 } | String { AbsC.Estring $1 } | Ident { AbsC.Evar $1 } | Constant { AbsC.Econst $1 } Constant :: { AbsC.Constant } Constant : Char { AbsC.Echar $1 } | Double { AbsC.Efloat $1 } | Integer { AbsC.Eint $1 } | CDouble { AbsC.Ecdouble $1 } | CFloat { AbsC.Ecfloat $1 } | CLongDouble { AbsC.Eclongdouble $1 } | HexLong { AbsC.Ehexalong $1 } | HexUnsLong { AbsC.Ehexaunslong $1 } | HexUnsigned { AbsC.Ehexaunsign $1 } | Hexadecimal { AbsC.Ehexadec $1 } | Long { AbsC.Elong $1 } | Octal { AbsC.Eoctal $1 } | OctalLong { AbsC.Eoctallong $1 } | OctalUnsLong { AbsC.Eoctalunslong $1 } | OctalUnsigned { AbsC.Eoctalunsign $1 } | Unsigned { AbsC.Eunsigned $1 } | UnsignedLong { AbsC.Eunsignlong $1 } Constant_expression :: { AbsC.Constant_expression } Constant_expression : Exp3 { AbsC.Especial $1 } Unary_operator :: { AbsC.Unary_operator } Unary_operator : '!' { AbsC.Logicalneg } | '&' { AbsC.Address } | '*' { AbsC.Indirection } | '+' { AbsC.Plus } | '-' { AbsC.Negative } | '~' { AbsC.Complement } ListExp2 :: { [AbsC.Exp] } ListExp2 : Exp2 { (:[]) $1 } | Exp2 ',' ListExp2 { (:) $1 $3 } Assignment_op :: { AbsC.Assignment_op } Assignment_op : '%=' { AbsC.AssignMod } | '&=' { AbsC.AssignAnd } | '*=' { AbsC.AssignMul } | '+=' { AbsC.AssignAdd } | '-=' { AbsC.AssignSub } | '/=' { AbsC.AssignDiv } | '<<=' { AbsC.AssignLeft } | '=' { AbsC.Assign } | '>>=' { AbsC.AssignRight } | '^=' { AbsC.AssignXor } | '|=' { AbsC.AssignOr } { type Err = Either String happyError :: [Token] -> Err a happyError ts = Left $ "syntax error at " ++ tokenPos ts ++ case ts of [] -> [] [Err _] -> " due to lexer error" t:_ -> " before `" ++ (prToken t) ++ "'" myLexer :: String -> [Token] myLexer = tokens }