]> Git — Sourcephile - gargantext.git/blob - src-test/Offline/JSON.hs
Partial support for bidirectional PhyloData parsing
[gargantext.git] / src-test / Offline / JSON.hs
1
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE TypeApplications #-}
4 {-# LANGUAGE QuasiQuotes #-}
5
6 module Offline.JSON (tests) where
7
8 import Data.Aeson
9 import Data.Either
10 import Gargantext.API.Node.Corpus.New
11 import Gargantext.API.Node.Corpus.Types
12 import Gargantext.Core.Viz.Phylo.API
13 import Prelude
14 import Test.Tasty
15 import Test.Tasty.HUnit
16 import Test.Tasty.QuickCheck
17 import Text.RawString.QQ
18 import qualified Data.ByteString.Lazy.Char8 as C8
19
20 jsonRoundtrip :: (Show a, FromJSON a, ToJSON a, Eq a) => a -> Property
21 jsonRoundtrip a = eitherDecode (encode a) === Right a
22
23 tests :: TestTree
24 tests = testGroup "JSON" [
25 testProperty "Datafield roundtrips" (jsonRoundtrip @Datafield)
26 , testProperty "WithQuery roundtrips" (jsonRoundtrip @WithQuery)
27 , testCase "WithQuery frontend compliance" testWithQueryFrontend
28 , testGroup "Phylo" [
29 testProperty "PhyloData" (jsonRoundtrip @PhyloData)
30 ]
31 ]
32
33 testWithQueryFrontend :: Assertion
34 testWithQueryFrontend = do
35 assertBool "JSON instance will break frontend!"
36 (isRight $ eitherDecode @WithQuery (C8.pack cannedWithQueryPayload))
37
38 -- The aim of this type is to catch regressions in the frontend serialisation; this
39 -- is what the frontend currently expects, and therefore if we were to change the JSON
40 -- instances, this test would fail, and we will be notified.
41 cannedWithQueryPayload :: String
42 cannedWithQueryPayload = [r| {"query":"Haskell","node_id":138,"lang":"EN","flowListWith":{"type":"MyListsFirst"},"datafield":"External Arxiv","databases":"Arxiv"} |]