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.
80 lines
2.9 KiB
80 lines
2.9 KiB
|
4 years ago
|
{-# LANGUAGE OverloadedStrings #-}
|
||
|
|
|
||
|
|
module Test.Nand2Tetris.VM
|
||
|
|
(
|
||
|
|
spec
|
||
|
|
) where
|
||
|
|
|
||
|
|
import Test.Hspec (Spec, describe, it, shouldBe)
|
||
|
|
|
||
|
|
import Nand2Tetris.VM (VMInstruction(VMMemAccess, VMArithmetic),
|
||
|
|
SegmentOffset(SegmentOffset),
|
||
|
|
AccessType(ACPush, ACPop),
|
||
|
|
SegmentId(SArgument, SLocal, SThis, SThat, SConstant, STemp, SPointer, SStatic),
|
||
|
|
SegmentOffset(SegmentOffset),
|
||
|
|
parseInstruction, ArithmeticCmd (ACAdd, ACNeg, ACSub, ACEq, ACGt, ACLt, ACAnd, ACOr, ACNot))
|
||
|
|
import Text.Megaparsec (runParser)
|
||
|
|
|
||
|
|
spec :: Spec
|
||
|
|
spec = do
|
||
|
|
describe "parseInstruction" $ do
|
||
|
|
it "Parses instruction: push argument 42" $
|
||
|
|
doParse "push argument 42" `shouldBe` Right (VMMemAccess ACPush SArgument (SegmentOffset 42))
|
||
|
|
|
||
|
|
it "Parses instruction: pop argument 42" $
|
||
|
|
doParse "pop argument 42" `shouldBe` Right (VMMemAccess ACPop SArgument (SegmentOffset 42))
|
||
|
|
|
||
|
|
it "Parses instruction: push local 42" $
|
||
|
|
doParse "push local 42" `shouldBe` Right (VMMemAccess ACPush SLocal (SegmentOffset 42))
|
||
|
|
|
||
|
|
it "Parses instruction: push this 42" $
|
||
|
|
doParse "push this 42" `shouldBe` Right (VMMemAccess ACPush SThis (SegmentOffset 42))
|
||
|
|
|
||
|
|
it "Parses instruction: push that 42" $
|
||
|
|
doParse "push that 42" `shouldBe` Right (VMMemAccess ACPush SThat (SegmentOffset 42))
|
||
|
|
|
||
|
|
it "Parses instruction: push constant 42" $
|
||
|
|
doParse "push constant 42" `shouldBe` Right (VMMemAccess ACPush SConstant (SegmentOffset 42))
|
||
|
|
|
||
|
|
it "Parses instruction: push static 42" $
|
||
|
|
doParse "push static 42" `shouldBe` Right (VMMemAccess ACPush SStatic (SegmentOffset 42))
|
||
|
|
|
||
|
|
it "Parses instruction: push pointer 42" $
|
||
|
|
doParse "push pointer 42" `shouldBe` Right (VMMemAccess ACPush SPointer (SegmentOffset 42))
|
||
|
|
|
||
|
|
it "Parses instruction: push temp 42" $
|
||
|
|
doParse "push temp 42" `shouldBe` Right (VMMemAccess ACPush STemp (SegmentOffset 42))
|
||
|
|
|
||
|
|
it "Parses instruction: push temp 11" $
|
||
|
|
doParse "push temp 11" `shouldBe` Right (VMMemAccess ACPush STemp (SegmentOffset 11))
|
||
|
|
|
||
|
|
it "Parses instruction: add" $
|
||
|
|
doParse "add" `shouldBe` Right (VMArithmetic ACAdd)
|
||
|
|
|
||
|
|
it "Parses instruction: sub" $
|
||
|
|
doParse "sub" `shouldBe` Right (VMArithmetic ACSub)
|
||
|
|
|
||
|
|
it "Parses instruction: neg" $
|
||
|
|
doParse "neg" `shouldBe` Right (VMArithmetic ACNeg)
|
||
|
|
|
||
|
|
it "Parses instruction: eq" $
|
||
|
|
doParse "eq" `shouldBe` Right (VMArithmetic ACEq)
|
||
|
|
|
||
|
|
it "Parses instruction: gt" $
|
||
|
|
doParse "gt" `shouldBe` Right (VMArithmetic ACGt)
|
||
|
|
|
||
|
|
it "Parses instruction: lt" $
|
||
|
|
doParse "lt" `shouldBe` Right (VMArithmetic ACLt)
|
||
|
|
|
||
|
|
it "Parses instruction: and" $
|
||
|
|
doParse "and" `shouldBe` Right (VMArithmetic ACAnd)
|
||
|
|
|
||
|
|
it "Parses instruction: or" $
|
||
|
|
doParse "or" `shouldBe` Right (VMArithmetic ACOr)
|
||
|
|
|
||
|
|
it "Parses instruction: not" $
|
||
|
|
doParse "not" `shouldBe` Right (VMArithmetic ACNot)
|
||
|
|
|
||
|
|
where
|
||
|
|
doParse = runParser parseInstruction ""
|