Pass relocations to the elf generator
This commit is contained in:
parent
a66365eef4
commit
25728ddc4a
@ -140,33 +140,37 @@ namespace elna::riscv
|
|||||||
auto references = generate(intermediate_code_generator, table, writer1);
|
auto references = generate(intermediate_code_generator, table, writer1);
|
||||||
generate(intermediate_code_generator, table, writer2);
|
generate(intermediate_code_generator, table, writer2);
|
||||||
|
|
||||||
writer2->pipe.close();
|
|
||||||
child.wait();
|
|
||||||
|
|
||||||
syma.arrange_local_symbols();
|
syma.arrange_local_symbols();
|
||||||
|
|
||||||
for (auto& reference : references)
|
for (auto& reference : references)
|
||||||
{
|
{
|
||||||
ELFIO::Elf_Word relocated_symbol = lookup(syma, reference.name);
|
ELFIO::Elf_Word relocated_symbol = lookup(syma, reference.name);
|
||||||
|
auto reference_offset = boost::endian::native_to_big(static_cast<std::uint32_t>(reference.offset));
|
||||||
|
std::uint8_t address_type{ 0 };
|
||||||
|
|
||||||
switch (reference.target)
|
switch (reference.target)
|
||||||
{
|
{
|
||||||
case address_t::high20:
|
case address_t::high20:
|
||||||
rela.add_entry(reference.offset, relocated_symbol, 26 /* ELFIO::R_RISCV_HI20 */);
|
address_type = 26;
|
||||||
// rela.add_entry(reference.offset, relocated_symbol, 51 /* ELFIO::R_RISCV_RELAX */);
|
|
||||||
break;
|
break;
|
||||||
case address_t::lower12i:
|
case address_t::lower12i:
|
||||||
rela.add_entry(reference.offset, relocated_symbol, 27 /* ELFIO::R_RISCV_LO12_I */);
|
address_type = 27;
|
||||||
// rela.add_entry(reference.offset, relocated_symbol, 51 /* ELFIO::R_RISCV_RELAX */);
|
|
||||||
break;
|
break;
|
||||||
case address_t::text:
|
case address_t::text:
|
||||||
rela.add_entry(reference.offset, relocated_symbol, 18 /* ELFIO::R_RISCV_CALL */);
|
address_type = 18;
|
||||||
// rela.add_entry(reference.offset, relocated_symbol, 51 /* ELFIO::R_RISCV_RELAX */);
|
|
||||||
break;
|
break;
|
||||||
}
|
}
|
||||||
|
rela.add_entry(reference.offset, relocated_symbol, 18 /* ELFIO::R_RISCV_CALL */);
|
||||||
|
// rela.add_entry(reference.offset, relocated_symbol, 51 /* ELFIO::R_RISCV_RELAX */);
|
||||||
|
writer2->pipe.write_some(boost::asio::buffer(&address_type, 1));
|
||||||
|
writer2->pipe.write_some(boost::asio::buffer(reference.name.data(), reference.name.size() + 1));
|
||||||
|
writer2->pipe.write_some(boost::asio::buffer(&reference_offset, 4));
|
||||||
}
|
}
|
||||||
|
|
||||||
// Create ELF object file
|
// Create ELF object file
|
||||||
|
writer2->pipe.close();
|
||||||
|
child.wait();
|
||||||
|
|
||||||
writer.save(out_file);
|
writer.save(out_file);
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
@ -27,6 +27,7 @@ common warnings
|
|||||||
ExplicitForAll,
|
ExplicitForAll,
|
||||||
LambdaCase,
|
LambdaCase,
|
||||||
OverloadedStrings,
|
OverloadedStrings,
|
||||||
|
DuplicateRecordFields,
|
||||||
RecordWildCards
|
RecordWildCards
|
||||||
default-language: GHC2021
|
default-language: GHC2021
|
||||||
|
|
||||||
|
@ -5,14 +5,18 @@ module Language.Elna.Object.Elf
|
|||||||
, Elf32_Word
|
, Elf32_Word
|
||||||
, Elf32_Sword
|
, Elf32_Sword
|
||||||
, Elf32_Ehdr(..)
|
, Elf32_Ehdr(..)
|
||||||
|
, Elf32_Rel(..)
|
||||||
|
, Elf32_Rela(..)
|
||||||
, Elf32_Shdr(..)
|
, Elf32_Shdr(..)
|
||||||
, Elf32_Sym(..)
|
, Elf32_Sym(..)
|
||||||
, ElfIdentification(..)
|
, ElfIdentification(..)
|
||||||
, ElfMachine(..)
|
, ElfMachine(..)
|
||||||
, ElfVersion(..)
|
, ElfVersion(..)
|
||||||
, ElfType(..)
|
|
||||||
, ElfClass(..)
|
, ElfClass(..)
|
||||||
, ElfData(..)
|
, ElfData(..)
|
||||||
|
, ElfType(..)
|
||||||
|
, ElfSymbolBinding(..)
|
||||||
|
, ElfSymbolType(..)
|
||||||
, elf32Addr
|
, elf32Addr
|
||||||
, elf32Half
|
, elf32Half
|
||||||
, elf32Off
|
, elf32Off
|
||||||
@ -20,10 +24,15 @@ module Language.Elna.Object.Elf
|
|||||||
, elf32Sword
|
, elf32Sword
|
||||||
, elf32Word
|
, elf32Word
|
||||||
, elf32Ehdr
|
, elf32Ehdr
|
||||||
|
, elf32Rel
|
||||||
|
, elf32Rela
|
||||||
, elf32Sym
|
, elf32Sym
|
||||||
, elfIdentification
|
, elfIdentification
|
||||||
|
, rInfo
|
||||||
|
, stInfo
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.Bits (Bits(..))
|
||||||
import qualified Data.ByteString.Builder as ByteString.Builder
|
import qualified Data.ByteString.Builder as ByteString.Builder
|
||||||
import Data.Int (Int32)
|
import Data.Int (Int32)
|
||||||
import Data.Word (Word8, Word16, Word32)
|
import Data.Word (Word8, Word16, Word32)
|
||||||
@ -118,7 +127,8 @@ data Elf32_Shdr = Elf32_Shdr
|
|||||||
} deriving Eq
|
} deriving Eq
|
||||||
|
|
||||||
data ElfMachine
|
data ElfMachine
|
||||||
= EM_NONE -- ^ No machine.
|
= ElfMachine Elf32_Half
|
||||||
|
| EM_NONE -- ^ No machine.
|
||||||
| EM_M32 -- ^ AT&T WE 32100.
|
| EM_M32 -- ^ AT&T WE 32100.
|
||||||
| EM_SPARC -- ^ SPARC.
|
| EM_SPARC -- ^ SPARC.
|
||||||
| EM_386 -- ^ Intel Architecture.
|
| EM_386 -- ^ Intel Architecture.
|
||||||
@ -140,7 +150,7 @@ instance Enum ElfMachine
|
|||||||
toEnum 7 = EM_860
|
toEnum 7 = EM_860
|
||||||
toEnum 8 = EM_MIPS
|
toEnum 8 = EM_MIPS
|
||||||
toEnum 10 = EM_MIPS_RS4_BE
|
toEnum 10 = EM_MIPS_RS4_BE
|
||||||
toEnum _ = error "Unknown Elf machine"
|
toEnum x = ElfMachine $ fromIntegral x
|
||||||
fromEnum EM_NONE = 0
|
fromEnum EM_NONE = 0
|
||||||
fromEnum EM_M32 = 1
|
fromEnum EM_M32 = 1
|
||||||
fromEnum EM_SPARC = 2
|
fromEnum EM_SPARC = 2
|
||||||
@ -150,9 +160,11 @@ instance Enum ElfMachine
|
|||||||
fromEnum EM_860 = 7
|
fromEnum EM_860 = 7
|
||||||
fromEnum EM_MIPS = 8
|
fromEnum EM_MIPS = 8
|
||||||
fromEnum EM_MIPS_RS4_BE = 10
|
fromEnum EM_MIPS_RS4_BE = 10
|
||||||
|
fromEnum (ElfMachine x) = fromIntegral x
|
||||||
|
|
||||||
data ElfVersion
|
data ElfVersion
|
||||||
= EV_NONE -- ^ Invalid versionn.
|
= ElfVersion Elf32_Word
|
||||||
|
| EV_NONE -- ^ Invalid versionn.
|
||||||
| EV_CURRENT -- ^ Current version.
|
| EV_CURRENT -- ^ Current version.
|
||||||
deriving Eq
|
deriving Eq
|
||||||
|
|
||||||
@ -160,12 +172,14 @@ instance Enum ElfVersion
|
|||||||
where
|
where
|
||||||
toEnum 0 = EV_NONE
|
toEnum 0 = EV_NONE
|
||||||
toEnum 1 = EV_CURRENT
|
toEnum 1 = EV_CURRENT
|
||||||
toEnum _ = error "Unknown Elf version"
|
toEnum x = ElfVersion $ fromIntegral x
|
||||||
fromEnum EV_NONE = 0
|
fromEnum EV_NONE = 0
|
||||||
fromEnum EV_CURRENT = 1
|
fromEnum EV_CURRENT = 1
|
||||||
|
fromEnum (ElfVersion x) = fromIntegral x
|
||||||
|
|
||||||
data ElfType
|
data ElfType
|
||||||
= ET_NONE -- ^ No file type.
|
= ElfType Elf32_Half
|
||||||
|
| ET_NONE -- ^ No file type.
|
||||||
| ET_REL -- ^ Relocatable file.
|
| ET_REL -- ^ Relocatable file.
|
||||||
| ET_EXEC -- ^ Executable file.
|
| ET_EXEC -- ^ Executable file.
|
||||||
| ET_DYN -- ^ Shared object file.
|
| ET_DYN -- ^ Shared object file.
|
||||||
@ -183,7 +197,7 @@ instance Enum ElfType
|
|||||||
toEnum 4 = ET_CORE
|
toEnum 4 = ET_CORE
|
||||||
toEnum 0xff00 = ET_LOPROC
|
toEnum 0xff00 = ET_LOPROC
|
||||||
toEnum 0xffff = ET_HIPROC
|
toEnum 0xffff = ET_HIPROC
|
||||||
toEnum _ = error "Unknown Elf type"
|
toEnum x = ElfType $ fromIntegral x
|
||||||
fromEnum ET_NONE = 0
|
fromEnum ET_NONE = 0
|
||||||
fromEnum ET_REL = 1
|
fromEnum ET_REL = 1
|
||||||
fromEnum ET_EXEC = 2
|
fromEnum ET_EXEC = 2
|
||||||
@ -191,6 +205,7 @@ instance Enum ElfType
|
|||||||
fromEnum ET_CORE = 4
|
fromEnum ET_CORE = 4
|
||||||
fromEnum ET_LOPROC = 0xff00
|
fromEnum ET_LOPROC = 0xff00
|
||||||
fromEnum ET_HIPROC = 0xffff
|
fromEnum ET_HIPROC = 0xffff
|
||||||
|
fromEnum (ElfType x) = fromIntegral x
|
||||||
|
|
||||||
data Elf32_Sym = Elf32_Sym
|
data Elf32_Sym = Elf32_Sym
|
||||||
{ st_name :: Elf32_Word
|
{ st_name :: Elf32_Word
|
||||||
@ -201,7 +216,72 @@ data Elf32_Sym = Elf32_Sym
|
|||||||
, st_shndx :: Elf32_Half
|
, st_shndx :: Elf32_Half
|
||||||
} deriving Eq
|
} deriving Eq
|
||||||
|
|
||||||
-- * Help types.
|
data ElfSymbolBinding
|
||||||
|
= ElfSymbolBinding Word8
|
||||||
|
| STB_LOCAL
|
||||||
|
| STB_GLOBAL
|
||||||
|
| STB_WEAK
|
||||||
|
| STB_LOPROC
|
||||||
|
| STB_HIPROC
|
||||||
|
deriving Eq
|
||||||
|
|
||||||
|
instance Enum ElfSymbolBinding
|
||||||
|
where
|
||||||
|
toEnum 0 = STB_LOCAL
|
||||||
|
toEnum 1 = STB_GLOBAL
|
||||||
|
toEnum 2 = STB_WEAK
|
||||||
|
toEnum 13 = STB_LOPROC
|
||||||
|
toEnum 15 = STB_HIPROC
|
||||||
|
toEnum x = ElfSymbolBinding $ fromIntegral x
|
||||||
|
fromEnum STB_LOCAL = 0
|
||||||
|
fromEnum STB_GLOBAL = 1
|
||||||
|
fromEnum STB_WEAK = 2
|
||||||
|
fromEnum STB_LOPROC = 13
|
||||||
|
fromEnum STB_HIPROC = 15
|
||||||
|
fromEnum (ElfSymbolBinding x) = fromIntegral x
|
||||||
|
|
||||||
|
data ElfSymbolType
|
||||||
|
= ElfSymbolType Word8
|
||||||
|
| STT_NOTYPE
|
||||||
|
| STT_OBJECT
|
||||||
|
| STT_FUNC
|
||||||
|
| STT_SECTION
|
||||||
|
| STT_FILE
|
||||||
|
| STT_LOPROC
|
||||||
|
| STT_HIPROC
|
||||||
|
deriving Eq
|
||||||
|
|
||||||
|
instance Enum ElfSymbolType
|
||||||
|
where
|
||||||
|
toEnum 0 = STT_NOTYPE
|
||||||
|
toEnum 1 = STT_OBJECT
|
||||||
|
toEnum 2 = STT_FUNC
|
||||||
|
toEnum 3 = STT_SECTION
|
||||||
|
toEnum 4 = STT_FILE
|
||||||
|
toEnum 13 = STT_LOPROC
|
||||||
|
toEnum 15 = STT_HIPROC
|
||||||
|
toEnum x = ElfSymbolType $ fromIntegral x
|
||||||
|
fromEnum STT_NOTYPE = 0
|
||||||
|
fromEnum STT_OBJECT = 1
|
||||||
|
fromEnum STT_FUNC = 2
|
||||||
|
fromEnum STT_SECTION = 3
|
||||||
|
fromEnum STT_FILE = 4
|
||||||
|
fromEnum STT_LOPROC = 13
|
||||||
|
fromEnum STT_HIPROC = 15
|
||||||
|
fromEnum (ElfSymbolType x) = fromIntegral x
|
||||||
|
|
||||||
|
data Elf32_Rel = Elf32_Rel
|
||||||
|
{ r_offset :: Elf32_Addr
|
||||||
|
, r_info :: Elf32_Word
|
||||||
|
} deriving Eq
|
||||||
|
|
||||||
|
data Elf32_Rela = Elf32_Rela
|
||||||
|
{ r_offset :: Elf32_Addr
|
||||||
|
, r_info :: Elf32_Word
|
||||||
|
, r_addend :: Elf32_Sword
|
||||||
|
} deriving Eq
|
||||||
|
|
||||||
|
-- * Help types and functions.
|
||||||
|
|
||||||
data ByteOrder = LSB | MSB
|
data ByteOrder = LSB | MSB
|
||||||
deriving Eq
|
deriving Eq
|
||||||
@ -217,6 +297,9 @@ instance Show ElfEncodingError
|
|||||||
show (ElfUnsupportedClassError class') =
|
show (ElfUnsupportedClassError class') =
|
||||||
concat ["Elf class \"", show class', "\" is not supported."]
|
concat ["Elf class \"", show class', "\" is not supported."]
|
||||||
|
|
||||||
|
fromIntegralEnum :: (Enum a, Num b) => a -> b
|
||||||
|
fromIntegralEnum = fromIntegral . fromEnum
|
||||||
|
|
||||||
-- * Encoding functions.
|
-- * Encoding functions.
|
||||||
|
|
||||||
elf32Addr :: ByteOrder -> Elf32_Addr -> ByteString.Builder.Builder
|
elf32Addr :: ByteOrder -> Elf32_Addr -> ByteString.Builder.Builder
|
||||||
@ -243,9 +326,9 @@ elfIdentification :: ElfIdentification -> ByteString.Builder.Builder
|
|||||||
elfIdentification (ElfIdentification elfClass elfData)
|
elfIdentification (ElfIdentification elfClass elfData)
|
||||||
= ByteString.Builder.word8 0x7f
|
= ByteString.Builder.word8 0x7f
|
||||||
<> ByteString.Builder.string7 "ELF"
|
<> ByteString.Builder.string7 "ELF"
|
||||||
<> ByteString.Builder.word8 (fromIntegral $ fromEnum elfClass)
|
<> ByteString.Builder.word8 (fromIntegralEnum elfClass)
|
||||||
<> ByteString.Builder.word8 (fromIntegral $ fromEnum elfData)
|
<> ByteString.Builder.word8 (fromIntegralEnum elfData)
|
||||||
<> ByteString.Builder.word8 (fromIntegral $ fromEnum EV_CURRENT)
|
<> ByteString.Builder.word8 (fromIntegralEnum EV_CURRENT)
|
||||||
<> ByteString.Builder.byteString (ByteString.replicate 9 0)
|
<> ByteString.Builder.byteString (ByteString.replicate 9 0)
|
||||||
|
|
||||||
elf32Ehdr :: Elf32_Ehdr -> Either ElfEncodingError ByteString.Builder.Builder
|
elf32Ehdr :: Elf32_Ehdr -> Either ElfEncodingError ByteString.Builder.Builder
|
||||||
@ -253,9 +336,9 @@ elf32Ehdr Elf32_Ehdr{..} = encode <$> byteOrder
|
|||||||
where
|
where
|
||||||
encode byteOrder'
|
encode byteOrder'
|
||||||
= elfIdentification e_ident
|
= elfIdentification e_ident
|
||||||
<> elf32Half byteOrder' (fromIntegral $ fromEnum e_type)
|
<> elf32Half byteOrder' (fromIntegralEnum e_type)
|
||||||
<> elf32Half byteOrder' (fromIntegral $ fromEnum e_machine)
|
<> elf32Half byteOrder' (fromIntegralEnum e_machine)
|
||||||
<> elf32Word byteOrder' (fromIntegral $ fromEnum e_version)
|
<> elf32Word byteOrder' (fromIntegralEnum e_version)
|
||||||
<> elf32Addr byteOrder' e_entry
|
<> elf32Addr byteOrder' e_entry
|
||||||
<> elf32Off byteOrder' e_phoff
|
<> elf32Off byteOrder' e_phoff
|
||||||
<> elf32Off byteOrder' e_shoff
|
<> elf32Off byteOrder' e_shoff
|
||||||
@ -294,3 +377,22 @@ elf32Sym byteOrder Elf32_Sym{..}
|
|||||||
<> ByteString.Builder.word8 st_info
|
<> ByteString.Builder.word8 st_info
|
||||||
<> ByteString.Builder.word8 st_other
|
<> ByteString.Builder.word8 st_other
|
||||||
<> elf32Half byteOrder st_shndx
|
<> elf32Half byteOrder st_shndx
|
||||||
|
|
||||||
|
elf32Rel :: ByteOrder -> Elf32_Rel -> ByteString.Builder.Builder
|
||||||
|
elf32Rel byteOrder Elf32_Rel{..}
|
||||||
|
= elf32Addr byteOrder r_offset
|
||||||
|
<> elf32Word byteOrder r_info
|
||||||
|
|
||||||
|
elf32Rela :: ByteOrder -> Elf32_Rela -> ByteString.Builder.Builder
|
||||||
|
elf32Rela byteOrder Elf32_Rela{..}
|
||||||
|
= elf32Addr byteOrder r_offset
|
||||||
|
<> elf32Word byteOrder r_info
|
||||||
|
<> elf32Sword byteOrder r_addend
|
||||||
|
|
||||||
|
stInfo :: ElfSymbolBinding -> ElfSymbolType -> Word8
|
||||||
|
stInfo binding type' = fromIntegralEnum binding `shiftL` 4
|
||||||
|
.|. (fromIntegralEnum type' .&. 0xf)
|
||||||
|
|
||||||
|
rInfo :: Elf32_Word -> Word8 -> Elf32_Word
|
||||||
|
rInfo symbol type' = symbol `shiftL` 8
|
||||||
|
.|. fromIntegralEnum type'
|
||||||
|
67
src/Main.hs
67
src/Main.hs
@ -2,16 +2,25 @@ module Main
|
|||||||
( main
|
( main
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.Elna.Object.Elf (Elf32_Sym(..))
|
import Language.Elna.Object.Elf
|
||||||
|
( Elf32_Addr
|
||||||
|
, Elf32_Half
|
||||||
|
, Elf32_Sym(..)
|
||||||
|
, ElfSymbolType(..)
|
||||||
|
, ElfSymbolBinding(..)
|
||||||
|
, stInfo
|
||||||
|
)
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import qualified Data.ByteString as ByteString
|
import qualified Data.ByteString as ByteString
|
||||||
import Data.Vector (Vector)
|
import Data.Vector (Vector)
|
||||||
import qualified Data.Vector as Vector
|
import qualified Data.Vector as Vector
|
||||||
import Data.Bits (Bits(..))
|
import Data.Bits (Bits(..))
|
||||||
|
import Data.Word (Word8)
|
||||||
|
|
||||||
data Chunk
|
data Chunk
|
||||||
= ExternSymbolChunk ByteString
|
= ExternSymbolChunk ByteString
|
||||||
| SymbolDefinitionChunk ByteString ByteString
|
| SymbolDefinitionChunk ByteString ByteString
|
||||||
|
| RelocationChunk Word8 ByteString Elf32_Addr
|
||||||
deriving Eq
|
deriving Eq
|
||||||
|
|
||||||
instance Show Chunk
|
instance Show Chunk
|
||||||
@ -25,13 +34,33 @@ instance Show Chunk
|
|||||||
<> " (Size: "
|
<> " (Size: "
|
||||||
<> show (ByteString.length chunk)
|
<> show (ByteString.length chunk)
|
||||||
<> ")"
|
<> ")"
|
||||||
|
show (RelocationChunk type' symbolName offset)
|
||||||
|
= "RelocationChunk (Type: "
|
||||||
|
<> show type'
|
||||||
|
<> ", symbol: " <> show symbolName
|
||||||
|
<> ", offset: " <> show offset <> ")"
|
||||||
|
|
||||||
splitContents :: [Chunk] -> ByteString -> [Chunk]
|
splitContents :: [Chunk] -> ByteString -> Maybe [Chunk]
|
||||||
splitContents accumulator remaining
|
splitContents accumulator remaining
|
||||||
| ByteString.null remaining = accumulator
|
| ByteString.null remaining = Just accumulator
|
||||||
| otherwise =
|
| Just (firstByte, tailBytes) <- ByteString.uncons remaining
|
||||||
|
, firstByte < 28 =
|
||||||
let (label, withoutLabel) = ByteString.drop 1
|
let (label, withoutLabel) = ByteString.drop 1
|
||||||
<$> ByteString.break (== 0) remaining
|
<$> ByteString.break (== 0) tailBytes
|
||||||
|
(rawSize, chunkAndRest) = ByteString.splitAt 4 withoutLabel
|
||||||
|
in case ByteString.unpack rawSize of
|
||||||
|
[x, y, t, u] ->
|
||||||
|
let convertedOffset :: Elf32_Addr
|
||||||
|
convertedOffset
|
||||||
|
= fromIntegral x `shiftL` 24
|
||||||
|
.|. fromIntegral y `shiftL` 16
|
||||||
|
.|. fromIntegral t `shiftL` 8
|
||||||
|
.|. fromIntegral u
|
||||||
|
in splitContents (RelocationChunk firstByte label convertedOffset : accumulator) chunkAndRest
|
||||||
|
_ -> Nothing
|
||||||
|
| Just nullPosition <- ByteString.elemIndex 0 remaining =
|
||||||
|
let (label, withoutLabel) =
|
||||||
|
ByteString.splitAt (succ nullPosition) remaining
|
||||||
(rawSize, chunkAndRest) = ByteString.splitAt 2 withoutLabel
|
(rawSize, chunkAndRest) = ByteString.splitAt 2 withoutLabel
|
||||||
in case ByteString.unpack rawSize of
|
in case ByteString.unpack rawSize of
|
||||||
[0, 0] -> splitContents (ExternSymbolChunk label : accumulator) chunkAndRest
|
[0, 0] -> splitContents (ExternSymbolChunk label : accumulator) chunkAndRest
|
||||||
@ -39,23 +68,35 @@ splitContents accumulator remaining
|
|||||||
let chunkSize = shiftL (fromIntegral x) 8 .|. fromIntegral y
|
let chunkSize = shiftL (fromIntegral x) 8 .|. fromIntegral y
|
||||||
(chunk, remaining') = ByteString.splitAt chunkSize chunkAndRest
|
(chunk, remaining') = ByteString.splitAt chunkSize chunkAndRest
|
||||||
in splitContents (SymbolDefinitionChunk label chunk : accumulator) remaining'
|
in splitContents (SymbolDefinitionChunk label chunk : accumulator) remaining'
|
||||||
_ -> ExternSymbolChunk label : accumulator
|
_ -> Nothing
|
||||||
|
| otherwise = Nothing
|
||||||
|
|
||||||
go
|
go
|
||||||
:: Chunk
|
:: Elf32_Half
|
||||||
-> (Vector Elf32_Sym, Vector ByteString)
|
-> Chunk
|
||||||
-> (Vector Elf32_Sym, Vector ByteString)
|
-> (Vector Elf32_Sym, Vector ByteString, ByteString)
|
||||||
go (ExternSymbolChunk symbolName) (symbolEntries, stringTable) =
|
-> (Vector Elf32_Sym, Vector ByteString, ByteString)
|
||||||
|
go _ (ExternSymbolChunk symbolName) (symbolEntries, stringTable, symbolTable) =
|
||||||
let symbolEntry = Elf32_Sym
|
let symbolEntry = Elf32_Sym
|
||||||
{ st_name = fromIntegral $ Vector.foldr ((+) . ByteString.length) 0 stringTable
|
{ st_name = fromIntegral $ Vector.foldr ((+) . ByteString.length) 0 stringTable
|
||||||
, st_value = 0
|
, st_value = 0
|
||||||
, st_size = 0
|
, st_size = 0
|
||||||
, st_info = shiftL 1 4 -- STB_GLOBAL and STT_NOTYPE
|
, st_info = stInfo STB_GLOBAL STT_NOTYPE
|
||||||
, st_other = 0
|
, st_other = 0
|
||||||
, st_shndx = 0 -- SHN_UNDEF
|
, st_shndx = 0 -- SHN_UNDEF
|
||||||
}
|
}
|
||||||
in (Vector.snoc symbolEntries symbolEntry, Vector.snoc stringTable symbolName)
|
in (Vector.snoc symbolEntries symbolEntry, Vector.snoc stringTable symbolName, symbolTable)
|
||||||
go (SymbolDefinitionChunk _ _) _acc = undefined
|
go symbolTableIndex (SymbolDefinitionChunk symbolName symbolValue) (symbolEntries, stringTable, symbolTable) =
|
||||||
|
let symbolEntry = Elf32_Sym
|
||||||
|
{ st_name = fromIntegral $ Vector.foldr ((+) . ByteString.length) 0 stringTable
|
||||||
|
, st_value = fromIntegral $ ByteString.length symbolTable
|
||||||
|
, st_size = fromIntegral $ ByteString.length symbolValue
|
||||||
|
, st_info = stInfo STB_GLOBAL STT_FUNC
|
||||||
|
, st_other = 0
|
||||||
|
, st_shndx = symbolTableIndex
|
||||||
|
}
|
||||||
|
in (Vector.snoc symbolEntries symbolEntry, Vector.snoc stringTable symbolName, symbolTable <> symbolValue)
|
||||||
|
go _ _ accumulator = accumulator
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
|
Loading…
x
Reference in New Issue
Block a user