Whitespace only in nativeGen/RegAlloc/Linear/Main.hs
[ghc-hetmet.git] / compiler / cmm / CmmMachOp.hs
1
2 module CmmMachOp
3     ( MachOp(..)
4     , pprMachOp, isCommutableMachOp, isAssociativeMachOp
5     , isComparisonMachOp, machOpResultType
6     , machOpArgReps, maybeInvertComparison
7
8     -- MachOp builders
9     , mo_wordAdd, mo_wordSub, mo_wordEq, mo_wordNe,mo_wordMul, mo_wordSQuot
10     , mo_wordSRem, mo_wordSNeg, mo_wordUQuot, mo_wordURem
11     , mo_wordSGe, mo_wordSLe, mo_wordSGt, mo_wordSLt, mo_wordUGe
12     , mo_wordULe, mo_wordUGt, mo_wordULt
13     , mo_wordAnd, mo_wordOr, mo_wordXor, mo_wordNot, mo_wordShl, mo_wordSShr, mo_wordUShr
14     , mo_u_8To32, mo_s_8To32, mo_u_16To32, mo_s_16To32
15     , mo_u_8ToWord, mo_s_8ToWord, mo_u_16ToWord, mo_s_16ToWord, mo_u_32ToWord, mo_s_32ToWord
16     , mo_32To8, mo_32To16, mo_WordTo8, mo_WordTo16, mo_WordTo32
17
18     -- CallishMachOp
19     , CallishMachOp(..)
20     , pprCallishMachOp
21    )
22 where
23
24 #include "HsVersions.h"
25
26 import CmmType
27 import Outputable
28
29 -----------------------------------------------------------------------------
30 --              MachOp
31 -----------------------------------------------------------------------------
32
33 {-
34 Implementation notes:
35
36 It might suffice to keep just a width, without distinguishing between
37 floating and integer types.  However, keeping the distinction will
38 help the native code generator to assign registers more easily.
39 -}
40
41
42 {- |
43 Machine-level primops; ones which we can reasonably delegate to the
44 native code generators to handle.  Basically contains C's primops
45 and no others.
46
47 Nomenclature: all ops indicate width and signedness, where
48 appropriate.  Widths: 8\/16\/32\/64 means the given size, obviously.
49 Nat means the operation works on STG word sized objects.
50 Signedness: S means signed, U means unsigned.  For operations where
51 signedness is irrelevant or makes no difference (for example
52 integer add), the signedness component is omitted.
53
54 An exception: NatP is a ptr-typed native word.  From the point of
55 view of the native code generators this distinction is irrelevant,
56 but the C code generator sometimes needs this info to emit the
57 right casts.
58 -}
59
60 data MachOp
61   -- Integer operations (insensitive to signed/unsigned)
62   = MO_Add Width
63   | MO_Sub Width
64   | MO_Eq  Width
65   | MO_Ne  Width
66   | MO_Mul Width                -- low word of multiply
67
68   -- Signed multiply/divide
69   | MO_S_MulMayOflo Width       -- nonzero if signed multiply overflows
70   | MO_S_Quot Width             -- signed / (same semantics as IntQuotOp)
71   | MO_S_Rem  Width             -- signed % (same semantics as IntRemOp)
72   | MO_S_Neg  Width             -- unary -
73
74   -- Unsigned multiply/divide
75   | MO_U_MulMayOflo Width       -- nonzero if unsigned multiply overflows
76   | MO_U_Quot Width             -- unsigned / (same semantics as WordQuotOp)
77   | MO_U_Rem  Width             -- unsigned % (same semantics as WordRemOp)
78
79   -- Signed comparisons
80   | MO_S_Ge Width
81   | MO_S_Le Width
82   | MO_S_Gt Width
83   | MO_S_Lt Width
84
85   -- Unsigned comparisons
86   | MO_U_Ge Width
87   | MO_U_Le Width
88   | MO_U_Gt Width
89   | MO_U_Lt Width
90
91   -- Floating point arithmetic
92   | MO_F_Add  Width
93   | MO_F_Sub  Width
94   | MO_F_Neg  Width             -- unary -
95   | MO_F_Mul  Width
96   | MO_F_Quot Width
97
98   -- Floating point comparison
99   | MO_F_Eq Width
100   | MO_F_Ne Width
101   | MO_F_Ge Width
102   | MO_F_Le Width
103   | MO_F_Gt Width
104   | MO_F_Lt Width
105
106   -- Bitwise operations.  Not all of these may be supported
107   -- at all sizes, and only integral Widths are valid.
108   | MO_And   Width
109   | MO_Or    Width
110   | MO_Xor   Width
111   | MO_Not   Width
112   | MO_Shl   Width
113   | MO_U_Shr Width      -- unsigned shift right
114   | MO_S_Shr Width      -- signed shift right
115
116   -- Conversions.  Some of these will be NOPs.
117   -- Floating-point conversions use the signed variant.
118   | MO_SF_Conv Width Width      -- Signed int -> Float
119   | MO_FS_Conv Width Width      -- Float -> Signed int
120   | MO_SS_Conv Width Width      -- Signed int -> Signed int
121   | MO_UU_Conv Width Width      -- unsigned int -> unsigned int
122   | MO_FF_Conv Width Width      -- Float -> Float
123   deriving (Eq, Show)
124
125 pprMachOp :: MachOp -> SDoc
126 pprMachOp mo = text (show mo)
127
128
129
130 -- -----------------------------------------------------------------------------
131 -- Some common MachReps
132
133 -- A 'wordRep' is a machine word on the target architecture
134 -- Specifically, it is the size of an Int#, Word#, Addr#
135 -- and the unit of allocation on the stack and the heap
136 -- Any pointer is also guaranteed to be a wordRep.
137
138 mo_wordAdd, mo_wordSub, mo_wordEq, mo_wordNe,mo_wordMul, mo_wordSQuot
139     , mo_wordSRem, mo_wordSNeg, mo_wordUQuot, mo_wordURem
140     , mo_wordSGe, mo_wordSLe, mo_wordSGt, mo_wordSLt, mo_wordUGe
141     , mo_wordULe, mo_wordUGt, mo_wordULt
142     , mo_wordAnd, mo_wordOr, mo_wordXor, mo_wordNot, mo_wordShl, mo_wordSShr, mo_wordUShr
143     , mo_u_8To32, mo_s_8To32, mo_u_16To32, mo_s_16To32
144     , mo_u_8ToWord, mo_s_8ToWord, mo_u_16ToWord, mo_s_16ToWord, mo_u_32ToWord, mo_s_32ToWord
145     , mo_32To8, mo_32To16, mo_WordTo8, mo_WordTo16, mo_WordTo32
146     :: MachOp
147
148 mo_wordAdd      = MO_Add wordWidth
149 mo_wordSub      = MO_Sub wordWidth
150 mo_wordEq       = MO_Eq  wordWidth
151 mo_wordNe       = MO_Ne  wordWidth
152 mo_wordMul      = MO_Mul wordWidth
153 mo_wordSQuot    = MO_S_Quot wordWidth
154 mo_wordSRem     = MO_S_Rem wordWidth
155 mo_wordSNeg     = MO_S_Neg wordWidth
156 mo_wordUQuot    = MO_U_Quot wordWidth
157 mo_wordURem     = MO_U_Rem wordWidth
158
159 mo_wordSGe      = MO_S_Ge  wordWidth
160 mo_wordSLe      = MO_S_Le  wordWidth
161 mo_wordSGt      = MO_S_Gt  wordWidth
162 mo_wordSLt      = MO_S_Lt  wordWidth
163
164 mo_wordUGe      = MO_U_Ge  wordWidth
165 mo_wordULe      = MO_U_Le  wordWidth
166 mo_wordUGt      = MO_U_Gt  wordWidth
167 mo_wordULt      = MO_U_Lt  wordWidth
168
169 mo_wordAnd      = MO_And wordWidth
170 mo_wordOr       = MO_Or  wordWidth
171 mo_wordXor      = MO_Xor wordWidth
172 mo_wordNot      = MO_Not wordWidth
173 mo_wordShl      = MO_Shl wordWidth
174 mo_wordSShr     = MO_S_Shr wordWidth
175 mo_wordUShr     = MO_U_Shr wordWidth
176
177 mo_u_8To32      = MO_UU_Conv W8 W32
178 mo_s_8To32      = MO_SS_Conv W8 W32
179 mo_u_16To32     = MO_UU_Conv W16 W32
180 mo_s_16To32     = MO_SS_Conv W16 W32
181
182 mo_u_8ToWord    = MO_UU_Conv W8  wordWidth
183 mo_s_8ToWord    = MO_SS_Conv W8  wordWidth
184 mo_u_16ToWord   = MO_UU_Conv W16 wordWidth
185 mo_s_16ToWord   = MO_SS_Conv W16 wordWidth
186 mo_s_32ToWord   = MO_SS_Conv W32 wordWidth
187 mo_u_32ToWord   = MO_UU_Conv W32 wordWidth
188
189 mo_WordTo8      = MO_UU_Conv wordWidth W8
190 mo_WordTo16     = MO_UU_Conv wordWidth W16
191 mo_WordTo32     = MO_UU_Conv wordWidth W32
192
193 mo_32To8        = MO_UU_Conv W32 W8
194 mo_32To16       = MO_UU_Conv W32 W16
195
196
197 -- ----------------------------------------------------------------------------
198 -- isCommutableMachOp
199
200 {- |
201 Returns 'True' if the MachOp has commutable arguments.  This is used
202 in the platform-independent Cmm optimisations.
203
204 If in doubt, return 'False'.  This generates worse code on the
205 native routes, but is otherwise harmless.
206 -}
207 isCommutableMachOp :: MachOp -> Bool
208 isCommutableMachOp mop =
209   case mop of
210         MO_Add _                -> True
211         MO_Eq _                 -> True
212         MO_Ne _                 -> True
213         MO_Mul _                -> True
214         MO_S_MulMayOflo _       -> True
215         MO_U_MulMayOflo _       -> True
216         MO_And _                -> True
217         MO_Or _                 -> True
218         MO_Xor _                -> True
219         _other                  -> False
220
221 -- ----------------------------------------------------------------------------
222 -- isAssociativeMachOp
223
224 {- |
225 Returns 'True' if the MachOp is associative (i.e. @(x+y)+z == x+(y+z)@)
226 This is used in the platform-independent Cmm optimisations.
227
228 If in doubt, return 'False'.  This generates worse code on the
229 native routes, but is otherwise harmless.
230 -}
231 isAssociativeMachOp :: MachOp -> Bool
232 isAssociativeMachOp mop =
233   case mop of
234         MO_Add {} -> True       -- NB: does not include
235         MO_Mul {} -> True --     floatint point!
236         MO_And {} -> True
237         MO_Or  {} -> True
238         MO_Xor {} -> True
239         _other    -> False
240
241 -- ----------------------------------------------------------------------------
242 -- isComparisonMachOp
243
244 {- |
245 Returns 'True' if the MachOp is a comparison.
246
247 If in doubt, return False.  This generates worse code on the
248 native routes, but is otherwise harmless.
249 -}
250 isComparisonMachOp :: MachOp -> Bool
251 isComparisonMachOp mop =
252   case mop of
253     MO_Eq   _  -> True
254     MO_Ne   _  -> True
255     MO_S_Ge _  -> True
256     MO_S_Le _  -> True
257     MO_S_Gt _  -> True
258     MO_S_Lt _  -> True
259     MO_U_Ge _  -> True
260     MO_U_Le _  -> True
261     MO_U_Gt _  -> True
262     MO_U_Lt _  -> True
263     MO_F_Eq {} -> True
264     MO_F_Ne {} -> True
265     MO_F_Ge {} -> True
266     MO_F_Le {} -> True
267     MO_F_Gt {} -> True
268     MO_F_Lt {} -> True
269     _other     -> False
270
271 -- -----------------------------------------------------------------------------
272 -- Inverting conditions
273
274 -- Sometimes it's useful to be able to invert the sense of a
275 -- condition.  Not all conditional tests are invertible: in
276 -- particular, floating point conditionals cannot be inverted, because
277 -- there exist floating-point values which return False for both senses
278 -- of a condition (eg. !(NaN > NaN) && !(NaN /<= NaN)).
279
280 maybeInvertComparison :: MachOp -> Maybe MachOp
281 maybeInvertComparison op
282   = case op of  -- None of these Just cases include floating point
283         MO_Eq r   -> Just (MO_Ne r)
284         MO_Ne r   -> Just (MO_Eq r)
285         MO_U_Lt r -> Just (MO_U_Ge r)
286         MO_U_Gt r -> Just (MO_U_Le r)
287         MO_U_Le r -> Just (MO_U_Gt r)
288         MO_U_Ge r -> Just (MO_U_Lt r)
289         MO_S_Lt r -> Just (MO_S_Ge r)
290         MO_S_Gt r -> Just (MO_S_Le r)
291         MO_S_Le r -> Just (MO_S_Gt r)
292         MO_S_Ge r -> Just (MO_S_Lt r)
293         MO_F_Eq r -> Just (MO_F_Ne r)
294         MO_F_Ne r -> Just (MO_F_Eq r)
295         MO_F_Ge r -> Just (MO_F_Le r)
296         MO_F_Le r -> Just (MO_F_Ge r)
297         MO_F_Gt r -> Just (MO_F_Lt r)
298         MO_F_Lt r -> Just (MO_F_Gt r)
299         _other    -> Nothing
300
301 -- ----------------------------------------------------------------------------
302 -- machOpResultType
303
304 {- |
305 Returns the MachRep of the result of a MachOp.
306 -}
307 machOpResultType :: MachOp -> [CmmType] -> CmmType
308 machOpResultType mop tys =
309   case mop of
310     MO_Add {}           -> ty1  -- Preserve GC-ptr-hood
311     MO_Sub {}           -> ty1  -- of first arg
312     MO_Mul    r         -> cmmBits r
313     MO_S_MulMayOflo r   -> cmmBits r
314     MO_S_Quot r         -> cmmBits r
315     MO_S_Rem  r         -> cmmBits r
316     MO_S_Neg  r         -> cmmBits r
317     MO_U_MulMayOflo r   -> cmmBits r
318     MO_U_Quot r         -> cmmBits r
319     MO_U_Rem  r         -> cmmBits r
320
321     MO_Eq {}            -> comparisonResultRep
322     MO_Ne {}            -> comparisonResultRep
323     MO_S_Ge {}          -> comparisonResultRep
324     MO_S_Le {}          -> comparisonResultRep
325     MO_S_Gt {}          -> comparisonResultRep
326     MO_S_Lt {}          -> comparisonResultRep
327
328     MO_U_Ge {}          -> comparisonResultRep
329     MO_U_Le {}          -> comparisonResultRep
330     MO_U_Gt {}          -> comparisonResultRep
331     MO_U_Lt {}          -> comparisonResultRep
332
333     MO_F_Add r          -> cmmFloat r
334     MO_F_Sub r          -> cmmFloat r
335     MO_F_Mul r          -> cmmFloat r
336     MO_F_Quot r         -> cmmFloat r
337     MO_F_Neg r          -> cmmFloat r
338     MO_F_Eq  {}         -> comparisonResultRep
339     MO_F_Ne  {}         -> comparisonResultRep
340     MO_F_Ge  {}         -> comparisonResultRep
341     MO_F_Le  {}         -> comparisonResultRep
342     MO_F_Gt  {}         -> comparisonResultRep
343     MO_F_Lt  {}         -> comparisonResultRep
344
345     MO_And {}           -> ty1  -- Used for pointer masking
346     MO_Or {}            -> ty1
347     MO_Xor {}           -> ty1
348     MO_Not   r          -> cmmBits r
349     MO_Shl   r          -> cmmBits r
350     MO_U_Shr r          -> cmmBits r
351     MO_S_Shr r          -> cmmBits r
352
353     MO_SS_Conv _ to     -> cmmBits to
354     MO_UU_Conv _ to     -> cmmBits to
355     MO_FS_Conv _ to     -> cmmBits to
356     MO_SF_Conv _ to     -> cmmFloat to
357     MO_FF_Conv _ to     -> cmmFloat to
358   where
359     (ty1:_) = tys
360
361 comparisonResultRep :: CmmType
362 comparisonResultRep = bWord  -- is it?
363
364
365 -- -----------------------------------------------------------------------------
366 -- machOpArgReps
367
368 -- | This function is used for debugging only: we can check whether an
369 -- application of a MachOp is "type-correct" by checking that the MachReps of
370 -- its arguments are the same as the MachOp expects.  This is used when
371 -- linting a CmmExpr.
372
373 machOpArgReps :: MachOp -> [Width]
374 machOpArgReps op =
375   case op of
376     MO_Add    r         -> [r,r]
377     MO_Sub    r         -> [r,r]
378     MO_Eq     r         -> [r,r]
379     MO_Ne     r         -> [r,r]
380     MO_Mul    r         -> [r,r]
381     MO_S_MulMayOflo r   -> [r,r]
382     MO_S_Quot r         -> [r,r]
383     MO_S_Rem  r         -> [r,r]
384     MO_S_Neg  r         -> [r]
385     MO_U_MulMayOflo r   -> [r,r]
386     MO_U_Quot r         -> [r,r]
387     MO_U_Rem  r         -> [r,r]
388
389     MO_S_Ge r           -> [r,r]
390     MO_S_Le r           -> [r,r]
391     MO_S_Gt r           -> [r,r]
392     MO_S_Lt r           -> [r,r]
393
394     MO_U_Ge r           -> [r,r]
395     MO_U_Le r           -> [r,r]
396     MO_U_Gt r           -> [r,r]
397     MO_U_Lt r           -> [r,r]
398
399     MO_F_Add r          -> [r,r]
400     MO_F_Sub r          -> [r,r]
401     MO_F_Mul r          -> [r,r]
402     MO_F_Quot r         -> [r,r]
403     MO_F_Neg r          -> [r]
404     MO_F_Eq  r          -> [r,r]
405     MO_F_Ne  r          -> [r,r]
406     MO_F_Ge  r          -> [r,r]
407     MO_F_Le  r          -> [r,r]
408     MO_F_Gt  r          -> [r,r]
409     MO_F_Lt  r          -> [r,r]
410
411     MO_And   r          -> [r,r]
412     MO_Or    r          -> [r,r]
413     MO_Xor   r          -> [r,r]
414     MO_Not   r          -> [r]
415     MO_Shl   r          -> [r,wordWidth]
416     MO_U_Shr r          -> [r,wordWidth]
417     MO_S_Shr r          -> [r,wordWidth]
418
419     MO_SS_Conv from _   -> [from]
420     MO_UU_Conv from _   -> [from]
421     MO_SF_Conv from _   -> [from]
422     MO_FS_Conv from _   -> [from]
423     MO_FF_Conv from _   -> [from]
424
425 -----------------------------------------------------------------------------
426 -- CallishMachOp
427 -----------------------------------------------------------------------------
428
429 -- CallishMachOps tend to be implemented by foreign calls in some backends,
430 -- so we separate them out.  In Cmm, these can only occur in a
431 -- statement position, in contrast to an ordinary MachOp which can occur
432 -- anywhere in an expression.
433 data CallishMachOp
434   = MO_F64_Pwr
435   | MO_F64_Sin
436   | MO_F64_Cos
437   | MO_F64_Tan
438   | MO_F64_Sinh
439   | MO_F64_Cosh
440   | MO_F64_Tanh
441   | MO_F64_Asin
442   | MO_F64_Acos
443   | MO_F64_Atan
444   | MO_F64_Log
445   | MO_F64_Exp
446   | MO_F64_Sqrt
447   | MO_F32_Pwr
448   | MO_F32_Sin
449   | MO_F32_Cos
450   | MO_F32_Tan
451   | MO_F32_Sinh
452   | MO_F32_Cosh
453   | MO_F32_Tanh
454   | MO_F32_Asin
455   | MO_F32_Acos
456   | MO_F32_Atan
457   | MO_F32_Log
458   | MO_F32_Exp
459   | MO_F32_Sqrt
460   | MO_WriteBarrier
461   | MO_Touch         -- Keep variables live (when using interior pointers)
462   
463   -- Note that these three MachOps all take 1 extra parameter than the
464   -- standard C lib versions. The extra (last) parameter contains
465   -- alignment of the pointers. Used for optimisation in backends.
466   | MO_Memcpy
467   | MO_Memset
468   | MO_Memmove
469   deriving (Eq, Show)
470
471 pprCallishMachOp :: CallishMachOp -> SDoc
472 pprCallishMachOp mo = text (show mo)
473