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