launchdarkly-server-sdk-2.0.2: Server-side SDK for integrating with LaunchDarkly

Safe HaskellNone
LanguageHaskell2010

LaunchDarkly.Server.Client

Description

This module contains the core functionality of the SDK.

Synopsis

Documentation

data Client Source #

Client is the LaunchDarkly client. Client instances are thread-safe. Applications should instantiate a single instance for the lifetime of their application.

makeClient :: Config -> IO Client Source #

Create a new instance of the LaunchDarkly client.

clientVersion :: Text Source #

The version string for this library.

boolVariation :: Client -> Text -> User -> Bool -> IO Bool Source #

Evaluate a Boolean typed flag.

boolVariationDetail :: Client -> Text -> User -> Bool -> IO (EvaluationDetail Bool) Source #

Evaluate a Boolean typed flag, and return an explation.

stringVariation :: Client -> Text -> User -> Text -> IO Text Source #

Evaluate a String typed flag.

stringVariationDetail :: Client -> Text -> User -> Text -> IO (EvaluationDetail Text) Source #

Evaluate a String typed flag, and return an explanation.

intVariation :: Client -> Text -> User -> Int -> IO Int Source #

Evaluate a Number typed flag, and truncate the result.

intVariationDetail :: Client -> Text -> User -> Int -> IO (EvaluationDetail Int) Source #

Evaluate a Number typed flag, truncate the result, and return an explanation.

doubleVariation :: Client -> Text -> User -> Double -> IO Double Source #

Evaluate a Number typed flag.

doubleVariationDetail :: Client -> Text -> User -> Double -> IO (EvaluationDetail Double) Source #

Evaluate a Number typed flag, and return an explanation.

jsonVariation :: Client -> Text -> User -> Value -> IO Value Source #

Evaluate a JSON typed flag.

jsonVariationDetail :: Client -> Text -> User -> Value -> IO (EvaluationDetail Value) Source #

Evaluate a JSON typed flag, and return an explanation.

data EvaluationDetail value Source #

Combines the result of a flag evaluation with an explanation of how it was calculated.

Constructors

EvaluationDetail 

Fields

  • 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.

  • variationIndex :: !(Maybe Natural)

    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.

  • reason :: !EvaluationReason

    Describes the main factor that influenced the flag evaluation value.

Instances
Eq value => Eq (EvaluationDetail value) Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Methods

(==) :: EvaluationDetail value -> EvaluationDetail value -> Bool #

(/=) :: EvaluationDetail value -> EvaluationDetail value -> Bool #

Show value => Show (EvaluationDetail value) Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Generic (EvaluationDetail value) Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Associated Types

type Rep (EvaluationDetail value) :: Type -> Type #

Methods

from :: EvaluationDetail value -> Rep (EvaluationDetail value) x #

to :: Rep (EvaluationDetail value) x -> EvaluationDetail value #

ToJSON a => ToJSON (EvaluationDetail a) Source # 
Instance details

Defined in LaunchDarkly.Server.Details

type Rep (EvaluationDetail value) Source # 
Instance details

Defined in LaunchDarkly.Server.Details

type Rep (EvaluationDetail value) = D1 (MetaData "EvaluationDetail" "LaunchDarkly.Server.Details" "launchdarkly-server-sdk-2.0.2-4m4PsKPomQSAdlZ6J89dko" False) (C1 (MetaCons "EvaluationDetail" PrefixI True) (S1 (MetaSel (Just "value") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 value) :*: (S1 (MetaSel (Just "variationIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Natural)) :*: S1 (MetaSel (Just "reason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 EvaluationReason))))

data EvaluationReason Source #

Defines the possible values of the Kind property of EvaluationReason.

Constructors

EvaluationReasonOff

Indicates that the flag was off and therefore returned its configured off value.

EvaluationReasonTargetMatch

indicates that the user key was specifically targeted for this flag.

EvaluationReasonRuleMatch

Indicates that the user matched one of the flag's rules.

Fields

  • ruleIndex :: !Natural

    The index of the rule that was matched (0 being the first).

  • ruleId :: !Text

    The unique identifier of the rule that was matched.

EvaluationReasonPrerequisiteFailed

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.

Fields

EvaluationReasonFallthrough

Indicates that the flag was on but the user did not match any targets or rules.

EvaluationReasonError

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.

Fields

Instances
Eq EvaluationReason Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Show EvaluationReason Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Generic EvaluationReason Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Associated Types

type Rep EvaluationReason :: Type -> Type #

ToJSON EvaluationReason Source # 
Instance details

Defined in LaunchDarkly.Server.Details

type Rep EvaluationReason Source # 
Instance details

Defined in LaunchDarkly.Server.Details

type Rep EvaluationReason = D1 (MetaData "EvaluationReason" "LaunchDarkly.Server.Details" "launchdarkly-server-sdk-2.0.2-4m4PsKPomQSAdlZ6J89dko" False) ((C1 (MetaCons "EvaluationReasonOff" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EvaluationReasonTargetMatch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EvaluationReasonRuleMatch" PrefixI True) (S1 (MetaSel (Just "ruleIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural) :*: S1 (MetaSel (Just "ruleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) :+: (C1 (MetaCons "EvaluationReasonPrerequisiteFailed" PrefixI True) (S1 (MetaSel (Just "prerequisiteKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: (C1 (MetaCons "EvaluationReasonFallthrough" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EvaluationReasonError" PrefixI True) (S1 (MetaSel (Just "errorKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 EvalErrorKind)))))

data EvalErrorKind Source #

Defines the possible values of the errorKind property of EvaluationReason.

Constructors

EvalErrorKindMalformedFlag

Indicates that there was an internal inconsistency in the flag data, e.g. a rule specified a nonexistent variation.

EvalErrorFlagNotFound

Indicates that the caller provided a flag key that did not match any known flag.

EvalErrorWrongType

Indicates that the result value was not of the requested type, e.g. you called boolVariationDetail but the value was an integer.

EvalErrorClientNotReady

Indicates that the caller tried to evaluate a flag before the client had successfully initialized.

EvalErrorExternalStore !Text

Indicates that some error was returned by the external feature store.

Instances
Eq EvalErrorKind Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Show EvalErrorKind Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Generic EvalErrorKind Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Associated Types

type Rep EvalErrorKind :: Type -> Type #

ToJSON EvalErrorKind Source # 
Instance details

Defined in LaunchDarkly.Server.Details

type Rep EvalErrorKind Source # 
Instance details

Defined in LaunchDarkly.Server.Details

type Rep EvalErrorKind = D1 (MetaData "EvalErrorKind" "LaunchDarkly.Server.Details" "launchdarkly-server-sdk-2.0.2-4m4PsKPomQSAdlZ6J89dko" False) ((C1 (MetaCons "EvalErrorKindMalformedFlag" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EvalErrorFlagNotFound" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "EvalErrorWrongType" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EvalErrorClientNotReady" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EvalErrorExternalStore" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

allFlags :: Client -> User -> IO (HashMap Text Value) Source #

Returns a map from feature flag keys to values for a given user. If the result of the flag's evaluation would result in the default value, Null will be returned. This method does not send analytics events back to LaunchDarkly.

close :: Client -> IO () Source #

Close shuts down the LaunchDarkly client. After calling this, the LaunchDarkly client should no longer be used. The method will block until all pending analytics events have been sent.

flushEvents :: Client -> IO () Source #

Flush tells the client that all pending analytics events (if any) should be delivered as soon as possible. Flushing is asynchronous, so this method will return before it is complete.

identify :: Client -> User -> IO () Source #

Identify reports details about a a user.

track :: Client -> User -> Text -> Maybe Value -> Maybe Double -> IO () Source #

Track reports that a user has performed an event. Custom data can be attached to the event, and / or a numeric value.

The numeric value is used by the LaunchDarkly experimentation feature in numeric custom metrics, and will also be returned as part of the custom event for Data Export.

data Status Source #

The status of the client initialization.

Constructors

Uninitialized

The client has not yet finished connecting to LaunchDarkly.

Unauthorized

The client attempted to connect to LaunchDarkly and was denied.

Initialized

The client has successfuly connected to LaunchDarkly.

ShuttingDown

The client is being terminated

Instances
Eq Status Source # 
Instance details

Defined in LaunchDarkly.Server.Client.Internal

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

getStatus :: Client -> IO Status Source #

Return the initialization status of the Client