{-# LANGUAGE CPP, MagicHash, ScopedTypeVariables #-} -- Get definitions for the structs, constants & config etc. #include "Rts.h" -- | -- Run-time info table support. This module provides support for -- creating and reading info tables /in the running program/. -- We use the RTS data structures directly via hsc2hs. -- module GHCi.InfoTable ( mkConInfoTable ) where import Prelude hiding (fail) -- See note [Why do we import Prelude here?] import Foreign import Foreign.C import GHC.Ptr import GHC.Exts import GHC.Exts.Heap import Data.ByteString (ByteString) import Control.Monad.Fail import qualified Data.ByteString as BS import GHC.Platform.Host (hostPlatformArch) import GHC.Platform.ArchOS -- NOTE: Must return a pointer acceptable for use in the header of a closure. -- If tables_next_to_code is enabled, then it must point the 'code' field. -- Otherwise, it should point to the start of the StgInfoTable. mkConInfoTable :: Bool -- TABLES_NEXT_TO_CODE -> Int -- ptr words -> Int -- non-ptr words -> Int -- constr tag -> Int -- pointer tag -> ByteString -- con desc -> IO (Ptr StgInfoTable) -- resulting info table is allocated with allocateExecPage(), and -- should be freed with freeExecPage(). mkConInfoTable tables_next_to_code ptr_words nonptr_words tag ptrtag con_desc = do let entry_addr = interpConstrEntry !! ptrtag code' <- if tables_next_to_code then Just <$> mkJumpToAddr entry_addr else pure Nothing let itbl = StgInfoTable { entry = if tables_next_to_code then Nothing else Just entry_addr, ptrs = fromIntegral ptr_words, nptrs = fromIntegral nonptr_words, tipe = CONSTR, srtlen = fromIntegral tag, code = code' } castFunPtrToPtr <$> newExecConItbl tables_next_to_code itbl con_desc -- ----------------------------------------------------------------------------- -- Building machine code fragments for a constructor's entry code funPtrToInt :: FunPtr a -> Int funPtrToInt (FunPtr a) = I## (addr2Int## a) mkJumpToAddr :: MonadFail m => EntryFunPtr-> m ItblCodes mkJumpToAddr a = case hostPlatformArch of ArchPPC -> pure $ -- We'll use r12, for no particular reason. -- 0xDEADBEEF stands for the address: -- 3D80DEAD lis r12,0xDEAD -- 618CBEEF ori r12,r12,0xBEEF -- 7D8903A6 mtctr r12 -- 4E800420 bctr let w32 = fromIntegral (funPtrToInt a) hi16 x = (x `shiftR` 16) .&. 0xFFFF lo16 x = x .&. 0xFFFF in Right [ 0x3D800000 .|. hi16 w32, 0x618C0000 .|. lo16 w32, 0x7D8903A6, 0x4E800420 ] ArchX86 -> pure $ -- Let the address to jump to be 0xWWXXYYZZ. -- Generate movl $0xWWXXYYZZ,%eax ; jmp *%eax -- which is -- B8 ZZ YY XX WW FF E0 let w32 = fromIntegral (funPtrToInt a) :: Word32 insnBytes :: [Word8] insnBytes = [0xB8, byte0 w32, byte1 w32, byte2 w32, byte3 w32, 0xFF, 0xE0] in Left insnBytes ArchX86_64 -> pure $ -- Generates: -- jmpq *.L1(%rip) -- .align 8 -- .L1: -- .quad -- -- which looks like: -- 8: ff 25 02 00 00 00 jmpq *0x2(%rip) # 10 -- with addr at 10. -- -- We need a full 64-bit pointer (we can't assume the info table is -- allocated in low memory). Assuming the info pointer is aligned to -- an 8-byte boundary, the addr will also be aligned. let w64 = fromIntegral (funPtrToInt a) :: Word64 insnBytes :: [Word8] insnBytes = [0xff, 0x25, 0x02, 0x00, 0x00, 0x00, 0x00, 0x00, byte0 w64, byte1 w64, byte2 w64, byte3 w64, byte4 w64, byte5 w64, byte6 w64, byte7 w64] in Left insnBytes ArchAlpha -> pure $ let w64 = fromIntegral (funPtrToInt a) :: Word64 in Right [ 0xc3800000 -- br at, .+4 , 0xa79c000c -- ldq at, 12(at) , 0x6bfc0000 -- jmp (at) # with zero hint -- oh well , 0x47ff041f -- nop , fromIntegral (w64 .&. 0x0000FFFF) , fromIntegral ((w64 `shiftR` 32) .&. 0x0000FFFF) ] ArchARM {} -> pure $ -- Generates Arm sequence, -- ldr r1, [pc, #0] -- bx r1 -- -- which looks like: -- 00000000 <.addr-0x8>: -- 0: 00109fe5 ldr r1, [pc] ; 8 <.addr> -- 4: 11ff2fe1 bx r1 let w32 = fromIntegral (funPtrToInt a) :: Word32 in Left [ 0x00, 0x10, 0x9f, 0xe5 , 0x11, 0xff, 0x2f, 0xe1 , byte0 w32, byte1 w32, byte2 w32, byte3 w32] ArchAArch64 {} -> pure $ -- Generates: -- -- ldr x1, label -- br x1 -- label: -- .quad -- -- which looks like: -- 0: 58000041 ldr x1,