2 % (c) The University of Glasgow 2000-2006
4 ByteCodeItbls: Generate infotables for interpreter-made bytecodes
7 {-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
10 -- The above warning supression flag is a temporary kludge.
11 -- While working on this module you are encouraged to remove it and fix
12 -- any warnings in the module. See
13 -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
16 module ByteCodeItbls ( ItblEnv, ItblPtr(..), itblCode, mkITbls
20 #include "HsVersions.h"
22 import ByteCodeFFI ( newExec )
23 import Name ( Name, getName )
25 import SMRep ( typeCgRep )
26 import DataCon ( DataCon, dataConRepArgTys, dataConIdentity )
27 import TyCon ( TyCon, tyConFamilySize, isDataTyCon, tyConDataCons )
28 import Constants ( mIN_PAYLOAD_SIZE, wORD_SIZE )
29 import CgHeapery ( mkVirtHeapOffsets )
30 import FastString ( FastString(..) )
36 import Foreign.C.String
37 import Data.Bits ( Bits(..), shiftR )
39 import GHC.Exts ( Int(I#), addr2Int# )
40 import GHC.Ptr ( Ptr(..) )
46 %************************************************************************
48 \subsection{Manufacturing of info tables for DataCons}
50 %************************************************************************
53 newtype ItblPtr = ItblPtr (Ptr ()) deriving Show
55 itblCode :: ItblPtr -> Ptr ()
56 itblCode (ItblPtr ptr)
57 | ghciTablesNextToCode = castPtr ptr `plusPtr` conInfoTableSizeB
58 | otherwise = castPtr ptr
61 conInfoTableSizeB = 3 * wORD_SIZE
63 type ItblEnv = NameEnv (Name, ItblPtr)
64 -- We need the Name in the range so we know which
65 -- elements to filter out when unloading a module
67 mkItblEnv :: [(Name,ItblPtr)] -> ItblEnv
68 mkItblEnv pairs = mkNameEnv [(n, (n,p)) | (n,p) <- pairs]
71 -- Make info tables for the data decls in this module
72 mkITbls :: [TyCon] -> IO ItblEnv
73 mkITbls [] = return emptyNameEnv
74 mkITbls (tc:tcs) = do itbls <- mkITbl tc
76 return (itbls `plusNameEnv` itbls2)
78 mkITbl :: TyCon -> IO ItblEnv
80 | not (isDataTyCon tc)
82 | dcs `lengthIs` n -- paranoia; this is an assertion.
83 = make_constr_itbls dcs
85 dcs = tyConDataCons tc
86 n = tyConFamilySize tc
88 #include "../includes/ClosureTypes.h"
89 cONSTR :: Int -- Defined in ClosureTypes.h
92 -- Assumes constructors are numbered from zero, not one
93 make_constr_itbls :: [DataCon] -> IO ItblEnv
94 make_constr_itbls cons
95 = do is <- mapM mk_dirret_itbl (zip cons [0..])
98 mk_dirret_itbl (dcon, conNo)
99 = mk_itbl dcon conNo stg_interp_constr_entry
101 mk_itbl :: DataCon -> Int -> Ptr () -> IO (Name,ItblPtr)
102 mk_itbl dcon conNo entry_addr = do
103 let rep_args = [ (typeCgRep arg,arg) | arg <- dataConRepArgTys dcon ]
104 (tot_wds, ptr_wds, _) = mkVirtHeapOffsets False{-not a THUNK-} rep_args
107 nptrs = tot_wds - ptr_wds
109 | ptrs + nptrs >= mIN_PAYLOAD_SIZE = nptrs
110 | otherwise = mIN_PAYLOAD_SIZE - ptrs
111 code = mkJumpToAddr entry_addr
112 itbl = StgInfoTable {
113 #ifndef GHCI_TABLES_NEXT_TO_CODE
116 ptrs = fromIntegral ptrs,
117 nptrs = fromIntegral nptrs_really,
118 tipe = fromIntegral cONSTR,
119 srtlen = fromIntegral conNo
120 #ifdef GHCI_TABLES_NEXT_TO_CODE
124 qNameCString <- newArray0 0 $ dataConIdentity dcon
125 let conInfoTbl = StgConInfoTable {
126 conDesc = qNameCString,
129 -- Make a piece of code to jump to "entry_label".
130 -- This is the only arch-dependent bit.
131 addrCon <- newExec [conInfoTbl]
132 --putStrLn ("SIZE of itbl is " ++ show (sizeOf itbl))
133 --putStrLn ("# ptrs of itbl is " ++ show ptrs)
134 --putStrLn ("# nptrs of itbl is " ++ show nptrs_really)
135 return (getName dcon, ItblPtr (castFunPtrToPtr addrCon))
138 -- Make code which causes a jump to the given address. This is the
139 -- only arch-dependent bit of the itbl story. The returned list is
140 -- itblCodeLength elements (bytes) long.
142 -- For sparc_TARGET_ARCH, i386_TARGET_ARCH, etc.
143 #include "nativeGen/NCG.h"
145 itblCodeLength :: Int
146 itblCodeLength = length (mkJumpToAddr undefined)
148 mkJumpToAddr :: Ptr () -> [ItblCode]
150 ptrToInt (Ptr a#) = I# (addr2Int# a#)
152 #if sparc_TARGET_ARCH
153 -- After some consideration, we'll try this, where
154 -- 0x55555555 stands in for the address to jump to.
155 -- According to ghc/includes/MachRegs.h, %g3 is very
156 -- likely indeed to be baggable.
158 -- 0000 07155555 sethi %hi(0x55555555), %g3
159 -- 0004 8610E155 or %g3, %lo(0x55555555), %g3
160 -- 0008 81C0C000 jmp %g3
163 type ItblCode = Word32
165 = let w32 = fromIntegral (ptrToInt a)
167 hi22, lo10 :: Word32 -> Word32
169 hi22 x = (x `shiftR` 10) .&. 0x3FFFF
171 in [ 0x07000000 .|. (hi22 w32),
172 0x8610E000 .|. (lo10 w32),
176 #elif powerpc_TARGET_ARCH
177 -- We'll use r12, for no particular reason.
178 -- 0xDEADBEEF stands for the adress:
179 -- 3D80DEAD lis r12,0xDEAD
180 -- 618CBEEF ori r12,r12,0xBEEF
181 -- 7D8903A6 mtctr r12
184 type ItblCode = Word32
186 let w32 = fromIntegral (ptrToInt a)
187 hi16 x = (x `shiftR` 16) .&. 0xFFFF
188 lo16 x = x .&. 0xFFFF
190 0x3D800000 .|. hi16 w32,
191 0x618C0000 .|. lo16 w32,
192 0x7D8903A6, 0x4E800420
195 #elif i386_TARGET_ARCH
196 -- Let the address to jump to be 0xWWXXYYZZ.
197 -- Generate movl $0xWWXXYYZZ,%eax ; jmp *%eax
199 -- B8 ZZ YY XX WW FF E0
201 type ItblCode = Word8
203 = let w32 = fromIntegral (ptrToInt a) :: Word32
206 = [0xB8, byte0 w32, byte1 w32,
207 byte2 w32, byte3 w32,
212 #elif x86_64_TARGET_ARCH
219 -- We need a full 64-bit pointer (we can't assume the info table is
220 -- allocated in low memory). Assuming the info pointer is aligned to
221 -- an 8-byte boundary, the addr will also be aligned.
223 type ItblCode = Word8
225 = let w64 = fromIntegral (ptrToInt a) :: Word64
228 = [0xff, 0x25, 0x02, 0x00, 0x00, 0x00, 0x00, 0x00,
229 byte0 w64, byte1 w64, byte2 w64, byte3 w64,
230 byte4 w64, byte5 w64, byte6 w64, byte7 w64]
234 #elif alpha_TARGET_ARCH
235 type ItblCode = Word32
237 = [ 0xc3800000 -- br at, .+4
238 , 0xa79c000c -- ldq at, 12(at)
239 , 0x6bfc0000 -- jmp (at) # with zero hint -- oh well
241 , fromIntegral (w64 .&. 0x0000FFFF)
242 , fromIntegral ((w64 `shiftR` 32) .&. 0x0000FFFF) ]
243 where w64 = fromIntegral (ptrToInt a) :: Word64
246 type ItblCode = Word32
252 byte0, byte1, byte2, byte3, byte4, byte5, byte6, byte7
253 :: (Integral w, Bits w) => w -> Word8
254 byte0 w = fromIntegral w
255 byte1 w = fromIntegral (w `shiftR` 8)
256 byte2 w = fromIntegral (w `shiftR` 16)
257 byte3 w = fromIntegral (w `shiftR` 24)
258 byte4 w = fromIntegral (w `shiftR` 32)
259 byte5 w = fromIntegral (w `shiftR` 40)
260 byte6 w = fromIntegral (w `shiftR` 48)
261 byte7 w = fromIntegral (w `shiftR` 56)
265 -- entry point for direct returns for created constr itbls
266 foreign import ccall "&stg_interp_constr_entry" stg_interp_constr_entry :: Ptr ()
272 -- Ultra-minimalist version specially for constructors
273 #if SIZEOF_VOID_P == 8
274 type HalfWord = Word32
276 type HalfWord = Word16
279 data StgConInfoTable = StgConInfoTable {
280 conDesc :: Ptr Word8,
281 infoTable :: StgInfoTable
284 instance Storable StgConInfoTable where
286 = sum [ sizeOf (conDesc conInfoTable)
287 , sizeOf (infoTable conInfoTable) ]
288 alignment conInfoTable = SIZEOF_VOID_P
290 = runState (castPtr ptr) $ do
291 #ifdef GHCI_TABLES_NEXT_TO_CODE
295 #ifndef GHCI_TABLES_NEXT_TO_CODE
301 #ifdef GHCI_TABLES_NEXT_TO_CODE
302 conDesc = castPtr $ ptr `plusPtr` conInfoTableSizeB `plusPtr` desc
309 = runState (castPtr ptr) $ do
310 #ifdef GHCI_TABLES_NEXT_TO_CODE
311 store (conDesc itbl `minusPtr` (ptr `plusPtr` conInfoTableSizeB))
313 store (infoTable itbl)
314 #ifndef GHCI_TABLES_NEXT_TO_CODE
318 data StgInfoTable = StgInfoTable {
319 #ifndef GHCI_TABLES_NEXT_TO_CODE
326 #ifdef GHCI_TABLES_NEXT_TO_CODE
331 instance Storable StgInfoTable where
336 #ifndef GHCI_TABLES_NEXT_TO_CODE
343 #ifdef GHCI_TABLES_NEXT_TO_CODE
344 ,fieldSz (head.code) itbl * itblCodeLength
352 = runState (castPtr a0)
354 #ifndef GHCI_TABLES_NEXT_TO_CODE
361 #ifdef GHCI_TABLES_NEXT_TO_CODE
362 sequence_ (map store (code itbl))
366 = runState (castPtr a0)
368 #ifndef GHCI_TABLES_NEXT_TO_CODE
375 #ifdef GHCI_TABLES_NEXT_TO_CODE
376 code <- sequence (replicate itblCodeLength load)
380 #ifndef GHCI_TABLES_NEXT_TO_CODE
387 #ifdef GHCI_TABLES_NEXT_TO_CODE
392 fieldSz :: (Storable a, Storable b) => (a -> b) -> a -> Int
393 fieldSz sel x = sizeOf (sel x)
395 newtype State s m a = State (s -> m (s, a))
397 instance Monad m => Monad (State s m) where
398 return a = State (\s -> return (s, a))
399 State m >>= k = State (\s -> m s >>= \(s', a) -> case k a of State n -> n s')
400 fail str = State (\s -> fail str)
402 class (Monad m, Monad (t m)) => MonadT t m where
405 instance Monad m => MonadT (State s) m where
406 lift m = State (\s -> m >>= \a -> return (s, a))
408 runState :: (Monad m) => s -> State s m a -> m a
409 runState s (State m) = m s >>= return . snd
411 type PtrIO = State (Ptr Word8) IO
413 advance :: Storable a => PtrIO (Ptr a)
414 advance = State adv where
415 adv addr = case castPtr addr of { addrCast -> return
416 (addr `plusPtr` sizeOfPointee addrCast, addrCast) }
418 sizeOfPointee :: (Storable a) => Ptr a -> Int
419 sizeOfPointee addr = sizeOf (typeHack addr)
420 where typeHack = undefined :: Ptr a -> a
422 store :: Storable a => a -> PtrIO ()
423 store x = do addr <- advance
426 load :: Storable a => PtrIO a
427 load = do addr <- advance