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