LLVM: Use the inbounds keyword for getelementptr instructions.
[ghc-hetmet.git] / compiler / llvmGen / Llvm / PpLlvm.hs
1 --------------------------------------------------------------------------------
2 -- | Pretty print LLVM IR Code.
3 --
4
5 module Llvm.PpLlvm (
6
7     -- * Top level LLVM objects.
8     ppLlvmModule,
9     ppLlvmComments,
10     ppLlvmComment,
11     ppLlvmGlobals,
12     ppLlvmGlobal,
13     ppLlvmType,
14     ppLlvmTypes,
15     ppLlvmFunctionDecls,
16     ppLlvmFunctionDecl,
17     ppLlvmFunctions,
18     ppLlvmFunction,
19
20     -- * Utility functions
21     llvmSDoc
22
23     ) where
24
25 #include "HsVersions.h"
26
27 import Llvm.AbsSyn
28 import Llvm.Types
29
30 import Data.List ( intersperse )
31 import Pretty
32 import qualified Outputable as Out
33 import Unique
34
35 --------------------------------------------------------------------------------
36 -- * Top Level Print functions
37 --------------------------------------------------------------------------------
38
39 -- | Print out a whole LLVM module.
40 ppLlvmModule :: LlvmModule -> Doc
41 ppLlvmModule (LlvmModule comments globals decls funcs)
42   = ppLlvmComments comments
43     $+$ empty
44     $+$ ppLlvmGlobals globals
45     $+$ empty
46     $+$ ppLlvmFunctionDecls decls
47     $+$ empty
48     $+$ ppLlvmFunctions funcs
49
50 -- | Print out a multi-line comment, can be inside a function or on its own
51 ppLlvmComments :: [LMString] -> Doc
52 ppLlvmComments comments = vcat $ map ppLlvmComment comments
53
54 -- | Print out a comment, can be inside a function or on its own
55 ppLlvmComment :: LMString -> Doc
56 ppLlvmComment com = semi <+> ftext com
57
58
59 -- | Print out a list of global mutable variable definitions
60 ppLlvmGlobals :: [LMGlobal] -> Doc
61 ppLlvmGlobals ls = vcat $ map ppLlvmGlobal ls
62
63 -- | Print out a global mutable variable definition
64 ppLlvmGlobal :: LMGlobal -> Doc
65 ppLlvmGlobal (var@(LMGlobalVar _ _ link x a c), dat) =
66     let sect = case x of
67             Just x' -> text ", section" <+> doubleQuotes (ftext x')
68             Nothing -> empty
69
70         align = case a of
71             Just a' -> text ", align" <+> int a'
72             Nothing -> empty
73
74         rhs = case dat of
75             Just stat -> texts stat
76             Nothing   -> texts (pLower $ getVarType var)
77
78         const' = if c then text "constant" else text "global"
79
80     in ppAssignment var $ texts link <+> const' <+> rhs <> sect <> align
81
82 ppLlvmGlobal oth = error $ "Non Global var ppr as global! " ++ show oth
83
84
85 -- | Print out a list of LLVM type aliases.
86 ppLlvmTypes :: [LlvmType] -> Doc
87 ppLlvmTypes tys = vcat $ map ppLlvmType tys
88
89 -- | Print out an LLVM type alias.
90 ppLlvmType :: LlvmType -> Doc
91
92 ppLlvmType al@(LMAlias _ t)
93   = texts al <+> equals <+> text "type" <+> texts t
94
95 ppLlvmType (LMFunction t)
96   = ppLlvmFunctionDecl t
97
98 ppLlvmType _ = empty
99
100
101 -- | Print out a list of function definitions.
102 ppLlvmFunctions :: LlvmFunctions -> Doc
103 ppLlvmFunctions funcs = vcat $ map ppLlvmFunction funcs
104
105 -- | Print out a function definition.
106 ppLlvmFunction :: LlvmFunction -> Doc
107 ppLlvmFunction (LlvmFunction dec args attrs sec body) =
108     let attrDoc = ppSpaceJoin attrs
109         secDoc = case sec of
110                       Just s' -> text "section" <+> (doubleQuotes $ ftext s')
111                       Nothing -> empty
112     in text "define" <+> ppLlvmFunctionHeader dec args
113         <+> attrDoc <+> secDoc
114         $+$ lbrace
115         $+$ ppLlvmBlocks body
116         $+$ rbrace
117
118 -- | Print out a function defenition header.
119 ppLlvmFunctionHeader :: LlvmFunctionDecl -> [LMString] -> Doc
120 ppLlvmFunctionHeader (LlvmFunctionDecl n l c r varg p a) args
121   = let varg' = if varg == VarArgs then text ", ..." else empty
122         align = case a of
123                      Just a' -> space <> text "align" <+> texts a'
124                      Nothing -> empty
125         args' = map (\((ty,p),n) -> texts ty <+> ppSpaceJoin p <+> text "%"
126                                     <> ftext n)
127                     (zip p args)
128     in texts l <+> texts c <+> texts r <+> text "@" <> ftext n <> lparen <>
129         (hcat $ intersperse comma args') <> varg' <> rparen <> align
130
131
132 -- | Print out a list of function declaration.
133 ppLlvmFunctionDecls :: LlvmFunctionDecls -> Doc
134 ppLlvmFunctionDecls decs = vcat $ map ppLlvmFunctionDecl decs
135
136 -- | Print out a function declaration.
137 -- Declarations define the function type but don't define the actual body of
138 -- the function.
139 ppLlvmFunctionDecl :: LlvmFunctionDecl -> Doc
140 ppLlvmFunctionDecl dec = text "declare" <+> texts dec
141
142
143 -- | Print out a list of LLVM blocks.
144 ppLlvmBlocks :: LlvmBlocks -> Doc
145 ppLlvmBlocks blocks = vcat $ map ppLlvmBlock blocks
146
147 -- | Print out an LLVM block.
148 -- It must be part of a function definition.
149 ppLlvmBlock :: LlvmBlock -> Doc
150 ppLlvmBlock (LlvmBlock blockId stmts)
151   = ppLlvmStatement (MkLabel blockId)
152         $+$ nest 4 (vcat $ map ppLlvmStatement stmts)
153
154
155 -- | Print out an LLVM statement.
156 ppLlvmStatement :: LlvmStatement -> Doc
157 ppLlvmStatement stmt
158   = case stmt of
159         Assignment  dst expr      -> ppAssignment dst (ppLlvmExpression expr)
160         Branch      target        -> ppBranch target
161         BranchIf    cond ifT ifF  -> ppBranchIf cond ifT ifF
162         Comment     comments      -> ppLlvmComments comments
163         MkLabel     label         -> (llvmSDoc $ pprUnique label) <> colon
164         Store       value ptr     -> ppStore value ptr
165         Switch      scrut def tgs -> ppSwitch scrut def tgs
166         Return      result        -> ppReturn result
167         Expr        expr          -> ppLlvmExpression expr
168         Unreachable               -> text "unreachable"
169
170
171 -- | Print out an LLVM expression.
172 ppLlvmExpression :: LlvmExpression -> Doc
173 ppLlvmExpression expr
174   = case expr of
175         Alloca     tp amount        -> ppAlloca tp amount
176         LlvmOp     op left right    -> ppMachOp op left right
177         Call       tp fp args attrs -> ppCall tp fp args attrs
178         Cast       op from to       -> ppCast op from to
179         Compare    op left right    -> ppCmpOp op left right
180         GetElemPtr inb ptr indexes  -> ppGetElementPtr inb ptr indexes
181         Load       ptr              -> ppLoad ptr
182         Malloc     tp amount        -> ppMalloc tp amount
183         Phi        tp precessors    -> ppPhi tp precessors
184
185
186 --------------------------------------------------------------------------------
187 -- * Individual print functions
188 --------------------------------------------------------------------------------
189
190 -- | Should always be a function pointer. So a global var of function type
191 -- (since globals are always pointers) or a local var of pointer function type.
192 ppCall :: LlvmCallType -> LlvmVar -> [LlvmVar] -> [LlvmFuncAttr] -> Doc
193 ppCall ct fptr vals attrs = case fptr of
194                            --
195     -- if local var function pointer, unwrap
196     LMLocalVar _ (LMPointer (LMFunction d)) -> ppCall' d
197
198     -- should be function type otherwise
199     LMGlobalVar _ (LMFunction d) _ _ _ _    -> ppCall' d
200
201     -- not pointer or function, so error
202     _other -> error $ "ppCall called with non LMFunction type!\nMust be "
203                 ++ " called with either global var of function type or "
204                 ++ "local var of pointer function type."
205
206     where
207         ppCall' (LlvmFunctionDecl _ _ cc ret argTy params _) =
208             let tc = if ct == TailCall then text "tail " else empty
209                 ppValues = ppCommaJoin vals
210                 ppParams = map (\(ty,p) -> texts ty <+> ppSpaceJoin p) params
211                 ppArgTy  = (hcat $ intersperse comma ppParams) <>
212                            (case argTy of
213                                VarArgs   -> text ", ..."
214                                FixedArgs -> empty)
215                 fnty = space <> lparen <> ppArgTy <> rparen <> text "*"
216                 attrDoc = ppSpaceJoin attrs
217             in  tc <> text "call" <+> texts cc <+> texts ret
218                     <> fnty <+> (text $ getName fptr) <> lparen <+> ppValues
219                     <+> rparen <+> attrDoc
220
221
222 ppMachOp :: LlvmMachOp -> LlvmVar -> LlvmVar -> Doc
223 ppMachOp op left right =
224   (texts op) <+> (texts (getVarType left)) <+> (text $ getName left)
225         <> comma <+> (text $ getName right)
226
227
228 ppCmpOp :: LlvmCmpOp -> LlvmVar -> LlvmVar -> Doc
229 ppCmpOp op left right =
230   let cmpOp
231         | isInt (getVarType left) && isInt (getVarType right) = text "icmp"
232         | isFloat (getVarType left) && isFloat (getVarType right) = text "fcmp"
233         | otherwise = text "icmp" -- Just continue as its much easier to debug
234         {-
235         | otherwise = error ("can't compare different types, left = "
236                 ++ (show $ getVarType left) ++ ", right = "
237                 ++ (show $ getVarType right))
238         -}
239   in cmpOp <+> texts op <+> texts (getVarType left)
240         <+> (text $ getName left) <> comma <+> (text $ getName right)
241
242
243 ppAssignment :: LlvmVar -> Doc -> Doc
244 ppAssignment var expr = (text $ getName var) <+> equals <+> expr
245
246
247 ppLoad :: LlvmVar -> Doc
248 ppLoad var = text "load" <+> texts var
249
250
251 ppStore :: LlvmVar -> LlvmVar -> Doc
252 ppStore val dst = text "store" <+> texts val <> comma <+> texts dst
253
254
255 ppCast :: LlvmCastOp -> LlvmVar -> LlvmType -> Doc
256 ppCast op from to = texts op <+> texts from <+> text "to" <+> texts to
257
258
259 ppMalloc :: LlvmType -> Int -> Doc
260 ppMalloc tp amount =
261   let amount' = LMLitVar $ LMIntLit (toInteger amount) i32
262   in text "malloc" <+> texts tp <> comma <+> texts amount'
263
264
265 ppAlloca :: LlvmType -> Int -> Doc
266 ppAlloca tp amount =
267   let amount' = LMLitVar $ LMIntLit (toInteger amount) i32
268   in text "alloca" <+> texts tp <> comma <+> texts amount'
269
270
271 ppGetElementPtr :: Bool -> LlvmVar -> [Int] -> Doc
272 ppGetElementPtr inb ptr idx =
273   let indexes = hcat $ map ((comma <+> texts i32 <+>) . texts) idx
274       inbound = if inb then text "inbounds" else empty
275   in text "getelementptr" <+> inbound <+> texts ptr <> indexes
276
277
278 ppReturn :: Maybe LlvmVar -> Doc
279 ppReturn (Just var) = text "ret" <+> texts var
280 ppReturn Nothing    = text "ret" <+> texts LMVoid
281
282
283 ppBranch :: LlvmVar -> Doc
284 ppBranch var = text "br" <+> texts var
285
286
287 ppBranchIf :: LlvmVar -> LlvmVar -> LlvmVar -> Doc
288 ppBranchIf cond trueT falseT
289   = text "br" <+> texts cond <> comma <+> texts trueT <> comma <+> texts falseT
290
291
292 ppPhi :: LlvmType -> [(LlvmVar,LlvmVar)] -> Doc
293 ppPhi tp preds =
294   let ppPreds (val, label) = brackets $ (text $ getName val) <> comma
295         <+> (text $ getName label)
296   in text "phi" <+> texts tp <+> hcat (intersperse comma $ map ppPreds preds)
297
298
299 ppSwitch :: LlvmVar -> LlvmVar -> [(LlvmVar,LlvmVar)] -> Doc
300 ppSwitch scrut dflt targets =
301   let ppTarget  (val, lab) = texts val <> comma <+> texts lab
302       ppTargets  xs        = brackets $ vcat (map ppTarget xs)
303   in text "switch" <+> texts scrut <> comma <+> texts dflt
304         <+> ppTargets targets
305
306
307 --------------------------------------------------------------------------------
308 -- * Misc functions
309 --------------------------------------------------------------------------------
310 ppCommaJoin :: (Show a) => [a] -> Doc
311 ppCommaJoin strs = hcat $ intersperse comma (map texts strs)
312
313 ppSpaceJoin :: (Show a) => [a] -> Doc
314 ppSpaceJoin strs = hcat $ intersperse space (map texts strs)
315
316 -- | Convert SDoc to Doc
317 llvmSDoc :: Out.SDoc -> Doc
318 llvmSDoc d
319         = Out.withPprStyleDoc (Out.mkCodeStyle Out.CStyle) d
320
321 -- | Showable to Doc
322 texts :: (Show a) => a -> Doc
323 texts = (text . show)
324