[project @ 2000-02-28 12:02:31 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     | F80   -- Intel 80-bit internal FP format; only used for spilling
305 #endif
306 #if sparc_TARGET_ARCH
307     = B     -- byte (signed)
308     | BU    -- byte (unsigned)
309 --  | HW    -- halfword, 2 bytes (signed): UNUSED
310 --  | HWU   -- halfword, 2 bytes (unsigned): UNUSED
311     | W     -- word, 4 bytes
312 --  | D     -- doubleword, 8 bytes: UNUSED
313     | F     -- IEEE single-precision floating pt
314     | DF    -- IEEE single-precision floating pt
315 #endif
316
317 primRepToSize :: PrimRep -> Size
318
319 primRepToSize PtrRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
320 primRepToSize CodePtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
321 primRepToSize DataPtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
322 primRepToSize RetRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
323 primRepToSize CostCentreRep = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
324 primRepToSize CharRep       = IF_ARCH_alpha( BU, IF_ARCH_i386( B, IF_ARCH_sparc( BU,)))
325 primRepToSize IntRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
326 primRepToSize WordRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
327 primRepToSize AddrRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
328 primRepToSize FloatRep      = IF_ARCH_alpha( TF, IF_ARCH_i386( F, IF_ARCH_sparc( F ,)))
329 primRepToSize DoubleRep     = IF_ARCH_alpha( TF, IF_ARCH_i386( DF,IF_ARCH_sparc( DF,)))
330 primRepToSize ArrayRep      = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
331 primRepToSize ByteArrayRep  = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
332 primRepToSize WeakPtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
333 primRepToSize ForeignObjRep  = IF_ARCH_alpha( Q, IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
334 primRepToSize StablePtrRep  = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
335 \end{code}
336
337 %************************************************************************
338 %*                                                                      *
339 \subsection{Machine's assembly language}
340 %*                                                                      *
341 %************************************************************************
342
343 We have a few common ``instructions'' (nearly all the pseudo-ops) but
344 mostly all of @Instr@ is machine-specific.
345
346 \begin{code}
347 data Instr
348   = COMMENT FAST_STRING         -- comment pseudo-op
349   | SEGMENT CodeSegment         -- {data,text} segment pseudo-op
350   | LABEL   CLabel              -- global label pseudo-op
351   | ASCII   Bool                -- True <=> needs backslash conversion
352             String              -- the literal string
353   | DATA    Size
354             [Imm]
355   | DELTA   Int                 -- specify current stack offset for
356                                 -- benefit of subsequent passes
357 \end{code}
358
359 \begin{code}
360 #if alpha_TARGET_ARCH
361
362 -- data Instr continues...
363
364 -- Loads and stores.
365
366               | LD            Size Reg MachRegsAddr -- size, dst, src
367               | LDA           Reg MachRegsAddr      -- dst, src
368               | LDAH          Reg MachRegsAddr      -- dst, src
369               | LDGP          Reg MachRegsAddr      -- dst, src
370               | LDI           Size Reg Imm     -- size, dst, src
371               | ST            Size Reg MachRegsAddr -- size, src, dst
372
373 -- Int Arithmetic.
374
375               | CLR           Reg                   -- dst
376               | ABS           Size RI Reg           -- size, src, dst
377               | NEG           Size Bool RI Reg      -- size, overflow, src, dst
378               | ADD           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
379               | SADD          Size Size Reg RI Reg  -- size, scale, src, src, dst
380               | SUB           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
381               | SSUB          Size Size Reg RI Reg  -- size, scale, src, src, dst
382               | MUL           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
383               | DIV           Size Bool Reg RI Reg  -- size, unsigned, src, src, dst
384               | REM           Size Bool Reg RI Reg  -- size, unsigned, src, src, dst
385
386 -- Simple bit-twiddling.
387
388               | NOT           RI Reg
389               | AND           Reg RI Reg
390               | ANDNOT        Reg RI Reg
391               | OR            Reg RI Reg
392               | ORNOT         Reg RI Reg
393               | XOR           Reg RI Reg
394               | XORNOT        Reg RI Reg
395               | SLL           Reg RI Reg
396               | SRL           Reg RI Reg
397               | SRA           Reg RI Reg
398
399               | ZAP           Reg RI Reg
400               | ZAPNOT        Reg RI Reg
401
402               | NOP
403
404 -- Comparison
405
406               | CMP           Cond Reg RI Reg
407
408 -- Float Arithmetic.
409
410               | FCLR          Reg
411               | FABS          Reg Reg
412               | FNEG          Size Reg Reg
413               | FADD          Size Reg Reg Reg
414               | FDIV          Size Reg Reg Reg
415               | FMUL          Size Reg Reg Reg
416               | FSUB          Size Reg Reg Reg
417               | CVTxy         Size Size Reg Reg
418               | FCMP          Size Cond Reg Reg Reg
419               | FMOV          Reg Reg
420
421 -- Jumping around.
422
423               | BI            Cond Reg Imm
424               | BF            Cond Reg Imm
425               | BR            Imm
426               | JMP           Reg MachRegsAddr Int
427               | BSR           Imm Int
428               | JSR           Reg MachRegsAddr Int
429
430 -- Alpha-specific pseudo-ops.
431
432               | FUNBEGIN CLabel
433               | FUNEND CLabel
434
435 data RI
436   = RIReg Reg
437   | RIImm Imm
438
439 #endif {- alpha_TARGET_ARCH -}
440 \end{code}
441
442 Intel, in their infinite wisdom, selected a stack model for floating
443 point registers on x86.  That might have made sense back in 1979 --
444 nowadays we can see it for the nonsense it really is.  A stack model
445 fits poorly with the existing nativeGen infrastructure, which assumes
446 flat integer and FP register sets.  Prior to this commit, nativeGen
447 could not generate correct x86 FP code -- to do so would have meant
448 somehow working the register-stack paradigm into the register
449 allocator and spiller, which sounds very difficult.
450   
451 We have decided to cheat, and go for a simple fix which requires no
452 infrastructure modifications, at the expense of generating ropey but
453 correct FP code.  All notions of the x86 FP stack and its insns have
454 been removed.  Instead, we pretend (to the instruction selector and
455 register allocator) that x86 has six floating point registers, %fake0
456 .. %fake5, which can be used in the usual flat manner.  We further
457 claim that x86 has floating point instructions very similar to SPARC
458 and Alpha, that is, a simple 3-operand register-register arrangement.
459 Code generation and register allocation proceed on this basis.
460   
461 When we come to print out the final assembly, our convenient fiction
462 is converted to dismal reality.  Each fake instruction is
463 independently converted to a series of real x86 instructions.
464 %fake0 .. %fake5 are mapped to %st(0) .. %st(5).  To do reg-reg
465 arithmetic operations, the two operands are pushed onto the top of the
466 FP stack, the operation done, and the result copied back into the
467 relevant register.  There are only six %fake registers because 2 are
468 needed for the translation, and x86 has 8 in total.
469
470 The translation is inefficient but is simple and it works.  A cleverer
471 translation would handle a sequence of insns, simulating the FP stack
472 contents, would not impose a fixed mapping from %fake to %st regs, and
473 hopefully could avoid most of the redundant reg-reg moves of the
474 current translation.
475
476 We might as well make use of whatever unique FP facilities Intel have
477 chosen to bless us with (let's not be churlish, after all).
478 Hence GLDZ and GLD1.  Bwahahahahahahaha!
479
480 \begin{code}
481 #if i386_TARGET_ARCH
482
483 -- data Instr continues...
484
485 -- Moves.
486
487               | MOV           Size Operand Operand
488               | MOVZxL        Size Operand Operand -- size is the size of operand 1
489               | MOVSxL        Size Operand Operand -- size is the size of operand 1
490
491 -- Load effective address (also a very useful three-operand add instruction :-)
492
493               | LEA           Size Operand Operand
494
495 -- Int Arithmetic.
496
497               | ADD           Size Operand Operand
498               | SUB           Size Operand Operand
499
500 -- Multiplication (signed and unsigned), Division (signed and unsigned),
501 -- result in %eax, %edx.
502
503               | IMUL          Size Operand Operand
504               | IDIV          Size Operand
505
506 -- Simple bit-twiddling.
507
508               | AND           Size Operand Operand
509               | OR            Size Operand Operand
510               | XOR           Size Operand Operand
511               | NOT           Size Operand
512               | NEGI          Size Operand -- NEG instruction (name clash with Cond)
513               | SHL           Size Imm Operand -- Only immediate shifts allowed
514               | SAR           Size Imm Operand -- Only immediate shifts allowed
515               | SHR           Size Imm Operand -- Only immediate shifts allowed
516               | BT            Size Imm Operand
517               | NOP
518
519 -- Float Arithmetic.
520
521 -- Note that we cheat by treating G{ABS,MOV,NEG} of doubles 
522 -- as single instructions right up until we spit them out.
523
524               -- all the 3-operand fake fp insns are src1 src2 dst
525               -- and furthermore are constrained to be fp regs only.
526               -- IMPORTANT: keep is_G_insn up to date with any changes here
527               | GMOV          Reg Reg -- src(fpreg), dst(fpreg)
528               | GLD           Size MachRegsAddr Reg -- src, dst(fpreg)
529               | GST           Size Reg MachRegsAddr -- src(fpreg), dst
530
531               | GLDZ          Reg -- dst(fpreg)
532               | GLD1          Reg -- dst(fpreg)
533
534               | GFTOD         Reg Reg -- src(fpreg), dst(fpreg)
535               | GFTOI         Reg Reg -- src(fpreg), dst(intreg)
536
537               | GDTOF         Reg Reg -- src(fpreg), dst(fpreg)
538               | GDTOI         Reg Reg -- src(fpreg), dst(intreg)
539
540               | GITOF         Reg Reg -- src(intreg), dst(fpreg)
541               | GITOD         Reg Reg -- src(intreg), dst(fpreg)
542
543               | GADD          Size Reg Reg Reg -- src1, src2, dst
544               | GDIV          Size Reg Reg Reg -- src1, src2, dst
545               | GSUB          Size Reg Reg Reg -- src1, src2, dst
546               | GMUL          Size Reg Reg Reg -- src1, src2, dst
547
548               | GCMP          Size Reg Reg -- src1, src2
549
550               | GABS          Size Reg Reg -- src, dst
551               | GNEG          Size Reg Reg -- src, dst
552               | GSQRT         Size Reg Reg -- src, dst
553               | GSIN          Size Reg Reg -- src, dst
554               | GCOS          Size Reg Reg -- src, dst
555               | GTAN          Size Reg Reg -- src, dst
556
557               | GFREE         -- do ffree on all x86 regs; an ugly hack
558 -- Comparison
559
560               | TEST          Size Operand Operand
561               | CMP           Size Operand Operand
562               | SETCC         Cond Operand
563
564 -- Stack Operations.
565
566               | PUSH          Size Operand
567               | POP           Size Operand
568               | PUSHA
569               | POPA
570
571 -- Jumping around.
572
573               | JMP           Operand -- target
574               | JXX           Cond CLabel -- target
575               | CALL          Imm
576
577 -- Other things.
578
579               | CLTD -- sign extend %eax into %edx:%eax
580
581 data Operand
582   = OpReg  Reg          -- register
583   | OpImm  Imm          -- immediate value
584   | OpAddr MachRegsAddr -- memory reference
585
586
587 i386_insert_ffrees :: [Instr] -> [Instr]
588 i386_insert_ffrees insns
589    | any is_G_instr insns
590    = concatMap ffree_before_nonlocal_transfers insns
591    | otherwise
592    = insns
593
594 ffree_before_nonlocal_transfers insn
595    = case insn of
596         CALL _                                      -> [GFREE, insn]
597         JMP (OpImm (ImmCLbl clbl)) | isAsmTemp clbl -> [insn]
598         JMP _                                       -> [GFREE, insn]
599         other                                       -> [insn]
600
601
602 -- if you ever add a new FP insn to the fake x86 FP insn set,
603 -- you must update this too
604 is_G_instr :: Instr -> Bool
605 is_G_instr instr
606    = case instr of
607         GMOV _ _ -> True; GLD _ _ _ -> True; GST _ _ _ -> True;
608         GLDZ _ -> True; GLD1 _ -> True;
609         GFTOD _ _ -> True; GFTOI _ _ -> True;
610         GDTOF _ _ -> True; GDTOI _ _ -> True;
611         GITOF _ _ -> True; GITOD _ _ -> True;
612         GADD _ _ _ _ -> True; GDIV _ _ _ _ -> True
613         GSUB _ _ _ _ -> True; GMUL _ _ _ _ -> True
614         GCMP _ _ _ -> True; GABS _ _ _ -> True
615         GNEG _ _ _ -> True; GSQRT _ _ _ -> True
616         GSIN _ _ _ -> True; GCOS _ _ _ -> True; GTAN _ _ _ -> True;
617         GFREE -> panic "is_G_instr: GFREE (!)"
618         other -> False
619
620 #endif {- i386_TARGET_ARCH -}
621 \end{code}
622
623 \begin{code}
624 #if sparc_TARGET_ARCH
625
626 -- data Instr continues...
627
628 -- Loads and stores.
629
630               | LD            Size MachRegsAddr Reg -- size, src, dst
631               | ST            Size Reg MachRegsAddr -- size, src, dst
632
633 -- Int Arithmetic.
634
635               | ADD           Bool Bool Reg RI Reg -- x?, cc?, src1, src2, dst
636               | SUB           Bool Bool Reg RI Reg -- x?, cc?, src1, src2, dst
637
638 -- Simple bit-twiddling.
639
640               | AND           Bool Reg RI Reg -- cc?, src1, src2, dst
641               | ANDN          Bool Reg RI Reg -- cc?, src1, src2, dst
642               | OR            Bool Reg RI Reg -- cc?, src1, src2, dst
643               | ORN           Bool Reg RI Reg -- cc?, src1, src2, dst
644               | XOR           Bool Reg RI Reg -- cc?, src1, src2, dst
645               | XNOR          Bool Reg RI Reg -- cc?, src1, src2, dst
646               | SLL           Reg RI Reg -- src1, src2, dst
647               | SRL           Reg RI Reg -- src1, src2, dst
648               | SRA           Reg RI Reg -- src1, src2, dst
649               | SETHI         Imm Reg -- src, dst
650               | NOP           -- Really SETHI 0, %g0, but worth an alias
651
652 -- Float Arithmetic.
653
654 -- Note that we cheat by treating F{ABS,MOV,NEG} of doubles as single instructions
655 -- right up until we spit them out.
656
657               | FABS          Size Reg Reg -- src dst
658               | FADD          Size Reg Reg Reg -- src1, src2, dst
659               | FCMP          Bool Size Reg Reg -- exception?, src1, src2, dst
660               | FDIV          Size Reg Reg Reg -- src1, src2, dst
661               | FMOV          Size Reg Reg -- src, dst
662               | FMUL          Size Reg Reg Reg -- src1, src2, dst
663               | FNEG          Size Reg Reg -- src, dst
664               | FSQRT         Size Reg Reg -- src, dst
665               | FSUB          Size Reg Reg Reg -- src1, src2, dst
666               | FxTOy         Size Size Reg Reg -- src, dst
667
668 -- Jumping around.
669
670               | BI            Cond Bool Imm -- cond, annul?, target
671               | BF            Cond Bool Imm -- cond, annul?, target
672
673               | JMP           MachRegsAddr      -- target
674               | CALL          Imm Int Bool -- target, args, terminal
675
676 data RI = RIReg Reg
677         | RIImm Imm
678
679 riZero :: RI -> Bool
680
681 riZero (RIImm (ImmInt 0))           = True
682 riZero (RIImm (ImmInteger 0))       = True
683 riZero (RIReg (FixedReg ILIT(0)))   = True
684 riZero _                            = False
685
686 #endif {- sparc_TARGET_ARCH -}
687 \end{code}