2024-09-08 02:08:13 +02:00
|
|
|
-- | Writer assembler to an object file.
|
|
|
|
module Language.Elna.PrinterWriter
|
|
|
|
( riscv32Elf
|
|
|
|
) where
|
|
|
|
|
2024-09-08 22:53:07 +02:00
|
|
|
import Data.Word (Word8)
|
2024-09-08 02:08:13 +02:00
|
|
|
import Data.ByteString (ByteString)
|
|
|
|
import qualified Data.ByteString as ByteString
|
|
|
|
import qualified Data.ByteString.Builder as ByteString.Builder
|
|
|
|
import qualified Data.ByteString.Lazy as LazyByteString
|
|
|
|
import Data.Vector (Vector)
|
|
|
|
import qualified Data.Vector as Vector
|
|
|
|
import Language.Elna.Object.Elf
|
|
|
|
( ByteOrder(..)
|
2024-09-08 22:53:07 +02:00
|
|
|
, Elf32_Addr
|
2024-09-08 02:08:13 +02:00
|
|
|
, Elf32_Ehdr(..)
|
|
|
|
, Elf32_Half
|
2024-09-12 02:21:48 +02:00
|
|
|
, Elf32_Word
|
2024-09-08 02:08:13 +02:00
|
|
|
, Elf32_Sym(..)
|
|
|
|
, ElfMachine(..)
|
|
|
|
, ElfType(..)
|
|
|
|
, ElfVersion(..)
|
|
|
|
, ElfIdentification(..)
|
|
|
|
, ElfClass(..)
|
|
|
|
, ElfData(..)
|
|
|
|
, Elf32_Shdr(..)
|
|
|
|
, ElfSectionType(..)
|
|
|
|
, ElfSymbolBinding(..)
|
|
|
|
, ElfSymbolType(..)
|
2024-09-12 02:21:48 +02:00
|
|
|
, Elf32_Rel(..)
|
|
|
|
, ElfWriter(..)
|
|
|
|
, ElfHeaderResult(..)
|
2024-09-08 02:08:13 +02:00
|
|
|
, elf32Sym
|
|
|
|
, elfHeaderSize
|
|
|
|
, elfSectionsSize
|
|
|
|
, stInfo
|
2024-09-08 22:53:07 +02:00
|
|
|
, rInfo
|
|
|
|
, elf32Rel
|
|
|
|
, shfInfoLink
|
2024-09-10 02:03:20 +02:00
|
|
|
, addSectionHeader
|
2024-09-08 02:08:13 +02:00
|
|
|
)
|
|
|
|
import System.IO (Handle)
|
|
|
|
import qualified Language.Elna.Architecture.RiscV as RiscV
|
2024-09-08 22:53:07 +02:00
|
|
|
import qualified Data.Text.Encoding as Text.Encoding
|
2024-09-10 02:03:20 +02:00
|
|
|
import Control.Monad.IO.Class (MonadIO(..))
|
|
|
|
import Control.Monad.Trans.State (get)
|
2024-09-08 02:08:13 +02:00
|
|
|
|
2024-09-08 22:53:07 +02:00
|
|
|
data UnresolvedRelocation = UnresolvedRelocation ByteString Elf32_Addr Word8
|
2024-09-12 02:21:48 +02:00
|
|
|
data UnresolvedRelocations = UnresolvedRelocations (Vector UnresolvedRelocation) Elf32_Word
|
2024-09-08 02:08:13 +02:00
|
|
|
|
2024-09-12 02:21:48 +02:00
|
|
|
riscv32Elf :: Vector RiscV.Instruction -> Handle -> ElfWriter Elf32_Ehdr
|
2024-09-10 02:03:20 +02:00
|
|
|
riscv32Elf code objectHandle = text
|
2024-09-12 02:21:48 +02:00
|
|
|
>>= uncurry symrel
|
|
|
|
>>= strtab
|
|
|
|
>> shstrtab
|
|
|
|
>>= riscv32Header
|
2024-09-08 02:08:13 +02:00
|
|
|
where
|
2024-09-12 02:21:48 +02:00
|
|
|
shstrtab :: ElfWriter Elf32_Half
|
|
|
|
shstrtab = do
|
|
|
|
ElfHeaderResult{..} <- ElfWriter get
|
|
|
|
let stringTable = sectionNames <> ".shstrtab\0"
|
|
|
|
nextHeader = Elf32_Shdr
|
|
|
|
{ sh_type = SHT_STRTAB
|
|
|
|
, sh_size = fromIntegral $ ByteString.length stringTable
|
|
|
|
, sh_offset = elfSectionsSize sectionHeaders
|
|
|
|
, sh_name = fromIntegral $ ByteString.length sectionNames
|
|
|
|
, sh_link = 0
|
|
|
|
, sh_info = 0
|
|
|
|
, sh_flags = 0
|
|
|
|
, sh_entsize = 0
|
|
|
|
, sh_addralign = 1
|
|
|
|
, sh_addr = 0
|
|
|
|
}
|
|
|
|
liftIO $ ByteString.hPut objectHandle stringTable
|
|
|
|
addSectionHeader ".shstrtab" nextHeader
|
|
|
|
pure $ fromIntegral $ Vector.length sectionHeaders
|
|
|
|
riscv32Header :: Elf32_Half -> ElfWriter Elf32_Ehdr
|
|
|
|
riscv32Header shstrndx = do
|
|
|
|
ElfHeaderResult{..} <- ElfWriter get
|
|
|
|
pure $ Elf32_Ehdr
|
|
|
|
{ e_version = EV_CURRENT
|
|
|
|
, e_type = ET_REL
|
|
|
|
, e_shstrndx = shstrndx
|
|
|
|
, e_shoff = elfSectionsSize sectionHeaders
|
|
|
|
, e_shnum = fromIntegral (Vector.length sectionHeaders)
|
|
|
|
, e_shentsize = 40
|
|
|
|
, e_phoff = 0
|
|
|
|
, e_phnum = 0
|
|
|
|
, e_phentsize = 32
|
|
|
|
, e_machine = EM_RISCV
|
|
|
|
, e_ident = ElfIdentification ELFCLASS32 ELFDATA2LSB
|
|
|
|
, e_flags = 0x4 -- EF_RISCV_FLOAT_ABI_DOUBLE
|
|
|
|
, e_entry = 0
|
|
|
|
, e_ehsize = fromIntegral elfHeaderSize
|
|
|
|
}
|
2024-09-08 22:53:07 +02:00
|
|
|
takeStringZ stringTable Elf32_Sym{ st_name }
|
|
|
|
= ByteString.takeWhile (/= 0)
|
|
|
|
$ ByteString.drop (fromIntegral st_name) stringTable
|
|
|
|
resolveRelocation (ElfHeaderResult stringTable entries) unresolvedRelocation
|
|
|
|
| UnresolvedRelocation symbolName offset type' <- unresolvedRelocation
|
|
|
|
, Just entry <- Vector.findIndex ((== symbolName) . takeStringZ stringTable) entries =
|
|
|
|
Right $ Elf32_Rel
|
|
|
|
{ r_offset = offset
|
|
|
|
, r_info = rInfo (fromIntegral entry) type'
|
2024-09-08 02:08:13 +02:00
|
|
|
}
|
2024-09-08 22:53:07 +02:00
|
|
|
| otherwise = Left unresolvedRelocation
|
2024-09-12 02:21:48 +02:00
|
|
|
symtab entries = do
|
2024-09-10 02:03:20 +02:00
|
|
|
ElfHeaderResult{..} <- ElfWriter get
|
2024-09-08 22:53:07 +02:00
|
|
|
let encodedSymbols = LazyByteString.toStrict
|
2024-09-08 02:08:13 +02:00
|
|
|
$ ByteString.Builder.toLazyByteString
|
|
|
|
$ foldMap (elf32Sym LSB) entries
|
2024-09-08 22:53:07 +02:00
|
|
|
symHeader = Elf32_Shdr
|
2024-09-08 02:08:13 +02:00
|
|
|
{ sh_type = SHT_SYMTAB
|
2024-09-08 22:53:07 +02:00
|
|
|
, sh_size = fromIntegral $ ByteString.length encodedSymbols
|
2024-09-10 02:03:20 +02:00
|
|
|
, sh_offset = elfSectionsSize sectionHeaders
|
2024-09-12 02:21:48 +02:00
|
|
|
, sh_name = fromIntegral $ ByteString.length sectionNames
|
2024-09-10 02:03:20 +02:00
|
|
|
, sh_link = fromIntegral $ Vector.length sectionHeaders + 2
|
2024-09-08 02:08:13 +02:00
|
|
|
, sh_info = 1
|
|
|
|
, sh_flags = 0
|
|
|
|
, sh_entsize = 16
|
2024-09-12 02:21:48 +02:00
|
|
|
, sh_addralign = 4
|
2024-09-08 02:08:13 +02:00
|
|
|
, sh_addr = 0
|
|
|
|
}
|
2024-09-10 02:03:20 +02:00
|
|
|
liftIO $ ByteString.hPut objectHandle encodedSymbols
|
2024-09-12 02:21:48 +02:00
|
|
|
addSectionHeader ".symtab" symHeader
|
|
|
|
pure $ fromIntegral $ Vector.length sectionHeaders
|
|
|
|
symrel symbols relocations = do
|
|
|
|
let UnresolvedRelocations relocationList index = relocations
|
|
|
|
ElfHeaderResult stringTable entries = symbols
|
|
|
|
|
|
|
|
sectionHeadersLength <- symtab entries
|
|
|
|
ElfHeaderResult{..} <- ElfWriter get
|
|
|
|
|
|
|
|
let encodedRelocations = LazyByteString.toStrict
|
2024-09-08 22:53:07 +02:00
|
|
|
$ ByteString.Builder.toLazyByteString
|
2024-09-12 02:21:48 +02:00
|
|
|
$ Vector.foldMap (either (const mempty) (elf32Rel LSB))
|
|
|
|
$ resolveRelocation symbols <$> relocationList
|
2024-09-08 22:53:07 +02:00
|
|
|
relHeader = Elf32_Shdr
|
|
|
|
{ sh_type = SHT_REL
|
|
|
|
, sh_size = fromIntegral $ ByteString.length encodedRelocations
|
2024-09-12 02:21:48 +02:00
|
|
|
, sh_offset = elfSectionsSize sectionHeaders
|
|
|
|
, sh_name = fromIntegral $ ByteString.length sectionNames
|
|
|
|
, sh_link = sectionHeadersLength
|
|
|
|
, sh_info = index
|
2024-09-08 22:53:07 +02:00
|
|
|
, sh_flags = shfInfoLink
|
|
|
|
, sh_entsize = 8
|
2024-09-12 02:21:48 +02:00
|
|
|
, sh_addralign = 4
|
2024-09-08 22:53:07 +02:00
|
|
|
, sh_addr = 0
|
|
|
|
}
|
2024-09-10 02:03:20 +02:00
|
|
|
liftIO $ ByteString.hPut objectHandle encodedRelocations
|
2024-09-12 02:21:48 +02:00
|
|
|
addSectionHeader ".rel.text" relHeader
|
|
|
|
pure stringTable
|
|
|
|
strtab stringTable = do
|
|
|
|
ElfHeaderResult{..} <- ElfWriter get
|
2024-09-08 22:53:07 +02:00
|
|
|
let strHeader = Elf32_Shdr
|
|
|
|
{ sh_type = SHT_STRTAB
|
|
|
|
, sh_size = fromIntegral $ ByteString.length stringTable
|
2024-09-12 02:21:48 +02:00
|
|
|
, sh_offset = elfSectionsSize sectionHeaders
|
|
|
|
, sh_name = fromIntegral $ ByteString.length sectionNames
|
2024-09-08 22:53:07 +02:00
|
|
|
, sh_link = 0
|
|
|
|
, sh_info = 0
|
|
|
|
, sh_flags = 0
|
|
|
|
, sh_entsize = 0
|
2024-09-12 02:21:48 +02:00
|
|
|
, sh_addralign = 1
|
2024-09-08 22:53:07 +02:00
|
|
|
, sh_addr = 0
|
|
|
|
}
|
2024-09-10 02:03:20 +02:00
|
|
|
liftIO $ ByteString.hPut objectHandle stringTable
|
|
|
|
addSectionHeader ".strtab" strHeader
|
|
|
|
text = do
|
|
|
|
ElfHeaderResult{..} <- ElfWriter get
|
|
|
|
let textTabIndex = fromIntegral $ Vector.length sectionHeaders
|
2024-09-08 22:53:07 +02:00
|
|
|
initialHeaders = ElfHeaderResult "\0"
|
|
|
|
$ Vector.singleton
|
|
|
|
$ Elf32_Sym
|
|
|
|
{ st_value = 0
|
|
|
|
, st_size = 0
|
|
|
|
, st_shndx = 0
|
|
|
|
, st_other = 0
|
|
|
|
, st_name = 0
|
|
|
|
, st_info = 0
|
|
|
|
}
|
|
|
|
(symbolResult, size, relocations) <- symbolEntry textTabIndex code
|
|
|
|
(initialHeaders, 0, mempty)
|
2024-09-08 02:08:13 +02:00
|
|
|
let newHeader = Elf32_Shdr
|
|
|
|
{ sh_type = SHT_PROGBITS
|
2024-09-08 22:53:07 +02:00
|
|
|
, sh_size = size
|
2024-09-10 02:03:20 +02:00
|
|
|
, sh_offset = elfSectionsSize sectionHeaders
|
|
|
|
, sh_name = fromIntegral $ ByteString.length sectionNames
|
2024-09-08 02:08:13 +02:00
|
|
|
, sh_link = 0
|
|
|
|
, sh_info = 0
|
|
|
|
, sh_flags = 0b110
|
|
|
|
, sh_entsize = 0
|
2024-09-12 02:21:48 +02:00
|
|
|
, sh_addralign = 4
|
2024-09-08 02:08:13 +02:00
|
|
|
, sh_addr = 0
|
|
|
|
}
|
2024-09-10 02:03:20 +02:00
|
|
|
addSectionHeader ".text" newHeader
|
2024-09-12 02:21:48 +02:00
|
|
|
pure (symbolResult, UnresolvedRelocations relocations $ fromIntegral $ Vector.length sectionHeaders)
|
2024-09-08 22:53:07 +02:00
|
|
|
symbolEntry
|
|
|
|
:: Elf32_Half
|
|
|
|
-> Vector RiscV.Instruction
|
|
|
|
-> (ElfHeaderResult Elf32_Sym, Elf32_Addr, Vector UnresolvedRelocation)
|
2024-09-10 02:03:20 +02:00
|
|
|
-> ElfWriter (ElfHeaderResult Elf32_Sym, Elf32_Addr, Vector UnresolvedRelocation)
|
2024-09-08 22:53:07 +02:00
|
|
|
symbolEntry shndx instructions (ElfHeaderResult names entries, offset, relocations) = do
|
|
|
|
let (encoded, size, updatedRelocations) =
|
|
|
|
Vector.foldl' encodeInstruction (mempty, offset, relocations) instructions
|
2024-09-08 02:08:13 +02:00
|
|
|
newEntry = Elf32_Sym
|
2024-09-08 22:53:07 +02:00
|
|
|
{ st_value = offset
|
|
|
|
, st_size = fromIntegral size
|
2024-09-08 02:08:13 +02:00
|
|
|
, st_shndx = shndx
|
|
|
|
, st_other = 0
|
|
|
|
, st_name = fromIntegral $ ByteString.length names
|
|
|
|
, st_info = stInfo STB_GLOBAL STT_FUNC
|
|
|
|
}
|
2024-09-10 02:03:20 +02:00
|
|
|
liftIO $ ByteString.hPut objectHandle $ LazyByteString.toStrict encoded
|
2024-09-08 22:53:07 +02:00
|
|
|
let newResult = ElfHeaderResult (names <> "_start\0")
|
|
|
|
$ Vector.snoc entries newEntry
|
|
|
|
pure (newResult, size, updatedRelocations)
|
|
|
|
encodeInstruction (instructions, offset, relocations) instruction =
|
|
|
|
let unresolvedRelocation = case instruction of
|
|
|
|
RiscV.RelocatableInstruction _ instructionType
|
|
|
|
| RiscV.Higher20 _ symbolName <- instructionType
|
2024-09-12 02:21:48 +02:00
|
|
|
-> Just -- R_RISCV_HI20
|
2024-09-08 22:53:07 +02:00
|
|
|
$ UnresolvedRelocation (Text.Encoding.encodeUtf8 symbolName) offset 26
|
|
|
|
| RiscV.Lower12I _ _ _ symbolName <- instructionType
|
2024-09-12 02:21:48 +02:00
|
|
|
-> Just -- R_RISCV_LO12_I
|
2024-09-08 22:53:07 +02:00
|
|
|
$ UnresolvedRelocation (Text.Encoding.encodeUtf8 symbolName) offset 27
|
|
|
|
| RiscV.Lower12S symbolName _ _ _ <- instructionType
|
2024-09-12 02:21:48 +02:00
|
|
|
-> Just -- R_RISCV_LO12_S
|
2024-09-08 22:53:07 +02:00
|
|
|
$ UnresolvedRelocation (Text.Encoding.encodeUtf8 symbolName) offset 28
|
|
|
|
RiscV.Instruction _ _ -> Nothing
|
|
|
|
encoded = ByteString.Builder.toLazyByteString
|
|
|
|
$ RiscV.instruction instruction
|
|
|
|
in
|
|
|
|
( instructions <> encoded
|
|
|
|
, offset + fromIntegral (LazyByteString.length encoded)
|
|
|
|
, maybe relocations (Vector.snoc relocations) unresolvedRelocation
|
|
|
|
)
|