[project @ 1998-04-30 19:25:19 by sof]
[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#, shiftRA#, 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 i2w_s x = (x::Int#)
298
299 exactLog2 :: Integer -> Maybe Integer
300 exactLog2 x
301   = if (x <= 0 || x >= 2147483648) then
302        Nothing
303     else
304        case (fromInteger x) of { I# x# ->
305        if (w2i ((i2w x#) `and#` (i2w (0# -# x#))) /=# x#) then
306           Nothing
307        else
308           Just (toInteger (I# (pow2 x#)))
309        }
310   where
311     shiftr x y = shiftRA# x y
312
313     pow2 x# | x# ==# 1# = 0#
314             | otherwise = 1# +# pow2 (w2i (i2w x# `shiftr` i2w_s 1#))
315 \end{code}
316
317 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
318
319 \begin{code}
320 data Cond
321 #if alpha_TARGET_ARCH
322   = ALWAYS      -- For BI (same as BR)
323   | EQQ         -- For CMP and BI (NB: "EQ" is a 1.3 Prelude name)
324   | GE          -- For BI only
325   | GTT         -- For BI only (NB: "GT" is a 1.3 Prelude name)
326   | LE          -- For CMP and BI
327   | LTT         -- For CMP and BI (NB: "LT" is a 1.3 Prelude name)
328   | NE          -- For BI only
329   | NEVER       -- For BI (null instruction)
330   | ULE         -- For CMP only
331   | ULT         -- For CMP only
332 #endif
333 #if i386_TARGET_ARCH
334   = ALWAYS      -- What's really used? ToDo
335   | EQQ
336   | GE
337   | GEU
338   | GTT
339   | GU
340   | LE
341   | LEU
342   | LTT
343   | LU
344   | NE
345   | NEG
346   | POS
347 #endif
348 #if sparc_TARGET_ARCH
349   = ALWAYS      -- What's really used? ToDo
350   | EQQ
351   | GE
352   | GEU
353   | GTT
354   | GU
355   | LE
356   | LEU
357   | LTT
358   | LU
359   | NE
360   | NEG
361   | NEVER
362   | POS
363   | VC
364   | VS
365 #endif
366 \end{code}
367
368 \begin{code}
369 data Size
370 #if alpha_TARGET_ARCH
371     = B     -- byte
372     | BU
373 --  | W     -- word (2 bytes): UNUSED
374 --  | WU    -- : UNUSED
375 --  | L     -- longword (4 bytes): UNUSED
376     | Q     -- quadword (8 bytes)
377 --  | FF    -- VAX F-style floating pt: UNUSED
378 --  | GF    -- VAX G-style floating pt: UNUSED
379 --  | DF    -- VAX D-style floating pt: UNUSED
380 --  | SF    -- IEEE single-precision floating pt: UNUSED
381     | TF    -- IEEE double-precision floating pt
382 #endif
383 #if i386_TARGET_ARCH
384     = B     -- byte (lower)
385 --  | HB    -- higher byte **UNUSED**
386 --  | S     -- : UNUSED
387     | L
388     | F     -- IEEE single-precision floating pt
389     | DF    -- IEEE single-precision floating pt
390 #endif
391 #if sparc_TARGET_ARCH
392     = B     -- byte (signed)
393     | BU    -- byte (unsigned)
394 --  | HW    -- halfword, 2 bytes (signed): UNUSED
395 --  | HWU   -- halfword, 2 bytes (unsigned): UNUSED
396     | W     -- word, 4 bytes
397 --  | D     -- doubleword, 8 bytes: UNUSED
398     | F     -- IEEE single-precision floating pt
399     | DF    -- IEEE single-precision floating pt
400 #endif
401
402 primRepToSize :: PrimRep -> Size
403
404 primRepToSize PtrRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
405 primRepToSize CodePtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
406 primRepToSize DataPtrRep    = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
407 primRepToSize RetRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
408 primRepToSize CostCentreRep = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
409 primRepToSize CharRep       = IF_ARCH_alpha( BU, IF_ARCH_i386( L, IF_ARCH_sparc( BU,)))
410 primRepToSize IntRep        = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
411 primRepToSize WordRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
412 primRepToSize AddrRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
413 primRepToSize FloatRep      = IF_ARCH_alpha( TF, IF_ARCH_i386( F, IF_ARCH_sparc( F ,)))
414 primRepToSize DoubleRep     = IF_ARCH_alpha( TF, IF_ARCH_i386( DF,IF_ARCH_sparc( DF,)))
415 primRepToSize ArrayRep      = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
416 primRepToSize ByteArrayRep  = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
417 primRepToSize StablePtrRep  = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
418 primRepToSize ForeignObjRep  = IF_ARCH_alpha( Q,         IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
419 \end{code}
420
421 %************************************************************************
422 %*                                                                      *
423 \subsection{Machine's assembly language}
424 %*                                                                      *
425 %************************************************************************
426
427 We have a few common ``instructions'' (nearly all the pseudo-ops) but
428 mostly all of @Instr@ is machine-specific.
429
430 \begin{code}
431 data Instr
432   = COMMENT FAST_STRING         -- comment pseudo-op
433   | SEGMENT CodeSegment         -- {data,text} segment pseudo-op
434   | LABEL   CLabel              -- global label pseudo-op
435   | ASCII   Bool                -- True <=> needs backslash conversion
436             String              -- the literal string
437   | DATA    Size
438             [Imm]
439 \end{code}
440
441 \begin{code}
442 #if alpha_TARGET_ARCH
443
444 -- data Instr continues...
445
446 -- Loads and stores.
447
448               | LD            Size Reg MachRegsAddr -- size, dst, src
449               | LDA           Reg MachRegsAddr      -- dst, src
450               | LDAH          Reg MachRegsAddr      -- dst, src
451               | LDGP          Reg MachRegsAddr      -- dst, src
452               | LDI           Size Reg Imm     -- size, dst, src
453               | ST            Size Reg MachRegsAddr -- size, src, dst
454
455 -- Int Arithmetic.
456
457               | CLR           Reg                   -- dst
458               | ABS           Size RI Reg           -- size, src, dst
459               | NEG           Size Bool RI Reg      -- size, overflow, src, dst
460               | ADD           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
461               | SADD          Size Size Reg RI Reg  -- size, scale, src, src, dst
462               | SUB           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
463               | SSUB          Size Size Reg RI Reg  -- size, scale, src, src, dst
464               | MUL           Size Bool Reg RI Reg  -- size, overflow, src, src, dst
465               | DIV           Size Bool Reg RI Reg  -- size, unsigned, src, src, dst
466               | REM           Size Bool Reg RI Reg  -- size, unsigned, src, src, dst
467
468 -- Simple bit-twiddling.
469
470               | NOT           RI Reg
471               | AND           Reg RI Reg
472               | ANDNOT        Reg RI Reg
473               | OR            Reg RI Reg
474               | ORNOT         Reg RI Reg
475               | XOR           Reg RI Reg
476               | XORNOT        Reg RI Reg
477               | SLL           Reg RI Reg
478               | SRL           Reg RI Reg
479               | SRA           Reg RI Reg
480
481               | ZAP           Reg RI Reg
482               | ZAPNOT        Reg RI Reg
483
484               | NOP
485
486 -- Comparison
487
488               | CMP           Cond Reg RI Reg
489
490 -- Float Arithmetic.
491
492               | FCLR          Reg
493               | FABS          Reg Reg
494               | FNEG          Size Reg Reg
495               | FADD          Size Reg Reg Reg
496               | FDIV          Size Reg Reg Reg
497               | FMUL          Size Reg Reg Reg
498               | FSUB          Size Reg Reg Reg
499               | CVTxy         Size Size Reg Reg
500               | FCMP          Size Cond Reg Reg Reg
501               | FMOV          Reg Reg
502
503 -- Jumping around.
504
505               | BI            Cond Reg Imm
506               | BF            Cond Reg Imm
507               | BR            Imm
508               | JMP           Reg MachRegsAddr Int
509               | BSR           Imm Int
510               | JSR           Reg MachRegsAddr Int
511
512 -- Alpha-specific pseudo-ops.
513
514               | FUNBEGIN CLabel
515               | FUNEND CLabel
516
517 data RI
518   = RIReg Reg
519   | RIImm Imm
520
521 #endif {- alpha_TARGET_ARCH -}
522 \end{code}
523
524 \begin{code}
525 #if i386_TARGET_ARCH
526
527 -- data Instr continues...
528
529 -- Moves.
530
531               | MOV           Size Operand Operand
532               | MOVZX         Size Operand Operand -- size is the size of operand 2
533               | MOVSX         Size Operand Operand -- size is the size of operand 2
534
535 -- Load effective address (also a very useful three-operand add instruction :-)
536
537               | LEA           Size Operand Operand
538
539 -- Int Arithmetic.
540
541               | ADD           Size Operand Operand
542               | SUB           Size Operand Operand
543
544 -- Multiplication (signed and unsigned), Division (signed and unsigned),
545 -- result in %eax, %edx.
546
547               | IMUL          Size Operand Operand
548               | IDIV          Size Operand
549
550 -- Simple bit-twiddling.
551
552               | AND           Size Operand Operand
553               | OR            Size Operand Operand
554               | XOR           Size Operand Operand
555               | NOT           Size Operand
556               | NEGI          Size Operand -- NEG instruction (name clash with Cond)
557               | SHL           Size Operand Operand -- 1st operand must be an Imm or CL
558               | SAR           Size Operand Operand -- 1st operand must be an Imm or CL
559               | SHR           Size Operand Operand -- 1st operand must be an Imm or CL
560               | NOP
561
562 -- Float Arithmetic. -- ToDo for 386
563
564 -- Note that we cheat by treating F{ABS,MOV,NEG} of doubles as single instructions
565 -- right up until we spit them out.
566
567               | SAHF          -- stores ah into flags
568               | FABS
569               | FADD          Size Operand -- src
570               | FADDP
571               | FIADD         Size MachRegsAddr -- src
572               | FCHS
573               | FCOM          Size Operand -- src
574               | FCOS
575               | FDIV          Size Operand -- src
576               | FDIVP
577               | FIDIV         Size MachRegsAddr -- src
578               | FDIVR         Size Operand -- src
579               | FDIVRP
580               | FIDIVR        Size MachRegsAddr -- src
581               | FICOM         Size MachRegsAddr -- src
582               | FILD          Size MachRegsAddr Reg -- src, dst
583               | FIST          Size MachRegsAddr -- dst
584               | FLD           Size Operand -- src
585               | FLD1
586               | FLDZ
587               | FMUL          Size Operand -- src
588               | FMULP
589               | FIMUL         Size MachRegsAddr -- src
590               | FRNDINT
591               | FSIN
592               | FSQRT
593               | FST           Size Operand -- dst
594               | FSTP          Size Operand -- dst
595               | FSUB          Size Operand -- src
596               | FSUBP
597               | FISUB         Size MachRegsAddr -- src
598               | FSUBR         Size Operand -- src
599               | FSUBRP
600               | FISUBR        Size MachRegsAddr -- src
601               | FTST
602               | FCOMP         Size Operand -- src
603               | FUCOMPP
604               | FXCH
605               | FNSTSW
606               | FNOP
607
608 -- Comparison
609
610               | TEST          Size Operand Operand
611               | CMP           Size Operand Operand
612               | SETCC         Cond Operand
613
614 -- Stack Operations.
615
616               | PUSH          Size Operand
617               | POP           Size Operand
618
619 -- Jumping around.
620
621               | JMP           Operand -- target
622               | JXX           Cond CLabel -- target
623               | CALL          Imm
624
625 -- Other things.
626
627               | CLTD -- sign extend %eax into %edx:%eax
628
629 data Operand
630   = OpReg  Reg          -- register
631   | OpImm  Imm          -- immediate value
632   | OpAddr MachRegsAddr -- memory reference
633
634 #endif {- i386_TARGET_ARCH -}
635 \end{code}
636
637 \begin{code}
638 #if sparc_TARGET_ARCH
639
640 -- data Instr continues...
641
642 -- Loads and stores.
643
644               | LD            Size MachRegsAddr Reg -- size, src, dst
645               | ST            Size Reg MachRegsAddr -- size, src, dst
646
647 -- Int Arithmetic.
648
649               | ADD           Bool Bool Reg RI Reg -- x?, cc?, src1, src2, dst
650               | SUB           Bool Bool Reg RI Reg -- x?, cc?, src1, src2, dst
651
652 -- Simple bit-twiddling.
653
654               | AND           Bool Reg RI Reg -- cc?, src1, src2, dst
655               | ANDN          Bool Reg RI Reg -- cc?, src1, src2, dst
656               | OR            Bool Reg RI Reg -- cc?, src1, src2, dst
657               | ORN           Bool Reg RI Reg -- cc?, src1, src2, dst
658               | XOR           Bool Reg RI Reg -- cc?, src1, src2, dst
659               | XNOR          Bool Reg RI Reg -- cc?, src1, src2, dst
660               | SLL           Reg RI Reg -- src1, src2, dst
661               | SRL           Reg RI Reg -- src1, src2, dst
662               | SRA           Reg RI Reg -- src1, src2, dst
663               | SETHI         Imm Reg -- src, dst
664               | NOP           -- Really SETHI 0, %g0, but worth an alias
665
666 -- Float Arithmetic.
667
668 -- Note that we cheat by treating F{ABS,MOV,NEG} of doubles as single instructions
669 -- right up until we spit them out.
670
671               | FABS          Size Reg Reg -- src dst
672               | FADD          Size Reg Reg Reg -- src1, src2, dst
673               | FCMP          Bool Size Reg Reg -- exception?, src1, src2, dst
674               | FDIV          Size Reg Reg Reg -- src1, src2, dst
675               | FMOV          Size Reg Reg -- src, dst
676               | FMUL          Size Reg Reg Reg -- src1, src2, dst
677               | FNEG          Size Reg Reg -- src, dst
678               | FSQRT         Size Reg Reg -- src, dst
679               | FSUB          Size Reg Reg Reg -- src1, src2, dst
680               | FxTOy         Size Size Reg Reg -- src, dst
681
682 -- Jumping around.
683
684               | BI            Cond Bool Imm -- cond, annul?, target
685               | BF            Cond Bool Imm -- cond, annul?, target
686
687               | JMP           MachRegsAddr      -- target
688               | CALL          Imm Int Bool -- target, args, terminal
689
690 data RI = RIReg Reg
691         | RIImm Imm
692
693 riZero :: RI -> Bool
694
695 riZero (RIImm (ImmInt 0))           = True
696 riZero (RIImm (ImmInteger 0))       = True
697 riZero (RIReg (FixedReg ILIT(0)))   = True
698 riZero _                            = False
699
700 #endif {- sparc_TARGET_ARCH -}
701 \end{code}