Put _start and main call into builtins
This commit is contained in:
parent
0a8d3fce2f
commit
daec506ed3
@ -148,7 +148,7 @@ data RelocationType
|
|||||||
deriving Eq
|
deriving Eq
|
||||||
|
|
||||||
data Instruction
|
data Instruction
|
||||||
= Instruction BaseOpcode Type
|
= BaseInstruction BaseOpcode Type
|
||||||
| RelocatableInstruction BaseOpcode RelocationType
|
| RelocatableInstruction BaseOpcode RelocationType
|
||||||
| CallInstruction Text
|
| CallInstruction Text
|
||||||
deriving Eq
|
deriving Eq
|
||||||
@ -305,11 +305,11 @@ relocationType (Higher20 rd _) = type' $ U rd 0
|
|||||||
|
|
||||||
instruction :: Instruction -> ByteString.Builder.Builder
|
instruction :: Instruction -> ByteString.Builder.Builder
|
||||||
instruction = \case
|
instruction = \case
|
||||||
(Instruction base instructionType) -> go base $ type' instructionType
|
(BaseInstruction base instructionType) -> go base $ type' instructionType
|
||||||
(RelocatableInstruction base instructionType) -> go base $ relocationType instructionType
|
(RelocatableInstruction base instructionType) -> go base $ relocationType instructionType
|
||||||
(CallInstruction _) -> foldMap instruction
|
(CallInstruction _) -> foldMap instruction
|
||||||
[ Instruction Auipc $ U RA 0
|
[ BaseInstruction Auipc $ U RA 0
|
||||||
, Instruction Jalr $ I RA JALR RA 0
|
, BaseInstruction Jalr $ I RA JALR RA 0
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
go base instructionType
|
go base instructionType
|
||||||
|
@ -1,17 +1,28 @@
|
|||||||
module Language.Elna.CodeGenerator
|
module Language.Elna.CodeGenerator
|
||||||
( generateCode
|
( Asm(..)
|
||||||
|
, generateCode
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.Text (Text)
|
||||||
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(..))
|
||||||
import qualified Language.Elna.Architecture.RiscV as RiscV
|
import qualified Language.Elna.Architecture.RiscV as RiscV
|
||||||
import Language.Elna.SymbolTable (SymbolTable)
|
import Language.Elna.SymbolTable (SymbolTable)
|
||||||
|
|
||||||
generateCode :: SymbolTable -> Vector Quadruple -> Vector RiscV.Instruction
|
data Directive
|
||||||
|
= GlobalDirective
|
||||||
|
| FunctionDirective
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
|
data Asm
|
||||||
|
= Instruction RiscV.Instruction
|
||||||
|
| JumpLabel Text [Directive]
|
||||||
|
deriving Eq
|
||||||
|
|
||||||
|
generateCode :: SymbolTable -> Vector Quadruple -> Vector Asm
|
||||||
generateCode _ _ = Vector.fromList
|
generateCode _ _ = Vector.fromList
|
||||||
[ RiscV.CallInstruction "printi"
|
[ JumpLabel "main" [GlobalDirective, FunctionDirective]
|
||||||
, RiscV.Instruction RiscV.OpImm $ RiscV.I RiscV.A0 RiscV.ADDI RiscV.Zero 0
|
, Instruction (RiscV.CallInstruction "printi")
|
||||||
, RiscV.Instruction RiscV.OpImm $ RiscV.I RiscV.A7 RiscV.ADDI RiscV.Zero 93
|
, Instruction (RiscV.BaseInstruction RiscV.Jalr $ RiscV.I RiscV.RA RiscV.JALR RiscV.Zero 0)
|
||||||
, RiscV.Instruction RiscV.System $ RiscV.Type RiscV.Zero RiscV.PRIV RiscV.Zero RiscV.ECALL
|
|
||||||
]
|
]
|
||||||
|
@ -25,7 +25,23 @@ data Error
|
|||||||
| IdentifierAlreadyDefinedError Identifier
|
| IdentifierAlreadyDefinedError Identifier
|
||||||
| UndefinedSymbolError Identifier
|
| UndefinedSymbolError Identifier
|
||||||
| UnexpectedArrayByValue Identifier
|
| UnexpectedArrayByValue Identifier
|
||||||
deriving (Eq, Show)
|
deriving Eq
|
||||||
|
|
||||||
|
instance Show Error
|
||||||
|
where
|
||||||
|
show (UndefinedTypeError identifier) =
|
||||||
|
concat ["Type \"", show identifier, "\" is not defined"]
|
||||||
|
show (UnexpectedTypeInfoError info) = show info
|
||||||
|
<> " expected to be a type"
|
||||||
|
show (IdentifierAlreadyDefinedError identifier) =
|
||||||
|
concat ["The identifier \"", show identifier, "\" is already defined"]
|
||||||
|
show (UndefinedSymbolError identifier) =
|
||||||
|
concat ["Symbol \"", show identifier, "\" is not defined"]
|
||||||
|
show (UnexpectedArrayByValue identifier) = concat
|
||||||
|
[ "Array \""
|
||||||
|
, show identifier
|
||||||
|
, "\" cannot be passed by value, only by reference"
|
||||||
|
]
|
||||||
|
|
||||||
newtype NameAnalysis a = NameAnalysis
|
newtype NameAnalysis a = NameAnalysis
|
||||||
{ runNameAnalysis :: Except Error a
|
{ runNameAnalysis :: Except Error a
|
||||||
@ -61,7 +77,7 @@ procedureDeclaration globalTable (AST.ProcedureDeclaration identifier parameters
|
|||||||
$ Vector.fromList parametersInfo
|
$ Vector.fromList parametersInfo
|
||||||
maybe (NameAnalysis $ throwE $ IdentifierAlreadyDefinedError identifier) pure
|
maybe (NameAnalysis $ throwE $ IdentifierAlreadyDefinedError identifier) pure
|
||||||
$ SymbolTable.enter identifier procedureInfo globalTable
|
$ SymbolTable.enter identifier procedureInfo globalTable
|
||||||
|
|
||||||
declaration :: SymbolTable -> AST.Declaration -> NameAnalysis SymbolTable
|
declaration :: SymbolTable -> AST.Declaration -> NameAnalysis SymbolTable
|
||||||
declaration globalTable (AST.ProcedureDeclaration identifier parameters variables body) = do
|
declaration globalTable (AST.ProcedureDeclaration identifier parameters variables body) = do
|
||||||
variableInfo <- mapM (variableDeclaration globalTable) variables
|
variableInfo <- mapM (variableDeclaration globalTable) variables
|
||||||
|
@ -44,11 +44,12 @@ import qualified Language.Elna.Architecture.RiscV as RiscV
|
|||||||
import qualified Data.Text.Encoding as Text.Encoding
|
import qualified Data.Text.Encoding as Text.Encoding
|
||||||
import Control.Monad.IO.Class (MonadIO(..))
|
import Control.Monad.IO.Class (MonadIO(..))
|
||||||
import Control.Monad.Trans.State (get)
|
import Control.Monad.Trans.State (get)
|
||||||
|
import Language.Elna.CodeGenerator (Asm(..))
|
||||||
|
|
||||||
data UnresolvedRelocation = UnresolvedRelocation ByteString Elf32_Addr Word8
|
data UnresolvedRelocation = UnresolvedRelocation ByteString Elf32_Addr Word8
|
||||||
data UnresolvedRelocations = UnresolvedRelocations (Vector UnresolvedRelocation) Elf32_Word
|
data UnresolvedRelocations = UnresolvedRelocations (Vector UnresolvedRelocation) Elf32_Word
|
||||||
|
|
||||||
riscv32Elf :: Vector RiscV.Instruction -> Handle -> ElfWriter Elf32_Ehdr
|
riscv32Elf :: Vector Asm -> Handle -> ElfWriter Elf32_Ehdr
|
||||||
riscv32Elf code objectHandle = text
|
riscv32Elf code objectHandle = text
|
||||||
>>= uncurry symrel
|
>>= uncurry symrel
|
||||||
>>= strtab
|
>>= strtab
|
||||||
@ -197,7 +198,7 @@ riscv32Elf code objectHandle = text
|
|||||||
pure (symbolResult, UnresolvedRelocations relocations $ fromIntegral $ Vector.length sectionHeaders)
|
pure (symbolResult, UnresolvedRelocations relocations $ fromIntegral $ Vector.length sectionHeaders)
|
||||||
symbolEntry
|
symbolEntry
|
||||||
:: Elf32_Half
|
:: Elf32_Half
|
||||||
-> Vector RiscV.Instruction
|
-> Vector Asm
|
||||||
-> (ElfHeaderResult Elf32_Sym, Elf32_Addr, Vector UnresolvedRelocation)
|
-> (ElfHeaderResult Elf32_Sym, Elf32_Addr, Vector UnresolvedRelocation)
|
||||||
-> ElfWriter (ElfHeaderResult Elf32_Sym, Elf32_Addr, Vector UnresolvedRelocation)
|
-> ElfWriter (ElfHeaderResult Elf32_Sym, Elf32_Addr, Vector UnresolvedRelocation)
|
||||||
symbolEntry shndx instructions (ElfHeaderResult names entries, offset, relocations) = do
|
symbolEntry shndx instructions (ElfHeaderResult names entries, offset, relocations) = do
|
||||||
@ -216,14 +217,14 @@ riscv32Elf code objectHandle = text
|
|||||||
, st_size = 0
|
, st_size = 0
|
||||||
, st_shndx = 0
|
, st_shndx = 0
|
||||||
, st_other = 0
|
, st_other = 0
|
||||||
, st_name = fromIntegral (ByteString.length names) + 7
|
, st_name = fromIntegral (ByteString.length names) + 5
|
||||||
, st_info = stInfo STB_GLOBAL STT_FUNC
|
, st_info = stInfo STB_GLOBAL STT_FUNC
|
||||||
}
|
}
|
||||||
liftIO $ ByteString.hPut objectHandle $ LazyByteString.toStrict encoded
|
liftIO $ ByteString.hPut objectHandle $ LazyByteString.toStrict encoded
|
||||||
let newResult = ElfHeaderResult (names <> "_start\0printi\0")
|
let newResult = ElfHeaderResult (names <> "main\0printi\0")
|
||||||
$ Vector.snoc (Vector.snoc entries newEntry) printEntry
|
$ Vector.snoc (Vector.snoc entries newEntry) printEntry
|
||||||
pure (newResult, size, updatedRelocations)
|
pure (newResult, size, updatedRelocations)
|
||||||
encodeInstruction (instructions, offset, relocations) instruction =
|
encodeInstruction (instructions, offset, relocations) (Instruction instruction) =
|
||||||
let unresolvedRelocation = case instruction of
|
let unresolvedRelocation = case instruction of
|
||||||
RiscV.RelocatableInstruction _ instructionType
|
RiscV.RelocatableInstruction _ instructionType
|
||||||
| RiscV.Higher20 _ symbolName <- instructionType
|
| RiscV.Higher20 _ symbolName <- instructionType
|
||||||
@ -238,7 +239,7 @@ riscv32Elf code objectHandle = text
|
|||||||
RiscV.CallInstruction symbolName
|
RiscV.CallInstruction symbolName
|
||||||
-> 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.Instruction _ _ -> Nothing
|
RiscV.BaseInstruction _ _ -> Nothing
|
||||||
encoded = ByteString.Builder.toLazyByteString
|
encoded = ByteString.Builder.toLazyByteString
|
||||||
$ RiscV.instruction instruction
|
$ RiscV.instruction instruction
|
||||||
in
|
in
|
||||||
@ -246,3 +247,4 @@ riscv32Elf code objectHandle = text
|
|||||||
, offset + fromIntegral (LazyByteString.length encoded)
|
, offset + fromIntegral (LazyByteString.length encoded)
|
||||||
, maybe relocations (Vector.snoc relocations) unresolvedRelocation
|
, maybe relocations (Vector.snoc relocations) unresolvedRelocation
|
||||||
)
|
)
|
||||||
|
encodeInstruction accumulator (JumpLabel _ _) = accumulator
|
||||||
|
@ -1,6 +1,12 @@
|
|||||||
|
.global main
|
||||||
|
.type main, @function
|
||||||
|
|
||||||
.global printi
|
.global printi
|
||||||
.type printi, @function
|
.type printi, @function
|
||||||
|
|
||||||
|
.global _start
|
||||||
|
.type _start, @function
|
||||||
|
|
||||||
.text
|
.text
|
||||||
printi:
|
printi:
|
||||||
addi sp, sp, -8
|
addi sp, sp, -8
|
||||||
@ -27,3 +33,9 @@ printi:
|
|||||||
lw ra, 4(sp)
|
lw ra, 4(sp)
|
||||||
addi sp, sp, 8
|
addi sp, sp, 8
|
||||||
ret
|
ret
|
||||||
|
|
||||||
|
_start:
|
||||||
|
call "main"
|
||||||
|
addi a0, zero, 0
|
||||||
|
addi a7, zero, 93
|
||||||
|
ecall
|
||||||
|
Loading…
Reference in New Issue
Block a user