Skip to content

Commit

Permalink
Add tests for select command
Browse files Browse the repository at this point in the history
  • Loading branch information
thomasebsmith committed Jul 19, 2020
1 parent 77b3c61 commit 170b07a
Show file tree
Hide file tree
Showing 4 changed files with 59 additions and 2 deletions.
2 changes: 1 addition & 1 deletion json-quick.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ test-suite json-quick-tests
type: exitcode-stdio-1.0
main-is: Main.hs
build-depends: base ^>=4.13.0.0, bytestring, hspec, json-quick
other-modules: PrettifyTests, VerifyTests
other-modules: PrettifyTests, SelectTests, VerifyTests
hs-source-dirs: tests
default-language: Haskell2010
ghc-options: -Wall -Werror -Wincomplete-uni-patterns
2 changes: 1 addition & 1 deletion src/ParseUtilities.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ takeEscape = do
hexDigits <- takeHexEscape
return $ C.cons 'u' <$> hexDigits
Just escape -> if isSingleEscapeChar escape
then return $ Right $ escape `C.cons` C.singleton escape
then return $ Right $ C.singleton escape
else return $ Left $
"Invalid string escape with character " ++ show escape

Expand Down
2 changes: 2 additions & 0 deletions tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,11 @@ module Main where

import Test.Hspec
import qualified PrettifyTests
import qualified SelectTests
import qualified VerifyTests

main :: IO ()
main = hspec $ do
PrettifyTests.spec
SelectTests.spec
VerifyTests.spec
55 changes: 55 additions & 0 deletions tests/SelectTests.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,55 @@
module SelectTests
( spec
) where

import Parse
import Select
import Test.Hspec
import qualified Data.ByteString.Lazy.Char8 as C

spec :: Spec
spec = do
describe "select" $ do
it "selects entire values" $ do
testSelect " " "\"Some\\nstring\"" `shouldBe` Just "\"Some\\nstring\"\n"
testSelect "" "100E3" `shouldBe` Just "100E3\n"
testSelect "\n" "true" `shouldBe` Just "true\n"
testSelect "\r" " false\t" `shouldBe` Just "false\n"
testSelect " " "\rnull" `shouldBe` Just "null\n"
testSelect "" "[1, 2, 3]" `shouldBe` Just "[1,2,3]\n"
testSelect "" "{\"key\": 89}" `shouldBe` Just "{\"key\":89}\n"
it "fails to select invalid JSON regions" $ do
testSelect "" "blah" `shouldBe` Nothing
testSelect "" "[1" `shouldBe` Nothing
testSelect "key" "{\"key\":[" `shouldBe` Nothing
testSelect "" "{[]}" `shouldBe` Nothing
it "selects properties" $ do
testSelect "prop1" "{\"prop2\":3,\"prop1\":4}" `shouldBe` Just "4\n"
testSelect "\"some key\"" "{\"some key2\":1,\"some key\":-1}" `shouldBe`
Just "-1\n"
it "fails to select properties that don't exist" $ do
testSelect "notexist" "{\"exists\":3.14159}" `shouldBe` Nothing
testSelect "property" "\"property\"" `shouldBe` Nothing
testSelect "key" "[1,2,3]" `shouldBe` Nothing
it "selects indices" $ do
testSelect "0" "[-1,-2]" `shouldBe` Just "-1\n"
testSelect "2" "[{},[],[]]" `shouldBe` Just "[]\n"
testSelect "1" "[0,{\"key\":3.14}]" `shouldBe` Just "{\"key\":3.14}\n"
it "fails to select indices that don't exist" $ do
testSelect "0" "[]" `shouldBe` Nothing
testSelect "2" "[1,2]" `shouldBe` Nothing
testSelect "0a" "[3,1,4]" `shouldBe` Nothing
it "selects all properties" $ do
testSelect "*" "[3,1,4,[1,5]]" `shouldBe` Just "[3,1,4,[1,5]]\n"
testSelect "*" "{\"k\":3,\"k2\":4}" `shouldBe` Just "[3,4]\n"
it "selects nested properties and indices" $ do
testSelect "prop.1.*" "{\"p\":3,\"prop\":[0,{\"a\":1,\"b\":2}]}"
`shouldBe` Just "[1,2]\n"
testSelect "\"key\".\"*\".*" "{\"key\":{\"*\":[1,2,3]}}\n" `shouldBe`
Just "[1,2,3]\n"

testSelect :: String -> String -> Maybe String
testSelect pattern input = case selected of
Left _ -> Nothing
Right value -> C.unpack <$> showAsByteString value
where selected = parseAndSelect (C.pack input) (C.pack pattern)

1 comment on commit 170b07a

@thomasebsmith
Copy link
Owner Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Work for #6.

Please sign in to comment.