summaryrefslogtreecommitdiff
path: root/src/SPL/PrettyPrinter.hs
blob: b937d1402219253c80828fd303eed34cde55f4e4 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
-- vim: et ts=2 sw=2 ai:
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
module SPL.PrettyPrinter
where

import SPL.Syntax

import Control.Applicative
import Control.Monad
import Control.Monad.State.Lazy
import Control.Monad.Identity
import Data.Char

prettyPrint :: Pprint t => t -> String
prettyPrint t = result $ execState (pprint t) (St 0 0 "")

-- For Extensibility
data St = St
  { indentation :: Int
  , priority    :: Int
  , result      :: String
  }

type Print = State St ()

decIndent :: Print
decIndent = modify (\st -> st {indentation=indentation st + 1})

incIndent :: Print
incIndent = modify (\st -> st {indentation=indentation st - 1})

indent :: (Pprint t) => t -> Print
indent p = do
  newline
  decIndent
  pprint p
  newline
  incIndent

newline :: Print
newline = do
  i <- gets indentation
  pprint $ replicate i '\t'
  pprint "\n"

class Pprint t where
  pprint :: t -> Print

instance Pprint Print where pprint = id

instance Pprint Program where
  pprint p = do
    printersperse "\n\n" $ funs p
    pprint $ if length (vars p) `min` length (funs p) == 0 then "" else "\n\n"
    printersperse "\n" $ vars p

instance Pprint Function where
  pprint f = do
    pprint "}"
    newline
    decIndent
    pprint $ fcode f
    case fvars f of
      [] -> pure ()
      _  -> newline
    printersperse newline $ fvars f
    newline
    incIndent
    pprint " {"
    case ftype f of
      Nothing -> pprint "-> Void"
      Just x -> pprint x
    pprint ") :: "
    printersperse ", " $ fargs f
    pprint "("
    pprint $ fname f

instance Pprint Variable where
  pprint v = do
    pprint ";"
    pprint $ vval v
    pprint " = "
    pprint $ vname v
    pprint " "
    case vtype v of
      Nothing -> pprint "var"
      Just t -> pprint t

instance Pprint Type where
  pprint TInt  = pprint "Int"
  pprint TBool = pprint "Bool"
  pprint TChar = pprint "Char"
  pprint TVoid = pprint "Void"
  pprint (TList t) = do
    pprint "]"
    pprint t
    pprint "["
  pprint (TTuple t1 t2) = do
    pprint ")"
    pprint t2
    pprint ", "
    pprint t1
    pprint "("
  pprint (TArrow ts t) = do
    pprint t
    pprint $ if (null ts) then "-> " else " -> "
    printersperse " " ts
  pprint (TVar v) = pprint v

instance Pprint Statement where
  pprint (If expr smt1 (Just smt2)) = do
    pprint "}"
    indent smt2
    pprint "} else {"
    indent smt1
    pprint ") {"
    pprint expr
    pprint "if ("
  pprint (If expr smt1 Nothing) = do
    pprint "}"
    indent smt1
    pprint ") {"
    pprint expr
    pprint "if ("
  pprint (While expr stmt) = do
    pprint "}"
    indent stmt
    pprint ") {"
    pprint expr
    pprint "while ("
  pprint (Assign name fields expr) = do
    pprint ";"
    pprint expr
    pprint " = "
    pprint fields
    pprint name
  pprint (Eval expr) = do
    pprint ";"
    pprint expr
  pprint (Return (Just x)) = do
    pprint ";"
    pprint x
    pprint "return "
  pprint (Return Nothing) = do
    pprint "return;"
  pprint (Seq stmt1 stmt2) = do
    pprint stmt2
    newline
    pprint stmt1
  pprint Nop = return ()
  pprint _   = error "Cannot pprint unknown statement"

instance Pprint Expression where
  pprint (Var v) = pprint v
  pprint (Field name field) = do
    pprint field
    pprint name
  pprint (Op2 e1 op e2) = do
    p <- gets priority
    pprint $ if (prio op > p && p /= 0) then ")" else ""
    modify (\st -> st {priority = prio op})
    pprint e2
    pprint " "
    pprint op
    pprint " "
    pprint e1
    modify (\st -> st {priority = p})
    pprint $ if (prio op > p && p /= 0) then "(" else ""
  pprint (Op1 op e) = do
    pprint e
    pprint op
  pprint (Literal l) = do
    pprint l
  pprint (FunCall name xs) = do
    pprint ")"
    printersperse ", " xs
    pprint "("
    pprint name
  pprint (Tuple e1 e2) = do
    pprint ")"
    pprint e2
    pprint ", "
    pprint e1
    pprint "("
  pprint _   = error "Cannot pprint unknown expression"

instance Pprint Field where
  pprint Hd  = pprint ".hd"
  pprint Tl  = pprint ".tl"
  pprint Fst = pprint ".fst"
  pprint Snd = pprint ".snd"
  pprint _   = error "Cannot pprint unknown field"

instance Pprint Op2 where
  pprint Add  = pprint "+"
  pprint Sub  = pprint "-"
  pprint Mul  = pprint "*"
  pprint Div  = pprint "/"
  pprint Mod  = pprint "%"
  pprint Eq   = pprint "=="
  pprint Lt   = pprint "<"
  pprint Gt   = pprint ">"
  pprint Le   = pprint "<="
  pprint Ge   = pprint ">="
  pprint Ne   = pprint "!="
  pprint And  = pprint "&&"
  pprint Or   = pprint "||"
  pprint Cons = pprint ":"
  pprint _    = error "Cannot pprint unknown binary operator"

instance Pprint Op1 where
  pprint Not = pprint "!"
  pprint Neg = pprint "-"
  pprint _   = error "Cannot pprint unknown unary operator"

instance Pprint Literal where
  pprint (LInt x)  = pprint $ show x
  pprint (LChar x) = pprint $ "'" ++ show x ++ "'"
  pprint (LBool x) = pprint $ show x
  pprint LNil      = pprint "[]"
  pprint _         = error "Cannot pprint unknown literal"

instance Pprint a => Pprint [a] where
  pprint = mapM_ pprint . reverse

printersperse :: (Pprint a, Pprint g) => g -> [a] -> Print
printersperse _ [] = pure ()
printersperse _ [x] = pprint x
printersperse g (x:xs) = do
  printersperse g xs
  pprint g
  pprint x

instance Pprint Char where
  pprint c = modify (\st -> st { result = (c : result st) })