diff options
author | Peter Trommler <ptrommler@acm.org> | 2018-12-30 22:23:53 +0100 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2019-01-01 11:44:16 -0500 |
commit | 374e44704b64afafc1179127e6c9c5bf1715ef39 (patch) | |
tree | e55962e8ac605a6762a18e30c8614d772effb2eb /compiler | |
parent | ae4f1033cfe131fca9416e2993bda081e1f8c152 (diff) | |
download | haskell-374e44704b64afafc1179127e6c9c5bf1715ef39.tar.gz |
PPC NCG: Remove Darwin support
Support for Mac OS X on PowerPC has been dropped by Apple years ago. We
follow suit and remove PowerPC support for Darwin.
Fixes #16106.
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/cmm/CmmPipeline.hs | 7 | ||||
-rw-r--r-- | compiler/codeGen/CodeGen/Platform.hs | 21 | ||||
-rw-r--r-- | compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs | 11 | ||||
-rw-r--r-- | compiler/ghc.cabal.in | 1 | ||||
-rw-r--r-- | compiler/nativeGen/PIC.hs | 62 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/CodeGen.hs | 94 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/Instr.hs | 5 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/Ppr.hs | 85 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/Regs.hs | 2 |
9 files changed, 47 insertions, 241 deletions
diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs index 8c4f21452a..7f7c111848 100644 --- a/compiler/cmm/CmmPipeline.hs +++ b/compiler/cmm/CmmPipeline.hs @@ -167,7 +167,6 @@ cpsTop hsc_env proc = usingInconsistentPicReg = case (platformArch platform, platformOS platform, positionIndependent dflags) of (ArchX86, OSDarwin, pic) -> pic - (ArchPPC, OSDarwin, pic) -> pic _ -> False -- Note [Sinking after stack layout] @@ -314,12 +313,6 @@ points, then at the join point we don't have a consistent value for Hence, on x86/Darwin, we have to split proc points, and then each proc point will get its own PIC initialisation sequence. -The situation is the same for ppc/Darwin. We use essentially the same -sequence to load the program counter onto reg: - - bcl 20,31,1f - 1: mflr reg - This isn't an issue on x86/ELF, where the sequence is call 1f diff --git a/compiler/codeGen/CodeGen/Platform.hs b/compiler/codeGen/CodeGen/Platform.hs index 3014a0596f..9d9a0cf2d1 100644 --- a/compiler/codeGen/CodeGen/Platform.hs +++ b/compiler/codeGen/CodeGen/Platform.hs @@ -12,7 +12,6 @@ import Reg import qualified CodeGen.Platform.ARM as ARM import qualified CodeGen.Platform.ARM64 as ARM64 import qualified CodeGen.Platform.PPC as PPC -import qualified CodeGen.Platform.PPC_Darwin as PPC_Darwin import qualified CodeGen.Platform.SPARC as SPARC import qualified CodeGen.Platform.X86 as X86 import qualified CodeGen.Platform.X86_64 as X86_64 @@ -33,9 +32,7 @@ callerSaves platform ArchARM64 -> ARM64.callerSaves arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> - case platformOS platform of - OSDarwin -> PPC_Darwin.callerSaves - _ -> PPC.callerSaves + PPC.callerSaves | otherwise -> NoRegs.callerSaves @@ -56,9 +53,7 @@ activeStgRegs platform ArchARM64 -> ARM64.activeStgRegs arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> - case platformOS platform of - OSDarwin -> PPC_Darwin.activeStgRegs - _ -> PPC.activeStgRegs + PPC.activeStgRegs | otherwise -> NoRegs.activeStgRegs @@ -74,9 +69,7 @@ haveRegBase platform ArchARM64 -> ARM64.haveRegBase arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> - case platformOS platform of - OSDarwin -> PPC_Darwin.haveRegBase - _ -> PPC.haveRegBase + PPC.haveRegBase | otherwise -> NoRegs.haveRegBase @@ -92,9 +85,7 @@ globalRegMaybe platform ArchARM64 -> ARM64.globalRegMaybe arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> - case platformOS platform of - OSDarwin -> PPC_Darwin.globalRegMaybe - _ -> PPC.globalRegMaybe + PPC.globalRegMaybe | otherwise -> NoRegs.globalRegMaybe @@ -110,9 +101,7 @@ freeReg platform ArchARM64 -> ARM64.freeReg arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> - case platformOS platform of - OSDarwin -> PPC_Darwin.freeReg - _ -> PPC.freeReg + PPC.freeReg | otherwise -> NoRegs.freeReg diff --git a/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs b/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs deleted file mode 100644 index 91923fd453..0000000000 --- a/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs +++ /dev/null @@ -1,11 +0,0 @@ -{-# LANGUAGE CPP #-} - -module CodeGen.Platform.PPC_Darwin where - -import GhcPrelude - -#define MACHREGS_NO_REGS 0 -#define MACHREGS_powerpc 1 -#define MACHREGS_darwin 1 -#include "../../../../includes/CodeGen.Platform.hs" - diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index 7f84cac192..5b93d3ceb2 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -272,7 +272,6 @@ Library CodeGen.Platform.ARM64 CodeGen.Platform.NoRegs CodeGen.Platform.PPC - CodeGen.Platform.PPC_Darwin CodeGen.Platform.SPARC CodeGen.Platform.X86 CodeGen.Platform.X86_64 diff --git a/compiler/nativeGen/PIC.hs b/compiler/nativeGen/PIC.hs index 2f300c4614..7778729368 100644 --- a/compiler/nativeGen/PIC.hs +++ b/compiler/nativeGen/PIC.hs @@ -569,60 +569,6 @@ pprGotDeclaration _ _ _ -- the splitter in driver/split/ghc-split.pl recognizes the new output pprImportedSymbol :: DynFlags -> Platform -> CLabel -> SDoc -pprImportedSymbol dflags platform@(Platform { platformArch = ArchPPC, platformOS = OSDarwin }) importedLbl - | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl - = case positionIndependent dflags of - False -> - vcat [ - text ".symbol_stub", - text "L" <> pprCLabel platform lbl <> ptext (sLit "$stub:"), - text "\t.indirect_symbol" <+> pprCLabel platform lbl, - text "\tlis r11,ha16(L" <> pprCLabel platform lbl - <> text "$lazy_ptr)", - text "\tlwz r12,lo16(L" <> pprCLabel platform lbl - <> text "$lazy_ptr)(r11)", - text "\tmtctr r12", - text "\taddi r11,r11,lo16(L" <> pprCLabel platform lbl - <> text "$lazy_ptr)", - text "\tbctr" - ] - True -> - vcat [ - text ".section __TEXT,__picsymbolstub1," - <> text "symbol_stubs,pure_instructions,32", - text "\t.align 2", - text "L" <> pprCLabel platform lbl <> ptext (sLit "$stub:"), - text "\t.indirect_symbol" <+> pprCLabel platform lbl, - text "\tmflr r0", - text "\tbcl 20,31,L0$" <> pprCLabel platform lbl, - text "L0$" <> pprCLabel platform lbl <> char ':', - text "\tmflr r11", - text "\taddis r11,r11,ha16(L" <> pprCLabel platform lbl - <> text "$lazy_ptr-L0$" <> pprCLabel platform lbl <> char ')', - text "\tmtlr r0", - text "\tlwzu r12,lo16(L" <> pprCLabel platform lbl - <> text "$lazy_ptr-L0$" <> pprCLabel platform lbl - <> text ")(r11)", - text "\tmtctr r12", - text "\tbctr" - ] - $+$ vcat [ - text ".lazy_symbol_pointer", - text "L" <> pprCLabel platform lbl <> ptext (sLit "$lazy_ptr:"), - text "\t.indirect_symbol" <+> pprCLabel platform lbl, - text "\t.long dyld_stub_binding_helper"] - - | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl - = vcat [ - text ".non_lazy_symbol_pointer", - char 'L' <> pprCLabel platform lbl <> text "$non_lazy_ptr:", - text "\t.indirect_symbol" <+> pprCLabel platform lbl, - text "\t.long\t0"] - - | otherwise - = empty - - pprImportedSymbol dflags platform@(Platform { platformArch = ArchX86, platformOS = OSDarwin }) importedLbl | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl = case positionIndependent dflags of @@ -827,14 +773,6 @@ initializePicBase_ppc ArchPPC os picReg return (CmmProc info lab live (ListGraph blocks') : statics) - -initializePicBase_ppc ArchPPC OSDarwin picReg - (CmmProc info lab live (ListGraph (entry:blocks)) : statics) -- just one entry because of splitting - = return (CmmProc info lab live (ListGraph (b':blocks)) : statics) - - where BasicBlock bID insns = entry - b' = BasicBlock bID (PPC.FETCHPC picReg : insns) - ------------------------------------------------------------------------- -- Load TOC into register 2 -- PowerPC 64-bit ELF ABI 2.0 requires the address of the callee diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index d46bef7ba5..bbc34117bb 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -1566,7 +1566,7 @@ genCCall target dest_regs argsAndHints = panic "genCall: Wrong number of arguments/results for fabs" -- TODO: replace 'Int' by an enum such as 'PPC_64ABI' -data GenCCallPlatform = GCPLinux | GCPDarwin | GCPLinux64ELF !Int | GCPAIX +data GenCCallPlatform = GCPLinux | GCPLinux64ELF !Int | GCPAIX platformToGCP :: Platform -> GenCCallPlatform platformToGCP platform = case platformOS platform of @@ -1576,7 +1576,6 @@ platformToGCP platform = case platformOS platform of ArchPPC_64 ELF_V2 -> GCPLinux64ELF 2 _ -> panic "PPC.CodeGen.platformToGCP: Unknown Linux" OSAIX -> GCPAIX - OSDarwin -> GCPDarwin _ -> panic "PPC.CodeGen.platformToGCP: not defined for this OS" @@ -1588,51 +1587,49 @@ genCCall' -> [CmmActual] -- arguments (of mixed type) -> NatM InstrBlock -{- - The PowerPC calling convention for Darwin/Mac OS X - is described in Apple's document - "Inside Mac OS X - Mach-O Runtime Architecture". - +{- PowerPC Linux uses the System V Release 4 Calling Convention for PowerPC. It is described in the "System V Application Binary Interface PowerPC Processor Supplement". - Both conventions are similar: + PowerPC 64 Linux uses the System V Release 4 Calling Convention for + 64-bit PowerPC. It is specified in + "64-bit PowerPC ELF Application Binary Interface Supplement 1.9" + (PPC64 ELF v1.9). + + PowerPC 64 Linux in little endian mode uses the "Power Architecture 64-Bit + ELF V2 ABI Specification -- OpenPOWER ABI for Linux Supplement" + (PPC64 ELF v2). + + AIX follows the "PowerOpen ABI: Application Binary Interface Big-Endian + 32-Bit Hardware Implementation" + + All four conventions are similar: Parameters may be passed in general-purpose registers starting at r3, in floating point registers starting at f1, or on the stack. But there are substantial differences: * The number of registers used for parameter passing and the exact set of nonvolatile registers differs (see MachRegs.hs). - * On Darwin, stack space is always reserved for parameters, even if they are - passed in registers. The called routine may choose to save parameters from - registers to the corresponding space on the stack. - * On Darwin, a corresponding amount of GPRs is skipped when a floating point - parameter is passed in an FPR. + * On AIX and 64-bit ELF, stack space is always reserved for parameters, + even if they are passed in registers. The called routine may choose to + save parameters from registers to the corresponding space on the stack. + * On AIX and 64-bit ELF, a corresponding amount of GPRs is skipped when + a floating point parameter is passed in an FPR. * SysV insists on either passing I64 arguments on the stack, or in two GPRs, starting with an odd-numbered GPR. It may skip a GPR to achieve this. - Darwin just treats an I64 like two separate II32s (high word first). + AIX just treats an I64 likt two separate I32s (high word first). * I64 and FF64 arguments are 8-byte aligned on the stack for SysV, but only - 4-byte aligned like everything else on Darwin. + 4-byte aligned like everything else on AIX. * The SysV spec claims that FF32 is represented as FF64 on the stack. GCC on PowerPC Linux does not agree, so neither do we. - PowerPC 64 Linux uses the System V Release 4 Calling Convention for - 64-bit PowerPC. It is specified in - "64-bit PowerPC ELF Application Binary Interface Supplement 1.9" - (PPC64 ELF v1.9). - PowerPC 64 Linux in little endian mode uses the "Power Architecture 64-Bit - ELF V2 ABI Specification -- OpenPOWER ABI for Linux Supplement" - (PPC64 ELF v2). - AIX follows the "PowerOpen ABI: Application Binary Interface Big-Endian - 32-Bit Hardware Implementation" - According to all conventions, the parameter area should be part of the caller's stack frame, allocated in the caller's prologue code (large enough to hold the parameter lists for all called routines). The NCG already uses the stack for register spilling, leaving 64 bytes free at the top. - If we need a larger parameter area than that, we just allocate a new stack - frame just before ccalling. + If we need a larger parameter area than that, we increase the size + of the stack frame just before ccalling. -} @@ -1715,7 +1712,6 @@ genCCall' dflags gcp target dest_regs args initialStackOffset = case gcp of GCPAIX -> 24 - GCPDarwin -> 24 GCPLinux -> 8 GCPLinux64ELF 1 -> 48 GCPLinux64ELF 2 -> 32 @@ -1725,9 +1721,6 @@ genCCall' dflags gcp target dest_regs args GCPAIX -> roundTo 16 $ (24 +) $ max 32 $ sum $ map (widthInBytes . typeWidth) argReps - GCPDarwin -> - roundTo 16 $ (24 +) $ max 32 $ sum $ - map (widthInBytes . typeWidth) argReps GCPLinux -> roundTo 16 finalStack GCPLinux64ELF 1 -> roundTo 16 $ (48 +) $ max 64 $ sum $ @@ -1783,19 +1776,7 @@ genCCall' dflags gcp target dest_regs args let vr_hi = getHiVRegFromLo vr_lo case gcp of - GCPAIX -> -- same as for Darwin - do let storeWord vr (gpr:_) _ = MR gpr vr - storeWord vr [] offset - = ST II32 vr (AddrRegImm sp (ImmInt offset)) - passArguments args - (drop 2 gprs) - fprs - (stackOffset+8) - (accumCode `appOL` code - `snocOL` storeWord vr_hi gprs stackOffset - `snocOL` storeWord vr_lo (drop 1 gprs) (stackOffset+4)) - ((take 2 gprs) ++ accumUsed) - GCPDarwin -> + GCPAIX -> do let storeWord vr (gpr:_) _ = MR gpr vr storeWord vr [] offset = ST II32 vr (AddrRegImm sp (ImmInt offset)) @@ -1836,10 +1817,9 @@ genCCall' dflags gcp target dest_regs args Fixed _ freg fcode -> fcode `snocOL` MR reg freg Any _ acode -> acode reg stackOffsetRes = case gcp of - -- The Darwin ABI requires that we reserve - -- stack slots for register parameters - GCPDarwin -> stackOffset + stackBytes - -- ... so does the PowerOpen ABI. + -- The PowerOpen ABI requires that we + -- reserve stack slots for register + -- parameters GCPAIX -> stackOffset + stackBytes -- ... the SysV ABI 32-bit doesn't. GCPLinux -> stackOffset @@ -1861,13 +1841,9 @@ genCCall' dflags gcp target dest_regs args accumUsed where stackOffset' = case gcp of - GCPDarwin -> - -- stackOffset is at least 4-byte aligned - -- The Darwin ABI is happy with that. - stackOffset GCPAIX -> -- The 32bit PowerOPEN ABI is happy with - -- 32bit-alignment as well... + -- 32bit-alignment ... stackOffset GCPLinux -- ... the SysV ABI requires 8-byte @@ -1914,18 +1890,6 @@ genCCall' dflags gcp target dest_regs args FF64 -> (2, 1, 8, fprs) II64 -> panic "genCCall' passArguments II64" FF80 -> panic "genCCall' passArguments FF80" - GCPDarwin -> - case cmmTypeFormat rep of - II8 -> (1, 0, 4, gprs) - II16 -> (1, 0, 4, gprs) - II32 -> (1, 0, 4, gprs) - -- The Darwin ABI requires that we skip a - -- corresponding number of GPRs when we use - -- the FPRs. - FF32 -> (1, 1, 4, fprs) - FF64 -> (2, 1, 8, fprs) - II64 -> panic "genCCall' passArguments II64" - FF80 -> panic "genCCall' passArguments FF80" GCPLinux -> case cmmTypeFormat rep of II8 -> (1, 0, 4, gprs) diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs index ade39430c0..8f3153ca16 100644 --- a/compiler/nativeGen/PPC/Instr.hs +++ b/compiler/nativeGen/PPC/Instr.hs @@ -582,7 +582,6 @@ stackFrameHeaderSize dflags ArchPPC_64 ELF_V2 -> 32 + 8 * 8 _ -> panic "PPC.stackFrameHeaderSize: Unknown Linux" OSAIX -> 24 + 8 * 4 - OSDarwin -> 64 -- TODO: check ABI spec _ -> panic "PPC.stackFrameHeaderSize: not defined for this OS" where platform = targetPlatform dflags @@ -602,8 +601,8 @@ maxSpillSlots dflags -- = 0 -- useful for testing allocMoreStack -- | The number of bytes that the stack pointer should be aligned --- to. This is 16 both on PPC32 and PPC64 at least for Darwin, and --- Linux (see ELF processor specific supplements). +-- to. This is 16 both on PPC32 and PPC64 ELF (see ELF processor +-- specific supplements). stackAlign :: Int stackAlign = 16 diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs index 3d9077df19..d7175b8689 100644 --- a/compiler/nativeGen/PPC/Ppr.hs +++ b/compiler/nativeGen/PPC/Ppr.hs @@ -129,7 +129,6 @@ pprData (CmmString str) = pprASCII str pprData (CmmUninitialised bytes) = keyword <> int bytes where keyword = sdocWithPlatform $ \platform -> case platformOS platform of - OSDarwin -> text ".space " OSAIX -> text ".space " _ -> text ".skip " pprData (CmmStaticLit lit) = pprDataItem lit @@ -181,50 +180,10 @@ pprReg r RegVirtual (VirtualRegSSE u) -> text "%vSSE_" <> pprUniqueAlways u where ppr_reg_no :: Int -> SDoc - ppr_reg_no i = - sdocWithPlatform $ \platform -> - case platformOS platform of - OSDarwin -> - ptext - (case i of { - 0 -> sLit "r0"; 1 -> sLit "r1"; - 2 -> sLit "r2"; 3 -> sLit "r3"; - 4 -> sLit "r4"; 5 -> sLit "r5"; - 6 -> sLit "r6"; 7 -> sLit "r7"; - 8 -> sLit "r8"; 9 -> sLit "r9"; - 10 -> sLit "r10"; 11 -> sLit "r11"; - 12 -> sLit "r12"; 13 -> sLit "r13"; - 14 -> sLit "r14"; 15 -> sLit "r15"; - 16 -> sLit "r16"; 17 -> sLit "r17"; - 18 -> sLit "r18"; 19 -> sLit "r19"; - 20 -> sLit "r20"; 21 -> sLit "r21"; - 22 -> sLit "r22"; 23 -> sLit "r23"; - 24 -> sLit "r24"; 25 -> sLit "r25"; - 26 -> sLit "r26"; 27 -> sLit "r27"; - 28 -> sLit "r28"; 29 -> sLit "r29"; - 30 -> sLit "r30"; 31 -> sLit "r31"; - 32 -> sLit "f0"; 33 -> sLit "f1"; - 34 -> sLit "f2"; 35 -> sLit "f3"; - 36 -> sLit "f4"; 37 -> sLit "f5"; - 38 -> sLit "f6"; 39 -> sLit "f7"; - 40 -> sLit "f8"; 41 -> sLit "f9"; - 42 -> sLit "f10"; 43 -> sLit "f11"; - 44 -> sLit "f12"; 45 -> sLit "f13"; - 46 -> sLit "f14"; 47 -> sLit "f15"; - 48 -> sLit "f16"; 49 -> sLit "f17"; - 50 -> sLit "f18"; 51 -> sLit "f19"; - 52 -> sLit "f20"; 53 -> sLit "f21"; - 54 -> sLit "f22"; 55 -> sLit "f23"; - 56 -> sLit "f24"; 57 -> sLit "f25"; - 58 -> sLit "f26"; 59 -> sLit "f27"; - 60 -> sLit "f28"; 61 -> sLit "f29"; - 62 -> sLit "f30"; 63 -> sLit "f31"; - _ -> sLit "very naughty powerpc register" - }) - _ - | i <= 31 -> int i -- GPRs - | i <= 63 -> int (i-32) -- FPRs - | otherwise -> text "very naughty powerpc register" + ppr_reg_no i + | i <= 31 = int i -- GPRs + | i <= 63 = int (i-32) -- FPRs + | otherwise = text "very naughty powerpc register" @@ -272,16 +231,10 @@ pprImm (LO (ImmInteger i)) = pprImm (ImmInteger (toInteger lo16)) lo16 = fromInteger (i .&. 0xffff) :: Int16 pprImm (LO i) - = sdocWithPlatform $ \platform -> - if platformOS platform == OSDarwin - then hcat [ text "lo16(", pprImm i, rparen ] - else pprImm i <> text "@l" + = pprImm i <> text "@l" pprImm (HI i) - = sdocWithPlatform $ \platform -> - if platformOS platform == OSDarwin - then hcat [ text "hi16(", pprImm i, rparen ] - else pprImm i <> text "@h" + = pprImm i <> text "@h" pprImm (HA (ImmInt i)) = pprImm (HA (ImmInteger (toInteger i))) pprImm (HA (ImmInteger i)) = pprImm (ImmInteger ha16) @@ -291,22 +244,13 @@ pprImm (HA (ImmInteger i)) = pprImm (ImmInteger ha16) lo16 = i .&. 0xffff pprImm (HA i) - = sdocWithPlatform $ \platform -> - if platformOS platform == OSDarwin - then hcat [ text "ha16(", pprImm i, rparen ] - else pprImm i <> text "@ha" + = pprImm i <> text "@ha" pprImm (HIGHERA i) - = sdocWithPlatform $ \platform -> - if platformOS platform == OSDarwin - then panic "PPC.pprImm: highera not implemented on Darwin" - else pprImm i <> text "@highera" + = pprImm i <> text "@highera" pprImm (HIGHESTA i) - = sdocWithPlatform $ \platform -> - if platformOS platform == OSDarwin - then panic "PPC.pprImm: highesta not implemented on Darwin" - else pprImm i <> text "@highesta" + = pprImm i <> text "@highesta" pprAddr :: AddrMode -> SDoc @@ -330,32 +274,25 @@ pprSectionAlign sec@(Section seg _) = pprAlignForSection :: SectionType -> SDoc pprAlignForSection seg = sdocWithPlatform $ \platform -> - let osDarwin = platformOS platform == OSDarwin - ppc64 = not $ target32Bit platform + let ppc64 = not $ target32Bit platform in ptext $ case seg of Text -> sLit ".align 2" Data | ppc64 -> sLit ".align 3" | otherwise -> sLit ".align 2" ReadOnlyData - | osDarwin -> sLit ".align 2" | ppc64 -> sLit ".align 3" | otherwise -> sLit ".align 2" RelocatableReadOnlyData - | osDarwin -> sLit ".align 2" | ppc64 -> sLit ".align 3" | otherwise -> sLit ".align 2" UninitialisedData - | osDarwin -> sLit ".align 2" | ppc64 -> sLit ".align 3" | otherwise -> sLit ".align 2" - ReadOnlyData16 - | osDarwin -> sLit ".align 4" - | otherwise -> sLit ".align 4" + ReadOnlyData16 -> sLit ".align 4" -- TODO: This is copied from the ReadOnlyData case, but it can likely be -- made more efficient. CString - | osDarwin -> sLit ".align 2" | ppc64 -> sLit ".align 3" | otherwise -> sLit ".align 2" OtherSection _ -> panic "PprMach.pprSectionAlign: unknown section" diff --git a/compiler/nativeGen/PPC/Regs.hs b/compiler/nativeGen/PPC/Regs.hs index 227517be88..a2c03b9b3c 100644 --- a/compiler/nativeGen/PPC/Regs.hs +++ b/compiler/nativeGen/PPC/Regs.hs @@ -232,7 +232,6 @@ callClobberedRegs :: Platform -> [Reg] callClobberedRegs platform = case platformOS platform of OSAIX -> map regSingle (0:[2..12] ++ map fReg [0..13]) - OSDarwin -> map regSingle (0:[2..12] ++ map fReg [0..13]) OSLinux -> map regSingle (0:[2..13] ++ map fReg [0..13]) _ -> panic "PPC.Regs.callClobberedRegs: not defined for this architecture" @@ -264,7 +263,6 @@ allFPArgRegs :: Platform -> [Reg] allFPArgRegs platform = case platformOS platform of OSAIX -> map (regSingle . fReg) [1..13] - OSDarwin -> map (regSingle . fReg) [1..13] OSLinux -> case platformArch platform of ArchPPC -> map (regSingle . fReg) [1..8] ArchPPC_64 _ -> map (regSingle . fReg) [1..13] |