[project @ 2000-09-06 10:23:52 by simonmar]
[ghc-hetmet.git] / ghc / compiler / codeGen / CgRetConv.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1992-1998
3 %
4 % $Id: CgRetConv.lhs,v 1.25 2000/09/06 10:23:52 simonmar Exp $
5 %
6 \section[CgRetConv]{Return conventions for the code generator}
7
8 The datatypes and functions here encapsulate what there is to know
9 about return conventions.
10
11 \begin{code}
12 module CgRetConv (
13         CtrlReturnConvention(..),
14         ctrlReturnConvAlg,
15         dataReturnConvPrim,
16         assignRegs, assignAllRegs
17     ) where
18
19 #include "HsVersions.h"
20
21 import AbsCSyn          -- quite a few things
22 import Constants        ( mAX_FAMILY_SIZE_FOR_VEC_RETURNS,
23                           mAX_Vanilla_REG, mAX_Float_REG,
24                           mAX_Double_REG, mAX_Long_REG
25                         )
26 import CmdLineOpts      ( opt_UseVanillaRegs, opt_UseFloatRegs,
27                           opt_UseDoubleRegs, opt_UseLongRegs
28                         )
29 import Maybes           ( catMaybes )
30 import PrimRep          ( isFloatingRep, PrimRep(..), is64BitRep )
31 import TyCon            ( TyCon, tyConFamilySize )
32 import Util             ( isn'tIn )
33
34 import Outputable
35 \end{code}
36
37 %************************************************************************
38 %*                                                                      *
39 \subsection[CgRetConv-possibilities]{Data types that encode possible return conventions}
40 %*                                                                      *
41 %************************************************************************
42
43 A @CtrlReturnConvention@ says how {\em control} is returned.
44 \begin{code}
45 data CtrlReturnConvention
46   = VectoredReturn      Int     -- size of the vector table (family size)
47   | UnvectoredReturn    Int     -- family size
48 \end{code}
49
50 %************************************************************************
51 %*                                                                      *
52 \subsection[CgRetConv-algebraic]{Return conventions for algebraic datatypes}
53 %*                                                                      *
54 %************************************************************************
55
56 \begin{code}
57 ctrlReturnConvAlg :: TyCon -> CtrlReturnConvention
58
59 ctrlReturnConvAlg tycon
60   = case (tyConFamilySize tycon) of
61       0 -> panic "ctrlRetConvAlg"
62       size -> -- we're supposed to know...
63         if (size > (1::Int) && size <= mAX_FAMILY_SIZE_FOR_VEC_RETURNS) then
64             VectoredReturn size
65         else
66             UnvectoredReturn size
67 \end{code}
68
69 %************************************************************************
70 %*                                                                      *
71 \subsection[CgRetConv-prim]{Return conventions for primitive datatypes}
72 %*                                                                      *
73 %************************************************************************
74
75 \begin{code}
76 dataReturnConvPrim :: PrimRep -> MagicId
77
78 dataReturnConvPrim IntRep       = VanillaReg IntRep  ILIT(1)
79 dataReturnConvPrim WordRep      = VanillaReg WordRep ILIT(1)
80 dataReturnConvPrim Int64Rep     = LongReg Int64Rep  ILIT(1)
81 dataReturnConvPrim Word64Rep    = LongReg Word64Rep ILIT(1)
82 dataReturnConvPrim AddrRep      = VanillaReg AddrRep ILIT(1)
83 dataReturnConvPrim CharRep      = VanillaReg CharRep ILIT(1)
84 dataReturnConvPrim Int8Rep      = VanillaReg Int8Rep ILIT(1)
85 dataReturnConvPrim FloatRep     = FloatReg  ILIT(1)
86 dataReturnConvPrim DoubleRep    = DoubleReg ILIT(1)
87 dataReturnConvPrim VoidRep      = VoidReg
88
89 -- Return a primitive-array pointer in the usual register:
90 dataReturnConvPrim ArrayRep     = VanillaReg ArrayRep ILIT(1)
91 dataReturnConvPrim ByteArrayRep = VanillaReg ByteArrayRep ILIT(1)
92 dataReturnConvPrim PrimPtrRep   = VanillaReg PrimPtrRep ILIT(1)
93
94 dataReturnConvPrim StablePtrRep = VanillaReg StablePtrRep ILIT(1)
95 dataReturnConvPrim ForeignObjRep = VanillaReg ForeignObjRep ILIT(1)
96 dataReturnConvPrim WeakPtrRep   = VanillaReg WeakPtrRep ILIT(1)
97
98 #ifdef DEBUG
99 dataReturnConvPrim PtrRep       = panic "dataReturnConvPrim: PtrRep"
100 dataReturnConvPrim _            = panic "dataReturnConvPrim: other"
101 #endif
102 \end{code}
103
104 %************************************************************************
105 %*                                                                      *
106 \subsubsection[CgRetConv-regs]{Register assignment}
107 %*                                                                      *
108 %************************************************************************
109
110 How to assign registers for 
111
112         1) Calling a fast entry point.
113         2) Returning an unboxed tuple.
114         3) Invoking an out-of-line PrimOp.
115
116 Registers are assigned in order.
117
118 If we run out, we don't attempt to assign any further registers (even
119 though we might have run out of only one kind of register); we just
120 return immediately with the left-overs specified.
121
122 The alternative version @assignAllRegs@ uses the complete set of
123 registers, including those that aren't mapped to real machine
124 registers.  This is used for calling special RTS functions and PrimOps
125 which expect their arguments to always be in the same registers.
126
127 \begin{code}
128 assignRegs, assignAllRegs
129         :: [MagicId]    -- Unavailable registers
130         -> [PrimRep]    -- Arg or result kinds to assign
131         -> ([MagicId],  -- Register assignment in same order
132                                 -- for *initial segment of* input list
133             [PrimRep])-- leftover kinds
134
135 assignRegs regs_in_use kinds
136  = assign_reg kinds [] (mkRegTbl regs_in_use)
137
138 assignAllRegs regs_in_use kinds
139  = assign_reg kinds [] (mkRegTbl_allRegs regs_in_use)
140
141 assign_reg 
142         :: [PrimRep]              -- arg kinds being scrutinized
143         -> [MagicId]              -- accum. regs assigned so far (reversed)
144         -> AvailRegs              -- regs still avail: Vanilla, Float, Double, longs
145         -> ([MagicId], [PrimRep])
146
147 assign_reg (VoidRep:ks) acc supply
148         = assign_reg ks (VoidReg:acc) supply 
149         -- one VoidReg is enough for everybody!
150
151 assign_reg (FloatRep:ks) acc (vanilla_rs, IBOX(f):float_rs, double_rs, long_rs)
152         = assign_reg ks (FloatReg f:acc) (vanilla_rs, float_rs, double_rs, long_rs)
153
154 assign_reg (DoubleRep:ks) acc (vanilla_rs, float_rs, IBOX(d):double_rs, long_rs)
155         = assign_reg ks (DoubleReg d:acc) (vanilla_rs, float_rs, double_rs, long_rs)
156
157 assign_reg (Word64Rep:ks) acc (vanilla_rs, float_rs, double_rs, IBOX(u):long_rs)
158         = assign_reg ks (LongReg Word64Rep u:acc) (vanilla_rs, float_rs, double_rs, long_rs)
159
160 assign_reg (Int64Rep:ks) acc (vanilla_rs, float_rs, double_rs, IBOX(l):long_rs)
161         = assign_reg ks (LongReg Int64Rep l:acc) (vanilla_rs, float_rs, double_rs, long_rs)
162
163 assign_reg (k:ks) acc (IBOX(v):vanilla_rs, float_rs, double_rs, long_rs)
164         | not (isFloatingRep k || is64BitRep k)
165         = assign_reg ks (VanillaReg k v:acc) (vanilla_rs, float_rs, double_rs, long_rs)
166
167 -- The catch-all.  It can happen because either
168 --      (a) we've assigned all the regs so leftover_ks is []
169 --  (b) we couldn't find a spare register in the appropriate supply
170 --  or, I suppose,
171 --  (c) we came across a Kind we couldn't handle (this one shouldn't happen)
172 assign_reg leftover_ks acc _ = (reverse acc, leftover_ks)
173
174 \end{code}
175
176 Register supplies.  Vanilla registers can contain pointers, Ints, Chars.
177 Floats and doubles have separate register supplies.
178
179 We take these register supplies from the *real* registers, i.e. those
180 that are guaranteed to map to machine registers.
181
182 \begin{code}
183 vanillaRegNos, floatRegNos, doubleRegNos, longRegNos :: [Int]
184 vanillaRegNos    = regList opt_UseVanillaRegs
185 floatRegNos      = regList opt_UseFloatRegs
186 doubleRegNos     = regList opt_UseDoubleRegs
187 longRegNos       = regList opt_UseLongRegs
188
189 allVanillaRegNos, allFloatRegNos, allDoubleRegNos, allLongRegNos :: [Int]
190 allVanillaRegNos = regList mAX_Vanilla_REG
191 allFloatRegNos   = regList mAX_Float_REG
192 allDoubleRegNos  = regList mAX_Double_REG
193 allLongRegNos    = regList mAX_Long_REG
194
195 regList 0 = []
196 regList n = [1 .. n]
197
198 type AvailRegs = ( [Int]   -- available vanilla regs.
199                  , [Int]   -- floats
200                  , [Int]   -- doubles
201                  , [Int]   -- longs (int64 and word64)
202                  )
203
204 mkRegTbl :: [MagicId] -> AvailRegs
205 mkRegTbl regs_in_use
206   = mkRegTbl' regs_in_use vanillaRegNos floatRegNos doubleRegNos longRegNos
207
208 mkRegTbl_allRegs :: [MagicId] -> AvailRegs
209 mkRegTbl_allRegs regs_in_use
210   = mkRegTbl' regs_in_use allVanillaRegNos allFloatRegNos allDoubleRegNos allLongRegNos
211
212 mkRegTbl' regs_in_use vanillas floats doubles longs
213   = (ok_vanilla, ok_float, ok_double, ok_long)
214   where
215     ok_vanilla = catMaybes (map (select (VanillaReg VoidRep))  vanillas)
216     ok_float   = catMaybes (map (select FloatReg)              floats)
217     ok_double  = catMaybes (map (select DoubleReg)             doubles)
218     ok_long    = catMaybes (map (select (LongReg Int64Rep))    longs)   
219                                     -- rep isn't looked at, hence we can use any old rep.
220
221     select :: (FAST_INT -> MagicId) -> Int{-cand-} -> Maybe Int
222         -- one we've unboxed the Int, we make a MagicId
223         -- and see if it is already in use; if not, return its number.
224
225     select mk_reg_fun cand@IBOX(i)
226       = let
227             reg = mk_reg_fun i
228         in
229         if reg `not_elem` regs_in_use
230         then Just cand
231         else Nothing
232       where
233         not_elem = isn'tIn "mkRegTbl"
234 \end{code}