d24d77a41de532a05f12fc2ce77c67fa1457da4c
[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   argumentsSize,
13 ) where
14
15 #include "HsVersions.h"
16
17 import Cmm
18 import MachOp
19 import SMRep
20
21 import Constants
22 import StaticFlags (opt_Unregisterised)
23 import Panic
24
25 -- Calculate the 'GlobalReg' or stack locations for function call
26 -- parameters as used by the Cmm calling convention.
27
28 data ParamLocation
29   = RegisterParam GlobalReg
30   | StackParam WordOff
31
32 type ArgumentFormat a = [(a, ParamLocation)]
33
34 assignArguments :: (a -> MachRep) -> [a] -> ArgumentFormat a
35 assignArguments f reps = assignments
36     where
37       (sizes, assignments) = unzip $ assignArguments' reps (negate (sum sizes)) availRegs
38       assignArguments' [] offset availRegs = []
39       assignArguments' (r:rs) offset availRegs =
40           (size,(r,assignment)):assignArguments' rs new_offset remaining
41           where 
42             (assignment, new_offset, size, remaining) =
43                 assign_reg (f r) offset availRegs
44
45 argumentsSize :: (a -> MachRep) -> [a] -> WordOff
46 argumentsSize f reps = maximum (0 : map arg_top args)
47     where
48       args = assignArguments f reps
49
50       arg_top (a, StackParam offset) = -offset
51       arg_top (_, RegisterParam _) = 0
52
53 -----------------------------------------------------------------------------
54 -- Local information about the registers available
55
56 type AvailRegs = ( [GlobalReg]   -- available vanilla regs.
57                  , [GlobalReg]   -- floats
58                  , [GlobalReg]   -- doubles
59                  , [GlobalReg]   -- longs (int64 and word64)
60                  )
61
62 -- Vanilla registers can contain pointers, Ints, Chars.
63 -- Floats and doubles have separate register supplies.
64 --
65 -- We take these register supplies from the *real* registers, i.e. those
66 -- that are guaranteed to map to machine registers.
67
68 useVanillaRegs | opt_Unregisterised = 0
69                | otherwise          = mAX_Real_Vanilla_REG
70 useFloatRegs   | opt_Unregisterised = 0
71                | otherwise          = mAX_Real_Float_REG
72 useDoubleRegs  | opt_Unregisterised = 0
73                | otherwise          = mAX_Real_Double_REG
74 useLongRegs    | opt_Unregisterised = 0
75                | otherwise          = mAX_Real_Long_REG
76
77 availRegs = (regList VanillaReg useVanillaRegs,
78              regList FloatReg useFloatRegs,
79              regList DoubleReg useDoubleRegs,
80              regList LongReg useLongRegs)
81     where
82       regList f max = map f [1 .. max]
83
84 slot_size :: LocalReg -> Int
85 slot_size reg =
86     ((machRepByteWidth (localRegRep reg) - 1) `div` wORD_SIZE) + 1
87
88 slot_size' :: MachRep -> Int
89 slot_size' reg = ((machRepByteWidth reg - 1) `div` wORD_SIZE) + 1
90
91 assign_reg :: MachRep -> WordOff -> AvailRegs -> (ParamLocation, WordOff, WordOff, AvailRegs)
92 assign_reg I8  off (v:vs, fs, ds, ls) = (RegisterParam $ v, off, 0, (vs, fs, ds, ls))
93 assign_reg I16 off (v:vs, fs, ds, ls) = (RegisterParam $ v, off, 0, (vs, fs, ds, ls))
94 assign_reg I32 off (v:vs, fs, ds, ls) = (RegisterParam $ v, off, 0, (vs, fs, ds, ls))
95 assign_reg I64 off (vs, fs, ds, l:ls) = (RegisterParam $ l, off, 0, (vs, fs, ds, ls))
96 assign_reg I128 off _                 = panic "I128 is not a supported register type"
97 assign_reg F32 off (vs, f:fs, ds, ls) = (RegisterParam $ f, off, 0, (vs, fs, ds, ls))
98 assign_reg F64 off (vs, fs, d:ds, ls) = (RegisterParam $ d, off, 0, (vs, fs, ds, ls))
99 assign_reg F80 off _                  = panic "F80 is not a supported register type"
100 assign_reg reg off _                  = (StackParam $ off, off + size, size, ([], [], [], [])) where size = slot_size' reg