tools/pas2c.hs
author koda
Fri, 18 Nov 2011 00:32:52 +0100
changeset 6394 f0a9042e7387
parent 6391 bd5851ab3157
child 6399 a904c735979c
permissions -rw-r--r--
yay, finally osx (and likely windows) fullscreen switch works like on linux! ALL textures had to be destroyed and recreated only after the new window got created. In other news, the new window must be cleaned with glClear to skip a first frame of garbage and AddProgress is only called the first time.
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
     1
module Pas2C where
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
     2
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
     3
import PascalParser
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
     4
import Text.PrettyPrint.HughesPJ
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
     5
import Data.Maybe
6277
627b5752733a A try to improve parser move (has regressions)
unc0rr
parents: 6275
diff changeset
     6
import Data.Char
6355
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
     7
import Text.Parsec.String
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
     8
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
     9
6355
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    10
pas2C :: String -> IO String
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    11
pas2C fileName = do
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    12
    ptree <- parseFromFile pascalUnit fileName
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    13
    case ptree of
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    14
         (Left a) -> return (show a)
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    15
         (Right a) -> (return . render . pascal2C) a
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    16
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    17
pascal2C :: PascalUnit -> Doc
6391
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    18
pascal2C (Unit unitName interface implementation init fin) = 
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    19
    interface2C interface
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    20
    $+$ 
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    21
    implementation2C implementation
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    22
6391
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    23
interface2C :: Interface -> Doc
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    24
interface2C (Interface uses tvars) = typesAndVars2C tvars
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    25
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    26
implementation2C :: Implementation -> Doc
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    27
implementation2C (Implementation uses tvars) = typesAndVars2C tvars
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    28
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    29
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    30
typesAndVars2C :: TypesAndVars -> Doc
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    31
typesAndVars2C (TypesAndVars ts) = vcat $ map tvar2C ts
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    32
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    33
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    34
tvar2C :: TypeVarDeclaration -> Doc
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    35
tvar2C (FunctionDeclaration (Identifier name) returnType Nothing) = 
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    36
    type2C returnType <+> text (name ++ "();")
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    37
tvar2C (FunctionDeclaration (Identifier name) returnType (Just phrase)) = 
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    38
    type2C returnType <+> text (name ++ "()") 
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    39
    $$
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    40
    phrase2C phrase
6355
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    41
tvar2C (TypeDeclaration (Identifier i) t) = text "type" <+> text i <+> type2C t <> text ";"
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    42
tvar2C (VarDeclaration isConst (ids, t) mInitExpr) = 
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    43
    if isConst then text "const" else empty
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    44
    <+>
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    45
    type2C t
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    46
    <+>
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    47
    (hsep . punctuate (char ',') . map (\(Identifier i) -> text i) $ ids)
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    48
    <+>
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    49
    initExpr mInitExpr
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    50
    <>
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    51
    text ";"
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    52
    where
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    53
    initExpr Nothing = empty
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    54
    initExpr (Just e) = text "=" <+> initExpr2C e
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    55
6391
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    56
initExpr2C :: InitExpression -> Doc
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    57
initExpr2C (InitBinOp op expr1 expr2) = parens $ (initExpr2C expr1) <+> op2C op <+> (initExpr2C expr2)
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    58
initExpr2C (InitNumber s) = text s
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    59
initExpr2C (InitFloat s) = text s
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    60
initExpr2C (InitHexNumber s) = text "0x" <> (text . map toLower $ s)
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    61
initExpr2C (InitString s) = doubleQuotes $ text s 
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    62
initExpr2C (InitReference (Identifier i)) = text i
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    63
bd5851ab3157 - Parse sets initialization
unc0rr
parents: 6355
diff changeset
    64
6355
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    65
initExpr2C _ = text "<<expression>>"
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    66
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    67
type2C :: TypeDecl -> Doc
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    68
type2C UnknownType = text "void"
6355
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    69
type2C String = text "string"
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    70
type2C (SimpleType (Identifier i)) = text i
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    71
type2C (PointerTo t) = type2C t <> text "*"
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    72
type2C (RecordType tvs) = text "{" $+$ (nest 4 . vcat . map tvar2C $ tvs) $+$ text "}"
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    73
type2C (RangeType r) = text "<<range type>>"
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    74
type2C (Sequence ids) = text "<<sequence type>>"
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    75
type2C (ArrayDecl r t) = text "<<array type>>"
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    76
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    77
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    78
phrase2C :: Phrase -> Doc
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    79
phrase2C (Phrases p) = text "{" $+$ (nest 4 . vcat . map phrase2C $ p) $+$ text "}"
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    80
phrase2C (ProcCall (Identifier name) params) = text name <> parens (hsep . punctuate (char ',') . map expr2C $ params) <> semi
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    81
phrase2C (IfThenElse (expr) phrase1 mphrase2) = text "if" <> parens (expr2C expr) $+$ (phrase2C . wrapPhrase) phrase1 $+$ elsePart
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    82
    where
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    83
    elsePart | isNothing mphrase2 = empty
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    84
             | otherwise = text "else" $$ (phrase2C . wrapPhrase) (fromJust mphrase2)
6277
627b5752733a A try to improve parser move (has regressions)
unc0rr
parents: 6275
diff changeset
    85
phrase2C (Assignment ref expr) = ref2C ref <> text " = " <> expr2C expr <> semi
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    86
phrase2C (WhileCycle expr phrase) = text "while" <> parens (expr2C expr) $$ (phrase2C $ wrapPhrase phrase)
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    87
phrase2C (SwitchCase expr cases mphrase) = text "switch" <> parens (expr2C expr) <> text "of" $+$ (nest 4 . vcat . map case2C) cases
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    88
    where
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    89
    case2C :: (Expression, Phrase) -> Doc
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    90
    case2C (e, p) = text "case" <+> parens (expr2C e) <> char ':' <> nest 4 (phrase2C p $+$ text "break;")
6355
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    91
phrase2C (WithBlock ref p) = text "namespace" <> parens (ref2C ref) $$ (phrase2C $ wrapPhrase p)
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    92
phrase2C (ForCycle (Identifier i) e1 e2 p) = 
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    93
    text "for" <> (parens . hsep . punctuate (char ';') $ [text i <+> text "=" <+> expr2C e1, text i <+> text "<=" <+> expr2C e2, text "++" <> text i])
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    94
    $$
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    95
    phrase2C (wrapPhrase p)
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    96
phrase2C (RepeatCycle e p) = text "do" <+> phrase2C (Phrases p) <+> text "while" <> parens (text "!" <> parens (expr2C e))
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
    97
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
    98
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
    99
wrapPhrase p@(Phrases _) = p
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   100
wrapPhrase p = Phrases [p]
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
   101
6355
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
   102
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
   103
expr2C :: Expression -> Doc
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
   104
expr2C (Expression s) = text s
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   105
expr2C (BinOp op expr1 expr2) = parens $ (expr2C expr1) <+> op2C op <+> (expr2C expr2)
6277
627b5752733a A try to improve parser move (has regressions)
unc0rr
parents: 6275
diff changeset
   106
expr2C (NumberLiteral s) = text s
627b5752733a A try to improve parser move (has regressions)
unc0rr
parents: 6275
diff changeset
   107
expr2C (HexNumber s) = text "0x" <> (text . map toLower $ s)
627b5752733a A try to improve parser move (has regressions)
unc0rr
parents: 6275
diff changeset
   108
expr2C (StringLiteral s) = doubleQuotes $ text s 
627b5752733a A try to improve parser move (has regressions)
unc0rr
parents: 6275
diff changeset
   109
expr2C (Reference ref) = ref2C ref
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   110
expr2C (PrefixOp op expr) = op2C op <+> expr2C expr
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   111
    {-
6277
627b5752733a A try to improve parser move (has regressions)
unc0rr
parents: 6275
diff changeset
   112
    | PostfixOp String Expression
627b5752733a A try to improve parser move (has regressions)
unc0rr
parents: 6275
diff changeset
   113
    | CharCode String
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
   114
    -}            
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
   115
expr2C _ = empty
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
   116
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   117
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   118
ref2C :: Reference -> Doc
6317
83b93a2d2741 Improve parsing of complex references like "a^[b[c], d]"
unc0rr
parents: 6307
diff changeset
   119
ref2C (ArrayElement exprs ref) = ref2C ref <> (brackets . hcat) (punctuate comma $ map expr2C exprs)
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   120
ref2C (SimpleReference (Identifier name)) = text name
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   121
ref2C (RecordField (Dereference ref1) ref2) = ref2C ref1 <> text "->" <> ref2C ref2
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   122
ref2C (RecordField ref1 ref2) = ref2C ref1 <> text "." <> ref2C ref2
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   123
ref2C (Dereference ref) = parens $ text "*" <> ref2C ref
6317
83b93a2d2741 Improve parsing of complex references like "a^[b[c], d]"
unc0rr
parents: 6307
diff changeset
   124
ref2C (FunCall params ref) = ref2C ref <> parens (hsep . punctuate (char ',') . map expr2C $ params)
83b93a2d2741 Improve parsing of complex references like "a^[b[c], d]"
unc0rr
parents: 6307
diff changeset
   125
ref2C (Address ref) = text "&" <> ref2C ref
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   126
6355
734fed7aefd3 Introduce initialization expressions
unc0rr
parents: 6317
diff changeset
   127
6275
f1b4f37dba22 Many improvements to the parser
unc0rr
parents: 6274
diff changeset
   128
op2C "or" = text "|"
f1b4f37dba22 Many improvements to the parser
unc0rr
parents: 6274
diff changeset
   129
op2C "and" = text "&"
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   130
op2C "not" = text "!"
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   131
op2C "xor" = text "^"
6275
f1b4f37dba22 Many improvements to the parser
unc0rr
parents: 6274
diff changeset
   132
op2C "div" = text "/"
f1b4f37dba22 Many improvements to the parser
unc0rr
parents: 6274
diff changeset
   133
op2C "mod" = text "%"
6307
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   134
op2C "shl" = text "<<"
25cfd9f4a567 Even more improvements to the parser and converter
unc0rr
parents: 6277
diff changeset
   135
op2C "shr" = text ">>"
6275
f1b4f37dba22 Many improvements to the parser
unc0rr
parents: 6274
diff changeset
   136
op2C "<>" = text "!="
6277
627b5752733a A try to improve parser move (has regressions)
unc0rr
parents: 6275
diff changeset
   137
op2C "=" = text "=="
6275
f1b4f37dba22 Many improvements to the parser
unc0rr
parents: 6274
diff changeset
   138
op2C a = text a
6273
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
   139
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
   140
maybeVoid "" = "void"
13262c6e5027 Starting pas2C using library called 'pretty'
unc0rr
parents:
diff changeset
   141
maybeVoid a = a