{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}

{- |
Module      : Unleash.Internal.JsonTypes
Copyright   : Copyright © FINN.no AS, Inc. All rights reserved.
License     : MIT
Stability   : experimental

Unleash domain transfer objects.
-}
module Unleash.Internal.JsonTypes (
    Features (..),
    Feature (..),
    Strategy (..),
    Constraint (..),
    Variant (..),
    Payload (..),
    Override (..),
    Context (..),
    emptyContext,
    Segment (..),
    VariantResponse (..),
    emptyVariantResponse,
    MetricsPayload (..),
    FullMetricsPayload (..),
    FullMetricsBucket (..),
    YesAndNoes (..),
    FullRegisterPayload (..),
    RegisterPayload (..),
) where

import Data.Aeson (FromJSON, Options (..), ToJSON (toJSON), defaultOptions, genericParseJSON, genericToJSON)
import Data.Aeson.Types (parseJSON)
import Data.Map.Strict (Map)
import Data.Text (Text)
import Data.Time (UTCTime)
import GHC.Generics (Generic)

-- | Feature toggle set.
data Features = Features
    { Features -> Int
version :: Int,
      Features -> [Feature]
features :: [Feature],
      Features -> Maybe [Segment]
segments :: Maybe [Segment]
    }
    deriving stock (Features -> Features -> Bool
(Features -> Features -> Bool)
-> (Features -> Features -> Bool) -> Eq Features
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Features -> Features -> Bool
$c/= :: Features -> Features -> Bool
== :: Features -> Features -> Bool
$c== :: Features -> Features -> Bool
Eq, Int -> Features -> ShowS
[Features] -> ShowS
Features -> String
(Int -> Features -> ShowS)
-> (Features -> String) -> ([Features] -> ShowS) -> Show Features
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Features] -> ShowS
$cshowList :: [Features] -> ShowS
show :: Features -> String
$cshow :: Features -> String
showsPrec :: Int -> Features -> ShowS
$cshowsPrec :: Int -> Features -> ShowS
Show, (forall x. Features -> Rep Features x)
-> (forall x. Rep Features x -> Features) -> Generic Features
forall x. Rep Features x -> Features
forall x. Features -> Rep Features x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Features x -> Features
$cfrom :: forall x. Features -> Rep Features x
Generic)
    deriving anyclass (Value -> Parser [Features]
Value -> Parser Features
(Value -> Parser Features)
-> (Value -> Parser [Features]) -> FromJSON Features
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Features]
$cparseJSONList :: Value -> Parser [Features]
parseJSON :: Value -> Parser Features
$cparseJSON :: Value -> Parser Features
FromJSON, [Features] -> Encoding
[Features] -> Value
Features -> Encoding
Features -> Value
(Features -> Value)
-> (Features -> Encoding)
-> ([Features] -> Value)
-> ([Features] -> Encoding)
-> ToJSON Features
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Features] -> Encoding
$ctoEncodingList :: [Features] -> Encoding
toJSONList :: [Features] -> Value
$ctoJSONList :: [Features] -> Value
toEncoding :: Features -> Encoding
$ctoEncoding :: Features -> Encoding
toJSON :: Features -> Value
$ctoJSON :: Features -> Value
ToJSON)

-- | Feature toggle.
data Feature = Feature
    { Feature -> Text
name :: Text,
      Feature -> Maybe Text
description :: Maybe Text,
      Feature -> Bool
enabled :: Bool,
      Feature -> [Strategy]
strategies :: [Strategy],
      Feature -> Maybe [Variant]
variants :: Maybe [Variant]
    }
    deriving stock (Feature -> Feature -> Bool
(Feature -> Feature -> Bool)
-> (Feature -> Feature -> Bool) -> Eq Feature
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Feature -> Feature -> Bool
$c/= :: Feature -> Feature -> Bool
== :: Feature -> Feature -> Bool
$c== :: Feature -> Feature -> Bool
Eq, Int -> Feature -> ShowS
[Feature] -> ShowS
Feature -> String
(Int -> Feature -> ShowS)
-> (Feature -> String) -> ([Feature] -> ShowS) -> Show Feature
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Feature] -> ShowS
$cshowList :: [Feature] -> ShowS
show :: Feature -> String
$cshow :: Feature -> String
showsPrec :: Int -> Feature -> ShowS
$cshowsPrec :: Int -> Feature -> ShowS
Show, (forall x. Feature -> Rep Feature x)
-> (forall x. Rep Feature x -> Feature) -> Generic Feature
forall x. Rep Feature x -> Feature
forall x. Feature -> Rep Feature x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Feature x -> Feature
$cfrom :: forall x. Feature -> Rep Feature x
Generic)
    deriving anyclass (Value -> Parser [Feature]
Value -> Parser Feature
(Value -> Parser Feature)
-> (Value -> Parser [Feature]) -> FromJSON Feature
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Feature]
$cparseJSONList :: Value -> Parser [Feature]
parseJSON :: Value -> Parser Feature
$cparseJSON :: Value -> Parser Feature
FromJSON, [Feature] -> Encoding
[Feature] -> Value
Feature -> Encoding
Feature -> Value
(Feature -> Value)
-> (Feature -> Encoding)
-> ([Feature] -> Value)
-> ([Feature] -> Encoding)
-> ToJSON Feature
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Feature] -> Encoding
$ctoEncodingList :: [Feature] -> Encoding
toJSONList :: [Feature] -> Value
$ctoJSONList :: [Feature] -> Value
toEncoding :: Feature -> Encoding
$ctoEncoding :: Feature -> Encoding
toJSON :: Feature -> Value
$ctoJSON :: Feature -> Value
ToJSON)

-- | Strategy. Encompasses all (supported) types of strategies.
data Strategy = Strategy
    { Strategy -> Text
name :: Text,
      Strategy -> Maybe (Map Text Text)
parameters :: Maybe (Map Text Text),
      Strategy -> Maybe [Constraint]
constraints :: Maybe [Constraint],
      Strategy -> Maybe [Int]
segments :: Maybe [Int]
    }
    deriving stock (Strategy -> Strategy -> Bool
(Strategy -> Strategy -> Bool)
-> (Strategy -> Strategy -> Bool) -> Eq Strategy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Strategy -> Strategy -> Bool
$c/= :: Strategy -> Strategy -> Bool
== :: Strategy -> Strategy -> Bool
$c== :: Strategy -> Strategy -> Bool
Eq, Int -> Strategy -> ShowS
[Strategy] -> ShowS
Strategy -> String
(Int -> Strategy -> ShowS)
-> (Strategy -> String) -> ([Strategy] -> ShowS) -> Show Strategy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Strategy] -> ShowS
$cshowList :: [Strategy] -> ShowS
show :: Strategy -> String
$cshow :: Strategy -> String
showsPrec :: Int -> Strategy -> ShowS
$cshowsPrec :: Int -> Strategy -> ShowS
Show, (forall x. Strategy -> Rep Strategy x)
-> (forall x. Rep Strategy x -> Strategy) -> Generic Strategy
forall x. Rep Strategy x -> Strategy
forall x. Strategy -> Rep Strategy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Strategy x -> Strategy
$cfrom :: forall x. Strategy -> Rep Strategy x
Generic)
    deriving anyclass (Value -> Parser [Strategy]
Value -> Parser Strategy
(Value -> Parser Strategy)
-> (Value -> Parser [Strategy]) -> FromJSON Strategy
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Strategy]
$cparseJSONList :: Value -> Parser [Strategy]
parseJSON :: Value -> Parser Strategy
$cparseJSON :: Value -> Parser Strategy
FromJSON, [Strategy] -> Encoding
[Strategy] -> Value
Strategy -> Encoding
Strategy -> Value
(Strategy -> Value)
-> (Strategy -> Encoding)
-> ([Strategy] -> Value)
-> ([Strategy] -> Encoding)
-> ToJSON Strategy
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Strategy] -> Encoding
$ctoEncodingList :: [Strategy] -> Encoding
toJSONList :: [Strategy] -> Value
$ctoJSONList :: [Strategy] -> Value
toEncoding :: Strategy -> Encoding
$ctoEncoding :: Strategy -> Encoding
toJSON :: Strategy -> Value
$ctoJSON :: Strategy -> Value
ToJSON)

-- | Strategy constraint.
data Constraint = Constraint
    { Constraint -> Text
contextName :: Text,
      Constraint -> Text
operator :: Text,
      Constraint -> Maybe [Text]
values :: Maybe [Text],
      Constraint -> Maybe Bool
caseInsensitive :: Maybe Bool,
      Constraint -> Maybe Bool
inverted :: Maybe Bool,
      Constraint -> Maybe Text
value :: Maybe Text
    }
    deriving stock (Constraint -> Constraint -> Bool
(Constraint -> Constraint -> Bool)
-> (Constraint -> Constraint -> Bool) -> Eq Constraint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Constraint -> Constraint -> Bool
$c/= :: Constraint -> Constraint -> Bool
== :: Constraint -> Constraint -> Bool
$c== :: Constraint -> Constraint -> Bool
Eq, Int -> Constraint -> ShowS
[Constraint] -> ShowS
Constraint -> String
(Int -> Constraint -> ShowS)
-> (Constraint -> String)
-> ([Constraint] -> ShowS)
-> Show Constraint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Constraint] -> ShowS
$cshowList :: [Constraint] -> ShowS
show :: Constraint -> String
$cshow :: Constraint -> String
showsPrec :: Int -> Constraint -> ShowS
$cshowsPrec :: Int -> Constraint -> ShowS
Show, (forall x. Constraint -> Rep Constraint x)
-> (forall x. Rep Constraint x -> Constraint) -> Generic Constraint
forall x. Rep Constraint x -> Constraint
forall x. Constraint -> Rep Constraint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Constraint x -> Constraint
$cfrom :: forall x. Constraint -> Rep Constraint x
Generic)
    deriving anyclass (Value -> Parser [Constraint]
Value -> Parser Constraint
(Value -> Parser Constraint)
-> (Value -> Parser [Constraint]) -> FromJSON Constraint
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Constraint]
$cparseJSONList :: Value -> Parser [Constraint]
parseJSON :: Value -> Parser Constraint
$cparseJSON :: Value -> Parser Constraint
FromJSON, [Constraint] -> Encoding
[Constraint] -> Value
Constraint -> Encoding
Constraint -> Value
(Constraint -> Value)
-> (Constraint -> Encoding)
-> ([Constraint] -> Value)
-> ([Constraint] -> Encoding)
-> ToJSON Constraint
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Constraint] -> Encoding
$ctoEncodingList :: [Constraint] -> Encoding
toJSONList :: [Constraint] -> Value
$ctoJSONList :: [Constraint] -> Value
toEncoding :: Constraint -> Encoding
$ctoEncoding :: Constraint -> Encoding
toJSON :: Constraint -> Value
$ctoJSON :: Constraint -> Value
ToJSON)

-- | Variant.
data Variant = Variant
    { Variant -> Text
name :: Text,
      Variant -> Maybe Payload
payload :: Maybe Payload,
      Variant -> Int
weight :: Int,
      Variant -> Maybe Text
stickiness :: Maybe Text,
      Variant -> Maybe [Override]
overrides :: Maybe [Override]
    }
    deriving stock (Variant -> Variant -> Bool
(Variant -> Variant -> Bool)
-> (Variant -> Variant -> Bool) -> Eq Variant
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Variant -> Variant -> Bool
$c/= :: Variant -> Variant -> Bool
== :: Variant -> Variant -> Bool
$c== :: Variant -> Variant -> Bool
Eq, Int -> Variant -> ShowS
[Variant] -> ShowS
Variant -> String
(Int -> Variant -> ShowS)
-> (Variant -> String) -> ([Variant] -> ShowS) -> Show Variant
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Variant] -> ShowS
$cshowList :: [Variant] -> ShowS
show :: Variant -> String
$cshow :: Variant -> String
showsPrec :: Int -> Variant -> ShowS
$cshowsPrec :: Int -> Variant -> ShowS
Show, (forall x. Variant -> Rep Variant x)
-> (forall x. Rep Variant x -> Variant) -> Generic Variant
forall x. Rep Variant x -> Variant
forall x. Variant -> Rep Variant x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Variant x -> Variant
$cfrom :: forall x. Variant -> Rep Variant x
Generic)
    deriving anyclass (Value -> Parser [Variant]
Value -> Parser Variant
(Value -> Parser Variant)
-> (Value -> Parser [Variant]) -> FromJSON Variant
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Variant]
$cparseJSONList :: Value -> Parser [Variant]
parseJSON :: Value -> Parser Variant
$cparseJSON :: Value -> Parser Variant
FromJSON, [Variant] -> Encoding
[Variant] -> Value
Variant -> Encoding
Variant -> Value
(Variant -> Value)
-> (Variant -> Encoding)
-> ([Variant] -> Value)
-> ([Variant] -> Encoding)
-> ToJSON Variant
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Variant] -> Encoding
$ctoEncodingList :: [Variant] -> Encoding
toJSONList :: [Variant] -> Value
$ctoJSONList :: [Variant] -> Value
toEncoding :: Variant -> Encoding
$ctoEncoding :: Variant -> Encoding
toJSON :: Variant -> Value
$ctoJSON :: Variant -> Value
ToJSON)

typeWorkAroundOptions :: Options
typeWorkAroundOptions :: Options
typeWorkAroundOptions =
    Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
typeWorkaround}
    where
        typeWorkaround :: String -> String
        typeWorkaround :: ShowS
typeWorkaround String
s = case String
s of
            String
"type" -> String
"type_"
            String
"type_" -> String
"type"
            String
_ -> String
s

-- | Variant payload.
data Payload = Payload
    { -- | Payload type.
      Payload -> Text
type_ :: Text,
      -- | Payload.
      Payload -> Text
value :: Text
    }
    deriving stock (Payload -> Payload -> Bool
(Payload -> Payload -> Bool)
-> (Payload -> Payload -> Bool) -> Eq Payload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Payload -> Payload -> Bool
$c/= :: Payload -> Payload -> Bool
== :: Payload -> Payload -> Bool
$c== :: Payload -> Payload -> Bool
Eq, Int -> Payload -> ShowS
[Payload] -> ShowS
Payload -> String
(Int -> Payload -> ShowS)
-> (Payload -> String) -> ([Payload] -> ShowS) -> Show Payload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Payload] -> ShowS
$cshowList :: [Payload] -> ShowS
show :: Payload -> String
$cshow :: Payload -> String
showsPrec :: Int -> Payload -> ShowS
$cshowsPrec :: Int -> Payload -> ShowS
Show, (forall x. Payload -> Rep Payload x)
-> (forall x. Rep Payload x -> Payload) -> Generic Payload
forall x. Rep Payload x -> Payload
forall x. Payload -> Rep Payload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Payload x -> Payload
$cfrom :: forall x. Payload -> Rep Payload x
Generic)

instance FromJSON Payload where
    parseJSON :: Value -> Parser Payload
parseJSON = Options -> Value -> Parser Payload
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
typeWorkAroundOptions

instance ToJSON Payload where
    toJSON :: Payload -> Value
toJSON = Options -> Payload -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
typeWorkAroundOptions

-- | Contextual override.
data Override = Override
    { Override -> Text
contextName :: Text,
      Override -> [Text]
values :: [Text]
    }
    deriving stock (Override -> Override -> Bool
(Override -> Override -> Bool)
-> (Override -> Override -> Bool) -> Eq Override
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Override -> Override -> Bool
$c/= :: Override -> Override -> Bool
== :: Override -> Override -> Bool
$c== :: Override -> Override -> Bool
Eq, Int -> Override -> ShowS
[Override] -> ShowS
Override -> String
(Int -> Override -> ShowS)
-> (Override -> String) -> ([Override] -> ShowS) -> Show Override
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Override] -> ShowS
$cshowList :: [Override] -> ShowS
show :: Override -> String
$cshow :: Override -> String
showsPrec :: Int -> Override -> ShowS
$cshowsPrec :: Int -> Override -> ShowS
Show, (forall x. Override -> Rep Override x)
-> (forall x. Rep Override x -> Override) -> Generic Override
forall x. Rep Override x -> Override
forall x. Override -> Rep Override x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Override x -> Override
$cfrom :: forall x. Override -> Rep Override x
Generic)
    deriving anyclass (Value -> Parser [Override]
Value -> Parser Override
(Value -> Parser Override)
-> (Value -> Parser [Override]) -> FromJSON Override
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Override]
$cparseJSONList :: Value -> Parser [Override]
parseJSON :: Value -> Parser Override
$cparseJSON :: Value -> Parser Override
FromJSON, [Override] -> Encoding
[Override] -> Value
Override -> Encoding
Override -> Value
(Override -> Value)
-> (Override -> Encoding)
-> ([Override] -> Value)
-> ([Override] -> Encoding)
-> ToJSON Override
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Override] -> Encoding
$ctoEncodingList :: [Override] -> Encoding
toJSONList :: [Override] -> Value
$ctoJSONList :: [Override] -> Value
toEncoding :: Override -> Encoding
$ctoEncoding :: Override -> Encoding
toJSON :: Override -> Value
$ctoJSON :: Override -> Value
ToJSON)

-- | Client context.
data Context = Context
    { -- | User ID.
      Context -> Maybe Text
userId :: Maybe Text,
      -- | Session ID.
      Context -> Maybe Text
sessionId :: Maybe Text,
      -- | Remote address.
      Context -> Maybe Text
remoteAddress :: Maybe Text,
      -- | Current UTC time.
      Context -> Maybe Text
currentTime :: Maybe Text,
      -- | Application environment (e.g. @Production@).
      Context -> Maybe Text
environment :: Maybe Text,
      -- | Application name.
      Context -> Maybe Text
appName :: Maybe Text,
      -- | Other custom properties.
      Context -> Maybe (Map Text (Maybe Text))
properties :: Maybe (Map Text (Maybe Text))
    }
    deriving stock (Context -> Context -> Bool
(Context -> Context -> Bool)
-> (Context -> Context -> Bool) -> Eq Context
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Context -> Context -> Bool
$c/= :: Context -> Context -> Bool
== :: Context -> Context -> Bool
$c== :: Context -> Context -> Bool
Eq, Int -> Context -> ShowS
[Context] -> ShowS
Context -> String
(Int -> Context -> ShowS)
-> (Context -> String) -> ([Context] -> ShowS) -> Show Context
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Context] -> ShowS
$cshowList :: [Context] -> ShowS
show :: Context -> String
$cshow :: Context -> String
showsPrec :: Int -> Context -> ShowS
$cshowsPrec :: Int -> Context -> ShowS
Show, (forall x. Context -> Rep Context x)
-> (forall x. Rep Context x -> Context) -> Generic Context
forall x. Rep Context x -> Context
forall x. Context -> Rep Context x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Context x -> Context
$cfrom :: forall x. Context -> Rep Context x
Generic)
    deriving anyclass (Value -> Parser [Context]
Value -> Parser Context
(Value -> Parser Context)
-> (Value -> Parser [Context]) -> FromJSON Context
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Context]
$cparseJSONList :: Value -> Parser [Context]
parseJSON :: Value -> Parser Context
$cparseJSON :: Value -> Parser Context
FromJSON, [Context] -> Encoding
[Context] -> Value
Context -> Encoding
Context -> Value
(Context -> Value)
-> (Context -> Encoding)
-> ([Context] -> Value)
-> ([Context] -> Encoding)
-> ToJSON Context
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Context] -> Encoding
$ctoEncodingList :: [Context] -> Encoding
toJSONList :: [Context] -> Value
$ctoJSONList :: [Context] -> Value
toEncoding :: Context -> Encoding
$ctoEncoding :: Context -> Encoding
toJSON :: Context -> Value
$ctoJSON :: Context -> Value
ToJSON)

-- | An initial client context.
emptyContext :: Context
emptyContext :: Context
emptyContext = Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe (Map Text (Maybe Text))
-> Context
Context Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe (Map Text (Maybe Text))
forall a. Maybe a
Nothing

-- | Segment.
data Segment = Segment
    { Segment -> Int
id :: Int,
      Segment -> [Constraint]
constraints :: [Constraint]
    }
    deriving stock (Segment -> Segment -> Bool
(Segment -> Segment -> Bool)
-> (Segment -> Segment -> Bool) -> Eq Segment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Segment -> Segment -> Bool
$c/= :: Segment -> Segment -> Bool
== :: Segment -> Segment -> Bool
$c== :: Segment -> Segment -> Bool
Eq, Int -> Segment -> ShowS
[Segment] -> ShowS
Segment -> String
(Int -> Segment -> ShowS)
-> (Segment -> String) -> ([Segment] -> ShowS) -> Show Segment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Segment] -> ShowS
$cshowList :: [Segment] -> ShowS
show :: Segment -> String
$cshow :: Segment -> String
showsPrec :: Int -> Segment -> ShowS
$cshowsPrec :: Int -> Segment -> ShowS
Show, (forall x. Segment -> Rep Segment x)
-> (forall x. Rep Segment x -> Segment) -> Generic Segment
forall x. Rep Segment x -> Segment
forall x. Segment -> Rep Segment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Segment x -> Segment
$cfrom :: forall x. Segment -> Rep Segment x
Generic)
    deriving anyclass (Value -> Parser [Segment]
Value -> Parser Segment
(Value -> Parser Segment)
-> (Value -> Parser [Segment]) -> FromJSON Segment
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Segment]
$cparseJSONList :: Value -> Parser [Segment]
parseJSON :: Value -> Parser Segment
$cparseJSON :: Value -> Parser Segment
FromJSON, [Segment] -> Encoding
[Segment] -> Value
Segment -> Encoding
Segment -> Value
(Segment -> Value)
-> (Segment -> Encoding)
-> ([Segment] -> Value)
-> ([Segment] -> Encoding)
-> ToJSON Segment
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Segment] -> Encoding
$ctoEncodingList :: [Segment] -> Encoding
toJSONList :: [Segment] -> Value
$ctoJSONList :: [Segment] -> Value
toEncoding :: Segment -> Encoding
$ctoEncoding :: Segment -> Encoding
toJSON :: Segment -> Value
$ctoJSON :: Segment -> Value
ToJSON)

-- | Variant response.
data VariantResponse = VariantResponse
    { -- | Variant name.
      VariantResponse -> Text
name :: Text,
      -- | Variant payload.
      VariantResponse -> Maybe Payload
payload :: Maybe Payload,
      -- | Variant state.
      VariantResponse -> Bool
enabled :: Bool
    }
    deriving stock (VariantResponse -> VariantResponse -> Bool
(VariantResponse -> VariantResponse -> Bool)
-> (VariantResponse -> VariantResponse -> Bool)
-> Eq VariantResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariantResponse -> VariantResponse -> Bool
$c/= :: VariantResponse -> VariantResponse -> Bool
== :: VariantResponse -> VariantResponse -> Bool
$c== :: VariantResponse -> VariantResponse -> Bool
Eq, Int -> VariantResponse -> ShowS
[VariantResponse] -> ShowS
VariantResponse -> String
(Int -> VariantResponse -> ShowS)
-> (VariantResponse -> String)
-> ([VariantResponse] -> ShowS)
-> Show VariantResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VariantResponse] -> ShowS
$cshowList :: [VariantResponse] -> ShowS
show :: VariantResponse -> String
$cshow :: VariantResponse -> String
showsPrec :: Int -> VariantResponse -> ShowS
$cshowsPrec :: Int -> VariantResponse -> ShowS
Show, (forall x. VariantResponse -> Rep VariantResponse x)
-> (forall x. Rep VariantResponse x -> VariantResponse)
-> Generic VariantResponse
forall x. Rep VariantResponse x -> VariantResponse
forall x. VariantResponse -> Rep VariantResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VariantResponse x -> VariantResponse
$cfrom :: forall x. VariantResponse -> Rep VariantResponse x
Generic)
    deriving anyclass (Value -> Parser [VariantResponse]
Value -> Parser VariantResponse
(Value -> Parser VariantResponse)
-> (Value -> Parser [VariantResponse]) -> FromJSON VariantResponse
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [VariantResponse]
$cparseJSONList :: Value -> Parser [VariantResponse]
parseJSON :: Value -> Parser VariantResponse
$cparseJSON :: Value -> Parser VariantResponse
FromJSON, [VariantResponse] -> Encoding
[VariantResponse] -> Value
VariantResponse -> Encoding
VariantResponse -> Value
(VariantResponse -> Value)
-> (VariantResponse -> Encoding)
-> ([VariantResponse] -> Value)
-> ([VariantResponse] -> Encoding)
-> ToJSON VariantResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [VariantResponse] -> Encoding
$ctoEncodingList :: [VariantResponse] -> Encoding
toJSONList :: [VariantResponse] -> Value
$ctoJSONList :: [VariantResponse] -> Value
toEncoding :: VariantResponse -> Encoding
$ctoEncoding :: VariantResponse -> Encoding
toJSON :: VariantResponse -> Value
$ctoJSON :: VariantResponse -> Value
ToJSON)

-- | The default (disabled) variant response.
emptyVariantResponse :: VariantResponse
emptyVariantResponse :: VariantResponse
emptyVariantResponse =
    VariantResponse :: Text -> Maybe Payload -> Bool -> VariantResponse
VariantResponse
        { $sel:name:VariantResponse :: Text
name = Text
"disabled",
          $sel:payload:VariantResponse :: Maybe Payload
payload = Maybe Payload
forall a. Maybe a
Nothing,
          $sel:enabled:VariantResponse :: Bool
enabled = Bool
False
        }

-- | Metrics payload.
data MetricsPayload = MetricsPayload
    { -- | Application name.
      MetricsPayload -> Text
appName :: Text,
      -- | Instance identifier (typically hostname).
      MetricsPayload -> Text
instanceId :: Text,
      -- | Start timestamp for this interval.
      MetricsPayload -> UTCTime
start :: UTCTime,
      -- | End timestamp for this interval.
      MetricsPayload -> UTCTime
stop :: UTCTime,
      -- | Feature toggle usage metrics.
      MetricsPayload -> [(Text, Bool)]
toggles :: [(Text, Bool)]
    }
    deriving stock (MetricsPayload -> MetricsPayload -> Bool
(MetricsPayload -> MetricsPayload -> Bool)
-> (MetricsPayload -> MetricsPayload -> Bool) -> Eq MetricsPayload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetricsPayload -> MetricsPayload -> Bool
$c/= :: MetricsPayload -> MetricsPayload -> Bool
== :: MetricsPayload -> MetricsPayload -> Bool
$c== :: MetricsPayload -> MetricsPayload -> Bool
Eq, Int -> MetricsPayload -> ShowS
[MetricsPayload] -> ShowS
MetricsPayload -> String
(Int -> MetricsPayload -> ShowS)
-> (MetricsPayload -> String)
-> ([MetricsPayload] -> ShowS)
-> Show MetricsPayload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MetricsPayload] -> ShowS
$cshowList :: [MetricsPayload] -> ShowS
show :: MetricsPayload -> String
$cshow :: MetricsPayload -> String
showsPrec :: Int -> MetricsPayload -> ShowS
$cshowsPrec :: Int -> MetricsPayload -> ShowS
Show, (forall x. MetricsPayload -> Rep MetricsPayload x)
-> (forall x. Rep MetricsPayload x -> MetricsPayload)
-> Generic MetricsPayload
forall x. Rep MetricsPayload x -> MetricsPayload
forall x. MetricsPayload -> Rep MetricsPayload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MetricsPayload x -> MetricsPayload
$cfrom :: forall x. MetricsPayload -> Rep MetricsPayload x
Generic)

-- | Full metrics payload.
data FullMetricsPayload = FullMetricsPayload
    { FullMetricsPayload -> Text
appName :: Text,
      FullMetricsPayload -> Text
instanceId :: Text,
      FullMetricsPayload -> FullMetricsBucket
bucket :: FullMetricsBucket
    }
    deriving stock (FullMetricsPayload -> FullMetricsPayload -> Bool
(FullMetricsPayload -> FullMetricsPayload -> Bool)
-> (FullMetricsPayload -> FullMetricsPayload -> Bool)
-> Eq FullMetricsPayload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FullMetricsPayload -> FullMetricsPayload -> Bool
$c/= :: FullMetricsPayload -> FullMetricsPayload -> Bool
== :: FullMetricsPayload -> FullMetricsPayload -> Bool
$c== :: FullMetricsPayload -> FullMetricsPayload -> Bool
Eq, Int -> FullMetricsPayload -> ShowS
[FullMetricsPayload] -> ShowS
FullMetricsPayload -> String
(Int -> FullMetricsPayload -> ShowS)
-> (FullMetricsPayload -> String)
-> ([FullMetricsPayload] -> ShowS)
-> Show FullMetricsPayload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FullMetricsPayload] -> ShowS
$cshowList :: [FullMetricsPayload] -> ShowS
show :: FullMetricsPayload -> String
$cshow :: FullMetricsPayload -> String
showsPrec :: Int -> FullMetricsPayload -> ShowS
$cshowsPrec :: Int -> FullMetricsPayload -> ShowS
Show, (forall x. FullMetricsPayload -> Rep FullMetricsPayload x)
-> (forall x. Rep FullMetricsPayload x -> FullMetricsPayload)
-> Generic FullMetricsPayload
forall x. Rep FullMetricsPayload x -> FullMetricsPayload
forall x. FullMetricsPayload -> Rep FullMetricsPayload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FullMetricsPayload x -> FullMetricsPayload
$cfrom :: forall x. FullMetricsPayload -> Rep FullMetricsPayload x
Generic)
    deriving anyclass ([FullMetricsPayload] -> Encoding
[FullMetricsPayload] -> Value
FullMetricsPayload -> Encoding
FullMetricsPayload -> Value
(FullMetricsPayload -> Value)
-> (FullMetricsPayload -> Encoding)
-> ([FullMetricsPayload] -> Value)
-> ([FullMetricsPayload] -> Encoding)
-> ToJSON FullMetricsPayload
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [FullMetricsPayload] -> Encoding
$ctoEncodingList :: [FullMetricsPayload] -> Encoding
toJSONList :: [FullMetricsPayload] -> Value
$ctoJSONList :: [FullMetricsPayload] -> Value
toEncoding :: FullMetricsPayload -> Encoding
$ctoEncoding :: FullMetricsPayload -> Encoding
toJSON :: FullMetricsPayload -> Value
$ctoJSON :: FullMetricsPayload -> Value
ToJSON)

-- | Full metrics bucket.
data FullMetricsBucket = FullMetricsBucket
    { -- | Start timestamp for this interval.
      FullMetricsBucket -> UTCTime
start :: UTCTime,
      -- | End timestamp for this interval.
      FullMetricsBucket -> UTCTime
stop :: UTCTime,
      -- | Feature toggle usage metrics.
      FullMetricsBucket -> Map Text YesAndNoes
toggles :: Map Text YesAndNoes
    }
    deriving stock (FullMetricsBucket -> FullMetricsBucket -> Bool
(FullMetricsBucket -> FullMetricsBucket -> Bool)
-> (FullMetricsBucket -> FullMetricsBucket -> Bool)
-> Eq FullMetricsBucket
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FullMetricsBucket -> FullMetricsBucket -> Bool
$c/= :: FullMetricsBucket -> FullMetricsBucket -> Bool
== :: FullMetricsBucket -> FullMetricsBucket -> Bool
$c== :: FullMetricsBucket -> FullMetricsBucket -> Bool
Eq, Int -> FullMetricsBucket -> ShowS
[FullMetricsBucket] -> ShowS
FullMetricsBucket -> String
(Int -> FullMetricsBucket -> ShowS)
-> (FullMetricsBucket -> String)
-> ([FullMetricsBucket] -> ShowS)
-> Show FullMetricsBucket
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FullMetricsBucket] -> ShowS
$cshowList :: [FullMetricsBucket] -> ShowS
show :: FullMetricsBucket -> String
$cshow :: FullMetricsBucket -> String
showsPrec :: Int -> FullMetricsBucket -> ShowS
$cshowsPrec :: Int -> FullMetricsBucket -> ShowS
Show, (forall x. FullMetricsBucket -> Rep FullMetricsBucket x)
-> (forall x. Rep FullMetricsBucket x -> FullMetricsBucket)
-> Generic FullMetricsBucket
forall x. Rep FullMetricsBucket x -> FullMetricsBucket
forall x. FullMetricsBucket -> Rep FullMetricsBucket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FullMetricsBucket x -> FullMetricsBucket
$cfrom :: forall x. FullMetricsBucket -> Rep FullMetricsBucket x
Generic)
    deriving anyclass ([FullMetricsBucket] -> Encoding
[FullMetricsBucket] -> Value
FullMetricsBucket -> Encoding
FullMetricsBucket -> Value
(FullMetricsBucket -> Value)
-> (FullMetricsBucket -> Encoding)
-> ([FullMetricsBucket] -> Value)
-> ([FullMetricsBucket] -> Encoding)
-> ToJSON FullMetricsBucket
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [FullMetricsBucket] -> Encoding
$ctoEncodingList :: [FullMetricsBucket] -> Encoding
toJSONList :: [FullMetricsBucket] -> Value
$ctoJSONList :: [FullMetricsBucket] -> Value
toEncoding :: FullMetricsBucket -> Encoding
$ctoEncoding :: FullMetricsBucket -> Encoding
toJSON :: FullMetricsBucket -> Value
$ctoJSON :: FullMetricsBucket -> Value
ToJSON)

-- | Helper data structure for metrics.
data YesAndNoes = YesAndNoes
    { -- | The number of times the feature toggle was fetched as enabled in an interval.
      YesAndNoes -> Int
yes :: Int,
      -- | The number of times the feature toggle was fetched as disabled in an interval.
      YesAndNoes -> Int
no :: Int
    }
    deriving stock (YesAndNoes -> YesAndNoes -> Bool
(YesAndNoes -> YesAndNoes -> Bool)
-> (YesAndNoes -> YesAndNoes -> Bool) -> Eq YesAndNoes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: YesAndNoes -> YesAndNoes -> Bool
$c/= :: YesAndNoes -> YesAndNoes -> Bool
== :: YesAndNoes -> YesAndNoes -> Bool
$c== :: YesAndNoes -> YesAndNoes -> Bool
Eq, Int -> YesAndNoes -> ShowS
[YesAndNoes] -> ShowS
YesAndNoes -> String
(Int -> YesAndNoes -> ShowS)
-> (YesAndNoes -> String)
-> ([YesAndNoes] -> ShowS)
-> Show YesAndNoes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [YesAndNoes] -> ShowS
$cshowList :: [YesAndNoes] -> ShowS
show :: YesAndNoes -> String
$cshow :: YesAndNoes -> String
showsPrec :: Int -> YesAndNoes -> ShowS
$cshowsPrec :: Int -> YesAndNoes -> ShowS
Show, (forall x. YesAndNoes -> Rep YesAndNoes x)
-> (forall x. Rep YesAndNoes x -> YesAndNoes) -> Generic YesAndNoes
forall x. Rep YesAndNoes x -> YesAndNoes
forall x. YesAndNoes -> Rep YesAndNoes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep YesAndNoes x -> YesAndNoes
$cfrom :: forall x. YesAndNoes -> Rep YesAndNoes x
Generic)
    deriving anyclass ([YesAndNoes] -> Encoding
[YesAndNoes] -> Value
YesAndNoes -> Encoding
YesAndNoes -> Value
(YesAndNoes -> Value)
-> (YesAndNoes -> Encoding)
-> ([YesAndNoes] -> Value)
-> ([YesAndNoes] -> Encoding)
-> ToJSON YesAndNoes
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [YesAndNoes] -> Encoding
$ctoEncodingList :: [YesAndNoes] -> Encoding
toJSONList :: [YesAndNoes] -> Value
$ctoJSONList :: [YesAndNoes] -> Value
toEncoding :: YesAndNoes -> Encoding
$ctoEncoding :: YesAndNoes -> Encoding
toJSON :: YesAndNoes -> Value
$ctoJSON :: YesAndNoes -> Value
ToJSON)

-- | Full client registration payload.
data FullRegisterPayload = FullRegisterPayload
    { -- | Application name.
      FullRegisterPayload -> Text
appName :: Text,
      -- | Instance identifier (typically hostname).
      FullRegisterPayload -> Text
instanceId :: Text,
      -- | Unleash client SDK version.
      FullRegisterPayload -> Text
sdkVersion :: Text,
      -- | Supported strategies.
      FullRegisterPayload -> [Text]
strategies :: [Text],
      -- | When the application was started.
      FullRegisterPayload -> UTCTime
started :: UTCTime,
      -- | Expected metrics sending interval.
      FullRegisterPayload -> Int
interval :: Int
    }
    deriving stock (FullRegisterPayload -> FullRegisterPayload -> Bool
(FullRegisterPayload -> FullRegisterPayload -> Bool)
-> (FullRegisterPayload -> FullRegisterPayload -> Bool)
-> Eq FullRegisterPayload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FullRegisterPayload -> FullRegisterPayload -> Bool
$c/= :: FullRegisterPayload -> FullRegisterPayload -> Bool
== :: FullRegisterPayload -> FullRegisterPayload -> Bool
$c== :: FullRegisterPayload -> FullRegisterPayload -> Bool
Eq, Int -> FullRegisterPayload -> ShowS
[FullRegisterPayload] -> ShowS
FullRegisterPayload -> String
(Int -> FullRegisterPayload -> ShowS)
-> (FullRegisterPayload -> String)
-> ([FullRegisterPayload] -> ShowS)
-> Show FullRegisterPayload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FullRegisterPayload] -> ShowS
$cshowList :: [FullRegisterPayload] -> ShowS
show :: FullRegisterPayload -> String
$cshow :: FullRegisterPayload -> String
showsPrec :: Int -> FullRegisterPayload -> ShowS
$cshowsPrec :: Int -> FullRegisterPayload -> ShowS
Show, (forall x. FullRegisterPayload -> Rep FullRegisterPayload x)
-> (forall x. Rep FullRegisterPayload x -> FullRegisterPayload)
-> Generic FullRegisterPayload
forall x. Rep FullRegisterPayload x -> FullRegisterPayload
forall x. FullRegisterPayload -> Rep FullRegisterPayload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FullRegisterPayload x -> FullRegisterPayload
$cfrom :: forall x. FullRegisterPayload -> Rep FullRegisterPayload x
Generic)
    deriving anyclass ([FullRegisterPayload] -> Encoding
[FullRegisterPayload] -> Value
FullRegisterPayload -> Encoding
FullRegisterPayload -> Value
(FullRegisterPayload -> Value)
-> (FullRegisterPayload -> Encoding)
-> ([FullRegisterPayload] -> Value)
-> ([FullRegisterPayload] -> Encoding)
-> ToJSON FullRegisterPayload
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [FullRegisterPayload] -> Encoding
$ctoEncodingList :: [FullRegisterPayload] -> Encoding
toJSONList :: [FullRegisterPayload] -> Value
$ctoJSONList :: [FullRegisterPayload] -> Value
toEncoding :: FullRegisterPayload -> Encoding
$ctoEncoding :: FullRegisterPayload -> Encoding
toJSON :: FullRegisterPayload -> Value
$ctoJSON :: FullRegisterPayload -> Value
ToJSON)

-- | Client registration payload.
data RegisterPayload = RegisterPayload
    { -- | Application name.
      RegisterPayload -> Text
appName :: Text,
      -- | Instance identifier (typically hostname).
      RegisterPayload -> Text
instanceId :: Text,
      -- | Client application startup timestamp.
      RegisterPayload -> UTCTime
started :: UTCTime,
      -- | Intended metrics sending interval.
      RegisterPayload -> Int
intervalSeconds :: Int
    }
    deriving stock (RegisterPayload -> RegisterPayload -> Bool
(RegisterPayload -> RegisterPayload -> Bool)
-> (RegisterPayload -> RegisterPayload -> Bool)
-> Eq RegisterPayload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterPayload -> RegisterPayload -> Bool
$c/= :: RegisterPayload -> RegisterPayload -> Bool
== :: RegisterPayload -> RegisterPayload -> Bool
$c== :: RegisterPayload -> RegisterPayload -> Bool
Eq, Int -> RegisterPayload -> ShowS
[RegisterPayload] -> ShowS
RegisterPayload -> String
(Int -> RegisterPayload -> ShowS)
-> (RegisterPayload -> String)
-> ([RegisterPayload] -> ShowS)
-> Show RegisterPayload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterPayload] -> ShowS
$cshowList :: [RegisterPayload] -> ShowS
show :: RegisterPayload -> String
$cshow :: RegisterPayload -> String
showsPrec :: Int -> RegisterPayload -> ShowS
$cshowsPrec :: Int -> RegisterPayload -> ShowS
Show, (forall x. RegisterPayload -> Rep RegisterPayload x)
-> (forall x. Rep RegisterPayload x -> RegisterPayload)
-> Generic RegisterPayload
forall x. Rep RegisterPayload x -> RegisterPayload
forall x. RegisterPayload -> Rep RegisterPayload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterPayload x -> RegisterPayload
$cfrom :: forall x. RegisterPayload -> Rep RegisterPayload x
Generic)
    deriving anyclass ([RegisterPayload] -> Encoding
[RegisterPayload] -> Value
RegisterPayload -> Encoding
RegisterPayload -> Value
(RegisterPayload -> Value)
-> (RegisterPayload -> Encoding)
-> ([RegisterPayload] -> Value)
-> ([RegisterPayload] -> Encoding)
-> ToJSON RegisterPayload
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RegisterPayload] -> Encoding
$ctoEncodingList :: [RegisterPayload] -> Encoding
toJSONList :: [RegisterPayload] -> Value
$ctoJSONList :: [RegisterPayload] -> Value
toEncoding :: RegisterPayload -> Encoding
$ctoEncoding :: RegisterPayload -> Encoding
toJSON :: RegisterPayload -> Value
$ctoJSON :: RegisterPayload -> Value
ToJSON)