Take function name from the generated asm

This commit is contained in:
Eugen Wissner 2024-09-22 23:45:59 +02:00
parent daec506ed3
commit e66ccf46f4
Signed by: belka
GPG Key ID: A27FDC1E8EE902C0
2 changed files with 66 additions and 52 deletions

View File

@ -3,7 +3,7 @@ module Language.Elna.CodeGenerator
, generateCode , generateCode
) where ) where
import Data.Text (Text) import Data.ByteString (ByteString)
import Data.Vector (Vector) import Data.Vector (Vector)
import qualified Data.Vector as Vector import qualified Data.Vector as Vector
import Language.Elna.Intermediate (Quadruple(..)) import Language.Elna.Intermediate (Quadruple(..))
@ -17,7 +17,7 @@ data Directive
data Asm data Asm
= Instruction RiscV.Instruction = Instruction RiscV.Instruction
| JumpLabel Text [Directive] | JumpLabel ByteString [Directive]
deriving Eq deriving Eq
generateCode :: SymbolTable -> Vector Quadruple -> Vector Asm generateCode :: SymbolTable -> Vector Quadruple -> Vector Asm

View File

@ -180,9 +180,11 @@ riscv32Elf code objectHandle = text
, st_name = 0 , st_name = 0
, st_info = 0 , st_info = 0
} }
(symbolResult, size, relocations) <- symbolEntry textTabIndex code (encoded, updatedRelocations, symbols) =
(initialHeaders, 0, mempty) encodeAsm textTabIndex (mempty, Vector.empty, initialHeaders) code
let newHeader = Elf32_Shdr symbolResult = encodeEmptyDefinitions symbols
size = fromIntegral $ LazyByteString.length encoded
newHeader = Elf32_Shdr
{ sh_type = SHT_PROGBITS { sh_type = SHT_PROGBITS
, sh_size = size , sh_size = size
, sh_offset = elfSectionsSize sectionHeaders , sh_offset = elfSectionsSize sectionHeaders
@ -194,38 +196,49 @@ riscv32Elf code objectHandle = text
, sh_addralign = 4 , sh_addralign = 4
, sh_addr = 0 , sh_addr = 0
} }
liftIO $ ByteString.hPut objectHandle $ LazyByteString.toStrict encoded
addSectionHeader ".text" newHeader addSectionHeader ".text" newHeader
pure (symbolResult, UnresolvedRelocations relocations $ fromIntegral $ Vector.length sectionHeaders) pure (symbolResult, UnresolvedRelocations updatedRelocations $ fromIntegral $ Vector.length sectionHeaders)
symbolEntry encodeEmptyDefinitions (ElfHeaderResult names entries) =
:: Elf32_Half let printEntry = Elf32_Sym
-> Vector Asm { st_value = 0
-> (ElfHeaderResult Elf32_Sym, Elf32_Addr, Vector UnresolvedRelocation) , st_size = 0
-> ElfWriter (ElfHeaderResult Elf32_Sym, Elf32_Addr, Vector UnresolvedRelocation) , st_shndx = 0
symbolEntry shndx instructions (ElfHeaderResult names entries, offset, relocations) = do , st_other = 0
let (encoded, size, updatedRelocations) = , st_name = fromIntegral (ByteString.length names)
Vector.foldl' encodeInstruction (mempty, offset, relocations) instructions , st_info = stInfo STB_GLOBAL STT_FUNC
}
in ElfHeaderResult (names <> "printi\0")
$ Vector.snoc entries printEntry
encodeAsm shndx (encoded, relocations, ElfHeaderResult names symbols) instructions
| Just (instruction, rest) <- Vector.uncons instructions =
case instruction of
Instruction _ ->
let (encoded', relocations', rest') =
encodeInstructions (encoded, relocations, instructions)
in encodeAsm shndx (encoded', relocations', ElfHeaderResult names symbols) rest'
JumpLabel labelName _ ->
let (encoded', relocations', rest') =
encodeInstructions (encoded, relocations, rest)
newEntry = Elf32_Sym newEntry = Elf32_Sym
{ st_value = offset { st_value = fromIntegral $ LazyByteString.length encoded
, st_size = fromIntegral size , st_size = fromIntegral $ LazyByteString.length encoded'
, st_shndx = shndx , st_shndx = shndx
, st_other = 0 , st_other = 0
, st_name = fromIntegral $ ByteString.length names , st_name = fromIntegral $ ByteString.length names
, st_info = stInfo STB_GLOBAL STT_FUNC , st_info = stInfo STB_GLOBAL STT_FUNC
} }
printEntry = Elf32_Sym result =
{ st_value = 0 ( encoded <> encoded'
, st_size = 0 , relocations <> relocations'
, st_shndx = 0 , ElfHeaderResult (names <> labelName <> "\0") (Vector.snoc symbols newEntry)
, st_other = 0 )
, st_name = fromIntegral (ByteString.length names) + 5 in encodeAsm shndx result rest'
, st_info = stInfo STB_GLOBAL STT_FUNC | otherwise = (encoded, relocations, ElfHeaderResult names symbols)
} encodeInstructions (encoded, relocations, instructions)
liftIO $ ByteString.hPut objectHandle $ LazyByteString.toStrict encoded | Just (Instruction instruction, rest) <- Vector.uncons instructions =
let newResult = ElfHeaderResult (names <> "main\0printi\0") let offset = fromIntegral $ LazyByteString.length encoded
$ Vector.snoc (Vector.snoc entries newEntry) printEntry unresolvedRelocation = case instruction of
pure (newResult, size, updatedRelocations)
encodeInstruction (instructions, offset, relocations) (Instruction instruction) =
let unresolvedRelocation = case instruction of
RiscV.RelocatableInstruction _ instructionType RiscV.RelocatableInstruction _ instructionType
| RiscV.Higher20 _ symbolName <- instructionType | RiscV.Higher20 _ symbolName <- instructionType
-> Just -- R_RISCV_HI20 -> Just -- R_RISCV_HI20
@ -240,11 +253,12 @@ riscv32Elf code objectHandle = text
-> Just -- R_RISCV_CALL_PLT -> Just -- R_RISCV_CALL_PLT
$ UnresolvedRelocation (Text.Encoding.encodeUtf8 symbolName) offset 19 $ UnresolvedRelocation (Text.Encoding.encodeUtf8 symbolName) offset 19
RiscV.BaseInstruction _ _ -> Nothing RiscV.BaseInstruction _ _ -> Nothing
encoded = ByteString.Builder.toLazyByteString chunk = ByteString.Builder.toLazyByteString
$ RiscV.instruction instruction $ RiscV.instruction instruction
in result =
( instructions <> encoded ( encoded <> chunk
, offset + fromIntegral (LazyByteString.length encoded)
, maybe relocations (Vector.snoc relocations) unresolvedRelocation , maybe relocations (Vector.snoc relocations) unresolvedRelocation
, rest
) )
encodeInstruction accumulator (JumpLabel _ _) = accumulator in encodeInstructions result
| otherwise = (encoded, relocations, Vector.drop 1 instructions)