simple-arithmetic-compiler/app/Assembler.hs

31 lines
743 B
Haskell

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)