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