Merge branch 'master' of http://darcs.haskell.org/ghc
[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 CmmExpr
12 import SMRep
13 import Cmm (Convention(..))
14 import PprCmm ()
15
16 import Constants
17 import qualified Data.List as L
18 import StaticFlags (opt_Unregisterised)
19 import Outputable
20
21 -- Calculate the 'GlobalReg' or stack locations for function call
22 -- parameters as used by the Cmm calling convention.
23
24 data ParamLocation a
25   = RegisterParam GlobalReg
26   | StackParam a
27
28 instance (Outputable a) => Outputable (ParamLocation a) where
29   ppr (RegisterParam g) = ppr g
30   ppr (StackParam p)    = ppr p
31
32 type ArgumentFormat a b = [(a, ParamLocation b)]
33
34 assignArguments :: (a -> CmmType) -> [a] -> ArgumentFormat a WordOff
35 -- Stack parameters are returned as word offsets.
36 assignArguments _ _ = panic "assignArguments only used in dead codegen" -- assignments
37
38 -- | JD: For the new stack story, I want arguments passed on the stack to manifest as
39 -- positive offsets in a CallArea, not negative offsets from the stack pointer.
40 -- Also, I want byte offsets, not word offsets.
41 assignArgumentsPos :: (Outputable a) => Convention -> (a -> CmmType) -> [a] ->
42                       ArgumentFormat a ByteOff
43 -- Given a list of arguments, and a function that tells their types,
44 -- return a list showing where each argument is passed
45 assignArgumentsPos conv arg_ty reps = assignments
46     where -- The calling conventions (CgCallConv.hs) are complicated, to say the least
47       regs = case (reps, conv) of
48                (_,   NativeNodeCall)   -> getRegsWithNode
49                (_,   NativeDirectCall) -> getRegsWithoutNode
50                ([_], NativeReturn)     -> allRegs
51                (_,   NativeReturn)     -> getRegsWithNode
52                -- GC calling convention *must* put values in registers
53                (_,   GC)               -> allRegs
54                (_,   PrimOpCall)       -> allRegs
55                ([_], PrimOpReturn)     -> allRegs
56                (_,   PrimOpReturn)     -> getRegsWithNode
57                (_,   Slow)             -> noRegs
58                _ -> pprPanic "Unknown calling convention" (ppr conv)
59       -- The calling conventions first assign arguments to registers,
60       -- then switch to the stack when we first run out of registers
61       -- (even if there are still available registers for args of a different type).
62       -- When returning an unboxed tuple, we also separate the stack
63       -- arguments by pointerhood.
64       (reg_assts, stk_args) = assign_regs [] reps regs
65       stk_args' = case conv of NativeReturn -> part
66                                PrimOpReturn -> part
67                                GC | length stk_args /= 0 -> panic "Failed to allocate registers for GC call"
68                                _            -> stk_args
69                   where part = uncurry (++)
70                                        (L.partition (not . isGcPtrType . arg_ty) stk_args)
71       stk_assts = assign_stk 0 [] (reverse stk_args')
72       assignments = reg_assts ++ stk_assts
73
74       assign_regs assts []     _    = (assts, [])
75       assign_regs assts (r:rs) regs = if isFloatType ty then float else int
76         where float = case (w, regs) of
77                         (W32, (vs, f:fs, ds, ls)) -> k (RegisterParam f, (vs, fs, ds, ls))
78                         (W64, (vs, fs, d:ds, ls)) -> k (RegisterParam d, (vs, fs, ds, ls))
79                         (W80, _) -> panic "F80 unsupported register type"
80                         _ -> (assts, (r:rs))
81               int = case (w, regs) of
82                       (W128, _) -> panic "W128 unsupported register type"
83                       (_, (v:vs, fs, ds, ls)) | widthInBits w <= widthInBits wordWidth
84                           -> k (RegisterParam (v gcp), (vs, fs, ds, ls))
85                       (_, (vs, fs, ds, l:ls)) | widthInBits w > widthInBits wordWidth
86                           -> k (RegisterParam l, (vs, fs, ds, ls))
87                       _   -> (assts, (r:rs))
88               k (asst, regs') = assign_regs ((r, asst) : assts) rs regs'
89               ty = arg_ty r
90               w  = typeWidth ty
91               gcp | isGcPtrType ty = VGcPtr
92                   | otherwise      = VNonGcPtr
93
94       assign_stk _      assts [] = assts
95       assign_stk offset assts (r:rs) = assign_stk off' ((r, StackParam off') : assts) rs
96         where w    = typeWidth (arg_ty r)
97               size = (((widthInBytes w - 1) `div` wORD_SIZE) + 1) * wORD_SIZE
98               off' = offset + size
99        
100      
101 argumentsSize :: (a -> CmmType) -> [a] -> WordOff
102 argumentsSize f reps = maximum (0 : map arg_top args)
103     where
104       args = assignArguments f reps
105       arg_top (_, StackParam offset) = -offset
106       arg_top (_, RegisterParam _) = 0
107
108 -----------------------------------------------------------------------------
109 -- Local information about the registers available
110
111 type AvailRegs = ( [VGcPtr -> GlobalReg]   -- available vanilla regs.
112                  , [GlobalReg]   -- floats
113                  , [GlobalReg]   -- doubles
114                  , [GlobalReg]   -- longs (int64 and word64)
115                  )
116
117 -- Vanilla registers can contain pointers, Ints, Chars.
118 -- Floats and doubles have separate register supplies.
119 --
120 -- We take these register supplies from the *real* registers, i.e. those
121 -- that are guaranteed to map to machine registers.
122
123 vanillaRegNos, floatRegNos, doubleRegNos, longRegNos :: [Int]
124 vanillaRegNos | opt_Unregisterised = []
125               | otherwise          = regList mAX_Real_Vanilla_REG
126 floatRegNos       | opt_Unregisterised = []
127               | otherwise          = regList mAX_Real_Float_REG
128 doubleRegNos  | opt_Unregisterised = []
129               | otherwise          = regList mAX_Real_Double_REG
130 longRegNos        | opt_Unregisterised = []
131               | otherwise          = regList mAX_Real_Long_REG
132
133 -- 
134 getRegsWithoutNode, getRegsWithNode :: AvailRegs
135 getRegsWithoutNode =
136   (filter (\r -> r VGcPtr /= node) intRegs,
137    map FloatReg  floatRegNos, map DoubleReg doubleRegNos, map LongReg longRegNos)
138     where intRegs = map VanillaReg vanillaRegNos
139 getRegsWithNode =
140   (intRegs, map FloatReg  floatRegNos, map DoubleReg doubleRegNos, map LongReg longRegNos)
141     where intRegs = map VanillaReg vanillaRegNos
142
143 allVanillaRegNos, allFloatRegNos, allDoubleRegNos, allLongRegNos :: [Int]
144 allVanillaRegNos = regList mAX_Vanilla_REG
145 allFloatRegNos   = regList mAX_Float_REG
146 allDoubleRegNos  = regList mAX_Double_REG
147 allLongRegNos      = regList mAX_Long_REG
148
149 regList :: Int -> [Int]
150 regList n = [1 .. n]
151
152 allRegs :: AvailRegs
153 allRegs = (map VanillaReg allVanillaRegNos, map FloatReg allFloatRegNos,
154            map DoubleReg  allDoubleRegNos,  map LongReg  allLongRegNos)
155
156 noRegs :: AvailRegs
157 noRegs    = ([], [], [], [])