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