2183d89b77dd5fe796869f66b4b67f8c2367ad52
[ghc-hetmet.git] / ghc / compiler / codeGen / CgInfoTbls.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Building info tables.
4 --
5 -- (c) The University of Glasgow 2004
6 --
7 -----------------------------------------------------------------------------
8
9 module CgInfoTbls (
10         emitClosureCodeAndInfoTable,
11         emitInfoTableAndCode,
12         dataConTagZ,
13         getSRTInfo,
14         emitDirectReturnTarget, emitAlgReturnTarget,
15         emitDirectReturnInstr, emitVectoredReturnInstr,
16         mkRetInfoTable,
17         mkStdInfoTable,
18         stdInfoTableSizeB,
19         mkFunGenInfoExtraBits,
20         entryCode, closureInfoPtr,
21         getConstrTag,
22         infoTable, infoTableClosureType,
23         infoTablePtrs, infoTableNonPtrs,
24         funInfoTable,
25         retVec
26   ) where
27
28
29 #include "HsVersions.h"
30
31 import ClosureInfo      ( ClosureInfo, closureTypeDescr, closureName,
32                           infoTableLabelFromCI, Liveness,
33                           closureValDescr, closureSRT, closureSMRep,
34                           closurePtrsSize, closureNonHdrSize, closureFunInfo,
35                           C_SRT(..), needsSRT, isConstrClosure_maybe,
36                           ArgDescr(..) )
37 import SMRep            ( StgHalfWord, hALF_WORD_SIZE_IN_BITS, hALF_WORD_SIZE,
38                           WordOff, ByteOff,
39                           smRepClosureTypeInt, tablesNextToCode,
40                           rET_BIG, rET_SMALL, rET_VEC_BIG, rET_VEC_SMALL )
41 import CgBindery        ( getLiveStackSlots )
42 import CgCallConv       ( isBigLiveness, mkLivenessCLit, buildContLiveness,
43                           argDescrType, getSequelAmode,
44                           CtrlReturnConvention(..) )
45 import CgUtils          ( mkStringCLit, packHalfWordsCLit, mkWordCLit, 
46                           cmmOffsetB, cmmOffsetExprW, cmmLabelOffW, cmmOffsetW,
47                           emitDataLits, emitRODataLits, emitSwitch, cmmNegate,
48                           newTemp )
49 import CgMonad
50
51 import CmmUtils         ( mkIntCLit, zeroCLit )
52 import Cmm              ( CmmStmt(..), CmmExpr(..), CmmLit(..), LocalReg,
53                           CmmBasicBlock, nodeReg )
54 import MachOp           ( MachOp(..), wordRep, halfWordRep )
55 import CLabel
56 import StgSyn           ( SRT(..) )
57 import Name             ( Name )
58 import DataCon          ( DataCon, dataConTag, fIRST_TAG )
59 import Unique           ( Uniquable(..) )
60 import CmdLineOpts      ( opt_SccProfilingOn, DynFlags(..), HscTarget(..) )
61 import ListSetOps       ( assocDefault )
62 import Maybes           ( isJust )
63 import Constants        ( wORD_SIZE, sIZEOF_StgFunInfoExtraRev )
64 import Outputable
65
66
67 -------------------------------------------------------------------------
68 --
69 --      Generating the info table and code for a closure
70 --
71 -------------------------------------------------------------------------
72
73 -- Here we make a concrete info table, represented as a list of CmmAddr
74 -- (it can't be simply a list of Word, because the SRT field is
75 -- represented by a label+offset expression).
76
77 -- With tablesNextToCode, the layout is
78 --      <reversed variable part>
79 --      <normal forward StgInfoTable, but without 
80 --              an entry point at the front>
81 --      <code>
82 --
83 -- Without tablesNextToCode, the layout of an info table is
84 --      <entry label>
85 --      <normal forward rest of StgInfoTable>
86 --      <forward variable part>
87 --
88 --      See includes/InfoTables.h
89
90 emitClosureCodeAndInfoTable :: ClosureInfo -> [LocalReg] -> CgStmts -> Code
91 emitClosureCodeAndInfoTable cl_info args body
92  = do   { ty_descr_lit <- 
93                 if opt_SccProfilingOn 
94                    then mkStringCLit (closureTypeDescr cl_info)
95                    else return (mkIntCLit 0)
96         ; cl_descr_lit <- 
97                 if opt_SccProfilingOn 
98                    then mkStringCLit cl_descr_string
99                    else return (mkIntCLit 0)
100         ; let std_info = mkStdInfoTable ty_descr_lit cl_descr_lit 
101                                         cl_type srt_len layout_lit
102
103         ; blks <- cgStmtsToBlocks body
104         ; emitInfoTableAndCode info_lbl std_info extra_bits args blks }
105   where
106     info_lbl  = infoTableLabelFromCI cl_info
107
108     cl_descr_string = closureValDescr cl_info
109     cl_type = smRepClosureTypeInt (closureSMRep cl_info)
110
111     srt = closureSRT cl_info         
112     needs_srt = needsSRT srt
113
114     mb_con = isConstrClosure_maybe  cl_info
115     is_con = isJust mb_con
116
117     (srt_label,srt_len)
118         = case mb_con of
119             Just con -> -- Constructors don't have an SRT
120                         -- We keep the *zero-indexed* tag in the srt_len
121                         -- field of the info table. 
122                         (mkIntCLit 0, fromIntegral (dataConTagZ con)) 
123
124             Nothing  -> -- Not a constructor
125                         srtLabelAndLength srt info_lbl
126
127     ptrs       = closurePtrsSize cl_info
128     nptrs      = size - ptrs
129     size       = closureNonHdrSize cl_info
130     layout_lit = packHalfWordsCLit ptrs nptrs
131
132     extra_bits
133         | is_fun    = fun_extra_bits
134         | is_con    = []
135         | needs_srt = [srt_label]
136         | otherwise = []
137
138     maybe_fun_stuff = closureFunInfo cl_info
139     is_fun = isJust maybe_fun_stuff
140     (Just (arity, arg_descr)) = maybe_fun_stuff
141
142     fun_extra_bits
143         | ArgGen liveness <- arg_descr
144         = [ fun_amode,
145             srt_label,
146             makeRelativeRefTo info_lbl $ mkLivenessCLit liveness, 
147             slow_entry ]
148         | needs_srt = [fun_amode, srt_label]
149         | otherwise = [fun_amode]
150
151     slow_entry = makeRelativeRefTo info_lbl (CmmLabel slow_entry_label)
152     slow_entry_label = mkSlowEntryLabel (closureName cl_info)
153
154     fun_amode = packHalfWordsCLit fun_type arity
155     fun_type  = argDescrType arg_descr
156
157 -- We keep the *zero-indexed* tag in the srt_len field of the info
158 -- table of a data constructor.
159 dataConTagZ :: DataCon -> ConTagZ
160 dataConTagZ con = dataConTag con - fIRST_TAG
161
162 -- A low-level way to generate the variable part of a fun-style info table.
163 -- (must match fun_extra_bits above).  Used by the C-- parser.
164 mkFunGenInfoExtraBits :: Int -> Int -> CmmLit -> CmmLit -> CmmLit -> [CmmLit]
165 mkFunGenInfoExtraBits fun_type arity srt_label liveness slow_entry
166   = [ packHalfWordsCLit fun_type arity,
167       srt_label,
168       liveness,
169       slow_entry ]
170
171 -------------------------------------------------------------------------
172 --
173 --      Generating the info table and code for a return point
174 --
175 -------------------------------------------------------------------------
176
177 --      Here's the layout of a return-point info table
178 --
179 -- Tables next to code:
180 --
181 --                      <reversed vector table>
182 --                      <srt slot>
183 --                      <standard info table>
184 --      ret-addr -->    <entry code (if any)>
185 --
186 -- Not tables-next-to-code:
187 --
188 --      ret-addr -->    <ptr to entry code>
189 --                      <standard info table>
190 --                      <srt slot>
191 --                      <forward vector table>
192 --
193 -- * The vector table is only present for vectored returns
194 --
195 -- * The SRT slot is only there if either
196 --      (a) there is SRT info to record, OR
197 --      (b) if the return is vectored
198 --   The latter (b) is necessary so that the vector is in a
199 --   predictable place
200
201 vectorSlot :: CmmExpr -> CmmExpr -> CmmExpr
202 -- Get the vector slot from the info pointer
203 vectorSlot info_amode zero_indexed_tag
204   | tablesNextToCode 
205   = cmmOffsetExprW (cmmOffsetW info_amode (- (stdInfoTableSizeW + 2)))
206                    (cmmNegate zero_indexed_tag)
207         -- The "2" is one for the SRT slot, and one more 
208         -- to get to the first word of the vector
209
210   | otherwise 
211   = cmmOffsetExprW (cmmOffsetW info_amode (stdInfoTableSizeW + 2))
212                    zero_indexed_tag
213         -- The "2" is one for the entry-code slot and one for the SRT slot
214
215 retVec :: CmmExpr -> CmmExpr -> CmmExpr
216 -- Get a return vector from the info pointer
217 retVec info_amode zero_indexed_tag
218   = let slot = vectorSlot info_amode zero_indexed_tag
219         tableEntry = CmmLoad slot wordRep
220     in if tablesNextToCode
221            then CmmMachOp (MO_Add wordRep) [tableEntry, info_amode]
222            else tableEntry
223            
224 emitReturnTarget
225    :: Name
226    -> CgStmts                   -- The direct-return code (if any)
227                                 --      (empty for vectored returns)
228    -> [CmmLit]                  -- Vector of return points 
229                                 --      (empty for non-vectored returns)
230    -> SRT
231    -> FCode CLabel
232 emitReturnTarget name stmts vector srt
233   = do  { live_slots <- getLiveStackSlots
234         ; liveness   <- buildContLiveness name live_slots
235         ; srt_info   <- getSRTInfo name srt
236
237         ; let
238               cl_type = case (null vector, isBigLiveness liveness) of
239                          (True,  True)  -> rET_BIG
240                          (True,  False) -> rET_SMALL
241                          (False, True)  -> rET_VEC_BIG
242                          (False, False) -> rET_VEC_SMALL
243  
244               (std_info, extra_bits) = 
245                    mkRetInfoTable info_lbl liveness srt_info cl_type vector
246
247         ; blks <- cgStmtsToBlocks stmts
248         ; emitInfoTableAndCode info_lbl std_info extra_bits args blks
249         ; return info_lbl }
250   where
251     args = trace "emitReturnTarget: missing args" []
252     uniq      = getUnique name
253     info_lbl  = mkReturnInfoLabel uniq
254
255
256 mkRetInfoTable
257   :: CLabel             -- info label
258   -> Liveness           -- liveness
259   -> C_SRT              -- SRT Info
260   -> Int                -- type (eg. rET_SMALL)
261   -> [CmmLit]           -- vector
262   -> ([CmmLit],[CmmLit])
263 mkRetInfoTable info_lbl liveness srt_info cl_type vector
264   =  (std_info, extra_bits)
265   where
266         (srt_label, srt_len) = srtLabelAndLength srt_info info_lbl
267  
268         srt_slot | need_srt  = [srt_label]
269                  | otherwise = []
270
271         need_srt = needsSRT srt_info || not (null vector)
272                 -- If there's a vector table then we must allocate
273                 -- an SRT slot, so that the vector table is at a 
274                 -- known offset from the info pointer
275  
276         liveness_lit = makeRelativeRefTo info_lbl $ mkLivenessCLit liveness
277         std_info = mkStdInfoTable zeroCLit zeroCLit cl_type srt_len liveness_lit
278         extra_bits = srt_slot ++ map (makeRelativeRefTo info_lbl) vector
279
280
281 emitDirectReturnTarget
282    :: Name
283    -> CgStmts           -- The direct-return code
284    -> SRT
285    -> FCode CLabel
286 emitDirectReturnTarget name code srt
287   = emitReturnTarget name code [] srt
288
289 emitAlgReturnTarget
290         :: Name                         -- Just for its unique
291         -> [(ConTagZ, CgStmts)]         -- Tagged branches
292         -> Maybe CgStmts                -- Default branch (if any)
293         -> SRT                          -- Continuation's SRT
294         -> CtrlReturnConvention
295         -> FCode (CLabel, SemiTaggingStuff)
296
297 emitAlgReturnTarget name branches mb_deflt srt ret_conv
298   = case ret_conv of
299       UnvectoredReturn fam_sz -> do     
300         { blks <- getCgStmts $
301                     emitSwitch tag_expr branches mb_deflt 0 (fam_sz - 1)
302                 -- NB: tag_expr is zero-based
303         ; lbl <- emitDirectReturnTarget name blks srt 
304         ; return (lbl, Nothing) }
305                 -- Nothing: the internal branches in the switch don't have
306                 -- global labels, so we can't use them at the 'call site'
307
308       VectoredReturn fam_sz -> do
309         { let tagged_lbls = zip (map fst branches) $
310                             map (CmmLabel . mkAltLabel uniq . fst) branches
311               deflt_lbl | isJust mb_deflt = CmmLabel $ mkDefaultLabel uniq
312                         | otherwise       = mkIntCLit 0
313         ; let vector = [ assocDefault deflt_lbl tagged_lbls i 
314                        | i <- [0..fam_sz-1]]
315         ; lbl <- emitReturnTarget name noCgStmts vector srt 
316         ; mapFCs emit_alt branches
317         ; emit_deflt mb_deflt
318         ; return (lbl, Just (tagged_lbls, deflt_lbl)) }
319   where
320     uniq = getUnique name 
321     tag_expr = getConstrTag (CmmReg nodeReg)
322
323     emit_alt :: (Int, CgStmts) -> FCode (Int, CmmLit)
324         -- Emit the code for the alternative as a top-level
325         -- code block returning a label for it
326     emit_alt (tag, stmts) = do   { let lbl = mkAltLabel uniq tag
327                                  ; blks <- cgStmtsToBlocks stmts
328                                  ; emitProc [] lbl [] blks
329                                  ; return (tag, CmmLabel lbl) }
330
331     emit_deflt (Just stmts) = do { let lbl = mkDefaultLabel uniq
332                                  ; blks <- cgStmtsToBlocks stmts
333                                  ; emitProc [] lbl [] blks
334                                  ; return (CmmLabel lbl) }
335     emit_deflt Nothing = return (mkIntCLit 0)
336                 -- Nothing case: the simplifier might have eliminated a case
337                 --               so we may have e.g. case xs of 
338                 --                                       [] -> e
339                 -- In that situation the default should never be taken, 
340                 -- so we just use a NULL pointer
341
342 --------------------------------
343 emitDirectReturnInstr :: Code
344 emitDirectReturnInstr 
345   = do  { info_amode <- getSequelAmode
346         ; stmtC (CmmJump (entryCode info_amode) []) }
347
348 emitVectoredReturnInstr :: CmmExpr      -- *Zero-indexed* constructor tag
349                         -> Code
350 emitVectoredReturnInstr zero_indexed_tag
351   = do  { info_amode <- getSequelAmode
352                 -- HACK! assign info_amode to a temp, because retVec
353                 -- uses it twice and the NCG doesn't have any CSE yet.
354                 -- Only do this for the NCG, because gcc is too stupid
355                 -- to optimise away the extra tmp (grrr).
356         ; dflags <- getDynFlags
357         ; x <- if hscTarget dflags == HscAsm
358                    then do z <- newTemp wordRep
359                            stmtC (CmmAssign z info_amode)
360                            return (CmmReg z)
361                    else
362                         return info_amode
363         ; let target = retVec x zero_indexed_tag
364         ; stmtC (CmmJump target []) }
365
366
367 -------------------------------------------------------------------------
368 --
369 --      Generating a standard info table
370 --
371 -------------------------------------------------------------------------
372
373 -- The standard bits of an info table.  This part of the info table
374 -- corresponds to the StgInfoTable type defined in InfoTables.h.
375 --
376 -- Its shape varies with ticky/profiling/tables next to code etc
377 -- so we can't use constant offsets from Constants
378
379 mkStdInfoTable
380    :: CmmLit            -- closure type descr (profiling)
381    -> CmmLit            -- closure descr (profiling)
382    -> Int               -- closure type
383    -> StgHalfWord       -- SRT length
384    -> CmmLit            -- layout field
385    -> [CmmLit]
386
387 mkStdInfoTable type_descr closure_descr cl_type srt_len layout_lit
388  =      -- Parallel revertible-black hole field
389     prof_info
390         -- Ticky info (none at present)
391         -- Debug info (none at present)
392  ++ [layout_lit, type_lit]
393
394  where  
395     prof_info 
396         | opt_SccProfilingOn = [closure_descr, type_descr]
397         | otherwise          = []
398
399     type_lit = packHalfWordsCLit cl_type srt_len
400         
401 stdInfoTableSizeW :: WordOff
402 -- The size of a standard info table varies with profiling/ticky etc,
403 -- so we can't get it from Constants
404 -- It must vary in sync with mkStdInfoTable
405 stdInfoTableSizeW
406   = size_fixed + size_prof
407   where
408     size_fixed = 2      -- layout, type
409     size_prof | opt_SccProfilingOn = 2
410               | otherwise          = 0
411
412 stdInfoTableSizeB = stdInfoTableSizeW * wORD_SIZE :: ByteOff
413
414 stdSrtBitmapOffset :: ByteOff
415 -- Byte offset of the SRT bitmap half-word which is 
416 -- in the *higher-addressed* part of the type_lit
417 stdSrtBitmapOffset = stdInfoTableSizeB - hALF_WORD_SIZE
418
419 stdClosureTypeOffset :: ByteOff
420 -- Byte offset of the closure type half-word 
421 stdClosureTypeOffset = stdInfoTableSizeB - wORD_SIZE
422
423 stdPtrsOffset, stdNonPtrsOffset :: ByteOff
424 stdPtrsOffset    = stdInfoTableSizeB - 2*wORD_SIZE
425 stdNonPtrsOffset = stdInfoTableSizeB - 2*wORD_SIZE + hALF_WORD_SIZE
426
427 -------------------------------------------------------------------------
428 --
429 --      Accessing fields of an info table
430 --
431 -------------------------------------------------------------------------
432
433 closureInfoPtr :: CmmExpr -> CmmExpr
434 -- Takes a closure pointer and returns the info table pointer
435 closureInfoPtr e = CmmLoad e wordRep
436
437 entryCode :: CmmExpr -> CmmExpr
438 -- Takes an info pointer (the first word of a closure)
439 -- and returns its entry code
440 entryCode e | tablesNextToCode = e
441             | otherwise        = CmmLoad e wordRep
442
443 getConstrTag :: CmmExpr -> CmmExpr
444 -- Takes a closure pointer, and return the *zero-indexed*
445 -- constructor tag obtained from the info table
446 -- This lives in the SRT field of the info table
447 -- (constructors don't need SRTs).
448 getConstrTag closure_ptr 
449   = CmmMachOp (MO_U_Conv halfWordRep wordRep) [infoTableConstrTag info_table]
450   where
451     info_table = infoTable (closureInfoPtr closure_ptr)
452
453 infoTable :: CmmExpr -> CmmExpr
454 -- Takes an info pointer (the first word of a closure)
455 -- and returns a pointer to the first word of the standard-form
456 -- info table, excluding the entry-code word (if present)
457 infoTable info_ptr
458   | tablesNextToCode = cmmOffsetB info_ptr (- stdInfoTableSizeB)
459   | otherwise        = cmmOffsetW info_ptr 1    -- Past the entry code pointer
460
461 infoTableConstrTag :: CmmExpr -> CmmExpr
462 -- Takes an info table pointer (from infoTable) and returns the constr tag
463 -- field of the info table (same as the srt_bitmap field)
464 infoTableConstrTag = infoTableSrtBitmap
465
466 infoTableSrtBitmap :: CmmExpr -> CmmExpr
467 -- Takes an info table pointer (from infoTable) and returns the srt_bitmap
468 -- field of the info table
469 infoTableSrtBitmap info_tbl
470   = CmmLoad (cmmOffsetB info_tbl stdSrtBitmapOffset) halfWordRep
471
472 infoTableClosureType :: CmmExpr -> CmmExpr
473 -- Takes an info table pointer (from infoTable) and returns the closure type
474 -- field of the info table.
475 infoTableClosureType info_tbl 
476   = CmmLoad (cmmOffsetB info_tbl stdClosureTypeOffset) halfWordRep
477
478 infoTablePtrs :: CmmExpr -> CmmExpr
479 infoTablePtrs info_tbl 
480   = CmmLoad (cmmOffsetB info_tbl stdPtrsOffset) halfWordRep
481
482 infoTableNonPtrs :: CmmExpr -> CmmExpr
483 infoTableNonPtrs info_tbl 
484   = CmmLoad (cmmOffsetB info_tbl stdNonPtrsOffset) halfWordRep
485
486 funInfoTable :: CmmExpr -> CmmExpr
487 -- Takes the info pointer of a function,
488 -- and returns a pointer to the first word of the StgFunInfoExtra struct
489 -- in the info table.
490 funInfoTable info_ptr
491   | tablesNextToCode
492   = cmmOffsetB info_ptr (- stdInfoTableSizeB - sIZEOF_StgFunInfoExtraRev)
493   | otherwise
494   = cmmOffsetW info_ptr (1 + stdInfoTableSizeW)
495                                 -- Past the entry code pointer
496
497 -------------------------------------------------------------------------
498 --
499 --      Emit the code for a closure (or return address)
500 --      and its associated info table
501 --
502 -------------------------------------------------------------------------
503
504 -- The complication here concerns whether or not we can
505 -- put the info table next to the code
506
507 emitInfoTableAndCode 
508         :: CLabel               -- Label of info table
509         -> [CmmLit]             -- ...its invariant part
510         -> [CmmLit]             -- ...and its variant part
511         -> [LocalReg]           -- ...args
512         -> [CmmBasicBlock]      -- ...and body
513         -> Code
514
515 emitInfoTableAndCode info_lbl std_info extra_bits args blocks
516   | tablesNextToCode    -- Reverse the extra_bits; and emit the top-level proc
517   = emitProc (reverse extra_bits ++ std_info) 
518              entry_lbl args blocks
519         -- NB: the info_lbl is discarded
520
521   | null blocks -- No actual code; only the info table is significant
522   =             -- Use a zero place-holder in place of the 
523                 -- entry-label in the info table
524     emitRODataLits info_lbl (zeroCLit : std_info ++ extra_bits)
525
526   | otherwise   -- Separately emit info table (with the function entry 
527   =             -- point as first entry) and the entry code 
528     do  { emitDataLits info_lbl (CmmLabel entry_lbl : std_info ++ extra_bits)
529         ; emitProc [] entry_lbl args blocks }
530
531   where
532         entry_lbl = infoLblToEntryLbl info_lbl
533
534 -------------------------------------------------------------------------
535 --
536 --      Static reference tables
537 --
538 -------------------------------------------------------------------------
539
540 -- There is just one SRT for each top level binding; all the nested
541 -- bindings use sub-sections of this SRT.  The label is passed down to
542 -- the nested bindings via the monad.
543
544 getSRTInfo :: Name -> SRT -> FCode C_SRT
545 getSRTInfo id NoSRT = return NoC_SRT
546 getSRTInfo id (SRT off len bmp)
547   | len > hALF_WORD_SIZE_IN_BITS || bmp == [fromIntegral srt_escape]
548   = do  { srt_lbl <- getSRTLabel
549         ; let srt_desc_lbl = mkSRTDescLabel id
550         ; emitRODataLits srt_desc_lbl
551                    ( cmmLabelOffW srt_lbl off
552                    : mkWordCLit (fromIntegral len)
553                    : map mkWordCLit bmp)
554         ; return (C_SRT srt_desc_lbl 0 srt_escape) }
555
556   | otherwise 
557   = do  { srt_lbl <- getSRTLabel
558         ; return (C_SRT srt_lbl off (fromIntegral (head bmp))) }
559                 -- The fromIntegral converts to StgHalfWord
560
561 srt_escape = (-1) :: StgHalfWord
562
563 srtLabelAndLength :: C_SRT -> CLabel -> (CmmLit, StgHalfWord)
564 srtLabelAndLength NoC_SRT _             
565   = (zeroCLit, 0)
566 srtLabelAndLength (C_SRT lbl off bitmap) info_lbl
567   = (makeRelativeRefTo info_lbl $ cmmLabelOffW lbl off, bitmap)
568
569 -------------------------------------------------------------------------
570 --
571 --      Position independent code
572 --
573 -------------------------------------------------------------------------
574 -- In order to support position independent code, we mustn't put absolute
575 -- references into read-only space. Info tables in the tablesNextToCode
576 -- case must be in .text, which is read-only, so we doctor the CmmLits
577 -- to use relative offsets instead.
578
579 -- Note that this is done even when the -fPIC flag is not specified,
580 -- as we want to keep binary compatibility between PIC and non-PIC.
581
582 makeRelativeRefTo :: CLabel -> CmmLit -> CmmLit
583         
584 makeRelativeRefTo info_lbl (CmmLabel lbl)
585   | tablesNextToCode
586   = CmmLabelDiffOff lbl info_lbl 0
587 makeRelativeRefTo info_lbl (CmmLabelOff lbl off)
588   | tablesNextToCode
589   = CmmLabelDiffOff lbl info_lbl off
590 makeRelativeRefTo _ lit = lit