Don't import FastString in HsVersions.h
[ghc-hetmet.git] / compiler / cmm / MachOp.hs
1 {-# OPTIONS -w #-}
2 -- The above warning supression flag is a temporary kludge.
3 -- While working on this module you are encouraged to remove it and fix
4 -- any warnings in the module. See
5 --     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
6 -- for details
7
8 -----------------------------------------------------------------------------
9 --
10 -- (c) The University of Glasgow 2002-2006
11 --
12 -- Low-level machine operations, used in the Cmm datatype.
13 --
14 -----------------------------------------------------------------------------
15
16 module MachOp   ( 
17         MachRep(..), 
18         machRepBitWidth,
19         machRepByteWidth,
20         machRepLogWidth,
21         isFloatingRep,
22
23         MachHint(..),
24
25         MachOp(..), 
26         pprMachOp,
27         isCommutableMachOp,
28         isAssociativeMachOp,
29         isComparisonMachOp,
30         resultRepOfMachOp,
31         machOpArgReps,
32         maybeInvertComparison,
33
34         CallishMachOp(..),
35         pprCallishMachOp,
36
37         wordRep,
38         halfWordRep,
39         cIntRep, cLongRep,
40
41         mo_wordAdd,
42         mo_wordSub,
43         mo_wordEq,
44         mo_wordNe,
45         mo_wordMul,
46         mo_wordSQuot,
47         mo_wordSRem,
48         mo_wordSNeg,
49         mo_wordUQuot,
50         mo_wordURem,
51
52         mo_wordSGe,
53         mo_wordSLe,
54         mo_wordSGt,
55         mo_wordSLt,
56
57         mo_wordUGe,
58         mo_wordULe,
59         mo_wordUGt,
60         mo_wordULt,
61
62         mo_wordAnd,
63         mo_wordOr,
64         mo_wordXor,
65         mo_wordNot,
66         mo_wordShl,
67         mo_wordSShr,
68         mo_wordUShr,
69
70         mo_u_8To32,
71         mo_s_8To32,
72         mo_u_16To32,
73         mo_s_16To32,
74
75         mo_u_8ToWord,
76         mo_s_8ToWord,
77         mo_u_16ToWord,
78         mo_s_16ToWord,
79         mo_u_32ToWord,
80         mo_s_32ToWord,
81
82         mo_32To8,
83         mo_32To16,
84         mo_WordTo8,
85         mo_WordTo16,
86         mo_WordTo32,
87   ) where
88
89 #include "HsVersions.h"
90
91 import Constants
92 import Outputable
93 import FastString
94
95 -- -----------------------------------------------------------------------------
96 -- MachRep
97
98 {- |
99 A MachRep is the "representation" of a value in Cmm.  It is used for
100 resource allocation: eg. which kind of register a value should be
101 stored in.  
102
103 The primary requirement is that there exists a function
104
105   cmmExprRep :: CmmExpr -> MachRep
106
107 This means that:
108
109   - a register has an implicit MachRep
110   - a literal has an implicit MachRep
111   - an operation (MachOp) has an implicit result MachRep
112
113 It also means that we can check that the arguments to a MachOp have
114 the correct MachRep, i.e. we can do a kind of lint-style type checking
115 on Cmm.
116 -}
117
118 data MachRep
119   = I8
120   | I16
121   | I32
122   | I64
123   | I128
124   | F32
125   | F64
126   | F80         -- extended double-precision, used in x86 native codegen only.
127   deriving (Eq, Ord, Show)
128
129 mrStr I8   = SLIT("I8")
130 mrStr I16  = SLIT("I16")
131 mrStr I32  = SLIT("I32")
132 mrStr I64  = SLIT("I64")
133 mrStr I128 = SLIT("I128")
134 mrStr F32  = SLIT("F32")
135 mrStr F64  = SLIT("F64")
136 mrStr F80  = SLIT("F80")
137
138 instance Outputable MachRep where
139    ppr rep = ptext (mrStr rep)
140
141 {- 
142 Implementation notes:
143
144 It might suffice to keep just a width, without distinguishing between
145 floating and integer types.  However, keeping the distinction will
146 help the native code generator to assign registers more easily.
147 -}
148
149 {-
150 Should a MachRep include a signed vs. unsigned distinction?
151
152 This is very much like a "hint" in C-- terminology: it isn't necessary
153 in order to generate correct code, but it might be useful in that the
154 compiler can generate better code if it has access to higher-level
155 hints about data.  This is important at call boundaries, because the
156 definition of a function is not visible at all of its call sites, so
157 the compiler cannot infer the hints.
158
159 Here in Cmm, we're taking a slightly different approach.  We include
160 the int vs. float hint in the MachRep, because (a) the majority of
161 platforms have a strong distinction between float and int registers,
162 and (b) we don't want to do any heavyweight hint-inference in the
163 native code backend in order to get good code.  We're treating the
164 hint more like a type: our Cmm is always completely consistent with
165 respect to hints.  All coercions between float and int are explicit.
166
167 What about the signed vs. unsigned hint?  This information might be
168 useful if we want to keep sub-word-sized values in word-size
169 registers, which we must do if we only have word-sized registers.
170
171 On such a system, there are two straightforward conventions for
172 representing sub-word-sized values:
173
174 (a) Leave the upper bits undefined.  Comparison operations must
175     sign- or zero-extend both operands before comparing them,
176     depending on whether the comparison is signed or unsigned.
177
178 (b) Always keep the values sign- or zero-extended as appropriate.
179     Arithmetic operations must narrow the result to the appropriate
180     size.
181
182 A clever compiler might not use either (a) or (b) exclusively, instead
183 it would attempt to minimize the coercions by analysis: the same kind
184 of analysis that propagates hints around.  In Cmm we don't want to
185 have to do this, so we plump for having richer types and keeping the
186 type information consistent.
187
188 If signed/unsigned hints are missing from MachRep, then the only
189 choice we have is (a), because we don't know whether the result of an
190 operation should be sign- or zero-extended.
191
192 Many architectures have extending load operations, which work well
193 with (b).  To make use of them with (a), you need to know whether the
194 value is going to be sign- or zero-extended by an enclosing comparison
195 (for example), which involves knowing above the context.  This is
196 doable but more complex.
197
198 Further complicating the issue is foreign calls: a foreign calling
199 convention can specify that signed 8-bit quantities are passed as
200 sign-extended 32 bit quantities, for example (this is the case on the
201 PowerPC).  So we *do* need sign information on foreign call arguments.
202
203 Pros for adding signed vs. unsigned to MachRep:
204
205   - It would let us use convention (b) above, and get easier
206     code generation for extending loads.
207
208   - Less information required on foreign calls.
209   
210   - MachOp type would be simpler
211
212 Cons:
213
214   - More complexity
215
216   - What is the MachRep for a VanillaReg?  Currently it is
217     always wordRep, but now we have to decide whether it is
218     signed or unsigned.  The same VanillaReg can thus have
219     different MachReps in different parts of the program.
220
221   - Extra coercions cluttering up expressions.
222
223 Currently for GHC, the foreign call point is moot, because we do our
224 own promotion of sub-word-sized values to word-sized values.  The Int8
225 type is represnted by an Int# which is kept sign-extended at all times
226 (this is slightly naughty, because we're making assumptions about the
227 C calling convention rather early on in the compiler).  However, given
228 this, the cons outweigh the pros.
229
230 -}
231
232
233 machRepBitWidth :: MachRep -> Int
234 machRepBitWidth I8   = 8
235 machRepBitWidth I16  = 16
236 machRepBitWidth I32  = 32
237 machRepBitWidth I64  = 64
238 machRepBitWidth I128 = 128
239 machRepBitWidth F32  = 32
240 machRepBitWidth F64  = 64
241 machRepBitWidth F80  = 80
242
243 machRepByteWidth :: MachRep -> Int
244 machRepByteWidth I8   = 1
245 machRepByteWidth I16  = 2
246 machRepByteWidth I32  = 4
247 machRepByteWidth I64  = 8
248 machRepByteWidth I128 = 16
249 machRepByteWidth F32  = 4
250 machRepByteWidth F64  = 8
251 machRepByteWidth F80  = 10
252
253 -- log_2 of the width in bytes, useful for generating shifts.
254 machRepLogWidth :: MachRep -> Int
255 machRepLogWidth I8   = 0
256 machRepLogWidth I16  = 1
257 machRepLogWidth I32  = 2
258 machRepLogWidth I64  = 3
259 machRepLogWidth I128 = 4
260 machRepLogWidth F32  = 2
261 machRepLogWidth F64  = 3
262 machRepLogWidth F80  = panic "machRepLogWidth: F80"
263
264 isFloatingRep :: MachRep -> Bool
265 isFloatingRep F32 = True
266 isFloatingRep F64 = True
267 isFloatingRep F80 = True
268 isFloatingRep _   = False
269
270 -- -----------------------------------------------------------------------------
271 -- Hints
272
273 {-
274 A hint gives a little more information about a data value.  Hints are
275 used on the arguments to a foreign call, where the code generator needs
276 to know some extra information on top of the MachRep of each argument in
277 order to generate a correct call.
278 -}
279
280 data MachHint
281   = NoHint
282   | PtrHint
283   | SignedHint
284   | FloatHint
285   deriving Eq
286
287 mhStr NoHint     = SLIT("NoHint")
288 mhStr PtrHint    = SLIT("PtrHint")
289 mhStr SignedHint = SLIT("SignedHint")
290 mhStr FloatHint  = SLIT("FloatHint")
291
292 instance Outputable MachHint where
293    ppr hint = ptext (mhStr hint)
294
295 -- -----------------------------------------------------------------------------
296 -- MachOp
297
298 {- |
299 Machine-level primops; ones which we can reasonably delegate to the
300 native code generators to handle.  Basically contains C's primops
301 and no others.
302
303 Nomenclature: all ops indicate width and signedness, where
304 appropriate.  Widths: 8\/16\/32\/64 means the given size, obviously.
305 Nat means the operation works on STG word sized objects.
306 Signedness: S means signed, U means unsigned.  For operations where
307 signedness is irrelevant or makes no difference (for example
308 integer add), the signedness component is omitted.
309
310 An exception: NatP is a ptr-typed native word.  From the point of
311 view of the native code generators this distinction is irrelevant,
312 but the C code generator sometimes needs this info to emit the
313 right casts.  
314 -}
315
316 data MachOp
317
318   -- Integer operations
319   = MO_Add    MachRep
320   | MO_Sub    MachRep
321   | MO_Eq     MachRep
322   | MO_Ne     MachRep
323   | MO_Mul    MachRep           -- low word of multiply
324   | MO_S_MulMayOflo MachRep     -- nonzero if signed multiply overflows
325   | MO_S_Quot MachRep           -- signed / (same semantics as IntQuotOp)
326   | MO_S_Rem  MachRep           -- signed % (same semantics as IntRemOp)
327   | MO_S_Neg  MachRep           -- unary -
328   | MO_U_MulMayOflo MachRep     -- nonzero if unsigned multiply overflows
329   | MO_U_Quot MachRep           -- unsigned / (same semantics as WordQuotOp)
330   | MO_U_Rem  MachRep           -- unsigned % (same semantics as WordRemOp)
331
332   -- Signed comparisons (floating-point comparisons also use these)
333   | MO_S_Ge MachRep
334   | MO_S_Le MachRep
335   | MO_S_Gt MachRep
336   | MO_S_Lt MachRep
337
338   -- Unsigned comparisons
339   | MO_U_Ge MachRep
340   | MO_U_Le MachRep
341   | MO_U_Gt MachRep
342   | MO_U_Lt MachRep
343
344   -- Bitwise operations.  Not all of these may be supported at all sizes,
345   -- and only integral MachReps are valid.
346   | MO_And   MachRep
347   | MO_Or    MachRep
348   | MO_Xor   MachRep
349   | MO_Not   MachRep
350   | MO_Shl   MachRep
351   | MO_U_Shr MachRep    -- unsigned shift right
352   | MO_S_Shr MachRep    -- signed shift right
353
354   -- Conversions.  Some of these will be NOPs.
355   -- Floating-point conversions use the signed variant.
356   | MO_S_Conv MachRep{-from-} MachRep{-to-}     -- signed conversion
357   | MO_U_Conv MachRep{-from-} MachRep{-to-}     -- unsigned conversion
358
359   deriving (Eq, Show)
360
361 pprMachOp :: MachOp -> SDoc
362 pprMachOp mo = text (show mo)
363
364
365 -- These MachOps tend to be implemented by foreign calls in some backends,
366 -- so we separate them out.  In Cmm, these can only occur in a
367 -- statement position, in contrast to an ordinary MachOp which can occur
368 -- anywhere in an expression.
369 data CallishMachOp
370   = MO_F64_Pwr
371   | MO_F64_Sin
372   | MO_F64_Cos
373   | MO_F64_Tan
374   | MO_F64_Sinh
375   | MO_F64_Cosh
376   | MO_F64_Tanh
377   | MO_F64_Asin
378   | MO_F64_Acos
379   | MO_F64_Atan
380   | MO_F64_Log
381   | MO_F64_Exp
382   | MO_F64_Sqrt
383   | MO_F32_Pwr
384   | MO_F32_Sin
385   | MO_F32_Cos
386   | MO_F32_Tan
387   | MO_F32_Sinh
388   | MO_F32_Cosh
389   | MO_F32_Tanh
390   | MO_F32_Asin
391   | MO_F32_Acos
392   | MO_F32_Atan
393   | MO_F32_Log
394   | MO_F32_Exp
395   | MO_F32_Sqrt
396   | MO_WriteBarrier
397   deriving (Eq, Show)
398
399 pprCallishMachOp :: CallishMachOp -> SDoc
400 pprCallishMachOp mo = text (show mo)
401
402 -- -----------------------------------------------------------------------------
403 -- Some common MachReps
404
405 -- A 'wordRep' is a machine word on the target architecture
406 -- Specifically, it is the size of an Int#, Word#, Addr# 
407 -- and the unit of allocation on the stack and the heap
408 -- Any pointer is also guaranteed to be a wordRep.
409
410 wordRep | wORD_SIZE == 4 = I32
411         | wORD_SIZE == 8 = I64
412         | otherwise      = panic "MachOp.wordRep: Unknown word size"
413
414 halfWordRep | wORD_SIZE == 4 = I16
415             | wORD_SIZE == 8 = I32
416             | otherwise      = panic "MachOp.halfWordRep: Unknown word size"
417
418 mo_wordAdd      = MO_Add wordRep
419 mo_wordSub      = MO_Sub wordRep
420 mo_wordEq       = MO_Eq  wordRep
421 mo_wordNe       = MO_Ne  wordRep
422 mo_wordMul      = MO_Mul wordRep
423 mo_wordSQuot    = MO_S_Quot wordRep
424 mo_wordSRem     = MO_S_Rem wordRep
425 mo_wordSNeg     = MO_S_Neg wordRep
426 mo_wordUQuot    = MO_U_Quot wordRep
427 mo_wordURem     = MO_U_Rem wordRep
428
429 mo_wordSGe      = MO_S_Ge  wordRep
430 mo_wordSLe      = MO_S_Le  wordRep
431 mo_wordSGt      = MO_S_Gt  wordRep
432 mo_wordSLt      = MO_S_Lt  wordRep
433
434 mo_wordUGe      = MO_U_Ge  wordRep
435 mo_wordULe      = MO_U_Le  wordRep
436 mo_wordUGt      = MO_U_Gt  wordRep
437 mo_wordULt      = MO_U_Lt  wordRep
438
439 mo_wordAnd      = MO_And wordRep
440 mo_wordOr       = MO_Or  wordRep
441 mo_wordXor      = MO_Xor wordRep
442 mo_wordNot      = MO_Not wordRep
443 mo_wordShl      = MO_Shl wordRep
444 mo_wordSShr     = MO_S_Shr wordRep 
445 mo_wordUShr     = MO_U_Shr wordRep 
446
447 mo_u_8To32      = MO_U_Conv I8 I32
448 mo_s_8To32      = MO_S_Conv I8 I32
449 mo_u_16To32     = MO_U_Conv I16 I32
450 mo_s_16To32     = MO_S_Conv I16 I32
451
452 mo_u_8ToWord    = MO_U_Conv I8  wordRep
453 mo_s_8ToWord    = MO_S_Conv I8  wordRep
454 mo_u_16ToWord   = MO_U_Conv I16 wordRep
455 mo_s_16ToWord   = MO_S_Conv I16 wordRep
456 mo_s_32ToWord   = MO_S_Conv I32 wordRep
457 mo_u_32ToWord   = MO_U_Conv I32 wordRep
458
459 mo_WordTo8      = MO_U_Conv wordRep I8
460 mo_WordTo16     = MO_U_Conv wordRep I16
461 mo_WordTo32     = MO_U_Conv wordRep I32
462
463 mo_32To8        = MO_U_Conv I32 I8
464 mo_32To16       = MO_U_Conv I32 I16
465
466 -- cIntRep is the MachRep for a C-language 'int'
467 #if SIZEOF_INT == 4
468 cIntRep = I32
469 #elif  SIZEOF_INT == 8
470 cIntRep = I64
471 #endif
472
473 #if SIZEOF_LONG == 4
474 cLongRep = I32
475 #elif  SIZEOF_LONG == 8
476 cLongRep = I64
477 #endif
478
479 -- ----------------------------------------------------------------------------
480 -- isCommutableMachOp
481
482 {- |
483 Returns 'True' if the MachOp has commutable arguments.  This is used
484 in the platform-independent Cmm optimisations.
485
486 If in doubt, return 'False'.  This generates worse code on the
487 native routes, but is otherwise harmless.
488 -}
489 isCommutableMachOp :: MachOp -> Bool
490 isCommutableMachOp mop = 
491   case mop of
492         MO_Add _                -> True
493         MO_Eq _                 -> True
494         MO_Ne _                 -> True
495         MO_Mul _                -> True
496         MO_S_MulMayOflo _       -> True
497         MO_U_MulMayOflo _       -> True
498         MO_And _                -> True
499         MO_Or _                 -> True
500         MO_Xor _                -> True
501         _other                  -> False
502
503 -- ----------------------------------------------------------------------------
504 -- isAssociativeMachOp
505
506 {- |
507 Returns 'True' if the MachOp is associative (i.e. @(x+y)+z == x+(y+z)@)
508 This is used in the platform-independent Cmm optimisations.
509
510 If in doubt, return 'False'.  This generates worse code on the
511 native routes, but is otherwise harmless.
512 -}
513 isAssociativeMachOp :: MachOp -> Bool
514 isAssociativeMachOp mop = 
515   case mop of
516         MO_Add r        -> not (isFloatingRep r)
517         MO_Mul r        -> not (isFloatingRep r)
518         MO_And _        -> True
519         MO_Or _         -> True
520         MO_Xor _        -> True
521         _other          -> False
522
523 -- ----------------------------------------------------------------------------
524 -- isComparisonMachOp
525
526 {- | 
527 Returns 'True' if the MachOp is a comparison.
528
529 If in doubt, return False.  This generates worse code on the
530 native routes, but is otherwise harmless.
531 -}
532 isComparisonMachOp :: MachOp -> Bool
533 isComparisonMachOp mop = 
534   case mop of
535     MO_Eq   _  -> True
536     MO_Ne   _  -> True
537     MO_S_Ge _  -> True
538     MO_S_Le _  -> True
539     MO_S_Gt _  -> True
540     MO_S_Lt _  -> True
541     MO_U_Ge _  -> True
542     MO_U_Le _  -> True
543     MO_U_Gt _  -> True
544     MO_U_Lt _  -> True
545     _other     -> False
546
547 -- -----------------------------------------------------------------------------
548 -- Inverting conditions
549
550 -- Sometimes it's useful to be able to invert the sense of a
551 -- condition.  Not all conditional tests are invertible: in
552 -- particular, floating point conditionals cannot be inverted, because
553 -- there exist floating-point values which return False for both senses
554 -- of a condition (eg. !(NaN > NaN) && !(NaN /<= NaN)).
555
556 maybeInvertComparison :: MachOp -> Maybe MachOp
557 maybeInvertComparison op
558   = case op of
559         MO_Eq r    | not (isFloatingRep r) -> Just (MO_Ne r)
560         MO_Ne r    | not (isFloatingRep r) -> Just (MO_Eq r)
561         MO_U_Lt r  | not (isFloatingRep r) -> Just (MO_U_Ge r)
562         MO_U_Gt r  | not (isFloatingRep r) -> Just (MO_U_Le r)
563         MO_U_Le r  | not (isFloatingRep r) -> Just (MO_U_Gt r)
564         MO_U_Ge r  | not (isFloatingRep r) -> Just (MO_U_Lt r)
565         MO_S_Lt r  | not (isFloatingRep r) -> Just (MO_S_Ge r)
566         MO_S_Gt r  | not (isFloatingRep r) -> Just (MO_S_Le r)
567         MO_S_Le r  | not (isFloatingRep r) -> Just (MO_S_Gt r)
568         MO_S_Ge r  | not (isFloatingRep r) -> Just (MO_S_Lt r)
569         _other  -> Nothing
570
571 -- ----------------------------------------------------------------------------
572 -- resultRepOfMachOp
573
574 {- |
575 Returns the MachRep of the result of a MachOp.
576 -}
577 resultRepOfMachOp :: MachOp -> MachRep
578 resultRepOfMachOp mop =
579   case mop of
580     MO_Add    r         -> r
581     MO_Sub    r         -> r
582     MO_Eq     r         -> comparisonResultRep
583     MO_Ne     r         -> comparisonResultRep
584     MO_Mul    r         -> r
585     MO_S_MulMayOflo r   -> r
586     MO_S_Quot r         -> r
587     MO_S_Rem  r         -> r
588     MO_S_Neg  r         -> r
589     MO_U_MulMayOflo r   -> r
590     MO_U_Quot r         -> r
591     MO_U_Rem  r         -> r
592
593     MO_S_Ge r           -> comparisonResultRep
594     MO_S_Le r           -> comparisonResultRep
595     MO_S_Gt r           -> comparisonResultRep
596     MO_S_Lt r           -> comparisonResultRep
597
598     MO_U_Ge r           -> comparisonResultRep
599     MO_U_Le r           -> comparisonResultRep
600     MO_U_Gt r           -> comparisonResultRep
601     MO_U_Lt r           -> comparisonResultRep
602
603     MO_And   r          -> r
604     MO_Or    r          -> r
605     MO_Xor   r          -> r
606     MO_Not   r          -> r
607     MO_Shl   r          -> r
608     MO_U_Shr r          -> r
609     MO_S_Shr r          -> r
610
611     MO_S_Conv from to   -> to
612     MO_U_Conv from to   -> to
613
614
615 comparisonResultRep = wordRep  -- is it?
616
617
618 -- -----------------------------------------------------------------------------
619 -- machOpArgReps
620
621 -- | This function is used for debugging only: we can check whether an
622 -- application of a MachOp is "type-correct" by checking that the MachReps of
623 -- its arguments are the same as the MachOp expects.  This is used when 
624 -- linting a CmmExpr.
625
626 machOpArgReps :: MachOp -> [MachRep]
627 machOpArgReps op = 
628   case op of
629     MO_Add    r         -> [r,r]
630     MO_Sub    r         -> [r,r]
631     MO_Eq     r         -> [r,r]
632     MO_Ne     r         -> [r,r]
633     MO_Mul    r         -> [r,r]
634     MO_S_MulMayOflo r   -> [r,r]
635     MO_S_Quot r         -> [r,r]
636     MO_S_Rem  r         -> [r,r]
637     MO_S_Neg  r         -> [r]
638     MO_U_MulMayOflo r   -> [r,r]
639     MO_U_Quot r         -> [r,r]
640     MO_U_Rem  r         -> [r,r]
641
642     MO_S_Ge r           -> [r,r]
643     MO_S_Le r           -> [r,r]
644     MO_S_Gt r           -> [r,r]
645     MO_S_Lt r           -> [r,r]
646
647     MO_U_Ge r           -> [r,r]
648     MO_U_Le r           -> [r,r]
649     MO_U_Gt r           -> [r,r]
650     MO_U_Lt r           -> [r,r]
651
652     MO_And   r          -> [r,r]
653     MO_Or    r          -> [r,r]
654     MO_Xor   r          -> [r,r]
655     MO_Not   r          -> [r]
656     MO_Shl   r          -> [r,wordRep]
657     MO_U_Shr r          -> [r,wordRep]
658     MO_S_Shr r          -> [r,wordRep]
659
660     MO_S_Conv from to   -> [from]
661     MO_U_Conv from to   -> [from]