X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fcmm%2FCmmCallConv.hs;h=210bcb2dbaa755adbc889786fe299433d3776dbd;hb=e4caa74b6c809cd17c5d1f7d472b9a47b2ea6f1c;hp=fed36172330a183f676a960bdc2bae228cb78620;hpb=a52543e55f4bcca008255c3d3947eb82895093b9;p=ghc-hetmet.git diff --git a/compiler/cmm/CmmCallConv.hs b/compiler/cmm/CmmCallConv.hs index fed3617..210bcb2 100644 --- a/compiler/cmm/CmmCallConv.hs +++ b/compiler/cmm/CmmCallConv.hs @@ -13,9 +13,9 @@ import SMRep import ZipCfgCmmRep (Convention(..)) import Constants +import qualified Data.List as L import StaticFlags (opt_Unregisterised) import Outputable -import Panic -- Calculate the 'GlobalReg' or stack locations for function call -- parameters as used by the Cmm calling convention. @@ -32,9 +32,9 @@ type ArgumentFormat a b = [(a, ParamLocation b)] -- Stack parameters are returned as word offsets. assignArguments :: (a -> CmmType) -> [a] -> ArgumentFormat a WordOff -assignArguments f reps = assignments +assignArguments f reps = panic "assignArguments only used in dead codegen" -- assignments where - availRegs = getRegs False + availRegs = getRegsWithNode (sizes, assignments) = unzip $ assignArguments' reps (negate (sum sizes)) availRegs assignArguments' [] _ _ = [] assignArguments' (r:rs) offset availRegs = @@ -46,20 +46,67 @@ assignArguments f reps = assignments -- | JD: For the new stack story, I want arguments passed on the stack to manifest as -- positive offsets in a CallArea, not negative offsets from the stack pointer. -- Also, I want byte offsets, not word offsets. --- The first argument tells us whether we are assigning positions for call arguments --- or return results. The distinction matters because some conventions use different --- global registers in each case. In particular, the native calling convention --- uses the `node' register to pass the closure environment. -assignArgumentsPos :: (Outputable a) => Convention -> Bool -> (a -> CmmType) -> [a] -> +assignArgumentsPos :: (Outputable a) => Convention -> (a -> CmmType) -> [a] -> ArgumentFormat a ByteOff -assignArgumentsPos conv isCall arg_ty reps = map cvt assignments - where - regs = case conv of Native -> getRegs isCall - GC -> getRegs False - PrimOp -> noStack - Slow -> noRegs - _ -> panic "unrecognized calling convention" - (sizes, assignments) = unzip $ assignArguments' reps (sum sizes) regs +assignArgumentsPos conv arg_ty reps = assignments -- old_assts' + where -- The calling conventions (CgCallConv.hs) are complicated, to say the least + regs = case (reps, conv) of + (_, NativeNodeCall) -> getRegsWithNode + (_, NativeDirectCall) -> getRegsWithoutNode + ([_], NativeReturn) -> allRegs + (_, NativeReturn) -> getRegsWithNode + (_, GC) -> getRegsWithNode + (_, PrimOpCall) -> allRegs + ([_], PrimOpReturn) -> allRegs + (_, PrimOpReturn) -> getRegsWithNode + (_, Slow) -> noRegs + _ -> pprPanic "Unknown calling convention" (ppr conv) + -- The calling conventions first assign arguments to registers, + -- then switch to the stack when we first run out of registers + -- (even if there are still available registers for args of a + -- different type). + -- When returning an unboxed tuple, we also separate the stack + -- arguments by pointerhood. + (reg_assts, stk_args) = assign_regs [] reps regs + stk_args' = case conv of NativeReturn -> part + PrimOpReturn -> part + _ -> stk_args + where part = uncurry (++) + (L.partition (not . isGcPtrType . arg_ty) stk_args) + stk_assts = assign_stk 0 [] (reverse stk_args') + assignments = reg_assts ++ stk_assts + + assign_regs assts [] _ = (assts, []) + assign_regs assts (r:rs) regs = if isFloatType ty then float else int + where float = case (w, regs) of + (W32, (vs, f:fs, ds, ls)) -> k (RegisterParam f, (vs, fs, ds, ls)) + (W64, (vs, fs, d:ds, ls)) -> k (RegisterParam d, (vs, fs, ds, ls)) + (W80, _) -> panic "F80 unsupported register type" + _ -> (assts, (r:rs)) + int = case (w, regs) of + (W128, _) -> panic "W128 unsupported register type" + (_, (v:vs, fs, ds, ls)) | widthInBits w <= widthInBits wordWidth + -> k (RegisterParam (v gcp), (vs, fs, ds, ls)) + (_, (vs, fs, ds, l:ls)) | widthInBits w > widthInBits wordWidth + -> k (RegisterParam l, (vs, fs, ds, ls)) + _ -> (assts, (r:rs)) + k (asst, regs') = assign_regs ((r, asst) : assts) rs regs' + ty = arg_ty r + w = typeWidth ty + gcp | isGcPtrType ty = VGcPtr + | otherwise = VNonGcPtr + + assign_stk offset assts [] = assts + assign_stk offset assts (r:rs) = assign_stk off' ((r, StackParam off') : assts) rs + where w = typeWidth (arg_ty r) + size = (((widthInBytes w - 1) `div` wORD_SIZE) + 1) * wORD_SIZE + off' = offset + size + + + -- DEAD CODE: + (old_sizes, old_assignments) = unzip $ assignArguments' reps (sum old_sizes) regs + old_assts' = map cvt old_assignments + assignArguments' [] _ _ = [] assignArguments' (r:rs) offset avails = (size, (r,assignment)):assignArguments' rs new_offset remaining @@ -91,29 +138,38 @@ type AvailRegs = ( [VGcPtr -> GlobalReg] -- available vanilla regs. -- We take these register supplies from the *real* registers, i.e. those -- that are guaranteed to map to machine registers. -useVanillaRegs, useFloatRegs, useDoubleRegs, useLongRegs :: Int -useVanillaRegs | opt_Unregisterised = 0 - | otherwise = mAX_Real_Vanilla_REG -useFloatRegs | opt_Unregisterised = 0 - | otherwise = mAX_Real_Float_REG -useDoubleRegs | opt_Unregisterised = 0 - | otherwise = mAX_Real_Double_REG -useLongRegs | opt_Unregisterised = 0 - | otherwise = mAX_Real_Long_REG - -getRegs :: Bool -> AvailRegs -getRegs reserveNode = - (if reserveNode then filter (\r -> r VGcPtr /= node) intRegs else intRegs, - regList FloatReg useFloatRegs, - regList DoubleReg useDoubleRegs, - regList LongReg useLongRegs) - where - regList f max = map f [1 .. max] - intRegs = regList VanillaReg useVanillaRegs - -noStack :: AvailRegs -noStack = (map VanillaReg any, map FloatReg any, map DoubleReg any, map LongReg any) - where any = [1 .. ] +vanillaRegNos, floatRegNos, doubleRegNos, longRegNos :: [Int] +vanillaRegNos | opt_Unregisterised = [] + | otherwise = regList mAX_Real_Vanilla_REG +floatRegNos | opt_Unregisterised = [] + | otherwise = regList mAX_Real_Float_REG +doubleRegNos | opt_Unregisterised = [] + | otherwise = regList mAX_Real_Double_REG +longRegNos | opt_Unregisterised = [] + | otherwise = regList mAX_Real_Long_REG + +-- +getRegsWithoutNode, getRegsWithNode :: AvailRegs +getRegsWithoutNode = + (filter (\r -> r VGcPtr /= node) intRegs, + map FloatReg floatRegNos, map DoubleReg doubleRegNos, map LongReg longRegNos) + where intRegs = map VanillaReg vanillaRegNos +getRegsWithNode = + (intRegs, map FloatReg floatRegNos, map DoubleReg doubleRegNos, map LongReg longRegNos) + where intRegs = map VanillaReg vanillaRegNos + +allVanillaRegNos, allFloatRegNos, allDoubleRegNos, allLongRegNos :: [Int] +allVanillaRegNos = regList mAX_Vanilla_REG +allFloatRegNos = regList mAX_Float_REG +allDoubleRegNos = regList mAX_Double_REG +allLongRegNos = regList mAX_Long_REG + +regList :: Int -> [Int] +regList n = [1 .. n] + +allRegs :: AvailRegs +allRegs = (map VanillaReg allVanillaRegNos, map FloatReg allFloatRegNos, + map DoubleReg allDoubleRegNos, map LongReg allLongRegNos) noRegs :: AvailRegs noRegs = ([], [], [], []) @@ -143,7 +199,7 @@ assign_reg slot ty off avails -- Assigning a slot using negative offsets from the stack pointer. -- JD: I don't know why this convention stops using all the registers --- after running out of one class of registers. +-- after running out of one class of registers, but that's how it is. assign_slot_neg :: SlotAssigner assign_slot_neg width off _regs = (StackParam $ off, off + size, size, ([], [], [], [])) where size = slot_size' width @@ -156,15 +212,15 @@ assign_slot_pos width off _regs = -- On calls in the native convention, `node` is used to hold the environment -- for the closure, so we can't pass arguments in that register. -assign_bits_reg :: SlotAssigner -> Width -> WordOff -> VGcPtr -> AvailRegs - -> Assignment +assign_bits_reg :: SlotAssigner -> Width -> WordOff -> VGcPtr -> AvailRegs -> Assignment assign_bits_reg _ W128 _ _ _ = panic "W128 is not a supported register type" -assign_bits_reg assign_slot w off gcp regs@(v:vs, fs, ds, ls) = - if widthInBits w <= widthInBits wordWidth then - (RegisterParam (v gcp), off, 0, (vs, fs, ds, ls)) - else assign_slot w off regs -assign_bits_reg assign_slot w off _ regs@([], _, _, _) = - assign_slot w off regs +assign_bits_reg _ w off gcp (v:vs, fs, ds, ls) + | widthInBits w <= widthInBits wordWidth = + (RegisterParam (v gcp), off, 0, (vs, fs, ds, ls)) +assign_bits_reg _ w off _ (vs, fs, ds, l:ls) + | widthInBits w > widthInBits wordWidth = + (RegisterParam l, off, 0, (vs, fs, ds, ls)) +assign_bits_reg assign_slot w off _ regs@(_, _, _, _) = assign_slot w off regs assign_float_reg :: SlotAssigner -> Width -> WordOff -> AvailRegs -> Assignment assign_float_reg _ W32 off (vs, f:fs, ds, ls) = (RegisterParam $ f, off, 0, (vs, fs, ds, ls))