launchdarkly-server-sdk-3.1.0: Server-side SDK for integrating with LaunchDarkly
Safe HaskellSafe-Inferred
LanguageHaskell2010

LaunchDarkly.Server

Description

This module re-exports the User, Client, and Config modules.

Synopsis

Documentation

data Config Source #

Config allows advanced configuration of the LaunchDarkly client.

makeConfig :: Text -> Config Source #

Create a default configuration from a given SDK key.

configSetKey :: Text -> Config -> Config Source #

Set the SDK key used to authenticate with LaunchDarkly.

configSetBaseURI :: Text -> Config -> Config Source #

The base URI of the main LaunchDarkly service. This should not normally be changed except for testing.

configSetStreamURI :: Text -> Config -> Config Source #

The base URI of the LaunchDarkly streaming service. This should not normally be changed except for testing.

configSetEventsURI :: Text -> Config -> Config Source #

The base URI of the LaunchDarkly service that accepts analytics events. This should not normally be changed except for testing.

configSetStreaming :: Bool -> Config -> Config Source #

Sets whether streaming mode should be enabled. By default, streaming is enabled. It should only be disabled on the advice of LaunchDarkly support.

configSetAllAttributesPrivate :: Bool -> Config -> Config Source #

Sets whether or not all user attributes (other than the key) should be hidden from LaunchDarkly. If this is true, all user attribute values will be private, not just the attributes specified in PrivateAttributeNames.

configSetPrivateAttributeNames :: Set Text -> Config -> Config Source #

Marks a set of user attribute names private. Any users sent to LaunchDarkly with this configuration active will have attributes with these names removed.

configSetFlushIntervalSeconds :: Natural -> Config -> Config Source #

The time between flushes of the event buffer. Decreasing the flush interval means that the event buffer is less likely to reach capacity.

configSetPollIntervalSeconds :: Natural -> Config -> Config Source #

The polling interval (when streaming is disabled).

configSetUserKeyLRUCapacity :: Natural -> Config -> Config Source #

The number of user keys that the event processor can remember at any one time, so that duplicate user details will not be sent in analytics events.

configSetInlineUsersInEvents :: Bool -> Config -> Config Source #

Set to true if you need to see the full user details in every analytics event.

configSetEventsCapacity :: Natural -> Config -> Config Source #

The capacity of the events buffer. The client buffers up to this many events in memory before flushing. If the capacity is exceeded before the buffer is flushed, events will be discarded.

configSetLogger :: (LoggingT IO () -> IO ()) -> Config -> Config Source #

Set the logger to be used by the client.

configSetManager :: Manager -> Config -> Config Source #

Sets the Manager to use with the client. If not set explicitly a new Manager will be created when creating the client.

configSetSendEvents :: Bool -> Config -> Config Source #

Sets whether to send analytics events back to LaunchDarkly. By default, the client will send events. This differs from Offline in that it only affects sending events, not streaming or polling for events from the server.

configSetOffline :: Bool -> Config -> Config Source #

Sets whether this client is offline. An offline client will not make any network connections to LaunchDarkly, and will return default values for all feature flags.

configSetRequestTimeoutSeconds :: Natural -> Config -> Config Source #

Sets how long an the HTTP client should wait before a response is returned.

configSetStoreBackend :: Maybe StoreInterface -> Config -> Config Source #

Configures a handle to an external store such as Redis.

configSetStoreTTL :: Natural -> Config -> Config Source #

When a store backend is configured, control how long values should be cached in memory before going back to the backend.

configSetUseLdd :: Bool -> Config -> Config Source #

Sets whether this client should use the LaunchDarkly Relay Proxy in daemon mode. In this mode, the client does not subscribe to the streaming or polling API, but reads data only from the feature store. See: https://docs.launchdarkly.com/home/relay-proxy

configSetDataSourceFactory :: Maybe DataSourceFactory -> Config -> Config Source #

Sets a data source to use instead of the default network based data source see LaunchDarkly.Server.Integrations.FileData

configSetApplicationInfo :: ApplicationInfo -> Config -> Config Source #

An object that allows configuration of application metadata.

Application metadata may be used in LaunchDarkly analytics or other product features, but does not affect feature flag evaluations.

If you want to set non-default values for any of these fields, provide the appropriately configured dict to the Config object.

data ApplicationInfo Source #

An object that allows configuration of application metadata.

Application metadata may be used in LaunchDarkly analytics or other product features, but does not affect feature flag evaluations.

To use these properties, provide an instance of ApplicationInfo to the Config with configSetApplicationInfo.

makeApplicationInfo :: ApplicationInfo Source #

Create a default instance

withApplicationValue :: Text -> Text -> ApplicationInfo -> ApplicationInfo Source #

Set a new name / value pair into the application info instance.

Values have the following restrictions: - Cannot be empty - Cannot exceed 64 characters in length - Can only contain a-z, A-Z, 0-9, period (.), dash (-), and underscore (_).

Invalid values or unsupported keys will be ignored.

data User Source #

User contains specific attributes of a user of your application

The only mandatory property is the Key, which must uniquely identify each user. For authenticated users, this may be a username or e-mail address. For anonymous users, this could be an IP address or session ID.

makeUser :: Text -> User Source #

Creates a new user identified by the given key.

userSetKey :: Text -> User -> User Source #

Set the primary key for a user.

userSetSecondary :: Maybe Text -> User -> User Source #

Set the secondary key for a user.

userSetIP :: Maybe Text -> User -> User Source #

Set the IP for a user.

userSetCountry :: Maybe Text -> User -> User Source #

Set the country for a user.

userSetEmail :: Maybe Text -> User -> User Source #

Set the email for a user.

userSetFirstName :: Maybe Text -> User -> User Source #

Set the first name for a user.

userSetLastName :: Maybe Text -> User -> User Source #

Set the last name for a user.

userSetAvatar :: Maybe Text -> User -> User Source #

Set the avatar for a user.

userSetName :: Maybe Text -> User -> User Source #

Set the name for a user.

userSetAnonymous :: Bool -> User -> User Source #

Set if the user is anonymous or not.

userSetCustom :: HashMap Text Value -> User -> User Source #

Set custom fields for a user.

userSetPrivateAttributeNames :: Set Text -> User -> User Source #

This contains list of attributes to keep private, whether they appear at the top-level or Custom The attribute "key" is always sent regardless of whether it is in this list, and "custom" cannot be used to eliminate all custom attributes

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

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 Integer)

    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

Instances details
ToJSON a => ToJSON (EvaluationDetail a) 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 #

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

Defined in LaunchDarkly.Server.Details

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

Defined in LaunchDarkly.Server.Details

Methods

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

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

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-3.1.0-8O1d71Fm46w1ehOf6tOOYm" 'False) (C1 ('MetaCons "EvaluationDetail" 'PrefixI 'True) (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 value) :*: (S1 ('MetaSel ('Just "variationIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Integer)) :*: 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 

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.

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

EvaluationReasonPrerequisiteFailed 

Fields

EvaluationReasonFallthrough 

Fields

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

EvaluationReasonError 

Fields

Instances

Instances details
ToJSON 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 #

Show EvaluationReason Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Eq 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-3.1.0-8O1d71Fm46w1ehOf6tOOYm" '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) :*: S1 ('MetaSel ('Just "inExperiment") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))) :+: (C1 ('MetaCons "EvaluationReasonPrerequisiteFailed" 'PrefixI 'True) (S1 ('MetaSel ('Just "prerequisiteKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "EvaluationReasonFallthrough" 'PrefixI 'True) (S1 ('MetaSel ('Just "inExperiment") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: 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

Instances details
ToJSON 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 #

Show EvalErrorKind Source # 
Instance details

Defined in LaunchDarkly.Server.Details

Eq 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-3.1.0-8O1d71Fm46w1ehOf6tOOYm" '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 (KeyMap 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.

allFlagsState :: Client -> User -> Bool -> Bool -> Bool -> IO AllFlagsState Source #

Returns an object that encapsulates the state of all feature flags for a given user. This includes the flag values, and also metadata that can be used on the front end.

The most common use case for this method is to bootstrap a set of client-side feature flags from a back-end service.

The first parameter will limit to only flags that are marked for use with the client-side SDK (by default, all flags are included).

The second parameter will include evaluation reasons in the state.

The third parameter will omit any metadata that is normally only used for event generation, such as flag versions and evaluation reasons, unless the flag has event tracking or debugging turned on

For more information, see the Reference Guide: https://docs.launchdarkly.com/sdk/features/all-flags#haskell

data AllFlagsState Source #

AllFlagsState captures the state of all feature flag keys as evaluated for a specific user. This includes their values, as well as other metadata.

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

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

Alias associates two users for analytics purposes with an alias event.

The first parameter should be the new version of the user, the second parameter should be the old version.

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

Instances details
Show Status Source # 
Instance details

Defined in LaunchDarkly.Server.Client.Status

Eq Status Source # 
Instance details

Defined in LaunchDarkly.Server.Client.Status

Methods

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

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

getStatus :: Client -> IO Status Source #

Return the initialization status of the Client