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