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