23 deriving Show |
23 deriving Show |
24 data TypesAndVars = TypesAndVars [TypeVarDeclaration] |
24 data TypesAndVars = TypesAndVars [TypeVarDeclaration] |
25 deriving Show |
25 deriving Show |
26 data TypeVarDeclaration = TypeDeclaration TypeDecl |
26 data TypeVarDeclaration = TypeDeclaration TypeDecl |
27 | ConstDeclaration String |
27 | ConstDeclaration String |
28 | VarDeclaration String |
28 | VarDeclaration Bool String |
29 | FunctionDeclaration Identifier Identifier (Maybe Phrase) |
29 | FunctionDeclaration Identifier Identifier (Maybe Phrase) |
30 deriving Show |
30 deriving Show |
31 data TypeDecl = SimpleType Identifier |
31 data TypeDecl = SimpleType Identifier |
32 | RangeType Range |
32 | RangeType Range |
33 | ArrayDecl Range TypeDecl |
33 | ArrayDecl Range TypeDecl |
41 data Uses = Uses [Identifier] |
41 data Uses = Uses [Identifier] |
42 deriving Show |
42 deriving Show |
43 data Phrase = ProcCall Identifier [Expression] |
43 data Phrase = ProcCall Identifier [Expression] |
44 | IfThenElse Expression Phrase (Maybe Phrase) |
44 | IfThenElse Expression Phrase (Maybe Phrase) |
45 | WhileCycle Expression Phrase |
45 | WhileCycle Expression Phrase |
46 | RepeatCycle Expression Phrase |
46 | RepeatCycle Expression [Phrase] |
47 | ForCycle |
47 | ForCycle Identifier Expression Expression Phrase |
|
48 | WithBlock Expression Phrase |
48 | Phrases [Phrase] |
49 | Phrases [Phrase] |
49 | SwitchCase Expression [(Expression, Phrase)] (Maybe Phrase) |
50 | SwitchCase Expression [(Expression, Phrase)] (Maybe Phrase) |
50 | Assignment Identifier Expression |
51 | Assignment Reference Expression |
51 deriving Show |
52 deriving Show |
52 data Expression = Expression String |
53 data Expression = Expression String |
53 | FunCall Identifier [Expression] |
54 | FunCall Identifier [Expression] |
54 | PrefixOp String Expression |
55 | PrefixOp String Expression |
|
56 | PostfixOp String Expression |
55 | BinOp String Expression Expression |
57 | BinOp String Expression Expression |
56 deriving Show |
58 | StringLiteral String |
57 |
59 | NumberLiteral String |
58 |
60 | Reference Reference |
|
61 deriving Show |
|
62 data Reference = ArrayElement Identifier Expression |
|
63 | SimpleReference Identifier |
|
64 | RecordField Reference Reference |
|
65 | Dereference Reference |
|
66 deriving Show |
|
67 |
59 pascalLanguageDef |
68 pascalLanguageDef |
60 = emptyDef |
69 = emptyDef |
61 { commentStart = "(*" |
70 { commentStart = "(*" |
62 , commentEnd = "*)" |
71 , commentEnd = "*)" |
63 , commentLine = "//" |
72 , commentLine = "//" |
67 , reservedNames = [ |
76 , reservedNames = [ |
68 "begin", "end", "program", "unit", "interface" |
77 "begin", "end", "program", "unit", "interface" |
69 , "implementation", "and", "or", "xor", "shl" |
78 , "implementation", "and", "or", "xor", "shl" |
70 , "shr", "while", "do", "repeat", "until", "case", "of" |
79 , "shr", "while", "do", "repeat", "until", "case", "of" |
71 , "type", "var", "const", "out", "array" |
80 , "type", "var", "const", "out", "array" |
72 , "procedure", "function" |
81 , "procedure", "function", "with", "for", "to" |
|
82 , "downto", "div", "mod" |
73 ] |
83 ] |
74 , reservedOpNames= [] |
84 , reservedOpNames= [] |
75 , caseSensitive = False |
85 , caseSensitive = False |
76 } |
86 } |
77 |
87 |
78 pas = makeTokenParser pascalLanguageDef |
88 pas = patch $ makeTokenParser pascalLanguageDef |
|
89 where |
|
90 patch tp = tp {stringLiteral = between (char '\'') (char '\'') (many $ noneOf "'")} |
79 |
91 |
80 comments = do |
92 comments = do |
81 spaces |
93 spaces |
82 skipMany $ do |
94 skipMany $ do |
83 comment |
95 comment |
93 char '{' >> manyTill anyChar (try $ char '}') |
105 char '{' >> manyTill anyChar (try $ char '}') |
94 , (try $ string "(*") >> manyTill anyChar (try $ string "*)") |
106 , (try $ string "(*") >> manyTill anyChar (try $ string "*)") |
95 , (try $ string "//") >> manyTill anyChar (try newline) |
107 , (try $ string "//") >> manyTill anyChar (try newline) |
96 ] |
108 ] |
97 |
109 |
|
110 iD = do |
|
111 i <- liftM Identifier (identifier pas) |
|
112 comments |
|
113 return i |
|
114 |
98 unit = do |
115 unit = do |
99 name <- liftM Identifier unitName |
116 string "unit" >> comments |
|
117 name <- iD |
|
118 semi pas |
100 comments |
119 comments |
101 int <- interface |
120 int <- interface |
102 impl <- implementation |
121 impl <- implementation |
103 comments |
122 comments |
104 return $ Unit name int impl Nothing Nothing |
123 return $ Unit name int impl Nothing Nothing |
105 where |
124 |
106 unitName = between (string "unit" >> comments) (semi pas) (identifier pas) |
125 |
107 |
126 reference = buildExpressionParser table term <?> "reference" |
|
127 where |
|
128 term = comments >> choice [ |
|
129 parens pas reference |
|
130 , try $ iD >>= \i -> (brackets pas) expression >>= return . ArrayElement i |
|
131 , iD >>= return . SimpleReference |
|
132 ] <?> "simple reference" |
|
133 |
|
134 table = [ |
|
135 [Postfix (char '^' >> return Dereference)] |
|
136 , [Infix (char '.' >> return RecordField) AssocLeft] |
|
137 ] |
|
138 |
|
139 |
108 varsDecl endsWithSemi = do |
140 varsDecl endsWithSemi = do |
109 vs <- many (try (aVarDecl >> semi pas) >> comments) |
141 vs <- many (try (aVarDecl >> semi pas) >> comments) |
110 when (not endsWithSemi) $ aVarDecl >> return () |
142 when (not endsWithSemi) $ aVarDecl >> return () |
111 comments |
143 comments |
112 return $ VarDeclaration $ show vs |
144 return $ VarDeclaration False $ show vs |
113 where |
145 where |
114 aVarDecl = do |
146 aVarDecl = do |
115 ids <- (commaSep1 pas) $ ((identifier pas) <?> "variable declaration") >>= \i -> comments >> return (Identifier i) |
147 when (not endsWithSemi) $ |
|
148 optional $ choice [ |
|
149 try $ string "var" |
|
150 , try $ string "const" |
|
151 , try $ string "out" |
|
152 ] |
|
153 comments |
|
154 ids <- (commaSep1 pas) $ (iD <?> "variable declaration") |
116 char ':' |
155 char ':' |
117 comments |
156 comments |
118 t <- typeDecl |
157 t <- typeDecl |
119 comments |
158 comments |
120 return (ids, t) |
159 return (ids, t) |
|
160 |
|
161 |
|
162 constsDecl = do |
|
163 vs <- many (try (aConstDecl >> semi pas) >> comments) |
|
164 comments |
|
165 return $ VarDeclaration True $ show vs |
|
166 where |
|
167 aConstDecl = do |
|
168 comments |
|
169 ids <- iD <?> "const declaration" |
|
170 optional $ do |
|
171 char ':' |
|
172 comments |
|
173 t <- typeDecl |
|
174 return () |
|
175 char '=' |
|
176 comments |
|
177 e <- expression |
|
178 comments |
|
179 return (ids, e) |
121 |
180 |
122 typeDecl = choice [ |
181 typeDecl = choice [ |
123 arrayDecl |
182 arrayDecl |
124 , rangeDecl >>= return . RangeType |
183 , rangeDecl >>= return . RangeType |
125 , identifier pas >>= return . SimpleType . Identifier |
184 , identifier pas >>= return . SimpleType . Identifier |
135 string "of" |
194 string "of" |
136 comments |
195 comments |
137 t <- typeDecl |
196 t <- typeDecl |
138 return $ ArrayDecl r t |
197 return $ ArrayDecl r t |
139 |
198 |
|
199 |
140 rangeDecl = choice [ |
200 rangeDecl = choice [ |
141 identifier pas >>= return . Range . Identifier |
201 iD >>= return . Range |
142 ] <?> "range declaration" |
202 ] <?> "range declaration" |
143 |
203 |
|
204 |
144 typeVarDeclaration isImpl = choice [ |
205 typeVarDeclaration isImpl = choice [ |
145 varSection, |
206 varSection, |
|
207 constSection, |
146 funcDecl, |
208 funcDecl, |
147 procDecl |
209 procDecl |
148 ] |
210 ] |
149 where |
211 where |
150 varSection = do |
212 varSection = do |
151 try $ string "var" |
213 try $ string "var" |
152 comments |
214 comments |
153 v <- varsDecl True |
215 v <- varsDecl True |
154 comments |
216 comments |
155 return v |
217 return v |
156 |
218 |
|
219 constSection = do |
|
220 try $ string "const" |
|
221 comments |
|
222 c <- constsDecl |
|
223 comments |
|
224 return c |
|
225 |
157 procDecl = do |
226 procDecl = do |
158 string "procedure" |
227 string "procedure" |
159 comments |
228 comments |
160 i <- liftM Identifier $ identifier pas |
229 i <- iD |
161 optional $ do |
230 optional $ do |
162 char '(' |
231 char '(' |
163 varsDecl False |
232 varsDecl False |
164 char ')' |
233 char ')' |
|
234 comments |
|
235 char ';' |
|
236 b <- if isImpl then |
|
237 do |
|
238 comments |
|
239 optional $ typeVarDeclaration isImpl |
|
240 comments |
|
241 liftM Just functionBody |
|
242 else |
|
243 return Nothing |
|
244 comments |
|
245 return $ FunctionDeclaration i (Identifier "") b |
|
246 |
|
247 funcDecl = do |
|
248 string "function" |
|
249 comments |
|
250 i <- iD |
|
251 optional $ do |
|
252 char '(' |
|
253 varsDecl False |
|
254 char ')' |
|
255 comments |
|
256 char ':' |
|
257 ret <- iD |
165 comments |
258 comments |
166 char ';' |
259 char ';' |
167 b <- if isImpl then |
260 b <- if isImpl then |
168 do |
261 do |
169 comments |
262 comments |
170 typeVarDeclaration isImpl |
263 typeVarDeclaration isImpl |
171 comments |
264 comments |
172 liftM Just functionBody |
265 liftM Just functionBody |
173 else |
266 else |
174 return Nothing |
267 return Nothing |
175 comments |
268 return $ FunctionDeclaration i ret Nothing |
176 return $ FunctionDeclaration i (Identifier "") b |
|
177 |
|
178 funcDecl = do |
|
179 string "function" |
|
180 comments |
|
181 optional $ do |
|
182 char '(' |
|
183 varsDecl False |
|
184 char ')' |
|
185 comments |
|
186 char ':' |
|
187 ret <- identifier pas |
|
188 comments |
|
189 char ';' |
|
190 b <- if isImpl then |
|
191 do |
|
192 comments |
|
193 typeVarDeclaration isImpl |
|
194 comments |
|
195 liftM Just functionBody |
|
196 else |
|
197 return Nothing |
|
198 return $ FunctionDeclaration (Identifier "function") (Identifier ret) Nothing |
|
199 |
269 |
200 program = do |
270 program = do |
201 name <- liftM Identifier programName |
271 string "program" |
|
272 comments |
|
273 name <- iD |
|
274 (char ';') |
202 comments |
275 comments |
203 impl <- implementation |
276 impl <- implementation |
204 comments |
277 comments |
205 return $ Program name impl |
278 return $ Program name impl |
206 where |
|
207 programName = between (string "program") (char ';') (identifier pas) |
|
208 |
279 |
209 interface = do |
280 interface = do |
210 string "interface" |
281 string "interface" |
211 comments |
282 comments |
212 u <- uses |
283 u <- uses |
227 |
298 |
228 expression = buildExpressionParser table term <?> "expression" |
299 expression = buildExpressionParser table term <?> "expression" |
229 where |
300 where |
230 term = comments >> choice [ |
301 term = comments >> choice [ |
231 parens pas $ expression |
302 parens pas $ expression |
232 , natural pas >>= return . Expression . show |
303 , integer pas >>= return . NumberLiteral . show |
233 , funCall |
304 , stringLiteral pas >>= return . StringLiteral |
|
305 , try $ funCall |
|
306 , reference >>= return . Reference |
234 ] <?> "simple expression" |
307 ] <?> "simple expression" |
235 |
308 |
236 table = [ |
309 table = [ |
237 [Infix (string "^." >> return (BinOp "^.")) AssocLeft] |
310 [Prefix (string "not" >> return (PrefixOp "not"))] |
238 , [Prefix (string "not" >> return (PrefixOp "not"))] |
|
239 , [ Infix (char '*' >> return (BinOp "*")) AssocLeft |
311 , [ Infix (char '*' >> return (BinOp "*")) AssocLeft |
240 , Infix (char '/' >> return (BinOp "/")) AssocLeft |
312 , Infix (char '/' >> return (BinOp "/")) AssocLeft |
241 ] |
313 , Infix (try (string "div") >> return (BinOp "div")) AssocLeft |
|
314 , Infix (try (string "mod") >> return (BinOp "mod")) AssocLeft |
|
315 ] |
242 , [ Infix (char '+' >> return (BinOp "+")) AssocLeft |
316 , [ Infix (char '+' >> return (BinOp "+")) AssocLeft |
243 , Infix (char '-' >> return (BinOp "-")) AssocLeft |
317 , Infix (char '-' >> return (BinOp "-")) AssocLeft |
244 ] |
318 , Prefix (char '-' >> return (PrefixOp "-")) |
245 , [ Infix (try (string "<>" )>> return (BinOp "<>")) AssocNone |
319 ] |
|
320 , [ Infix (try (string "<>") >> return (BinOp "<>")) AssocNone |
246 , Infix (try (string "<=") >> return (BinOp "<=")) AssocNone |
321 , Infix (try (string "<=") >> return (BinOp "<=")) AssocNone |
247 , Infix (try (string ">=") >> return (BinOp ">=")) AssocNone |
322 , Infix (try (string ">=") >> return (BinOp ">=")) AssocNone |
248 , Infix (char '<' >> return (BinOp "<")) AssocNone |
323 , Infix (char '<' >> return (BinOp "<")) AssocNone |
249 , Infix (char '>' >> return (BinOp ">")) AssocNone |
324 , Infix (char '>' >> return (BinOp ">")) AssocNone |
250 , Infix (char '=' >> return (BinOp "=")) AssocNone |
325 , Infix (char '=' >> return (BinOp "=")) AssocNone |
251 ] |
326 ] |
252 , [ Infix (try $ string "and" >> return (BinOp "and")) AssocNone |
327 , [ Infix (try $ string "and" >> return (BinOp "and")) AssocLeft |
253 , Infix (try $ string "or" >> return (BinOp "or")) AssocNone |
328 , Infix (try $ string "or" >> return (BinOp "or")) AssocLeft |
254 , Infix (try $ string "xor" >> return (BinOp "xor")) AssocNone |
329 , Infix (try $ string "xor" >> return (BinOp "xor")) AssocLeft |
255 ] |
330 ] |
256 ] |
331 ] |
257 |
332 |
258 phrasesBlock = do |
333 phrasesBlock = do |
259 try $ string "begin" |
334 try $ string "begin" |
260 comments |
335 comments |