diff -r afd8c9a3672d -r 090269e528df tools/pas2c.hs --- a/tools/pas2c.hs Mon Nov 28 23:14:11 2011 +0300 +++ b/tools/pas2c.hs Tue Nov 29 17:42:42 2011 +0400 @@ -1,6 +1,5 @@ module Pas2C where -import PascalParser import Text.PrettyPrint.HughesPJ import Data.Maybe import Data.Char @@ -14,12 +13,14 @@ import System.IO.Error import qualified Data.Map as Map +import PascalParser +import PascalUnitSyntaxTree pas2C :: String -> IO () pas2C fn = do setCurrentDirectory "../hedgewars/" s <- flip execStateT initState $ f fn - writeFile "dump" $ show s + mapM_ toCFiles (Map.toList s) where printLn = liftIO . hPutStrLn stderr print = liftIO . hPutStr stderr @@ -49,15 +50,21 @@ modify (Map.insert fileName a) mapM_ f (usesFiles a) - -usesFiles :: PascalUnit -> [String] +toCFiles :: (String, PascalUnit) -> IO () +toCFiles (_, System) = return () +toCFiles (fn, p@(Program {})) = writeFile (fn ++ ".c") $ (render . pascal2C) p +toCFiles (fn, (Unit _ interface implementation _ _)) = do + writeFile (fn ++ ".h") $ (render . interface2C) interface + writeFile (fn ++ ".c") $ (render . implementation2C) implementation + +usesFiles :: PascalUnit -> [String] usesFiles (Program _ (Implementation uses _) _) = uses2List uses usesFiles (Unit _ (Interface uses1 _) (Implementation uses2 _) _ _) = uses2List uses1 ++ uses2List uses2 pascal2C :: PascalUnit -> Doc -pascal2C (Unit unitName interface implementation init fin) = +pascal2C (Unit _ interface implementation init fin) = interface2C interface $+$ implementation2C implementation @@ -65,6 +72,8 @@ implementation2C implementation $+$ tvar2C (FunctionDeclaration (Identifier "main") (SimpleType $ Identifier "int") [] (Just (TypesAndVars [], mainFunction))) + + interface2C :: Interface -> Doc interface2C (Interface uses tvars) = uses2C uses $+$ typesAndVars2C tvars @@ -83,9 +92,9 @@ tvar2C :: TypeVarDeclaration -> Doc tvar2C (FunctionDeclaration (Identifier name) returnType params Nothing) = - type2C returnType <+> text (name ++ "();") + type2C returnType <+> text name <> parens (hcat $ map tvar2C params) <> text ";" tvar2C (FunctionDeclaration (Identifier name) returnType params (Just (tvars, phrase))) = - type2C returnType <+> text (name ++ "()") + type2C returnType <+> text name <> parens (hcat $ map tvar2C params) $+$ text "{" $+$ nest 4 ( @@ -112,6 +121,8 @@ where initExpr Nothing = empty initExpr (Just e) = text "=" <+> initExpr2C e +tvar2C (OperatorDeclaration op _ ret params body) = + tvar2C (FunctionDeclaration (Identifier "") ret params body) initExpr2C :: InitExpression -> Doc initExpr2C (InitBinOp op expr1 expr2) = parens $ (initExpr2C expr1) <+> op2C op <+> (initExpr2C expr2) @@ -133,10 +144,12 @@ type2C (RangeType r) = text "<>" type2C (Sequence ids) = text "<>" type2C (ArrayDecl r t) = text "<>" - +type2C (Set t) = text "<>" +type2C (FunctionType returnType params) = text "<>" phrase2C :: Phrase -> Doc phrase2C (Phrases p) = text "{" $+$ (nest 4 . vcat . map phrase2C $ p) $+$ text "}" +phrase2C (ProcCall f@(FunCall {}) []) = ref2C f <> semi phrase2C (ProcCall ref params) = ref2C ref <> parens (hsep . punctuate (char ',') . map expr2C $ params) <> semi phrase2C (IfThenElse (expr) phrase1 mphrase2) = text "if" <> parens (expr2C expr) $+$ (phrase2C . wrapPhrase) phrase1 $+$ elsePart where @@ -154,6 +167,7 @@ $$ phrase2C (wrapPhrase p) phrase2C (RepeatCycle e p) = text "do" <+> phrase2C (Phrases p) <+> text "while" <> parens (text "!" <> parens (expr2C e)) +phrase2C NOP = text ";" wrapPhrase p@(Phrases _) = p @@ -164,15 +178,14 @@ expr2C (Expression s) = text s expr2C (BinOp op expr1 expr2) = parens $ (expr2C expr1) <+> op2C op <+> (expr2C expr2) expr2C (NumberLiteral s) = text s +expr2C (FloatLiteral s) = text s expr2C (HexNumber s) = text "0x" <> (text . map toLower $ s) expr2C (StringLiteral s) = doubleQuotes $ text s expr2C (Reference ref) = ref2C ref expr2C (PrefixOp op expr) = op2C op <+> expr2C expr - {- - | PostfixOp String Expression - | CharCode String - -} -expr2C _ = empty +expr2C Null = text "NULL" +expr2C (BuiltInFunCall params ref) = ref2C ref <> parens (hsep . punctuate (char ',') . map expr2C $ params) +expr2C _ = text "<>" ref2C :: Reference -> Doc @@ -182,8 +195,9 @@ ref2C (RecordField ref1 ref2) = ref2C ref1 <> text "." <> ref2C ref2 ref2C (Dereference ref) = parens $ text "*" <> ref2C ref ref2C (FunCall params ref) = ref2C ref <> parens (hsep . punctuate (char ',') . map expr2C $ params) -ref2C (Address ref) = text "&" <> ref2C ref - +ref2C (Address ref) = text "&" <> parens (ref2C ref) +ref2C (TypeCast (Identifier t) expr) = parens (text t) <> expr2C expr +ref2C (RefExpression expr) = expr2C expr op2C "or" = text "|" op2C "and" = text "&"