tools/pas2c/PascalPreprocessor.hs
author koda
Tue, 21 Jan 2014 22:38:13 +0100
changeset 10015 4feced261c68
parent 9982 24ea101fdc7f
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: 9982
diff changeset
     1
{-# LANGUAGE ScopedTypeVariables #-}
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
     2
module PascalPreprocessor where
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
     3
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
     4
import Text.Parsec
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
     5
import Control.Monad.IO.Class
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
     6
import Control.Monad
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
     7
import System.IO
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
     8
import qualified Data.Map as Map
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
     9
import Control.Exception(catch, IOException)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    10
import Data.Char
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    11
import Prelude hiding (catch)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    12
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    13
-- comments are removed
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    14
comment = choice [
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    15
        char '{' >> notFollowedBy (char '$') >> manyTill anyChar (try $ char '}') >> return ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    16
        , (try $ string "(*") >> manyTill anyChar (try $ string "*)") >> return ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    17
        , (try $ string "//") >> manyTill anyChar (try newline) >> return "\n"
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    18
        ]
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    19
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    20
preprocess :: String -> String -> String -> [String] -> IO String
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    21
preprocess inputPath alternateInputPath fn symbols = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    22
    r <- runParserT (preprocessFile (inputPath ++ fn)) (Map.fromList $ map (\s -> (s, "")) symbols, [True]) "" ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    23
    case r of
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    24
         (Left a) -> do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    25
             hPutStrLn stderr (show a)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    26
             return ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    27
         (Right a) -> return a
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    28
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    29
    where
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    30
    preprocessFile fn = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    31
        f <- liftIO (readFile fn)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    32
        setInput f
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    33
        preprocessor
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    34
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    35
    preprocessor, codeBlock, switch :: ParsecT String (Map.Map String String, [Bool]) IO String
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    36
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    37
    preprocessor = chainr codeBlock (return (++)) ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    38
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    39
    codeBlock = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    40
        s <- choice [
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    41
            switch
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    42
            , comment
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    43
            , char '\'' >> many (noneOf "'\n") >>= \s -> char '\'' >> return ('\'' : s ++ "'")
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    44
            , identifier >>= replace
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    45
            , noneOf "{" >>= \a -> return [a]
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    46
            ]
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    47
        (_, ok) <- getState
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    48
        return $ if and ok then s else ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    49
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    50
    --otherChar c = c `notElem` "{/('_" && not (isAlphaNum c)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    51
    identifier = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    52
        c <- letter <|> oneOf "_"
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    53
        s <- many (alphaNum <|> oneOf "_")
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    54
        return $ c:s
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    55
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    56
    switch = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    57
        try $ string "{$"
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    58
        s <- choice [
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    59
            include
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    60
            , ifdef
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    61
            , if'
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    62
            , elseSwitch
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    63
            , endIf
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    64
            , define
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    65
            , unknown
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    66
            ]
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    67
        return s
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    68
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    69
    include = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    70
        try $ string "INCLUDE"
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    71
        spaces
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    72
        (char '"')
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    73
        fn <- many1 $ noneOf "\"\n"
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    74
        char '"'
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    75
        spaces
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    76
        char '}'
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    77
        f <- liftIO (readFile (inputPath ++ fn) `catch` (\(exc :: IOException) -> readFile (alternateInputPath ++ fn) `catch` (\(_ :: IOException) -> error ("File not found: " ++ fn))))
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    78
        c <- getInput
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    79
        setInput $ f ++ c
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    80
        return ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    81
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    82
    ifdef = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    83
        s <- try (string "IFDEF") <|> try (string "IFNDEF")
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    84
        let f = if s == "IFNDEF" then not else id
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    85
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    86
        spaces
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    87
        d <- identifier
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    88
        spaces
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    89
        char '}'
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    90
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    91
        updateState $ \(m, b) ->
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    92
            (m, (f $ d `Map.member` m) : b)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    93
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    94
        return ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    95
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    96
    if' = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    97
        s <- try (string "IF" >> notFollowedBy alphaNum)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    98
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
    99
        manyTill anyChar (char '}')
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   100
        --char '}'
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   101
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   102
        updateState $ \(m, b) ->
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   103
            (m, False : b)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   104
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   105
        return ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   106
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   107
    elseSwitch = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   108
        try $ string "ELSE}"
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   109
        updateState $ \(m, b:bs) -> (m, (not b):bs)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   110
        return ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   111
    endIf = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   112
        try $ string "ENDIF}"
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   113
        updateState $ \(m, b:bs) -> (m, bs)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   114
        return ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   115
    define = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   116
        try $ string "DEFINE"
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   117
        spaces
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   118
        i <- identifier
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   119
        d <- ((string ":=" >> return ()) <|> spaces) >> many (noneOf "}")
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   120
        char '}'
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   121
        updateState $ \(m, b) -> (if (and b) && (head i /= '_') then Map.insert i d m else m, b)
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   122
        return ""
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   123
    replace s = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   124
        (m, _) <- getState
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   125
        return $ Map.findWithDefault s s m
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   126
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   127
    unknown = do
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   128
        fn <- many1 $ noneOf "}\n"
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   129
        char '}'
4feced261c68 partial merge of the webgl branch
koda
parents: 9982
diff changeset
   130
        return $ "{$" ++ fn ++ "}"