summaryrefslogtreecommitdiff
path: root/compiler/cmm/CmmCallConv.hs
diff options
context:
space:
mode:
authordias@cs.tufts.edu <unknown>2009-09-18 19:29:32 +0000
committerdias@cs.tufts.edu <unknown>2009-09-18 19:29:32 +0000
commitc6206fd81612e51e257a650390646421c7c1d1cb (patch)
treee4c1befffb9741db9e4ec1bc97b2c8c70b1b1d48 /compiler/cmm/CmmCallConv.hs
parentced4c754ae05fcd3fb7afb0ca3218517011f231c (diff)
downloadhaskell-c6206fd81612e51e257a650390646421c7c1d1cb.tar.gz
Morguing dead code
Diffstat (limited to 'compiler/cmm/CmmCallConv.hs')
-rw-r--r--compiler/cmm/CmmCallConv.hs93
1 files changed, 8 insertions, 85 deletions
diff --git a/compiler/cmm/CmmCallConv.hs b/compiler/cmm/CmmCallConv.hs
index 210bcb2dba..3fb347f7d2 100644
--- a/compiler/cmm/CmmCallConv.hs
+++ b/compiler/cmm/CmmCallConv.hs
@@ -32,23 +32,14 @@ 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
+assignArguments _ _ = panic "assignArguments only used in dead codegen" -- 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.
assignArgumentsPos :: (Outputable a) => Convention -> (a -> CmmType) -> [a] ->
ArgumentFormat a ByteOff
-assignArgumentsPos conv arg_ty reps = assignments -- old_assts'
+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
@@ -63,8 +54,7 @@ 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
@@ -96,26 +86,13 @@ 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
@@ -127,10 +104,10 @@ argumentsSize f reps = maximum (0 : map arg_top args)
-- 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 +150,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