finally setup an LSP - fixed all warnings
This commit is contained in:
@@ -1,9 +1,7 @@
|
||||
module Compiler where
|
||||
|
||||
import Parser
|
||||
import Text.Printf (printf)
|
||||
import Control.Monad (void)
|
||||
import System.Process
|
||||
import System.IO
|
||||
import Control.Monad.Trans.State
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
@@ -183,51 +181,51 @@ handleSymbol h (ZorthASTWord "<=") = do
|
||||
return ()
|
||||
|
||||
handleSymbol h (ZorthASTWord w) = do
|
||||
state <- get
|
||||
_ <- compileZorthASTState h ((environment state) M.! w) -- parent env to child and discard
|
||||
s <- get
|
||||
_ <- compileZorthASTState h (environment s M.! w) -- parent env to child and discard
|
||||
return ()
|
||||
|
||||
handleSymbol _ (ZorthASTWordDecl (name,ast)) = do
|
||||
(Environment labels state) <- get
|
||||
put $ Environment labels (M.insert name ast state) -- maybe use `lens`?..
|
||||
(Environment labels s) <- get
|
||||
put $ Environment labels (M.insert name ast s) -- maybe use `lens`?..
|
||||
return ()
|
||||
|
||||
-- honestly, this feels kinda janky, the way I manipulate state
|
||||
handleSymbol h (ZorthASTIfElse (ifBranch,elseBranch)) = do
|
||||
(Environment l state) <- get
|
||||
(Environment l s) <- get
|
||||
let l1 = show $ l+1
|
||||
let l2 = show $ l+2
|
||||
put $ Environment (l+2) state
|
||||
put $ Environment (l+2) s
|
||||
liftIO $ hPutStr h $
|
||||
" pop rax\n\
|
||||
\ cmp rax, 0\n\
|
||||
\ je .L"<>l1<>"\n"
|
||||
compileZorthASTState h ifBranch
|
||||
(Environment l' _) <- get
|
||||
put $ Environment l' state
|
||||
put $ Environment l' s
|
||||
liftIO $ hPutStr h $ " jmp .L"<>l2<>"\n.L"<>l1<>":\n"
|
||||
compileZorthASTState h elseBranch
|
||||
(Environment l'' _) <- get
|
||||
put $ Environment l'' state
|
||||
put $ Environment l'' s
|
||||
liftIO $ hPutStr h $ ".L"<>l2<>":\n"
|
||||
|
||||
handleSymbol h (ZorthASTWhile (condition,body)) = do
|
||||
(Environment l state) <- get
|
||||
(Environment l s) <- get
|
||||
let bodyl = show $ l+1
|
||||
let conditionl = show $ l+2
|
||||
let restl = show $ l+3
|
||||
put $ Environment (l+3) state
|
||||
put $ Environment (l+3) s
|
||||
liftIO $ hPutStrLn h $ " jmp .L"<>conditionl
|
||||
liftIO $ hPutStrLn h $ ".L"<>bodyl<>":"
|
||||
compileZorthASTState h body
|
||||
(Environment l' _) <- get
|
||||
put $ Environment l' state
|
||||
put $ Environment l' s
|
||||
liftIO $ hPutStrLn h $ "\n.L"<>conditionl<>":"
|
||||
compileZorthASTState h condition
|
||||
(Environment l'' _) <- get
|
||||
put $ Environment l'' state
|
||||
liftIO $ hPutStrLn h $ " pop rax"
|
||||
liftIO $ hPutStrLn h $ " cmp rax,0"
|
||||
put $ Environment l'' s
|
||||
liftIO $ hPutStrLn h " pop rax"
|
||||
liftIO $ hPutStrLn h " cmp rax,0"
|
||||
liftIO $ hPutStrLn h $ " jg .L"<>bodyl
|
||||
liftIO $ hPutStrLn h $ ".L"<>restl<>":"
|
||||
|
||||
@@ -242,10 +240,10 @@ truthOperator h s =
|
||||
\ push rax\n"
|
||||
|
||||
compileZorthASTState :: Handle -> ZorthAST -> StateT Environment IO ()
|
||||
compileZorthASTState h ast = (foldl (\m x -> m >> handleSymbol h x) (return ()) ast)
|
||||
compileZorthASTState h = foldl (\m x -> m >> handleSymbol h x) (return ())
|
||||
|
||||
compileZorthAST :: Handle -> ZorthAST -> Environment -> IO ()
|
||||
compileZorthAST h ast state = runStateT (compileZorthASTState h ast) state >> return ()
|
||||
compileZorthAST h ast s = void $ runStateT (compileZorthASTState h ast) s
|
||||
|
||||
compileZorth :: Handle -> ZorthAST -> IO ()
|
||||
compileZorth _ [] = return ()
|
||||
@@ -256,4 +254,4 @@ compileZorth h xs = do
|
||||
\ mov rdi,0\n\
|
||||
\ syscall\n"
|
||||
hPutStr h "section .bss\n\
|
||||
\ mem: resq 640000\n"
|
||||
\ mem: resq 640000\n"
|
||||
|
||||
Reference in New Issue
Block a user