730e4dee4d2f93da20b1599da4f896f75d2570cc
[ghc-hetmet.git] / compiler / ghci / ByteCodeItbls.lhs
1 %
2 % (c) The University of Glasgow 2000-2006
3 %
4 ByteCodeItbls: Generate infotables for interpreter-made bytecodes
5
6 \begin{code}
7 {-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
8
9 module ByteCodeItbls ( ItblEnv, ItblPtr(..), itblCode, mkITbls
10                      , StgInfoTable(..)
11                      ) where
12
13 #include "HsVersions.h"
14
15 import ByteCodeFFI      ( newExec )
16 import Name             ( Name, getName )
17 import NameEnv
18 import SMRep            ( typeCgRep )
19 import DataCon          ( DataCon, dataConRepArgTys, dataConIdentity )
20 import TyCon            ( TyCon, tyConFamilySize, isDataTyCon, tyConDataCons )
21 import Constants        ( mIN_PAYLOAD_SIZE, wORD_SIZE )
22 import CgHeapery        ( mkVirtHeapOffsets )
23 import FastString       ( FastString(..) )
24 import Util             ( lengthIs, listLengthCmp )
25 import Outputable
26
27 import Foreign
28 import Foreign.C
29 import Foreign.C.String
30 import Data.Bits        ( Bits(..), shiftR )
31
32 import GHC.Exts         ( Int(I#), addr2Int# )
33 import GHC.Ptr          ( Ptr(..) )
34 import GHC.Prim
35
36 import Debug.Trace
37 import Text.Printf
38 \end{code}
39
40 %************************************************************************
41 %*                                                                      *
42 \subsection{Manufacturing of info tables for DataCons}
43 %*                                                                      *
44 %************************************************************************
45
46 \begin{code}
47 newtype ItblPtr = ItblPtr (Ptr ()) deriving Show
48
49 itblCode :: ItblPtr -> Ptr ()
50 itblCode (ItblPtr ptr)
51    = (castPtr ptr)
52 #ifdef GHCI_TABLES_NEXT_TO_CODE
53                  `plusPtr` conInfoTableSizeB
54 #endif
55
56 -- XXX bogus
57 conInfoTableSizeB = 3 * wORD_SIZE
58
59 type ItblEnv = NameEnv (Name, ItblPtr)
60         -- We need the Name in the range so we know which
61         -- elements to filter out when unloading a module
62
63 mkItblEnv :: [(Name,ItblPtr)] -> ItblEnv
64 mkItblEnv pairs = mkNameEnv [(n, (n,p)) | (n,p) <- pairs]
65
66
67 -- Make info tables for the data decls in this module
68 mkITbls :: [TyCon] -> IO ItblEnv
69 mkITbls [] = return emptyNameEnv
70 mkITbls (tc:tcs) = do itbls  <- mkITbl tc
71                       itbls2 <- mkITbls tcs
72                       return (itbls `plusNameEnv` itbls2)
73
74 mkITbl :: TyCon -> IO ItblEnv
75 mkITbl tc
76    | not (isDataTyCon tc) 
77    = return emptyNameEnv
78    | dcs `lengthIs` n -- paranoia; this is an assertion.
79    = make_constr_itbls dcs
80      where
81         dcs = tyConDataCons tc
82         n   = tyConFamilySize tc
83
84 #include "../includes/ClosureTypes.h"
85 cONSTR :: Int   -- Defined in ClosureTypes.h
86 cONSTR = CONSTR 
87
88 -- Assumes constructors are numbered from zero, not one
89 make_constr_itbls :: [DataCon] -> IO ItblEnv
90 make_constr_itbls cons
91    = do is <- mapM mk_dirret_itbl (zip cons [0..])
92         return (mkItblEnv is)
93      where
94         mk_dirret_itbl (dcon, conNo)
95            = mk_itbl dcon conNo stg_interp_constr_entry
96
97         mk_itbl :: DataCon -> Int -> Ptr () -> IO (Name,ItblPtr)
98         mk_itbl dcon conNo entry_addr = do
99            let rep_args = [ (typeCgRep arg,arg) | arg <- dataConRepArgTys dcon ]
100                (tot_wds, ptr_wds, _) = mkVirtHeapOffsets False{-not a THUNK-} rep_args
101
102                ptrs  = ptr_wds
103                nptrs = tot_wds - ptr_wds
104                nptrs_really
105                   | ptrs + nptrs >= mIN_PAYLOAD_SIZE = nptrs
106                   | otherwise = mIN_PAYLOAD_SIZE - ptrs
107                code = mkJumpToAddr entry_addr
108                itbl  = StgInfoTable {
109 #ifndef GHCI_TABLES_NEXT_TO_CODE
110                            entry = entry_addr,
111 #endif
112                            ptrs  = fromIntegral ptrs, 
113                            nptrs = fromIntegral nptrs_really,
114                            tipe  = fromIntegral cONSTR,
115                            srtlen = fromIntegral conNo
116 #ifdef GHCI_TABLES_NEXT_TO_CODE
117                          , code  = code
118 #endif
119                         }
120            qNameCString <- newArray0 0 $ dataConIdentity dcon 
121            let conInfoTbl = StgConInfoTable {
122                                  conDesc = qNameCString,
123                                  infoTable = itbl
124                             }
125                -- Make a piece of code to jump to "entry_label".
126                -- This is the only arch-dependent bit.
127            addrCon <- newExec [conInfoTbl]
128                     --putStrLn ("SIZE of itbl is " ++ show (sizeOf itbl))
129                     --putStrLn ("# ptrs  of itbl is " ++ show ptrs)
130                     --putStrLn ("# nptrs of itbl is " ++ show nptrs_really)
131            return (getName dcon, ItblPtr (castFunPtrToPtr addrCon))
132
133
134 -- Make code which causes a jump to the given address.  This is the
135 -- only arch-dependent bit of the itbl story.  The returned list is
136 -- itblCodeLength elements (bytes) long.
137
138 -- For sparc_TARGET_ARCH, i386_TARGET_ARCH, etc.
139 #include "nativeGen/NCG.h"
140
141 itblCodeLength :: Int
142 itblCodeLength = length (mkJumpToAddr undefined)
143
144 mkJumpToAddr :: Ptr () -> [ItblCode]
145
146 ptrToInt (Ptr a#) = I# (addr2Int# a#)
147
148 #if sparc_TARGET_ARCH
149 -- After some consideration, we'll try this, where
150 -- 0x55555555 stands in for the address to jump to.
151 -- According to ghc/includes/MachRegs.h, %g3 is very
152 -- likely indeed to be baggable.
153 --
154 --   0000 07155555              sethi   %hi(0x55555555), %g3
155 --   0004 8610E155              or      %g3, %lo(0x55555555), %g3
156 --   0008 81C0C000              jmp     %g3
157 --   000c 01000000              nop
158
159 type ItblCode = Word32
160 mkJumpToAddr a
161    = let w32 = fromIntegral (ptrToInt a)
162
163          hi22, lo10 :: Word32 -> Word32
164          lo10 x = x .&. 0x3FF
165          hi22 x = (x `shiftR` 10) .&. 0x3FFFF
166
167      in  [ 0x07000000 .|. (hi22 w32),
168            0x8610E000 .|. (lo10 w32),
169            0x81C0C000,
170            0x01000000 ]
171
172 #elif powerpc_TARGET_ARCH
173 -- We'll use r12, for no particular reason.
174 -- 0xDEADBEEF stands for the adress:
175 -- 3D80DEAD lis r12,0xDEAD
176 -- 618CBEEF ori r12,r12,0xBEEF
177 -- 7D8903A6 mtctr r12
178 -- 4E800420 bctr
179
180 type ItblCode = Word32
181 mkJumpToAddr a =
182     let w32 = fromIntegral (ptrToInt a)
183         hi16 x = (x `shiftR` 16) .&. 0xFFFF
184         lo16 x = x .&. 0xFFFF
185     in  [
186         0x3D800000 .|. hi16 w32,
187         0x618C0000 .|. lo16 w32,
188         0x7D8903A6, 0x4E800420
189         ]
190
191 #elif i386_TARGET_ARCH
192 -- Let the address to jump to be 0xWWXXYYZZ.
193 -- Generate   movl $0xWWXXYYZZ,%eax  ;  jmp *%eax
194 -- which is
195 -- B8 ZZ YY XX WW FF E0
196
197 type ItblCode = Word8
198 mkJumpToAddr a
199    = let w32 = fromIntegral (ptrToInt a) :: Word32
200          insnBytes :: [Word8]
201          insnBytes
202             = [0xB8, byte0 w32, byte1 w32, 
203                      byte2 w32, byte3 w32, 
204                0xFF, 0xE0]
205      in
206          insnBytes
207
208 #elif x86_64_TARGET_ARCH
209 -- Generates:
210 --      jmpq *.L1(%rip)
211 --      .align 8
212 -- .L1: 
213 --      .quad <addr>
214 --
215 -- We need a full 64-bit pointer (we can't assume the info table is
216 -- allocated in low memory).  Assuming the info pointer is aligned to
217 -- an 8-byte boundary, the addr will also be aligned.
218
219 type ItblCode = Word8
220 mkJumpToAddr a
221    = let w64 = fromIntegral (ptrToInt a) :: Word64
222          insnBytes :: [Word8]
223          insnBytes
224             = [0xff, 0x25, 0x02, 0x00, 0x00, 0x00, 0x00, 0x00,
225                byte0 w64, byte1 w64, byte2 w64, byte3 w64,
226                byte4 w64, byte5 w64, byte6 w64, byte7 w64]
227      in
228          insnBytes
229
230 #elif alpha_TARGET_ARCH
231 type ItblCode = Word32
232 mkJumpToAddr a
233     = [ 0xc3800000      -- br   at, .+4
234       , 0xa79c000c      -- ldq  at, 12(at)
235       , 0x6bfc0000      -- jmp  (at)    # with zero hint -- oh well
236       , 0x47ff041f      -- nop
237       , fromIntegral (w64 .&. 0x0000FFFF)
238       , fromIntegral ((w64 `shiftR` 32) .&. 0x0000FFFF) ]
239     where w64 = fromIntegral (ptrToInt a) :: Word64
240
241 #else
242 type ItblCode = Word32
243 mkJumpToAddr a
244     = undefined
245 #endif
246
247
248 byte0, byte1, byte2, byte3, byte4, byte5, byte6, byte7
249    :: (Integral w, Bits w) => w -> Word8
250 byte0 w = fromIntegral w
251 byte1 w = fromIntegral (w `shiftR` 8)
252 byte2 w = fromIntegral (w `shiftR` 16)
253 byte3 w = fromIntegral (w `shiftR` 24)
254 byte4 w = fromIntegral (w `shiftR` 32)
255 byte5 w = fromIntegral (w `shiftR` 40)
256 byte6 w = fromIntegral (w `shiftR` 48)
257 byte7 w = fromIntegral (w `shiftR` 56)
258
259
260 #ifndef __HADDOCK__
261 -- entry point for direct returns for created constr itbls
262 foreign import ccall "&stg_interp_constr_entry" stg_interp_constr_entry :: Ptr ()
263 #endif
264
265
266
267
268 -- Ultra-minimalist version specially for constructors
269 #if SIZEOF_VOID_P == 8
270 type HalfWord = Word32
271 #else
272 type HalfWord = Word16
273 #endif
274
275 data StgConInfoTable = StgConInfoTable {
276    conDesc   :: Ptr Word8,
277    infoTable :: StgInfoTable
278 }
279
280 instance Storable StgConInfoTable where
281    sizeOf conInfoTable    
282       = sum [ sizeOf (conDesc conInfoTable)
283             , sizeOf (infoTable conInfoTable) ]
284    alignment conInfoTable = SIZEOF_VOID_P
285    peek ptr 
286       = runState (castPtr ptr) $ do
287 #ifdef GHCI_TABLES_NEXT_TO_CODE
288            desc <- load
289 #endif
290            itbl <- load
291 #ifndef GHCI_TABLES_NEXT_TO_CODE
292            desc <- load
293 #endif
294            return  
295               StgConInfoTable 
296               { 
297 #ifdef GHCI_TABLES_NEXT_TO_CODE
298                 conDesc   = castPtr $ ptr `plusPtr` conInfoTableSizeB `plusPtr` desc
299 #else
300                 conDesc   = desc
301 #endif
302               , infoTable = itbl
303               }
304    poke ptr itbl 
305       = runState (castPtr ptr) $ do
306 #ifdef GHCI_TABLES_NEXT_TO_CODE
307            store (conDesc itbl `minusPtr` (ptr `plusPtr` conInfoTableSizeB))
308 #endif
309            store (infoTable itbl)
310 #ifndef GHCI_TABLES_NEXT_TO_CODE
311            store (conDesc itbl)
312 #endif
313
314 data StgInfoTable = StgInfoTable {
315 #ifndef GHCI_TABLES_NEXT_TO_CODE
316    entry  :: Ptr (),
317 #endif
318    ptrs   :: HalfWord,
319    nptrs  :: HalfWord,
320    tipe   :: HalfWord,
321    srtlen :: HalfWord
322 #ifdef GHCI_TABLES_NEXT_TO_CODE
323  , code   :: [ItblCode]
324 #endif
325   }
326
327 instance Storable StgInfoTable where
328
329    sizeOf itbl 
330       = sum
331         [
332 #ifndef GHCI_TABLES_NEXT_TO_CODE
333          fieldSz entry itbl,
334 #endif
335          fieldSz ptrs itbl,
336          fieldSz nptrs itbl,
337          fieldSz tipe itbl,
338          fieldSz srtlen itbl
339 #ifdef GHCI_TABLES_NEXT_TO_CODE
340         ,fieldSz (head.code) itbl * itblCodeLength
341 #endif
342         ]
343
344    alignment itbl 
345       = SIZEOF_VOID_P
346
347    poke a0 itbl
348       = runState (castPtr a0)
349       $ do
350 #ifndef GHCI_TABLES_NEXT_TO_CODE
351            store (entry  itbl)
352 #endif
353            store (ptrs   itbl)
354            store (nptrs  itbl)
355            store (tipe   itbl)
356            store (srtlen itbl)
357 #ifdef GHCI_TABLES_NEXT_TO_CODE
358            sequence_ (map store (code itbl))
359 #endif
360
361    peek a0
362       = runState (castPtr a0)
363       $ do
364 #ifndef GHCI_TABLES_NEXT_TO_CODE
365            entry  <- load
366 #endif
367            ptrs   <- load
368            nptrs  <- load
369            tipe   <- load
370            srtlen <- load
371 #ifdef GHCI_TABLES_NEXT_TO_CODE
372            code   <- sequence (replicate itblCodeLength load)
373 #endif
374            return 
375               StgInfoTable { 
376 #ifndef GHCI_TABLES_NEXT_TO_CODE
377                  entry  = entry,
378 #endif
379                  ptrs   = ptrs,
380                  nptrs  = nptrs, 
381                  tipe   = tipe,
382                  srtlen = srtlen
383 #ifdef GHCI_TABLES_NEXT_TO_CODE
384                 ,code   = code
385 #endif
386               }
387
388 fieldSz :: (Storable a, Storable b) => (a -> b) -> a -> Int
389 fieldSz sel x = sizeOf (sel x)
390
391 newtype State s m a = State (s -> m (s, a))
392
393 instance Monad m => Monad (State s m) where
394   return a      = State (\s -> return (s, a))
395   State m >>= k = State (\s -> m s >>= \(s', a) -> case k a of State n -> n s')
396   fail str      = State (\s -> fail str)
397
398 class (Monad m, Monad (t m)) => MonadT t m where
399   lift :: m a -> t m a
400
401 instance Monad m => MonadT (State s) m where
402   lift m        = State (\s -> m >>= \a -> return (s, a))
403
404 runState :: (Monad m) => s -> State s m a -> m a
405 runState s (State m) = m s >>= return . snd
406
407 type PtrIO = State (Ptr Word8) IO
408
409 advance :: Storable a => PtrIO (Ptr a)
410 advance = State adv where
411     adv addr = case castPtr addr of { addrCast -> return
412         (addr `plusPtr` sizeOfPointee addrCast, addrCast) }
413
414 sizeOfPointee :: (Storable a) => Ptr a -> Int
415 sizeOfPointee addr = sizeOf (typeHack addr)
416     where typeHack = undefined :: Ptr a -> a
417
418 store :: Storable a => a -> PtrIO ()
419 store x = do addr <- advance
420              lift (poke addr x)
421
422 load :: Storable a => PtrIO a
423 load = do addr <- advance
424           lift (peek addr)
425
426 \end{code}