diff --git a/MVM.cabal b/MVM.cabal index 33af7de..546c1d9 100644 --- a/MVM.cabal +++ b/MVM.cabal @@ -57,6 +57,7 @@ test-suite spec other-modules: Assembler.TokenizerSpec Assembler.ParserSpec + UtilSpec VirtualMachine Assembler.Tokenizer diff --git a/app/Assembler/Tokenizer.hs b/app/Assembler/Tokenizer.hs index c5a78cd..8612a40 100644 --- a/app/Assembler/Tokenizer.hs +++ b/app/Assembler/Tokenizer.hs @@ -111,12 +111,7 @@ sepTokenizer _ _ [] = Nothing sepTokenizer predicate tokenizer input = do result@(TokenizeResult _ consumed) <- tokenizer input let next = drop consumed input - let (isSep, _) = if null next - then (True, 0) - else if predicate . head $ next - then (True, 1) - else (False, 0) - if isSep + if null next || (predicate . head $ next) then return $ result else Nothing diff --git a/app/Util.hs b/app/Util.hs index ed0138c..ea8feb1 100644 --- a/app/Util.hs +++ b/app/Util.hs @@ -63,6 +63,7 @@ controlChar x = case x of explode :: (Foldable f) => (a -> Bool) -> f a -> [[a]] explode predicate xs = filter (not . null) $ foldr split [[]] xs where + split _ [] = [] split y (ys:yss) | predicate y = []:ys:yss - | otherwise = (y:ys):yss \ No newline at end of file + | otherwise = (y:ys):yss \ No newline at end of file diff --git a/app/VirtualMachine.hs b/app/VirtualMachine.hs index eba5890..3ea4736 100644 --- a/app/VirtualMachine.hs +++ b/app/VirtualMachine.hs @@ -97,6 +97,8 @@ instructions = [ Simple { _op = Nop, _noParams = 0, _noPops = 0, _sAction = (\ ] jumpIf :: (Int -> Int -> Bool) -> VM -> Args -> Either String VM +jumpIf _ _ [] = Left $ "Address expected" +jumpIf _ _ (_:_:_) = Left $ "Multiple parameters are not supported by jmp* instructions" jumpIf predicate vm [addr] = Right $ vm { _pc = pc } where (top:_) = toList . _stack $ vm diff --git a/test/UtilSpec.hs b/test/UtilSpec.hs new file mode 100644 index 0000000..dedb14f --- /dev/null +++ b/test/UtilSpec.hs @@ -0,0 +1,63 @@ +module UtilSpec where + +import Prelude hiding (head) +import Test.Hspec +import Util + +import Data.Word +import Data.Char (chr) + +spec :: Spec +spec = do + describe "toLowerCase" $ do + it "converts arbitrary string to lowercase" $ + toLowerCase "Some UpPeR CASED sTRi_NG" `shouldBe` "some upper cased stri_ng" + it "does not convert already lowercased string" $ + toLowerCase "some lower cased string" `shouldBe` "some lower cased string" + + describe "byteStr" $ do + it "presents byte as hex" $ do + let input = [0, 1, 5, 10, 15, 16, 255 ] :: [Word8] + let expected = ["00", "01", "05", "0a", "0f", "10", "ff"] + map byteStr input `shouldBe` expected + + describe "bytesStr" $ do + it "presents bytes as hex in fixed columns of width 5" $ do + let input = [0..19] :: [Word8] + let expected = "00 01 02 03 04 \n\ + \05 06 07 08 09 \n\ + \0a 0b 0c 0d 0e \n\ + \0f 10 11 12 13" + bytesStr 5 input `shouldBe` expected + + describe "head" $ do + it "returns just a head of list" $ do + head [4, 3, 6] `shouldBe` (Just 4 :: Maybe Int) + it "returns Nothing if list is empty" $ do + head [] `shouldBe` (Nothing :: Maybe Int) + + describe "unescape" $ do + it "properly converts escape sequences to correct ASCII characters" $ do + let input = "\\tHello,\\nworld!\\0" + let expected = "\tHello,\nworld!\0" + unescape input `shouldBe` Just expected + it "supports all escape sequences" $ do + let input = "\\n\\t\\v\\b\\r\\f\\a\\\\\\\"\\0" + let expected = map chr [10, 9, 11, 8, 13, 12, 7, 92, 34, 0] + unescape input `shouldBe` Just expected + it "returns nothing if unknown escape sequence encountered" $ do + let input = "Unknown escape: \\x" + unescape input `shouldBe` Nothing + + describe "explode" $ do + it "splits the list by given character" $ do + let input = "hello:world: what's : up?" + let expected = ["hello", "world", " what's ", " up?"] + explode (==':') input `shouldBe` expected + it "supports empty input" $ do + let input = "" + explode (==':') input `shouldBe` [] + it "filters out empty lists" $ do + let input = ":hello:world:::::: what's : up?" + let expected = ["hello", "world", " what's ", " up?"] + explode (==':') input `shouldBe` expected \ No newline at end of file