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