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