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