tools/pas2c.hs
changeset 6467 090269e528df
parent 6455 d2b13364eddd
child 6474 42e9773eedfd
equal deleted inserted replaced
6466:afd8c9a3672d 6467:090269e528df
     1 module Pas2C where
     1 module Pas2C where
     2 
     2 
     3 import PascalParser
       
     4 import Text.PrettyPrint.HughesPJ
     3 import Text.PrettyPrint.HughesPJ
     5 import Data.Maybe
     4 import Data.Maybe
     6 import Data.Char
     5 import Data.Char
     7 import Text.Parsec.Prim
     6 import Text.Parsec.Prim
     8 import Control.Monad.State
     7 import Control.Monad.State
    12 import PascalPreprocessor
    11 import PascalPreprocessor
    13 import Control.Exception
    12 import Control.Exception
    14 import System.IO.Error
    13 import System.IO.Error
    15 import qualified Data.Map as Map
    14 import qualified Data.Map as Map
    16 
    15 
       
    16 import PascalParser
       
    17 import PascalUnitSyntaxTree
    17 
    18 
    18 pas2C :: String -> IO ()
    19 pas2C :: String -> IO ()
    19 pas2C fn = do
    20 pas2C fn = do
    20     setCurrentDirectory "../hedgewars/"
    21     setCurrentDirectory "../hedgewars/"
    21     s <- flip execStateT initState $ f fn
    22     s <- flip execStateT initState $ f fn
    22     writeFile "dump" $ show s
    23     mapM_ toCFiles (Map.toList s)
    23     where
    24     where
    24     printLn = liftIO . hPutStrLn stderr
    25     printLn = liftIO . hPutStrLn stderr
    25     print = liftIO . hPutStr stderr
    26     print = liftIO . hPutStr stderr
    26     initState = Map.empty
    27     initState = Map.empty
    27     f :: String -> StateT (Map.Map String PascalUnit) IO ()
    28     f :: String -> StateT (Map.Map String PascalUnit) IO ()
    47                          (Right a) -> do
    48                          (Right a) -> do
    48                             printLn "ok"
    49                             printLn "ok"
    49                             modify (Map.insert fileName a)
    50                             modify (Map.insert fileName a)
    50                             mapM_ f (usesFiles a)
    51                             mapM_ f (usesFiles a)
    51 
    52 
    52 
    53 toCFiles :: (String, PascalUnit) -> IO ()
    53 usesFiles :: PascalUnit -> [String]         
    54 toCFiles (_, System) = return ()
       
    55 toCFiles (fn, p@(Program {})) = writeFile (fn ++ ".c") $ (render . pascal2C) p
       
    56 toCFiles (fn, (Unit _ interface implementation _ _)) = do
       
    57     writeFile (fn ++ ".h") $ (render . interface2C) interface
       
    58     writeFile (fn ++ ".c") $ (render . implementation2C) implementation
       
    59                             
       
    60 usesFiles :: PascalUnit -> [String]
    54 usesFiles (Program _ (Implementation uses _) _) = uses2List uses
    61 usesFiles (Program _ (Implementation uses _) _) = uses2List uses
    55 usesFiles (Unit _ (Interface uses1 _) (Implementation uses2 _) _ _) = uses2List uses1 ++ uses2List uses2
    62 usesFiles (Unit _ (Interface uses1 _) (Implementation uses2 _) _ _) = uses2List uses1 ++ uses2List uses2
    56 
    63 
    57 
    64 
    58 
    65 
    59 pascal2C :: PascalUnit -> Doc
    66 pascal2C :: PascalUnit -> Doc
    60 pascal2C (Unit unitName interface implementation init fin) = 
    67 pascal2C (Unit _ interface implementation init fin) = 
    61     interface2C interface
    68     interface2C interface
    62     $+$ 
    69     $+$ 
    63     implementation2C implementation
    70     implementation2C implementation
    64 pascal2C (Program _ implementation mainFunction) =
    71 pascal2C (Program _ implementation mainFunction) =
    65     implementation2C implementation
    72     implementation2C implementation
    66     $+$
    73     $+$
    67     tvar2C (FunctionDeclaration (Identifier "main") (SimpleType $ Identifier "int") [] (Just (TypesAndVars [], mainFunction)))
    74     tvar2C (FunctionDeclaration (Identifier "main") (SimpleType $ Identifier "int") [] (Just (TypesAndVars [], mainFunction)))
       
    75     
       
    76     
    68 interface2C :: Interface -> Doc
    77 interface2C :: Interface -> Doc
    69 interface2C (Interface uses tvars) = uses2C uses $+$ typesAndVars2C tvars
    78 interface2C (Interface uses tvars) = uses2C uses $+$ typesAndVars2C tvars
    70 
    79 
    71 implementation2C :: Implementation -> Doc
    80 implementation2C :: Implementation -> Doc
    72 implementation2C (Implementation uses tvars) = uses2C uses $+$ typesAndVars2C tvars
    81 implementation2C (Implementation uses tvars) = uses2C uses $+$ typesAndVars2C tvars
    81 uses2List :: Uses -> [String]
    90 uses2List :: Uses -> [String]
    82 uses2List (Uses ids) = map (\(Identifier i) -> i) ids
    91 uses2List (Uses ids) = map (\(Identifier i) -> i) ids
    83 
    92 
    84 tvar2C :: TypeVarDeclaration -> Doc
    93 tvar2C :: TypeVarDeclaration -> Doc
    85 tvar2C (FunctionDeclaration (Identifier name) returnType params Nothing) = 
    94 tvar2C (FunctionDeclaration (Identifier name) returnType params Nothing) = 
    86     type2C returnType <+> text (name ++ "();")
    95     type2C returnType <+> text name <> parens (hcat $ map tvar2C params) <> text ";"
    87 tvar2C (FunctionDeclaration (Identifier name) returnType params (Just (tvars, phrase))) = 
    96 tvar2C (FunctionDeclaration (Identifier name) returnType params (Just (tvars, phrase))) = 
    88     type2C returnType <+> text (name ++ "()") 
    97     type2C returnType <+> text name <> parens (hcat $ map tvar2C params)
    89     $+$
    98     $+$
    90     text "{" 
    99     text "{" 
    91     $+$ nest 4 (
   100     $+$ nest 4 (
    92         typesAndVars2C tvars
   101         typesAndVars2C tvars
    93         $+$
   102         $+$
   110     <>
   119     <>
   111     text ";"
   120     text ";"
   112     where
   121     where
   113     initExpr Nothing = empty
   122     initExpr Nothing = empty
   114     initExpr (Just e) = text "=" <+> initExpr2C e
   123     initExpr (Just e) = text "=" <+> initExpr2C e
       
   124 tvar2C (OperatorDeclaration op _ ret params body) = 
       
   125     tvar2C (FunctionDeclaration (Identifier "<op>") ret params body)
   115 
   126 
   116 initExpr2C :: InitExpression -> Doc
   127 initExpr2C :: InitExpression -> Doc
   117 initExpr2C (InitBinOp op expr1 expr2) = parens $ (initExpr2C expr1) <+> op2C op <+> (initExpr2C expr2)
   128 initExpr2C (InitBinOp op expr1 expr2) = parens $ (initExpr2C expr1) <+> op2C op <+> (initExpr2C expr2)
   118 initExpr2C (InitNumber s) = text s
   129 initExpr2C (InitNumber s) = text s
   119 initExpr2C (InitFloat s) = text s
   130 initExpr2C (InitFloat s) = text s
   131 type2C (PointerTo t) = type2C t <> text "*"
   142 type2C (PointerTo t) = type2C t <> text "*"
   132 type2C (RecordType tvs union) = text "{" $+$ (nest 4 . vcat . map tvar2C $ tvs) $+$ text "}"
   143 type2C (RecordType tvs union) = text "{" $+$ (nest 4 . vcat . map tvar2C $ tvs) $+$ text "}"
   133 type2C (RangeType r) = text "<<range type>>"
   144 type2C (RangeType r) = text "<<range type>>"
   134 type2C (Sequence ids) = text "<<sequence type>>"
   145 type2C (Sequence ids) = text "<<sequence type>>"
   135 type2C (ArrayDecl r t) = text "<<array type>>"
   146 type2C (ArrayDecl r t) = text "<<array type>>"
   136 
   147 type2C (Set t) = text "<<set>>"
       
   148 type2C (FunctionType returnType params) = text "<<function>>"
   137 
   149 
   138 phrase2C :: Phrase -> Doc
   150 phrase2C :: Phrase -> Doc
   139 phrase2C (Phrases p) = text "{" $+$ (nest 4 . vcat . map phrase2C $ p) $+$ text "}"
   151 phrase2C (Phrases p) = text "{" $+$ (nest 4 . vcat . map phrase2C $ p) $+$ text "}"
       
   152 phrase2C (ProcCall f@(FunCall {}) []) = ref2C f <> semi
   140 phrase2C (ProcCall ref params) = ref2C ref <> parens (hsep . punctuate (char ',') . map expr2C $ params) <> semi
   153 phrase2C (ProcCall ref params) = ref2C ref <> parens (hsep . punctuate (char ',') . map expr2C $ params) <> semi
   141 phrase2C (IfThenElse (expr) phrase1 mphrase2) = text "if" <> parens (expr2C expr) $+$ (phrase2C . wrapPhrase) phrase1 $+$ elsePart
   154 phrase2C (IfThenElse (expr) phrase1 mphrase2) = text "if" <> parens (expr2C expr) $+$ (phrase2C . wrapPhrase) phrase1 $+$ elsePart
   142     where
   155     where
   143     elsePart | isNothing mphrase2 = empty
   156     elsePart | isNothing mphrase2 = empty
   144              | otherwise = text "else" $$ (phrase2C . wrapPhrase) (fromJust mphrase2)
   157              | otherwise = text "else" $$ (phrase2C . wrapPhrase) (fromJust mphrase2)
   152 phrase2C (ForCycle (Identifier i) e1 e2 p) = 
   165 phrase2C (ForCycle (Identifier i) e1 e2 p) = 
   153     text "for" <> (parens . hsep . punctuate (char ';') $ [text i <+> text "=" <+> expr2C e1, text i <+> text "<=" <+> expr2C e2, text "++" <> text i])
   166     text "for" <> (parens . hsep . punctuate (char ';') $ [text i <+> text "=" <+> expr2C e1, text i <+> text "<=" <+> expr2C e2, text "++" <> text i])
   154     $$
   167     $$
   155     phrase2C (wrapPhrase p)
   168     phrase2C (wrapPhrase p)
   156 phrase2C (RepeatCycle e p) = text "do" <+> phrase2C (Phrases p) <+> text "while" <> parens (text "!" <> parens (expr2C e))
   169 phrase2C (RepeatCycle e p) = text "do" <+> phrase2C (Phrases p) <+> text "while" <> parens (text "!" <> parens (expr2C e))
       
   170 phrase2C NOP = text ";"
   157 
   171 
   158 
   172 
   159 wrapPhrase p@(Phrases _) = p
   173 wrapPhrase p@(Phrases _) = p
   160 wrapPhrase p = Phrases [p]
   174 wrapPhrase p = Phrases [p]
   161 
   175 
   162 
   176 
   163 expr2C :: Expression -> Doc
   177 expr2C :: Expression -> Doc
   164 expr2C (Expression s) = text s
   178 expr2C (Expression s) = text s
   165 expr2C (BinOp op expr1 expr2) = parens $ (expr2C expr1) <+> op2C op <+> (expr2C expr2)
   179 expr2C (BinOp op expr1 expr2) = parens $ (expr2C expr1) <+> op2C op <+> (expr2C expr2)
   166 expr2C (NumberLiteral s) = text s
   180 expr2C (NumberLiteral s) = text s
       
   181 expr2C (FloatLiteral s) = text s
   167 expr2C (HexNumber s) = text "0x" <> (text . map toLower $ s)
   182 expr2C (HexNumber s) = text "0x" <> (text . map toLower $ s)
   168 expr2C (StringLiteral s) = doubleQuotes $ text s 
   183 expr2C (StringLiteral s) = doubleQuotes $ text s 
   169 expr2C (Reference ref) = ref2C ref
   184 expr2C (Reference ref) = ref2C ref
   170 expr2C (PrefixOp op expr) = op2C op <+> expr2C expr
   185 expr2C (PrefixOp op expr) = op2C op <+> expr2C expr
   171     {-
   186 expr2C Null = text "NULL"
   172     | PostfixOp String Expression
   187 expr2C (BuiltInFunCall params ref) = ref2C ref <> parens (hsep . punctuate (char ',') . map expr2C $ params)
   173     | CharCode String
   188 expr2C _ = text "<<expression>>"
   174     -}            
       
   175 expr2C _ = empty
       
   176 
   189 
   177 
   190 
   178 ref2C :: Reference -> Doc
   191 ref2C :: Reference -> Doc
   179 ref2C (ArrayElement exprs ref) = ref2C ref <> (brackets . hcat) (punctuate comma $ map expr2C exprs)
   192 ref2C (ArrayElement exprs ref) = ref2C ref <> (brackets . hcat) (punctuate comma $ map expr2C exprs)
   180 ref2C (SimpleReference (Identifier name)) = text name
   193 ref2C (SimpleReference (Identifier name)) = text name
   181 ref2C (RecordField (Dereference ref1) ref2) = ref2C ref1 <> text "->" <> ref2C ref2
   194 ref2C (RecordField (Dereference ref1) ref2) = ref2C ref1 <> text "->" <> ref2C ref2
   182 ref2C (RecordField ref1 ref2) = ref2C ref1 <> text "." <> ref2C ref2
   195 ref2C (RecordField ref1 ref2) = ref2C ref1 <> text "." <> ref2C ref2
   183 ref2C (Dereference ref) = parens $ text "*" <> ref2C ref
   196 ref2C (Dereference ref) = parens $ text "*" <> ref2C ref
   184 ref2C (FunCall params ref) = ref2C ref <> parens (hsep . punctuate (char ',') . map expr2C $ params)
   197 ref2C (FunCall params ref) = ref2C ref <> parens (hsep . punctuate (char ',') . map expr2C $ params)
   185 ref2C (Address ref) = text "&" <> ref2C ref
   198 ref2C (Address ref) = text "&" <> parens (ref2C ref)
   186 
   199 ref2C (TypeCast (Identifier t) expr) = parens (text t) <> expr2C expr
       
   200 ref2C (RefExpression expr) = expr2C expr
   187 
   201 
   188 op2C "or" = text "|"
   202 op2C "or" = text "|"
   189 op2C "and" = text "&"
   203 op2C "and" = text "&"
   190 op2C "not" = text "!"
   204 op2C "not" = text "!"
   191 op2C "xor" = text "^"
   205 op2C "xor" = text "^"