A few bug fixes; some improvements spurred by paper writing
[ghc-hetmet.git] / compiler / cmm / CmmCallConv.hs
1 module CmmCallConv (
2   ParamLocation(..),
3   ArgumentFormat,
4   assignArguments,
5   assignArgumentsPos,
6   argumentsSize,
7 ) where
8
9 #include "HsVersions.h"
10
11 import Cmm
12 import SMRep
13 import ZipCfgCmmRep (Convention(..))
14
15 import Constants
16 import StaticFlags (opt_Unregisterised)
17 import Outputable
18 import Panic
19
20 -- Calculate the 'GlobalReg' or stack locations for function call
21 -- parameters as used by the Cmm calling convention.
22
23 data ParamLocation a
24   = RegisterParam GlobalReg
25   | StackParam a
26
27 instance (Outputable a) => Outputable (ParamLocation a) where
28   ppr (RegisterParam g) = ppr g
29   ppr (StackParam p)    = ppr p
30
31 type ArgumentFormat a b = [(a, ParamLocation b)]
32
33 -- Stack parameters are returned as word offsets.
34 assignArguments :: (a -> CmmType) -> [a] -> ArgumentFormat a WordOff
35 assignArguments f reps = assignments
36     where
37       availRegs = getRegs False
38       (sizes, assignments) = unzip $ assignArguments' reps (negate (sum sizes)) availRegs
39       assignArguments' [] _ _ = []
40       assignArguments' (r:rs) offset availRegs =
41           (size,(r,assignment)):assignArguments' rs new_offset remaining
42           where 
43             (assignment, new_offset, size, remaining) =
44                 assign_reg assign_slot_neg (f r) offset availRegs
45
46 -- | JD: For the new stack story, I want arguments passed on the stack to manifest as
47 -- positive offsets in a CallArea, not negative offsets from the stack pointer.
48 -- Also, I want byte offsets, not word offsets.
49 -- The first argument tells us whether we are assigning positions for call arguments
50 -- or return results. The distinction matters because some conventions use different
51 -- global registers in each case. In particular, the native calling convention
52 -- uses the `node' register to pass the closure environment.
53 assignArgumentsPos :: (Outputable a) => Convention -> Bool -> (a -> CmmType) -> [a] ->
54                       ArgumentFormat a ByteOff
55 assignArgumentsPos conv isCall arg_ty reps = map cvt assignments
56     where
57       regs = case conv of Native -> getRegs isCall
58                           GC     -> getRegs False
59                           PrimOp -> if isCall then noStack else getRegs isCall
60                           Slow   -> noRegs
61                           _   -> getRegs isCall
62                           -- _      -> panic "unrecognized calling convention"
63       (sizes, assignments) = unzip $ assignArguments' reps (sum sizes) regs
64       assignArguments' [] _ _ = []
65       assignArguments' (r:rs) offset avails =
66           (size, (r,assignment)):assignArguments' rs new_offset remaining
67           where 
68             (assignment, new_offset, size, remaining) =
69                 assign_reg assign_slot_pos (arg_ty r) offset avails
70       cvt (l, RegisterParam r) = (l, RegisterParam r)
71       cvt (l, StackParam off)  = (l, StackParam $ off * wORD_SIZE)
72
73 argumentsSize :: (a -> CmmType) -> [a] -> WordOff
74 argumentsSize f reps = maximum (0 : map arg_top args)
75     where
76       args = assignArguments f reps
77       arg_top (_, StackParam offset) = -offset
78       arg_top (_, RegisterParam _) = 0
79
80 -----------------------------------------------------------------------------
81 -- Local information about the registers available
82
83 type AvailRegs = ( [VGcPtr -> GlobalReg]   -- available vanilla regs.
84                  , [GlobalReg]   -- floats
85                  , [GlobalReg]   -- doubles
86                  , [GlobalReg]   -- longs (int64 and word64)
87                  )
88
89 -- Vanilla registers can contain pointers, Ints, Chars.
90 -- Floats and doubles have separate register supplies.
91 --
92 -- We take these register supplies from the *real* registers, i.e. those
93 -- that are guaranteed to map to machine registers.
94
95 useVanillaRegs, useFloatRegs, useDoubleRegs, useLongRegs :: Int
96 useVanillaRegs | opt_Unregisterised = 0
97                | otherwise          = mAX_Real_Vanilla_REG
98 useFloatRegs   | opt_Unregisterised = 0
99                | otherwise          = mAX_Real_Float_REG
100 useDoubleRegs  | opt_Unregisterised = 0
101                | otherwise          = mAX_Real_Double_REG
102 useLongRegs    | opt_Unregisterised = 0
103                | otherwise          = mAX_Real_Long_REG
104
105 getRegs :: Bool -> AvailRegs
106 getRegs reserveNode =
107   (if reserveNode then filter (\r -> r VGcPtr /= node) intRegs else intRegs,
108    regList FloatReg  useFloatRegs,
109    regList DoubleReg useDoubleRegs,
110    regList LongReg   useLongRegs)
111     where
112       regList f max = map f [1 .. max]
113       intRegs = regList VanillaReg useVanillaRegs
114
115 noStack :: AvailRegs
116 noStack = (map VanillaReg any, map FloatReg any, map DoubleReg any, map LongReg any)
117   where any = [1 .. ]
118
119 noRegs :: AvailRegs
120 noRegs    = ([], [], [], [])
121
122 -- Round the size of a local register up to the nearest word.
123 {-
124 UNUSED 2008-12-29
125
126 slot_size :: LocalReg -> Int
127 slot_size reg = slot_size' (typeWidth (localRegType reg))
128 -}
129
130 slot_size' :: Width -> Int
131 slot_size' reg = ((widthInBytes reg - 1) `div` wORD_SIZE) + 1
132
133 type Assignment = (ParamLocation WordOff, WordOff, WordOff, AvailRegs)
134 type SlotAssigner = Width -> Int -> AvailRegs -> Assignment
135
136 assign_reg :: SlotAssigner -> CmmType -> WordOff -> AvailRegs -> Assignment
137 assign_reg slot ty off avails
138   | isFloatType ty = assign_float_reg slot width off avails
139   | otherwise      = assign_bits_reg  slot width off gcp avails
140   where
141     width = typeWidth ty
142     gcp | isGcPtrType ty = VGcPtr
143         | otherwise      = VNonGcPtr
144
145 -- Assigning a slot using negative offsets from the stack pointer.
146 -- JD: I don't know why this convention stops using all the registers
147 --     after running out of one class of registers.
148 assign_slot_neg :: SlotAssigner
149 assign_slot_neg width off _regs =
150   (StackParam $ off, off + size, size, ([], [], [], [])) where size = slot_size' width
151
152 -- Assigning a slot using positive offsets into a CallArea.
153 assign_slot_pos :: SlotAssigner
154 assign_slot_pos width off _regs =
155   (StackParam $ off, off - size, size, ([], [], [], []))
156   where size = slot_size' width
157
158 -- On calls in the native convention, `node` is used to hold the environment
159 -- for the closure, so we can't pass arguments in that register.
160 assign_bits_reg :: SlotAssigner -> Width -> WordOff -> VGcPtr -> AvailRegs
161                 -> Assignment
162 assign_bits_reg _ W128 _ _ _ = panic "W128 is not a supported register type"
163 assign_bits_reg assign_slot w off gcp regs@(v:vs, fs, ds, ls) =
164   if widthInBits w <= widthInBits wordWidth then
165     (RegisterParam (v gcp), off, 0, (vs, fs, ds, ls))
166   else assign_slot w off regs
167 assign_bits_reg assign_slot w off _ regs@([], _, _, _) =
168   assign_slot w off regs
169
170 assign_float_reg :: SlotAssigner -> Width -> WordOff -> AvailRegs -> Assignment
171 assign_float_reg _ W32 off (vs, f:fs, ds, ls) = (RegisterParam $ f, off, 0, (vs, fs, ds, ls))
172 assign_float_reg _ W64 off (vs, fs, d:ds, ls) = (RegisterParam $ d, off, 0, (vs, fs, ds, ls))
173 assign_float_reg _ W80 _   _                  = panic "F80 is not a supported register type"
174 assign_float_reg assign_slot width off r = assign_slot width off r