1 module PascalUnitSyntaxTree where |
|
2 |
|
3 import Data.Maybe |
|
4 import Data.Char |
|
5 |
|
6 data PascalUnit = |
|
7 Program Identifier Implementation Phrase |
|
8 | Unit Identifier Interface Implementation (Maybe Initialize) (Maybe Finalize) |
|
9 | System [TypeVarDeclaration] |
|
10 | Redo [TypeVarDeclaration] |
|
11 deriving Show |
|
12 data Interface = Interface Uses TypesAndVars |
|
13 deriving Show |
|
14 data Implementation = Implementation Uses TypesAndVars |
|
15 deriving Show |
|
16 data Identifier = Identifier String BaseType |
|
17 deriving Show |
|
18 data TypesAndVars = TypesAndVars [TypeVarDeclaration] |
|
19 deriving Show |
|
20 data TypeVarDeclaration = TypeDeclaration Identifier TypeDecl |
|
21 | VarDeclaration Bool Bool ([Identifier], TypeDecl) (Maybe InitExpression) |
|
22 | FunctionDeclaration Identifier Bool TypeDecl [TypeVarDeclaration] (Maybe (TypesAndVars, Phrase)) |
|
23 | OperatorDeclaration String Identifier Bool TypeDecl [TypeVarDeclaration] (Maybe (TypesAndVars, Phrase)) |
|
24 deriving Show |
|
25 data TypeDecl = SimpleType Identifier |
|
26 | RangeType Range |
|
27 | Sequence [Identifier] |
|
28 | ArrayDecl (Maybe Range) TypeDecl |
|
29 | RecordType [TypeVarDeclaration] (Maybe [[TypeVarDeclaration]]) |
|
30 | PointerTo TypeDecl |
|
31 | String Integer |
|
32 | Set TypeDecl |
|
33 | FunctionType TypeDecl [TypeVarDeclaration] |
|
34 | DeriveType InitExpression |
|
35 | VoidType |
|
36 | VarParamType TypeDecl -- this is a hack |
|
37 deriving Show |
|
38 data Range = Range Identifier |
|
39 | RangeFromTo InitExpression InitExpression |
|
40 | RangeInfinite |
|
41 deriving Show |
|
42 data Initialize = Initialize String |
|
43 deriving Show |
|
44 data Finalize = Finalize String |
|
45 deriving Show |
|
46 data Uses = Uses [Identifier] |
|
47 deriving Show |
|
48 data Phrase = ProcCall Reference [Expression] |
|
49 | IfThenElse Expression Phrase (Maybe Phrase) |
|
50 | WhileCycle Expression Phrase |
|
51 | RepeatCycle Expression [Phrase] |
|
52 | ForCycle Identifier Expression Expression Phrase Bool -- The last Boolean indicates wether it's up or down counting |
|
53 | WithBlock Reference Phrase |
|
54 | Phrases [Phrase] |
|
55 | SwitchCase Expression [([InitExpression], Phrase)] (Maybe [Phrase]) |
|
56 | Assignment Reference Expression |
|
57 | BuiltInFunctionCall [Expression] Reference |
|
58 | NOP |
|
59 deriving Show |
|
60 data Expression = Expression String |
|
61 | BuiltInFunCall [Expression] Reference |
|
62 | PrefixOp String Expression |
|
63 | PostfixOp String Expression |
|
64 | BinOp String Expression Expression |
|
65 | StringLiteral String |
|
66 | PCharLiteral String |
|
67 | CharCode String |
|
68 | HexCharCode String |
|
69 | NumberLiteral String |
|
70 | FloatLiteral String |
|
71 | HexNumber String |
|
72 | Reference Reference |
|
73 | SetExpression [Identifier] |
|
74 | Null |
|
75 deriving Show |
|
76 data Reference = ArrayElement [Expression] Reference |
|
77 | FunCall [Expression] Reference |
|
78 | TypeCast Identifier Expression |
|
79 | SimpleReference Identifier |
|
80 | Dereference Reference |
|
81 | RecordField Reference Reference |
|
82 | Address Reference |
|
83 | RefExpression Expression |
|
84 deriving Show |
|
85 data InitExpression = InitBinOp String InitExpression InitExpression |
|
86 | InitPrefixOp String InitExpression |
|
87 | InitReference Identifier |
|
88 | InitArray [InitExpression] |
|
89 | InitRecord [(Identifier, InitExpression)] |
|
90 | InitFloat String |
|
91 | InitNumber String |
|
92 | InitHexNumber String |
|
93 | InitString String |
|
94 | InitChar String |
|
95 | BuiltInFunction String [InitExpression] |
|
96 | InitSet [InitExpression] |
|
97 | InitAddress InitExpression |
|
98 | InitNull |
|
99 | InitRange Range |
|
100 | InitTypeCast Identifier InitExpression |
|
101 deriving Show |
|
102 |
|
103 data BaseType = BTUnknown |
|
104 | BTChar |
|
105 | BTString |
|
106 | BTInt |
|
107 | BTBool |
|
108 | BTFloat |
|
109 | BTRecord String [(String, BaseType)] |
|
110 | BTArray Range BaseType BaseType |
|
111 | BTFunction Bool Int BaseType |
|
112 | BTPointerTo BaseType |
|
113 | BTUnresolved String |
|
114 | BTSet BaseType |
|
115 | BTEnum [String] |
|
116 | BTVoid |
|
117 | BTUnit |
|
118 | BTVarParam BaseType |
|
119 deriving Show |
|