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