graphql-engine/server/src-test/Data/Parser/JSONPathSpec.hs
Samir Talwar 975b022b29 server/parsers: Reduce usages of "utils"-like functions.
This reduces the usage of "utils" modules in the parsers code, especially those that are simply re-exported from elsewhere, to facilitate extracting the parsers code into its own library.

It mostly inlines the imports that are re-exported from `Hasura.Prelude` and `Data.Parser.JSONPath`. It also removes references to `Data.*.Extended` modules. When necessary, it re-implements the functionality (which is typically trivial).

It does not tackle all external dependencies. I observed the following that will take more work:

- `Data.GADT.Compare.Extended`
- `Data.Text.Extended`
- `Hasura.Base.Error`
- `Hasura.RQL.Types.Common`
- `Hasura.Server.Utils`

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4964
GitOrigin-RevId: 54ad3c1b7a31f13e34340ebe9fcc36d0ad57b8bd
2022-07-06 07:56:35 +00:00

53 lines
1.9 KiB
Haskell

module Data.Parser.JSONPathSpec (spec) where
import Data.Aeson (JSONPath)
import Data.Aeson.Key qualified as K
import Data.Aeson.Types (JSONPathElement (..))
import Data.Parser.JSONPath
import Data.Text qualified as T
import Hasura.Prelude
import Test.Hspec
import Test.QuickCheck
spec :: Spec
spec = do
describe "encoding a JSON path" $ do
it "encodes a one-level path" $
encodeJSONPath [Key "ABCD"] `shouldBe` "$.ABCD"
it "encodes a multi-level path" $
encodeJSONPath [Key "7seven", Index 0, Key "@!^@*#(!("] `shouldBe` "$[\"7seven\"][0][\"@!^@*#(!(\"]"
it "escapes control characters and quotes" $
encodeJSONPath [Key "/\\ '\" \t\r\n \xfffd"] `shouldBe` "$[\"/\\\\ '\\\" \\t\\r\\n \xfffd\"]"
describe "parsing a JSON path" $ do
it "parses a single '$'" $
parseJSONPath "$" `shouldBe` Right []
it "parses bracketed single quotes" $
parseJSONPath "$['foo \\' \" bar']" `shouldBe` Right [Key "foo ' \" bar"]
it "parses bracketed double quotes" $
parseJSONPath "$[\"bar ' \\\" foo\"]" `shouldBe` Right [Key "bar ' \" foo"]
describe "the round trip" $ do
it "encodes and parses random JSON paths" $
withMaxSuccess 1000 $
forAll (resize 20 generateJSONPath) $ \jsonPath ->
let encPath = encodeJSONPath jsonPath
parsedJSONPathE = parseJSONPath encPath
in case parsedJSONPathE of
Left err -> counterexample (T.unpack (err <> ": " <> encPath)) False
Right parsedJSONPath -> property $ parsedJSONPath === jsonPath
generateJSONPath :: Gen JSONPath
generateJSONPath = map (either id id) <$> listOf1 genPathElementEither
where
genPathElementEither = do
indexLeft <- Left <$> genIndex
keyRight <- Right <$> genKey
elements [indexLeft, keyRight]
genIndex = Index <$> choose (0, 100)
genKey = Key . K.fromText . T.pack <$> listOf1 arbitraryUnicodeChar