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