{-# LANGUAGE OverloadedLists #-}moduleLaunchDarkly.Server.DetailswhereimportData.Aeson.Types(ToJSON,Value(..),toJSON)importData.Text(Text)importGHC.Exts(fromList)importGHC.Generics(Generic)importGHC.Natural(Natural)-- |-- Combines the result of a flag evaluation with an explanation of how it was-- calculated.dataEvaluationDetailvalue=EvaluationDetail{EvaluationDetail value -> value
value::!value-- ^ The result of the flag evaluation. This will be either one of the-- flag's variations or the default value passed by the application.,EvaluationDetail value -> Maybe Integer
variationIndex::!(MaybeInteger)-- ^ The index of the returned value within the flag's list of variations,-- e.g. 0 for the first variation - or Nothing if the default value was-- returned.,EvaluationDetail value -> EvaluationReason
reason::!EvaluationReason-- ^ Describes the main factor that influenced the flag evaluation value.}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)instanceToJSONa=>ToJSON(EvaluationDetaila)wheretoJSON :: EvaluationDetail a -> Value
toJSON=EvaluationDetail a -> Value
forall a. ToJSON a => a -> Value
toJSON-- | Defines the possible values of the Kind property of EvaluationReason.dataEvaluationReason=-- | Indicates that the flag was off and therefore returned its configured-- off value.EvaluationReasonOff|-- | indicates that the context key was specifically targeted for this flag.EvaluationReasonTargetMatch|EvaluationReasonRuleMatch{EvaluationReason -> Natural
ruleIndex::!Natural-- ^ The index of the rule that was matched (0 being the first).,EvaluationReason -> Text
ruleId::!Text-- ^ The unique identifier of the rule that was matched.,EvaluationReason -> Bool
inExperiment::!Bool-- ^ Whether the evaluation was part of an experiment. Is true if-- the evaluation resulted in an experiment rollout *and* served-- one of the variations in the experiment. Otherwise false.}|-- \^ Indicates that the context matched one of the flag's rules.EvaluationReasonPrerequisiteFailed{EvaluationReason -> Text
prerequisiteKey::!Text-- ^ The flag key of the prerequisite that failed.}|-- \^ Indicates that the flag was considered off because it had at least-- one prerequisite flag that either was off or did not return the desired-- variation.EvaluationReasonFallthrough{inExperiment::!Bool-- ^ Whether the evaluation was part of an experiment. Is-- true if the evaluation resulted in an experiment rollout *and*-- served one of the variations in the experiment. Otherwise false.}|-- \^ Indicates that the flag was on but the context did not match any targets-- or rules.EvaluationReasonError{EvaluationReason -> EvalErrorKind
errorKind::!EvalErrorKind-- ^ Describes the type of error.}-- \^ Indicates that the flag could not be evaluated, e.g. because it does-- not exist or due to an unexpected error. In this case the result value-- will be the default value that the caller passed to the client.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)instanceToJSONEvaluationReasonwheretoJSON :: EvaluationReason -> Value
toJSONx :: EvaluationReason
x=caseEvaluationReason
xofEvaluationReasonOff->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")](EvaluationReasonRuleMatchruleIndex :: Natural
ruleIndexruleId :: Text
ruleIdTrue)->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
toJSONNatural
ruleIndex),("ruleId",Text -> Value
forall a. ToJSON a => a -> Value
toJSONText
ruleId),("inExperiment",Bool -> Value
forall a. ToJSON a => a -> Value
toJSONBool
True)](EvaluationReasonRuleMatchruleIndex :: Natural
ruleIndexruleId :: Text
ruleIdFalse)->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
toJSONNatural
ruleIndex),("ruleId",Text -> Value
forall a. ToJSON a => a -> Value
toJSONText
ruleId)](EvaluationReasonPrerequisiteFailedprerequisiteKey :: 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
toJSONText
prerequisiteKey)]EvaluationReasonFallthroughTrue->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
toJSONBool
True)]EvaluationReasonFallthroughFalse->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")](EvaluationReasonErrorerrorKind :: 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
toJSONEvalErrorKind
errorKind)]isInExperiment::EvaluationReason->BoolisInExperiment :: EvaluationReason -> Bool
isInExperimentreason :: EvaluationReason
reason=caseEvaluationReason
reasonofEvaluationReasonRuleMatch__inExperiment :: Bool
inExperiment->Bool
inExperimentEvaluationReasonFallthroughinExperiment :: Bool
inExperiment->Bool
inExperiment_->Bool
False-- | Defines the possible values of the errorKind property of EvaluationReason.dataEvalErrorKind=-- | Indicates that there was an internal inconsistency in the flag data,-- e.g. a rule specified a nonexistent variation.EvalErrorKindMalformedFlag|-- | Indicates that the caller provided a flag key that did not match any-- known flag.EvalErrorFlagNotFound|-- | Indicates that the result value was not of the requested type, e.g.-- you called boolVariationDetail but the value was an integer.EvalErrorWrongType|-- | Indicates that the caller tried to evaluate a flag before the client-- had successfully initialized.EvalErrorClientNotReady|-- | Indicates that the caller tried to evaluate a flag with an invalid-- contextEvalErrorInvalidContext|-- | Indicates that some error was returned by the external feature store.EvalErrorExternalStore!Textderiving((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)instanceToJSONEvalErrorKindwheretoJSON :: EvalErrorKind -> Value
toJSONx :: EvalErrorKind
x=Text -> Value
String(Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$caseEvalErrorKind
xofEvalErrorKindMalformedFlag->"MALFORMED_FLAG"EvalErrorFlagNotFound->"FLAG_NOT_FOUND"EvalErrorWrongType->"WRONG_TYPE"EvalErrorClientNotReady->"CLIENT_NOT_READY"EvalErrorExternalStore_->"EXTERNAL_STORE_ERROR"EvalErrorInvalidContext->"ERROR_INVALID_CONTEXT"