diff --git a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs index 5fc389b89e77bb8445ef6a46613069dbf9d2fdd7..724d7d6b2544924af8040c34413c256f89548696 100644 --- a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs +++ b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs @@ -43,7 +43,7 @@ import qualified X86.Instr class Show freeRegs => FR freeRegs where frAllocateReg :: RealReg -> freeRegs -> freeRegs - frGetFreeRegs :: RegClass -> freeRegs -> [RealReg] + frGetFreeRegs :: Platform -> RegClass -> freeRegs -> [RealReg] frInitFreeRegs :: Platform -> freeRegs frReleaseReg :: RealReg -> freeRegs -> freeRegs @@ -55,13 +55,13 @@ instance FR X86.FreeRegs where instance FR PPC.FreeRegs where frAllocateReg = PPC.allocateReg - frGetFreeRegs = PPC.getFreeRegs + frGetFreeRegs = \_ -> PPC.getFreeRegs frInitFreeRegs = \_ -> PPC.initFreeRegs frReleaseReg = PPC.releaseReg instance FR SPARC.FreeRegs where frAllocateReg = SPARC.allocateReg - frGetFreeRegs = SPARC.getFreeRegs + frGetFreeRegs = \_ -> SPARC.getFreeRegs frInitFreeRegs = \_ -> SPARC.initFreeRegs frReleaseReg = SPARC.releaseReg diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs index 7d6e85e6646be9aa6eb65b8c9a4daad3a781ecac..54c69909483d7134b69ce9156d71742682217524 100644 --- a/compiler/nativeGen/RegAlloc/Linear/Main.hs +++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs @@ -604,7 +604,7 @@ saveClobberedTemps platform clobbered dying = do freeRegs <- getFreeRegsR let regclass = targetClassOfRealReg platform reg - freeRegs_thisClass = frGetFreeRegs regclass freeRegs + freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs case filter (`notElem` clobbered) freeRegs_thisClass of @@ -745,7 +745,7 @@ allocRegsAndSpill_spill :: (FR freeRegs, Instruction instr, Outputable instr) allocRegsAndSpill_spill platform reading keep spills alloc r rs assig spill_loc = do freeRegs <- getFreeRegsR - let freeRegs_thisClass = frGetFreeRegs (classOfVirtualReg r) freeRegs + let freeRegs_thisClass = frGetFreeRegs platform (classOfVirtualReg r) freeRegs case freeRegs_thisClass of diff --git a/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs index debdf3cd03c7f6aa2bba31ef38c8a4f0cc41f365..03c27f45e28efb80885b3194dd34a445e25fd52e 100644 --- a/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs +++ b/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs @@ -40,12 +40,12 @@ initFreeRegs :: Platform -> FreeRegs initFreeRegs platform = foldr releaseReg noFreeRegs (allocatableRegs platform) -getFreeRegs :: RegClass -> FreeRegs -> [RealReg] -- lazilly -getFreeRegs cls f = go f 0 +getFreeRegs :: Platform -> RegClass -> FreeRegs -> [RealReg] -- lazilly +getFreeRegs platform cls f = go f 0 where go 0 _ = [] go n m - | n .&. 1 /= 0 && classOfRealReg (RealRegSingle m) == cls + | n .&. 1 /= 0 && classOfRealReg platform (RealRegSingle m) == cls = RealRegSingle m : (go (n `shiftR` 1) $! (m+1)) | otherwise diff --git a/compiler/nativeGen/TargetReg.hs b/compiler/nativeGen/TargetReg.hs index 13293deeee62e9d9e28b91530d04afa904b3070d..f0d382d0d68a5109909b6628a32da38b260bd98c 100644 --- a/compiler/nativeGen/TargetReg.hs +++ b/compiler/nativeGen/TargetReg.hs @@ -72,8 +72,8 @@ targetRealRegSqueeze platform targetClassOfRealReg :: Platform -> RealReg -> RegClass targetClassOfRealReg platform = case platformArch platform of - ArchX86 -> X86.classOfRealReg - ArchX86_64 -> X86.classOfRealReg + ArchX86 -> X86.classOfRealReg platform + ArchX86_64 -> X86.classOfRealReg platform ArchPPC -> PPC.classOfRealReg ArchSPARC -> SPARC.classOfRealReg ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs index f33169855660e68b29ba23fd34e8501755859b26..ab9b778ad4c4c6f9631c4904a1e794f412ddfead 100644 --- a/compiler/nativeGen/X86/Regs.hs +++ b/compiler/nativeGen/X86/Regs.hs @@ -238,15 +238,15 @@ lastxmm platform | target32Bit platform = 31 | otherwise = 39 -lastint :: RegNo -#if i386_TARGET_ARCH -lastint = 7 -- not %r8..%r15 -#else -lastint = 15 -#endif +lastint :: Platform -> RegNo +lastint platform + | target32Bit platform = 7 -- not %r8..%r15 + | otherwise = 15 + +intregnos :: Platform -> [RegNo] +intregnos platform = [0 .. lastint platform] -intregnos, fakeregnos :: [RegNo] -intregnos = [0..lastint] +fakeregnos :: [RegNo] fakeregnos = [firstfake .. lastfake] xmmregnos :: Platform -> [RegNo] @@ -264,21 +264,21 @@ argRegs _ = panic "MachRegs.argRegs(x86): should not be used!" -- | The complete set of machine registers. allMachRegNos :: Platform -> [RegNo] -allMachRegNos platform = intregnos ++ floatregnos platform +allMachRegNos platform = intregnos platform ++ floatregnos platform -- | Take the class of a register. -{-# INLINE classOfRealReg #-} -classOfRealReg :: RealReg -> RegClass +{-# 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 reg +classOfRealReg platform reg = case reg of RealRegSingle i - | i <= lastint -> RcInteger - | i <= lastfake -> RcDouble - | otherwise -> RcDoubleSSE + | i <= lastint platform -> RcInteger + | i <= lastfake -> RcDouble + | otherwise -> RcDoubleSSE RealRegPair{} -> panic "X86.Regs.classOfRealReg: RegPairs on this arch"