tools/pas2c/PascalBasics.hs
author koda
Tue, 21 Jan 2014 22:38:13 +0100
changeset 10015 4feced261c68
parent 8020 00b1facf2805
child 10113 b26c2772e754
permissions -rw-r--r--
partial merge of the webgl branch This commit contains the new pas2c conversion tool, the pascal to c build structure and the opengl2 rendering backend. Patch reviewed by unC0Rr.
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
10015
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
     1
{-# LANGUAGE FlexibleContexts #-}
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
     2
module PascalBasics where
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
     3
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
     4
import Text.Parsec.Combinator
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
     5
import Text.Parsec.Char
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
     6
import Text.Parsec.Prim
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
     7
import Text.Parsec.Token
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
     8
import Text.Parsec.Language
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
     9
import Data.Char
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    10
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    11
builtin = ["succ", "pred", "low", "high", "ord", "inc", "dec", "exit", "break", "continue", "length"]
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    12
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    13
pascalLanguageDef
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    14
    = emptyDef
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    15
    { commentStart   = "(*"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    16
    , commentEnd     = "*)"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    17
    , commentLine    = "//"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    18
    , nestedComments = False
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    19
    , identStart     = letter <|> oneOf "_"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    20
    , identLetter    = alphaNum <|> oneOf "_"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    21
    , opLetter       = letter
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    22
    , reservedNames  = [
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    23
            "begin", "end", "program", "unit", "interface"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    24
            , "implementation", "and", "or", "xor", "shl"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    25
            , "shr", "while", "do", "repeat", "until", "case", "of"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    26
            , "type", "var", "const", "out", "array", "packed"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    27
            , "procedure", "function", "with", "for", "to"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    28
            , "downto", "div", "mod", "record", "set", "nil"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    29
            , "cdecl", "external", "if", "then", "else"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    30
            ] -- ++ builtin
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    31
    , caseSensitive  = False
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    32
    }
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    33
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    34
preprocessorSwitch :: Stream s m Char => ParsecT s u m String
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    35
preprocessorSwitch = do
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    36
    try $ string "{$"
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    37
    s <- manyTill (noneOf "\n") $ char '}'
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    38
    return s
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    39
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    40
caseInsensitiveString s = do
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    41
    mapM_ (\a -> satisfy (\b -> toUpper a == toUpper b)) s <?> s
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    42
    return s
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    43
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    44
pas = patch $ makeTokenParser pascalLanguageDef
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    45
    where
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    46
    patch tp = tp {stringLiteral = stringL}
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    47
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    48
comment = choice [
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    49
        char '{' >> notFollowedBy (char '$') >> manyTill anyChar (try $ char '}')
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    50
        , (try $ string "(*") >> manyTill anyChar (try $ string "*)")
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    51
        , (try $ string "//") >> manyTill anyChar (try newline)
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    52
        ]
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    53
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    54
comments = do
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    55
    spaces
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    56
    skipMany $ do
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    57
        preprocessorSwitch <|> comment
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    58
        spaces
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    59
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    60
stringL = do
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    61
    (char '\'')
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    62
    s <- (many $ noneOf "'")
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    63
    (char '\'')
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    64
    ss <- many $ do
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    65
        (char '\'')
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    66
        s' <- (many $ noneOf "'")
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    67
        (char '\'')
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    68
        return $ '\'' : s'
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    69
    comments
4feced261c68 partial merge of the webgl branch
koda
parents: 8020
diff changeset
    70
    return $ concat (s:ss)