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