Merging in 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
21 import Constants
22 import StaticFlags (opt_Unregisterised)
23 import Outputable
24 import Panic
25
26 -- Calculate the 'GlobalReg' or stack locations for function call
27 -- parameters as used by the Cmm calling convention.
28
29 data ParamLocation a
30   = RegisterParam GlobalReg
31   | StackParam a
32
33 type ArgumentFormat a b = [(a, ParamLocation b)]
34
35 -- Stack parameters are returned as word offsets.
36 assignArguments :: (a -> CmmType) -> [a] -> ArgumentFormat a WordOff
37 assignArguments f reps = assignments
38     where
39       (sizes, assignments) = unzip $ assignArguments' reps (negate (sum sizes)) availRegs
40       assignArguments' [] offset availRegs = []
41       assignArguments' (r:rs) offset availRegs =
42           (size,(r,assignment)):assignArguments' rs new_offset remaining
43           where 
44             (assignment, new_offset, size, remaining) =
45                 assign_reg False assign_slot_up (f r) offset availRegs
46
47 -- | JD: For the new stack story, I want arguments passed on the stack to manifest as
48 -- positive offsets in a CallArea, not negative offsets from the stack pointer.
49 -- Also, I want byte offsets, not word offsets.
50 -- The first argument tells us whether we are assigning positions for call arguments
51 -- or return results. The distinction matters because we reserve different
52 -- global registers in each case.
53 assignArgumentsPos :: Bool -> (a -> CmmType) -> [a] -> ArgumentFormat a ByteOff
54 assignArgumentsPos isCall arg_ty reps = map cvt assignments
55     where
56       (sizes, assignments) = unzip $ assignArguments' reps 0 availRegs
57       assignArguments' [] _ _ = []
58       assignArguments' (r:rs) offset avails =
59           (size,(r,assignment)):assignArguments' rs new_offset remaining
60           where 
61             (assignment, new_offset, size, remaining) =
62                 assign_reg isCall assign_slot_down (arg_ty r) offset avails
63       cvt (l, RegisterParam r) = (l, RegisterParam r)
64       cvt (l, StackParam off)  = (l, StackParam $ off * wORD_SIZE)
65
66 argumentsSize :: (a -> CmmType) -> [a] -> WordOff
67 argumentsSize f reps = maximum (0 : map arg_top args)
68     where
69       args = assignArguments f reps
70       arg_top (a, StackParam offset) = -offset
71       arg_top (_, RegisterParam _) = 0
72
73 -----------------------------------------------------------------------------
74 -- Local information about the registers available
75
76 type AvailRegs = ( [VGcPtr -> GlobalReg]   -- available vanilla regs.
77                  , [GlobalReg]   -- floats
78                  , [GlobalReg]   -- doubles
79                  , [GlobalReg]   -- longs (int64 and word64)
80                  )
81
82 -- Vanilla registers can contain pointers, Ints, Chars.
83 -- Floats and doubles have separate register supplies.
84 --
85 -- We take these register supplies from the *real* registers, i.e. those
86 -- that are guaranteed to map to machine registers.
87
88 useVanillaRegs | opt_Unregisterised = 0
89                | otherwise          = mAX_Real_Vanilla_REG
90 useFloatRegs   | opt_Unregisterised = 0
91                | otherwise          = mAX_Real_Float_REG
92 useDoubleRegs  | opt_Unregisterised = 0
93                | otherwise          = mAX_Real_Double_REG
94 useLongRegs    | opt_Unregisterised = 0
95                | otherwise          = mAX_Real_Long_REG
96
97 availRegs = (regList VanillaReg useVanillaRegs,
98              regList FloatReg useFloatRegs,
99              regList DoubleReg useDoubleRegs,
100              regList LongReg useLongRegs)
101     where
102       regList f max = map f [1 .. max]
103
104 -- Round the size of a local register up to the nearest word.
105 slot_size :: LocalReg -> Int
106 slot_size reg = slot_size' (typeWidth (localRegType reg))
107
108 slot_size' :: Width -> Int
109 slot_size' reg = ((widthInBytes reg - 1) `div` wORD_SIZE) + 1
110
111 type Assignment = (ParamLocation WordOff, WordOff, WordOff, AvailRegs)
112 type SlotAssigner = Width -> Int -> AvailRegs -> Assignment
113
114 assign_reg :: Bool -> SlotAssigner -> CmmType -> WordOff -> AvailRegs -> Assignment
115 assign_reg isCall slot ty off avails
116   | isFloatType ty = assign_float_reg        slot width off avails
117   | otherwise      = assign_bits_reg  isCall slot width off gcp avails
118   where
119     width = typeWidth ty
120     gcp | isGcPtrType ty = VGcPtr
121         | otherwise      = VNonGcPtr
122
123 -- Assigning a slot on a stack that grows up:
124 -- JD: I don't know why this convention stops using all the registers
125 --     after running out of one class of registers.
126 assign_slot_up :: SlotAssigner
127 assign_slot_up width off regs =
128   (StackParam $ off, off + size, size, ([], [], [], [])) where size = slot_size' width
129
130 -- Assigning a slot on a stack that grows down:
131 assign_slot_down :: SlotAssigner
132 assign_slot_down width off regs =
133   (StackParam $ off + size, off + size, size, ([], [], [], []))
134   where size = slot_size' width
135
136 -- On calls, `node` is used to hold the closure that is entered, so we can't
137 -- pass arguments in that register.
138 assign_bits_reg _ _ W128 _ _ _ = panic "I128 is not a supported register type"
139 assign_bits_reg isCall assign_slot w off gcp regs@(v:vs, fs, ds, ls) =
140   if isCall && v gcp == node then
141     assign_bits_reg isCall assign_slot w off gcp (vs, fs, ds, ls)
142   else if widthInBits w <= widthInBits wordWidth then
143     (RegisterParam (v gcp), off, 0, (vs, fs, ds, ls))
144   else assign_slot w off regs
145
146 assign_float_reg _ W32 off (vs, f:fs, ds, ls) = (RegisterParam $ f, off, 0, (vs, fs, ds, ls))
147 assign_float_reg _ W64 off (vs, fs, d:ds, ls) = (RegisterParam $ d, off, 0, (vs, fs, ds, ls))
148 assign_float_reg _ W80 off _                  = panic "F80 is not a supported register type"
149 assign_float_reg assign_slot width off r = assign_slot width off r