Skip to content

Commit 3144f85

Browse files
kgardassimonmar
authored andcommitted
add support for ARM hard-float ABI (fixes #5914)
This patch enhances Platform's ArchARM to include ARM ABI value. It also tweaks configure machinery to detect hard-float ABI and to set it wherever needed. Finally when hard-float ABI is in use, pass appropriate compiler option to the LLVM's llc. Fixes #5914.
1 parent 18c2a2f commit 3144f85

File tree

10 files changed

+345
-337
lines changed

10 files changed

+345
-337
lines changed

aclocal.m4

+1-1
Original file line numberDiff line numberDiff line change
@@ -171,7 +171,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS],
171171
;;
172172
arm)
173173
GET_ARM_ISA()
174-
test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT}\""
174+
test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\""
175175
;;
176176
alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax)
177177
test -z "[$]2" || eval "[$]2=ArchUnknown"

compiler/main/DriverPipeline.hs

+12-4
Original file line numberDiff line numberDiff line change
@@ -1372,7 +1372,8 @@ runPhase LlvmLlc input_fn dflags
13721372
SysTools.Option "-o", SysTools.FileOption "" output_fn]
13731373
++ map SysTools.Option lc_opts
13741374
++ [SysTools.Option tbaa]
1375-
++ map SysTools.Option fpOpts)
1375+
++ map SysTools.Option fpOpts
1376+
++ map SysTools.Option abiOpts)
13761377

13771378
return (next_phase, output_fn)
13781379
where
@@ -1384,12 +1385,19 @@ runPhase LlvmLlc input_fn dflags
13841385
-- while compiling GHC source code. It's probably due to fact that it
13851386
-- does not enable VFP by default. Let's do this manually here
13861387
fpOpts = case platformArch (targetPlatform dflags) of
1387-
ArchARM ARMv7 ext -> if (elem VFPv3 ext)
1388+
ArchARM ARMv7 ext _ -> if (elem VFPv3 ext)
13881389
then ["-mattr=+v7,+vfp3"]
13891390
else if (elem VFPv3D16 ext)
13901391
then ["-mattr=+v7,+vfp3,+d16"]
13911392
else []
13921393
_ -> []
1394+
-- On Ubuntu/Debian with ARM hard float ABI, LLVM's llc still
1395+
-- compiles into soft-float ABI. We need to explicitly set abi
1396+
-- to hard
1397+
abiOpts = case platformArch (targetPlatform dflags) of
1398+
ArchARM ARMv7 _ HARD -> ["-float-abi=hard"]
1399+
ArchARM ARMv7 _ _ -> []
1400+
_ -> []
13931401

13941402
-----------------------------------------------------------------------------
13951403
-- LlvmMangle phase
@@ -1538,8 +1546,8 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do
15381546

15391547
elfSectionNote :: String
15401548
elfSectionNote = case platformArch (targetPlatform dflags) of
1541-
ArchARM _ _ -> "%note"
1542-
_ -> "@note"
1549+
ArchARM _ _ _ -> "%note"
1550+
_ -> "@note"
15431551

15441552
-- The "link info" is a string representing the parameters of the
15451553
-- link. We save this information in the binary, and the next time we

compiler/nativeGen/AsmCodeGen.lhs

+1-1
Original file line numberDiff line numberDiff line change
@@ -200,7 +200,7 @@ nativeCodeGen dflags h us cmms
200200
,ncgExpandTop = map SPARC.CodeGen.Expand.expandTop
201201
,ncgMakeFarBranches = id
202202
}
203-
ArchARM _ _ ->
203+
ArchARM _ _ _ ->
204204
panic "nativeCodeGen: No NCG for ARM"
205205
ArchPPC_64 ->
206206
panic "nativeCodeGen: No NCG for PPC 64"

compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs

+28-28
Original file line numberDiff line numberDiff line change
@@ -107,13 +107,13 @@ trivColorable
107107
trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts exclusions
108108
| let !cALLOCATABLE_REGS_INTEGER
109109
= iUnbox (case platformArch platform of
110-
ArchX86 -> 3
111-
ArchX86_64 -> 5
112-
ArchPPC -> 16
113-
ArchSPARC -> 14
114-
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
115-
ArchARM _ _ -> panic "trivColorable ArchARM"
116-
ArchUnknown -> panic "trivColorable ArchUnknown")
110+
ArchX86 -> 3
111+
ArchX86_64 -> 5
112+
ArchPPC -> 16
113+
ArchSPARC -> 14
114+
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
115+
ArchARM _ _ _ -> panic "trivColorable ArchARM"
116+
ArchUnknown -> panic "trivColorable ArchUnknown")
117117
, count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_INTEGER
118118
(virtualRegSqueeze RcInteger)
119119
conflicts
@@ -127,13 +127,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl
127127
trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclusions
128128
| let !cALLOCATABLE_REGS_FLOAT
129129
= iUnbox (case platformArch platform of
130-
ArchX86 -> 0
131-
ArchX86_64 -> 0
132-
ArchPPC -> 0
133-
ArchSPARC -> 22
134-
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
135-
ArchARM _ _ -> panic "trivColorable ArchARM"
136-
ArchUnknown -> panic "trivColorable ArchUnknown")
130+
ArchX86 -> 0
131+
ArchX86_64 -> 0
132+
ArchPPC -> 0
133+
ArchSPARC -> 22
134+
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
135+
ArchARM _ _ _ -> panic "trivColorable ArchARM"
136+
ArchUnknown -> panic "trivColorable ArchUnknown")
137137
, count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_FLOAT
138138
(virtualRegSqueeze RcFloat)
139139
conflicts
@@ -147,13 +147,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus
147147
trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclusions
148148
| let !cALLOCATABLE_REGS_DOUBLE
149149
= iUnbox (case platformArch platform of
150-
ArchX86 -> 6
151-
ArchX86_64 -> 0
152-
ArchPPC -> 26
153-
ArchSPARC -> 11
154-
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
155-
ArchARM _ _ -> panic "trivColorable ArchARM"
156-
ArchUnknown -> panic "trivColorable ArchUnknown")
150+
ArchX86 -> 6
151+
ArchX86_64 -> 0
152+
ArchPPC -> 26
153+
ArchSPARC -> 11
154+
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
155+
ArchARM _ _ _ -> panic "trivColorable ArchARM"
156+
ArchUnknown -> panic "trivColorable ArchUnknown")
157157
, count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_DOUBLE
158158
(virtualRegSqueeze RcDouble)
159159
conflicts
@@ -167,13 +167,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu
167167
trivColorable platform virtualRegSqueeze realRegSqueeze RcDoubleSSE conflicts exclusions
168168
| let !cALLOCATABLE_REGS_SSE
169169
= iUnbox (case platformArch platform of
170-
ArchX86 -> 8
171-
ArchX86_64 -> 10
172-
ArchPPC -> 0
173-
ArchSPARC -> 0
174-
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
175-
ArchARM _ _ -> panic "trivColorable ArchARM"
176-
ArchUnknown -> panic "trivColorable ArchUnknown")
170+
ArchX86 -> 8
171+
ArchX86_64 -> 10
172+
ArchPPC -> 0
173+
ArchSPARC -> 0
174+
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
175+
ArchARM _ _ _ -> panic "trivColorable ArchARM"
176+
ArchUnknown -> panic "trivColorable ArchUnknown")
177177
, count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_SSE
178178
(virtualRegSqueeze RcDoubleSSE)
179179
conflicts

compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs

+7-7
Original file line numberDiff line numberDiff line change
@@ -68,11 +68,11 @@ instance FR SPARC.FreeRegs where
6868
maxSpillSlots :: Platform -> Int
6969
maxSpillSlots platform
7070
= case platformArch platform of
71-
ArchX86 -> X86.Instr.maxSpillSlots True -- 32bit
72-
ArchX86_64 -> X86.Instr.maxSpillSlots False -- not 32bit
73-
ArchPPC -> PPC.Instr.maxSpillSlots
74-
ArchSPARC -> SPARC.Instr.maxSpillSlots
75-
ArchARM _ _ -> panic "maxSpillSlots ArchARM"
76-
ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64"
77-
ArchUnknown -> panic "maxSpillSlots ArchUnknown"
71+
ArchX86 -> X86.Instr.maxSpillSlots True -- 32bit
72+
ArchX86_64 -> X86.Instr.maxSpillSlots False -- not 32bit
73+
ArchPPC -> PPC.Instr.maxSpillSlots
74+
ArchSPARC -> SPARC.Instr.maxSpillSlots
75+
ArchARM _ _ _ -> panic "maxSpillSlots ArchARM"
76+
ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64"
77+
ArchUnknown -> panic "maxSpillSlots ArchUnknown"
7878

compiler/nativeGen/RegAlloc/Linear/Main.hs

+7-7
Original file line numberDiff line numberDiff line change
@@ -180,13 +180,13 @@ linearRegAlloc
180180
linearRegAlloc dflags first_id block_live sccs
181181
= let platform = targetPlatform dflags
182182
in case platformArch platform of
183-
ArchX86 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs
184-
ArchX86_64 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs
185-
ArchSPARC -> linearRegAlloc' platform (frInitFreeRegs :: SPARC.FreeRegs) first_id block_live sccs
186-
ArchPPC -> linearRegAlloc' platform (frInitFreeRegs :: PPC.FreeRegs) first_id block_live sccs
187-
ArchARM _ _ -> panic "linearRegAlloc ArchARM"
188-
ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64"
189-
ArchUnknown -> panic "linearRegAlloc ArchUnknown"
183+
ArchX86 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs
184+
ArchX86_64 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs
185+
ArchSPARC -> linearRegAlloc' platform (frInitFreeRegs :: SPARC.FreeRegs) first_id block_live sccs
186+
ArchPPC -> linearRegAlloc' platform (frInitFreeRegs :: PPC.FreeRegs) first_id block_live sccs
187+
ArchARM _ _ _ -> panic "linearRegAlloc ArchARM"
188+
ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64"
189+
ArchUnknown -> panic "linearRegAlloc ArchUnknown"
190190

191191
linearRegAlloc'
192192
:: (FR freeRegs, PlatformOutputable instr, Instruction instr)

compiler/nativeGen/TargetReg.hs

+35-35
Original file line numberDiff line numberDiff line change
@@ -50,35 +50,35 @@ import qualified SPARC.Regs as SPARC
5050
targetVirtualRegSqueeze :: Platform -> RegClass -> VirtualReg -> FastInt
5151
targetVirtualRegSqueeze platform
5252
= case platformArch platform of
53-
ArchX86 -> X86.virtualRegSqueeze
54-
ArchX86_64 -> X86.virtualRegSqueeze
55-
ArchPPC -> PPC.virtualRegSqueeze
56-
ArchSPARC -> SPARC.virtualRegSqueeze
57-
ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64"
58-
ArchARM _ _ -> panic "targetVirtualRegSqueeze ArchARM"
59-
ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown"
53+
ArchX86 -> X86.virtualRegSqueeze
54+
ArchX86_64 -> X86.virtualRegSqueeze
55+
ArchPPC -> PPC.virtualRegSqueeze
56+
ArchSPARC -> SPARC.virtualRegSqueeze
57+
ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64"
58+
ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM"
59+
ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown"
6060

6161
targetRealRegSqueeze :: Platform -> RegClass -> RealReg -> FastInt
6262
targetRealRegSqueeze platform
6363
= case platformArch platform of
64-
ArchX86 -> X86.realRegSqueeze
65-
ArchX86_64 -> X86.realRegSqueeze
66-
ArchPPC -> PPC.realRegSqueeze
67-
ArchSPARC -> SPARC.realRegSqueeze
68-
ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64"
69-
ArchARM _ _ -> panic "targetRealRegSqueeze ArchARM"
70-
ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown"
64+
ArchX86 -> X86.realRegSqueeze
65+
ArchX86_64 -> X86.realRegSqueeze
66+
ArchPPC -> PPC.realRegSqueeze
67+
ArchSPARC -> SPARC.realRegSqueeze
68+
ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64"
69+
ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM"
70+
ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown"
7171

7272
targetClassOfRealReg :: Platform -> RealReg -> RegClass
7373
targetClassOfRealReg platform
7474
= case platformArch platform of
75-
ArchX86 -> X86.classOfRealReg
76-
ArchX86_64 -> X86.classOfRealReg
77-
ArchPPC -> PPC.classOfRealReg
78-
ArchSPARC -> SPARC.classOfRealReg
79-
ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64"
80-
ArchARM _ _ -> panic "targetClassOfRealReg ArchARM"
81-
ArchUnknown -> panic "targetClassOfRealReg ArchUnknown"
75+
ArchX86 -> X86.classOfRealReg
76+
ArchX86_64 -> X86.classOfRealReg
77+
ArchPPC -> PPC.classOfRealReg
78+
ArchSPARC -> SPARC.classOfRealReg
79+
ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64"
80+
ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM"
81+
ArchUnknown -> panic "targetClassOfRealReg ArchUnknown"
8282

8383
-- TODO: This should look at targetPlatform too
8484
targetWordSize :: Size
@@ -87,24 +87,24 @@ targetWordSize = intSize wordWidth
8787
targetMkVirtualReg :: Platform -> Unique -> Size -> VirtualReg
8888
targetMkVirtualReg platform
8989
= case platformArch platform of
90-
ArchX86 -> X86.mkVirtualReg
91-
ArchX86_64 -> X86.mkVirtualReg
92-
ArchPPC -> PPC.mkVirtualReg
93-
ArchSPARC -> SPARC.mkVirtualReg
94-
ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64"
95-
ArchARM _ _ -> panic "targetMkVirtualReg ArchARM"
96-
ArchUnknown -> panic "targetMkVirtualReg ArchUnknown"
90+
ArchX86 -> X86.mkVirtualReg
91+
ArchX86_64 -> X86.mkVirtualReg
92+
ArchPPC -> PPC.mkVirtualReg
93+
ArchSPARC -> SPARC.mkVirtualReg
94+
ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64"
95+
ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM"
96+
ArchUnknown -> panic "targetMkVirtualReg ArchUnknown"
9797

9898
targetRegDotColor :: Platform -> RealReg -> SDoc
9999
targetRegDotColor platform
100100
= case platformArch platform of
101-
ArchX86 -> X86.regDotColor platform
102-
ArchX86_64 -> X86.regDotColor platform
103-
ArchPPC -> PPC.regDotColor
104-
ArchSPARC -> SPARC.regDotColor
105-
ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64"
106-
ArchARM _ _ -> panic "targetRegDotColor ArchARM"
107-
ArchUnknown -> panic "targetRegDotColor ArchUnknown"
101+
ArchX86 -> X86.regDotColor platform
102+
ArchX86_64 -> X86.regDotColor platform
103+
ArchPPC -> PPC.regDotColor
104+
ArchSPARC -> SPARC.regDotColor
105+
ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64"
106+
ArchARM _ _ _ -> panic "targetRegDotColor ArchARM"
107+
ArchUnknown -> panic "targetRegDotColor ArchUnknown"
108108

109109

110110
targetClassOfReg :: Platform -> Reg -> RegClass

compiler/utils/Platform.hs

+10-2
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module Platform (
77
OS(..),
88
ArmISA(..),
99
ArmISAExt(..),
10+
ArmABI(..),
1011

1112
target32Bit,
1213
osElfTarget
@@ -41,7 +42,9 @@ data Arch
4142
| ArchSPARC
4243
| ArchARM
4344
{ armISA :: ArmISA
44-
, armISAExt :: [ArmISAExt] }
45+
, armISAExt :: [ArmISAExt]
46+
, armABI :: ArmABI
47+
}
4548
deriving (Read, Show, Eq)
4649

4750

@@ -61,7 +64,7 @@ data OS
6164
| OSHaiku
6265
deriving (Read, Show, Eq)
6366

64-
-- | ARM Instruction Set Architecture and Extensions
67+
-- | ARM Instruction Set Architecture, Extensions and ABI
6568
--
6669
data ArmISA
6770
= ARMv5
@@ -77,6 +80,11 @@ data ArmISAExt
7780
| IWMMX2
7881
deriving (Read, Show, Eq)
7982

83+
data ArmABI
84+
= SOFT
85+
| SOFTFP
86+
| HARD
87+
deriving (Read, Show, Eq)
8088

8189
target32Bit :: Platform -> Bool
8290
target32Bit p = platformWordSize p == 4

0 commit comments

Comments
 (0)