http-client-overrides-0.1.1.0: HTTP client overrides

Safe HaskellNone
LanguageHaskell2010

Network.HTTP.Client.Overrides

Contents

Synopsis

HTTP client overrides

withHttpClientOverrides :: HasCallStack => ManagerSettings -> IO (Either ParseException ManagerSettings) Source #

If the HTTP_CLIENT_OVERRIDES environment variable is set, this function reads the specified file as a ConfigFile and applies the overrides to ManagerSettings.

withHttpClientOverridesThrow :: HasCallStack => ManagerSettings -> IO ManagerSettings Source #

If the HTTP_CLIENT_OVERRIDES environment variable is set, this function reads the specified file as a ConfigFile and applies the overrides to ManagerSettings. Throws an exception if the config file can't be parsed.

httpClientOverrides :: Config -> ManagerSettings -> ManagerSettings Source #

Overrides ManagerSettings using an HTTP client override Config. Use this function if you want to define overrides directly in your source code rather than from a config file.

parseConfigFile :: FilePath -> IO (Either ParseException ConfigFile) Source #

Parses a file as a ConfigFile. Use this function if you need control over how the config file is loaded.

Types

data ConfigFile Source #

The configuration file is versioned so that it can be changed in the future and the old format gradually deprecated. The parsers uses the version field to decide how to parse the file.

Constructors

V1 Config 
Instances
Eq ConfigFile Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Show ConfigFile Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Generic ConfigFile Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Associated Types

type Rep ConfigFile :: Type -> Type #

FromJSON ConfigFile Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep ConfigFile Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep ConfigFile = D1 (MetaData "ConfigFile" "Network.HTTP.Client.Overrides.Internal.Types" "http-client-overrides-0.1.1.0-1ADWa4mmzAO6LjqUP7rpo" False) (C1 (MetaCons "V1" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Config)))

data Config Source #

This type is used when the ConfigFile version is v1.

Constructors

Config 

Fields

Instances
Eq Config Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Methods

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

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

Show Config Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Generic Config Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Associated Types

type Rep Config :: Type -> Type #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

FromJSON Config Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep Config Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep Config = D1 (MetaData "Config" "Network.HTTP.Client.Overrides.Internal.Types" "http-client-overrides-0.1.1.0-1ADWa4mmzAO6LjqUP7rpo" False) (C1 (MetaCons "Config" PrefixI True) (S1 (MetaSel (Just "logOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LogOptions) :*: S1 (MetaSel (Just "requestOverrides") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [RequestOverride])))

data LogOptions Source #

Constructors

LogOptions 

Fields

Instances
Eq LogOptions Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Show LogOptions Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Generic LogOptions Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Associated Types

type Rep LogOptions :: Type -> Type #

FromJSON LogOptions Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep LogOptions Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep LogOptions = D1 (MetaData "LogOptions" "Network.HTTP.Client.Overrides.Internal.Types" "http-client-overrides-0.1.1.0-1ADWa4mmzAO6LjqUP7rpo" False) (C1 (MetaCons "LogOptions" PrefixI True) (S1 (MetaSel (Just "logResponses") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LogFormat)) :*: (S1 (MetaSel (Just "logRequests") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LogFormat)) :*: S1 (MetaSel (Just "logRequestOverrides") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LogFormat)))))

data LogFormat Source #

Constructors

Simple

Simple log format (single-line)

Detailed

Detailed log format

Instances
Eq LogFormat Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Show LogFormat Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Generic LogFormat Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Associated Types

type Rep LogFormat :: Type -> Type #

FromJSON LogFormat Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep LogFormat Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep LogFormat = D1 (MetaData "LogFormat" "Network.HTTP.Client.Overrides.Internal.Types" "http-client-overrides-0.1.1.0-1ADWa4mmzAO6LjqUP7rpo" False) (C1 (MetaCons "Simple" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Detailed" PrefixI False) (U1 :: Type -> Type))

data RequestOverride Source #

Constructors

RequestOverride 

Fields

  • match :: !URL

    Match HTTP requests according to this URL

  • override :: !URL

    Override HTTP reuests using this URL

data URL Source #

Constructors

URL 

Fields

Instances
Eq URL Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Methods

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

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

Show URL Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Generic URL Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

Associated Types

type Rep URL :: Type -> Type #

Methods

from :: URL -> Rep URL x #

to :: Rep URL x -> URL #

FromJSON URL Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep URL Source # 
Instance details

Defined in Network.HTTP.Client.Overrides.Internal.Types

type Rep URL = D1 (MetaData "URL" "Network.HTTP.Client.Overrides.Internal.Types" "http-client-overrides-0.1.1.0-1ADWa4mmzAO6LjqUP7rpo" False) (C1 (MetaCons "URL" PrefixI True) ((S1 (MetaSel (Just "secure") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "host") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ByteString))) :*: (S1 (MetaSel (Just "port") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "path") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ByteString)))))