2 % (c) The University of Glasgow 2000
4 \section[ByteCodeItbls]{Generate infotables for interpreter-made bytecodes}
8 {-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
10 module ByteCodeItbls ( ItblEnv, ItblPtr, mkITbls ) where
12 #include "HsVersions.h"
14 import Name ( Name, getName )
16 import Type ( typePrimRep )
17 import DataCon ( DataCon, dataConRepArgTys )
18 import TyCon ( TyCon, tyConFamilySize, isDataTyCon, tyConDataCons )
19 import Constants ( mIN_SIZE_NonUpdHeapObject )
20 import ClosureInfo ( mkVirtHeapOffsets )
21 import FastString ( FastString(..) )
22 import Util ( lengthIs, listLengthCmp )
24 import Foreign ( Storable(..), Word8, Word16, Word32, Word64,
25 malloc, castPtr, plusPtr )
26 import DATA_BITS ( Bits(..), shiftR )
28 import GHC.Exts ( Int(I#), addr2Int# )
29 #if __GLASGOW_HASKELL__ < 503
30 import Ptr ( Ptr(..) )
32 import GHC.Ptr ( Ptr(..) )
36 %************************************************************************
38 \subsection{Manufacturing of info tables for DataCons}
40 %************************************************************************
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
48 mkItblEnv :: [(Name,ItblPtr)] -> ItblEnv
49 mkItblEnv pairs = mkNameEnv [(n, (n,p)) | (n,p) <- pairs]
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
57 return (itbls `plusNameEnv` itbls2)
59 mkITbl :: TyCon -> IO ItblEnv
61 | not (isDataTyCon tc)
63 | dcs `lengthIs` n -- paranoia; this is an assertion.
64 = make_constr_itbls dcs
66 dcs = tyConDataCons tc
67 n = tyConFamilySize tc
70 cONSTR = 1 -- as defined in ghc/includes/ClosureTypes.h
72 -- Assumes constructors are numbered from zero, not one
73 make_constr_itbls :: [DataCon] -> IO ItblEnv
74 make_constr_itbls cons
75 | listLengthCmp cons 8 /= GT -- <= 8 elements in the list
76 = do is <- mapM mk_vecret_itbl (zip cons [0..])
79 = do is <- mapM mk_dirret_itbl (zip cons [0..])
82 mk_vecret_itbl (dcon, conNo)
83 = mk_itbl dcon conNo (vecret_entry conNo)
84 mk_dirret_itbl (dcon, conNo)
85 = mk_itbl dcon conNo stg_interp_constr_entry
87 mk_itbl :: DataCon -> Int -> Ptr () -> IO (Name,ItblPtr)
88 mk_itbl dcon conNo entry_addr
89 = let (tot_wds, ptr_wds, _)
90 = mkVirtHeapOffsets typePrimRep (dataConRepArgTys dcon)
92 nptrs = tot_wds - ptr_wds
94 | ptrs + nptrs >= mIN_SIZE_NonUpdHeapObject = nptrs
95 | otherwise = mIN_SIZE_NonUpdHeapObject - ptrs
97 ptrs = fromIntegral ptrs,
98 nptrs = fromIntegral nptrs_really,
99 tipe = fromIntegral cONSTR,
100 srtlen = fromIntegral conNo,
103 -- Make a piece of code to jump to "entry_label".
104 -- This is the only arch-dependent bit.
105 code = mkJumpToAddr entry_addr
108 --putStrLn ("SIZE of itbl is " ++ show (sizeOf itbl))
109 --putStrLn ("# ptrs of itbl is " ++ show ptrs)
110 --putStrLn ("# nptrs of itbl is " ++ show nptrs_really)
112 return (getName dcon, addr `plusPtr` 8)
115 -- Make code which causes a jump to the given address. This is the
116 -- only arch-dependent bit of the itbl story. The returned list is
117 -- itblCodeLength elements (bytes) long.
119 -- For sparc_TARGET_ARCH, i386_TARGET_ARCH, etc.
120 #include "nativeGen/NCG.h"
122 itblCodeLength :: Int
123 itblCodeLength = length (mkJumpToAddr undefined)
125 mkJumpToAddr :: Ptr () -> [ItblCode]
127 ptrToInt (Ptr a#) = I# (addr2Int# a#)
129 #if sparc_TARGET_ARCH
130 -- After some consideration, we'll try this, where
131 -- 0x55555555 stands in for the address to jump to.
132 -- According to ghc/includes/MachRegs.h, %g3 is very
133 -- likely indeed to be baggable.
135 -- 0000 07155555 sethi %hi(0x55555555), %g3
136 -- 0004 8610E155 or %g3, %lo(0x55555555), %g3
137 -- 0008 81C0C000 jmp %g3
140 type ItblCode = Word32
142 = let w32 = fromIntegral (ptrToInt a)
144 hi22, lo10 :: Word32 -> Word32
146 hi22 x = (x `shiftR` 10) .&. 0x3FFFF
148 in [ 0x07000000 .|. (hi22 w32),
149 0x8610E000 .|. (lo10 w32),
153 #elif powerpc_TARGET_ARCH
154 -- We'll use r12, for no particular reason.
155 -- 0xDEADBEEF stands for the adress:
156 -- 3D80DEAD lis r12,0xDEAD
157 -- 618CBEEF ori r12,r12,0xBEEF
158 -- 7D8903A6 mtctr r12
161 type ItblCode = Word32
163 let w32 = fromIntegral (ptrToInt a)
164 hi16 x = (x `shiftR` 16) .&. 0xFFFF
165 lo16 x = x .&. 0xFFFF
167 0x3D800000 .|. hi16 w32,
168 0x618C0000 .|. lo16 w32,
169 0x7D8903A6, 0x4E800420
172 #elif i386_TARGET_ARCH
173 -- Let the address to jump to be 0xWWXXYYZZ.
174 -- Generate movl $0xWWXXYYZZ,%eax ; jmp *%eax
176 -- B8 ZZ YY XX WW FF E0
178 type ItblCode = Word8
180 = let w32 = fromIntegral (ptrToInt a)
183 = [0xB8, byte 0 w32, byte 1 w32,
184 byte 2 w32, byte 3 w32,
189 #elif alpha_TARGET_ARCH
190 type ItblCode = Word32
192 = [ 0xc3800000 -- br at, .+4
193 , 0xa79c000c -- ldq at, 12(at)
194 , 0x6bfc0000 -- jmp (at) # with zero hint -- oh well
196 , fromIntegral (w64 .&. 0x0000FFFF)
197 , fromIntegral ((w64 `shiftR` 32) .&. 0x0000FFFF) ]
198 where w64 = fromIntegral (ptrToInt a) :: Word64
201 type ItblCode = Word32
207 byte :: Int -> Word32 -> Word8
208 byte 0 w = fromIntegral (w .&. 0xFF)
209 byte 1 w = fromIntegral ((w `shiftR` 8) .&. 0xFF)
210 byte 2 w = fromIntegral ((w `shiftR` 16) .&. 0xFF)
211 byte 3 w = fromIntegral ((w `shiftR` 24) .&. 0xFF)
214 vecret_entry 0 = stg_interp_constr1_entry
215 vecret_entry 1 = stg_interp_constr2_entry
216 vecret_entry 2 = stg_interp_constr3_entry
217 vecret_entry 3 = stg_interp_constr4_entry
218 vecret_entry 4 = stg_interp_constr5_entry
219 vecret_entry 5 = stg_interp_constr6_entry
220 vecret_entry 6 = stg_interp_constr7_entry
221 vecret_entry 7 = stg_interp_constr8_entry
223 -- entry point for direct returns for created constr itbls
224 foreign label "stg_interp_constr_entry" stg_interp_constr_entry :: Ptr ()
225 -- and the 8 vectored ones
226 foreign label "stg_interp_constr1_entry" stg_interp_constr1_entry :: Ptr ()
227 foreign label "stg_interp_constr2_entry" stg_interp_constr2_entry :: Ptr ()
228 foreign label "stg_interp_constr3_entry" stg_interp_constr3_entry :: Ptr ()
229 foreign label "stg_interp_constr4_entry" stg_interp_constr4_entry :: Ptr ()
230 foreign label "stg_interp_constr5_entry" stg_interp_constr5_entry :: Ptr ()
231 foreign label "stg_interp_constr6_entry" stg_interp_constr6_entry :: Ptr ()
232 foreign label "stg_interp_constr7_entry" stg_interp_constr7_entry :: Ptr ()
233 foreign label "stg_interp_constr8_entry" stg_interp_constr8_entry :: Ptr ()
239 -- Ultra-minimalist version specially for constructors
240 #if SIZEOF_VOID_P == 8
241 type HalfWord = Word32
243 type HalfWord = Word16
246 data StgInfoTable = StgInfoTable {
254 instance Storable StgInfoTable where
262 fieldSz (head.code) itbl * itblCodeLength]
268 = runState (castPtr a0)
269 $ do store (ptrs itbl)
273 sequence_ (map store (code itbl))
276 = runState (castPtr a0)
281 code <- sequence (replicate itblCodeLength load)
291 fieldSz :: (Storable a, Storable b) => (a -> b) -> a -> Int
292 fieldSz sel x = sizeOf (sel x)
294 newtype State s m a = State (s -> m (s, a))
296 instance Monad m => Monad (State s m) where
297 return a = State (\s -> return (s, a))
298 State m >>= k = State (\s -> m s >>= \(s', a) -> case k a of State n -> n s')
299 fail str = State (\s -> fail str)
301 class (Monad m, Monad (t m)) => MonadT t m where
304 instance Monad m => MonadT (State s) m where
305 lift m = State (\s -> m >>= \a -> return (s, a))
307 runState :: (Monad m) => s -> State s m a -> m a
308 runState s (State m) = m s >>= return . snd
310 type PtrIO = State (Ptr Word8) IO
312 advance :: Storable a => PtrIO (Ptr a)
313 advance = State adv where
314 adv addr = case castPtr addr of { addrCast -> return
315 (addr `plusPtr` sizeOfPointee addrCast, addrCast) }
317 sizeOfPointee :: (Storable a) => Ptr a -> Int
318 sizeOfPointee addr = sizeOf (typeHack addr)
319 where typeHack = undefined :: Ptr a -> a
321 store :: Storable a => a -> PtrIO ()
322 store x = do addr <- advance
325 load :: Storable a => PtrIO a
326 load = do addr <- advance