| Copyright | Copyright © FINN.no AS Inc. All rights reserved. |
|---|---|
| License | MIT |
| Stability | experimental |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Unleash.Client
Description
Functions and types that constitute an Unleash client SDK.
This module re-exports select constructors from unleash-client-haskell-core.
Synopsis
- makeUnleashConfig :: MonadIO m => Text -> Text -> BaseUrl -> Maybe Text -> m UnleashConfig
- data UnleashConfig = UnleashConfig {}
- class HasUnleash r where
- getUnleashConfig :: r -> UnleashConfig
- registerClient :: (HasUnleash r, MonadReader r m, MonadIO m) => m (Either ClientError ())
- registerClientWithCustomStrategies :: (HasUnleash r, MonadReader r m, MonadIO m) => SupportedStrategies -> m (Either ClientError ())
- pollToggles :: (HasUnleash r, MonadReader r m, MonadIO m) => m (Either ClientError ())
- pollTogglesWithCustomStrategies :: (HasUnleash r, MonadReader r m, MonadIO m) => StrategyEvaluator -> m (Either ClientError ())
- pushMetrics :: (HasUnleash r, MonadReader r m, MonadIO m) => m (Either ClientError ())
- isEnabled :: (HasUnleash r, MonadReader r m, MonadIO m) => Text -> m Bool
- isEnabledWithContext :: (HasUnleash r, MonadReader r m, MonadIO m) => Text -> Context -> m Bool
- tryIsEnabled :: (HasUnleash r, MonadReader r m, MonadIO m) => Text -> m Bool
- tryIsEnabledWithContext :: (HasUnleash r, MonadReader r m, MonadIO m) => Text -> Context -> m Bool
- getVariant :: (HasUnleash r, MonadReader r m, MonadIO m) => Text -> Context -> m VariantResponse
- tryGetVariant :: (HasUnleash r, MonadReader r m, MonadIO m) => Text -> Context -> m VariantResponse
- data Context = Context {}
- emptyContext :: Context
- type FeatureToggleName = Text
- data Strategy = Strategy {
- name :: Text
- parameters :: Maybe (Map Text Text)
- constraints :: Maybe [Constraint]
- segments :: Maybe [Int]
- type StrategyEvaluator = forall (m :: Type -> Type). MonadIO m => Strategy -> FeatureToggleName -> Context -> m Bool
- type SupportedStrategies = [Text]
- data VariantResponse = VariantResponse {}
Documentation
Arguments
| :: MonadIO m | |
| => Text | Application name. |
| -> Text | Instance identifier. |
| -> BaseUrl | Unleash server base URL. |
| -> Maybe Text | API key for authorization. |
| -> m UnleashConfig | Configuration instance. |
Smart constructor for Unleash client configuration. Initializes the mutable variables properly.
data UnleashConfig Source #
Unleash client configuration. Use the smart constructor or make sure the mutable metrics variables are not empty.
Constructors
| UnleashConfig | |
Fields
| |
class HasUnleash r where Source #
Reader monad convenience class. Use this to get an Unleash configuration from inside of an application configuration (for example).
Methods
getUnleashConfig :: r -> UnleashConfig Source #
registerClient :: (HasUnleash r, MonadReader r m, MonadIO m) => m (Either ClientError ()) Source #
Register client for the Unleash server. Call this on application startup before calling the state poller and metrics pusher functions.
registerClientWithCustomStrategies :: (HasUnleash r, MonadReader r m, MonadIO m) => SupportedStrategies -> m (Either ClientError ()) Source #
Register client for the Unleash server. Custom strategies are added to default strategies. Call this on application startup before calling the state poller and metrics pusher functions.
pollToggles :: (HasUnleash r, MonadReader r m, MonadIO m) => m (Either ClientError ()) Source #
Fetch the most recent feature toggle set from the Unleash server. Meant to be run every statePollIntervalInSeconds. Non-blocking.
pollTogglesWithCustomStrategies :: (HasUnleash r, MonadReader r m, MonadIO m) => StrategyEvaluator -> m (Either ClientError ()) Source #
Fetch the most recent feature toggle set from the Unleash server. Custom strategies are added to default strategies. Meant to be run every statePollIntervalInSeconds. Non-blocking.
pushMetrics :: (HasUnleash r, MonadReader r m, MonadIO m) => m (Either ClientError ()) Source #
Push metrics to the Unleash server. Meant to be run every metricsPushIntervalInSeconds. Blocks if the mutable metrics variables are empty.
Arguments
| :: (HasUnleash r, MonadReader r m, MonadIO m) | |
| => Text | Feature toggle name. |
| -> m Bool | Client context. |
Check if a feature is enabled or not. Blocks until first feature toggle set is received. Blocks if the mutable metrics variables are empty.
Arguments
| :: (HasUnleash r, MonadReader r m, MonadIO m) | |
| => Text | Feature toggle name. |
| -> Context | Client context. |
| -> m Bool | Whether or not the feature toggle is enabled. |
Check if a feature is enabled or not. Blocks until first feature toggle set is received. Blocks if the mutable metrics variables are empty.
Arguments
| :: (HasUnleash r, MonadReader r m, MonadIO m) | |
| => Text | Feature toggle name. |
| -> m Bool | Client context. |
Check if a feature is enabled or not. Returns false for all toggles until first toggle set is received. Blocks if the mutable metrics variables are empty.
tryIsEnabledWithContext Source #
Arguments
| :: (HasUnleash r, MonadReader r m, MonadIO m) | |
| => Text | Feature toggle name. |
| -> Context | Client context. |
| -> m Bool | Whether or not the feature toggle is enabled. |
Check if a feature is enabled or not. Returns false for all toggles until first toggle set is received. Blocks if the mutable metrics variables are empty.
Arguments
| :: (HasUnleash r, MonadReader r m, MonadIO m) | |
| => Text | Feature toggle name. |
| -> Context | Client context. |
| -> m VariantResponse | Variant. |
Get a variant. Blocks until first feature toggle set is received.
Arguments
| :: (HasUnleash r, MonadReader r m, MonadIO m) | |
| => Text | Feature toggle name. |
| -> Context | Client context. |
| -> m VariantResponse | Variant. |
Get a variant. Returns an empty variant until first toggle set is received.
Client context.
Constructors
| Context | |
Fields
| |
Instances
emptyContext :: Context #
An initial client context.
type FeatureToggleName = Text #
Alias used for feature toggle names (as they are represented on Unleash servers).
Strategy. Encompasses all (supported) types of strategies.
Constructors
| Strategy | |
Fields
| |
Instances
| FromJSON Strategy | |
| ToJSON Strategy | |
Defined in Unleash.Internal.JsonTypes | |
| Generic Strategy | |
| Show Strategy | |
| Eq Strategy | |
| type Rep Strategy | |
Defined in Unleash.Internal.JsonTypes type Rep Strategy = D1 ('MetaData "Strategy" "Unleash.Internal.JsonTypes" "unleash-client-haskell-core-0.11.0-8vB3e9Qkwy0Bxo8PcypJr9" 'False) (C1 ('MetaCons "Strategy" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "parameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text Text)))) :*: (S1 ('MetaSel ('Just "constraints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Constraint])) :*: S1 ('MetaSel ('Just "segments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Int]))))) | |
type StrategyEvaluator = forall (m :: Type -> Type). MonadIO m => Strategy -> FeatureToggleName -> Context -> m Bool #
Functions that implement strategies.
type SupportedStrategies = [Text] #
Alias for a list of supported strategies.
data VariantResponse #
Variant response.
Constructors
| VariantResponse | |