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