Merging in the new codegen branch
[ghc-hetmet.git] / compiler / cmm / CmmInfo.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/Commentary/CodingStyle#Warnings
6 -- for details
7
8 module CmmInfo (
9   cmmToRawCmm,
10   mkInfoTable
11 ) where
12
13 #include "HsVersions.h"
14
15 import Cmm
16 import CmmUtils
17
18 import CLabel
19
20 import Bitmap
21 import ClosureInfo
22 import CgInfoTbls
23 import CgCallConv
24 import CgUtils
25 import SMRep
26
27 import Constants
28 import Outputable
29 import StaticFlags
30 import Unique
31 import UniqSupply
32 import Panic
33
34 import Data.Bits
35
36 cmmToRawCmm :: [Cmm] -> IO [RawCmm]
37 cmmToRawCmm cmm = do
38   info_tbl_uniques <- mkSplitUniqSupply 'i'
39   return $ zipWith raw_cmm (listSplitUniqSupply info_tbl_uniques) cmm
40     where
41       raw_cmm uniq_supply (Cmm procs) =
42           Cmm $ concat $ zipWith mkInfoTable (uniqsFromSupply uniq_supply) procs
43
44 -- Make a concrete info table, represented as a list of CmmStatic
45 -- (it can't be simply a list of Word, because the SRT field is
46 -- represented by a label+offset expression).
47 --
48 -- With tablesNextToCode, the layout is
49 --      <reversed variable part>
50 --      <normal forward StgInfoTable, but without 
51 --              an entry point at the front>
52 --      <code>
53 --
54 -- Without tablesNextToCode, the layout of an info table is
55 --      <entry label>
56 --      <normal forward rest of StgInfoTable>
57 --      <forward variable part>
58 --
59 --      See includes/InfoTables.h
60 --
61 -- For return-points these are as follows
62 --
63 -- Tables next to code:
64 --
65 --                      <srt slot>
66 --                      <standard info table>
67 --      ret-addr -->    <entry code (if any)>
68 --
69 -- Not tables-next-to-code:
70 --
71 --      ret-addr -->    <ptr to entry code>
72 --                      <standard info table>
73 --                      <srt slot>
74 --
75 --  * The SRT slot is only there if there is SRT info to record
76
77 mkInfoTable :: Unique -> CmmTop -> [RawCmmTop]
78 mkInfoTable uniq (CmmData sec dat) = [CmmData sec dat]
79 mkInfoTable uniq (CmmProc (CmmInfo _ _ info) entry_label arguments blocks) =
80     case info of
81       -- Code without an info table.  Easy.
82       CmmNonInfoTable -> [CmmProc [] entry_label arguments blocks]
83
84       CmmInfoTable (ProfilingInfo ty_prof cl_prof) type_tag type_info ->
85           let info_label = entryLblToInfoLbl entry_label
86               ty_prof'   = makeRelativeRefTo info_label ty_prof
87               cl_prof'   = makeRelativeRefTo info_label cl_prof
88           in case type_info of
89           -- A function entry point.
90           FunInfo (ptrs, nptrs) srt fun_arity pap_bitmap slow_entry ->
91               mkInfoTableAndCode info_label std_info fun_extra_bits entry_label
92                                  arguments blocks
93             where
94               fun_type = argDescrType pap_bitmap
95               fun_extra_bits =
96                  [packHalfWordsCLit fun_type fun_arity] ++
97                  case pap_bitmap of
98                  ArgGen liveness ->
99                      (if null srt_label then [mkIntCLit 0] else srt_label) ++
100                      [makeRelativeRefTo info_label $ mkLivenessCLit liveness,
101                       makeRelativeRefTo info_label slow_entry]
102                  _ -> srt_label
103               std_info = mkStdInfoTable ty_prof' cl_prof' type_tag srt_bitmap
104                                         layout
105               (srt_label, srt_bitmap) = mkSRTLit info_label srt
106               layout = packHalfWordsCLit ptrs nptrs
107
108           -- A constructor.
109           ConstrInfo (ptrs, nptrs) con_tag descr ->
110               mkInfoTableAndCode info_label std_info [con_name] entry_label
111                                  arguments blocks
112               where
113                 std_info = mkStdInfoTable ty_prof' cl_prof' type_tag con_tag layout
114                 con_name = makeRelativeRefTo info_label descr
115                 layout = packHalfWordsCLit ptrs nptrs
116           -- A thunk.
117           ThunkInfo (ptrs, nptrs) srt ->
118               mkInfoTableAndCode info_label std_info srt_label entry_label
119                                  arguments blocks
120               where
121                 std_info = mkStdInfoTable ty_prof' cl_prof' type_tag srt_bitmap layout
122                 (srt_label, srt_bitmap) = mkSRTLit info_label srt
123                 layout = packHalfWordsCLit ptrs nptrs
124
125           -- A selector thunk.
126           ThunkSelectorInfo offset srt ->
127               mkInfoTableAndCode info_label std_info [{- no SRT -}] entry_label
128                                  arguments blocks
129               where
130                 std_info = mkStdInfoTable ty_prof' cl_prof' type_tag 0 (mkWordCLit offset)
131
132           -- A continuation/return-point.
133           ContInfo stack_layout srt ->
134               liveness_data ++
135               mkInfoTableAndCode info_label std_info srt_label entry_label
136                                  arguments blocks
137               where
138                 std_info = mkStdInfoTable ty_prof' cl_prof' maybe_big_type_tag srt_bitmap
139                                           (makeRelativeRefTo info_label liveness_lit)
140                 (liveness_lit, liveness_data, liveness_tag) =
141                     mkLiveness uniq stack_layout
142                 maybe_big_type_tag = if type_tag == rET_SMALL
143                                      then liveness_tag
144                                      else type_tag
145                 (srt_label, srt_bitmap) = mkSRTLit info_label srt
146
147 -- Handle the differences between tables-next-to-code
148 -- and not tables-next-to-code
149 mkInfoTableAndCode :: CLabel
150                    -> [CmmLit]
151                    -> [CmmLit]
152                    -> CLabel
153                    -> CmmFormals
154                    -> ListGraph CmmStmt
155                    -> [RawCmmTop]
156 mkInfoTableAndCode info_lbl std_info extra_bits entry_lbl args blocks
157   | tablesNextToCode    -- Reverse the extra_bits; and emit the top-level proc
158   = [CmmProc (map CmmStaticLit (reverse extra_bits ++ std_info))
159              entry_lbl args blocks]
160
161   | ListGraph [] <- blocks -- No code; only the info table is significant
162   =             -- Use a zero place-holder in place of the 
163                 -- entry-label in the info table
164     [mkRODataLits info_lbl (zeroCLit : std_info ++ extra_bits)]
165
166   | otherwise   -- Separately emit info table (with the function entry 
167   =             -- point as first entry) and the entry code 
168     [CmmProc [] entry_lbl args blocks,
169      mkDataLits info_lbl (CmmLabel entry_lbl : std_info ++ extra_bits)]
170
171 mkSRTLit :: CLabel
172          -> C_SRT
173          -> ([CmmLit],    -- srt_label
174              StgHalfWord) -- srt_bitmap
175 mkSRTLit info_label NoC_SRT = ([], 0)
176 mkSRTLit info_label (C_SRT lbl off bitmap) =
177     ([makeRelativeRefTo info_label (cmmLabelOffW lbl off)], bitmap)
178
179 -------------------------------------------------------------------------
180 --
181 --              Build a liveness mask for the stack layout
182 --
183 -------------------------------------------------------------------------
184
185 -- There are four kinds of things on the stack:
186 --
187 --      - pointer variables (bound in the environment)
188 --      - non-pointer variables (bound in the environment)
189 --      - free slots (recorded in the stack free list)
190 --      - non-pointer data slots (recorded in the stack free list)
191 --
192 -- The first two are represented with a 'Just' of a 'LocalReg'.
193 -- The last two with one or more 'Nothing' constructors.
194 -- Each 'Nothing' represents one used word.
195 --
196 -- The head of the stack layout is the top of the stack and
197 -- the least-significant bit.
198
199 -- TODO: refactor to use utility functions
200 -- TODO: combine with CgCallConv.mkLiveness (see comment there)
201 mkLiveness :: Unique
202            -> [Maybe LocalReg]
203            -> (CmmLit, [RawCmmTop], ClosureTypeTag)
204               -- ^ Returns:
205               --   1. The bitmap (literal value or label)
206               --   2. Large bitmap CmmData if needed
207               --   3. rET_SMALL or rET_BIG
208 mkLiveness uniq live =
209   if length bits > mAX_SMALL_BITMAP_SIZE
210     -- does not fit in one word
211     then (CmmLabel big_liveness, [data_lits], rET_BIG)
212     -- fits in one word
213     else (mkWordCLit  small_liveness, [], rET_SMALL)
214   where
215     mkBits [] = []
216     mkBits (reg:regs) = take sizeW bits ++ mkBits regs where
217         sizeW = case reg of
218                   Nothing -> 1
219                   Just r -> (widthInBytes (typeWidth (localRegType r)) + wORD_SIZE - 1)
220                             `quot` wORD_SIZE
221                             -- number of words, rounded up
222         bits = repeat $ is_non_ptr reg -- True <=> Non Ptr
223
224     is_non_ptr Nothing    = True
225     is_non_ptr (Just reg) = not $ isGcPtrType (localRegType reg)
226
227     bits :: [Bool]
228     bits = mkBits live
229
230     bitmap :: Bitmap
231     bitmap = mkBitmap bits
232
233     small_bitmap = case bitmap of 
234                    []  -> 0
235                    [b] -> fromIntegral b
236                    _   -> panic "mkLiveness"
237     small_liveness =
238         fromIntegral (length bits) .|. (small_bitmap `shiftL` bITMAP_BITS_SHIFT)
239
240     big_liveness = mkBitmapLabel uniq
241     lits = mkWordCLit (fromIntegral (length bits)) : map mkWordCLit bitmap
242     data_lits = mkRODataLits big_liveness lits
243
244 -------------------------------------------------------------------------
245 --
246 --      Generating a standard info table
247 --
248 -------------------------------------------------------------------------
249
250 -- The standard bits of an info table.  This part of the info table
251 -- corresponds to the StgInfoTable type defined in InfoTables.h.
252 --
253 -- Its shape varies with ticky/profiling/tables next to code etc
254 -- so we can't use constant offsets from Constants
255
256 mkStdInfoTable
257    :: CmmLit            -- closure type descr (profiling)
258    -> CmmLit            -- closure descr (profiling)
259    -> StgHalfWord       -- closure type
260    -> StgHalfWord       -- SRT length
261    -> CmmLit            -- layout field
262    -> [CmmLit]
263
264 mkStdInfoTable type_descr closure_descr cl_type srt_len layout_lit
265  =      -- Parallel revertible-black hole field
266     prof_info
267         -- Ticky info (none at present)
268         -- Debug info (none at present)
269  ++ [layout_lit, type_lit]
270
271  where  
272     prof_info 
273         | opt_SccProfilingOn = [type_descr, closure_descr]
274         | otherwise          = []
275
276     type_lit = packHalfWordsCLit cl_type srt_len
277