feat: Implement Assembler

This commit is contained in:
Laborratte 5 2024-07-20 18:15:58 +02:00
parent 8e5fba32f6
commit 29e5f97dae
Signed by: Laborratte5
GPG key ID: 3A30072E35202C02
3 changed files with 38 additions and 3 deletions

31
app/Assembler.hs Normal file
View file

@ -0,0 +1,31 @@
module Assembler where
import Data.Int
import qualified Data.Binary as B
import qualified Data.Binary.Builder as Bu
import qualified Data.Binary.Put as P
import qualified Data.ByteString.Lazy as BL
import Compiler
-- Binary (huffman) encoding of instructions
-- 0x00 reserver
-- 0x01 Const
-- 0x04 Add
-- 0x05 Sub
-- 0x06 Mult
-- 0x07 Div
type Bytecode = BL.ByteString
toBinary :: Command -> P.Put
toBinary (Const i) = do
P.putWord8 0x0001
P.putInt32be ((fromIntegral i)::Int32)
toBinary Add = P.putWord8 0x0004
toBinary Sub = P.putWord8 0x0005
toBinary Mult = P.putWord8 0x0006
toBinary Div = P.putWord8 0x0007
assemble :: [Command] -> Bytecode
assemble cmds = Bu.toLazyByteString $ mconcat (map (P.execPut . toBinary) cmds)

View file

@ -4,10 +4,12 @@ import qualified Lexer
import qualified Parser
import qualified AbstractSyntaxTree as AST
import qualified Compiler
import qualified Assembler
import qualified Data.ByteString.Lazy as BL
main :: IO ()
main = do
source <- readFile "arithmetic.txt"
case Parser.parse $ Lexer.lex source of
Just source -> print $ Compiler.compile $ AST.createAST source
Just source -> BL.putStr $ Assembler.assemble $ Compiler.compile $ AST.createAST source
_ -> putStr "Some error"

View file

@ -52,13 +52,15 @@ executable simple-arithmetic-compiler
main-is: Main.hs
-- Modules included in this executable, other than Main.
other-modules: Lexer, Parser, AbstractSyntaxTree, Compiler
other-modules: Lexer, Parser, AbstractSyntaxTree, Compiler, Assembler
-- LANGUAGE extensions used by modules in this package.
-- other-extensions:
-- Other library packages from which modules are imported.
build-depends: base ^>=4.16.4.0
build-depends: base ^>=4.16.4.0,
binary ^>=0.8.9.2,
bytestring ^>=0.11.4.0
-- Directories containing source files.
hs-source-dirs: app