author | Xeli |
Sat, 05 May 2012 16:38:41 +0200 | |
changeset 7022 | 107651b3c5a0 |
parent 6897 | a9126661f613 |
child 7043 | 7c080e5ac8d0 |
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 |
|
6412 | 3 |
import Text.Parsec |
6272 | 4 |
import Text.Parsec.Char |
5 |
import Text.Parsec.Token |
|
6 |
import Text.Parsec.Language |
|
6412 | 7 |
import Text.Parsec.Expr |
6272 | 8 |
import Text.Parsec.Prim |
9 |
import Text.Parsec.Combinator |
|
10 |
import Text.Parsec.String |
|
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
11 |
import Control.Monad |
6399 | 12 |
import Data.Maybe |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
13 |
|
6412 | 14 |
import PascalBasics |
6467 | 15 |
import PascalUnitSyntaxTree |
6450 | 16 |
|
6891
ab9843957664
Improve rendering of function types, ranges, and more
unc0rr
parents:
6875
diff
changeset
|
17 |
knownTypes = ["shortstring", "ansistring", "char", "byte"] |
6357 | 18 |
|
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 |
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
|
20 |
comments |
6512 | 21 |
u <- choice [program, unit, systemUnit] |
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
|
22 |
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
|
23 |
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
|
24 |
|
6275 | 25 |
iD = do |
6618 | 26 |
i <- liftM (flip Identifier BTUnknown) (identifier pas) |
6275 | 27 |
comments |
28 |
return i |
|
29 |
||
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
|
30 |
unit = do |
6275 | 31 |
string "unit" >> comments |
32 |
name <- iD |
|
33 |
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
|
34 |
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
|
35 |
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
|
36 |
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
|
37 |
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
|
38 |
return $ Unit name int impl Nothing Nothing |
6275 | 39 |
|
40 |
||
41 |
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
|
42 |
where |
6275 | 43 |
term = comments >> choice [ |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
44 |
parens pas (liftM RefExpression expression >>= postfixes) >>= postfixes |
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
45 |
, try $ typeCast >>= postfixes |
6450 | 46 |
, char '@' >> liftM Address reference >>= postfixes |
6386
7d7703b26bda
Prefix followed by prefix issue solved. Also some slight improvements.
unc0rr
parents:
6357
diff
changeset
|
47 |
, liftM SimpleReference iD >>= postfixes |
6275 | 48 |
] <?> "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
|
49 |
|
6275 | 50 |
table = [ |
51 |
] |
|
6386
7d7703b26bda
Prefix followed by prefix issue solved. Also some slight improvements.
unc0rr
parents:
6357
diff
changeset
|
52 |
|
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
53 |
postfixes r = many postfix >>= return . foldl (flip ($)) r |
6386
7d7703b26bda
Prefix followed by prefix issue solved. Also some slight improvements.
unc0rr
parents:
6357
diff
changeset
|
54 |
postfix = choice [ |
7d7703b26bda
Prefix followed by prefix issue solved. Also some slight improvements.
unc0rr
parents:
6357
diff
changeset
|
55 |
parens pas (option [] parameters) >>= return . FunCall |
7d7703b26bda
Prefix followed by prefix issue solved. Also some slight improvements.
unc0rr
parents:
6357
diff
changeset
|
56 |
, char '^' >> return Dereference |
7d7703b26bda
Prefix followed by prefix issue solved. Also some slight improvements.
unc0rr
parents:
6357
diff
changeset
|
57 |
, (brackets pas) (commaSep1 pas $ expression) >>= return . ArrayElement |
6467 | 58 |
, (char '.' >> notFollowedBy (char '.')) >> liftM (flip RecordField) reference |
6386
7d7703b26bda
Prefix followed by prefix issue solved. Also some slight improvements.
unc0rr
parents:
6357
diff
changeset
|
59 |
] |
6316 | 60 |
|
6450 | 61 |
typeCast = do |
62 |
t <- choice $ map (\s -> try $ caseInsensitiveString s >>= \i -> notFollowedBy alphaNum >> return i) knownTypes |
|
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
63 |
e <- parens pas expression |
6450 | 64 |
comments |
6618 | 65 |
return $ TypeCast (Identifier t BTUnknown) e |
6450 | 66 |
|
6275 | 67 |
|
6290 | 68 |
varsDecl1 = varsParser sepEndBy1 |
69 |
varsDecl = varsParser sepEndBy |
|
6277 | 70 |
varsParser m endsWithSemi = do |
6290 | 71 |
vs <- m (aVarDecl endsWithSemi) (semi pas) |
72 |
return vs |
|
73 |
||
74 |
aVarDecl endsWithSemi = do |
|
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
75 |
unless endsWithSemi $ |
6290 | 76 |
optional $ choice [ |
77 |
try $ string "var" |
|
78 |
, try $ string "const" |
|
79 |
, try $ string "out" |
|
80 |
] |
|
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
|
81 |
comments |
6290 | 82 |
ids <- do |
83 |
i <- (commaSep1 pas) $ (try iD <?> "variable declaration") |
|
84 |
char ':' |
|
85 |
return i |
|
86 |
comments |
|
87 |
t <- typeDecl <?> "variable type declaration" |
|
88 |
comments |
|
89 |
init <- option Nothing $ do |
|
90 |
char '=' |
|
6275 | 91 |
comments |
6355 | 92 |
e <- initExpression |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
93 |
comments |
6290 | 94 |
return (Just e) |
95 |
return $ VarDeclaration False (ids, t) init |
|
6275 | 96 |
|
97 |
||
98 |
constsDecl = do |
|
6317
83b93a2d2741
Improve parsing of complex references like "a^[b[c], d]"
unc0rr
parents:
6316
diff
changeset
|
99 |
vs <- many1 (try (aConstDecl >>= \i -> semi pas >> return i) >>= \i -> comments >> return i) |
6275 | 100 |
comments |
6277 | 101 |
return vs |
6275 | 102 |
where |
103 |
aConstDecl = do |
|
104 |
comments |
|
6443
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
105 |
i <- iD |
6444 | 106 |
t <- optionMaybe $ do |
6275 | 107 |
char ':' |
108 |
comments |
|
109 |
t <- typeDecl |
|
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
110 |
comments |
6444 | 111 |
return t |
6275 | 112 |
char '=' |
113 |
comments |
|
6355 | 114 |
e <- initExpression |
6275 | 115 |
comments |
6875
6528171ce36d
First try to compile with clang: improve renderer a bit. The result of pas2c is still far from normal C source.
unc0rr
parents:
6858
diff
changeset
|
116 |
return $ VarDeclaration (isNothing t) ([i], fromMaybe (DeriveType e) t) (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
|
117 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. 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 |
typeDecl = choice [ |
6290 | 119 |
char '^' >> typeDecl >>= return . PointerTo |
6399 | 120 |
, try (string "shortstring") >> return (String 255) |
121 |
, try (string "string") >> optionMaybe (brackets pas $ integer pas) >>= return . String . fromMaybe 255 |
|
6891
ab9843957664
Improve rendering of function types, ranges, and more
unc0rr
parents:
6875
diff
changeset
|
122 |
, try (string "ansistring") >> optionMaybe (brackets pas $ integer pas) >>= return . String . fromMaybe 255 |
6290 | 123 |
, arrayDecl |
6277 | 124 |
, recordDecl |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
125 |
, setDecl |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
126 |
, functionType |
6355 | 127 |
, sequenceDecl >>= return . Sequence |
6489 | 128 |
, try iD >>= return . SimpleType |
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
|
129 |
, rangeDecl >>= return . RangeType |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
130 |
] <?> "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
|
131 |
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
|
132 |
arrayDecl = do |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
133 |
try $ do |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
134 |
optional $ (try $ string "packed") >> comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
135 |
string "array" |
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
|
136 |
comments |
6426 | 137 |
r <- option [] $ do |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
138 |
char '[' |
6426 | 139 |
r <- commaSep pas rangeDecl |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
140 |
char ']' |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
141 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
142 |
return 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
|
143 |
string "of" |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
144 |
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
|
145 |
t <- typeDecl |
6426 | 146 |
if null r then |
147 |
return $ ArrayDecl Nothing t |
|
148 |
else |
|
149 |
return $ foldr (\a b -> ArrayDecl (Just a) b) (ArrayDecl (Just $ head r) t) (tail r) |
|
6277 | 150 |
recordDecl = do |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
151 |
try $ do |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
152 |
optional $ (try $ string "packed") >> comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
153 |
string "record" |
6277 | 154 |
comments |
155 |
vs <- varsDecl True |
|
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
156 |
union <- optionMaybe $ do |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
157 |
string "case" |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
158 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
159 |
iD |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
160 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
161 |
string "of" |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
162 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
163 |
many unionCase |
6277 | 164 |
string "end" |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
165 |
return $ RecordType vs union |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
166 |
setDecl = do |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
167 |
try $ string "set" >> space |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
168 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
169 |
string "of" |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
170 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
171 |
liftM Set typeDecl |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
172 |
unionCase = do |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
173 |
try $ commaSep pas $ (iD >> return ()) <|> (integer pas >> return ()) |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
174 |
char ':' |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
175 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
176 |
u <- parens pas $ varsDecl True |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
177 |
char ';' |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
178 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
179 |
return u |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
180 |
sequenceDecl = (parens pas) $ (commaSep pas) (iD >>= \i -> optional (spaces >> char '=' >> spaces >> integer pas) >> return i) |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
181 |
functionType = do |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
182 |
fp <- try (string "function") <|> try (string "procedure") |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
183 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
184 |
vs <- option [] $ parens pas $ varsDecl False |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
185 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
186 |
ret <- if (fp == "function") then do |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
187 |
char ':' |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
188 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
189 |
ret <- typeDecl |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
190 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
191 |
return ret |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
192 |
else |
6826 | 193 |
return VoidType |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
194 |
optional $ try $ char ';' >> comments >> string "cdecl" |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
195 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
196 |
return $ FunctionType ret vs |
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
|
197 |
|
6277 | 198 |
typesDecl = many (aTypeDecl >>= \t -> comments >> return t) |
199 |
where |
|
200 |
aTypeDecl = do |
|
201 |
i <- try $ do |
|
202 |
i <- iD <?> "type declaration" |
|
203 |
comments |
|
204 |
char '=' |
|
205 |
return i |
|
206 |
comments |
|
207 |
t <- typeDecl |
|
208 |
comments |
|
209 |
semi pas |
|
210 |
comments |
|
211 |
return $ TypeDeclaration i t |
|
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
212 |
|
6275 | 213 |
|
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
|
214 |
rangeDecl = choice [ |
6277 | 215 |
try $ rangeft |
216 |
, 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
|
217 |
] <?> "range declaration" |
6277 | 218 |
where |
219 |
rangeft = do |
|
6388 | 220 |
e1 <- initExpression |
6277 | 221 |
string ".." |
6388 | 222 |
e2 <- initExpression |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
223 |
return $ RangeFromTo e1 e2 |
6275 | 224 |
|
6277 | 225 |
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
|
226 |
varSection, |
6275 | 227 |
constSection, |
6277 | 228 |
typeSection, |
6443
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
229 |
funcDecl, |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
230 |
operatorDecl |
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
|
231 |
] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
232 |
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
|
233 |
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
|
234 |
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
|
235 |
comments |
6443
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
236 |
v <- varsDecl1 True <?> "variable declaration" |
6272 | 237 |
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
|
238 |
return v |
6275 | 239 |
|
240 |
constSection = do |
|
241 |
try $ string "const" |
|
242 |
comments |
|
6443
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
243 |
c <- constsDecl <?> "const declaration" |
6275 | 244 |
comments |
245 |
return c |
|
6277 | 246 |
|
247 |
typeSection = do |
|
248 |
try $ string "type" |
|
249 |
comments |
|
6443
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
250 |
t <- typesDecl <?> "type declaration" |
6277 | 251 |
comments |
252 |
return t |
|
6275 | 253 |
|
6443
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
254 |
operatorDecl = do |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
255 |
try $ string "operator" |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
256 |
comments |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
257 |
i <- manyTill anyChar space |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
258 |
comments |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
259 |
vs <- parens pas $ varsDecl False |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
260 |
comments |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
261 |
rid <- iD |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
262 |
comments |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
263 |
char ':' |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
264 |
comments |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
265 |
ret <- typeDecl |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
266 |
comments |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
267 |
return ret |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
268 |
char ';' |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
269 |
comments |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
270 |
forward <- liftM isJust $ optionMaybe (try (string "forward;") >> comments) |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
271 |
many functionDecorator |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
272 |
b <- if isImpl && (not forward) then |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
273 |
liftM Just functionBody |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
274 |
else |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
275 |
return Nothing |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
276 |
return $ [OperatorDeclaration i rid ret vs b] |
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
277 |
|
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
278 |
|
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
279 |
funcDecl = do |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
280 |
fp <- try (string "function") <|> try (string "procedure") |
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
|
281 |
comments |
6275 | 282 |
i <- iD |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
283 |
vs <- option [] $ parens pas $ 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
|
284 |
comments |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
285 |
ret <- if (fp == "function") then do |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
286 |
char ':' |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
287 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
288 |
ret <- typeDecl |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
289 |
comments |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
290 |
return ret |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
291 |
else |
6836 | 292 |
return VoidType |
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
|
293 |
char ';' |
6399 | 294 |
comments |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
295 |
forward <- liftM isJust $ optionMaybe (try (string "forward;") >> comments) |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
296 |
many functionDecorator |
6417
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
297 |
b <- if isImpl && (not forward) then |
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
|
298 |
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
|
299 |
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
|
300 |
return Nothing |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
301 |
return $ [FunctionDeclaration i ret vs b] |
6443
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
302 |
|
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
303 |
functionDecorator = choice [ |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
304 |
try $ string "inline;" |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
305 |
, try $ caseInsensitiveString "cdecl;" |
6444 | 306 |
, try $ string "overload;" |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
307 |
, try $ string "export;" |
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
308 |
, try $ string "varargs;" |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
309 |
, try (string "external") >> comments >> iD >> optional (string "name" >> comments >> stringLiteral pas)>> string ";" |
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
310 |
] >> comments |
6443
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
311 |
|
23364a5fcc86
- Help parser by dropping that insane formatting syntax in str function
unc0rr
parents:
6426
diff
changeset
|
312 |
|
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
|
313 |
program = do |
6275 | 314 |
string "program" |
315 |
comments |
|
316 |
name <- iD |
|
317 |
(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
|
318 |
comments |
6417
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
319 |
comments |
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
320 |
u <- uses |
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
321 |
comments |
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
322 |
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
|
323 |
comments |
6417
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
324 |
p <- phrase |
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
325 |
comments |
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
326 |
char '.' |
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
327 |
comments |
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
328 |
return $ Program name (Implementation u (TypesAndVars tv)) 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
|
329 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. 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 |
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
|
331 |
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
|
332 |
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
|
333 |
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
|
334 |
comments |
6277 | 335 |
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
|
336 |
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
|
337 |
return $ Interface u (TypesAndVars tv) |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
338 |
|
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
|
339 |
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
|
340 |
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
|
341 |
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
|
342 |
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
|
343 |
comments |
6277 | 344 |
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
|
345 |
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
|
346 |
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
|
347 |
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
|
348 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. 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 |
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
|
350 |
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
|
351 |
term = comments >> choice [ |
6618 | 352 |
builtInFunction expression >>= \(n, e) -> return $ BuiltInFunCall e (SimpleReference (Identifier n BTUnknown)) |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
353 |
, try (parens pas $ expression >>= \e -> notFollowedBy (comments >> char '.') >> return e) |
6450 | 354 |
, brackets pas (commaSep pas iD) >>= return . SetExpression |
6412 | 355 |
, try $ natural pas >>= \i -> notFollowedBy (char '.') >> (return . NumberLiteral . show) i |
6452 | 356 |
, float pas >>= return . FloatLiteral . show |
357 |
, natural pas >>= return . NumberLiteral . show |
|
6275 | 358 |
, stringLiteral pas >>= return . StringLiteral |
6444 | 359 |
, try (string "#$") >> many hexDigit >>= \c -> comments >> return (HexCharCode c) |
6417
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
360 |
, char '#' >> many digit >>= \c -> comments >> return (CharCode c) |
eae5900fd8a4
Improve parser a bit, preparation to parsing whole program at once and compiling it into single C file
unc0rr
parents:
6414
diff
changeset
|
361 |
, char '$' >> many hexDigit >>= \h -> comments >> return (HexNumber h) |
6412 | 362 |
, char '-' >> expression >>= return . PrefixOp "-" |
6290 | 363 |
, try $ string "nil" >> return Null |
6467 | 364 |
, try $ string "not" >> expression >>= return . PrefixOp "not" |
6275 | 365 |
, 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
|
366 |
] <?> "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
|
367 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
368 |
table = [ |
6290 | 369 |
[ 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
|
370 |
, Infix (char '/' >> return (BinOp "/")) AssocLeft |
6275 | 371 |
, Infix (try (string "div") >> return (BinOp "div")) AssocLeft |
372 |
, Infix (try (string "mod") >> return (BinOp "mod")) AssocLeft |
|
6450 | 373 |
, Infix (try (string "in") >> return (BinOp "in")) AssocNone |
6275 | 374 |
] |
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
|
375 |
, [ 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
|
376 |
, Infix (char '-' >> return (BinOp "-")) AssocLeft |
6275 | 377 |
] |
378 |
, [ 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
|
379 |
, 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
|
380 |
, 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
|
381 |
, 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
|
382 |
, 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
|
383 |
, Infix (char '=' >> return (BinOp "=")) AssocNone |
6275 | 384 |
] |
385 |
, [ Infix (try $ string "and" >> return (BinOp "and")) AssocLeft |
|
386 |
, Infix (try $ string "or" >> return (BinOp "or")) AssocLeft |
|
387 |
, Infix (try $ string "xor" >> return (BinOp "xor")) AssocLeft |
|
388 |
] |
|
6355 | 389 |
, [ Infix (try $ string "shl" >> return (BinOp "shl")) AssocNone |
390 |
, Infix (try $ string "shr" >> return (BinOp "shr")) AssocNone |
|
6307 | 391 |
] |
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
|
392 |
] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. 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 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
394 |
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
|
395 |
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
|
396 |
comments |
6444 | 397 |
p <- manyTill phrase (try $ string "end" >> notFollowedBy alphaNum) |
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
|
398 |
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
|
399 |
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
|
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 |
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
|
402 |
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
|
403 |
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
|
404 |
, 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
|
405 |
, whileCycle |
6275 | 406 |
, 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
|
407 |
, switchCase |
6275 | 408 |
, withBlock |
409 |
, forCycle |
|
410 |
, (try $ reference >>= \r -> string ":=" >> return r) >>= \r -> expression >>= return . Assignment r |
|
6895 | 411 |
, builtInFunction expression >>= \(n, e) -> return $ BuiltInFunctionCall e (SimpleReference (Identifier n BTUnknown)) |
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
|
412 |
, procCall |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
413 |
, char ';' >> comments >> return NOP |
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
|
414 |
] |
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. 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 |
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
|
416 |
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
|
417 |
return o |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
418 |
|
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 |
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
|
420 |
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
|
421 |
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
|
422 |
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
|
423 |
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
|
424 |
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
|
425 |
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
|
426 |
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
|
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 |
o2 <- optionMaybe $ do |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
429 |
try $ string "else" >> space |
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
|
430 |
comments |
6450 | 431 |
o <- option NOP 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
|
432 |
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
|
433 |
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
|
434 |
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
|
435 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. 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 |
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
|
437 |
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
|
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 |
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
|
440 |
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
|
441 |
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
|
442 |
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
|
443 |
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
|
444 |
return $ WhileCycle e o |
4353
671d66ba3af6
Dumb parser of pascal, and a program which lists unit dependencies
unC0Rr
parents:
diff
changeset
|
445 |
|
6275 | 446 |
withBlock = do |
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
447 |
try $ string "with" >> space |
6275 | 448 |
comments |
6387 | 449 |
rs <- (commaSep1 pas) reference |
6275 | 450 |
comments |
451 |
string "do" |
|
452 |
comments |
|
453 |
o <- phrase |
|
6387 | 454 |
return $ foldr WithBlock o rs |
6275 | 455 |
|
456 |
repeatCycle = do |
|
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
457 |
try $ string "repeat" >> space |
6275 | 458 |
comments |
459 |
o <- many phrase |
|
460 |
string "until" |
|
461 |
comments |
|
462 |
e <- expression |
|
463 |
comments |
|
464 |
return $ RepeatCycle e o |
|
465 |
||
466 |
forCycle = do |
|
6425
1ef4192aa80d
- Parse unions, sets, function type, packed arrays and some more imporvements to the parser. Now it parses uVariable, uConsts and even SDLh.pas
unc0rr
parents:
6417
diff
changeset
|
467 |
try $ string "for" >> space |
6275 | 468 |
comments |
469 |
i <- iD |
|
470 |
comments |
|
471 |
string ":=" |
|
472 |
comments |
|
473 |
e1 <- expression |
|
474 |
comments |
|
475 |
choice [string "to", string "downto"] |
|
476 |
comments |
|
477 |
e2 <- expression |
|
478 |
comments |
|
479 |
string "do" |
|
480 |
comments |
|
481 |
p <- phrase |
|
482 |
comments |
|
483 |
return $ ForCycle i e1 e2 p |
|
484 |
||
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
|
485 |
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
|
486 |
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
|
487 |
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
|
488 |
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
|
489 |
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
|
490 |
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
|
491 |
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
|
492 |
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
|
493 |
o2 <- optionMaybe $ do |
6450 | 494 |
try $ string "else" >> notFollowedBy alphaNum |
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
|
495 |
comments |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
496 |
o <- many 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
|
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 |
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
|
499 |
string "end" |
6399 | 500 |
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
|
501 |
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
|
502 |
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
|
503 |
aCase = do |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
504 |
e <- (commaSep pas) $ (liftM InitRange rangeDecl <|> initExpression) |
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
|
505 |
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
|
506 |
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
|
507 |
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
|
508 |
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
|
509 |
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
|
510 |
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
|
511 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. 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 |
procCall = do |
6450 | 513 |
r <- 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
|
514 |
p <- option [] $ (parens pas) parameters |
6450 | 515 |
return $ ProcCall 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
|
516 |
|
6275 | 517 |
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
|
518 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. 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 |
functionBody = do |
6399 | 520 |
tv <- typeVarDeclaration True |
521 |
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
|
522 |
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
|
523 |
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
|
524 |
comments |
6399 | 525 |
return (TypesAndVars tv, 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 |
|
0a99f73dd8dd
Improve pascal parser, now it is able to successfully parse uGame.pas (though it eats all comments). Many things are still missing. Well, it's just a matter of time to implement the rest. All basic work is already done anyway.
unc0rr
parents:
4353
diff
changeset
|
527 |
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
|
528 |
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
|
529 |
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
|
530 |
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
|
531 |
comments |
6275 | 532 |
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
|
533 |
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
|
534 |
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
|
535 |
return u |
6355 | 536 |
|
537 |
initExpression = buildExpressionParser table term <?> "initialization expression" |
|
538 |
where |
|
539 |
term = comments >> choice [ |
|
6388 | 540 |
liftM (uncurry BuiltInFunction) $ builtInFunction initExpression |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
541 |
, try $ brackets pas (commaSep pas $ initExpression) >>= return . InitSet |
6388 | 542 |
, try $ parens pas (commaSep pas $ initExpression) >>= return . InitArray |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
543 |
, parens pas (sepEndBy recField (char ';' >> comments)) >>= return . InitRecord |
6355 | 544 |
, try $ integer pas >>= \i -> notFollowedBy (char '.') >> (return . InitNumber . show) i |
545 |
, try $ float pas >>= return . InitFloat . show |
|
6388 | 546 |
, try $ integer pas >>= return . InitNumber . show |
6355 | 547 |
, stringLiteral pas >>= return . InitString |
6444 | 548 |
, char '#' >> many digit >>= \c -> comments >> return (InitChar c) |
549 |
, char '$' >> many hexDigit >>= \h -> comments >> return (InitHexNumber h) |
|
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
550 |
, char '@' >> initExpression >>= \c -> comments >> return (InitAddress c) |
6355 | 551 |
, try $ string "nil" >> return InitNull |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
552 |
, itypeCast |
6355 | 553 |
, iD >>= return . InitReference |
554 |
] |
|
555 |
||
556 |
recField = do |
|
557 |
i <- iD |
|
558 |
spaces |
|
559 |
char ':' |
|
560 |
spaces |
|
561 |
e <- initExpression |
|
562 |
spaces |
|
563 |
return (i ,e) |
|
564 |
||
565 |
table = [ |
|
566 |
[ Infix (char '*' >> return (InitBinOp "*")) AssocLeft |
|
567 |
, Infix (char '/' >> return (InitBinOp "/")) AssocLeft |
|
568 |
, Infix (try (string "div") >> return (InitBinOp "div")) AssocLeft |
|
569 |
, Infix (try (string "mod") >> return (InitBinOp "mod")) AssocLeft |
|
570 |
] |
|
571 |
, [ Infix (char '+' >> return (InitBinOp "+")) AssocLeft |
|
572 |
, Infix (char '-' >> return (InitBinOp "-")) AssocLeft |
|
573 |
, Prefix (char '-' >> return (InitPrefixOp "-")) |
|
574 |
] |
|
575 |
, [ Infix (try (string "<>") >> return (InitBinOp "<>")) AssocNone |
|
576 |
, Infix (try (string "<=") >> return (InitBinOp "<=")) AssocNone |
|
577 |
, Infix (try (string ">=") >> return (InitBinOp ">=")) AssocNone |
|
578 |
, Infix (char '<' >> return (InitBinOp "<")) AssocNone |
|
579 |
, Infix (char '>' >> return (InitBinOp ">")) AssocNone |
|
580 |
, Infix (char '=' >> return (InitBinOp "=")) AssocNone |
|
581 |
] |
|
582 |
, [ Infix (try $ string "and" >> return (InitBinOp "and")) AssocLeft |
|
583 |
, Infix (try $ string "or" >> return (InitBinOp "or")) AssocLeft |
|
584 |
, Infix (try $ string "xor" >> return (InitBinOp "xor")) AssocLeft |
|
585 |
] |
|
6858 | 586 |
, [ Infix (try $ string "shl" >> return (InitBinOp "shl")) AssocNone |
587 |
, Infix (try $ string "shr" >> return (InitBinOp "shr")) AssocNone |
|
6355 | 588 |
] |
589 |
, [Prefix (try (string "not") >> return (InitPrefixOp "not"))] |
|
590 |
] |
|
6388 | 591 |
|
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
592 |
itypeCast = do |
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
593 |
t <- choice $ map (\s -> try $ caseInsensitiveString s >>= \i -> notFollowedBy alphaNum >> return i) knownTypes |
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
594 |
i <- parens pas initExpression |
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
595 |
comments |
6618 | 596 |
return $ InitTypeCast (Identifier t BTUnknown) i |
6453
11c578d30bd3
Countless imporvements to the parser and countless help to the parser in sources.
unc0rr
parents:
6452
diff
changeset
|
597 |
|
6388 | 598 |
builtInFunction e = do |
599 |
name <- choice $ map (\s -> try $ caseInsensitiveString s >>= \i -> notFollowedBy alphaNum >> return i) builtin |
|
600 |
spaces |
|
6897 | 601 |
exprs <- option [] $ parens pas $ option [] $ commaSep1 pas $ e |
6388 | 602 |
spaces |
603 |
return (name, exprs) |
|
6512 | 604 |
|
605 |
systemUnit = do |
|
606 |
string "system;" |
|
607 |
comments |
|
608 |
string "type" |
|
609 |
comments |
|
610 |
t <- typesDecl |
|
611 |
string "var" |
|
612 |
v <- varsDecl True |
|
613 |
return $ System (t ++ v) |
|
6618 | 614 |