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