c7f829e77dd87e0939767c218f484a5fcc0ade38
[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 FiniteMap        ( FiniteMap, listToFM, emptyFM, plusFM )
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 )
23
24 import Foreign          ( Storable(..), Word8, Word16, Word32, Word64,
25                           malloc, castPtr, plusPtr )
26 import Bits             ( Bits(..), shiftR )
27
28 import Monad            ( liftM )
29
30 import GHC.Exts         ( Int(I#), addr2Int# )
31 import GHC.Ptr          ( Ptr(..) )
32 \end{code}
33
34 %************************************************************************
35 %*                                                                      *
36 \subsection{Manufacturing of info tables for DataCons}
37 %*                                                                      *
38 %************************************************************************
39
40 \begin{code}
41
42 type ItblPtr = Ptr StgInfoTable
43 type ItblEnv = FiniteMap Name ItblPtr
44
45
46 -- Make info tables for the data decls in this module
47 mkITbls :: [TyCon] -> IO ItblEnv
48 mkITbls [] = return emptyFM
49 mkITbls (tc:tcs) = do itbls  <- mkITbl tc
50                       itbls2 <- mkITbls tcs
51                       return (itbls `plusFM` itbls2)
52
53 mkITbl :: TyCon -> IO ItblEnv
54 mkITbl tc
55    | not (isDataTyCon tc) 
56    = return emptyFM
57    | dcs `lengthIs` n -- paranoia; this is an assertion.
58    = make_constr_itbls dcs
59      where
60         dcs = tyConDataCons tc
61         n   = tyConFamilySize tc
62
63 cONSTR :: Int
64 cONSTR = 1  -- as defined in ghc/includes/ClosureTypes.h
65
66 -- Assumes constructors are numbered from zero, not one
67 make_constr_itbls :: [DataCon] -> IO ItblEnv
68 make_constr_itbls cons
69    | listLengthCmp cons 8 /= GT -- <= 8 elements in the list
70    = do is <- mapM mk_vecret_itbl (zip cons [0..])
71         return (listToFM is)
72    | otherwise
73    = do is <- mapM mk_dirret_itbl (zip cons [0..])
74         return (listToFM is)
75      where
76         mk_vecret_itbl (dcon, conNo)
77            = mk_itbl dcon conNo (vecret_entry conNo)
78         mk_dirret_itbl (dcon, conNo)
79            = mk_itbl dcon conNo stg_interp_constr_entry
80
81         mk_itbl :: DataCon -> Int -> Ptr () -> IO (Name,ItblPtr)
82         mk_itbl dcon conNo entry_addr
83            = let (tot_wds, ptr_wds, _) 
84                     = mkVirtHeapOffsets typePrimRep (dataConRepArgTys dcon)
85                  ptrs  = ptr_wds
86                  nptrs = tot_wds - ptr_wds
87                  nptrs_really
88                     | ptrs + nptrs >= mIN_SIZE_NonUpdHeapObject = nptrs
89                     | otherwise = mIN_SIZE_NonUpdHeapObject - ptrs
90                  itbl  = StgInfoTable {
91                            ptrs  = fromIntegral ptrs, 
92                            nptrs = fromIntegral nptrs_really,
93                            tipe  = fromIntegral cONSTR,
94                            srtlen = fromIntegral conNo,
95                            code  = code
96                         }
97                  -- Make a piece of code to jump to "entry_label".
98                  -- This is the only arch-dependent bit.
99                  code = mkJumpToAddr entry_addr
100              in
101                  do addr <- malloc
102                     --putStrLn ("SIZE of itbl is " ++ show (sizeOf itbl))
103                     --putStrLn ("# ptrs  of itbl is " ++ show ptrs)
104                     --putStrLn ("# nptrs of itbl is " ++ show nptrs_really)
105                     poke addr itbl
106                     return (getName dcon, addr `plusPtr` 8)
107
108
109 -- Make code which causes a jump to the given address.  This is the
110 -- only arch-dependent bit of the itbl story.  The returned list is
111 -- itblCodeLength elements (bytes) long.
112
113 -- For sparc_TARGET_ARCH, i386_TARGET_ARCH, etc.
114 #include "nativeGen/NCG.h"
115
116 itblCodeLength :: Int
117 itblCodeLength = length (mkJumpToAddr undefined)
118
119 mkJumpToAddr :: Ptr () -> [ItblCode]
120
121 ptrToInt (Ptr a#) = I# (addr2Int# a#)
122
123 #if sparc_TARGET_ARCH
124 -- After some consideration, we'll try this, where
125 -- 0x55555555 stands in for the address to jump to.
126 -- According to ghc/includes/MachRegs.h, %g3 is very
127 -- likely indeed to be baggable.
128 --
129 --   0000 07155555              sethi   %hi(0x55555555), %g3
130 --   0004 8610E155              or      %g3, %lo(0x55555555), %g3
131 --   0008 81C0C000              jmp     %g3
132 --   000c 01000000              nop
133
134 type ItblCode = Word32
135 mkJumpToAddr a
136    = let w32 = fromIntegral (ptrToInt a)
137
138          hi22, lo10 :: Word32 -> Word32
139          lo10 x = x .&. 0x3FF
140          hi22 x = (x `shiftR` 10) .&. 0x3FFFF
141
142      in  [ 0x07000000 .|. (hi22 w32),
143            0x8610E000 .|. (lo10 w32),
144            0x81C0C000,
145            0x01000000 ]
146
147 #elif powerpc_TARGET_ARCH
148 -- We'll use r12, for no particular reason.
149 -- 0xDEADBEEF stands for the adress:
150 -- 3D80DEAD lis r12,0xDEAD
151 -- 618CBEEF ori r12,r12,0xBEEF
152 -- 7D8903A6 mtctr r12
153 -- 4E800420 bctr
154
155 type ItblCode = Word32
156 mkJumpToAddr a =
157     let w32 = fromIntegral (ptrToInt a)
158         hi16 x = (x `shiftR` 16) .&. 0xFFFF
159         lo16 x = x .&. 0xFFFF
160     in  [
161         0x3D800000 .|. hi16 w32,
162         0x618C0000 .|. lo16 w32,
163         0x7D8903A6, 0x4E800420
164         ]
165
166 #elif i386_TARGET_ARCH
167 -- Let the address to jump to be 0xWWXXYYZZ.
168 -- Generate   movl $0xWWXXYYZZ,%eax  ;  jmp *%eax
169 -- which is
170 -- B8 ZZ YY XX WW FF E0
171
172 type ItblCode = Word8
173 mkJumpToAddr a
174    = let w32 = fromIntegral (ptrToInt a)
175          insnBytes :: [Word8]
176          insnBytes
177             = [0xB8, byte 0 w32, byte 1 w32, 
178                      byte 2 w32, byte 3 w32, 
179                0xFF, 0xE0]
180      in
181          insnBytes
182
183 #elif alpha_TARGET_ARCH
184 type ItblCode = Word32
185 mkJumpToAddr a
186     = [ 0xc3800000      -- br   at, .+4
187       , 0xa79c000c      -- ldq  at, 12(at)
188       , 0x6bfc0000      -- jmp  (at)    # with zero hint -- oh well
189       , 0x47ff041f      -- nop
190       , fromIntegral (w64 .&. 0x0000FFFF)
191       , fromIntegral ((w64 `shiftR` 32) .&. 0x0000FFFF) ]
192     where w64 = fromIntegral (ptrToInt a) :: Word64
193
194 #else
195 type ItblCode = Word32
196 mkJumpToAddr a
197     = undefined
198 #endif
199
200
201 byte :: Int -> Word32 -> Word8
202 byte 0 w = fromIntegral (w .&. 0xFF)
203 byte 1 w = fromIntegral ((w `shiftR` 8) .&. 0xFF)
204 byte 2 w = fromIntegral ((w `shiftR` 16) .&. 0xFF)
205 byte 3 w = fromIntegral ((w `shiftR` 24) .&. 0xFF)
206
207
208 vecret_entry 0 = stg_interp_constr1_entry
209 vecret_entry 1 = stg_interp_constr2_entry
210 vecret_entry 2 = stg_interp_constr3_entry
211 vecret_entry 3 = stg_interp_constr4_entry
212 vecret_entry 4 = stg_interp_constr5_entry
213 vecret_entry 5 = stg_interp_constr6_entry
214 vecret_entry 6 = stg_interp_constr7_entry
215 vecret_entry 7 = stg_interp_constr8_entry
216
217 -- entry point for direct returns for created constr itbls
218 foreign label "stg_interp_constr_entry" stg_interp_constr_entry :: Ptr ()
219 -- and the 8 vectored ones
220 foreign label "stg_interp_constr1_entry" stg_interp_constr1_entry :: Ptr ()
221 foreign label "stg_interp_constr2_entry" stg_interp_constr2_entry :: Ptr ()
222 foreign label "stg_interp_constr3_entry" stg_interp_constr3_entry :: Ptr ()
223 foreign label "stg_interp_constr4_entry" stg_interp_constr4_entry :: Ptr ()
224 foreign label "stg_interp_constr5_entry" stg_interp_constr5_entry :: Ptr ()
225 foreign label "stg_interp_constr6_entry" stg_interp_constr6_entry :: Ptr ()
226 foreign label "stg_interp_constr7_entry" stg_interp_constr7_entry :: Ptr ()
227 foreign label "stg_interp_constr8_entry" stg_interp_constr8_entry :: Ptr ()
228
229
230
231
232
233 -- Ultra-minimalist version specially for constructors
234 #if SIZEOF_VOID_P == 8
235 type HalfWord = Word32
236 #else
237 type HalfWord = Word16
238 #endif
239
240 data StgInfoTable = StgInfoTable {
241    ptrs   :: HalfWord,
242    nptrs  :: HalfWord,
243    tipe   :: HalfWord,
244    srtlen :: HalfWord,
245    code   :: [ItblCode]
246 }
247
248 instance Storable StgInfoTable where
249
250    sizeOf itbl 
251       = sum
252         [fieldSz ptrs itbl,
253          fieldSz nptrs itbl,
254          fieldSz tipe itbl,
255          fieldSz srtlen itbl,
256          fieldSz (head.code) itbl * itblCodeLength]
257
258    alignment itbl 
259       = SIZEOF_VOID_P
260
261    poke a0 itbl
262       = runState (castPtr a0)
263       $ do store (ptrs   itbl)
264            store (nptrs  itbl)
265            store (tipe   itbl)
266            store (srtlen itbl)
267            sequence_ (map store (code itbl))
268
269    peek a0
270       = runState (castPtr a0)
271       $ do ptrs   <- load
272            nptrs  <- load
273            tipe   <- load
274            srtlen <- load
275            code   <- sequence (replicate itblCodeLength load)
276            return 
277               StgInfoTable { 
278                  ptrs   = ptrs,
279                  nptrs  = nptrs, 
280                  tipe   = tipe,
281                  srtlen = srtlen,
282                  code   = code
283               }
284
285 fieldSz :: (Storable a, Storable b) => (a -> b) -> a -> Int
286 fieldSz sel x = sizeOf (sel x)
287
288 newtype State s m a = State (s -> m (s, a))
289
290 instance Monad m => Monad (State s m) where
291   return a      = State (\s -> return (s, a))
292   State m >>= k = State (\s -> m s >>= \(s', a) -> case k a of State n -> n s')
293   fail str      = State (\s -> fail str)
294
295 class (Monad m, Monad (t m)) => MonadT t m where
296   lift :: m a -> t m a
297
298 instance Monad m => MonadT (State s) m where
299   lift m        = State (\s -> m >>= \a -> return (s, a))
300
301 runState :: (Monad m) => s -> State s m a -> m a
302 runState s (State m) = m s >>= return . snd
303
304 type PtrIO = State (Ptr Word8) IO
305
306 advance :: Storable a => PtrIO (Ptr a)
307 advance = State adv where
308     adv addr = case castPtr addr of { addrCast -> return
309         (addr `plusPtr` sizeOfPointee addrCast, addrCast) }
310
311 sizeOfPointee :: (Storable a) => Ptr a -> Int
312 sizeOfPointee addr = sizeOf (typeHack addr)
313     where typeHack = undefined :: Ptr a -> a
314
315 store :: Storable a => a -> PtrIO ()
316 store x = do addr <- advance
317              lift (poke addr x)
318
319 load :: Storable a => PtrIO a
320 load = do addr <- advance
321           lift (peek addr)
322
323 \end{code}