[project @ 1996-04-05 08:26:04 by partain]
[ghc-hetmet.git] / ghc / compiler / nativeGen / MachMisc.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1993-1996
3 %
4 \section[MachMisc]{Description of various machine-specific things}
5
6 \begin{code}
7 #include "HsVersions.h"
8 #include "nativeGen/NCG.h"
9
10 module MachMisc (
11
12         fixedHdrSizeInWords, varHdrSizeInWords,
13         charLikeSize, intLikeSize, mutHS, dataHS,
14         sizeOf, primRepToSize,
15
16         eXTRA_STK_ARGS_HERE,
17
18         volatileSaves, volatileRestores,
19
20         storageMgrInfo, smCAFlist, smOldLim, smOldMutables,
21         smStablePtrTable,
22
23         targetMaxDouble, targetMaxInt, targetMinDouble, targetMinInt,
24
25         underscorePrefix,
26         fmtAsmLbl,
27         cvtLitLit,
28         exactLog2,
29
30         Instr(..),  IF_ARCH_i386(Operand(..) COMMA,)
31         Cond(..),
32         Size(..)
33         
34 #if alpha_TARGET_ARCH
35         , RI(..)
36 #endif
37 #if i386_TARGET_ARCH
38 #endif
39 #if sparc_TARGET_ARCH
40         , RI(..), riZero
41 #endif
42     ) where
43
44 import Ubiq{-uitous-}
45 import AbsCLoop         ( fixedHdrSizeInWords, varHdrSizeInWords ) -- paranoia
46 import NcgLoop          ( underscorePrefix, fmtAsmLbl ) -- paranoia
47
48 import AbsCSyn          ( MagicId(..) ) 
49 import AbsCUtils        ( magicIdPrimRep )
50 import CmdLineOpts      ( opt_SccProfilingOn )
51 import Literal          ( mkMachInt, Literal(..) )
52 import MachRegs         ( stgReg, callerSaves, RegLoc(..),
53                           Imm(..), Reg(..), Addr
54                         )
55 import OrdList          ( OrdList )
56 import PrimRep          ( PrimRep(..) )
57 import SMRep            ( SMRep(..), SMSpecRepKind(..), SMUpdateKind(..) )
58 import Stix             ( StixTree(..), StixReg(..), sStLitLbl,
59                           CodeSegment
60                         )
61 import Util             ( panic )
62 \end{code}
63
64 \begin{code}
65 underscorePrefix :: Bool   -- leading underscore on labels?
66
67 underscorePrefix
68   = IF_ARCH_alpha(False
69     ,{-else-} IF_ARCH_i386(
70         IF_OS_linuxaout(True
71         , IF_OS_freebsd(True
72         , IF_OS_bsdi(True
73         , {-otherwise-} False)))
74      ,{-else-}IF_ARCH_sparc(
75         IF_OS_sunos4(True, {-otherwise-} False)
76      ,)))
77
78 ---------------------------
79 fmtAsmLbl :: String -> String  -- for formatting labels
80
81 fmtAsmLbl s
82   =  IF_ARCH_alpha(
83      {- The alpha assembler likes temporary labels to look like $L123
84         instead of L123.  (Don't toss the L, because then Lf28
85         turns into $f28.)
86      -}
87      '$' : s
88      ,{-otherwise-}
89      s
90      )
91
92 ---------------------------
93 cvtLitLit :: String -> String
94
95 -- ToDo: some kind of *careful* attention needed...
96
97 cvtLitLit "stdin"  = IF_ARCH_alpha("_iob+0" {-probably OK...-}
98                     ,IF_ARCH_i386("_IO_stdin_"
99                     ,IF_ARCH_sparc("__iob+0x0"{-probably OK...-}
100                     ,)))
101 cvtLitLit "stdout" = IF_ARCH_alpha("_iob+56"{-dodgy *at best*...-}
102                     ,IF_ARCH_i386("_IO_stdout_"
103                     ,IF_ARCH_sparc("__iob+0x14"{-dodgy *at best*...-}
104                     ,)))
105 cvtLitLit "stderr" = IF_ARCH_alpha("_iob+112"{-dodgy *at best*...-}
106                     ,IF_ARCH_i386("_IO_stderr_"
107                     ,IF_ARCH_sparc("__iob+0x28"{-dodgy *at best*...-}
108                     ,)))
109 cvtLitLit s
110   | isHex s   = s
111   | otherwise = error ("Native code generator can't handle ``" ++ s ++ "''")
112   where
113     isHex ('0':'x':xs) = all isHexDigit xs
114     isHex _ = False
115     -- Now, where have I seen this before?
116     isHexDigit c = isDigit c || c >= 'A' && c <= 'F' || c >= 'a' && c <= 'f'
117 \end{code}
118
119 % ----------------------------------------------------------------
120
121 We (allegedly) put the first six C-call arguments in registers;
122 where do we start putting the rest of them?
123 \begin{code}
124 eXTRA_STK_ARGS_HERE :: Int
125 eXTRA_STK_ARGS_HERE
126   = IF_ARCH_alpha(0, IF_ARCH_i386(23{-6x4bytes-}, IF_ARCH_sparc(23,???)))
127 \end{code}
128
129 % ----------------------------------------------------------------
130
131 @fixedHdrSizeInWords@ and @varHdrSizeInWords@: these are not dependent
132 on target architecture.
133 \begin{code}
134 fixedHdrSizeInWords :: Int
135
136 fixedHdrSizeInWords
137   = 1{-info ptr-} + profFHS + parFHS + tickyFHS
138     -- obviously, we aren't taking non-sequential too seriously yet
139   where
140     profFHS  = if opt_SccProfilingOn then 1 else 0
141     parFHS   = {-if PAR or GRAN then 1 else-} 0
142     tickyFHS = {-if ticky ... then 1 else-} 0
143
144 varHdrSizeInWords :: SMRep -> Int{-in words-}
145
146 varHdrSizeInWords sm
147   = case sm of
148     StaticRep _ _          -> 0
149     SpecialisedRep _ _ _ _ -> 0
150     GenericRep _ _ _       -> 0
151     BigTupleRep _          -> 1
152     MuTupleRep _           -> 2 {- (1 + GC_MUT_RESERVED_WORDS) -}
153     DataRep _              -> 1
154     DynamicRep             -> 2
155     BlackHoleRep           -> 0
156     PhantomRep             -> panic "MachMisc.varHdrSizeInWords:phantom"
157 \end{code}
158
159 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
160
161 Static closure sizes:
162 \begin{code}
163 charLikeSize, intLikeSize :: Int
164
165 charLikeSize = blahLikeSize CharLikeRep
166 intLikeSize  = blahLikeSize IntLikeRep
167
168 blahLikeSize blah
169   = fromInteger (sizeOf PtrRep)
170   * (fixedHdrSizeInWords + varHdrSizeInWords blahLikeRep + 1)
171   where
172     blahLikeRep = SpecialisedRep blah 0 1 SMNormalForm
173
174 --------
175 mutHS, dataHS :: StixTree
176
177 mutHS  = blah_hs (MuTupleRep 0)
178 dataHS = blah_hs (DataRep 0)
179
180 blah_hs blah
181   = StInt (toInteger words)
182   where
183     words = fixedHdrSizeInWords + varHdrSizeInWords blah
184 \end{code}
185
186 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
187
188 Size of a @PrimRep@, in bytes.
189
190 \begin{code}
191 sizeOf :: PrimRep -> Integer{-in bytes-}
192     -- the result is an Integer only because it's more convenient
193
194 sizeOf pr = case (primRepToSize pr) of
195   IF_ARCH_alpha({B -> 1; BU -> 1; {-W -> 2; WU -> 2; L -> 4; SF -> 4;-} _ -> 8},)
196   IF_ARCH_sparc({B -> 1; BU -> 1; {-HW -> 2; HWU -> 2;-} W -> 4; {-D -> 8;-} F -> 4; DF -> 8},)
197   IF_ARCH_i386( {B -> 1; {-S -> 2;-} L -> 4; F -> 4; DF -> 8 },)
198 \end{code}
199
200 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
201
202 Now the volatile saves and restores.  We add the basic guys to the
203 list of ``user'' registers provided.  Note that there are more basic
204 registers on the restore list, because some are reloaded from
205 constants.
206
207 (@volatileRestores@ used only for wrapper-hungry PrimOps.)
208
209 \begin{code}
210 volatileSaves, volatileRestores :: [MagicId] -> [StixTree]
211
212 save_cands    = [BaseReg,SpA,SuA,SpB,SuB,Hp,HpLim,RetReg]
213 restore_cands = save_cands ++ [StkStubReg,StdUpdRetVecReg]
214
215 volatileSaves vols
216   = map save ((filter callerSaves) (save_cands ++ vols))
217   where
218     save x = StAssign (magicIdPrimRep x) loc reg
219       where
220         reg = StReg (StixMagicId x)
221         loc = case stgReg x of
222                 Save loc -> loc
223                 Always _ -> panic "volatileSaves"
224
225 volatileRestores vols
226   = map restore ((filter callerSaves) (restore_cands ++ vols))
227   where
228     restore x = StAssign (magicIdPrimRep x) reg loc
229       where
230         reg = StReg (StixMagicId x)
231         loc = case stgReg x of
232                 Save loc -> loc
233                 Always _ -> panic "volatileRestores"
234 \end{code}
235
236 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
237
238 Obviously slightly weedy
239 (Note that the floating point values aren't terribly important.)
240 ToDo: Fix!(JSM)
241 \begin{code}
242 targetMinDouble = MachDouble (-1.7976931348623157e+308)
243 targetMaxDouble = MachDouble (1.7976931348623157e+308)
244 targetMinInt = mkMachInt (-2147483647)
245 targetMaxInt = mkMachInt 2147483647
246 \end{code}
247
248 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
249
250 Storage manager nonsense.  Note that the indices are dependent on
251 the definition of the smInfo structure in SMinterface.lh
252
253 \begin{code}
254 storageMgrInfo, smCAFlist, smOldMutables, smOldLim :: StixTree
255
256 storageMgrInfo   = sStLitLbl SLIT("StorageMgrInfo")
257 smCAFlist        = StInd PtrRep (StIndex PtrRep storageMgrInfo (StInt SM_CAFLIST))
258 smOldMutables    = StInd PtrRep (StIndex PtrRep storageMgrInfo (StInt SM_OLDMUTABLES))
259 smOldLim         = StInd PtrRep (StIndex PtrRep storageMgrInfo (StInt SM_OLDLIM))
260 smStablePtrTable = StInd PtrRep (StIndex PtrRep storageMgrInfo (StInt SM_STABLEPOINTERTABLE))
261 \end{code}
262
263 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
264
265 This algorithm for determining the $\log_2$ of exact powers of 2 comes
266 from GCC.  It requires bit manipulation primitives, and we use GHC
267 extensions.  Tough.
268
269 \begin{code}
270 w2i x = word2Int# x
271 i2w x = int2Word# x
272 i2w_s x = (x::Int#)
273
274 exactLog2 :: Integer -> Maybe Integer
275 exactLog2 x
276   = if (x <= 0 || x >= 2147483648) then
277        Nothing
278     else
279        case (fromInteger x) of { I# x# ->
280        if (w2i ((i2w x#) `and#` (i2w (0# -# x#))) /=# x#) then
281           Nothing
282        else
283           Just (toInteger (I# (pow2 x#)))
284        }
285   where
286     shiftr x y = shiftRA# x y
287
288     pow2 x# | x# ==# 1# = 0#
289             | otherwise = 1# +# pow2 (w2i (i2w x# `shiftr` i2w_s 1#))
290 \end{code}
291
292 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
293
294 \begin{code}
295 data Cond
296 #if alpha_TARGET_ARCH
297   = ALWAYS      -- For BI (same as BR)
298   | EQ          -- For CMP and BI
299   | GE          -- For BI only
300   | GT          -- For BI only
301   | LE          -- For CMP and BI
302   | LT          -- For CMP and BI
303   | NE          -- For BI only
304   | NEVER       -- For BI (null instruction)
305   | ULE         -- For CMP only
306   | ULT         -- For CMP only
307 #endif
308 #if i386_TARGET_ARCH
309   = ALWAYS      -- What's really used? ToDo
310   | EQ
311   | GE
312   | GEU
313   | GT
314   | GU
315   | LE
316   | LEU
317   | LT
318   | LU
319   | NE
320   | NEG
321   | POS
322 #endif
323 #if sparc_TARGET_ARCH
324   = ALWAYS      -- What's really used? ToDo
325   | EQ
326   | GE
327   | GEU
328   | GT
329   | GU
330   | LE
331   | LEU
332   | LT
333   | LU
334   | NE
335   | NEG
336   | NEVER
337   | POS
338   | VC
339   | VS
340 #endif
341 \end{code}
342
343 \begin{code}
344 data Size
345 #if alpha_TARGET_ARCH
346     = B     -- byte
347     | BU
348 --  | W     -- word (2 bytes): UNUSED
349 --  | WU    -- : UNUSED
350 --  | L     -- longword (4 bytes): UNUSED
351     | Q     -- quadword (8 bytes)
352 --  | FF    -- VAX F-style floating pt: UNUSED
353 --  | GF    -- VAX G-style floating pt: UNUSED
354 --  | DF    -- VAX D-style floating pt: UNUSED
355 --  | SF    -- IEEE single-precision floating pt: UNUSED
356     | TF    -- IEEE double-precision floating pt
357 #endif
358 #if i386_TARGET_ARCH
359     = B     -- byte (lower)
360 --  | HB    -- higher byte **UNUSED**
361 --  | S     -- : UNUSED
362     | L
363     | F     -- IEEE single-precision floating pt
364     | DF    -- IEEE single-precision floating pt
365 #endif
366 #if sparc_TARGET_ARCH
367     = B     -- byte (signed)
368     | BU    -- byte (unsigned)
369 --  | HW    -- halfword, 2 bytes (signed): UNUSED
370 --  | HWU   -- halfword, 2 bytes (unsigned): UNUSED
371     | W     -- word, 4 bytes
372 --  | D     -- doubleword, 8 bytes: UNUSED
373     | F     -- IEEE single-precision floating pt
374     | DF    -- IEEE single-precision floating pt
375 #endif
376
377 primRepToSize :: PrimRep -> Size
378
379 primRepToSize PtrRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
380 primRepToSize CodePtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
381 primRepToSize DataPtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
382 primRepToSize RetRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
383 primRepToSize CostCentreRep = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
384 primRepToSize CharRep       = IF_ARCH_alpha( BU, IF_ARCH_i386( L, IF_ARCH_sparc( BU,)))
385 primRepToSize IntRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
386 primRepToSize WordRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
387 primRepToSize AddrRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
388 primRepToSize FloatRep      = IF_ARCH_alpha( TF, IF_ARCH_i386( F, IF_ARCH_sparc( F ,)))
389 primRepToSize DoubleRep     = IF_ARCH_alpha( TF, IF_ARCH_i386( DF,IF_ARCH_sparc( DF,)))
390 primRepToSize ArrayRep      = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
391 primRepToSize ByteArrayRep  = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
392 primRepToSize StablePtrRep  = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
393 primRepToSize MallocPtrRep  = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
394 \end{code}
395
396 %************************************************************************
397 %*                                                                      *
398 \subsection{Machine's assembly language}
399 %*                                                                      *
400 %************************************************************************
401
402 We have a few common ``instructions'' (nearly all the pseudo-ops) but
403 mostly all of @Instr@ is machine-specific.
404
405 \begin{code}
406 data Instr
407   = COMMENT FAST_STRING         -- comment pseudo-op
408   | SEGMENT CodeSegment         -- {data,text} segment pseudo-op
409   | LABEL   CLabel              -- global label pseudo-op
410   | ASCII   Bool                -- True <=> needs backslash conversion
411             String              -- the literal string
412   | DATA    Size
413             [Imm]
414 \end{code}
415
416 \begin{code}
417 #if alpha_TARGET_ARCH
418
419 -- data Instr continues...
420
421 -- Loads and stores.
422
423               | LD            Size Reg Addr -- size, dst, src
424               | LDA           Reg Addr      -- dst, src
425               | LDAH          Reg Addr      -- dst, src
426               | LDGP          Reg Addr      -- dst, src
427               | LDI           Size Reg Imm  -- size, dst, src
428               | ST            Size Reg Addr -- size, src, dst
429
430 -- Int Arithmetic.
431
432               | CLR           Reg                   -- dst
433               | ABS           Size RI Reg           -- size, src, dst
434               | NEG           Size Bool RI Reg      -- size, overflow, src, dst
435               | ADD           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
436               | SADD          Size Size Reg RI Reg  -- size, scale, src, src, dst
437               | SUB           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
438               | SSUB          Size Size Reg RI Reg  -- size, scale, src, src, dst
439               | MUL           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
440               | DIV           Size Bool Reg RI Reg  -- size, unsigned, src, src, dst
441               | REM           Size Bool Reg RI Reg  -- size, unsigned, src, src, dst
442
443 -- Simple bit-twiddling.
444
445               | NOT           RI Reg
446               | AND           Reg RI Reg
447               | ANDNOT        Reg RI Reg
448               | OR            Reg RI Reg
449               | ORNOT         Reg RI Reg
450               | XOR           Reg RI Reg
451               | XORNOT        Reg RI Reg
452               | SLL           Reg RI Reg
453               | SRL           Reg RI Reg
454               | SRA           Reg RI Reg
455
456               | ZAP           Reg RI Reg
457               | ZAPNOT        Reg RI Reg
458
459               | NOP
460
461 -- Comparison
462
463               | CMP           Cond Reg RI Reg
464
465 -- Float Arithmetic.
466
467               | FCLR          Reg
468               | FABS          Reg Reg
469               | FNEG          Size Reg Reg
470               | FADD          Size Reg Reg Reg
471               | FDIV          Size Reg Reg Reg
472               | FMUL          Size Reg Reg Reg
473               | FSUB          Size Reg Reg Reg
474               | CVTxy         Size Size Reg Reg
475               | FCMP          Size Cond Reg Reg Reg
476               | FMOV          Reg Reg
477
478 -- Jumping around.
479
480               | BI            Cond Reg Imm
481               | BF            Cond Reg Imm
482               | BR            Imm
483               | JMP           Reg Addr Int
484               | BSR           Imm Int
485               | JSR           Reg Addr Int
486
487 -- Alpha-specific pseudo-ops.
488
489               | FUNBEGIN CLabel
490               | FUNEND CLabel
491
492 data RI
493   = RIReg Reg
494   | RIImm Imm
495
496 #endif {- alpha_TARGET_ARCH -}
497 \end{code}
498
499 \begin{code}
500 #if i386_TARGET_ARCH
501
502 -- data Instr continues...
503
504 -- Moves.
505
506               | MOV           Size Operand Operand
507               | MOVZX         Size Operand Operand -- size is the size of operand 2
508               | MOVSX         Size Operand Operand -- size is the size of operand 2
509
510 -- Load effective address (also a very useful three-operand add instruction :-)
511
512               | LEA           Size Operand Operand
513
514 -- Int Arithmetic.
515
516               | ADD           Size Operand Operand
517               | SUB           Size Operand Operand
518
519 -- Multiplication (signed and unsigned), Division (signed and unsigned),
520 -- result in %eax, %edx.
521
522               | IMUL          Size Operand Operand
523               | IDIV          Size Operand
524
525 -- Simple bit-twiddling.
526
527               | AND           Size Operand Operand
528               | OR            Size Operand Operand
529               | XOR           Size Operand Operand
530               | NOT           Size Operand
531               | NEGI          Size Operand -- NEG instruction (name clash with Cond)
532               | SHL           Size Operand Operand -- 1st operand must be an Imm
533               | SAR           Size Operand Operand -- 1st operand must be an Imm
534               | SHR           Size Operand Operand -- 1st operand must be an Imm
535               | NOP
536
537 -- Float Arithmetic. -- ToDo for 386
538
539 -- Note that we cheat by treating F{ABS,MOV,NEG} of doubles as single instructions
540 -- right up until we spit them out.
541
542               | SAHF          -- stores ah into flags
543               | FABS
544               | FADD          Size Operand -- src
545               | FADDP
546               | FIADD         Size Addr -- src
547               | FCHS
548               | FCOM          Size Operand -- src
549               | FCOS
550               | FDIV          Size Operand -- src
551               | FDIVP
552               | FIDIV         Size Addr -- src
553               | FDIVR         Size Operand -- src
554               | FDIVRP
555               | FIDIVR        Size Addr -- src
556               | FICOM         Size Addr -- src
557               | FILD          Size Addr Reg -- src, dst
558               | FIST          Size Addr -- dst
559               | FLD           Size Operand -- src
560               | FLD1
561               | FLDZ
562               | FMUL          Size Operand -- src
563               | FMULP
564               | FIMUL         Size Addr -- src
565               | FRNDINT
566               | FSIN
567               | FSQRT
568               | FST           Size Operand -- dst
569               | FSTP          Size Operand -- dst
570               | FSUB          Size Operand -- src
571               | FSUBP
572               | FISUB         Size Addr -- src
573               | FSUBR         Size Operand -- src
574               | FSUBRP
575               | FISUBR        Size Addr -- src
576               | FTST
577               | FCOMP         Size Operand -- src
578               | FUCOMPP
579               | FXCH
580               | FNSTSW
581               | FNOP
582
583 -- Comparison
584
585               | TEST          Size Operand Operand
586               | CMP           Size Operand Operand
587               | SETCC         Cond Operand
588
589 -- Stack Operations.
590
591               | PUSH          Size Operand
592               | POP           Size Operand
593
594 -- Jumping around.
595
596               | JMP           Operand -- target
597               | JXX           Cond CLabel -- target
598               | CALL          Imm
599
600 -- Other things.
601
602               | CLTD -- sign extend %eax into %edx:%eax
603
604 data Operand
605   = OpReg  Reg  -- register
606   | OpImm  Imm  -- immediate value
607   | OpAddr Addr -- memory reference
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 Addr Reg -- size, src, dst
620               | ST            Size Reg Addr -- 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           Addr -- 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}