Implement Compiler
This commit is contained in:
parent
eb03afe343
commit
8e5fba32f6
3 changed files with 22 additions and 2 deletions
19
app/Compiler.hs
Normal file
19
app/Compiler.hs
Normal file
|
|
@ -0,0 +1,19 @@
|
||||||
|
module Compiler where
|
||||||
|
|
||||||
|
import qualified AbstractSyntaxTree as AST
|
||||||
|
|
||||||
|
data Command = Const Int -- Load integer const
|
||||||
|
| Add
|
||||||
|
| Sub
|
||||||
|
| Mult
|
||||||
|
| Div
|
||||||
|
deriving Show
|
||||||
|
|
||||||
|
compile :: AST.AST -> [Command]
|
||||||
|
compile = reverse . compile'
|
||||||
|
where compile' ast = case ast of
|
||||||
|
AST.Scalar i -> [Const i]
|
||||||
|
AST.Operation AST.Add left right -> Add : compile' left ++ compile' right
|
||||||
|
AST.Operation AST.Sub left right -> Sub : compile' left ++ compile' right
|
||||||
|
AST.Operation AST.Mult left right -> Mult : compile' left ++ compile' right
|
||||||
|
AST.Operation AST.Div left right -> Div : compile' left ++ compile' right
|
||||||
|
|
@ -3,10 +3,11 @@ module Main where
|
||||||
import qualified Lexer
|
import qualified Lexer
|
||||||
import qualified Parser
|
import qualified Parser
|
||||||
import qualified AbstractSyntaxTree as AST
|
import qualified AbstractSyntaxTree as AST
|
||||||
|
import qualified Compiler
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
source <- readFile "arithmetic.txt"
|
source <- readFile "arithmetic.txt"
|
||||||
case Parser.parse $ Lexer.lex source of
|
case Parser.parse $ Lexer.lex source of
|
||||||
Just source -> print $ AST.createAST source
|
Just source -> print $ Compiler.compile $ AST.createAST source
|
||||||
_ -> putStr "Some error"
|
_ -> putStr "Some error"
|
||||||
|
|
|
||||||
|
|
@ -52,7 +52,7 @@ executable simple-arithmetic-compiler
|
||||||
main-is: Main.hs
|
main-is: Main.hs
|
||||||
|
|
||||||
-- Modules included in this executable, other than Main.
|
-- Modules included in this executable, other than Main.
|
||||||
other-modules: Lexer, Parser, AbstractSyntaxTree
|
other-modules: Lexer, Parser, AbstractSyntaxTree, Compiler
|
||||||
|
|
||||||
-- LANGUAGE extensions used by modules in this package.
|
-- LANGUAGE extensions used by modules in this package.
|
||||||
-- other-extensions:
|
-- other-extensions:
|
||||||
|
|
|
||||||
Loading…
Add table
Add a link
Reference in a new issue