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