Make dumpIfSet_dyn_or use dumpSDoc
[ghc-hetmet.git] / compiler / llvmGen / Llvm / Types.hs
1 --------------------------------------------------------------------------------
2 -- | The LLVM Type System.
3 --
4
5 module Llvm.Types where
6
7 #include "HsVersions.h"
8
9 import Data.Char
10 import Numeric
11
12 import Constants
13 import FastString
14 import Unique
15
16 -- from NCG
17 import PprBase
18
19 -- -----------------------------------------------------------------------------
20 -- * LLVM Basic Types and Variables
21 --
22
23 -- | A global mutable variable. Maybe defined or external
24 type LMGlobal = (LlvmVar, Maybe LlvmStatic)
25 -- | A String in LLVM
26 type LMString = FastString
27
28 -- | A type alias
29 type LlvmAlias = (LMString, LlvmType)
30
31 -- | Llvm Types
32 data LlvmType
33   = LMInt Int            -- ^ An integer with a given width in bits.
34   | LMFloat              -- ^ 32 bit floating point
35   | LMDouble             -- ^ 64 bit floating point
36   | LMFloat80            -- ^ 80 bit (x86 only) floating point
37   | LMFloat128           -- ^ 128 bit floating point
38   | LMPointer LlvmType   -- ^ A pointer to a 'LlvmType'
39   | LMArray Int LlvmType -- ^ An array of 'LlvmType'
40   | LMLabel              -- ^ A 'LlvmVar' can represent a label (address)
41   | LMVoid               -- ^ Void type
42   | LMStruct [LlvmType]  -- ^ Structure type
43   | LMAlias LlvmAlias    -- ^ A type alias
44
45   -- | Function type, used to create pointers to functions
46   | LMFunction LlvmFunctionDecl
47   deriving (Eq)
48
49 instance Show LlvmType where
50   show (LMInt size    ) = "i" ++ show size
51   show (LMFloat       ) = "float"
52   show (LMDouble      ) = "double"
53   show (LMFloat80     ) = "x86_fp80"
54   show (LMFloat128    ) = "fp128"
55   show (LMPointer x   ) = show x ++ "*"
56   show (LMArray nr tp ) = "[" ++ show nr ++ " x " ++ show tp ++ "]"
57   show (LMLabel       ) = "label"
58   show (LMVoid        ) = "void"
59   show (LMStruct tys  ) = "<{" ++ (commaCat tys) ++ "}>"
60
61   show (LMFunction (LlvmFunctionDecl _ _ _ r varg p _))
62     = let args = ((drop 1).concat) $ -- use drop since it can handle empty lists
63                   map (\(t,a) -> "," ++ show t ++ " " ++ spaceCat a) p
64           varg' = case varg of
65                         VarArgs | not (null args) -> ", ..."
66                                 | otherwise       -> "..."
67                         _otherwise                -> ""
68       in show r ++ " (" ++ args ++ varg' ++ ")"
69
70   show (LMAlias (s,_)) = "%" ++ unpackFS s
71
72 -- | An LLVM section definition. If Nothing then let LLVM decide the section
73 type LMSection = Maybe LMString
74 type LMAlign = Maybe Int
75 type LMConst = Bool -- ^ is a variable constant or not
76
77 -- | Llvm Variables
78 data LlvmVar
79   -- | Variables with a global scope.
80   = LMGlobalVar LMString LlvmType LlvmLinkageType LMSection LMAlign LMConst
81   -- | Variables local to a function or parameters.
82   | LMLocalVar Unique LlvmType
83   -- | Named local variables. Sometimes we need to be able to explicitly name
84   -- variables (e.g for function arguments).
85   | LMNLocalVar LMString LlvmType
86   -- | A constant variable
87   | LMLitVar LlvmLit
88   deriving (Eq)
89
90 instance Show LlvmVar where
91   show (LMLitVar x) = show x
92   show (x         ) = show (getVarType x) ++ " " ++ getName x
93
94
95 -- | Llvm Literal Data.
96 --
97 -- These can be used inline in expressions.
98 data LlvmLit
99   -- | Refers to an integer constant (i64 42).
100   = LMIntLit Integer LlvmType
101   -- | Floating point literal
102   | LMFloatLit Double LlvmType
103   -- | Literal NULL, only applicable to pointer types
104   | LMNullLit LlvmType
105   -- | Undefined value, random bit pattern. Useful for optimisations.
106   | LMUndefLit LlvmType
107   deriving (Eq)
108
109 instance Show LlvmLit where
110   show l = show (getLitType l) ++ " " ++ getLit l
111
112
113 -- | Llvm Static Data.
114 --
115 -- These represent the possible global level variables and constants.
116 data LlvmStatic
117   = LMComment LMString                  -- ^ A comment in a static section
118   | LMStaticLit LlvmLit                 -- ^ A static variant of a literal value
119   | LMUninitType LlvmType               -- ^ For uninitialised data
120   | LMStaticStr LMString LlvmType       -- ^ Defines a static 'LMString'
121   | LMStaticArray [LlvmStatic] LlvmType -- ^ A static array
122   | LMStaticStruc [LlvmStatic] LlvmType -- ^ A static structure type
123   | LMStaticPointer LlvmVar             -- ^ A pointer to other data
124
125   -- static expressions, could split out but leave
126   -- for moment for ease of use. Not many of them.
127
128   | LMBitc LlvmStatic LlvmType         -- ^ Pointer to Pointer conversion
129   | LMPtoI LlvmStatic LlvmType         -- ^ Pointer to Integer conversion
130   | LMAdd LlvmStatic LlvmStatic        -- ^ Constant addition operation
131   | LMSub LlvmStatic LlvmStatic        -- ^ Constant subtraction operation
132
133 instance Show LlvmStatic where
134   show (LMComment       s) = "; " ++ unpackFS s
135   show (LMStaticLit   l  ) = show l
136   show (LMUninitType    t) = show t ++ " undef"
137   show (LMStaticStr   s t) = show t ++ " c\"" ++ unpackFS s ++ "\\00\""
138
139   show (LMStaticArray d t)
140       = let struc = case d of
141               [] -> "[]"
142               ts -> "[" ++ show (head ts) ++
143                       concat (map (\x -> "," ++ show x) (tail ts)) ++ "]"
144         in show t ++ " " ++ struc
145
146   show (LMStaticStruc d t)
147       = let struc = case d of
148               [] -> "<{}>"
149               ts -> "<{" ++ show (head ts) ++
150                       concat (map (\x -> "," ++ show x) (tail ts)) ++ "}>"
151         in show t ++ " " ++ struc
152
153   show (LMStaticPointer v) = show v
154
155   show (LMBitc v t)
156       = show t ++ " bitcast (" ++ show v ++ " to " ++ show t ++ ")"
157
158   show (LMPtoI v t)
159       = show t ++ " ptrtoint (" ++ show v ++ " to " ++ show t ++ ")"
160
161   show (LMAdd s1 s2)
162       = let ty1 = getStatType s1
163             op  = if isFloat ty1 then " fadd (" else " add ("
164         in if ty1 == getStatType s2
165                 then show ty1 ++ op ++ show s1 ++ "," ++ show s2 ++ ")"
166                 else error $ "LMAdd with different types! s1: "
167                         ++ show s1 ++ ", s2: " ++ show s2
168   show (LMSub s1 s2)
169       = let ty1 = getStatType s1
170             op  = if isFloat ty1 then " fsub (" else " sub ("
171         in if ty1 == getStatType s2
172                 then show ty1 ++ op ++ show s1 ++ "," ++ show s2 ++ ")"
173                 else error $ "LMSub with different types! s1: "
174                         ++ show s1 ++ ", s2: " ++ show s2
175
176
177 -- | Concatenate an array together, separated by commas
178 commaCat :: Show a => [a] -> String
179 commaCat [] = ""
180 commaCat x  = show (head x) ++ (concat $ map (\y -> "," ++ show y) (tail x))
181
182 -- | Concatenate an array together, separated by commas
183 spaceCat :: Show a => [a] -> String
184 spaceCat [] = ""
185 spaceCat x  = show (head x) ++ (concat $ map (\y -> " " ++ show y) (tail x))
186
187 -- -----------------------------------------------------------------------------
188 -- ** Operations on LLVM Basic Types and Variables
189 --
190
191 -- | Return the variable name or value of the 'LlvmVar'
192 -- in Llvm IR textual representation (e.g. @\@x@, @%y@ or @42@).
193 getName :: LlvmVar -> String
194 getName v@(LMGlobalVar _ _ _ _ _ _) = "@" ++ getPlainName v
195 getName v@(LMLocalVar  _ _        ) = "%" ++ getPlainName v
196 getName v@(LMNLocalVar _ _        ) = "%" ++ getPlainName v
197 getName v@(LMLitVar    _          ) = getPlainName v
198
199 -- | Return the variable name or value of the 'LlvmVar'
200 -- in a plain textual representation (e.g. @x@, @y@ or @42@).
201 getPlainName :: LlvmVar -> String
202 getPlainName (LMGlobalVar x _ _ _ _ _) = unpackFS x
203 getPlainName (LMLocalVar  x LMLabel  ) = show x
204 getPlainName (LMLocalVar  x _        ) = "l" ++ show x
205 getPlainName (LMNLocalVar x _        ) = unpackFS x
206 getPlainName (LMLitVar    x          ) = getLit x
207
208 -- | Print a literal value. No type.
209 getLit :: LlvmLit -> String
210 getLit (LMIntLit   i _) = show ((fromInteger i)::Int)
211 getLit (LMFloatLit r LMFloat ) = fToStr $ realToFrac r
212 getLit (LMFloatLit r LMDouble) = dToStr r
213 getLit f@(LMFloatLit _ _) = error $ "Can't print this float literal!" ++ show f
214 getLit (LMNullLit _) = "null"
215 getLit (LMUndefLit _) = "undef"
216
217 -- | Return the 'LlvmType' of the 'LlvmVar'
218 getVarType :: LlvmVar -> LlvmType
219 getVarType (LMGlobalVar _ y _ _ _ _) = y
220 getVarType (LMLocalVar  _ y        ) = y
221 getVarType (LMNLocalVar _ y        ) = y
222 getVarType (LMLitVar    l          ) = getLitType l
223
224 -- | Return the 'LlvmType' of a 'LlvmLit'
225 getLitType :: LlvmLit -> LlvmType
226 getLitType (LMIntLit   _ t) = t
227 getLitType (LMFloatLit _ t) = t
228 getLitType (LMNullLit    t) = t
229 getLitType (LMUndefLit   t) = t
230
231 -- | Return the 'LlvmType' of the 'LlvmStatic'
232 getStatType :: LlvmStatic -> LlvmType
233 getStatType (LMStaticLit   l  ) = getLitType l
234 getStatType (LMUninitType    t) = t
235 getStatType (LMStaticStr   _ t) = t
236 getStatType (LMStaticArray _ t) = t
237 getStatType (LMStaticStruc _ t) = t
238 getStatType (LMStaticPointer v) = getVarType v
239 getStatType (LMBitc        _ t) = t
240 getStatType (LMPtoI        _ t) = t
241 getStatType (LMAdd         t _) = getStatType t
242 getStatType (LMSub         t _) = getStatType t
243 getStatType (LMComment       _) = error "Can't call getStatType on LMComment!"
244
245 -- | Return the 'LlvmType' of the 'LMGlobal'
246 getGlobalType :: LMGlobal -> LlvmType
247 getGlobalType (v, _) = getVarType v
248
249 -- | Return the 'LlvmVar' part of a 'LMGlobal'
250 getGlobalVar :: LMGlobal -> LlvmVar
251 getGlobalVar (v, _) = v
252
253 -- | Return the 'LlvmLinkageType' for a 'LlvmVar'
254 getLink :: LlvmVar -> LlvmLinkageType
255 getLink (LMGlobalVar _ _ l _ _ _) = l
256 getLink _                         = Internal
257
258 -- | Add a pointer indirection to the supplied type. 'LMLabel' and 'LMVoid'
259 -- cannot be lifted.
260 pLift :: LlvmType -> LlvmType
261 pLift (LMLabel) = error "Labels are unliftable"
262 pLift (LMVoid)  = error "Voids are unliftable"
263 pLift x         = LMPointer x
264
265 -- | Lower a variable of 'LMPointer' type.
266 pVarLift :: LlvmVar -> LlvmVar
267 pVarLift (LMGlobalVar s t l x a c) = LMGlobalVar s (pLift t) l x a c
268 pVarLift (LMLocalVar  s t        ) = LMLocalVar  s (pLift t)
269 pVarLift (LMNLocalVar s t        ) = LMNLocalVar s (pLift t)
270 pVarLift (LMLitVar    _          ) = error $ "Can't lower a literal type!"
271
272 -- | Remove the pointer indirection of the supplied type. Only 'LMPointer'
273 -- constructors can be lowered.
274 pLower :: LlvmType -> LlvmType
275 pLower (LMPointer x) = x
276 pLower x  = error $ show x ++ " is a unlowerable type, need a pointer"
277
278 -- | Lower a variable of 'LMPointer' type.
279 pVarLower :: LlvmVar -> LlvmVar
280 pVarLower (LMGlobalVar s t l x a c) = LMGlobalVar s (pLower t) l x a c
281 pVarLower (LMLocalVar  s t        ) = LMLocalVar  s (pLower t)
282 pVarLower (LMNLocalVar s t        ) = LMNLocalVar s (pLower t)
283 pVarLower (LMLitVar    _          ) = error $ "Can't lower a literal type!"
284
285 -- | Test if the given 'LlvmType' is an integer
286 isInt :: LlvmType -> Bool
287 isInt (LMInt _) = True
288 isInt _         = False
289
290 -- | Test if the given 'LlvmType' is a floating point type
291 isFloat :: LlvmType -> Bool
292 isFloat LMFloat    = True
293 isFloat LMDouble   = True
294 isFloat LMFloat80  = True
295 isFloat LMFloat128 = True
296 isFloat _          = False
297
298 -- | Test if the given 'LlvmType' is an 'LMPointer' construct
299 isPointer :: LlvmType -> Bool
300 isPointer (LMPointer _) = True
301 isPointer _             = False
302
303 -- | Test if a 'LlvmVar' is global.
304 isGlobal :: LlvmVar -> Bool
305 isGlobal (LMGlobalVar _ _ _ _ _ _) = True
306 isGlobal _                         = False
307
308 -- | Width in bits of an 'LlvmType', returns 0 if not applicable
309 llvmWidthInBits :: LlvmType -> Int
310 llvmWidthInBits (LMInt n)       = n
311 llvmWidthInBits (LMFloat)       = 32
312 llvmWidthInBits (LMDouble)      = 64
313 llvmWidthInBits (LMFloat80)     = 80
314 llvmWidthInBits (LMFloat128)    = 128
315 -- Could return either a pointer width here or the width of what
316 -- it points to. We will go with the former for now.
317 llvmWidthInBits (LMPointer _)   = llvmWidthInBits llvmWord
318 llvmWidthInBits (LMArray _ _)   = llvmWidthInBits llvmWord
319 llvmWidthInBits LMLabel         = 0
320 llvmWidthInBits LMVoid          = 0
321 llvmWidthInBits (LMStruct tys)  = sum $ map llvmWidthInBits tys
322 llvmWidthInBits (LMFunction  _) = 0
323 llvmWidthInBits (LMAlias (_,t)) = llvmWidthInBits t
324
325
326 -- -----------------------------------------------------------------------------
327 -- ** Shortcut for Common Types
328 --
329
330 i128, i64, i32, i16, i8, i1, i8Ptr :: LlvmType
331 i128  = LMInt 128
332 i64   = LMInt  64
333 i32   = LMInt  32
334 i16   = LMInt  16
335 i8    = LMInt   8
336 i1    = LMInt   1
337 i8Ptr = pLift i8
338
339 -- | The target architectures word size
340 llvmWord, llvmWordPtr :: LlvmType
341 llvmWord    = LMInt (wORD_SIZE * 8)
342 llvmWordPtr = pLift llvmWord
343
344 -- -----------------------------------------------------------------------------
345 -- * LLVM Function Types
346 --
347
348 -- | An LLVM Function
349 data LlvmFunctionDecl = LlvmFunctionDecl {
350         -- | Unique identifier of the function
351         decName       :: LMString,
352         -- | LinkageType of the function
353         funcLinkage   :: LlvmLinkageType,
354         -- | The calling convention of the function
355         funcCc        :: LlvmCallConvention,
356         -- | Type of the returned value
357         decReturnType :: LlvmType,
358         -- | Indicates if this function uses varargs
359         decVarargs    :: LlvmParameterListType,
360         -- | Parameter types and attributes
361         decParams     :: [LlvmParameter],
362         -- | Function align value, must be power of 2
363         funcAlign     :: LMAlign
364   }
365   deriving (Eq)
366
367 instance Show LlvmFunctionDecl where
368   show (LlvmFunctionDecl n l c r varg p a)
369     = let args = ((drop 1).concat) $ -- use drop since it can handle empty lists
370                   map (\(t,a) -> "," ++ show t ++ " " ++ spaceCat a) p
371           varg' = case varg of
372                         VarArgs | not (null args) -> ", ..."
373                                 | otherwise       -> "..."
374                         _otherwise                -> ""
375           align = case a of
376                        Just a' -> " align " ++ show a'
377                        Nothing -> ""
378       in show l ++ " " ++ show c ++ " " ++ show r ++ " @" ++ unpackFS n ++
379              "(" ++ args ++ varg' ++ ")" ++ align
380
381 type LlvmFunctionDecls = [LlvmFunctionDecl]
382
383 type LlvmParameter = (LlvmType, [LlvmParamAttr])
384
385 -- | LLVM Parameter Attributes.
386 --
387 -- Parameter attributes are used to communicate additional information about
388 -- the result or parameters of a function
389 data LlvmParamAttr
390   -- | This indicates to the code generator that the parameter or return value
391   -- should be zero-extended to a 32-bit value by the caller (for a parameter)
392   -- or the callee (for a return value).
393   = ZeroExt
394   -- | This indicates to the code generator that the parameter or return value
395   -- should be sign-extended to a 32-bit value by the caller (for a parameter)
396   -- or the callee (for a return value).
397   | SignExt
398   -- | This indicates that this parameter or return value should be treated in
399   -- a special target-dependent fashion during while emitting code for a
400   -- function call or return (usually, by putting it in a register as opposed
401   -- to memory).
402   | InReg
403   -- | This indicates that the pointer parameter should really be passed by
404   -- value to the function.
405   | ByVal
406   -- | This indicates that the pointer parameter specifies the address of a
407   -- structure that is the return value of the function in the source program.
408   | SRet
409   -- | This indicates that the pointer does not alias any global or any other
410   -- parameter.
411   | NoAlias
412   -- | This indicates that the callee does not make any copies of the pointer
413   -- that outlive the callee itself
414   | NoCapture
415   -- | This indicates that the pointer parameter can be excised using the
416   -- trampoline intrinsics.
417   | Nest
418   deriving (Eq)
419
420 instance Show LlvmParamAttr where
421   show ZeroExt   = "zeroext"
422   show SignExt   = "signext"
423   show InReg     = "inreg"
424   show ByVal     = "byval"
425   show SRet      = "sret"
426   show NoAlias   = "noalias"
427   show NoCapture = "nocapture"
428   show Nest      = "nest"
429
430 -- | Llvm Function Attributes.
431 --
432 -- Function attributes are set to communicate additional information about a
433 -- function. Function attributes are considered to be part of the function,
434 -- not of the function type, so functions with different parameter attributes
435 -- can have the same function type. Functions can have multiple attributes.
436 --
437 -- Descriptions taken from <http://llvm.org/docs/LangRef.html#fnattrs>
438 data LlvmFuncAttr
439   -- | This attribute indicates that the inliner should attempt to inline this
440   -- function into callers whenever possible, ignoring any active inlining
441   -- size threshold for this caller.
442   = AlwaysInline
443   -- | This attribute indicates that the source code contained a hint that
444   -- inlining this function is desirable (such as the \"inline\" keyword in
445   -- C/C++). It is just a hint; it imposes no requirements on the inliner.
446   | InlineHint
447   -- | This attribute indicates that the inliner should never inline this
448   -- function in any situation. This attribute may not be used together
449   -- with the alwaysinline attribute.
450   | NoInline
451   -- | This attribute suggests that optimization passes and code generator
452   -- passes make choices that keep the code size of this function low, and
453   -- otherwise do optimizations specifically to reduce code size.
454   | OptSize
455   -- | This function attribute indicates that the function never returns
456   -- normally. This produces undefined behavior at runtime if the function
457   -- ever does dynamically return.
458   | NoReturn
459   -- | This function attribute indicates that the function never returns with
460   -- an unwind or exceptional control flow. If the function does unwind, its
461   -- runtime behavior is undefined.
462   | NoUnwind
463   -- | This attribute indicates that the function computes its result (or
464   -- decides to unwind an exception) based strictly on its arguments, without
465   -- dereferencing any pointer arguments or otherwise accessing any mutable
466   -- state (e.g. memory, control registers, etc) visible to caller functions.
467   -- It does not write through any pointer arguments (including byval
468   -- arguments) and never changes any state visible to callers. This means
469   -- that it cannot unwind exceptions by calling the C++ exception throwing
470   -- methods, but could use the unwind instruction.
471   | ReadNone
472   -- | This attribute indicates that the function does not write through any
473   -- pointer arguments (including byval arguments) or otherwise modify any
474   -- state (e.g. memory, control registers, etc) visible to caller functions.
475   -- It may dereference pointer arguments and read state that may be set in
476   -- the caller. A readonly function always returns the same value (or unwinds
477   -- an exception identically) when called with the same set of arguments and
478   -- global state. It cannot unwind an exception by calling the C++ exception
479   -- throwing methods, but may use the unwind instruction.
480   | ReadOnly
481   -- | This attribute indicates that the function should emit a stack smashing
482   -- protector. It is in the form of a \"canary\"—a random value placed on the
483   -- stack before the local variables that's checked upon return from the
484   -- function to see if it has been overwritten. A heuristic is used to
485   -- determine if a function needs stack protectors or not.
486   --
487   -- If a function that has an ssp attribute is inlined into a function that
488   -- doesn't have an ssp attribute, then the resulting function will have an
489   -- ssp attribute.
490   | Ssp
491   -- | This attribute indicates that the function should always emit a stack
492   -- smashing protector. This overrides the ssp function attribute.
493   --
494   -- If a function that has an sspreq attribute is inlined into a function
495   -- that doesn't have an sspreq attribute or which has an ssp attribute,
496   -- then the resulting function will have an sspreq attribute.
497   | SspReq
498   -- | This attribute indicates that the code generator should not use a red
499   -- zone, even if the target-specific ABI normally permits it.
500   | NoRedZone
501   -- | This attributes disables implicit floating point instructions.
502   | NoImplicitFloat
503   -- | This attribute disables prologue / epilogue emission for the function.
504   -- This can have very system-specific consequences.
505   | Naked
506   deriving (Eq)
507
508 instance Show LlvmFuncAttr where
509   show AlwaysInline       = "alwaysinline"
510   show InlineHint         = "inlinehint"
511   show NoInline           = "noinline"
512   show OptSize            = "optsize"
513   show NoReturn           = "noreturn"
514   show NoUnwind           = "nounwind"
515   show ReadNone           = "readnon"
516   show ReadOnly           = "readonly"
517   show Ssp                = "ssp"
518   show SspReq             = "ssqreq"
519   show NoRedZone          = "noredzone"
520   show NoImplicitFloat    = "noimplicitfloat"
521   show Naked              = "naked"
522
523
524 -- | Different types to call a function.
525 data LlvmCallType
526   -- | Normal call, allocate a new stack frame.
527   = StdCall
528   -- | Tail call, perform the call in the current stack frame.
529   | TailCall
530   deriving (Eq,Show)
531
532 -- | Different calling conventions a function can use.
533 data LlvmCallConvention
534   -- | The C calling convention.
535   -- This calling convention (the default if no other calling convention is
536   -- specified) matches the target C calling conventions. This calling
537   -- convention supports varargs function calls and tolerates some mismatch in
538   -- the declared prototype and implemented declaration of the function (as
539   -- does normal C).
540   = CC_Ccc
541   -- | This calling convention attempts to make calls as fast as possible
542   -- (e.g. by passing things in registers). This calling convention allows
543   -- the target to use whatever tricks it wants to produce fast code for the
544   -- target, without having to conform to an externally specified ABI
545   -- (Application Binary Interface). Implementations of this convention should
546   -- allow arbitrary tail call optimization to be supported. This calling
547   -- convention does not support varargs and requires the prototype of al
548   -- callees to exactly match the prototype of the function definition.
549   | CC_Fastcc
550   -- | This calling convention attempts to make code in the caller as efficient
551   -- as possible under the assumption that the call is not commonly executed.
552   -- As such, these calls often preserve all registers so that the call does
553   -- not break any live ranges in the caller side. This calling convention
554   -- does not support varargs and requires the prototype of all callees to
555   -- exactly match the prototype of the function definition.
556   | CC_Coldcc
557   -- | Any calling convention may be specified by number, allowing
558   -- target-specific calling conventions to be used. Target specific calling
559   -- conventions start at 64.
560   | CC_Ncc Int
561   -- | X86 Specific 'StdCall' convention. LLVM includes a specific alias for it
562   -- rather than just using CC_Ncc.
563   | CC_X86_Stdcc
564   deriving (Eq)
565
566 instance Show LlvmCallConvention where
567   show CC_Ccc       = "ccc"
568   show CC_Fastcc    = "fastcc"
569   show CC_Coldcc    = "coldcc"
570   show (CC_Ncc i)   = "cc " ++ show i
571   show CC_X86_Stdcc = "x86_stdcallcc"
572
573
574 -- | Functions can have a fixed amount of parameters, or a variable amount.
575 data LlvmParameterListType
576   -- Fixed amount of arguments.
577   = FixedArgs
578   -- Variable amount of arguments.
579   | VarArgs
580   deriving (Eq,Show)
581
582
583 -- | Linkage type of a symbol.
584 --
585 -- The description of the constructors is copied from the Llvm Assembly Language
586 -- Reference Manual <http://www.llvm.org/docs/LangRef.html#linkage>, because
587 -- they correspond to the Llvm linkage types.
588 data LlvmLinkageType
589   -- | Global values with internal linkage are only directly accessible by
590   -- objects in the current module. In particular, linking code into a module
591   -- with an internal global value may cause the internal to be renamed as
592   -- necessary to avoid collisions. Because the symbol is internal to the
593   -- module, all references can be updated. This corresponds to the notion
594   -- of the @static@ keyword in C.
595   = Internal
596   -- | Globals with @linkonce@ linkage are merged with other globals of the
597   -- same name when linkage occurs. This is typically used to implement
598   -- inline functions, templates, or other code which must be generated
599   -- in each translation unit that uses it. Unreferenced linkonce globals are
600   -- allowed to be discarded.
601   | LinkOnce
602   -- | @weak@ linkage is exactly the same as linkonce linkage, except that
603   -- unreferenced weak globals may not be discarded. This is used for globals
604   -- that may be emitted in multiple translation units, but that are not
605   -- guaranteed to be emitted into every translation unit that uses them. One
606   -- example of this are common globals in C, such as @int X;@ at global
607   -- scope.
608   | Weak
609   -- | @appending@ linkage may only be applied to global variables of pointer
610   -- to array type. When two global variables with appending linkage are
611   -- linked together, the two global arrays are appended together. This is
612   -- the Llvm, typesafe, equivalent of having the system linker append
613   -- together @sections@ with identical names when .o files are linked.
614   | Appending
615   -- | The semantics of this linkage follow the ELF model: the symbol is weak
616   -- until linked, if not linked, the symbol becomes null instead of being an
617   -- undefined reference.
618   | ExternWeak
619   -- | The symbol participates in linkage and can be used to resolve external
620   --  symbol references.
621   | ExternallyVisible
622   -- | Alias for 'ExternallyVisible' but with explicit textual form in LLVM
623   --  assembly.
624   | External
625   deriving (Eq)
626
627 instance Show LlvmLinkageType where
628   show Internal          = "internal"
629   show LinkOnce          = "linkonce"
630   show Weak              = "weak"
631   show Appending         = "appending"
632   show ExternWeak        = "extern_weak"
633   -- ExternallyVisible does not have a textual representation, it is
634   -- the linkage type a function resolves to if no other is specified
635   -- in Llvm.
636   show ExternallyVisible = ""
637   show External          = "external"
638
639
640 -- -----------------------------------------------------------------------------
641 -- * LLVM Operations
642 --
643
644 -- | Llvm binary operators machine operations.
645 data LlvmMachOp
646   = LM_MO_Add  -- ^ add two integer, floating point or vector values.
647   | LM_MO_Sub  -- ^ subtract two ...
648   | LM_MO_Mul  -- ^ multiply ..
649   | LM_MO_UDiv -- ^ unsigned integer or vector division.
650   | LM_MO_SDiv -- ^ signed integer ..
651   | LM_MO_URem -- ^ unsigned integer or vector remainder (mod)
652   | LM_MO_SRem -- ^ signed ...
653
654   | LM_MO_FAdd -- ^ add two floating point or vector values.
655   | LM_MO_FSub -- ^ subtract two ...
656   | LM_MO_FMul -- ^ multiply ...
657   | LM_MO_FDiv -- ^ divide ...
658   | LM_MO_FRem -- ^ remainder ...
659
660   -- | Left shift
661   | LM_MO_Shl
662   -- | Logical shift right
663   -- Shift right, filling with zero
664   | LM_MO_LShr
665   -- | Arithmetic shift right
666   -- The most significant bits of the result will be equal to the sign bit of
667   -- the left operand.
668   | LM_MO_AShr
669
670   | LM_MO_And -- ^ AND bitwise logical operation.
671   | LM_MO_Or  -- ^ OR bitwise logical operation.
672   | LM_MO_Xor -- ^ XOR bitwise logical operation.
673   deriving (Eq)
674
675 instance Show LlvmMachOp where
676   show LM_MO_Add  = "add"
677   show LM_MO_Sub  = "sub"
678   show LM_MO_Mul  = "mul"
679   show LM_MO_UDiv = "udiv"
680   show LM_MO_SDiv = "sdiv"
681   show LM_MO_URem = "urem"
682   show LM_MO_SRem = "srem"
683   show LM_MO_FAdd = "fadd"
684   show LM_MO_FSub = "fsub"
685   show LM_MO_FMul = "fmul"
686   show LM_MO_FDiv = "fdiv"
687   show LM_MO_FRem = "frem"
688   show LM_MO_Shl  = "shl"
689   show LM_MO_LShr = "lshr"
690   show LM_MO_AShr = "ashr"
691   show LM_MO_And  = "and"
692   show LM_MO_Or   = "or"
693   show LM_MO_Xor  = "xor"
694
695
696 -- | Llvm compare operations.
697 data LlvmCmpOp
698   = LM_CMP_Eq  -- ^ Equal (Signed and Unsigned)
699   | LM_CMP_Ne  -- ^ Not equal (Signed and Unsigned)
700   | LM_CMP_Ugt -- ^ Unsigned greater than
701   | LM_CMP_Uge -- ^ Unsigned greater than or equal
702   | LM_CMP_Ult -- ^ Unsigned less than
703   | LM_CMP_Ule -- ^ Unsigned less than or equal
704   | LM_CMP_Sgt -- ^ Signed greater than
705   | LM_CMP_Sge -- ^ Signed greater than or equal
706   | LM_CMP_Slt -- ^ Signed less than
707   | LM_CMP_Sle -- ^ Signed less than or equal
708
709   -- Float comparisons. GHC uses a mix of ordered and unordered float
710   -- comparisons.
711   | LM_CMP_Feq -- ^ Float equal
712   | LM_CMP_Fne -- ^ Float not equal
713   | LM_CMP_Fgt -- ^ Float greater than
714   | LM_CMP_Fge -- ^ Float greater than or equal
715   | LM_CMP_Flt -- ^ Float less than
716   | LM_CMP_Fle -- ^ Float less than or equal
717   deriving (Eq)
718
719 instance Show LlvmCmpOp where
720   show LM_CMP_Eq  = "eq"
721   show LM_CMP_Ne  = "ne"
722   show LM_CMP_Ugt = "ugt"
723   show LM_CMP_Uge = "uge"
724   show LM_CMP_Ult = "ult"
725   show LM_CMP_Ule = "ule"
726   show LM_CMP_Sgt = "sgt"
727   show LM_CMP_Sge = "sge"
728   show LM_CMP_Slt = "slt"
729   show LM_CMP_Sle = "sle"
730   show LM_CMP_Feq = "oeq"
731   show LM_CMP_Fne = "une"
732   show LM_CMP_Fgt = "ogt"
733   show LM_CMP_Fge = "oge"
734   show LM_CMP_Flt = "olt"
735   show LM_CMP_Fle = "ole"
736
737
738 -- | Llvm cast operations.
739 data LlvmCastOp
740   = LM_Trunc    -- ^ Integer truncate
741   | LM_Zext     -- ^ Integer extend (zero fill)
742   | LM_Sext     -- ^ Integer extend (sign fill)
743   | LM_Fptrunc  -- ^ Float truncate
744   | LM_Fpext    -- ^ Float extend
745   | LM_Fptoui   -- ^ Float to unsigned Integer
746   | LM_Fptosi   -- ^ Float to signed Integer
747   | LM_Uitofp   -- ^ Unsigned Integer to Float
748   | LM_Sitofp   -- ^ Signed Int to Float
749   | LM_Ptrtoint -- ^ Pointer to Integer
750   | LM_Inttoptr -- ^ Integer to Pointer
751   | LM_Bitcast  -- ^ Cast between types where no bit manipulation is needed
752   deriving (Eq)
753
754 instance Show LlvmCastOp where
755   show LM_Trunc    = "trunc"
756   show LM_Zext     = "zext"
757   show LM_Sext     = "sext"
758   show LM_Fptrunc  = "fptrunc"
759   show LM_Fpext    = "fpext"
760   show LM_Fptoui   = "fptoui"
761   show LM_Fptosi   = "fptosi"
762   show LM_Uitofp   = "uitofp"
763   show LM_Sitofp   = "sitofp"
764   show LM_Ptrtoint = "ptrtoint"
765   show LM_Inttoptr = "inttoptr"
766   show LM_Bitcast  = "bitcast"
767
768
769 -- -----------------------------------------------------------------------------
770 -- * Floating point conversion
771 --
772
773 -- | Convert a Haskell Double to an LLVM hex encoded floating point form. In
774 -- Llvm float literals can be printed in a big-endian hexadecimal format,
775 -- regardless of underlying architecture.
776 dToStr :: Double -> String
777 dToStr d
778   = let bs     = doubleToBytes d
779         hex d' = case showHex d' "" of
780                      []    -> error "dToStr: too few hex digits for float"
781                      [x]   -> ['0',x]
782                      [x,y] -> [x,y]
783                      _     -> error "dToStr: too many hex digits for float"
784
785         str  = map toUpper $ concat . fixEndian . (map hex) $ bs
786     in  "0x" ++ str
787
788 -- | Convert a Haskell Float to an LLVM hex encoded floating point form.
789 -- LLVM uses the same encoding for both floats and doubles (16 digit hex
790 -- string) but floats must have the last half all zeroes so it can fit into
791 -- a float size type.
792 {-# NOINLINE fToStr #-}
793 fToStr :: Float -> String
794 fToStr = (dToStr . realToFrac)
795
796 -- | Reverse or leave byte data alone to fix endianness on this target.
797 fixEndian :: [a] -> [a]
798 #ifdef WORDS_BIGENDIAN
799 fixEndian = id
800 #else
801 fixEndian = reverse
802 #endif
803