-- Haskel data types for the abstract syntax. -- Generated by the BNF converter. {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE PatternSynonyms #-} -- | The abstract syntax of language C. module AbsC where import qualified Prelude as T (Char, Double, Integer, String) import qualified Prelude as C ( Eq , Ord , Show , Read , Functor , Foldable , Traversable , Int, Maybe(..) ) import Data.String type Program = Program' BNFC'Position data Program' a = Progr a [External_declaration' a] -- ^ Program ::= External_declaration deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type External_declaration = External_declaration' BNFC'Position data External_declaration' a = Afunc a (Function_def' a) -- ^ External_declaration ::= Function_def | Global a (Dec' a) -- ^ External_declaration ::= Dec deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Function_def = Function_def' BNFC'Position data Function_def' a = NewFunc a [Declaration_specifier' a] (Declarator' a) (Compound_stm' a) -- ^ Function_def ::= Declaration_specifier Declarator Compound_stm | NewFuncInt a (Declarator' a) (Compound_stm' a) -- ^ Function_def ::= Declarator Compound_stm | OldFunc a [Declaration_specifier' a] (Declarator' a) [Dec' a] (Compound_stm' a) -- ^ Function_def ::= Declaration_specifier Declarator Dec Compound_stm | OldFuncInt a (Declarator' a) [Dec' a] (Compound_stm' a) -- ^ Function_def ::= Declarator Dec Compound_stm deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Dec = Dec' BNFC'Position data Dec' a = Declarators a [Declaration_specifier' a] [Init_declarator' a] -- ^ Dec ::= Declaration_specifier Init_declarator ";" | NoDeclarator a [Declaration_specifier' a] -- ^ Dec ::= Declaration_specifier ";" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Declaration_specifier = Declaration_specifier' BNFC'Position data Declaration_specifier' a = SpecProp a (Type_qualifier' a) -- ^ Declaration_specifier ::= Type_qualifier | Storage a (Storage_class_specifier' a) -- ^ Declaration_specifier ::= Storage_class_specifier | Type a (Type_specifier' a) -- ^ Declaration_specifier ::= Type_specifier deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Init_declarator = Init_declarator' BNFC'Position data Init_declarator' a = InitDecl a (Declarator' a) (Initializer' a) -- ^ Init_declarator ::= Declarator "=" Initializer | OnlyDecl a (Declarator' a) -- ^ Init_declarator ::= Declarator deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Type_specifier = Type_specifier' BNFC'Position data Type_specifier' a = Tchar a -- ^ Type_specifier ::= "char" | Tdouble a -- ^ Type_specifier ::= "double" | Tenum a (Enum_specifier' a) -- ^ Type_specifier ::= Enum_specifier | Tfloat a -- ^ Type_specifier ::= "float" | Tint a -- ^ Type_specifier ::= "int" | Tlong a -- ^ Type_specifier ::= "long" | Tname a -- ^ Type_specifier ::= "Typedef_name" | Tshort a -- ^ Type_specifier ::= "short" | Tsigned a -- ^ Type_specifier ::= "signed" | Tstruct a (Struct_or_union_spec' a) -- ^ Type_specifier ::= Struct_or_union_spec | Tunsigned a -- ^ Type_specifier ::= "unsigned" | Tvoid a -- ^ Type_specifier ::= "void" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Storage_class_specifier = Storage_class_specifier' BNFC'Position data Storage_class_specifier' a = GlobalPrograms a -- ^ Storage_class_specifier ::= "extern" | LocalBlock a -- ^ Storage_class_specifier ::= "auto" | LocalProgram a -- ^ Storage_class_specifier ::= "static" | LocalReg a -- ^ Storage_class_specifier ::= "register" | MyType a -- ^ Storage_class_specifier ::= "typedef" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Type_qualifier = Type_qualifier' BNFC'Position data Type_qualifier' a = Const a -- ^ Type_qualifier ::= "const" | NoOptim a -- ^ Type_qualifier ::= "volatile" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Struct_or_union_spec = Struct_or_union_spec' BNFC'Position data Struct_or_union_spec' a = Tag a (Struct_or_union' a) Ident [Struct_dec' a] -- ^ Struct_or_union_spec ::= Struct_or_union Ident "{" Struct_dec "}" | TagType a (Struct_or_union' a) Ident -- ^ Struct_or_union_spec ::= Struct_or_union Ident | Unique a (Struct_or_union' a) [Struct_dec' a] -- ^ Struct_or_union_spec ::= Struct_or_union "{" Struct_dec "}" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Struct_or_union = Struct_or_union' BNFC'Position data Struct_or_union' a = Struct a -- ^ Struct_or_union ::= "struct" | Union a -- ^ Struct_or_union ::= "union" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Struct_dec = Struct_dec' BNFC'Position data Struct_dec' a = Structen a [Spec_qual' a] [Struct_declarator' a] -- ^ Struct_dec ::= Spec_qual Struct_declarator ";" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Spec_qual = Spec_qual' BNFC'Position data Spec_qual' a = QualSpec a (Type_qualifier' a) -- ^ Spec_qual ::= Type_qualifier | TypeSpec a (Type_specifier' a) -- ^ Spec_qual ::= Type_specifier deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Struct_declarator = Struct_declarator' BNFC'Position data Struct_declarator' a = DecField a (Declarator' a) (Constant_expression' a) -- ^ Struct_declarator ::= Declarator ":" Constant_expression | Decl a (Declarator' a) -- ^ Struct_declarator ::= Declarator | Field a (Constant_expression' a) -- ^ Struct_declarator ::= ":" Constant_expression deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Enum_specifier = Enum_specifier' BNFC'Position data Enum_specifier' a = EnumDec a [Enumerator' a] -- ^ Enum_specifier ::= "enum" "{" Enumerator "}" | EnumName a Ident [Enumerator' a] -- ^ Enum_specifier ::= "enum" Ident "{" Enumerator "}" | EnumVar a Ident -- ^ Enum_specifier ::= "enum" Ident deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Enumerator = Enumerator' BNFC'Position data Enumerator' a = EnumInit a Ident (Constant_expression' a) -- ^ Enumerator ::= Ident "=" Constant_expression | Plain a Ident -- ^ Enumerator ::= Ident deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Declarator = Declarator' BNFC'Position data Declarator' a = BeginPointer a (Pointer' a) (Direct_declarator' a) -- ^ Declarator ::= Pointer Direct_declarator | NoPointer a (Direct_declarator' a) -- ^ Declarator ::= Direct_declarator deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Direct_declarator = Direct_declarator' BNFC'Position data Direct_declarator' a = Incomplete a (Direct_declarator' a) -- ^ Direct_declarator ::= Direct_declarator "[" "]" | InnitArray a (Direct_declarator' a) (Constant_expression' a) -- ^ Direct_declarator ::= Direct_declarator "[" Constant_expression "]" | Name a Ident -- ^ Direct_declarator ::= Ident | NewFuncDec a (Direct_declarator' a) (Parameter_type' a) -- ^ Direct_declarator ::= Direct_declarator "(" Parameter_type ")" | OldFuncDec a (Direct_declarator' a) -- ^ Direct_declarator ::= Direct_declarator "(" ")" | OldFuncDef a (Direct_declarator' a) [Ident] -- ^ Direct_declarator ::= Direct_declarator "(" Ident ")" | ParenDecl a (Declarator' a) -- ^ Direct_declarator ::= "(" Declarator ")" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Pointer = Pointer' BNFC'Position data Pointer' a = Point a -- ^ Pointer ::= "*" | PointPoint a (Pointer' a) -- ^ Pointer ::= "*" Pointer | PointQual a [Type_qualifier' a] -- ^ Pointer ::= "*" Type_qualifier | PointQualPoint a [Type_qualifier' a] (Pointer' a) -- ^ Pointer ::= "*" Type_qualifier Pointer deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Parameter_type = Parameter_type' BNFC'Position data Parameter_type' a = AllSpec a (Parameter_declarations' a) -- ^ Parameter_type ::= Parameter_declarations | More a (Parameter_declarations' a) -- ^ Parameter_type ::= Parameter_declarations "," "..." deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Parameter_declarations = Parameter_declarations' BNFC'Position data Parameter_declarations' a = MoreParamDec a (Parameter_declarations' a) (Parameter_declaration' a) -- ^ Parameter_declarations ::= Parameter_declarations "," Parameter_declaration | ParamDec a (Parameter_declaration' a) -- ^ Parameter_declarations ::= Parameter_declaration deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Parameter_declaration = Parameter_declaration' BNFC'Position data Parameter_declaration' a = Abstract a [Declaration_specifier' a] (Abstract_declarator' a) -- ^ Parameter_declaration ::= Declaration_specifier Abstract_declarator | OnlyType a [Declaration_specifier' a] -- ^ Parameter_declaration ::= Declaration_specifier | TypeAndParam a [Declaration_specifier' a] (Declarator' a) -- ^ Parameter_declaration ::= Declaration_specifier Declarator deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Initializer = Initializer' BNFC'Position data Initializer' a = InitExpr a (Exp' a) -- ^ Initializer ::= Exp2 | InitListOne a (Initializers' a) -- ^ Initializer ::= "{" Initializers "}" | InitListTwo a (Initializers' a) -- ^ Initializer ::= "{" Initializers "," "}" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Initializers = Initializers' BNFC'Position data Initializers' a = AnInit a (Initializer' a) -- ^ Initializers ::= Initializer | MoreInit a (Initializers' a) (Initializer' a) -- ^ Initializers ::= Initializers "," Initializer deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Type_name = Type_name' BNFC'Position data Type_name' a = ExtendedType a [Spec_qual' a] (Abstract_declarator' a) -- ^ Type_name ::= Spec_qual Abstract_declarator | PlainType a [Spec_qual' a] -- ^ Type_name ::= Spec_qual deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Abstract_declarator = Abstract_declarator' BNFC'Position data Abstract_declarator' a = Advanced a (Dir_abs_dec' a) -- ^ Abstract_declarator ::= Dir_abs_dec | PointAdvanced a (Pointer' a) (Dir_abs_dec' a) -- ^ Abstract_declarator ::= Pointer Dir_abs_dec | PointerStart a (Pointer' a) -- ^ Abstract_declarator ::= Pointer deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Dir_abs_dec = Dir_abs_dec' BNFC'Position data Dir_abs_dec' a = Array a -- ^ Dir_abs_dec ::= "[" "]" | Initiated a (Dir_abs_dec' a) (Constant_expression' a) -- ^ Dir_abs_dec ::= Dir_abs_dec "[" Constant_expression "]" | InitiatedArray a (Constant_expression' a) -- ^ Dir_abs_dec ::= "[" Constant_expression "]" | NewFuncExpr a (Dir_abs_dec' a) (Parameter_type' a) -- ^ Dir_abs_dec ::= Dir_abs_dec "(" Parameter_type ")" | NewFunction a (Parameter_type' a) -- ^ Dir_abs_dec ::= "(" Parameter_type ")" | OldFuncExpr a (Dir_abs_dec' a) -- ^ Dir_abs_dec ::= Dir_abs_dec "(" ")" | OldFunction a -- ^ Dir_abs_dec ::= "(" ")" | UnInitiated a (Dir_abs_dec' a) -- ^ Dir_abs_dec ::= Dir_abs_dec "[" "]" | WithinParentes a (Abstract_declarator' a) -- ^ Dir_abs_dec ::= "(" Abstract_declarator ")" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Stm = Stm' BNFC'Position data Stm' a = CompS a (Compound_stm' a) -- ^ Stm ::= Compound_stm | ExprS a (Expression_stm' a) -- ^ Stm ::= Expression_stm | IterS a (Iter_stm' a) -- ^ Stm ::= Iter_stm | JumpS a (Jump_stm' a) -- ^ Stm ::= Jump_stm | LabelS a (Labeled_stm' a) -- ^ Stm ::= Labeled_stm | SelS a (Selection_stm' a) -- ^ Stm ::= Selection_stm deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Labeled_stm = Labeled_stm' BNFC'Position data Labeled_stm' a = SlabelOne a Ident (Stm' a) -- ^ Labeled_stm ::= Ident ":" Stm | SlabelThree a (Stm' a) -- ^ Labeled_stm ::= "default" ":" Stm | SlabelTwo a (Constant_expression' a) (Stm' a) -- ^ Labeled_stm ::= "case" Constant_expression ":" Stm deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Compound_stm = Compound_stm' BNFC'Position data Compound_stm' a = ScompFour a [Dec' a] [Stm' a] -- ^ Compound_stm ::= "{" Dec Stm "}" | ScompOne a -- ^ Compound_stm ::= "{" "}" | ScompThree a [Dec' a] -- ^ Compound_stm ::= "{" Dec "}" | ScompTwo a [Stm' a] -- ^ Compound_stm ::= "{" Stm "}" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Expression_stm = Expression_stm' BNFC'Position data Expression_stm' a = SexprOne a -- ^ Expression_stm ::= ";" | SexprTwo a (Exp' a) -- ^ Expression_stm ::= Exp ";" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Selection_stm = Selection_stm' BNFC'Position data Selection_stm' a = SselOne a (Exp' a) (Stm' a) -- ^ Selection_stm ::= "if" "(" Exp ")" Stm | SselThree a (Exp' a) (Stm' a) -- ^ Selection_stm ::= "switch" "(" Exp ")" Stm | SselTwo a (Exp' a) (Stm' a) (Stm' a) -- ^ Selection_stm ::= "if" "(" Exp ")" Stm "else" Stm deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Iter_stm = Iter_stm' BNFC'Position data Iter_stm' a = SiterFour a (Expression_stm' a) (Expression_stm' a) (Exp' a) (Stm' a) -- ^ Iter_stm ::= "for" "(" Expression_stm Expression_stm Exp ")" Stm | SiterOne a (Exp' a) (Stm' a) -- ^ Iter_stm ::= "while" "(" Exp ")" Stm | SiterThree a (Expression_stm' a) (Expression_stm' a) (Stm' a) -- ^ Iter_stm ::= "for" "(" Expression_stm Expression_stm ")" Stm | SiterTwo a (Stm' a) (Exp' a) -- ^ Iter_stm ::= "do" Stm "while" "(" Exp ")" ";" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Jump_stm = Jump_stm' BNFC'Position data Jump_stm' a = SjumpFive a (Exp' a) -- ^ Jump_stm ::= "return" Exp ";" | SjumpFour a -- ^ Jump_stm ::= "return" ";" | SjumpOne a Ident -- ^ Jump_stm ::= "goto" Ident ";" | SjumpThree a -- ^ Jump_stm ::= "break" ";" | SjumpTwo a -- ^ Jump_stm ::= "continue" ";" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Exp = Exp' BNFC'Position data Exp' a = Earray a (Exp' a) (Exp' a) -- ^ Exp ::= Exp16 "[" Exp "]" | Eassign a (Exp' a) (Assignment_op' a) (Exp' a) -- ^ Exp ::= Exp15 Assignment_op Exp2 | Ebitand a (Exp' a) (Exp' a) -- ^ Exp ::= Exp8 "&" Exp9 | Ebitexor a (Exp' a) (Exp' a) -- ^ Exp ::= Exp7 "^" Exp8 | Ebitor a (Exp' a) (Exp' a) -- ^ Exp ::= Exp6 "|" Exp7 | Ebytesexpr a (Exp' a) -- ^ Exp ::= "sizeof" Exp15 | Ebytestype a (Type_name' a) -- ^ Exp ::= "sizeof" "(" Type_name ")" | Ecomma a (Exp' a) (Exp' a) -- ^ Exp ::= Exp "," Exp2 | Econdition a (Exp' a) (Exp' a) (Exp' a) -- ^ Exp ::= Exp4 "?" Exp ":" Exp3 | Econst a (Constant' a) -- ^ Exp ::= Constant | Ediv a (Exp' a) (Exp' a) -- ^ Exp ::= Exp13 "/" Exp14 | Eeq a (Exp' a) (Exp' a) -- ^ Exp ::= Exp9 "==" Exp10 | Efunk a (Exp' a) -- ^ Exp ::= Exp16 "(" ")" | Efunkpar a (Exp' a) [Exp' a] -- ^ Exp ::= Exp16 "(" Exp2 ")" | Ege a (Exp' a) (Exp' a) -- ^ Exp ::= Exp10 ">=" Exp11 | Egrthen a (Exp' a) (Exp' a) -- ^ Exp ::= Exp10 ">" Exp11 | Eland a (Exp' a) (Exp' a) -- ^ Exp ::= Exp5 "&&" Exp6 | Ele a (Exp' a) (Exp' a) -- ^ Exp ::= Exp10 "<=" Exp11 | Eleft a (Exp' a) (Exp' a) -- ^ Exp ::= Exp11 "<<" Exp12 | Elor a (Exp' a) (Exp' a) -- ^ Exp ::= Exp4 "||" Exp5 | Elthen a (Exp' a) (Exp' a) -- ^ Exp ::= Exp10 "<" Exp11 | Eminus a (Exp' a) (Exp' a) -- ^ Exp ::= Exp12 "-" Exp13 | Emod a (Exp' a) (Exp' a) -- ^ Exp ::= Exp13 "%" Exp14 | Eneq a (Exp' a) (Exp' a) -- ^ Exp ::= Exp9 "!=" Exp10 | Eplus a (Exp' a) (Exp' a) -- ^ Exp ::= Exp12 "+" Exp13 | Epoint a (Exp' a) Ident -- ^ Exp ::= Exp16 "->" Ident | Epostdec a (Exp' a) -- ^ Exp ::= Exp16 "--" | Epostinc a (Exp' a) -- ^ Exp ::= Exp16 "++" | Epredec a (Exp' a) -- ^ Exp ::= "--" Exp15 | Epreinc a (Exp' a) -- ^ Exp ::= "++" Exp15 | Epreop a (Unary_operator' a) (Exp' a) -- ^ Exp ::= Unary_operator Exp14 | Eright a (Exp' a) (Exp' a) -- ^ Exp ::= Exp11 ">>" Exp12 | Eselect a (Exp' a) Ident -- ^ Exp ::= Exp16 "." Ident | Estring a T.String -- ^ Exp ::= String | Etimes a (Exp' a) (Exp' a) -- ^ Exp ::= Exp13 "*" Exp14 | Etypeconv a (Type_name' a) (Exp' a) -- ^ Exp ::= "(" Type_name ")" Exp14 | Evar a Ident -- ^ Exp ::= Ident deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Constant = Constant' BNFC'Position data Constant' a = Ecdouble a CDouble -- ^ Constant ::= CDouble | Ecfloat a CFloat -- ^ Constant ::= CFloat | Echar a T.Char -- ^ Constant ::= Char | Eclongdouble a CLongDouble -- ^ Constant ::= CLongDouble | Edouble a T.Double -- ^ Constant ::= Double | Efloat a T.Double -- ^ Constant ::= Double | Ehexadec a Hexadecimal -- ^ Constant ::= Hexadecimal | Ehexalong a HexLong -- ^ Constant ::= HexLong | Ehexaunsign a HexUnsigned -- ^ Constant ::= HexUnsigned | Ehexaunslong a HexUnsLong -- ^ Constant ::= HexUnsLong | Eint a T.Integer -- ^ Constant ::= Integer | Elong a Long -- ^ Constant ::= Long | Elonger a T.Integer -- ^ Constant ::= Integer | Eoctal a Octal -- ^ Constant ::= Octal | Eoctallong a OctalLong -- ^ Constant ::= OctalLong | Eoctalunsign a OctalUnsigned -- ^ Constant ::= OctalUnsigned | Eoctalunslong a OctalUnsLong -- ^ Constant ::= OctalUnsLong | Eunsigned a Unsigned -- ^ Constant ::= Unsigned | Eunsignlong a UnsignedLong -- ^ Constant ::= UnsignedLong deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Constant_expression = Constant_expression' BNFC'Position data Constant_expression' a = Especial a (Exp' a) -- ^ Constant_expression ::= Exp3 deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Unary_operator = Unary_operator' BNFC'Position data Unary_operator' a = Address a -- ^ Unary_operator ::= "&" | Complement a -- ^ Unary_operator ::= "~" | Indirection a -- ^ Unary_operator ::= "*" | Logicalneg a -- ^ Unary_operator ::= "!" | Negative a -- ^ Unary_operator ::= "-" | Plus a -- ^ Unary_operator ::= "+" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Assignment_op = Assignment_op' BNFC'Position data Assignment_op' a = Assign a -- ^ Assignment_op ::= "=" | AssignAdd a -- ^ Assignment_op ::= "+=" | AssignAnd a -- ^ Assignment_op ::= "&=" | AssignDiv a -- ^ Assignment_op ::= "/=" | AssignLeft a -- ^ Assignment_op ::= "<<=" | AssignMod a -- ^ Assignment_op ::= "%=" | AssignMul a -- ^ Assignment_op ::= "*=" | AssignOr a -- ^ Assignment_op ::= "|=" | AssignRight a -- ^ Assignment_op ::= ">>=" | AssignSub a -- ^ Assignment_op ::= "-=" | AssignXor a -- ^ Assignment_op ::= "^=" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) newtype Ident = Ident T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype Unsigned = Unsigned T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype Long = Long T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype UnsignedLong = UnsignedLong T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype Hexadecimal = Hexadecimal T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype HexUnsigned = HexUnsigned T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype HexLong = HexLong T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype HexUnsLong = HexUnsLong T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype Octal = Octal T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype OctalUnsigned = OctalUnsigned T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype OctalLong = OctalLong T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype OctalUnsLong = OctalUnsLong T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype CDouble = CDouble T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype CFloat = CFloat T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) newtype CLongDouble = CLongDouble T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) -- | Start position (line, column) of something. type BNFC'Position = C.Maybe (C.Int, C.Int) pattern BNFC'NoPosition :: BNFC'Position pattern BNFC'NoPosition = C.Nothing pattern BNFC'Position :: C.Int -> C.Int -> BNFC'Position pattern BNFC'Position line col = C.Just (line, col) -- | Get the start position of something. class HasPosition a where hasPosition :: a -> BNFC'Position instance HasPosition Program where hasPosition = \case Progr p _ -> p instance HasPosition External_declaration where hasPosition = \case Afunc p _ -> p Global p _ -> p instance HasPosition Function_def where hasPosition = \case NewFunc p _ _ _ -> p NewFuncInt p _ _ -> p OldFunc p _ _ _ _ -> p OldFuncInt p _ _ _ -> p instance HasPosition Dec where hasPosition = \case Declarators p _ _ -> p NoDeclarator p _ -> p instance HasPosition Declaration_specifier where hasPosition = \case SpecProp p _ -> p Storage p _ -> p Type p _ -> p instance HasPosition Init_declarator where hasPosition = \case InitDecl p _ _ -> p OnlyDecl p _ -> p instance HasPosition Type_specifier where hasPosition = \case Tchar p -> p Tdouble p -> p Tenum p _ -> p Tfloat p -> p Tint p -> p Tlong p -> p Tname p -> p Tshort p -> p Tsigned p -> p Tstruct p _ -> p Tunsigned p -> p Tvoid p -> p instance HasPosition Storage_class_specifier where hasPosition = \case GlobalPrograms p -> p LocalBlock p -> p LocalProgram p -> p LocalReg p -> p MyType p -> p instance HasPosition Type_qualifier where hasPosition = \case Const p -> p NoOptim p -> p instance HasPosition Struct_or_union_spec where hasPosition = \case Tag p _ _ _ -> p TagType p _ _ -> p Unique p _ _ -> p instance HasPosition Struct_or_union where hasPosition = \case Struct p -> p Union p -> p instance HasPosition Struct_dec where hasPosition = \case Structen p _ _ -> p instance HasPosition Spec_qual where hasPosition = \case QualSpec p _ -> p TypeSpec p _ -> p instance HasPosition Struct_declarator where hasPosition = \case DecField p _ _ -> p Decl p _ -> p Field p _ -> p instance HasPosition Enum_specifier where hasPosition = \case EnumDec p _ -> p EnumName p _ _ -> p EnumVar p _ -> p instance HasPosition Enumerator where hasPosition = \case EnumInit p _ _ -> p Plain p _ -> p instance HasPosition Declarator where hasPosition = \case BeginPointer p _ _ -> p NoPointer p _ -> p instance HasPosition Direct_declarator where hasPosition = \case Incomplete p _ -> p InnitArray p _ _ -> p Name p _ -> p NewFuncDec p _ _ -> p OldFuncDec p _ -> p OldFuncDef p _ _ -> p ParenDecl p _ -> p instance HasPosition Pointer where hasPosition = \case Point p -> p PointPoint p _ -> p PointQual p _ -> p PointQualPoint p _ _ -> p instance HasPosition Parameter_type where hasPosition = \case AllSpec p _ -> p More p _ -> p instance HasPosition Parameter_declarations where hasPosition = \case MoreParamDec p _ _ -> p ParamDec p _ -> p instance HasPosition Parameter_declaration where hasPosition = \case Abstract p _ _ -> p OnlyType p _ -> p TypeAndParam p _ _ -> p instance HasPosition Initializer where hasPosition = \case InitExpr p _ -> p InitListOne p _ -> p InitListTwo p _ -> p instance HasPosition Initializers where hasPosition = \case AnInit p _ -> p MoreInit p _ _ -> p instance HasPosition Type_name where hasPosition = \case ExtendedType p _ _ -> p PlainType p _ -> p instance HasPosition Abstract_declarator where hasPosition = \case Advanced p _ -> p PointAdvanced p _ _ -> p PointerStart p _ -> p instance HasPosition Dir_abs_dec where hasPosition = \case Array p -> p Initiated p _ _ -> p InitiatedArray p _ -> p NewFuncExpr p _ _ -> p NewFunction p _ -> p OldFuncExpr p _ -> p OldFunction p -> p UnInitiated p _ -> p WithinParentes p _ -> p instance HasPosition Stm where hasPosition = \case CompS p _ -> p ExprS p _ -> p IterS p _ -> p JumpS p _ -> p LabelS p _ -> p SelS p _ -> p instance HasPosition Labeled_stm where hasPosition = \case SlabelOne p _ _ -> p SlabelThree p _ -> p SlabelTwo p _ _ -> p instance HasPosition Compound_stm where hasPosition = \case ScompFour p _ _ -> p ScompOne p -> p ScompThree p _ -> p ScompTwo p _ -> p instance HasPosition Expression_stm where hasPosition = \case SexprOne p -> p SexprTwo p _ -> p instance HasPosition Selection_stm where hasPosition = \case SselOne p _ _ -> p SselThree p _ _ -> p SselTwo p _ _ _ -> p instance HasPosition Iter_stm where hasPosition = \case SiterFour p _ _ _ _ -> p SiterOne p _ _ -> p SiterThree p _ _ _ -> p SiterTwo p _ _ -> p instance HasPosition Jump_stm where hasPosition = \case SjumpFive p _ -> p SjumpFour p -> p SjumpOne p _ -> p SjumpThree p -> p SjumpTwo p -> p instance HasPosition Exp where hasPosition = \case Earray p _ _ -> p Eassign p _ _ _ -> p Ebitand p _ _ -> p Ebitexor p _ _ -> p Ebitor p _ _ -> p Ebytesexpr p _ -> p Ebytestype p _ -> p Ecomma p _ _ -> p Econdition p _ _ _ -> p Econst p _ -> p Ediv p _ _ -> p Eeq p _ _ -> p Efunk p _ -> p Efunkpar p _ _ -> p Ege p _ _ -> p Egrthen p _ _ -> p Eland p _ _ -> p Ele p _ _ -> p Eleft p _ _ -> p Elor p _ _ -> p Elthen p _ _ -> p Eminus p _ _ -> p Emod p _ _ -> p Eneq p _ _ -> p Eplus p _ _ -> p Epoint p _ _ -> p Epostdec p _ -> p Epostinc p _ -> p Epredec p _ -> p Epreinc p _ -> p Epreop p _ _ -> p Eright p _ _ -> p Eselect p _ _ -> p Estring p _ -> p Etimes p _ _ -> p Etypeconv p _ _ -> p Evar p _ -> p instance HasPosition Constant where hasPosition = \case Ecdouble p _ -> p Ecfloat p _ -> p Echar p _ -> p Eclongdouble p _ -> p Edouble p _ -> p Efloat p _ -> p Ehexadec p _ -> p Ehexalong p _ -> p Ehexaunsign p _ -> p Ehexaunslong p _ -> p Eint p _ -> p Elong p _ -> p Elonger p _ -> p Eoctal p _ -> p Eoctallong p _ -> p Eoctalunsign p _ -> p Eoctalunslong p _ -> p Eunsigned p _ -> p Eunsignlong p _ -> p instance HasPosition Constant_expression where hasPosition = \case Especial p _ -> p instance HasPosition Unary_operator where hasPosition = \case Address p -> p Complement p -> p Indirection p -> p Logicalneg p -> p Negative p -> p Plus p -> p instance HasPosition Assignment_op where hasPosition = \case Assign p -> p AssignAdd p -> p AssignAnd p -> p AssignDiv p -> p AssignLeft p -> p AssignMod p -> p AssignMul p -> p AssignOr p -> p AssignRight p -> p AssignSub p -> p AssignXor p -> p