[project @ 2000-08-07 14:11:48 by sewardj]
[ghc-hetmet.git] / ghc / compiler / nativeGen / MachMisc.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1993-1998
3 %
4 \section[MachMisc]{Description of various machine-specific things}
5
6 \begin{code}
7 #include "nativeGen/NCG.h"
8
9 module MachMisc (
10
11         sizeOf, primRepToSize,
12
13         eXTRA_STK_ARGS_HERE,
14
15         volatileSaves, volatileRestores,
16
17         targetMaxDouble, targetMaxInt, targetMinDouble, targetMinInt,
18
19         underscorePrefix,
20         fmtAsmLbl,
21         exactLog2,
22
23         Instr(..),  IF_ARCH_i386(Operand(..) COMMA,)
24         Cond(..),
25         Size(..),
26         IF_ARCH_i386(i386_insert_ffrees COMMA,) 
27
28 #if alpha_TARGET_ARCH
29         , RI(..)
30 #endif
31 #if i386_TARGET_ARCH
32 #endif
33 #if sparc_TARGET_ARCH
34         RI(..), riZero, fpRelEA, moveSp, fPair
35 #endif
36     ) where
37
38 #include "HsVersions.h"
39 -- #include "config.h"
40
41 import AbsCSyn          ( MagicId(..) ) 
42 import AbsCUtils        ( magicIdPrimRep )
43 import CLabel           ( CLabel, isAsmTemp )
44 import Literal          ( mkMachInt, Literal(..) )
45 import MachRegs         ( stgReg, callerSaves, RegLoc(..),
46                           Imm(..), Reg(..), 
47                           MachRegsAddr(..)
48 #                         if sparc_TARGET_ARCH
49                           ,fp, sp
50 #                         endif
51                         )
52 import PrimRep          ( PrimRep(..) )
53 import Stix             ( StixTree(..), StixReg(..), CodeSegment )
54 import Panic            ( panic )
55 import GlaExts          ( word2Int#, int2Word#, shiftRL#, and#, (/=#) )
56 import Outputable       ( pprPanic, ppr )
57 import IOExts           ( trace )
58 \end{code}
59
60 \begin{code}
61 underscorePrefix :: Bool   -- leading underscore on assembler labels?
62
63 #ifdef LEADING_UNDERSCORE
64 underscorePrefix = True
65 #else
66 underscorePrefix = False
67 #endif
68
69 ---------------------------
70 fmtAsmLbl :: String -> String  -- for formatting labels
71
72 fmtAsmLbl s
73   =  IF_ARCH_alpha(
74      {- The alpha assembler likes temporary labels to look like $L123
75         instead of L123.  (Don't toss the L, because then Lf28
76         turns into $f28.)
77      -}
78      '$' : s
79      ,{-otherwise-}
80      '.':'L':s
81      )
82 \end{code}
83
84 % ----------------------------------------------------------------
85
86 We (allegedly) put the first six C-call arguments in registers;
87 where do we start putting the rest of them?
88 \begin{code}
89 eXTRA_STK_ARGS_HERE :: Int
90 eXTRA_STK_ARGS_HERE
91   = IF_ARCH_alpha(0, IF_ARCH_i386(23{-6x4bytes-}, IF_ARCH_sparc(23,???)))
92 \end{code}
93
94 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
95
96 Size of a @PrimRep@, in bytes.
97
98 \begin{code}
99 sizeOf :: PrimRep -> Integer{-in bytes-}
100     -- the result is an Integer only because it's more convenient
101
102 sizeOf pr = case (primRepToSize pr) of
103   IF_ARCH_alpha({B -> 1; BU -> 1; {-W -> 2; WU -> 2; L -> 4; SF -> 4;-} _ -> 8},)
104   IF_ARCH_sparc({B -> 1; BU -> 1; {-HW -> 2; HWU -> 2;-} W -> 4; {-D -> 8;-} F -> 4; DF -> 8},)
105   IF_ARCH_i386( {B -> 1; {-S -> 2;-} L -> 4; F -> 4; DF -> 8 },)
106 \end{code}
107
108 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
109
110 Now the volatile saves and restores.  We add the basic guys to the
111 list of ``user'' registers provided.  Note that there are more basic
112 registers on the restore list, because some are reloaded from
113 constants.
114
115 (@volatileRestores@ used only for wrapper-hungry PrimOps.)
116
117 \begin{code}
118 volatileSaves, volatileRestores :: [MagicId] -> [StixTree]
119
120 save_cands    = [BaseReg,Sp,Su,SpLim,Hp,HpLim]
121 restore_cands = save_cands
122
123 volatileSaves vols
124   = map save ((filter callerSaves) (save_cands ++ vols))
125   where
126     save x = StAssign (magicIdPrimRep x) loc reg
127       where
128         reg = StReg (StixMagicId x)
129         loc = case stgReg x of
130                 Save loc -> loc
131                 Always _ -> panic "volatileSaves"
132
133 volatileRestores vols
134   = map restore ((filter callerSaves) (restore_cands ++ vols))
135   where
136     restore x = StAssign (magicIdPrimRep x) reg loc
137       where
138         reg = StReg (StixMagicId x)
139         loc = case stgReg x of
140                 Save loc -> loc
141                 Always _ -> panic "volatileRestores"
142 \end{code}
143
144 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
145
146 Obviously slightly weedy
147 (Note that the floating point values aren't terribly important.)
148 ToDo: Fix!(JSM)
149 \begin{code}
150 targetMinDouble = MachDouble (-1.7976931348623157e+308)
151 targetMaxDouble = MachDouble (1.7976931348623157e+308)
152 targetMinInt = mkMachInt (-2147483648)
153 targetMaxInt = mkMachInt 2147483647
154 \end{code}
155
156 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
157
158 This algorithm for determining the $\log_2$ of exact powers of 2 comes
159 from GCC.  It requires bit manipulation primitives, and we use GHC
160 extensions.  Tough.
161
162 \begin{code}
163 w2i x = word2Int# x
164 i2w x = int2Word# x
165
166 exactLog2 :: Integer -> Maybe Integer
167 exactLog2 x
168   = if (x <= 0 || x >= 2147483648) then
169        Nothing
170     else
171        case (fromInteger x) of { I# x# ->
172        if (w2i ((i2w x#) `and#` (i2w (0# -# x#))) /=# x#) then
173           Nothing
174        else
175           Just (toInteger (I# (pow2 x#)))
176        }
177   where
178     shiftr x y = shiftRL# x y
179
180     pow2 x# | x# ==# 1# = 0#
181             | otherwise = 1# +# pow2 (w2i (i2w x# `shiftr` 1#))
182 \end{code}
183
184 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
185
186 \begin{code}
187 data Cond
188 #if alpha_TARGET_ARCH
189   = ALWAYS      -- For BI (same as BR)
190   | EQQ         -- For CMP and BI (NB: "EQ" is a 1.3 Prelude name)
191   | GE          -- For BI only
192   | GTT         -- For BI only (NB: "GT" is a 1.3 Prelude name)
193   | LE          -- For CMP and BI
194   | LTT         -- For CMP and BI (NB: "LT" is a 1.3 Prelude name)
195   | NE          -- For BI only
196   | NEVER       -- For BI (null instruction)
197   | ULE         -- For CMP only
198   | ULT         -- For CMP only
199 #endif
200 #if i386_TARGET_ARCH
201   = ALWAYS      -- What's really used? ToDo
202   | EQQ
203   | GE
204   | GEU
205   | GTT
206   | GU
207   | LE
208   | LEU
209   | LTT
210   | LU
211   | NE
212   | NEG
213   | POS
214 #endif
215 #if sparc_TARGET_ARCH
216   = ALWAYS      -- What's really used? ToDo
217   | EQQ
218   | GE
219   | GEU
220   | GTT
221   | GU
222   | LE
223   | LEU
224   | LTT
225   | LU
226   | NE
227   | NEG
228   | NEVER
229   | POS
230   | VC
231   | VS
232 #endif
233 \end{code}
234
235 \begin{code}
236 data Size
237 #if alpha_TARGET_ARCH
238     = B     -- byte
239     | BU
240 --  | W     -- word (2 bytes): UNUSED
241 --  | WU    -- : UNUSED
242 --  | L     -- longword (4 bytes): UNUSED
243     | Q     -- quadword (8 bytes)
244 --  | FF    -- VAX F-style floating pt: UNUSED
245 --  | GF    -- VAX G-style floating pt: UNUSED
246 --  | DF    -- VAX D-style floating pt: UNUSED
247 --  | SF    -- IEEE single-precision floating pt: UNUSED
248     | TF    -- IEEE double-precision floating pt
249 #endif
250 #if i386_TARGET_ARCH
251     = B     -- byte (lower)
252 --  | HB    -- higher byte **UNUSED**
253 --  | S     -- : UNUSED
254     | L
255     | F     -- IEEE single-precision floating pt
256     | DF    -- IEEE single-precision floating pt
257     | F80   -- Intel 80-bit internal FP format; only used for spilling
258 #endif
259 #if sparc_TARGET_ARCH
260     = B     -- byte (signed)
261     | BU    -- byte (unsigned)
262 --  | HW    -- halfword, 2 bytes (signed): UNUSED
263 --  | HWU   -- halfword, 2 bytes (unsigned): UNUSED
264     | W     -- word, 4 bytes
265 --  | D     -- doubleword, 8 bytes: UNUSED
266     | F     -- IEEE single-precision floating pt
267     | DF    -- IEEE single-precision floating pt
268 #endif
269
270 primRepToSize :: PrimRep -> Size
271
272 primRepToSize PtrRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
273 primRepToSize CodePtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
274 primRepToSize DataPtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
275 primRepToSize RetRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
276 primRepToSize CostCentreRep = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
277 primRepToSize CharRep       = IF_ARCH_alpha( BU, IF_ARCH_i386( B, IF_ARCH_sparc( BU,)))
278 primRepToSize IntRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
279 primRepToSize WordRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
280 primRepToSize AddrRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
281 primRepToSize FloatRep      = IF_ARCH_alpha( TF, IF_ARCH_i386( F, IF_ARCH_sparc( F ,)))
282 primRepToSize DoubleRep     = IF_ARCH_alpha( TF, IF_ARCH_i386( DF,IF_ARCH_sparc( DF,)))
283 primRepToSize ArrayRep      = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
284 primRepToSize ByteArrayRep  = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
285 primRepToSize WeakPtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
286 primRepToSize ForeignObjRep = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
287 primRepToSize BCORep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
288 primRepToSize StablePtrRep  = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
289 primRepToSize ThreadIdRep   = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
290 -- SUP: Wrong!!! Only for testing the rest of the NCG
291 primRepToSize Word64Rep     = trace "primRepToSize: Word64Rep not handled" B
292 primRepToSize Int64Rep      = trace "primRepToSize: Int64Rep not handled"  B
293 \end{code}
294
295 %************************************************************************
296 %*                                                                      *
297 \subsection{Machine's assembly language}
298 %*                                                                      *
299 %************************************************************************
300
301 We have a few common ``instructions'' (nearly all the pseudo-ops) but
302 mostly all of @Instr@ is machine-specific.
303
304 \begin{code}
305 data Instr
306   = COMMENT FAST_STRING         -- comment pseudo-op
307   | SEGMENT CodeSegment         -- {data,text} segment pseudo-op
308   | LABEL   CLabel              -- global label pseudo-op
309   | ASCII   Bool                -- True <=> needs backslash conversion
310             String              -- the literal string
311   | DATA    Size
312             [Imm]
313   | DELTA   Int                 -- specify current stack offset for
314                                 -- benefit of subsequent passes
315 \end{code}
316
317 \begin{code}
318 #if alpha_TARGET_ARCH
319
320 -- data Instr continues...
321
322 -- Loads and stores.
323
324               | LD            Size Reg MachRegsAddr -- size, dst, src
325               | LDA           Reg MachRegsAddr      -- dst, src
326               | LDAH          Reg MachRegsAddr      -- dst, src
327               | LDGP          Reg MachRegsAddr      -- dst, src
328               | LDI           Size Reg Imm     -- size, dst, src
329               | ST            Size Reg MachRegsAddr -- size, src, dst
330
331 -- Int Arithmetic.
332
333               | CLR           Reg                   -- dst
334               | ABS           Size RI Reg           -- size, src, dst
335               | NEG           Size Bool RI Reg      -- size, overflow, src, dst
336               | ADD           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
337               | SADD          Size Size Reg RI Reg  -- size, scale, src, src, dst
338               | SUB           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
339               | SSUB          Size Size Reg RI Reg  -- size, scale, src, src, dst
340               | MUL           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
341               | DIV           Size Bool Reg RI Reg  -- size, unsigned, src, src, dst
342               | REM           Size Bool Reg RI Reg  -- size, unsigned, src, src, dst
343
344 -- Simple bit-twiddling.
345
346               | NOT           RI Reg
347               | AND           Reg RI Reg
348               | ANDNOT        Reg RI Reg
349               | OR            Reg RI Reg
350               | ORNOT         Reg RI Reg
351               | XOR           Reg RI Reg
352               | XORNOT        Reg RI Reg
353               | SLL           Reg RI Reg
354               | SRL           Reg RI Reg
355               | SRA           Reg RI Reg
356
357               | ZAP           Reg RI Reg
358               | ZAPNOT        Reg RI Reg
359
360               | NOP
361
362 -- Comparison
363
364               | CMP           Cond Reg RI Reg
365
366 -- Float Arithmetic.
367
368               | FCLR          Reg
369               | FABS          Reg Reg
370               | FNEG          Size Reg Reg
371               | FADD          Size Reg Reg Reg
372               | FDIV          Size Reg Reg Reg
373               | FMUL          Size Reg Reg Reg
374               | FSUB          Size Reg Reg Reg
375               | CVTxy         Size Size Reg Reg
376               | FCMP          Size Cond Reg Reg Reg
377               | FMOV          Reg Reg
378
379 -- Jumping around.
380
381               | BI            Cond Reg Imm
382               | BF            Cond Reg Imm
383               | BR            Imm
384               | JMP           Reg MachRegsAddr Int
385               | BSR           Imm Int
386               | JSR           Reg MachRegsAddr Int
387
388 -- Alpha-specific pseudo-ops.
389
390               | FUNBEGIN CLabel
391               | FUNEND CLabel
392
393 data RI
394   = RIReg Reg
395   | RIImm Imm
396
397 #endif {- alpha_TARGET_ARCH -}
398 \end{code}
399
400 Intel, in their infinite wisdom, selected a stack model for floating
401 point registers on x86.  That might have made sense back in 1979 --
402 nowadays we can see it for the nonsense it really is.  A stack model
403 fits poorly with the existing nativeGen infrastructure, which assumes
404 flat integer and FP register sets.  Prior to this commit, nativeGen
405 could not generate correct x86 FP code -- to do so would have meant
406 somehow working the register-stack paradigm into the register
407 allocator and spiller, which sounds very difficult.
408   
409 We have decided to cheat, and go for a simple fix which requires no
410 infrastructure modifications, at the expense of generating ropey but
411 correct FP code.  All notions of the x86 FP stack and its insns have
412 been removed.  Instead, we pretend (to the instruction selector and
413 register allocator) that x86 has six floating point registers, %fake0
414 .. %fake5, which can be used in the usual flat manner.  We further
415 claim that x86 has floating point instructions very similar to SPARC
416 and Alpha, that is, a simple 3-operand register-register arrangement.
417 Code generation and register allocation proceed on this basis.
418   
419 When we come to print out the final assembly, our convenient fiction
420 is converted to dismal reality.  Each fake instruction is
421 independently converted to a series of real x86 instructions.
422 %fake0 .. %fake5 are mapped to %st(0) .. %st(5).  To do reg-reg
423 arithmetic operations, the two operands are pushed onto the top of the
424 FP stack, the operation done, and the result copied back into the
425 relevant register.  There are only six %fake registers because 2 are
426 needed for the translation, and x86 has 8 in total.
427
428 The translation is inefficient but is simple and it works.  A cleverer
429 translation would handle a sequence of insns, simulating the FP stack
430 contents, would not impose a fixed mapping from %fake to %st regs, and
431 hopefully could avoid most of the redundant reg-reg moves of the
432 current translation.
433
434 We might as well make use of whatever unique FP facilities Intel have
435 chosen to bless us with (let's not be churlish, after all).
436 Hence GLDZ and GLD1.  Bwahahahahahahaha!
437
438 \begin{code}
439 #if i386_TARGET_ARCH
440
441 -- data Instr continues...
442
443 -- Moves.
444
445               | MOV           Size Operand Operand
446               | MOVZxL        Size Operand Operand -- size is the size of operand 1
447               | MOVSxL        Size Operand Operand -- size is the size of operand 1
448
449 -- Load effective address (also a very useful three-operand add instruction :-)
450
451               | LEA           Size Operand Operand
452
453 -- Int Arithmetic.
454
455               | ADD           Size Operand Operand
456               | SUB           Size Operand Operand
457
458 -- Multiplication (signed and unsigned), Division (signed and unsigned),
459 -- result in %eax, %edx.
460
461               | IMUL          Size Operand Operand
462               | IDIV          Size Operand
463
464 -- Simple bit-twiddling.
465
466               | AND           Size Operand Operand
467               | OR            Size Operand Operand
468               | XOR           Size Operand Operand
469               | NOT           Size Operand
470               | NEGI          Size Operand -- NEG instruction (name clash with Cond)
471               | SHL           Size Imm Operand -- Only immediate shifts allowed
472               | SAR           Size Imm Operand -- Only immediate shifts allowed
473               | SHR           Size Imm Operand -- Only immediate shifts allowed
474               | BT            Size Imm Operand
475               | NOP
476
477 -- Float Arithmetic.
478
479 -- Note that we cheat by treating G{ABS,MOV,NEG} of doubles 
480 -- as single instructions right up until we spit them out.
481
482               -- all the 3-operand fake fp insns are src1 src2 dst
483               -- and furthermore are constrained to be fp regs only.
484               -- IMPORTANT: keep is_G_insn up to date with any changes here
485               | GMOV          Reg Reg -- src(fpreg), dst(fpreg)
486               | GLD           Size MachRegsAddr Reg -- src, dst(fpreg)
487               | GST           Size Reg MachRegsAddr -- src(fpreg), dst
488
489               | GLDZ          Reg -- dst(fpreg)
490               | GLD1          Reg -- dst(fpreg)
491
492               | GFTOD         Reg Reg -- src(fpreg), dst(fpreg)
493               | GFTOI         Reg Reg -- src(fpreg), dst(intreg)
494
495               | GDTOF         Reg Reg -- src(fpreg), dst(fpreg)
496               | GDTOI         Reg Reg -- src(fpreg), dst(intreg)
497
498               | GITOF         Reg Reg -- src(intreg), dst(fpreg)
499               | GITOD         Reg Reg -- src(intreg), dst(fpreg)
500
501               | GADD          Size Reg Reg Reg -- src1, src2, dst
502               | GDIV          Size Reg Reg Reg -- src1, src2, dst
503               | GSUB          Size Reg Reg Reg -- src1, src2, dst
504               | GMUL          Size Reg Reg Reg -- src1, src2, dst
505
506               | GCMP          Size Reg Reg -- src1, src2
507
508               | GABS          Size Reg Reg -- src, dst
509               | GNEG          Size Reg Reg -- src, dst
510               | GSQRT         Size Reg Reg -- src, dst
511               | GSIN          Size Reg Reg -- src, dst
512               | GCOS          Size Reg Reg -- src, dst
513               | GTAN          Size Reg Reg -- src, dst
514
515               | GFREE         -- do ffree on all x86 regs; an ugly hack
516 -- Comparison
517
518               | TEST          Size Operand Operand
519               | CMP           Size Operand Operand
520               | SETCC         Cond Operand
521
522 -- Stack Operations.
523
524               | PUSH          Size Operand
525               | POP           Size Operand
526               | PUSHA
527               | POPA
528
529 -- Jumping around.
530
531               | JMP           Operand -- target
532               | JXX           Cond CLabel -- target
533               | CALL          Imm
534
535 -- Other things.
536
537               | CLTD -- sign extend %eax into %edx:%eax
538
539 data Operand
540   = OpReg  Reg          -- register
541   | OpImm  Imm          -- immediate value
542   | OpAddr MachRegsAddr -- memory reference
543
544
545 i386_insert_ffrees :: [Instr] -> [Instr]
546 i386_insert_ffrees insns
547    | any is_G_instr insns
548    = concatMap ffree_before_nonlocal_transfers insns
549    | otherwise
550    = insns
551
552 ffree_before_nonlocal_transfers insn
553    = case insn of
554         CALL _                                      -> [GFREE, insn]
555         JMP (OpImm (ImmCLbl clbl)) | isAsmTemp clbl -> [insn]
556         JMP _                                       -> [GFREE, insn]
557         other                                       -> [insn]
558
559
560 -- if you ever add a new FP insn to the fake x86 FP insn set,
561 -- you must update this too
562 is_G_instr :: Instr -> Bool
563 is_G_instr instr
564    = case instr of
565         GMOV _ _ -> True; GLD _ _ _ -> True; GST _ _ _ -> True;
566         GLDZ _ -> True; GLD1 _ -> True;
567         GFTOD _ _ -> True; GFTOI _ _ -> True;
568         GDTOF _ _ -> True; GDTOI _ _ -> True;
569         GITOF _ _ -> True; GITOD _ _ -> True;
570         GADD _ _ _ _ -> True; GDIV _ _ _ _ -> True
571         GSUB _ _ _ _ -> True; GMUL _ _ _ _ -> True
572         GCMP _ _ _ -> True; GABS _ _ _ -> True
573         GNEG _ _ _ -> True; GSQRT _ _ _ -> True
574         GSIN _ _ _ -> True; GCOS _ _ _ -> True; GTAN _ _ _ -> True;
575         GFREE -> panic "is_G_instr: GFREE (!)"
576         other -> False
577
578 #endif {- i386_TARGET_ARCH -}
579 \end{code}
580
581 \begin{code}
582 #if sparc_TARGET_ARCH
583
584 -- data Instr continues...
585
586 -- Loads and stores.
587
588               | LD            Size MachRegsAddr Reg -- size, src, dst
589               | ST            Size Reg MachRegsAddr -- size, src, dst
590
591 -- Int Arithmetic.
592
593               | ADD           Bool Bool Reg RI Reg -- x?, cc?, src1, src2, dst
594               | SUB           Bool Bool Reg RI Reg -- x?, cc?, src1, src2, dst
595
596 -- Simple bit-twiddling.
597
598               | AND           Bool Reg RI Reg -- cc?, src1, src2, dst
599               | ANDN          Bool Reg RI Reg -- cc?, src1, src2, dst
600               | OR            Bool Reg RI Reg -- cc?, src1, src2, dst
601               | ORN           Bool Reg RI Reg -- cc?, src1, src2, dst
602               | XOR           Bool Reg RI Reg -- cc?, src1, src2, dst
603               | XNOR          Bool Reg RI Reg -- cc?, src1, src2, dst
604               | SLL           Reg RI Reg -- src1, src2, dst
605               | SRL           Reg RI Reg -- src1, src2, dst
606               | SRA           Reg RI Reg -- src1, src2, dst
607               | SETHI         Imm Reg -- src, dst
608               | NOP           -- Really SETHI 0, %g0, but worth an alias
609
610 -- Float Arithmetic.
611
612 -- Note that we cheat by treating F{ABS,MOV,NEG} of doubles as single instructions
613 -- right up until we spit them out.
614
615               | FABS          Size Reg Reg -- src dst
616               | FADD          Size Reg Reg Reg -- src1, src2, dst
617               | FCMP          Bool Size Reg Reg -- exception?, src1, src2, dst
618               | FDIV          Size Reg Reg Reg -- src1, src2, dst
619               | FMOV          Size Reg Reg -- src, dst
620               | FMUL          Size Reg Reg Reg -- src1, src2, dst
621               | FNEG          Size Reg Reg -- src, dst
622               | FSQRT         Size Reg Reg -- src, dst
623               | FSUB          Size Reg Reg Reg -- src1, src2, dst
624               | FxTOy         Size Size Reg Reg -- src, dst
625
626 -- Jumping around.
627
628               | BI            Cond Bool Imm -- cond, annul?, target
629               | BF            Cond Bool Imm -- cond, annul?, target
630
631               | JMP           MachRegsAddr      -- target
632               | CALL          Imm Int Bool -- target, args, terminal
633
634 data RI = RIReg Reg
635         | RIImm Imm
636
637 riZero :: RI -> Bool
638
639 riZero (RIImm (ImmInt 0))           = True
640 riZero (RIImm (ImmInteger 0))       = True
641 riZero (RIReg (RealReg 0))          = True
642 riZero _                            = False
643
644 -- Calculate the effective address which would be used by the
645 -- corresponding fpRel sequence.  fpRel is in MachRegs.lhs,
646 -- alas -- can't have fpRelEA here because of module dependencies.
647 fpRelEA :: Int -> Reg -> Instr
648 fpRelEA n dst
649    = ADD False False fp (RIImm (ImmInt (n * BYTES_PER_WORD))) dst
650
651 -- Code to shift the stack pointer by n words.
652 moveSp :: Int -> Instr
653 moveSp n
654    = ADD False False sp (RIImm (ImmInt (n * BYTES_PER_WORD))) sp
655
656 -- Produce the second-half-of-a-double register given the first half.
657 fPair :: Reg -> Reg
658 fPair (RealReg n) | n >= 32 && n `mod` 2 == 0  = RealReg (n+1)
659 fPair other = pprPanic "fPair(sparc NCG)" (ppr other)
660 #endif {- sparc_TARGET_ARCH -}
661 \end{code}