summaryrefslogtreecommitdiff
path: root/compiler/nativeGen/X86/Regs.hs
blob: f0e4c7d5f69769bca5cb7d28d89883a0ff4184be (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
{-# LANGUAGE CPP #-}

module X86.Regs (
        -- squeese functions for the graph allocator
        virtualRegSqueeze,
        realRegSqueeze,

        -- immediates
        Imm(..),
        strImmLit,
        litToImm,

        -- addressing modes
        AddrMode(..),
        addrOffset,

        -- registers
        spRel,
        argRegs,
        allArgRegs,
        allIntArgRegs,
        callClobberedRegs,
        instrClobberedRegs,
        allMachRegNos,
        classOfRealReg,
        showReg,

        -- machine specific
        EABase(..), EAIndex(..), addrModeRegs,

        eax, ebx, ecx, edx, esi, edi, ebp, esp,


        rax, rbx, rcx, rdx, rsi, rdi, rbp, rsp,
        r8,  r9,  r10, r11, r12, r13, r14, r15,
        lastint,
        xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
        xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15,
        xmm,
        firstxmm, lastxmm,

        ripRel,
        allFPArgRegs,

        allocatableRegs
)

where

#include "nativeGen/NCG.h"
#include "HsVersions.h"

import GhcPrelude

import CodeGen.Platform
import Reg
import RegClass

import Cmm
import CLabel           ( CLabel )
import DynFlags
import Outputable
import GHC.Platform

import qualified Data.Array as A

-- | regSqueeze_class reg
--      Calculate the maximum number of register colors that could be
--      denied to a node of this class due to having this reg
--      as a neighbour.
--
{-# INLINE virtualRegSqueeze #-}
virtualRegSqueeze :: RegClass -> VirtualReg -> Int

virtualRegSqueeze cls vr
 = case cls of
        RcInteger
         -> case vr of
                VirtualRegI{}           -> 1
                VirtualRegHi{}          -> 1
                _other                  -> 0

        RcDouble
         -> case vr of
                VirtualRegD{}           -> 1
                VirtualRegF{}           -> 0
                VirtualRegVec{}         -> 1
                _other                  -> 0


        _other -> 0

{-# INLINE realRegSqueeze #-}
realRegSqueeze :: RegClass -> RealReg -> Int
realRegSqueeze cls rr
 = case cls of
        RcInteger
         -> case rr of
                RealRegSingle regNo
                        | regNo < firstxmm -> 1
                        | otherwise     -> 0

                RealRegPair{}           -> 0

        RcDouble
         -> case rr of
                RealRegSingle regNo
                        | regNo >= firstxmm  -> 1
                        | otherwise     -> 0

                RealRegPair{}           -> 0


        _other -> 0

-- -----------------------------------------------------------------------------
-- Immediates

data Imm
  = ImmInt      Int
  | ImmInteger  Integer     -- Sigh.
  | ImmCLbl     CLabel      -- AbstractC Label (with baggage)
  | ImmLit      SDoc        -- Simple string
  | ImmIndex    CLabel Int
  | ImmFloat    Rational
  | ImmDouble   Rational
  | ImmConstantSum Imm Imm
  | ImmConstantDiff Imm Imm

strImmLit :: String -> Imm
strImmLit s = ImmLit (text s)


litToImm :: CmmLit -> Imm
litToImm (CmmInt i w)        = ImmInteger (narrowS w i)
                -- narrow to the width: a CmmInt might be out of
                -- range, but we assume that ImmInteger only contains
                -- in-range values.  A signed value should be fine here.
litToImm (CmmFloat f W32)    = ImmFloat f
litToImm (CmmFloat f W64)    = ImmDouble f
litToImm (CmmLabel l)        = ImmCLbl l
litToImm (CmmLabelOff l off) = ImmIndex l off
litToImm (CmmLabelDiffOff l1 l2 off _)
                             = ImmConstantSum
                               (ImmConstantDiff (ImmCLbl l1) (ImmCLbl l2))
                               (ImmInt off)
litToImm _                   = panic "X86.Regs.litToImm: no match"

-- addressing modes ------------------------------------------------------------

data AddrMode
        = AddrBaseIndex EABase EAIndex Displacement
        | ImmAddr Imm Int

data EABase       = EABaseNone  | EABaseReg Reg | EABaseRip
data EAIndex      = EAIndexNone | EAIndex Reg Int
type Displacement = Imm


addrOffset :: AddrMode -> Int -> Maybe AddrMode
addrOffset addr off
  = case addr of
      ImmAddr i off0      -> Just (ImmAddr i (off0 + off))

      AddrBaseIndex r i (ImmInt n) -> Just (AddrBaseIndex r i (ImmInt (n + off)))
      AddrBaseIndex r i (ImmInteger n)
        -> Just (AddrBaseIndex r i (ImmInt (fromInteger (n + toInteger off))))

      AddrBaseIndex r i (ImmCLbl lbl)
        -> Just (AddrBaseIndex r i (ImmIndex lbl off))

      AddrBaseIndex r i (ImmIndex lbl ix)
        -> Just (AddrBaseIndex r i (ImmIndex lbl (ix+off)))

      _ -> Nothing  -- in theory, shouldn't happen


addrModeRegs :: AddrMode -> [Reg]
addrModeRegs (AddrBaseIndex b i _) =  b_regs ++ i_regs
  where
   b_regs = case b of { EABaseReg r -> [r]; _ -> [] }
   i_regs = case i of { EAIndex r _ -> [r]; _ -> [] }
addrModeRegs _ = []


-- registers -------------------------------------------------------------------

-- @spRel@ gives us a stack relative addressing mode for volatile
-- temporaries and for excess call arguments.  @fpRel@, where
-- applicable, is the same but for the frame pointer.


spRel :: DynFlags
      -> Int -- ^ desired stack offset in bytes, positive or negative
      -> AddrMode
spRel dflags n
 | target32Bit (targetPlatform dflags)
    = AddrBaseIndex (EABaseReg esp) EAIndexNone (ImmInt n)
 | otherwise
    = AddrBaseIndex (EABaseReg rsp) EAIndexNone (ImmInt n)

-- The register numbers must fit into 32 bits on x86, so that we can
-- use a Word32 to represent the set of free registers in the register
-- allocator.



firstxmm :: RegNo
firstxmm  = 16

--  on 32bit platformOSs, only the first 8 XMM/YMM/ZMM registers are available
lastxmm :: Platform -> RegNo
lastxmm platform
 | target32Bit platform = firstxmm + 7  -- xmm0 - xmmm7
 | otherwise            = firstxmm + 15 -- xmm0 -xmm15

lastint :: Platform -> RegNo
lastint platform
 | target32Bit platform = 7 -- not %r8..%r15
 | otherwise            = 15

intregnos :: Platform -> [RegNo]
intregnos platform = [0 .. lastint platform]



xmmregnos :: Platform -> [RegNo]
xmmregnos platform = [firstxmm  .. lastxmm platform]

floatregnos :: Platform -> [RegNo]
floatregnos platform = xmmregnos platform

-- argRegs is the set of regs which are read for an n-argument call to C.
-- For archs which pass all args on the stack (x86), is empty.
-- Sparc passes up to the first 6 args in regs.
argRegs :: RegNo -> [Reg]
argRegs _       = panic "MachRegs.argRegs(x86): should not be used!"

-- | The complete set of machine registers.
allMachRegNos :: Platform -> [RegNo]
allMachRegNos platform = intregnos platform ++ floatregnos platform

-- | Take the class of a register.
{-# INLINE classOfRealReg #-}
classOfRealReg :: Platform -> RealReg -> RegClass
-- On x86, we might want to have an 8-bit RegClass, which would
-- contain just regs 1-4 (the others don't have 8-bit versions).
-- However, we can get away without this at the moment because the
-- only allocatable integer regs are also 8-bit compatible (1, 3, 4).
classOfRealReg platform reg
    = case reg of
        RealRegSingle i
            | i <= lastint platform -> RcInteger
            | i <= lastxmm platform -> RcDouble
            | otherwise             -> panic "X86.Reg.classOfRealReg registerSingle too high"
        _   -> panic "X86.Regs.classOfRealReg: RegPairs on this arch"

-- | Get the name of the register with this number.
-- NOTE: fixme, we dont track which "way" the XMM registers are used
showReg :: Platform -> RegNo -> String
showReg platform n
        | n >= firstxmm && n <= lastxmm  platform = "%xmm" ++ show (n-firstxmm)
        | n >= 8   && n < firstxmm      = "%r" ++ show n
        | otherwise      = regNames platform A.! n

regNames :: Platform -> A.Array Int String
regNames platform
    = if target32Bit platform
      then A.listArray (0,8) ["%eax", "%ebx", "%ecx", "%edx", "%esi", "%edi", "%ebp", "%esp"]
      else A.listArray (0,8) ["%rax", "%rbx", "%rcx", "%rdx", "%rsi", "%rdi", "%rbp", "%rsp"]



-- machine specific ------------------------------------------------------------


{-
Intel x86 architecture:
- All registers except 7 (esp) are available for use.
- Only ebx, esi, edi and esp are available across a C call (they are callee-saves).
- Registers 0-7 have 16-bit counterparts (ax, bx etc.)
- Registers 0-3 have 8 bit counterparts (ah, bh etc.)

The fp registers are all Double registers; we don't have any RcFloat class
regs.  @regClass@ barfs if you give it a VirtualRegF, and mkVReg above should
never generate them.

TODO: cleanup modelling float vs double registers and how they are the same class.
-}


eax, ebx, ecx, edx, esp, ebp, esi, edi :: Reg

eax   = regSingle 0
ebx   = regSingle 1
ecx   = regSingle 2
edx   = regSingle 3
esi   = regSingle 4
edi   = regSingle 5
ebp   = regSingle 6
esp   = regSingle 7




{-
AMD x86_64 architecture:
- All 16 integer registers are addressable as 8, 16, 32 and 64-bit values:

  8     16    32    64
  ---------------------
  al    ax    eax   rax
  bl    bx    ebx   rbx
  cl    cx    ecx   rcx
  dl    dx    edx   rdx
  sil   si    esi   rsi
  dil   si    edi   rdi
  bpl   bp    ebp   rbp
  spl   sp    esp   rsp
  r10b  r10w  r10d  r10
  r11b  r11w  r11d  r11
  r12b  r12w  r12d  r12
  r13b  r13w  r13d  r13
  r14b  r14w  r14d  r14
  r15b  r15w  r15d  r15
-}

rax, rbx, rcx, rdx, rsp, rbp, rsi, rdi,
  r8, r9, r10, r11, r12, r13, r14, r15,
  xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
  xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15 :: Reg

rax   = regSingle 0
rbx   = regSingle 1
rcx   = regSingle 2
rdx   = regSingle 3
rsi   = regSingle 4
rdi   = regSingle 5
rbp   = regSingle 6
rsp   = regSingle 7
r8    = regSingle 8
r9    = regSingle 9
r10   = regSingle 10
r11   = regSingle 11
r12   = regSingle 12
r13   = regSingle 13
r14   = regSingle 14
r15   = regSingle 15
xmm0  = regSingle 16
xmm1  = regSingle 17
xmm2  = regSingle 18
xmm3  = regSingle 19
xmm4  = regSingle 20
xmm5  = regSingle 21
xmm6  = regSingle 22
xmm7  = regSingle 23
xmm8  = regSingle 24
xmm9  = regSingle 25
xmm10 = regSingle 26
xmm11 = regSingle 27
xmm12 = regSingle 28
xmm13 = regSingle 29
xmm14 = regSingle 30
xmm15 = regSingle 31

ripRel :: Displacement -> AddrMode
ripRel imm      = AddrBaseIndex EABaseRip EAIndexNone imm


 -- so we can re-use some x86 code:
{-
eax = rax
ebx = rbx
ecx = rcx
edx = rdx
esi = rsi
edi = rdi
ebp = rbp
esp = rsp
-}

xmm :: RegNo -> Reg
xmm n = regSingle (firstxmm+n)




-- | these are the regs which we cannot assume stay alive over a C call.
callClobberedRegs       :: Platform -> [Reg]
-- caller-saves registers
callClobberedRegs platform
 | target32Bit platform = [eax,ecx,edx] ++ map regSingle (floatregnos platform)
 | platformOS platform == OSMinGW32
   = [rax,rcx,rdx,r8,r9,r10,r11]
   -- Only xmm0-5 are caller-saves registers on 64bit windows.
   -- ( https://docs.microsoft.com/en-us/cpp/build/register-usage )
   -- For details check the Win64 ABI.
   ++ map xmm [0  .. 5]
 | otherwise
    -- all xmm regs are caller-saves
    -- caller-saves registers
    = [rax,rcx,rdx,rsi,rdi,r8,r9,r10,r11]
   ++ map regSingle (floatregnos platform)

allArgRegs :: Platform -> [(Reg, Reg)]
allArgRegs platform
 | platformOS platform == OSMinGW32 = zip [rcx,rdx,r8,r9]
                                          (map regSingle [firstxmm ..])
 | otherwise = panic "X86.Regs.allArgRegs: not defined for this arch"

allIntArgRegs :: Platform -> [Reg]
allIntArgRegs platform
 | (platformOS platform == OSMinGW32) || target32Bit platform
    = panic "X86.Regs.allIntArgRegs: not defined for this platform"
 | otherwise = [rdi,rsi,rdx,rcx,r8,r9]


-- | on 64bit platforms we pass the first 8 float/double arguments
-- in the xmm registers.
allFPArgRegs :: Platform -> [Reg]
allFPArgRegs platform
 | platformOS platform == OSMinGW32
    = panic "X86.Regs.allFPArgRegs: not defined for this platform"
 | otherwise = map regSingle [firstxmm .. firstxmm + 7 ]


-- Machine registers which might be clobbered by instructions that
-- generate results into fixed registers, or need arguments in a fixed
-- register.
instrClobberedRegs :: Platform -> [Reg]
instrClobberedRegs platform
 | target32Bit platform = [ eax, ecx, edx ]
 | otherwise            = [ rax, rcx, rdx ]

--

-- allocatableRegs is allMachRegNos with the fixed-use regs removed.
-- i.e., these are the regs for which we are prepared to allow the
-- register allocator to attempt to map VRegs to.
allocatableRegs :: Platform -> [RealReg]
allocatableRegs platform
   = let isFree i = freeReg platform i
     in  map RealRegSingle $ filter isFree (allMachRegNos platform)