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