|
1 module Pas2C where |
|
2 |
|
3 import PascalParser |
|
4 import Text.PrettyPrint.HughesPJ |
|
5 import Data.Maybe |
|
6 |
|
7 |
|
8 pascal2C :: PascalUnit -> Doc |
|
9 pascal2C (Unit unitName interface implementation init fin) = implementation2C implementation |
|
10 |
|
11 |
|
12 implementation2C :: Implementation -> Doc |
|
13 implementation2C (Implementation uses tvars) = typesAndVars2C tvars |
|
14 |
|
15 |
|
16 typesAndVars2C :: TypesAndVars -> Doc |
|
17 typesAndVars2C (TypesAndVars ts) = vcat $ map tvar2C ts |
|
18 |
|
19 |
|
20 tvar2C :: TypeVarDeclaration -> Doc |
|
21 tvar2C (FunctionDeclaration (Identifier name) (Identifier returnType) Nothing) = |
|
22 text $ maybeVoid returnType ++ " " ++ name ++ "();" |
|
23 |
|
24 |
|
25 tvar2C (FunctionDeclaration (Identifier name) (Identifier returnType) (Just phrase)) = |
|
26 text (maybeVoid returnType ++ " " ++ name ++ "()") |
|
27 $$ |
|
28 phrase2C phrase |
|
29 tvar2C _ = empty |
|
30 |
|
31 |
|
32 phrase2C :: Phrase -> Doc |
|
33 phrase2C (Phrases p) = braces . nest 4 . vcat . map phrase2C $ p |
|
34 phrase2C (ProcCall (Identifier name) params) = text name <> parens (hsep . punctuate (char ',') . map expr2C $ params) <> semi |
|
35 phrase2C (IfThenElse (expr) phrase1 mphrase2) = text "if" <> parens (expr2C expr) $$ (braces . nest 4 . phrase2C) phrase1 <+> elsePart |
|
36 where |
|
37 elsePart | isNothing mphrase2 = empty |
|
38 | otherwise = text "else" $$ (braces . nest 4 . phrase2C) (fromJust mphrase2) |
|
39 phrase2C (Assignment (Identifier name) expr) = text name <> text " = " <> expr2C expr <> semi |
|
40 phrase2C (WhileCycle expr phrase) = text "while" <> parens (expr2C expr) $$ nest 4 (phrase2C phrase) |
|
41 phrase2C (SwitchCase expr cases mphrase) = text "switch" <> parens (expr2C expr) <> text "of" $$ (nest 4 . vcat . map case2C) cases |
|
42 where |
|
43 case2C :: (Expression, Phrase) -> Doc |
|
44 case2C (e, p) = text "case" <+> parens (expr2C e) <> char ':' <> nest 4 (phrase2C p $$ text "break;") |
|
45 {- |
|
46 | RepeatCycle Expression Phrase |
|
47 | ForCycle |
|
48 | SwitchCase Expression [(Expression, Phrase)] (Maybe Phrase) |
|
49 | Assignment Identifier Expression |
|
50 -} |
|
51 phrase2C _ = empty |
|
52 |
|
53 |
|
54 expr2C :: Expression -> Doc |
|
55 expr2C (Expression s) = text s |
|
56 expr2C (FunCall (Identifier name) params) = text name <> parens (hsep . punctuate (char ',') . map expr2C $ params) |
|
57 expr2C (BinOp op expr1 expr2) = (expr2C expr1) <+> op2C op <+> (expr2C expr2) |
|
58 {- | FunCall Identifier [Expression] |
|
59 | PrefixOp String Expression |
|
60 | BinOp String Expression Expression |
|
61 -} |
|
62 expr2C _ = empty |
|
63 |
|
64 op2C = text |
|
65 |
|
66 maybeVoid "" = "void" |
|
67 maybeVoid a = a |