author | nemo |
Sun, 06 Nov 2011 10:26:12 -0500 | |
changeset 6299 | fa5bc796261d |
parent 6290 | c6245ed6cbc0 |
child 6307 | 25cfd9f4a567 |
permissions | -rw-r--r-- |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
1 |
module PascalParser where |
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
2 |
|
6272 | 3 |
import Text.Parsec.Expr |
4 |
import Text.Parsec.Char |
|
5 |
import Text.Parsec.Token |
|
6 |
import Text.Parsec.Language |
|
7 |
import Text.Parsec.Prim |
|
8 |
import Text.Parsec.Combinator |
|
9 |
import Text.Parsec.String |
|
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
10 |
import Control.Monad |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
11 |
import Data.Char |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
12 |
|
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
13 |
data PascalUnit = |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
14 |
Program Identifier Implementation |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
15 |
| Unit Identifier Interface Implementation (Maybe Initialize) (Maybe Finalize) |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
16 |
deriving Show |
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
17 |
data Interface = Interface Uses TypesAndVars |
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
18 |
deriving Show |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
19 |
data Implementation = Implementation Uses TypesAndVars |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
20 |
deriving Show |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
21 |
data Identifier = Identifier String |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
22 |
deriving Show |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
23 |
data TypesAndVars = TypesAndVars [TypeVarDeclaration] |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
24 |
deriving Show |
6277 | 25 |
data TypeVarDeclaration = TypeDeclaration Identifier TypeDecl |
26 |
| VarDeclaration Bool ([Identifier], TypeDecl) (Maybe Expression) |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
27 |
| FunctionDeclaration Identifier Identifier (Maybe Phrase) |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
28 |
deriving Show |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
29 |
data TypeDecl = SimpleType Identifier |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
30 |
| RangeType Range |
6277 | 31 |
| Sequence [Identifier] |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
32 |
| ArrayDecl Range TypeDecl |
6277 | 33 |
| RecordType [TypeVarDeclaration] |
6290 | 34 |
| PointerTo TypeDecl |
6277 | 35 |
| UnknownType |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
36 |
deriving Show |
6277 | 37 |
data Range = Range Identifier |
38 |
| RangeFromTo Expression Expression |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
39 |
deriving Show |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
40 |
data Initialize = Initialize String |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
41 |
deriving Show |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
42 |
data Finalize = Finalize String |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
43 |
deriving Show |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
44 |
data Uses = Uses [Identifier] |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
45 |
deriving Show |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
46 |
data Phrase = ProcCall Identifier [Expression] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
47 |
| IfThenElse Expression Phrase (Maybe Phrase) |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
48 |
| WhileCycle Expression Phrase |
6275 | 49 |
| RepeatCycle Expression [Phrase] |
50 |
| ForCycle Identifier Expression Expression Phrase |
|
51 |
| WithBlock Expression Phrase |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
52 |
| Phrases [Phrase] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
53 |
| SwitchCase Expression [(Expression, Phrase)] (Maybe Phrase) |
6275 | 54 |
| Assignment Reference Expression |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
55 |
deriving Show |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
56 |
data Expression = Expression String |
6277 | 57 |
| FunCall Reference [Expression] |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
58 |
| PrefixOp String Expression |
6275 | 59 |
| PostfixOp String Expression |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
60 |
| BinOp String Expression Expression |
6275 | 61 |
| StringLiteral String |
6277 | 62 |
| CharCode String |
6275 | 63 |
| NumberLiteral String |
6277 | 64 |
| HexNumber String |
65 |
| Address Reference |
|
6275 | 66 |
| Reference Reference |
6290 | 67 |
| Null |
6275 | 68 |
deriving Show |
69 |
data Reference = ArrayElement Identifier Expression |
|
70 |
| SimpleReference Identifier |
|
71 |
| RecordField Reference Reference |
|
72 |
| Dereference Reference |
|
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
73 |
deriving Show |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
74 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
75 |
pascalLanguageDef |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
76 |
= emptyDef |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
77 |
{ commentStart = "(*" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
78 |
, commentEnd = "*)" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
79 |
, commentLine = "//" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
80 |
, nestedComments = False |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
81 |
, identStart = letter <|> oneOf "_" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
82 |
, identLetter = alphaNum <|> oneOf "_." |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
83 |
, reservedNames = [ |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
84 |
"begin", "end", "program", "unit", "interface" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
85 |
, "implementation", "and", "or", "xor", "shl" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
86 |
, "shr", "while", "do", "repeat", "until", "case", "of" |
6290 | 87 |
, "type", "var", "const", "out", "array", "packed" |
6275 | 88 |
, "procedure", "function", "with", "for", "to" |
6290 | 89 |
, "downto", "div", "mod", "record", "set", "nil" |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
90 |
] |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
91 |
, reservedOpNames= [] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
92 |
, caseSensitive = False |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
93 |
} |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
94 |
|
6275 | 95 |
pas = patch $ makeTokenParser pascalLanguageDef |
96 |
where |
|
6277 | 97 |
patch tp = tp {stringLiteral = sl} |
98 |
sl = do |
|
99 |
(char '\'') |
|
100 |
s <- (many $ noneOf "'") |
|
101 |
(char '\'') |
|
102 |
ss <- many $ do |
|
103 |
(char '\'') |
|
104 |
s' <- (many $ noneOf "'") |
|
105 |
(char '\'') |
|
106 |
return $ '\'' : s' |
|
107 |
comments |
|
108 |
return $ concat (s:ss) |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
109 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
110 |
comments = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
111 |
spaces |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
112 |
skipMany $ do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
113 |
comment |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
114 |
spaces |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
115 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
116 |
pascalUnit = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
117 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
118 |
u <- choice [program, unit] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
119 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
120 |
return u |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
121 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
122 |
comment = choice [ |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
123 |
char '{' >> manyTill anyChar (try $ char '}') |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
124 |
, (try $ string "(*") >> manyTill anyChar (try $ string "*)") |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
125 |
, (try $ string "//") >> manyTill anyChar (try newline) |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
126 |
] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
127 |
|
6275 | 128 |
iD = do |
129 |
i <- liftM Identifier (identifier pas) |
|
130 |
comments |
|
131 |
return i |
|
132 |
||
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
133 |
unit = do |
6275 | 134 |
string "unit" >> comments |
135 |
name <- iD |
|
136 |
semi pas |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
137 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
138 |
int <- interface |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
139 |
impl <- implementation |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
140 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
141 |
return $ Unit name int impl Nothing Nothing |
6275 | 142 |
|
143 |
||
144 |
reference = buildExpressionParser table term <?> "reference" |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
145 |
where |
6275 | 146 |
term = comments >> choice [ |
147 |
parens pas reference |
|
148 |
, try $ iD >>= \i -> (brackets pas) expression >>= return . ArrayElement i |
|
149 |
, iD >>= return . SimpleReference |
|
150 |
] <?> "simple reference" |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
151 |
|
6275 | 152 |
table = [ |
153 |
[Postfix (char '^' >> return Dereference)] |
|
154 |
, [Infix (char '.' >> return RecordField) AssocLeft] |
|
155 |
] |
|
156 |
||
6290 | 157 |
varsDecl1 = varsParser sepEndBy1 |
158 |
varsDecl = varsParser sepEndBy |
|
6277 | 159 |
varsParser m endsWithSemi = do |
6290 | 160 |
vs <- m (aVarDecl endsWithSemi) (semi pas) |
161 |
return vs |
|
162 |
||
163 |
aVarDecl endsWithSemi = do |
|
164 |
when (not endsWithSemi) $ |
|
165 |
optional $ choice [ |
|
166 |
try $ string "var" |
|
167 |
, try $ string "const" |
|
168 |
, try $ string "out" |
|
169 |
] |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
170 |
comments |
6290 | 171 |
ids <- do |
172 |
i <- (commaSep1 pas) $ (try iD <?> "variable declaration") |
|
173 |
char ':' |
|
174 |
return i |
|
175 |
comments |
|
176 |
t <- typeDecl <?> "variable type declaration" |
|
177 |
comments |
|
178 |
init <- option Nothing $ do |
|
179 |
char '=' |
|
6275 | 180 |
comments |
6290 | 181 |
e <- expression |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
182 |
comments |
6290 | 183 |
return (Just e) |
184 |
return $ VarDeclaration False (ids, t) init |
|
6275 | 185 |
|
186 |
||
187 |
constsDecl = do |
|
6277 | 188 |
vs <- many (try (aConstDecl >>= \i -> semi pas >> return i) >>= \i -> comments >> return i) |
6275 | 189 |
comments |
6277 | 190 |
return vs |
6275 | 191 |
where |
192 |
aConstDecl = do |
|
193 |
comments |
|
6277 | 194 |
i <- iD <?> "const declaration" |
6275 | 195 |
optional $ do |
196 |
char ':' |
|
197 |
comments |
|
198 |
t <- typeDecl |
|
199 |
return () |
|
200 |
char '=' |
|
201 |
comments |
|
202 |
e <- expression |
|
203 |
comments |
|
6277 | 204 |
return $ VarDeclaration False ([i], UnknownType) (Just e) |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
205 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
206 |
typeDecl = choice [ |
6290 | 207 |
char '^' >> typeDecl >>= return . PointerTo |
208 |
, arrayDecl |
|
6277 | 209 |
, recordDecl |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
210 |
, rangeDecl >>= return . RangeType |
6277 | 211 |
, seqenceDecl >>= return . Sequence |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
212 |
, identifier pas >>= return . SimpleType . Identifier |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
213 |
] <?> "type declaration" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
214 |
where |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
215 |
arrayDecl = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
216 |
try $ string "array" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
217 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
218 |
char '[' |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
219 |
r <- rangeDecl |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
220 |
char ']' |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
221 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
222 |
string "of" |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
223 |
comments |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
224 |
t <- typeDecl |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
225 |
return $ ArrayDecl r t |
6277 | 226 |
recordDecl = do |
6290 | 227 |
optional $ (try $ string "packed") >> comments |
6277 | 228 |
try $ string "record" |
229 |
comments |
|
230 |
vs <- varsDecl True |
|
231 |
string "end" |
|
232 |
return $ RecordType vs |
|
233 |
seqenceDecl = (parens pas) $ (commaSep pas) iD |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
234 |
|
6277 | 235 |
typesDecl = many (aTypeDecl >>= \t -> comments >> return t) |
236 |
where |
|
237 |
aTypeDecl = do |
|
238 |
i <- try $ do |
|
239 |
i <- iD <?> "type declaration" |
|
240 |
comments |
|
241 |
char '=' |
|
242 |
return i |
|
243 |
comments |
|
244 |
t <- typeDecl |
|
245 |
comments |
|
246 |
semi pas |
|
247 |
comments |
|
248 |
return $ TypeDeclaration i t |
|
6275 | 249 |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
250 |
rangeDecl = choice [ |
6277 | 251 |
try $ rangeft |
252 |
, iD >>= return . Range |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
253 |
] <?> "range declaration" |
6277 | 254 |
where |
255 |
rangeft = do |
|
256 |
e1 <- expression |
|
257 |
string ".." |
|
258 |
e2 <- expression |
|
259 |
return $ RangeFromTo e1 e2 |
|
6275 | 260 |
|
6277 | 261 |
typeVarDeclaration isImpl = (liftM concat . many . choice) [ |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
262 |
varSection, |
6275 | 263 |
constSection, |
6277 | 264 |
typeSection, |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
265 |
funcDecl, |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
266 |
procDecl |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
267 |
] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
268 |
where |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
269 |
varSection = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
270 |
try $ string "var" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
271 |
comments |
6277 | 272 |
v <- varsDecl1 True |
6272 | 273 |
comments |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
274 |
return v |
6275 | 275 |
|
276 |
constSection = do |
|
277 |
try $ string "const" |
|
278 |
comments |
|
279 |
c <- constsDecl |
|
280 |
comments |
|
281 |
return c |
|
6277 | 282 |
|
283 |
typeSection = do |
|
284 |
try $ string "type" |
|
285 |
comments |
|
286 |
t <- typesDecl |
|
287 |
comments |
|
288 |
return t |
|
6275 | 289 |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
290 |
procDecl = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
291 |
string "procedure" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
292 |
comments |
6275 | 293 |
i <- iD |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
294 |
optional $ do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
295 |
char '(' |
6272 | 296 |
varsDecl False |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
297 |
char ')' |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
298 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
299 |
char ';' |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
300 |
b <- if isImpl then |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
301 |
do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
302 |
comments |
6277 | 303 |
optional $ typeVarDeclaration True |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
304 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
305 |
liftM Just functionBody |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
306 |
else |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
307 |
return Nothing |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
308 |
comments |
6277 | 309 |
return $ [FunctionDeclaration i (Identifier "") b] |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
310 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
311 |
funcDecl = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
312 |
string "function" |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
313 |
comments |
6275 | 314 |
i <- iD |
6272 | 315 |
optional $ do |
316 |
char '(' |
|
317 |
varsDecl False |
|
318 |
char ')' |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
319 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
320 |
char ':' |
6290 | 321 |
comments |
6275 | 322 |
ret <- iD |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
323 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
324 |
char ';' |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
325 |
b <- if isImpl then |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
326 |
do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
327 |
comments |
6277 | 328 |
optional $ typeVarDeclaration True |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
329 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
330 |
liftM Just functionBody |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
331 |
else |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
332 |
return Nothing |
6277 | 333 |
return $ [FunctionDeclaration i ret Nothing] |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
334 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
335 |
program = do |
6275 | 336 |
string "program" |
337 |
comments |
|
338 |
name <- iD |
|
339 |
(char ';') |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
340 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
341 |
impl <- implementation |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
342 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
343 |
return $ Program name impl |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
344 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
345 |
interface = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
346 |
string "interface" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
347 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
348 |
u <- uses |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
349 |
comments |
6277 | 350 |
tv <- typeVarDeclaration False |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
351 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
352 |
return $ Interface u (TypesAndVars tv) |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
353 |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
354 |
implementation = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
355 |
string "implementation" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
356 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
357 |
u <- uses |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
358 |
comments |
6277 | 359 |
tv <- typeVarDeclaration True |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
360 |
string "end." |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
361 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
362 |
return $ Implementation u (TypesAndVars tv) |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
363 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
364 |
expression = buildExpressionParser table term <?> "expression" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
365 |
where |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
366 |
term = comments >> choice [ |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
367 |
parens pas $ expression |
6275 | 368 |
, integer pas >>= return . NumberLiteral . show |
369 |
, stringLiteral pas >>= return . StringLiteral |
|
6277 | 370 |
, char '#' >> many digit >>= return . CharCode |
371 |
, char '$' >> many hexDigit >>= return . HexNumber |
|
372 |
, char '@' >> reference >>= return . Address |
|
6290 | 373 |
, try $ string "nil" >> return Null |
6275 | 374 |
, try $ funCall |
375 |
, reference >>= return . Reference |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
376 |
] <?> "simple expression" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
377 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
378 |
table = [ |
6290 | 379 |
[ Infix (char '*' >> return (BinOp "*")) AssocLeft |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
380 |
, Infix (char '/' >> return (BinOp "/")) AssocLeft |
6275 | 381 |
, Infix (try (string "div") >> return (BinOp "div")) AssocLeft |
382 |
, Infix (try (string "mod") >> return (BinOp "mod")) AssocLeft |
|
383 |
] |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
384 |
, [ Infix (char '+' >> return (BinOp "+")) AssocLeft |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
385 |
, Infix (char '-' >> return (BinOp "-")) AssocLeft |
6275 | 386 |
, Prefix (char '-' >> return (PrefixOp "-")) |
387 |
] |
|
388 |
, [ Infix (try (string "<>") >> return (BinOp "<>")) AssocNone |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
389 |
, Infix (try (string "<=") >> return (BinOp "<=")) AssocNone |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
390 |
, Infix (try (string ">=") >> return (BinOp ">=")) AssocNone |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
391 |
, Infix (char '<' >> return (BinOp "<")) AssocNone |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
392 |
, Infix (char '>' >> return (BinOp ">")) AssocNone |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
393 |
, Infix (char '=' >> return (BinOp "=")) AssocNone |
6275 | 394 |
] |
395 |
, [ Infix (try $ string "and" >> return (BinOp "and")) AssocLeft |
|
396 |
, Infix (try $ string "or" >> return (BinOp "or")) AssocLeft |
|
397 |
, Infix (try $ string "xor" >> return (BinOp "xor")) AssocLeft |
|
398 |
] |
|
6290 | 399 |
, [Prefix (try (string "not") >> return (PrefixOp "not"))] |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
400 |
] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
401 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
402 |
phrasesBlock = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
403 |
try $ string "begin" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
404 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
405 |
p <- manyTill phrase (try $ string "end") |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
406 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
407 |
return $ Phrases p |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
408 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
409 |
phrase = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
410 |
o <- choice [ |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
411 |
phrasesBlock |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
412 |
, ifBlock |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
413 |
, whileCycle |
6275 | 414 |
, repeatCycle |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
415 |
, switchCase |
6275 | 416 |
, withBlock |
417 |
, forCycle |
|
418 |
, (try $ reference >>= \r -> string ":=" >> return r) >>= \r -> expression >>= return . Assignment r |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
419 |
, procCall |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
420 |
] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
421 |
optional $ char ';' |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
422 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
423 |
return o |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
424 |
|
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
425 |
ifBlock = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
426 |
try $ string "if" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
427 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
428 |
e <- expression |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
429 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
430 |
string "then" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
431 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
432 |
o1 <- phrase |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
433 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
434 |
o2 <- optionMaybe $ do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
435 |
try $ string "else" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
436 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
437 |
o <- phrase |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
438 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
439 |
return o |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
440 |
return $ IfThenElse e o1 o2 |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
441 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
442 |
whileCycle = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
443 |
try $ string "while" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
444 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
445 |
e <- expression |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
446 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
447 |
string "do" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
448 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
449 |
o <- phrase |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
450 |
return $ WhileCycle e o |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
451 |
|
6275 | 452 |
withBlock = do |
453 |
try $ string "with" |
|
454 |
comments |
|
455 |
e <- expression |
|
456 |
comments |
|
457 |
string "do" |
|
458 |
comments |
|
459 |
o <- phrase |
|
460 |
return $ WithBlock e o |
|
461 |
||
462 |
repeatCycle = do |
|
463 |
try $ string "repeat" |
|
464 |
comments |
|
465 |
o <- many phrase |
|
466 |
string "until" |
|
467 |
comments |
|
468 |
e <- expression |
|
469 |
comments |
|
470 |
return $ RepeatCycle e o |
|
471 |
||
472 |
forCycle = do |
|
473 |
try $ string "for" |
|
474 |
comments |
|
475 |
i <- iD |
|
476 |
comments |
|
477 |
string ":=" |
|
478 |
comments |
|
479 |
e1 <- expression |
|
480 |
comments |
|
481 |
choice [string "to", string "downto"] |
|
482 |
comments |
|
483 |
e2 <- expression |
|
484 |
comments |
|
485 |
string "do" |
|
486 |
comments |
|
487 |
p <- phrase |
|
488 |
comments |
|
489 |
return $ ForCycle i e1 e2 p |
|
490 |
||
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
491 |
switchCase = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
492 |
try $ string "case" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
493 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
494 |
e <- expression |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
495 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
496 |
string "of" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
497 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
498 |
cs <- many1 aCase |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
499 |
o2 <- optionMaybe $ do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
500 |
try $ string "else" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
501 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
502 |
o <- phrase |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
503 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
504 |
return o |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
505 |
string "end" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
506 |
return $ SwitchCase e cs o2 |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
507 |
where |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
508 |
aCase = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
509 |
e <- expression |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
510 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
511 |
char ':' |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
512 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
513 |
p <- phrase |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
514 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
515 |
return (e, p) |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
516 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
517 |
procCall = do |
6275 | 518 |
i <- iD |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
519 |
p <- option [] $ (parens pas) parameters |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
520 |
return $ ProcCall i p |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
521 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
522 |
funCall = do |
6277 | 523 |
r <- reference |
6275 | 524 |
p <- (parens pas) $ option [] parameters |
6277 | 525 |
return $ FunCall r p |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
526 |
|
6275 | 527 |
parameters = (commaSep pas) expression <?> "parameters" |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
528 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
529 |
functionBody = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
530 |
p <- phrasesBlock |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
531 |
char ';' |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
532 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
533 |
return p |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
534 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
535 |
uses = liftM Uses (option [] u) |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
536 |
where |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
537 |
u = do |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
538 |
string "uses" |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
539 |
comments |
6275 | 540 |
u <- (iD >>= \i -> comments >> return i) `sepBy1` (char ',' >> comments) |
6270
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
541 |
char ';' |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
542 |
comments |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
543 |
return u |