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