|
1 {-# LANGUAGE FlexibleContexts #-} |
|
2 module PascalBasics where |
|
3 |
|
4 import Text.Parsec.Combinator |
|
5 import Text.Parsec.Char |
|
6 import Text.Parsec.Prim |
|
7 import Text.Parsec.Token |
|
8 import Text.Parsec.Language |
|
9 import Data.Char |
|
10 |
|
11 builtin = ["succ", "pred", "low", "high", "ord", "inc", "dec", "exit", "break", "continue", "length"] |
|
12 |
|
13 pascalLanguageDef |
|
14 = emptyDef |
|
15 { commentStart = "(*" |
|
16 , commentEnd = "*)" |
|
17 , commentLine = "//" |
|
18 , nestedComments = False |
|
19 , identStart = letter <|> oneOf "_" |
|
20 , identLetter = alphaNum <|> oneOf "_" |
|
21 , reservedNames = [ |
|
22 "begin", "end", "program", "unit", "interface" |
|
23 , "implementation", "and", "or", "xor", "shl" |
|
24 , "shr", "while", "do", "repeat", "until", "case", "of" |
|
25 , "type", "var", "const", "out", "array", "packed" |
|
26 , "procedure", "function", "with", "for", "to" |
|
27 , "downto", "div", "mod", "record", "set", "nil" |
|
28 , "cdecl", "external", "if", "then", "else" |
|
29 ] -- ++ builtin |
|
30 , reservedOpNames= [] |
|
31 , caseSensitive = False |
|
32 } |
|
33 |
|
34 preprocessorSwitch :: Stream s m Char => ParsecT s u m String |
|
35 preprocessorSwitch = do |
|
36 try $ string "{$" |
|
37 s <- manyTill (noneOf "\n") $ char '}' |
|
38 return s |
|
39 |
|
40 caseInsensitiveString s = do |
|
41 mapM_ (\a -> satisfy (\b -> toUpper a == toUpper b)) s <?> s |
|
42 return s |
|
43 |
|
44 pas = patch $ makeTokenParser pascalLanguageDef |
|
45 where |
|
46 patch tp = tp {stringLiteral = stringL} |
|
47 |
|
48 comment = choice [ |
|
49 char '{' >> notFollowedBy (char '$') >> manyTill anyChar (try $ char '}') |
|
50 , (try $ string "(*") >> manyTill anyChar (try $ string "*)") |
|
51 , (try $ string "//") >> manyTill anyChar (try newline) |
|
52 ] |
|
53 |
|
54 comments = do |
|
55 spaces |
|
56 skipMany $ do |
|
57 preprocessorSwitch <|> comment |
|
58 spaces |
|
59 |
|
60 stringL = do |
|
61 (char '\'') |
|
62 s <- (many $ noneOf "'") |
|
63 (char '\'') |
|
64 ss <- many $ do |
|
65 (char '\'') |
|
66 s' <- (many $ noneOf "'") |
|
67 (char '\'') |
|
68 return $ '\'' : s' |
|
69 comments |
|
70 return $ concat (s:ss) |