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
12 import Gargantext.Core.Types.Phylo
13 import Gargantext.Core.Viz.Phylo.API
16 import Test.Tasty.HUnit
17 import Test.Tasty.QuickCheck
18 import Text.RawString.QQ
19 import qualified Data.ByteString.Lazy.Char8 as C8
21 jsonRoundtrip :: (Show a, FromJSON a, ToJSON a, Eq a) => a -> Property
23 counterexample ("Parsed JSON: " <> C8.unpack (encode a)) $ eitherDecode (encode a) === Right a
26 tests = testGroup "JSON" [
27 testProperty "Datafield roundtrips" (jsonRoundtrip @Datafield)
28 , testProperty "WithQuery roundtrips" (jsonRoundtrip @WithQuery)
29 , testCase "WithQuery frontend compliance" testWithQueryFrontend
31 testProperty "PeriodToNode" (jsonRoundtrip @PeriodToNodeData)
32 , testProperty "GraphData" (jsonRoundtrip @GraphData)
33 , testProperty "GraphDataData" (jsonRoundtrip @GraphDataData)
34 , testProperty "ObjectData" (jsonRoundtrip @ObjectData)
35 , testProperty "PhyloData" (jsonRoundtrip @PhyloData)
39 testWithQueryFrontend :: Assertion
40 testWithQueryFrontend = do
41 assertBool "JSON instance will break frontend!"
42 (isRight $ eitherDecode @WithQuery (C8.pack cannedWithQueryPayload))
44 -- The aim of this type is to catch regressions in the frontend serialisation; this
45 -- is what the frontend currently expects, and therefore if we were to change the JSON
46 -- instances, this test would fail, and we will be notified.
47 cannedWithQueryPayload :: String
48 cannedWithQueryPayload = [r| {"query":"Haskell","node_id":138,"lang":"EN","flowListWith":{"type":"MyListsFirst"},"datafield":"External Arxiv","databases":"Arxiv"} |]