2 % (c) The University of Glasgow 2002
4 \section[ByteCodeLink]{Bytecode assembler and linker}
7 {-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
10 assembleBCOs, assembleBCO,
13 UnlinkedBCO(..), BCOPtr(..), bcoFreeNames,
14 SizedSeq, sizeSS, ssElts,
15 iNTERP_STACK_CHECK_THRESH
18 #include "HsVersions.h"
21 import ByteCodeItbls ( ItblEnv, mkITbls )
23 import Name ( Name, getName )
25 import FiniteMap ( addToFM, lookupFM, emptyFM )
26 import Literal ( Literal(..) )
27 import TyCon ( TyCon )
28 import PrimOp ( PrimOp )
29 import PrimRep ( PrimRep(..), isFollowableRep, is64BitRep )
30 import Constants ( wORD_SIZE )
31 import FastString ( FastString(..), unpackFS )
32 import SMRep ( StgWord )
36 import Control.Monad ( foldM, zipWithM )
37 import Control.Monad.ST ( ST, runST )
39 import GHC.Word ( Word(..) )
40 import Data.Array.MArray
41 import Data.Array.Unboxed ( listArray )
42 import Data.Array.Base ( STUArray, UArray(..), unsafeWrite )
43 import Data.Array.ST ( castSTUArray )
44 import Foreign ( Word16, free )
45 import Data.Int ( Int64 )
47 import GHC.Base ( ByteArray# )
48 import GHC.IOBase ( IO(..) )
49 import GHC.Ptr ( Ptr(..) )
51 -- -----------------------------------------------------------------------------
54 -- CompiledByteCode represents the result of byte-code
55 -- compiling a bunch of functions and data types
58 = ByteCode [UnlinkedBCO] -- Bunch of interpretable bindings
59 ItblEnv -- A mapping from DataCons to their itbls
61 instance Outputable CompiledByteCode where
62 ppr (ByteCode bcos _) = ppr bcos
67 unlinkedBCOName :: Name,
68 unlinkedBCOArity :: Int,
69 unlinkedBCOInstrs :: ByteArray#, -- insns
70 unlinkedBCOBitmap :: ByteArray#, -- bitmap
71 unlinkedBCOLits :: (SizedSeq (Either Word FastString)), -- literals
72 -- Either literal words or a pointer to a asciiz
73 -- string, denoting a label whose *address* should
74 -- be determined at link time
75 unlinkedBCOPtrs :: (SizedSeq BCOPtr), -- ptrs
76 unlinkedBCOItbls :: (SizedSeq Name) -- itbl refs
82 | BCOPtrBCO UnlinkedBCO
84 -- | Finds external references. Remember to remove the names
85 -- defined by this group of BCOs themselves
86 bcoFreeNames :: UnlinkedBCO -> NameSet
88 = bco_refs bco `minusNameSet` mkNameSet [unlinkedBCOName bco]
90 bco_refs (UnlinkedBCO _ _ _ _ _ ptrs itbls)
92 mkNameSet [ n | BCOPtrName n <- ssElts ptrs ] :
93 mkNameSet (ssElts itbls) :
94 map bco_refs [ bco | BCOPtrBCO bco <- ssElts ptrs ]
97 instance Outputable UnlinkedBCO where
98 ppr (UnlinkedBCO nm arity insns bitmap lits ptrs itbls)
99 = sep [text "BCO", ppr nm, text "with",
100 int (sizeSS lits), text "lits",
101 int (sizeSS ptrs), text "ptrs",
102 int (sizeSS itbls), text "itbls"]
104 -- -----------------------------------------------------------------------------
105 -- The bytecode assembler
107 -- The object format for bytecodes is: 16 bits for the opcode, and 16
108 -- for each field -- so the code can be considered a sequence of
109 -- 16-bit ints. Each field denotes either a stack offset or number of
110 -- items on the stack (eg SLIDE), and index into the pointer table (eg
111 -- PUSH_G), an index into the literal table (eg PUSH_I/D/L), or a
112 -- bytecode address in this BCO.
114 -- Top level assembler fn.
115 assembleBCOs :: [ProtoBCO Name] -> [TyCon] -> IO CompiledByteCode
116 assembleBCOs proto_bcos tycons
117 = do itblenv <- mkITbls tycons
118 bcos <- mapM assembleBCO proto_bcos
119 return (ByteCode bcos itblenv)
121 assembleBCO :: ProtoBCO Name -> IO UnlinkedBCO
122 assembleBCO (ProtoBCO nm instrs bitmap bsize arity origin malloced)
124 -- pass 1: collect up the offsets of the local labels.
125 -- Remember that the first insn starts at offset 1 since offset 0
126 -- (eventually) will hold the total # of insns.
127 label_env = mkLabelEnv emptyFM 1 instrs
129 mkLabelEnv env i_offset [] = env
130 mkLabelEnv env i_offset (i:is)
132 = case i of LABEL n -> addToFM env n i_offset ; _ -> env
133 in mkLabelEnv new_env (i_offset + instrSize16s i) is
136 = case lookupFM label_env lab of
137 Just bco_offset -> bco_offset
138 Nothing -> pprPanic "assembleBCO.findLabel" (int lab)
140 do -- pass 2: generate the instruction, ptr and nonptr bits
141 insns <- return emptySS :: IO (SizedSeq Word16)
142 lits <- return emptySS :: IO (SizedSeq (Either Word FastString))
143 ptrs <- return emptySS :: IO (SizedSeq BCOPtr)
144 itbls <- return emptySS :: IO (SizedSeq Name)
145 let init_asm_state = (insns,lits,ptrs,itbls)
146 (final_insns, final_lits, final_ptrs, final_itbls)
147 <- mkBits findLabel init_asm_state instrs
149 let asm_insns = ssElts final_insns
150 n_insns = sizeSS final_insns
153 | n_insns > 65535 = panic "linkBCO: >= 64k insns in BCO"
154 | otherwise = mkInstrArray n_insns asm_insns
155 insns_barr = case insns_arr of UArray _lo _hi barr -> barr
157 bitmap_arr = mkBitmapArray bsize bitmap
158 bitmap_barr = case bitmap_arr of UArray _lo _hi barr -> barr
160 let ul_bco = UnlinkedBCO nm arity insns_barr bitmap_barr final_lits
161 final_ptrs final_itbls
163 -- 8 Aug 01: Finalisers aren't safe when attached to non-primitive
164 -- objects, since they might get run too early. Disable this until
165 -- we figure out what to do.
166 -- when (notNull malloced) (addFinalizer ul_bco (mapM_ zonk malloced))
170 zonk ptr = do -- putStrLn ("freeing malloc'd block at " ++ show (A# a#))
173 mkBitmapArray :: Int -> [StgWord] -> UArray Int StgWord
174 mkBitmapArray bsize bitmap
175 = listArray (0, length bitmap) (fromIntegral bsize : bitmap)
177 mkInstrArray :: Int -> [Word16] -> UArray Int Word16
178 mkInstrArray n_insns asm_insns
179 = listArray (0, n_insns) (fromIntegral n_insns : asm_insns)
181 -- instrs nonptrs ptrs itbls
182 type AsmState = (SizedSeq Word16,
183 SizedSeq (Either Word FastString),
187 data SizedSeq a = SizedSeq !Int [a]
188 emptySS = SizedSeq 0 []
190 -- Why are these two monadic???
191 addToSS (SizedSeq n r_xs) x = return (SizedSeq (n+1) (x:r_xs))
192 addListToSS (SizedSeq n r_xs) xs
193 = return (SizedSeq (n + length xs) (reverse xs ++ r_xs))
195 ssElts :: SizedSeq a -> [a]
196 ssElts (SizedSeq n r_xs) = reverse r_xs
198 sizeSS :: SizedSeq a -> Int
199 sizeSS (SizedSeq n r_xs) = n
201 -- Bring in all the bci_ bytecode constants.
202 #include "Bytecodes.h"
204 -- This is where all the action is (pass 2 of the assembler)
205 mkBits :: (Int -> Int) -- label finder
207 -> [BCInstr] -- instructions (in)
210 mkBits findLabel st proto_insns
211 = foldM doInstr st proto_insns
213 doInstr :: AsmState -> BCInstr -> IO AsmState
216 STKCHECK n -> instr2 st bci_STKCHECK n
217 PUSH_L o1 -> instr2 st bci_PUSH_L o1
218 PUSH_LL o1 o2 -> instr3 st bci_PUSH_LL o1 o2
219 PUSH_LLL o1 o2 o3 -> instr4 st bci_PUSH_LLL o1 o2 o3
220 PUSH_G nm -> do (p, st2) <- ptr st (BCOPtrName nm)
221 instr2 st2 bci_PUSH_G p
222 PUSH_PRIMOP op -> do (p, st2) <- ptr st (BCOPtrPrimOp op)
223 instr2 st2 bci_PUSH_G p
224 PUSH_BCO proto -> do ul_bco <- assembleBCO proto
225 (p, st2) <- ptr st (BCOPtrBCO ul_bco)
226 instr2 st2 bci_PUSH_G p
227 PUSH_ALTS proto -> do ul_bco <- assembleBCO proto
228 (p, st2) <- ptr st (BCOPtrBCO ul_bco)
229 instr2 st2 bci_PUSH_ALTS p
230 PUSH_ALTS_UNLIFTED proto pk -> do
231 ul_bco <- assembleBCO proto
232 (p, st2) <- ptr st (BCOPtrBCO ul_bco)
233 instr2 st2 (push_alts pk) p
234 PUSH_UBX (Left lit) nws
235 -> do (np, st2) <- literal st lit
236 instr3 st2 bci_PUSH_UBX np nws
237 PUSH_UBX (Right aa) nws
238 -> do (np, st2) <- addr st aa
239 instr3 st2 bci_PUSH_UBX np nws
241 PUSH_APPLY_N -> do instr1 st bci_PUSH_APPLY_N
242 PUSH_APPLY_V -> do instr1 st bci_PUSH_APPLY_V
243 PUSH_APPLY_F -> do instr1 st bci_PUSH_APPLY_F
244 PUSH_APPLY_D -> do instr1 st bci_PUSH_APPLY_D
245 PUSH_APPLY_L -> do instr1 st bci_PUSH_APPLY_L
246 PUSH_APPLY_P -> do instr1 st bci_PUSH_APPLY_P
247 PUSH_APPLY_PP -> do instr1 st bci_PUSH_APPLY_PP
248 PUSH_APPLY_PPP -> do instr1 st bci_PUSH_APPLY_PPP
249 PUSH_APPLY_PPPP -> do instr1 st bci_PUSH_APPLY_PPPP
250 PUSH_APPLY_PPPPP -> do instr1 st bci_PUSH_APPLY_PPPPP
251 PUSH_APPLY_PPPPPP -> do instr1 st bci_PUSH_APPLY_PPPPPP
252 PUSH_APPLY_PPPPPPP -> do instr1 st bci_PUSH_APPLY_PPPPPPP
254 SLIDE n by -> instr3 st bci_SLIDE n by
255 ALLOC_AP n -> instr2 st bci_ALLOC_AP n
256 ALLOC_PAP arity n -> instr3 st bci_ALLOC_PAP arity n
257 MKAP off sz -> instr3 st bci_MKAP off sz
258 UNPACK n -> instr2 st bci_UNPACK n
259 PACK dcon sz -> do (itbl_no,st2) <- itbl st dcon
260 instr3 st2 bci_PACK itbl_no sz
261 LABEL lab -> return st
262 TESTLT_I i l -> do (np, st2) <- int st i
263 instr3 st2 bci_TESTLT_I np (findLabel l)
264 TESTEQ_I i l -> do (np, st2) <- int st i
265 instr3 st2 bci_TESTEQ_I np (findLabel l)
266 TESTLT_F f l -> do (np, st2) <- float st f
267 instr3 st2 bci_TESTLT_F np (findLabel l)
268 TESTEQ_F f l -> do (np, st2) <- float st f
269 instr3 st2 bci_TESTEQ_F np (findLabel l)
270 TESTLT_D d l -> do (np, st2) <- double st d
271 instr3 st2 bci_TESTLT_D np (findLabel l)
272 TESTEQ_D d l -> do (np, st2) <- double st d
273 instr3 st2 bci_TESTEQ_D np (findLabel l)
274 TESTLT_P i l -> instr3 st bci_TESTLT_P i (findLabel l)
275 TESTEQ_P i l -> instr3 st bci_TESTEQ_P i (findLabel l)
276 CASEFAIL -> instr1 st bci_CASEFAIL
277 SWIZZLE stkoff n -> instr3 st bci_SWIZZLE stkoff n
278 JMP l -> instr2 st bci_JMP (findLabel l)
279 ENTER -> instr1 st bci_ENTER
280 RETURN -> instr1 st bci_RETURN
281 RETURN_UBX rep -> instr1 st (return_ubx rep)
282 CCALL off m_addr -> do (np, st2) <- addr st m_addr
283 instr3 st2 bci_CCALL off np
288 instr1 (st_i0,st_l0,st_p0,st_I0) i1
289 = do st_i1 <- addToSS st_i0 i1
290 return (st_i1,st_l0,st_p0,st_I0)
292 instr2 (st_i0,st_l0,st_p0,st_I0) i1 i2
293 = do st_i1 <- addToSS st_i0 (i2s i1)
294 st_i2 <- addToSS st_i1 (i2s i2)
295 return (st_i2,st_l0,st_p0,st_I0)
297 instr3 (st_i0,st_l0,st_p0,st_I0) i1 i2 i3
298 = do st_i1 <- addToSS st_i0 (i2s i1)
299 st_i2 <- addToSS st_i1 (i2s i2)
300 st_i3 <- addToSS st_i2 (i2s i3)
301 return (st_i3,st_l0,st_p0,st_I0)
303 instr4 (st_i0,st_l0,st_p0,st_I0) i1 i2 i3 i4
304 = do st_i1 <- addToSS st_i0 (i2s i1)
305 st_i2 <- addToSS st_i1 (i2s i2)
306 st_i3 <- addToSS st_i2 (i2s i3)
307 st_i4 <- addToSS st_i3 (i2s i4)
308 return (st_i4,st_l0,st_p0,st_I0)
310 float (st_i0,st_l0,st_p0,st_I0) f
311 = do let ws = mkLitF f
312 st_l1 <- addListToSS st_l0 (map Left ws)
313 return (sizeSS st_l0, (st_i0,st_l1,st_p0,st_I0))
315 double (st_i0,st_l0,st_p0,st_I0) d
316 = do let ws = mkLitD d
317 st_l1 <- addListToSS st_l0 (map Left ws)
318 return (sizeSS st_l0, (st_i0,st_l1,st_p0,st_I0))
320 int (st_i0,st_l0,st_p0,st_I0) i
321 = do let ws = mkLitI i
322 st_l1 <- addListToSS st_l0 (map Left ws)
323 return (sizeSS st_l0, (st_i0,st_l1,st_p0,st_I0))
325 int64 (st_i0,st_l0,st_p0,st_I0) i
326 = do let ws = mkLitI64 i
327 st_l1 <- addListToSS st_l0 (map Left ws)
328 return (sizeSS st_l0, (st_i0,st_l1,st_p0,st_I0))
330 addr (st_i0,st_l0,st_p0,st_I0) a
331 = do let ws = mkLitPtr a
332 st_l1 <- addListToSS st_l0 (map Left ws)
333 return (sizeSS st_l0, (st_i0,st_l1,st_p0,st_I0))
335 litlabel (st_i0,st_l0,st_p0,st_I0) fs
336 = do st_l1 <- addListToSS st_l0 [Right fs]
337 return (sizeSS st_l0, (st_i0,st_l1,st_p0,st_I0))
339 ptr (st_i0,st_l0,st_p0,st_I0) p
340 = do st_p1 <- addToSS st_p0 p
341 return (sizeSS st_p0, (st_i0,st_l0,st_p1,st_I0))
343 itbl (st_i0,st_l0,st_p0,st_I0) dcon
344 = do st_I1 <- addToSS st_I0 (getName dcon)
345 return (sizeSS st_I0, (st_i0,st_l0,st_p0,st_I1))
347 literal st (MachLabel fs _) = litlabel st fs
348 literal st (MachWord w) = int st (fromIntegral w)
349 literal st (MachInt j) = int st (fromIntegral j)
350 literal st (MachFloat r) = float st (fromRational r)
351 literal st (MachDouble r) = double st (fromRational r)
352 literal st (MachChar c) = int st c
353 literal st (MachInt64 ii) = int64 st (fromIntegral ii)
354 literal st (MachWord64 ii) = int64 st (fromIntegral ii)
355 literal st other = pprPanic "ByteCodeLink.literal" (ppr other)
358 push_alts WordRep = bci_PUSH_ALTS_N
359 push_alts IntRep = bci_PUSH_ALTS_N
360 push_alts AddrRep = bci_PUSH_ALTS_N
361 push_alts CharRep = bci_PUSH_ALTS_N
362 push_alts FloatRep = bci_PUSH_ALTS_F
363 push_alts DoubleRep = bci_PUSH_ALTS_D
364 push_alts VoidRep = bci_PUSH_ALTS_V
366 | is64BitRep pk = bci_PUSH_ALTS_L
367 | isFollowableRep pk = bci_PUSH_ALTS_P
369 return_ubx WordRep = bci_RETURN_N
370 return_ubx IntRep = bci_RETURN_N
371 return_ubx AddrRep = bci_RETURN_N
372 return_ubx CharRep = bci_RETURN_N
373 return_ubx FloatRep = bci_RETURN_F
374 return_ubx DoubleRep = bci_RETURN_D
375 return_ubx VoidRep = bci_RETURN_V
377 | is64BitRep pk = bci_RETURN_L
378 | isFollowableRep pk = bci_RETURN_P
381 -- The size in 16-bit entities of an instruction.
382 instrSize16s :: BCInstr -> Int
393 PUSH_ALTS_UNLIFTED{} -> 2
402 PUSH_APPLY_PPP{} -> 1
403 PUSH_APPLY_PPPP{} -> 1
404 PUSH_APPLY_PPPPP{} -> 1
405 PUSH_APPLY_PPPPPP{} -> 1
406 PUSH_APPLY_PPPPPPP{} -> 1
430 -- Make lists of host-sized words for literals, so that when the
431 -- words are placed in memory at increasing addresses, the
432 -- bit pattern is correct for the host's word size and endianness.
433 mkLitI :: Int -> [Word]
434 mkLitF :: Float -> [Word]
435 mkLitD :: Double -> [Word]
436 mkLitPtr :: Ptr () -> [Word]
437 mkLitI64 :: Int64 -> [Word]
441 arr <- newArray_ ((0::Int),0)
443 f_arr <- castSTUArray arr
444 w0 <- readArray f_arr 0
451 arr <- newArray_ ((0::Int),1)
453 d_arr <- castSTUArray arr
454 w0 <- readArray d_arr 0
455 w1 <- readArray d_arr 1
456 return [w0 :: Word, w1]
460 arr <- newArray_ ((0::Int),0)
462 d_arr <- castSTUArray arr
463 w0 <- readArray d_arr 0
470 arr <- newArray_ ((0::Int),1)
472 d_arr <- castSTUArray arr
473 w0 <- readArray d_arr 0
474 w1 <- readArray d_arr 1
475 return [w0 :: Word,w1]
479 arr <- newArray_ ((0::Int),0)
481 d_arr <- castSTUArray arr
482 w0 <- readArray d_arr 0
488 arr <- newArray_ ((0::Int),0)
490 i_arr <- castSTUArray arr
491 w0 <- readArray i_arr 0
497 arr <- newArray_ ((0::Int),0)
499 a_arr <- castSTUArray arr
500 w0 <- readArray a_arr 0
504 iNTERP_STACK_CHECK_THRESH = (INTERP_STACK_CHECK_THRESH :: Int)