diff options
Diffstat (limited to 'compiler/GHC')
-rw-r--r-- | compiler/GHC/Cmm/CallConv.hs | 50 | ||||
-rw-r--r-- | compiler/GHC/Cmm/Lexer.x | 1 | ||||
-rw-r--r-- | compiler/GHC/Cmm/Reg.hs | 10 | ||||
-rw-r--r-- | compiler/GHC/CmmToC.hs | 1 | ||||
-rw-r--r-- | compiler/GHC/CmmToLlvm/Regs.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/StgToCmm/CgUtils.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/StgToCmm/Heap.hs | 1 |
7 files changed, 21 insertions, 46 deletions
diff --git a/compiler/GHC/Cmm/CallConv.hs b/compiler/GHC/Cmm/CallConv.hs index a0fee0e5c6..5986f5e674 100644 --- a/compiler/GHC/Cmm/CallConv.hs +++ b/compiler/GHC/Cmm/CallConv.hs @@ -68,29 +68,27 @@ assignArgumentsPos profile off conv arg_ty reps = (stk_off, assignments) | isFloatType ty = float | otherwise = int where vec = case (w, regs) of - (W128, (vs, fs, ds, ls, s:ss)) - | passVectorInReg W128 profile -> k (RegisterParam (XmmReg s), (vs, fs, ds, ls, ss)) - (W256, (vs, fs, ds, ls, s:ss)) - | passVectorInReg W256 profile -> k (RegisterParam (YmmReg s), (vs, fs, ds, ls, ss)) - (W512, (vs, fs, ds, ls, s:ss)) - | passVectorInReg W512 profile -> k (RegisterParam (ZmmReg s), (vs, fs, ds, ls, ss)) + (W128, (vs, fs, ds, s:ss)) + | passVectorInReg W128 profile -> k (RegisterParam (XmmReg s), (vs, fs, ds, ss)) + (W256, (vs, fs, ds, s:ss)) + | passVectorInReg W256 profile -> k (RegisterParam (YmmReg s), (vs, fs, ds, ss)) + (W512, (vs, fs, ds, s:ss)) + | passVectorInReg W512 profile -> k (RegisterParam (ZmmReg s), (vs, fs, ds, ss)) _ -> (assts, (r:rs)) float = case (w, regs) of - (W32, (vs, fs, ds, ls, s:ss)) - | passFloatInXmm -> k (RegisterParam (FloatReg s), (vs, fs, ds, ls, ss)) - (W32, (vs, f:fs, ds, ls, ss)) - | not passFloatInXmm -> k (RegisterParam f, (vs, fs, ds, ls, ss)) - (W64, (vs, fs, ds, ls, s:ss)) - | passFloatInXmm -> k (RegisterParam (DoubleReg s), (vs, fs, ds, ls, ss)) - (W64, (vs, fs, d:ds, ls, ss)) - | not passFloatInXmm -> k (RegisterParam d, (vs, fs, ds, ls, ss)) + (W32, (vs, fs, ds, s:ss)) + | passFloatInXmm -> k (RegisterParam (FloatReg s), (vs, fs, ds, ss)) + (W32, (vs, f:fs, ds, ss)) + | not passFloatInXmm -> k (RegisterParam f, (vs, fs, ds, ss)) + (W64, (vs, fs, ds, s:ss)) + | passFloatInXmm -> k (RegisterParam (DoubleReg s), (vs, fs, ds, ss)) + (W64, (vs, fs, d:ds, ss)) + | not passFloatInXmm -> k (RegisterParam d, (vs, fs, ds, ss)) _ -> (assts, (r:rs)) int = case (w, regs) of (W128, _) -> panic "W128 unsupported register type" - (_, (v:vs, fs, ds, ls, ss)) | widthInBits w <= widthInBits (wordWidth platform) - -> k (RegisterParam (v gcp), (vs, fs, ds, ls, ss)) - (_, (vs, fs, ds, l:ls, ss)) | widthInBits w > widthInBits (wordWidth platform) - -> k (RegisterParam l, (vs, fs, ds, ls, ss)) + (_, (v:vs, fs, ds, ss)) | widthInBits w <= widthInBits (wordWidth platform) + -> k (RegisterParam (v gcp), (vs, fs, ds, ss)) _ -> (assts, (r:rs)) k (asst, regs') = assign_regs ((r, asst) : assts) rs regs' ty = arg_ty r @@ -134,7 +132,6 @@ assignStack platform offset arg_ty args = assign_stk offset [] (reverse args) type AvailRegs = ( [VGcPtr -> GlobalReg] -- available vanilla regs. , [GlobalReg] -- floats , [GlobalReg] -- doubles - , [GlobalReg] -- longs (int64 and word64) , [Int] -- XMM (floats and doubles) ) @@ -149,7 +146,6 @@ getRegsWithoutNode platform = ( filter (\r -> r VGcPtr /= node) (realVanillaRegs platform) , realFloatRegs platform , realDoubleRegs platform - , realLongRegs platform , realXmmRegNos platform) -- getRegsWithNode uses R1/node even if it isn't a register @@ -159,26 +155,23 @@ getRegsWithNode platform = else realVanillaRegs platform , realFloatRegs platform , realDoubleRegs platform - , realLongRegs platform , realXmmRegNos platform) -allFloatRegs, allDoubleRegs, allLongRegs :: Platform -> [GlobalReg] +allFloatRegs, allDoubleRegs :: Platform -> [GlobalReg] allVanillaRegs :: Platform -> [VGcPtr -> GlobalReg] allXmmRegs :: Platform -> [Int] allVanillaRegs platform = map VanillaReg $ regList (pc_MAX_Vanilla_REG (platformConstants platform)) allFloatRegs platform = map FloatReg $ regList (pc_MAX_Float_REG (platformConstants platform)) allDoubleRegs platform = map DoubleReg $ regList (pc_MAX_Double_REG (platformConstants platform)) -allLongRegs platform = map LongReg $ regList (pc_MAX_Long_REG (platformConstants platform)) allXmmRegs platform = regList (pc_MAX_XMM_REG (platformConstants platform)) -realFloatRegs, realDoubleRegs, realLongRegs :: Platform -> [GlobalReg] +realFloatRegs, realDoubleRegs :: Platform -> [GlobalReg] realVanillaRegs :: Platform -> [VGcPtr -> GlobalReg] realVanillaRegs platform = map VanillaReg $ regList (pc_MAX_Real_Vanilla_REG (platformConstants platform)) realFloatRegs platform = map FloatReg $ regList (pc_MAX_Real_Float_REG (platformConstants platform)) realDoubleRegs platform = map DoubleReg $ regList (pc_MAX_Real_Double_REG (platformConstants platform)) -realLongRegs platform = map LongReg $ regList (pc_MAX_Real_Long_REG (platformConstants platform)) realXmmRegNos :: Platform -> [Int] realXmmRegNos platform @@ -192,12 +185,11 @@ allRegs :: Platform -> AvailRegs allRegs platform = ( allVanillaRegs platform , allFloatRegs platform , allDoubleRegs platform - , allLongRegs platform , allXmmRegs platform ) nodeOnly :: AvailRegs -nodeOnly = ([VanillaReg 1], [], [], [], []) +nodeOnly = ([VanillaReg 1], [], [], []) -- This returns the set of global registers that *cover* the machine registers -- used for argument passing. On platforms where registers can overlap---right @@ -208,7 +200,6 @@ realArgRegsCover :: Platform -> [GlobalReg] realArgRegsCover platform | passFloatArgsInXmm platform = map ($ VGcPtr) (realVanillaRegs platform) ++ - realLongRegs platform ++ realDoubleRegs platform -- we only need to save the low Double part of XMM registers. -- Moreover, the NCG can't load/store full XMM -- registers for now... @@ -216,8 +207,7 @@ realArgRegsCover platform | otherwise = map ($ VGcPtr) (realVanillaRegs platform) ++ realFloatRegs platform ++ - realDoubleRegs platform ++ - realLongRegs platform + realDoubleRegs platform -- we don't save XMM registers if they are not used for parameter passing -- Like realArgRegsCover but always includes the node. This covers the real diff --git a/compiler/GHC/Cmm/Lexer.x b/compiler/GHC/Cmm/Lexer.x index bf379ec7da..abb674ef38 100644 --- a/compiler/GHC/Cmm/Lexer.x +++ b/compiler/GHC/Cmm/Lexer.x @@ -103,7 +103,6 @@ $white_no_nl+ ; R@decimal { global_regN (\n -> VanillaReg n VNonGcPtr) } F@decimal { global_regN FloatReg } D@decimal { global_regN DoubleReg } - L@decimal { global_regN LongReg } Sp { global_reg Sp } SpLim { global_reg SpLim } Hp { global_reg Hp } diff --git a/compiler/GHC/Cmm/Reg.hs b/compiler/GHC/Cmm/Reg.hs index 6c94ecb2eb..911e27fdc0 100644 --- a/compiler/GHC/Cmm/Reg.hs +++ b/compiler/GHC/Cmm/Reg.hs @@ -142,9 +142,6 @@ data GlobalReg | DoubleReg -- double-precision floating-point registers {-# UNPACK #-} !Int -- its number - | LongReg -- long int registers (64-bit, really) - {-# UNPACK #-} !Int -- its number - | XmmReg -- 128-bit SIMD vector register {-# UNPACK #-} !Int -- its number @@ -197,7 +194,6 @@ instance Eq GlobalReg where VanillaReg i _ == VanillaReg j _ = i==j -- Ignore type when seeking clashes FloatReg i == FloatReg j = i==j DoubleReg i == DoubleReg j = i==j - LongReg i == LongReg j = i==j -- NOTE: XMM, YMM, ZMM registers actually are the same registers -- at least with respect to store at YMM i and then read from XMM i -- and similarly for ZMM etc. @@ -228,7 +224,6 @@ instance Ord GlobalReg where -- Ignore type when seeking clashes compare (FloatReg i) (FloatReg j) = compare i j compare (DoubleReg i) (DoubleReg j) = compare i j - compare (LongReg i) (LongReg j) = compare i j compare (XmmReg i) (XmmReg j) = compare i j compare (YmmReg i) (YmmReg j) = compare i j compare (ZmmReg i) (ZmmReg j) = compare i j @@ -253,8 +248,6 @@ instance Ord GlobalReg where compare _ (FloatReg _) = GT compare (DoubleReg _) _ = LT compare _ (DoubleReg _) = GT - compare (LongReg _) _ = LT - compare _ (LongReg _) = GT compare (XmmReg _) _ = LT compare _ (XmmReg _) = GT compare (YmmReg _) _ = LT @@ -305,7 +298,6 @@ pprGlobalReg gr -- VanillaReg n VGcPtr -> char 'P' <> int n FloatReg n -> char 'F' <> int n DoubleReg n -> char 'D' <> int n - LongReg n -> char 'L' <> int n XmmReg n -> text "XMM" <> int n YmmReg n -> text "YMM" <> int n ZmmReg n -> text "ZMM" <> int n @@ -349,7 +341,6 @@ globalRegType platform = \case (VanillaReg _ VNonGcPtr) -> bWord platform (FloatReg _) -> cmmFloat W32 (DoubleReg _) -> cmmFloat W64 - (LongReg _) -> cmmBits W64 -- TODO: improve the internal model of SIMD/vectorized registers -- the right design SHOULd improve handling of float and double code too. -- see remarks in Note [SIMD Design for the future] in GHC.StgToCmm.Prim @@ -365,7 +356,6 @@ isArgReg :: GlobalReg -> Bool isArgReg (VanillaReg {}) = True isArgReg (FloatReg {}) = True isArgReg (DoubleReg {}) = True -isArgReg (LongReg {}) = True isArgReg (XmmReg {}) = True isArgReg (YmmReg {}) = True isArgReg (ZmmReg {}) = True diff --git a/compiler/GHC/CmmToC.hs b/compiler/GHC/CmmToC.hs index 44d4657052..05b32239f4 100644 --- a/compiler/GHC/CmmToC.hs +++ b/compiler/GHC/CmmToC.hs @@ -1126,7 +1126,6 @@ pprGlobalReg gr = case gr of -- JMP_(*R1.p); FloatReg n -> char 'F' <> int n DoubleReg n -> char 'D' <> int n - LongReg n -> char 'L' <> int n Sp -> text "Sp" SpLim -> text "SpLim" Hp -> text "Hp" diff --git a/compiler/GHC/CmmToLlvm/Regs.hs b/compiler/GHC/CmmToLlvm/Regs.hs index b18df77ed4..81505652a3 100644 --- a/compiler/GHC/CmmToLlvm/Regs.hs +++ b/compiler/GHC/CmmToLlvm/Regs.hs @@ -81,7 +81,7 @@ lmGlobalReg platform suf reg MachSp -> wordGlobal $ "MachSp" ++ suf _other -> panic $ "GHC.CmmToLlvm.Reg: GlobalReg (" ++ (show reg) ++ ") not supported!" - -- LongReg, HpLim, CCSS, CurrentTSO, CurrentNusery, HpAlloc + -- HpLim, CCSS, CurrentTSO, CurrentNusery, HpAlloc -- EagerBlackholeInfo, GCEnter1, GCFun, BaseReg, PicBaseReg where wordGlobal name = LMNLocalVar (fsLit name) (llvmWord platform) diff --git a/compiler/GHC/StgToCmm/CgUtils.hs b/compiler/GHC/StgToCmm/CgUtils.hs index 4718cbf74a..d26602b0fd 100644 --- a/compiler/GHC/StgToCmm/CgUtils.hs +++ b/compiler/GHC/StgToCmm/CgUtils.hs @@ -81,8 +81,6 @@ baseRegOffset platform reg = case reg of ZmmReg n -> panic ("Registers above ZMM6 are not supported (tried to use ZMM" ++ show n ++ ")") Sp -> pc_OFFSET_StgRegTable_rSp constants SpLim -> pc_OFFSET_StgRegTable_rSpLim constants - LongReg 1 -> pc_OFFSET_StgRegTable_rL1 constants - LongReg n -> panic ("Registers above L1 are not supported (tried to use L" ++ show n ++ ")") Hp -> pc_OFFSET_StgRegTable_rHp constants HpLim -> pc_OFFSET_StgRegTable_rHpLim constants CCCS -> pc_OFFSET_StgRegTable_rCCCS constants diff --git a/compiler/GHC/StgToCmm/Heap.hs b/compiler/GHC/StgToCmm/Heap.hs index a7e7f23e9d..a1490e5f28 100644 --- a/compiler/GHC/StgToCmm/Heap.hs +++ b/compiler/GHC/StgToCmm/Heap.hs @@ -471,7 +471,6 @@ cannedGCEntryPoint platform regs _ -> Nothing | width == wordWidth platform -> Just (mkGcLabel "stg_gc_unbx_r1") - | width == W64 -> Just (mkGcLabel "stg_gc_l1") | otherwise -> Nothing where width = typeWidth ty |