Commit 2fd9c3e9 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Add JSON roundtrip tests

parent 775aab73
......@@ -831,6 +831,22 @@ instance Arbitrary Filter where
instance Arbitrary PhyloParam where
arbitrary = pure defaultPhyloParam
instance Arbitrary ComputeTimeHistory where
arbitrary = oneof [ pure NoHistoricalDataAvailable, ComputeTimeHistory . NE.fromList . getNonEmpty <$> arbitrary ]
-- The 'resize' ensure our tests won't take too long as
-- we won't be generating very long lists.
instance Arbitrary Phylo where
arbitrary = Phylo <$> resize 6 arbitrary
<*> resize 6 arbitrary
<*> resize 6 arbitrary
<*> resize 6 arbitrary
<*> resize 6 arbitrary
<*> resize 6 arbitrary
<*> resize 6 arbitrary
<*> resize 6 arbitrary
<*> resize 6 arbitrary
--
-- Functions that uses the lenses
--
......
......@@ -17,19 +17,20 @@ Portability : POSIX
module Gargantext.Utils.UTCTime where
import Data.Fixed (Fixed(..))
import Data.Morpheus.Kind (SCALAR)
import Data.Morpheus.Types (GQLType(..), DecodeScalar(..), EncodeScalar(..))
import Data.Morpheus.Types qualified as DMT
import Data.String (fromString)
import Data.Swagger (ToSchema (..))
import Data.Text qualified as T
import Data.Time (UTCTime, nominalDiffTimeToSeconds)
import Data.Time.Clock.POSIX (getPOSIXTime, POSIXTime)
import Data.Time (UTCTime, nominalDiffTimeToSeconds)
import Data.TreeDiff.Class
import Gargantext.Prelude
import Gargantext.System.Logging
import Prelude (String)
import Data.TreeDiff.Class
import Data.Fixed (Fixed(..))
import Test.QuickCheck hiding (label)
newtype NUTCTime = NUTCTime UTCTime
......@@ -61,6 +62,9 @@ instance ToExpr ElapsedSeconds where
instance ToSchema ElapsedSeconds where
declareNamedSchema _ = declareNamedSchema (Proxy @Int)
instance Arbitrary ElapsedSeconds where
arbitrary = ElapsedSeconds . fromInteger . getPositive <$> arbitrary
timeMeasured :: (MonadLogger m, MonadBase IO m, HasCallStack)
=> String
-- ^ A label
......
......@@ -6,14 +6,15 @@
module Test.Offline.JSON (tests) where
import Data.Aeson
import Data.ByteString qualified as B
import Data.ByteString.Lazy.Char8 qualified as C8
import Data.ByteString qualified as B
import Data.Either
import Gargantext.API.Errors
import Gargantext.API.Node.Corpus.Types
import Gargantext.API.Node.Types
import Gargantext.API.Viz.Types
import Gargantext.Core.Types.Phylo
import qualified Gargantext.Core.Viz.Phylo as VizPhylo
import Gargantext.Database.Admin.Types.Node
import Paths_gargantext
import Prelude
......@@ -62,6 +63,8 @@ tests = testGroup "JSON" [
, testProperty "GraphDataData" (jsonRoundtrip @GraphDataData)
, testProperty "ObjectData" (jsonRoundtrip @ObjectData)
, testProperty "PhyloData" (jsonRoundtrip @PhyloData)
, testProperty "ComputeTimeHistory" (jsonRoundtrip @VizPhylo.ComputeTimeHistory)
, testProperty "Phylo" (jsonRoundtrip @VizPhylo.Phylo)
, testProperty "LayerData" (jsonRoundtrip @LayerData)
, testCase "can parse bpa_phylo_test.json" testParseBpaPhylo
, testCase "can parse open_science.json" testOpenSciencePhylo
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment