X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fcmm%2FCmmCallConv.hs;h=c81b868167f070b0de92b6613474ee1607236814;hb=5909e9a896d40a18b4bcf6abb95e0b071bfd7db2;hp=210bcb2dbaa755adbc889786fe299433d3776dbd;hpb=e4caa74b6c809cd17c5d1f7d472b9a47b2ea6f1c;p=ghc-hetmet.git diff --git a/compiler/cmm/CmmCallConv.hs b/compiler/cmm/CmmCallConv.hs index 210bcb2..c81b868 100644 --- a/compiler/cmm/CmmCallConv.hs +++ b/compiler/cmm/CmmCallConv.hs @@ -1,16 +1,14 @@ module CmmCallConv ( ParamLocation(..), - ArgumentFormat, - assignArguments, - assignArgumentsPos, - argumentsSize, + assignArgumentsPos ) where #include "HsVersions.h" -import Cmm +import CmmExpr import SMRep -import ZipCfgCmmRep (Convention(..)) +import Cmm (Convention(..)) +import PprCmm () import Constants import qualified Data.List as L @@ -20,42 +18,30 @@ import Outputable -- Calculate the 'GlobalReg' or stack locations for function call -- parameters as used by the Cmm calling convention. -data ParamLocation a +data ParamLocation = RegisterParam GlobalReg - | StackParam a + | StackParam ByteOff -instance (Outputable a) => Outputable (ParamLocation a) where +instance Outputable ParamLocation where ppr (RegisterParam g) = ppr g ppr (StackParam p) = ppr p -type ArgumentFormat a b = [(a, ParamLocation b)] - --- Stack parameters are returned as word offsets. -assignArguments :: (a -> CmmType) -> [a] -> ArgumentFormat a WordOff -assignArguments f reps = panic "assignArguments only used in dead codegen" -- assignments - where - availRegs = getRegsWithNode - (sizes, assignments) = unzip $ assignArguments' reps (negate (sum sizes)) availRegs - assignArguments' [] _ _ = [] - assignArguments' (r:rs) offset availRegs = - (size,(r,assignment)):assignArguments' rs new_offset remaining - where - (assignment, new_offset, size, remaining) = - assign_reg assign_slot_neg (f r) offset availRegs - -- | 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. -assignArgumentsPos :: (Outputable a) => Convention -> (a -> CmmType) -> [a] -> - ArgumentFormat a ByteOff -assignArgumentsPos conv arg_ty reps = assignments -- old_assts' +assignArgumentsPos :: Convention -> (a -> CmmType) -> [a] -> + [(a, ParamLocation)] +-- Given a list of arguments, and a function that tells their types, +-- return a list showing where each argument is passed +assignArgumentsPos conv arg_ty reps = assignments 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 + -- GC calling convention *must* put values in registers + (_, GC) -> allRegs (_, PrimOpCall) -> allRegs ([_], PrimOpReturn) -> allRegs (_, PrimOpReturn) -> getRegsWithNode @@ -63,13 +49,13 @@ assignArgumentsPos conv arg_ty reps = assignments -- old_assts' _ -> 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). + -- (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 + GC | length stk_args /= 0 -> panic "Failed to allocate registers for GC call" _ -> stk_args where part = uncurry (++) (L.partition (not . isGcPtrType . arg_ty) stk_args) @@ -96,41 +82,20 @@ assignArgumentsPos conv arg_ty reps = assignments -- old_assts' gcp | isGcPtrType ty = VGcPtr | otherwise = VNonGcPtr - assign_stk offset assts [] = assts + assign_stk _ 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 - where - (assignment, new_offset, size, remaining) = - assign_reg assign_slot_pos (arg_ty r) offset avails - cvt (l, RegisterParam r) = (l, RegisterParam r) - cvt (l, StackParam off) = (l, StackParam $ off * wORD_SIZE) - -argumentsSize :: (a -> CmmType) -> [a] -> WordOff -argumentsSize f reps = maximum (0 : map arg_top args) - where - args = assignArguments f reps - arg_top (_, StackParam offset) = -offset - arg_top (_, RegisterParam _) = 0 ----------------------------------------------------------------------------- -- Local information about the registers available type AvailRegs = ( [VGcPtr -> GlobalReg] -- available vanilla regs. - , [GlobalReg] -- floats - , [GlobalReg] -- doubles - , [GlobalReg] -- longs (int64 and word64) - ) + , [GlobalReg] -- floats + , [GlobalReg] -- doubles + , [GlobalReg] -- longs (int64 and word64) + ) -- Vanilla registers can contain pointers, Ints, Chars. -- Floats and doubles have separate register supplies. @@ -173,57 +138,3 @@ allRegs = (map VanillaReg allVanillaRegNos, map FloatReg allFloatRegNos, noRegs :: AvailRegs noRegs = ([], [], [], []) - --- Round the size of a local register up to the nearest word. -{- -UNUSED 2008-12-29 - -slot_size :: LocalReg -> Int -slot_size reg = slot_size' (typeWidth (localRegType reg)) --} - -slot_size' :: Width -> Int -slot_size' reg = ((widthInBytes reg - 1) `div` wORD_SIZE) + 1 - -type Assignment = (ParamLocation WordOff, WordOff, WordOff, AvailRegs) -type SlotAssigner = Width -> Int -> AvailRegs -> Assignment - -assign_reg :: SlotAssigner -> CmmType -> WordOff -> AvailRegs -> Assignment -assign_reg slot ty off avails - | isFloatType ty = assign_float_reg slot width off avails - | otherwise = assign_bits_reg slot width off gcp avails - where - width = typeWidth ty - gcp | isGcPtrType ty = VGcPtr - | otherwise = VNonGcPtr - --- 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, 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 - --- Assigning a slot using positive offsets into a CallArea. -assign_slot_pos :: SlotAssigner -assign_slot_pos width off _regs = - (StackParam $ off, off - size, size, ([], [], [], [])) - where size = slot_size' width - --- 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 _ W128 _ _ _ = panic "W128 is not a supported register type" -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)) -assign_float_reg _ W64 off (vs, fs, d:ds, ls) = (RegisterParam $ d, off, 0, (vs, fs, ds, ls)) -assign_float_reg _ W80 _ _ = panic "F80 is not a supported register type" -assign_float_reg assign_slot width off r = assign_slot width off r