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