9c332317ea114b48b9be59da1a085a5596085dc7
[ghc-hetmet.git] / compiler / nativeGen / SPARC / Instr.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Machine-dependent assembly language
4 --
5 -- (c) The University of Glasgow 1993-2004
6 --
7 -----------------------------------------------------------------------------
8
9 #include "HsVersions.h"
10 #include "nativeGen/NCG.h"
11
12 module SPARC.Instr (
13         Cond(..),
14         RI(..),
15         Instr(..),
16         riZero,
17         fpRelEA,
18         moveSp,
19         fPair,
20 )
21
22 where
23
24 import BlockId
25 import RegsBase
26 import SPARC.Regs
27 import Cmm
28 import Outputable
29 import Constants        ( wORD_SIZE )
30 import FastString
31
32 import GHC.Exts
33
34
35 -- | Branch condition codes.
36 data Cond
37         = ALWAYS
38         | EQQ
39         | GE
40         | GEU
41         | GTT
42         | GU
43         | LE
44         | LEU
45         | LTT
46         | LU
47         | NE
48         | NEG
49         | NEVER
50         | POS
51         | VC
52         | VS
53         deriving Eq
54
55
56 -- | Register or immediate
57 data RI 
58         = RIReg Reg
59         | RIImm Imm
60
61
62 -- | SPARC isntruction set.
63 data Instr
64
65         -- meta ops --------------------------------------------------
66         -- comment pseudo-op
67         = COMMENT FastString            
68
69         -- some static data spat out during code generation.
70         -- Will be extracted before pretty-printing.
71         | LDATA   Section [CmmStatic]   
72
73         -- Start a new basic block.  Useful during codegen, removed later.
74         -- Preceding instruction should be a jump, as per the invariants
75         -- for a BasicBlock (see Cmm).
76         | NEWBLOCK BlockId              
77
78         -- specify current stack offset for benefit of subsequent passes.
79         | DELTA   Int
80
81         -- | spill this reg to a stack slot
82         | SPILL   Reg Int
83
84         -- | reload this reg from a stack slot
85         | RELOAD  Int Reg
86
87         -- real instrs -----------------------------------------------
88         -- Loads and stores.
89         | LD            Size AddrMode Reg               -- size, src, dst
90         | ST            Size Reg AddrMode               -- size, src, dst
91
92         -- Int Arithmetic.
93         | ADD           Bool Bool Reg RI Reg            -- x?, cc?, src1, src2, dst
94         | SUB           Bool Bool Reg RI Reg            -- x?, cc?, src1, src2, dst
95
96         | UMUL          Bool Reg RI Reg                 --     cc?, src1, src2, dst
97         | SMUL          Bool Reg RI Reg                 --     cc?, src1, src2, dst
98
99
100         -- The SPARC divide instructions perform 64bit by 32bit division
101         --   The Y register is xored into the first operand.
102
103         --   On _some implementations_ the Y register is overwritten by
104         --   the remainder, so we have to make sure it is 0 each time.
105
106         --   dst <- ((Y `shiftL` 32) `or` src1) `div` src2
107         | UDIV          Bool Reg RI Reg                 --     cc?, src1, src2, dst
108         | SDIV          Bool Reg RI Reg                 --     cc?, src1, src2, dst
109
110         | RDY           Reg                             -- move contents of Y register to reg
111         | WRY           Reg  Reg                        -- Y <- src1 `xor` src2
112         
113         -- Logic operations.
114         | AND           Bool Reg RI Reg                 -- cc?, src1, src2, dst
115         | ANDN          Bool Reg RI Reg                 -- cc?, src1, src2, dst
116         | OR            Bool Reg RI Reg                 -- cc?, src1, src2, dst
117         | ORN           Bool Reg RI Reg                 -- cc?, src1, src2, dst
118         | XOR           Bool Reg RI Reg                 -- cc?, src1, src2, dst
119         | XNOR          Bool Reg RI Reg                 -- cc?, src1, src2, dst
120         | SLL           Reg RI Reg                      -- src1, src2, dst
121         | SRL           Reg RI Reg                      -- src1, src2, dst
122         | SRA           Reg RI Reg                      -- src1, src2, dst
123
124         -- Load immediates.
125         | SETHI         Imm Reg                         -- src, dst
126
127         -- Do nothing.
128         -- Implemented by the assembler as SETHI 0, %g0, but worth an alias
129         | NOP                                           
130
131         -- Float Arithmetic.
132         -- Note that we cheat by treating F{ABS,MOV,NEG} of doubles as single
133         -- instructions right up until we spit them out.
134         --
135         | FABS          Size Reg Reg                    -- src dst
136         | FADD          Size Reg Reg Reg                -- src1, src2, dst
137         | FCMP          Bool Size Reg Reg               -- exception?, src1, src2, dst
138         | FDIV          Size Reg Reg Reg                -- src1, src2, dst
139         | FMOV          Size Reg Reg                    -- src, dst
140         | FMUL          Size Reg Reg Reg                -- src1, src2, dst
141         | FNEG          Size Reg Reg                    -- src, dst
142         | FSQRT         Size Reg Reg                    -- src, dst
143         | FSUB          Size Reg Reg Reg                -- src1, src2, dst
144         | FxTOy         Size Size Reg Reg               -- src, dst
145
146         -- Jumping around.
147         | BI            Cond Bool BlockId               -- cond, annul?, target
148         | BF            Cond Bool BlockId               -- cond, annul?, target
149
150         | JMP           AddrMode                        -- target
151
152         -- With a tabled jump we know all the possible destinations.
153         -- We also need this info so we can work out what regs are live across the jump.
154         -- 
155         | JMP_TBL       AddrMode [BlockId]
156
157         | CALL          (Either Imm Reg) Int Bool       -- target, args, terminal
158
159
160 -- | Check if a RI represents a zero value.
161 --      - a literal zero
162 --      - register %g0, which is always zero.
163 --
164 riZero :: RI -> Bool
165 riZero (RIImm (ImmInt 0))           = True
166 riZero (RIImm (ImmInteger 0))       = True
167 riZero (RIReg (RealReg 0))          = True
168 riZero _                            = False
169
170
171 -- | Calculate the effective address which would be used by the
172 --      corresponding fpRel sequence.  fpRel is in MachRegs.lhs,
173 --      alas -- can't have fpRelEA here because of module dependencies.
174 fpRelEA :: Int -> Reg -> Instr
175 fpRelEA n dst
176    = ADD False False fp (RIImm (ImmInt (n * wORD_SIZE))) dst
177
178
179 -- | Code to shift the stack pointer by n words.
180 moveSp :: Int -> Instr
181 moveSp n
182    = ADD False False sp (RIImm (ImmInt (n * wORD_SIZE))) sp
183
184
185 -- | Produce the second-half-of-a-double register given the first half.
186 fPair :: Reg -> Maybe Reg
187 fPair (RealReg n) 
188         | n >= 32 && n `mod` 2 == 0  = Just (RealReg (n+1))
189
190 fPair (VirtualRegD u)
191         = Just (VirtualRegHi u)
192
193 fPair _
194         = trace ("MachInstrs.fPair: can't get high half of supposed double reg ") 
195                 Nothing