Commit 2e3c3122 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[metrics] add missing G.D.A.T.Metrics module

parent 68ff5f8b
Pipeline #869 failed with stage
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Admin.Types.Metrics where
import Control.Lens hiding (elements, (&))
import Data.Aeson
import Data.Aeson.TH (deriveJSON)
import Data.Swagger
import GHC.Generics (Generic)
import Data.Text (Text, unpack)
import Test.QuickCheck.Arbitrary
import Gargantext.Core.Types (ListType(..))
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
----------------------------------------------------------------------------
data Metrics = Metrics
{ metrics_data :: [Metric]}
deriving (Generic, Show)
instance ToSchema Metrics where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "metrics_")
instance Arbitrary Metrics
where
arbitrary = Metrics <$> arbitrary
data Metric = Metric
{ m_label :: !Text
, m_x :: !Double
, m_y :: !Double
, m_cat :: !ListType
} deriving (Generic, Show)
instance ToSchema Metric where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "m_")
instance Arbitrary Metric
where
arbitrary = Metric <$> arbitrary
<*> arbitrary
<*> arbitrary
<*> arbitrary
deriveJSON (unPrefix "metrics_") ''Metrics
deriveJSON (unPrefix "m_") ''Metric
data ChartMetrics a = ChartMetrics { chartMetrics_data :: a }
deriving (Generic, Show)
instance (ToSchema a) => ToSchema (ChartMetrics a) where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "chartMetrics_")
instance (Arbitrary a) => Arbitrary (ChartMetrics a)
where
arbitrary = ChartMetrics <$> arbitrary
deriveJSON (unPrefix "chartMetrics_") ''ChartMetrics
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