# HG changeset patch # User unc0rr # Date 1322574162 -14400 # Node ID 090269e528dfbc800a8228da0d9b682c05fc34ad # Parent afd8c9a3672d85708cf106b964bec1d5caf18830 - Improve parsing of prefix operators - Improve C renderer - pas2c now saves converted .c and .h files diff -r afd8c9a3672d -r 090269e528df hedgewars/uTextures.pas --- a/hedgewars/uTextures.pas Mon Nov 28 23:14:11 2011 +0300 +++ b/hedgewars/uTextures.pas Tue Nov 29 17:42:42 2011 +0400 @@ -119,6 +119,8 @@ fromP4:= @(fromP4^[Surf^.pitch div 4]) end; end; + + function Surface2Tex(surf: PSDL_Surface; enableClamp: boolean): PTexture; var tw, th, x, y: Longword; tmpp: pointer; diff -r afd8c9a3672d -r 090269e528df tools/PascalParser.hs --- a/tools/PascalParser.hs Mon Nov 28 23:14:11 2011 +0300 +++ b/tools/PascalParser.hs Tue Nov 29 17:42:42 2011 +0400 @@ -12,97 +12,7 @@ import Data.Maybe import PascalBasics - -data PascalUnit = - Program Identifier Implementation Phrase - | Unit Identifier Interface Implementation (Maybe Initialize) (Maybe Finalize) - | System - deriving Show -data Interface = Interface Uses TypesAndVars - deriving Show -data Implementation = Implementation Uses TypesAndVars - deriving Show -data Identifier = Identifier String - deriving Show -data TypesAndVars = TypesAndVars [TypeVarDeclaration] - deriving Show -data TypeVarDeclaration = TypeDeclaration Identifier TypeDecl - | VarDeclaration Bool ([Identifier], TypeDecl) (Maybe InitExpression) - | FunctionDeclaration Identifier TypeDecl [TypeVarDeclaration] (Maybe (TypesAndVars, Phrase)) - | OperatorDeclaration String Identifier TypeDecl [TypeVarDeclaration] (Maybe (TypesAndVars, Phrase)) - deriving Show -data TypeDecl = SimpleType Identifier - | RangeType Range - | Sequence [Identifier] - | ArrayDecl (Maybe Range) TypeDecl - | RecordType [TypeVarDeclaration] (Maybe [[TypeVarDeclaration]]) - | PointerTo TypeDecl - | String Integer - | Set TypeDecl - | FunctionType TypeDecl [TypeVarDeclaration] - | UnknownType - deriving Show -data Range = Range Identifier - | RangeFromTo InitExpression InitExpression - deriving Show -data Initialize = Initialize String - deriving Show -data Finalize = Finalize String - deriving Show -data Uses = Uses [Identifier] - deriving Show -data Phrase = ProcCall Reference [Expression] - | IfThenElse Expression Phrase (Maybe Phrase) - | WhileCycle Expression Phrase - | RepeatCycle Expression [Phrase] - | ForCycle Identifier Expression Expression Phrase - | WithBlock Reference Phrase - | Phrases [Phrase] - | SwitchCase Expression [([InitExpression], Phrase)] (Maybe [Phrase]) - | Assignment Reference Expression - | NOP - deriving Show -data Expression = Expression String - | BuiltInFunCall [Expression] Reference - | PrefixOp String Expression - | PostfixOp String Expression - | BinOp String Expression Expression - | StringLiteral String - | CharCode String - | HexCharCode String - | NumberLiteral String - | FloatLiteral String - | HexNumber String - | Reference Reference - | SetExpression [Identifier] - | Null - deriving Show -data Reference = ArrayElement [Expression] Reference - | FunCall [Expression] Reference - | TypeCast Identifier Expression - | SimpleReference Identifier - | Dereference Reference - | RecordField Reference Reference - | Address Reference - | RefExpression Expression - deriving Show -data InitExpression = InitBinOp String InitExpression InitExpression - | InitPrefixOp String InitExpression - | InitReference Identifier - | InitArray [InitExpression] - | InitRecord [(Identifier, InitExpression)] - | InitFloat String - | InitNumber String - | InitHexNumber String - | InitString String - | InitChar String - | BuiltInFunction String [InitExpression] - | InitSet [InitExpression] - | InitAddress InitExpression - | InitNull - | InitRange Range - | InitTypeCast Identifier InitExpression - deriving Show +import PascalUnitSyntaxTree knownTypes = ["shortstring", "char", "byte"] @@ -145,7 +55,7 @@ parens pas (option [] parameters) >>= return . FunCall , char '^' >> return Dereference , (brackets pas) (commaSep1 pas $ expression) >>= return . ArrayElement - , (char '.' >> notFollowedBy (char '.')) >> liftM RecordField reference + , (char '.' >> notFollowedBy (char '.')) >> liftM (flip RecordField) reference ] typeCast = do @@ -450,6 +360,7 @@ , char '$' >> many hexDigit >>= \h -> comments >> return (HexNumber h) , char '-' >> expression >>= return . PrefixOp "-" , try $ string "nil" >> return Null + , try $ string "not" >> expression >>= return . PrefixOp "not" , reference >>= return . Reference ] "simple expression" @@ -463,7 +374,6 @@ , [ Infix (char '+' >> return (BinOp "+")) AssocLeft , Infix (char '-' >> return (BinOp "-")) AssocLeft ] - , [Prefix (try (string "not") >> return (PrefixOp "not"))] , [ Infix (try (string "<>") >> return (BinOp "<>")) AssocNone , Infix (try (string "<=") >> return (BinOp "<=")) AssocNone , Infix (try (string ">=") >> return (BinOp ">=")) AssocNone diff -r afd8c9a3672d -r 090269e528df tools/PascalUnitSyntaxTree.hs --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/tools/PascalUnitSyntaxTree.hs Tue Nov 29 17:42:42 2011 +0400 @@ -0,0 +1,94 @@ +module PascalUnitSyntaxTree where + +import Data.Traversable + +data PascalUnit = + Program Identifier Implementation Phrase + | Unit Identifier Interface Implementation (Maybe Initialize) (Maybe Finalize) + | System + deriving Show +data Interface = Interface Uses TypesAndVars + deriving Show +data Implementation = Implementation Uses TypesAndVars + deriving Show +data Identifier = Identifier String + deriving Show +data TypesAndVars = TypesAndVars [TypeVarDeclaration] + deriving Show +data TypeVarDeclaration = TypeDeclaration Identifier TypeDecl + | VarDeclaration Bool ([Identifier], TypeDecl) (Maybe InitExpression) + | FunctionDeclaration Identifier TypeDecl [TypeVarDeclaration] (Maybe (TypesAndVars, Phrase)) + | OperatorDeclaration String Identifier TypeDecl [TypeVarDeclaration] (Maybe (TypesAndVars, Phrase)) + deriving Show +data TypeDecl = SimpleType Identifier + | RangeType Range + | Sequence [Identifier] + | ArrayDecl (Maybe Range) TypeDecl + | RecordType [TypeVarDeclaration] (Maybe [[TypeVarDeclaration]]) + | PointerTo TypeDecl + | String Integer + | Set TypeDecl + | FunctionType TypeDecl [TypeVarDeclaration] + | UnknownType + deriving Show +data Range = Range Identifier + | RangeFromTo InitExpression InitExpression + deriving Show +data Initialize = Initialize String + deriving Show +data Finalize = Finalize String + deriving Show +data Uses = Uses [Identifier] + deriving Show +data Phrase = ProcCall Reference [Expression] + | IfThenElse Expression Phrase (Maybe Phrase) + | WhileCycle Expression Phrase + | RepeatCycle Expression [Phrase] + | ForCycle Identifier Expression Expression Phrase + | WithBlock Reference Phrase + | Phrases [Phrase] + | SwitchCase Expression [([InitExpression], Phrase)] (Maybe [Phrase]) + | Assignment Reference Expression + | NOP + deriving Show +data Expression = Expression String + | BuiltInFunCall [Expression] Reference + | PrefixOp String Expression + | PostfixOp String Expression + | BinOp String Expression Expression + | StringLiteral String + | CharCode String + | HexCharCode String + | NumberLiteral String + | FloatLiteral String + | HexNumber String + | Reference Reference + | SetExpression [Identifier] + | Null + deriving Show +data Reference = ArrayElement [Expression] Reference + | FunCall [Expression] Reference + | TypeCast Identifier Expression + | SimpleReference Identifier + | Dereference Reference + | RecordField Reference Reference + | Address Reference + | RefExpression Expression + deriving Show +data InitExpression = InitBinOp String InitExpression InitExpression + | InitPrefixOp String InitExpression + | InitReference Identifier + | InitArray [InitExpression] + | InitRecord [(Identifier, InitExpression)] + | InitFloat String + | InitNumber String + | InitHexNumber String + | InitString String + | InitChar String + | BuiltInFunction String [InitExpression] + | InitSet [InitExpression] + | InitAddress InitExpression + | InitNull + | InitRange Range + | InitTypeCast Identifier InitExpression + deriving Show 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 "&"