File: TargetReg.hs

package info (click to toggle)
ghc 7.10.3-4~bpo8%2B1
  • links: PTS, VCS
  • area: main
  • in suites: jessie-backports
  • size: 55,924 kB
  • sloc: haskell: 321,892; ansic: 54,199; xml: 36,271; sh: 4,902; makefile: 975; perl: 507; python: 290; asm: 133; lisp: 7
file content (131 lines) | stat: -rw-r--r-- 5,488 bytes parent folder | download | duplicates (2)
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
{-# LANGUAGE CPP #-}
-- | Hard wired things related to registers.
--      This is module is preventing the native code generator being able to
--      emit code for non-host architectures.
--
--      TODO: Do a better job of the overloading, and eliminate this module.
--      We'd probably do better with a Register type class, and hook this to
--      Instruction somehow.
--
--      TODO: We should also make arch specific versions of RegAlloc.Graph.TrivColorable
module TargetReg (
        targetVirtualRegSqueeze,
        targetRealRegSqueeze,
        targetClassOfRealReg,
        targetMkVirtualReg,
        targetRegDotColor,
        targetClassOfReg
)

where

#include "HsVersions.h"

import Reg
import RegClass
import Size

import Outputable
import Unique
import FastTypes
import Platform

import qualified X86.Regs       as X86
import qualified X86.RegInfo    as X86

import qualified PPC.Regs       as PPC

import qualified SPARC.Regs     as SPARC

targetVirtualRegSqueeze :: Platform -> RegClass -> VirtualReg -> FastInt
targetVirtualRegSqueeze platform
    = case platformArch platform of
      ArchX86       -> X86.virtualRegSqueeze
      ArchX86_64    -> X86.virtualRegSqueeze
      ArchPPC       -> PPC.virtualRegSqueeze
      ArchSPARC     -> SPARC.virtualRegSqueeze
      ArchSPARC64   -> panic "targetVirtualRegSqueeze ArchSPARC64"
      ArchPPC_64    -> panic "targetVirtualRegSqueeze ArchPPC_64"
      ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM"
      ArchARM64     -> panic "targetVirtualRegSqueeze ArchARM64"
      ArchAlpha     -> panic "targetVirtualRegSqueeze ArchAlpha"
      ArchMipseb    -> panic "targetVirtualRegSqueeze ArchMipseb"
      ArchMipsel    -> panic "targetVirtualRegSqueeze ArchMipsel"
      ArchJavaScript-> panic "targetVirtualRegSqueeze ArchJavaScript"
      ArchUnknown   -> panic "targetVirtualRegSqueeze ArchUnknown"


targetRealRegSqueeze :: Platform -> RegClass -> RealReg -> FastInt
targetRealRegSqueeze platform
    = case platformArch platform of
      ArchX86       -> X86.realRegSqueeze
      ArchX86_64    -> X86.realRegSqueeze
      ArchPPC       -> PPC.realRegSqueeze
      ArchSPARC     -> SPARC.realRegSqueeze
      ArchSPARC64   -> panic "targetRealRegSqueeze ArchSPARC64"
      ArchPPC_64    -> panic "targetRealRegSqueeze ArchPPC_64"
      ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM"
      ArchARM64     -> panic "targetRealRegSqueeze ArchARM64"
      ArchAlpha     -> panic "targetRealRegSqueeze ArchAlpha"
      ArchMipseb    -> panic "targetRealRegSqueeze ArchMipseb"
      ArchMipsel    -> panic "targetRealRegSqueeze ArchMipsel"
      ArchJavaScript-> panic "targetRealRegSqueeze ArchJavaScript"
      ArchUnknown   -> panic "targetRealRegSqueeze ArchUnknown"

targetClassOfRealReg :: Platform -> RealReg -> RegClass
targetClassOfRealReg platform
    = case platformArch platform of
      ArchX86       -> X86.classOfRealReg platform
      ArchX86_64    -> X86.classOfRealReg platform
      ArchPPC       -> PPC.classOfRealReg
      ArchSPARC     -> SPARC.classOfRealReg
      ArchSPARC64   -> panic "targetClassOfRealReg ArchSPARC64"
      ArchPPC_64    -> panic "targetClassOfRealReg ArchPPC_64"
      ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM"
      ArchARM64     -> panic "targetClassOfRealReg ArchARM64"
      ArchAlpha     -> panic "targetClassOfRealReg ArchAlpha"
      ArchMipseb    -> panic "targetClassOfRealReg ArchMipseb"
      ArchMipsel    -> panic "targetClassOfRealReg ArchMipsel"
      ArchJavaScript-> panic "targetClassOfRealReg ArchJavaScript"
      ArchUnknown   -> panic "targetClassOfRealReg ArchUnknown"

targetMkVirtualReg :: Platform -> Unique -> Size -> VirtualReg
targetMkVirtualReg platform
    = case platformArch platform of
      ArchX86       -> X86.mkVirtualReg
      ArchX86_64    -> X86.mkVirtualReg
      ArchPPC       -> PPC.mkVirtualReg
      ArchSPARC     -> SPARC.mkVirtualReg
      ArchSPARC64   -> panic "targetMkVirtualReg ArchSPARC64"
      ArchPPC_64    -> panic "targetMkVirtualReg ArchPPC_64"
      ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM"
      ArchARM64     -> panic "targetMkVirtualReg ArchARM64"
      ArchAlpha     -> panic "targetMkVirtualReg ArchAlpha"
      ArchMipseb    -> panic "targetMkVirtualReg ArchMipseb"
      ArchMipsel    -> panic "targetMkVirtualReg ArchMipsel"
      ArchJavaScript-> panic "targetMkVirtualReg ArchJavaScript"
      ArchUnknown   -> panic "targetMkVirtualReg ArchUnknown"

targetRegDotColor :: Platform -> RealReg -> SDoc
targetRegDotColor platform
    = case platformArch platform of
      ArchX86       -> X86.regDotColor platform
      ArchX86_64    -> X86.regDotColor platform
      ArchPPC       -> PPC.regDotColor
      ArchSPARC     -> SPARC.regDotColor
      ArchSPARC64   -> panic "targetRegDotColor ArchSPARC64"
      ArchPPC_64    -> panic "targetRegDotColor ArchPPC_64"
      ArchARM _ _ _ -> panic "targetRegDotColor ArchARM"
      ArchARM64     -> panic "targetRegDotColor ArchARM64"
      ArchAlpha     -> panic "targetRegDotColor ArchAlpha"
      ArchMipseb    -> panic "targetRegDotColor ArchMipseb"
      ArchMipsel    -> panic "targetRegDotColor ArchMipsel"
      ArchJavaScript-> panic "targetRegDotColor ArchJavaScript"
      ArchUnknown   -> panic "targetRegDotColor ArchUnknown"


targetClassOfReg :: Platform -> Reg -> RegClass
targetClassOfReg platform reg
 = case reg of
   RegVirtual vr -> classOfVirtualReg vr
   RegReal rr -> targetClassOfRealReg platform rr