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