{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Core.Viz.Types where
import Data.Aeson.TH (deriveJSON)
import Data.Swagger
import Data.Vector (Vector)
import qualified Data.Vector as V
import Protolude
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
data Chart = ChartHisto | ChartScatter | ChartPie
deriving ((forall x. Chart -> Rep Chart x)
-> (forall x. Rep Chart x -> Chart) -> Generic Chart
forall x. Rep Chart x -> Chart
forall x. Chart -> Rep Chart x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Chart x -> Chart
$cfrom :: forall x. Chart -> Rep Chart x
Generic)
data Histo = Histo { Histo -> Vector Text
histo_dates :: !(Vector Text)
, Histo -> Vector Int
histo_count :: !(Vector Int)
}
deriving (Int -> Histo -> ShowS
[Histo] -> ShowS
Histo -> String
(Int -> Histo -> ShowS)
-> (Histo -> String) -> ([Histo] -> ShowS) -> Show Histo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Histo] -> ShowS
$cshowList :: [Histo] -> ShowS
show :: Histo -> String
$cshow :: Histo -> String
showsPrec :: Int -> Histo -> ShowS
$cshowsPrec :: Int -> Histo -> ShowS
Show, (forall x. Histo -> Rep Histo x)
-> (forall x. Rep Histo x -> Histo) -> Generic Histo
forall x. Rep Histo x -> Histo
forall x. Histo -> Rep Histo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Histo x -> Histo
$cfrom :: forall x. Histo -> Rep Histo x
Generic)
instance ToSchema Histo where
declareNamedSchema :: Proxy Histo -> Declare (Definitions Schema) NamedSchema
declareNamedSchema = SchemaOptions
-> Proxy Histo -> Declare (Definitions Schema) NamedSchema
forall a.
(Generic a, GToSchema (Rep a),
TypeHasSimpleShape a "genericDeclareNamedSchemaUnrestricted") =>
SchemaOptions
-> Proxy a -> Declare (Definitions Schema) NamedSchema
genericDeclareNamedSchema (String -> SchemaOptions
unPrefixSwagger String
"histo_")
instance Arbitrary Histo
where
arbitrary :: Gen Histo
arbitrary = [Histo] -> Gen Histo
forall a. [a] -> Gen a
elements [ Vector Text -> Vector Int -> Histo
Histo (Text -> Vector Text
forall a. a -> Vector a
V.singleton Text
"2012") (Int -> Vector Int
forall a. a -> Vector a
V.singleton Int
1)
, Vector Text -> Vector Int -> Histo
Histo (Text -> Vector Text
forall a. a -> Vector a
V.singleton Text
"2013") (Int -> Vector Int
forall a. a -> Vector a
V.singleton Int
1)
]
deriveJSON (unPrefix "histo_") ''Histo