{-# LANGUAGE OverloadedLists #-}
module LaunchDarkly.Server.Details where
import Data.Aeson.Types (ToJSON, Value (..), toJSON)
import Data.Text (Text)
import GHC.Exts (fromList)
import GHC.Generics (Generic)
import GHC.Natural (Natural)
data EvaluationDetail value = EvaluationDetail
{ EvaluationDetail value -> value
value :: !value
, EvaluationDetail value -> Maybe Integer
variationIndex :: !(Maybe Integer)
, EvaluationDetail value -> EvaluationReason
reason :: !EvaluationReason
}
deriving ((forall x.
EvaluationDetail value -> Rep (EvaluationDetail value) x)
-> (forall x.
Rep (EvaluationDetail value) x -> EvaluationDetail value)
-> Generic (EvaluationDetail value)
forall x. Rep (EvaluationDetail value) x -> EvaluationDetail value
forall x. EvaluationDetail value -> Rep (EvaluationDetail value) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall value x.
Rep (EvaluationDetail value) x -> EvaluationDetail value
forall value x.
EvaluationDetail value -> Rep (EvaluationDetail value) x
$cto :: forall value x.
Rep (EvaluationDetail value) x -> EvaluationDetail value
$cfrom :: forall value x.
EvaluationDetail value -> Rep (EvaluationDetail value) x
Generic, EvaluationDetail value -> EvaluationDetail value -> Bool
(EvaluationDetail value -> EvaluationDetail value -> Bool)
-> (EvaluationDetail value -> EvaluationDetail value -> Bool)
-> Eq (EvaluationDetail value)
forall value.
Eq value =>
EvaluationDetail value -> EvaluationDetail value -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EvaluationDetail value -> EvaluationDetail value -> Bool
$c/= :: forall value.
Eq value =>
EvaluationDetail value -> EvaluationDetail value -> Bool
== :: EvaluationDetail value -> EvaluationDetail value -> Bool
$c== :: forall value.
Eq value =>
EvaluationDetail value -> EvaluationDetail value -> Bool
Eq, Int -> EvaluationDetail value -> ShowS
[EvaluationDetail value] -> ShowS
EvaluationDetail value -> String
(Int -> EvaluationDetail value -> ShowS)
-> (EvaluationDetail value -> String)
-> ([EvaluationDetail value] -> ShowS)
-> Show (EvaluationDetail value)
forall value. Show value => Int -> EvaluationDetail value -> ShowS
forall value. Show value => [EvaluationDetail value] -> ShowS
forall value. Show value => EvaluationDetail value -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EvaluationDetail value] -> ShowS
$cshowList :: forall value. Show value => [EvaluationDetail value] -> ShowS
show :: EvaluationDetail value -> String
$cshow :: forall value. Show value => EvaluationDetail value -> String
showsPrec :: Int -> EvaluationDetail value -> ShowS
$cshowsPrec :: forall value. Show value => Int -> EvaluationDetail value -> ShowS
Show)
instance ToJSON a => ToJSON (EvaluationDetail a) where
toJSON :: EvaluationDetail a -> Value
toJSON = EvaluationDetail a -> Value
forall a. ToJSON a => a -> Value
toJSON
data EvaluationReason
=
EvaluationReasonOff
|
EvaluationReasonTargetMatch
| EvaluationReasonRuleMatch
{ EvaluationReason -> Natural
ruleIndex :: !Natural
, EvaluationReason -> Text
ruleId :: !Text
, EvaluationReason -> Bool
inExperiment :: !Bool
}
|
EvaluationReasonPrerequisiteFailed
{ EvaluationReason -> Text
prerequisiteKey :: !Text
}
|
EvaluationReasonFallthrough
{ inExperiment :: !Bool
}
|
EvaluationReasonError
{ EvaluationReason -> EvalErrorKind
errorKind :: !EvalErrorKind
}
deriving ((forall x. EvaluationReason -> Rep EvaluationReason x)
-> (forall x. Rep EvaluationReason x -> EvaluationReason)
-> Generic EvaluationReason
forall x. Rep EvaluationReason x -> EvaluationReason
forall x. EvaluationReason -> Rep EvaluationReason x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EvaluationReason x -> EvaluationReason
$cfrom :: forall x. EvaluationReason -> Rep EvaluationReason x
Generic, EvaluationReason -> EvaluationReason -> Bool
(EvaluationReason -> EvaluationReason -> Bool)
-> (EvaluationReason -> EvaluationReason -> Bool)
-> Eq EvaluationReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EvaluationReason -> EvaluationReason -> Bool
$c/= :: EvaluationReason -> EvaluationReason -> Bool
== :: EvaluationReason -> EvaluationReason -> Bool
$c== :: EvaluationReason -> EvaluationReason -> Bool
Eq, Int -> EvaluationReason -> ShowS
[EvaluationReason] -> ShowS
EvaluationReason -> String
(Int -> EvaluationReason -> ShowS)
-> (EvaluationReason -> String)
-> ([EvaluationReason] -> ShowS)
-> Show EvaluationReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EvaluationReason] -> ShowS
$cshowList :: [EvaluationReason] -> ShowS
show :: EvaluationReason -> String
$cshow :: EvaluationReason -> String
showsPrec :: Int -> EvaluationReason -> ShowS
$cshowsPrec :: Int -> EvaluationReason -> ShowS
Show)
instance ToJSON EvaluationReason where
toJSON :: EvaluationReason -> Value
toJSON x :: EvaluationReason
x = case EvaluationReason
x of
EvaluationReasonOff ->
Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ [Item Object] -> Object
forall l. IsList l => [Item l] -> l
fromList [("kind", "OFF")]
EvaluationReasonTargetMatch ->
Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ [Item Object] -> Object
forall l. IsList l => [Item l] -> l
fromList [("kind", "TARGET_MATCH")]
(EvaluationReasonRuleMatch ruleIndex :: Natural
ruleIndex ruleId :: Text
ruleId True) ->
Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ [Item Object] -> Object
forall l. IsList l => [Item l] -> l
fromList [("kind", "RULE_MATCH"), ("ruleIndex", Natural -> Value
forall a. ToJSON a => a -> Value
toJSON Natural
ruleIndex), ("ruleId", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
ruleId), ("inExperiment", Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
True)]
(EvaluationReasonRuleMatch ruleIndex :: Natural
ruleIndex ruleId :: Text
ruleId False) ->
Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ [Item Object] -> Object
forall l. IsList l => [Item l] -> l
fromList [("kind", "RULE_MATCH"), ("ruleIndex", Natural -> Value
forall a. ToJSON a => a -> Value
toJSON Natural
ruleIndex), ("ruleId", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
ruleId)]
(EvaluationReasonPrerequisiteFailed prerequisiteKey :: Text
prerequisiteKey) ->
Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ [Item Object] -> Object
forall l. IsList l => [Item l] -> l
fromList [("kind", "PREREQUISITE_FAILED"), ("prerequisiteKey", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
prerequisiteKey)]
EvaluationReasonFallthrough True ->
Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ [Item Object] -> Object
forall l. IsList l => [Item l] -> l
fromList [("kind", "FALLTHROUGH"), ("inExperiment", Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
True)]
EvaluationReasonFallthrough False ->
Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ [Item Object] -> Object
forall l. IsList l => [Item l] -> l
fromList [("kind", "FALLTHROUGH")]
(EvaluationReasonError errorKind :: EvalErrorKind
errorKind) ->
Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ [Item Object] -> Object
forall l. IsList l => [Item l] -> l
fromList [("kind", "ERROR"), ("errorKind", EvalErrorKind -> Value
forall a. ToJSON a => a -> Value
toJSON EvalErrorKind
errorKind)]
isInExperiment :: EvaluationReason -> Bool
isInExperiment :: EvaluationReason -> Bool
isInExperiment reason :: EvaluationReason
reason = case EvaluationReason
reason of
EvaluationReasonRuleMatch _ _ inExperiment :: Bool
inExperiment -> Bool
inExperiment
EvaluationReasonFallthrough inExperiment :: Bool
inExperiment -> Bool
inExperiment
_ -> Bool
False
data EvalErrorKind
=
EvalErrorKindMalformedFlag
|
EvalErrorFlagNotFound
|
EvalErrorWrongType
|
EvalErrorClientNotReady
|
EvalErrorInvalidContext
|
EvalErrorExternalStore !Text
deriving ((forall x. EvalErrorKind -> Rep EvalErrorKind x)
-> (forall x. Rep EvalErrorKind x -> EvalErrorKind)
-> Generic EvalErrorKind
forall x. Rep EvalErrorKind x -> EvalErrorKind
forall x. EvalErrorKind -> Rep EvalErrorKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EvalErrorKind x -> EvalErrorKind
$cfrom :: forall x. EvalErrorKind -> Rep EvalErrorKind x
Generic, EvalErrorKind -> EvalErrorKind -> Bool
(EvalErrorKind -> EvalErrorKind -> Bool)
-> (EvalErrorKind -> EvalErrorKind -> Bool) -> Eq EvalErrorKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EvalErrorKind -> EvalErrorKind -> Bool
$c/= :: EvalErrorKind -> EvalErrorKind -> Bool
== :: EvalErrorKind -> EvalErrorKind -> Bool
$c== :: EvalErrorKind -> EvalErrorKind -> Bool
Eq, Int -> EvalErrorKind -> ShowS
[EvalErrorKind] -> ShowS
EvalErrorKind -> String
(Int -> EvalErrorKind -> ShowS)
-> (EvalErrorKind -> String)
-> ([EvalErrorKind] -> ShowS)
-> Show EvalErrorKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EvalErrorKind] -> ShowS
$cshowList :: [EvalErrorKind] -> ShowS
show :: EvalErrorKind -> String
$cshow :: EvalErrorKind -> String
showsPrec :: Int -> EvalErrorKind -> ShowS
$cshowsPrec :: Int -> EvalErrorKind -> ShowS
Show)
instance ToJSON EvalErrorKind where
toJSON :: EvalErrorKind -> Value
toJSON x :: EvalErrorKind
x = Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ case EvalErrorKind
x of
EvalErrorKindMalformedFlag -> "MALFORMED_FLAG"
EvalErrorFlagNotFound -> "FLAG_NOT_FOUND"
EvalErrorWrongType -> "WRONG_TYPE"
EvalErrorClientNotReady -> "CLIENT_NOT_READY"
EvalErrorExternalStore _ -> "EXTERNAL_STORE_ERROR"
EvalErrorInvalidContext -> "ERROR_INVALID_CONTEXT"