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