Nand2Tetris course artifacts: assembler, VM compiler and more
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 

54 lines
2.2 KiB

{-# LANGUAGE OverloadedStrings #-}
module Main (main) where
import Control.Monad (forM_)
import qualified Data.Text.IO as TIO
import Nand2Tetris.Hack (AsmLine (..), HackInstruction (..),
canonicalRepresentation)
import Nand2Tetris.VM (AnnotatedAsmLine (..),
compileInstructions, parseInstructions)
import Options.Applicative (execParser, fullDesc, header, help,
helper, info, long, metavar, progDesc,
short, strOption, (<**>))
import System.IO (IOMode (WriteMode), hPutStrLn, withFile)
import Text.Megaparsec (runParser)
import Text.Megaparsec.Error (ParseErrorBundle,
ShowErrorComponent (showErrorComponent),
errorBundlePretty)
data Options =
Options
{
inputFile :: FilePath,
outputFile :: FilePath
}
main :: IO ()
main = do
options <- execParser opts
programText <- TIO.readFile (inputFile options)
let result = runParser parseInstructions (inputFile options) programText
case result of
Left err -> putStrLn $ errorBundlePretty err
Right parsed -> do
let compiled = compileInstructions parsed
withFile (outputFile options) WriteMode $ \h -> forM_ compiled (\x -> TIO.hPutStrLn h (printLine x))
where
printLine (Comment t) = "// " <> t
printLine (Code i) = canonicalRepresentation (LineInstruction i)
printLine (ALabel l) = canonicalRepresentation (LineLabel l)
opts = info (hackAsmOptParser <**> helper)
( fullDesc
<> progDesc "Compiles Hack VM code to Hack assembly"
<> header "vmcompiler - Hack VM compiler (nand2tetris)" )
hackAsmOptParser = Options <$>
strOption ( long "input"
<> short 'i'
<> metavar "FILENAME"
<> help "Input file" ) <*>
strOption ( long "output"
<> short 'o'
<> metavar "FILENAME"
<> help "Output file" )