2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE TypeApplications #-}
4 {-# LANGUAGE QuasiQuotes #-}
6 module Offline.JSON (tests) where
10 import Gargantext.API.Node.Corpus.New
11 import Gargantext.API.Node.Corpus.Types
14 import Test.Tasty.HUnit
15 import Test.Tasty.QuickCheck
16 import Text.RawString.QQ
17 import qualified Data.ByteString.Lazy.Char8 as C8
19 jsonRoundtrip :: (Show a, FromJSON a, ToJSON a, Eq a) => a -> Property
20 jsonRoundtrip a = eitherDecode (encode a) === Right a
23 tests = testGroup "JSON" [
24 testProperty "Datafield roundtrips" (jsonRoundtrip @Datafield)
25 , testProperty "WithQuery roundtrips" (jsonRoundtrip @WithQuery)
26 , testCase "WithQuery frontend compliance" testWithQueryFrontend
29 testWithQueryFrontend :: Assertion
30 testWithQueryFrontend = do
31 assertBool "JSON instance will break frontend!"
32 (isRight $ eitherDecode @WithQuery (C8.pack cannedWithQueryPayload))
34 -- The aim of this type is to catch regressions in the frontend serialisation; this
35 -- is what the frontend currently expects, and therefore if we were to change the JSON
36 -- instances, this test would fail, and we will be notified.
37 cannedWithQueryPayload :: String
38 cannedWithQueryPayload = [r| {"query":"Haskell","node_id":138,"lang":"EN","flowListWith":{"type":"MyListsFirst"},"datafield":"External Arxiv","databases":"Arxiv"} |]