-- ------------------------------------------------------ --
-- Copyright © 2014 AlephCloud Systems, Inc.
-- ------------------------------------------------------ --

{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UnicodeSyntax #-}

{-# OPTIONS_HADDOCK show-extensions #-}

module Configuration.Utils.Http
(
-- * HTTP Service TLS Configuration
  HttpServiceTLSConfiguration
, hstcCertFile
, hstcKeyFile
, defaultHttpServiceTLSConfiguration
, pHttpServiceTLSConfiguration
, validateHttpServiceTLSConfiguration

-- * HTTP Service Configuration
, HttpServiceConfiguration
, hscHost
, hscPort
, hscUseTLS
, defaultHttpServiceConfiguration
, pHttpServiceConfiguration
, validateHttpServiceConfiguration

-- * Http Client Configuration
, HttpClientConfiguration
, hccHost
, hccPort
, hccUseTLS
, defaultHttpClientConfiguration
, pHttpClientConfiguration
, validateHttpClientConfiguration
, httpService2clientConfiguration
) where

import Configuration.Utils
import Configuration.Utils.Internal
import Configuration.Utils.Validation

import Control.Monad (when)
import Control.Monad.Writer.Class (tell)

import qualified Data.ByteString.Char8 as B8
import qualified Data.DList as DL
import Data.Maybe (isJust)
import Data.Monoid.Unicode

#if MIN_VERSION_base(4,13,0)
import Prelude.Unicode hiding ((×))
#else
import Prelude.Unicode
#endif

-- -------------------------------------------------------------------------- --
-- Http Service TLS Configuration

-- | In order to make TLS optional this type should be used
-- wrapped into a Maybe.
--
data HttpServiceTLSConfiguration = HttpServiceTLSConfiguration
    { HttpServiceTLSConfiguration -> FilePath
_hstcCertFile  !FilePath
    , HttpServiceTLSConfiguration -> FilePath
_hstcKeyFile  !FilePath
    }
    deriving (Int -> HttpServiceTLSConfiguration -> ShowS
[HttpServiceTLSConfiguration] -> ShowS
HttpServiceTLSConfiguration -> FilePath
(Int -> HttpServiceTLSConfiguration -> ShowS)
-> (HttpServiceTLSConfiguration -> FilePath)
-> ([HttpServiceTLSConfiguration] -> ShowS)
-> Show HttpServiceTLSConfiguration
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [HttpServiceTLSConfiguration] -> ShowS
$cshowList :: [HttpServiceTLSConfiguration] -> ShowS
show :: HttpServiceTLSConfiguration -> FilePath
$cshow :: HttpServiceTLSConfiguration -> FilePath
showsPrec :: Int -> HttpServiceTLSConfiguration -> ShowS
$cshowsPrec :: Int -> HttpServiceTLSConfiguration -> ShowS
Show, ReadPrec [HttpServiceTLSConfiguration]
ReadPrec HttpServiceTLSConfiguration
Int -> ReadS HttpServiceTLSConfiguration
ReadS [HttpServiceTLSConfiguration]
(Int -> ReadS HttpServiceTLSConfiguration)
-> ReadS [HttpServiceTLSConfiguration]
-> ReadPrec HttpServiceTLSConfiguration
-> ReadPrec [HttpServiceTLSConfiguration]
-> Read HttpServiceTLSConfiguration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HttpServiceTLSConfiguration]
$creadListPrec :: ReadPrec [HttpServiceTLSConfiguration]
readPrec :: ReadPrec HttpServiceTLSConfiguration
$creadPrec :: ReadPrec HttpServiceTLSConfiguration
readList :: ReadS [HttpServiceTLSConfiguration]
$creadList :: ReadS [HttpServiceTLSConfiguration]
readsPrec :: Int -> ReadS HttpServiceTLSConfiguration
$creadsPrec :: Int -> ReadS HttpServiceTLSConfiguration
Read, HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
(HttpServiceTLSConfiguration
 -> HttpServiceTLSConfiguration -> Bool)
-> (HttpServiceTLSConfiguration
    -> HttpServiceTLSConfiguration -> Bool)
-> Eq HttpServiceTLSConfiguration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
$c/= :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
== :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
$c== :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
Eq, Eq HttpServiceTLSConfiguration
Eq HttpServiceTLSConfiguration
-> (HttpServiceTLSConfiguration
    -> HttpServiceTLSConfiguration -> Ordering)
-> (HttpServiceTLSConfiguration
    -> HttpServiceTLSConfiguration -> Bool)
-> (HttpServiceTLSConfiguration
    -> HttpServiceTLSConfiguration -> Bool)
-> (HttpServiceTLSConfiguration
    -> HttpServiceTLSConfiguration -> Bool)
-> (HttpServiceTLSConfiguration
    -> HttpServiceTLSConfiguration -> Bool)
-> (HttpServiceTLSConfiguration
    -> HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
-> (HttpServiceTLSConfiguration
    -> HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
-> Ord HttpServiceTLSConfiguration
HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
HttpServiceTLSConfiguration
-> HttpServiceTLSConfiguration -> Ordering
HttpServiceTLSConfiguration
-> HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HttpServiceTLSConfiguration
-> HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration
$cmin :: HttpServiceTLSConfiguration
-> HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration
max :: HttpServiceTLSConfiguration
-> HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration
$cmax :: HttpServiceTLSConfiguration
-> HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration
>= :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
$c>= :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
> :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
$c> :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
<= :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
$c<= :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
< :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
$c< :: HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration -> Bool
compare :: HttpServiceTLSConfiguration
-> HttpServiceTLSConfiguration -> Ordering
$ccompare :: HttpServiceTLSConfiguration
-> HttpServiceTLSConfiguration -> Ordering
$cp1Ord :: Eq HttpServiceTLSConfiguration
Ord)

hstcCertFile  Lens' HttpServiceTLSConfiguration FilePath
hstcCertFile :: (FilePath -> f FilePath)
-> HttpServiceTLSConfiguration -> f HttpServiceTLSConfiguration
hstcCertFile = (HttpServiceTLSConfiguration -> FilePath)
-> (HttpServiceTLSConfiguration
    -> FilePath -> HttpServiceTLSConfiguration)
-> Lens
     HttpServiceTLSConfiguration
     HttpServiceTLSConfiguration
     FilePath
     FilePath
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HttpServiceTLSConfiguration -> FilePath
_hstcCertFile ((HttpServiceTLSConfiguration
  -> FilePath -> HttpServiceTLSConfiguration)
 -> Lens
      HttpServiceTLSConfiguration
      HttpServiceTLSConfiguration
      FilePath
      FilePath)
-> (HttpServiceTLSConfiguration
    -> FilePath -> HttpServiceTLSConfiguration)
-> Lens
     HttpServiceTLSConfiguration
     HttpServiceTLSConfiguration
     FilePath
     FilePath
forall a b. (a -> b) -> a -> b
$ \HttpServiceTLSConfiguration
s FilePath
a  HttpServiceTLSConfiguration
s { _hstcCertFile :: FilePath
_hstcCertFile = FilePath
a}

hstcKeyFile  Lens' HttpServiceTLSConfiguration FilePath
hstcKeyFile :: (FilePath -> f FilePath)
-> HttpServiceTLSConfiguration -> f HttpServiceTLSConfiguration
hstcKeyFile = (HttpServiceTLSConfiguration -> FilePath)
-> (HttpServiceTLSConfiguration
    -> FilePath -> HttpServiceTLSConfiguration)
-> Lens
     HttpServiceTLSConfiguration
     HttpServiceTLSConfiguration
     FilePath
     FilePath
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HttpServiceTLSConfiguration -> FilePath
_hstcKeyFile ((HttpServiceTLSConfiguration
  -> FilePath -> HttpServiceTLSConfiguration)
 -> Lens
      HttpServiceTLSConfiguration
      HttpServiceTLSConfiguration
      FilePath
      FilePath)
-> (HttpServiceTLSConfiguration
    -> FilePath -> HttpServiceTLSConfiguration)
-> Lens
     HttpServiceTLSConfiguration
     HttpServiceTLSConfiguration
     FilePath
     FilePath
forall a b. (a -> b) -> a -> b
$ \HttpServiceTLSConfiguration
s FilePath
a  HttpServiceTLSConfiguration
s { _hstcKeyFile :: FilePath
_hstcKeyFile = FilePath
a}

defaultHttpServiceTLSConfiguration  HttpServiceTLSConfiguration
defaultHttpServiceTLSConfiguration :: HttpServiceTLSConfiguration
defaultHttpServiceTLSConfiguration = HttpServiceTLSConfiguration :: FilePath -> FilePath -> HttpServiceTLSConfiguration
HttpServiceTLSConfiguration
    { _hstcCertFile :: FilePath
_hstcCertFile = FilePath
"cert.pem"
    , _hstcKeyFile :: FilePath
_hstcKeyFile = FilePath
"key.pem"
    }

validateHttpServiceTLSConfiguration
     ConfigValidation HttpServiceTLSConfiguration f
validateHttpServiceTLSConfiguration :: HttpServiceTLSConfiguration -> m ()
validateHttpServiceTLSConfiguration HttpServiceTLSConfiguration
conf = do
    Text -> FilePath -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
Text -> FilePath -> m ()
validateFileReadable Text
"cert-file" (FilePath -> m ()) -> FilePath -> m ()
forall a b. (a -> b) -> a -> b
$ HttpServiceTLSConfiguration -> FilePath
_hstcCertFile HttpServiceTLSConfiguration
conf
    Text -> FilePath -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
Text -> FilePath -> m ()
validateFileReadable Text
"key-file" (FilePath -> m ()) -> FilePath -> m ()
forall a b. (a -> b) -> a -> b
$ HttpServiceTLSConfiguration -> FilePath
_hstcKeyFile HttpServiceTLSConfiguration
conf

instance FromJSON (HttpServiceTLSConfiguration  HttpServiceTLSConfiguration) where
    parseJSON :: Value
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
parseJSON = FilePath
-> (Object
    -> Parser
         (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration))
-> Value
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
forall a. FilePath -> (Object -> Parser a) -> Value -> Parser a
withObject FilePath
"HttpServiceTLSConfiguration" ((Object
  -> Parser
       (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration))
 -> Value
 -> Parser
      (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration))
-> (Object
    -> Parser
         (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration))
-> Value
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
forall a b. (a -> b) -> a -> b
$ \Object
o  HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration
forall a. a -> a
id
        (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
forall (f :: * -> *) b c a.
Functor f =>
(b -> c) -> f (a -> b) -> f (a -> c)
<$< Lens
  HttpServiceTLSConfiguration
  HttpServiceTLSConfiguration
  FilePath
  FilePath
hstcCertFile Lens
  HttpServiceTLSConfiguration
  HttpServiceTLSConfiguration
  FilePath
  FilePath
-> Text
-> Object
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
forall b a.
FromJSON b =>
Lens' a b -> Text -> Object -> Parser (a -> a)
..: Text
"cert-file" (Object
 -> Parser
      (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration))
-> Object
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
forall a b. (a -> b) -> a -> b
% Object
o
        Parser (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< Lens
  HttpServiceTLSConfiguration
  HttpServiceTLSConfiguration
  FilePath
  FilePath
hstcKeyFile Lens
  HttpServiceTLSConfiguration
  HttpServiceTLSConfiguration
  FilePath
  FilePath
-> Text
-> Object
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
forall b a.
FromJSON b =>
Lens' a b -> Text -> Object -> Parser (a -> a)
..: Text
"pem-file" (Object
 -> Parser
      (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration))
-> Object
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
forall a b. (a -> b) -> a -> b
% Object
o

-- | This is used as default when wrapped into Maybe and
--
-- 1. the parsed value is not 'Null' and
-- 2. the given default is not 'Nothing'.
--
instance FromJSON HttpServiceTLSConfiguration where
    parseJSON :: Value -> Parser HttpServiceTLSConfiguration
parseJSON Value
v = Value
-> Parser
     (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
-> Parser HttpServiceTLSConfiguration
-> Parser HttpServiceTLSConfiguration
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> HttpServiceTLSConfiguration -> Parser HttpServiceTLSConfiguration
forall (f :: * -> *) a. Applicative f => a -> f a
pure HttpServiceTLSConfiguration
defaultHttpServiceTLSConfiguration

instance ToJSON HttpServiceTLSConfiguration where
    toJSON :: HttpServiceTLSConfiguration -> Value
toJSON HttpServiceTLSConfiguration{FilePath
_hstcKeyFile :: FilePath
_hstcCertFile :: FilePath
_hstcKeyFile :: HttpServiceTLSConfiguration -> FilePath
_hstcCertFile :: HttpServiceTLSConfiguration -> FilePath
..} = [Pair] -> Value
object
        [ Text
"cert-file" Text -> FilePath -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= FilePath
_hstcCertFile
        , Text
"key-file" Text -> FilePath -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= FilePath
_hstcKeyFile
        ]

-- | This option parser does not allow to enable or disable
-- usage of TLS. The option will have effect only when TLS
-- usage is configured in the configuration file or the default
-- configuration.
--
-- FIXME: print a warning and exit when one of these options is
-- provided even though TLS is turned off.
--
pHttpServiceTLSConfiguration  String  MParser HttpServiceTLSConfiguration
pHttpServiceTLSConfiguration :: FilePath -> MParser HttpServiceTLSConfiguration
pHttpServiceTLSConfiguration FilePath
prefix = HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration
forall a. a -> a
id
    (HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
-> MParser HttpServiceTLSConfiguration
-> MParser HttpServiceTLSConfiguration
forall (f :: * -> *) b c a.
Functor f =>
(b -> c) -> f (a -> b) -> f (a -> c)
<$< Lens
  HttpServiceTLSConfiguration
  HttpServiceTLSConfiguration
  FilePath
  FilePath
hstcCertFile Lens
  HttpServiceTLSConfiguration
  HttpServiceTLSConfiguration
  FilePath
  FilePath
-> Parser FilePath -> MParser HttpServiceTLSConfiguration
forall (f :: * -> *) a b.
(Alternative f, Applicative f) =>
Lens' a b -> f b -> f (a -> a)
.:: Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
        (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
% FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long (FilePath
prefix FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
"cert-file")
        Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall α. Monoid α => α -> α -> α
 FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"File with PEM encoded TLS Certificate"
    MParser HttpServiceTLSConfiguration
-> MParser HttpServiceTLSConfiguration
-> MParser HttpServiceTLSConfiguration
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< Lens
  HttpServiceTLSConfiguration
  HttpServiceTLSConfiguration
  FilePath
  FilePath
hstcKeyFile Lens
  HttpServiceTLSConfiguration
  HttpServiceTLSConfiguration
  FilePath
  FilePath
-> Parser FilePath -> MParser HttpServiceTLSConfiguration
forall (f :: * -> *) a b.
(Alternative f, Applicative f) =>
Lens' a b -> f b -> f (a -> a)
.:: Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
        (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
% FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long (FilePath
prefix FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
"key-file")
        Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall α. Monoid α => α -> α -> α
 FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"File with PEM encoded TLS key"

-- -------------------------------------------------------------------------- --
-- Http Service Configuration

-- | We restrict services to use either HTTP or HTTPS but not both.
--
-- TLS can be turned off explicitely in the configuration file by
-- setting the respective section to @null@. It can not be
-- turned on or off via command line options. But once it is turned
-- on the values for the certificate and key file can be changed
-- by command line options.
--
data HttpServiceConfiguration = HttpServiceConfiguration
    { HttpServiceConfiguration -> ByteString
_hscHost  !B8.ByteString
    , HttpServiceConfiguration -> Int
_hscPort  !Int
    , HttpServiceConfiguration -> ByteString
_hscInterface  !B8.ByteString
    , HttpServiceConfiguration -> Maybe HttpServiceTLSConfiguration
_hscUseTLS  !(Maybe HttpServiceTLSConfiguration)
    }
    deriving (Int -> HttpServiceConfiguration -> ShowS
[HttpServiceConfiguration] -> ShowS
HttpServiceConfiguration -> FilePath
(Int -> HttpServiceConfiguration -> ShowS)
-> (HttpServiceConfiguration -> FilePath)
-> ([HttpServiceConfiguration] -> ShowS)
-> Show HttpServiceConfiguration
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [HttpServiceConfiguration] -> ShowS
$cshowList :: [HttpServiceConfiguration] -> ShowS
show :: HttpServiceConfiguration -> FilePath
$cshow :: HttpServiceConfiguration -> FilePath
showsPrec :: Int -> HttpServiceConfiguration -> ShowS
$cshowsPrec :: Int -> HttpServiceConfiguration -> ShowS
Show, ReadPrec [HttpServiceConfiguration]
ReadPrec HttpServiceConfiguration
Int -> ReadS HttpServiceConfiguration
ReadS [HttpServiceConfiguration]
(Int -> ReadS HttpServiceConfiguration)
-> ReadS [HttpServiceConfiguration]
-> ReadPrec HttpServiceConfiguration
-> ReadPrec [HttpServiceConfiguration]
-> Read HttpServiceConfiguration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HttpServiceConfiguration]
$creadListPrec :: ReadPrec [HttpServiceConfiguration]
readPrec :: ReadPrec HttpServiceConfiguration
$creadPrec :: ReadPrec HttpServiceConfiguration
readList :: ReadS [HttpServiceConfiguration]
$creadList :: ReadS [HttpServiceConfiguration]
readsPrec :: Int -> ReadS HttpServiceConfiguration
$creadsPrec :: Int -> ReadS HttpServiceConfiguration
Read, HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
(HttpServiceConfiguration -> HttpServiceConfiguration -> Bool)
-> (HttpServiceConfiguration -> HttpServiceConfiguration -> Bool)
-> Eq HttpServiceConfiguration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
$c/= :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
== :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
$c== :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
Eq, Eq HttpServiceConfiguration
Eq HttpServiceConfiguration
-> (HttpServiceConfiguration
    -> HttpServiceConfiguration -> Ordering)
-> (HttpServiceConfiguration -> HttpServiceConfiguration -> Bool)
-> (HttpServiceConfiguration -> HttpServiceConfiguration -> Bool)
-> (HttpServiceConfiguration -> HttpServiceConfiguration -> Bool)
-> (HttpServiceConfiguration -> HttpServiceConfiguration -> Bool)
-> (HttpServiceConfiguration
    -> HttpServiceConfiguration -> HttpServiceConfiguration)
-> (HttpServiceConfiguration
    -> HttpServiceConfiguration -> HttpServiceConfiguration)
-> Ord HttpServiceConfiguration
HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
HttpServiceConfiguration -> HttpServiceConfiguration -> Ordering
HttpServiceConfiguration
-> HttpServiceConfiguration -> HttpServiceConfiguration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HttpServiceConfiguration
-> HttpServiceConfiguration -> HttpServiceConfiguration
$cmin :: HttpServiceConfiguration
-> HttpServiceConfiguration -> HttpServiceConfiguration
max :: HttpServiceConfiguration
-> HttpServiceConfiguration -> HttpServiceConfiguration
$cmax :: HttpServiceConfiguration
-> HttpServiceConfiguration -> HttpServiceConfiguration
>= :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
$c>= :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
> :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
$c> :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
<= :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
$c<= :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
< :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
$c< :: HttpServiceConfiguration -> HttpServiceConfiguration -> Bool
compare :: HttpServiceConfiguration -> HttpServiceConfiguration -> Ordering
$ccompare :: HttpServiceConfiguration -> HttpServiceConfiguration -> Ordering
$cp1Ord :: Eq HttpServiceConfiguration
Ord)

hscHost  Lens' HttpServiceConfiguration B8.ByteString
hscHost :: (ByteString -> f ByteString)
-> HttpServiceConfiguration -> f HttpServiceConfiguration
hscHost = (HttpServiceConfiguration -> ByteString)
-> (HttpServiceConfiguration
    -> ByteString -> HttpServiceConfiguration)
-> Lens
     HttpServiceConfiguration
     HttpServiceConfiguration
     ByteString
     ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HttpServiceConfiguration -> ByteString
_hscHost ((HttpServiceConfiguration
  -> ByteString -> HttpServiceConfiguration)
 -> Lens
      HttpServiceConfiguration
      HttpServiceConfiguration
      ByteString
      ByteString)
-> (HttpServiceConfiguration
    -> ByteString -> HttpServiceConfiguration)
-> Lens
     HttpServiceConfiguration
     HttpServiceConfiguration
     ByteString
     ByteString
forall a b. (a -> b) -> a -> b
$ \HttpServiceConfiguration
s ByteString
a  HttpServiceConfiguration
s { _hscHost :: ByteString
_hscHost = ByteString
a}

hscPort  Lens' HttpServiceConfiguration Int
hscPort :: (Int -> f Int)
-> HttpServiceConfiguration -> f HttpServiceConfiguration
hscPort = (HttpServiceConfiguration -> Int)
-> (HttpServiceConfiguration -> Int -> HttpServiceConfiguration)
-> Lens HttpServiceConfiguration HttpServiceConfiguration Int Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HttpServiceConfiguration -> Int
_hscPort ((HttpServiceConfiguration -> Int -> HttpServiceConfiguration)
 -> Lens HttpServiceConfiguration HttpServiceConfiguration Int Int)
-> (HttpServiceConfiguration -> Int -> HttpServiceConfiguration)
-> Lens HttpServiceConfiguration HttpServiceConfiguration Int Int
forall a b. (a -> b) -> a -> b
$ \HttpServiceConfiguration
s Int
a  HttpServiceConfiguration
s { _hscPort :: Int
_hscPort = Int
a}

hscInterface  Lens' HttpServiceConfiguration B8.ByteString
hscInterface :: (ByteString -> f ByteString)
-> HttpServiceConfiguration -> f HttpServiceConfiguration
hscInterface = (HttpServiceConfiguration -> ByteString)
-> (HttpServiceConfiguration
    -> ByteString -> HttpServiceConfiguration)
-> Lens
     HttpServiceConfiguration
     HttpServiceConfiguration
     ByteString
     ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HttpServiceConfiguration -> ByteString
_hscInterface ((HttpServiceConfiguration
  -> ByteString -> HttpServiceConfiguration)
 -> Lens
      HttpServiceConfiguration
      HttpServiceConfiguration
      ByteString
      ByteString)
-> (HttpServiceConfiguration
    -> ByteString -> HttpServiceConfiguration)
-> Lens
     HttpServiceConfiguration
     HttpServiceConfiguration
     ByteString
     ByteString
forall a b. (a -> b) -> a -> b
$ \HttpServiceConfiguration
s ByteString
a  HttpServiceConfiguration
s { _hscInterface :: ByteString
_hscInterface = ByteString
a}

hscUseTLS  Lens' HttpServiceConfiguration (Maybe HttpServiceTLSConfiguration)
hscUseTLS :: (Maybe HttpServiceTLSConfiguration
 -> f (Maybe HttpServiceTLSConfiguration))
-> HttpServiceConfiguration -> f HttpServiceConfiguration
hscUseTLS = (HttpServiceConfiguration -> Maybe HttpServiceTLSConfiguration)
-> (HttpServiceConfiguration
    -> Maybe HttpServiceTLSConfiguration -> HttpServiceConfiguration)
-> Lens
     HttpServiceConfiguration
     HttpServiceConfiguration
     (Maybe HttpServiceTLSConfiguration)
     (Maybe HttpServiceTLSConfiguration)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HttpServiceConfiguration -> Maybe HttpServiceTLSConfiguration
_hscUseTLS ((HttpServiceConfiguration
  -> Maybe HttpServiceTLSConfiguration -> HttpServiceConfiguration)
 -> Lens
      HttpServiceConfiguration
      HttpServiceConfiguration
      (Maybe HttpServiceTLSConfiguration)
      (Maybe HttpServiceTLSConfiguration))
-> (HttpServiceConfiguration
    -> Maybe HttpServiceTLSConfiguration -> HttpServiceConfiguration)
-> Lens
     HttpServiceConfiguration
     HttpServiceConfiguration
     (Maybe HttpServiceTLSConfiguration)
     (Maybe HttpServiceTLSConfiguration)
forall a b. (a -> b) -> a -> b
$ \HttpServiceConfiguration
s Maybe HttpServiceTLSConfiguration
a  HttpServiceConfiguration
s { _hscUseTLS :: Maybe HttpServiceTLSConfiguration
_hscUseTLS = Maybe HttpServiceTLSConfiguration
a}

defaultHttpServiceConfiguration  HttpServiceConfiguration
defaultHttpServiceConfiguration :: HttpServiceConfiguration
defaultHttpServiceConfiguration = HttpServiceConfiguration :: ByteString
-> Int
-> ByteString
-> Maybe HttpServiceTLSConfiguration
-> HttpServiceConfiguration
HttpServiceConfiguration
    { _hscHost :: ByteString
_hscHost = ByteString
"localhost"
    , _hscPort :: Int
_hscPort = Int
80
    , _hscInterface :: ByteString
_hscInterface = ByteString
"0.0.0.0"
    , _hscUseTLS :: Maybe HttpServiceTLSConfiguration
_hscUseTLS = Maybe HttpServiceTLSConfiguration
forall a. Maybe a
Nothing
    }

validateHttpServiceConfiguration  ConfigValidation HttpServiceConfiguration DL.DList
validateHttpServiceConfiguration :: HttpServiceConfiguration -> m ()
validateHttpServiceConfiguration HttpServiceConfiguration
conf = do
    m ()
-> (HttpServiceTLSConfiguration -> m ())
-> Maybe HttpServiceTLSConfiguration
-> m ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) HttpServiceTLSConfiguration -> m ()
forall (f :: * -> *).
ConfigValidation HttpServiceTLSConfiguration f
validateHttpServiceTLSConfiguration (Maybe HttpServiceTLSConfiguration -> m ())
-> Maybe HttpServiceTLSConfiguration -> m ()
forall a b. (a -> b) -> a -> b
$ HttpServiceConfiguration -> Maybe HttpServiceTLSConfiguration
_hscUseTLS HttpServiceConfiguration
conf
    Text -> Int -> m ()
forall (m :: * -> *) n.
(MonadError Text m, Integral n, Show n) =>
Text -> n -> m ()
validatePort Text
"port" (Int -> m ()) -> Int -> m ()
forall a b. (a -> b) -> a -> b
$ HttpServiceConfiguration -> Int
_hscPort HttpServiceConfiguration
conf
    Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (HttpServiceConfiguration -> Int
_hscPort HttpServiceConfiguration
conf Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1024) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
        DList Text -> m ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [Item (DList Text)
"listening on a priviledged port requires super user rights"]
    Text -> ByteString -> m ()
forall (m :: * -> *) a.
(MonadError Text m, Eq a, Monoid a) =>
Text -> a -> m ()
validateNonEmpty Text
"host" (ByteString -> m ()) -> ByteString -> m ()
forall a b. (a -> b) -> a -> b
$ HttpServiceConfiguration -> ByteString
_hscHost HttpServiceConfiguration
conf
    Text -> FilePath -> m ()
forall (m :: * -> *). MonadError Text m => Text -> FilePath -> m ()
validateIPv4 Text
"interface" (FilePath -> m ())
-> (ByteString -> FilePath) -> ByteString -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> FilePath
B8.unpack (ByteString -> m ()) -> ByteString -> m ()
forall a b. (a -> b) -> a -> b
$ HttpServiceConfiguration -> ByteString
_hscInterface HttpServiceConfiguration
conf

instance FromJSON (HttpServiceConfiguration  HttpServiceConfiguration) where
    parseJSON :: Value
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
parseJSON = FilePath
-> (Object
    -> Parser (HttpServiceConfiguration -> HttpServiceConfiguration))
-> Value
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall a. FilePath -> (Object -> Parser a) -> Value -> Parser a
withObject FilePath
"HttpServiceConfiguration" ((Object
  -> Parser (HttpServiceConfiguration -> HttpServiceConfiguration))
 -> Value
 -> Parser (HttpServiceConfiguration -> HttpServiceConfiguration))
-> (Object
    -> Parser (HttpServiceConfiguration -> HttpServiceConfiguration))
-> Value
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall a b. (a -> b) -> a -> b
$ \Object
o  HttpServiceConfiguration -> HttpServiceConfiguration
forall a. a -> a
id
        (HttpServiceConfiguration -> HttpServiceConfiguration)
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall (f :: * -> *) b c a.
Functor f =>
(b -> c) -> f (a -> b) -> f (a -> c)
<$< (ByteString -> f ByteString)
-> HttpServiceConfiguration -> f HttpServiceConfiguration
Lens
  HttpServiceConfiguration
  HttpServiceConfiguration
  ByteString
  ByteString
hscHost ((ByteString -> f ByteString)
 -> HttpServiceConfiguration -> f HttpServiceConfiguration)
-> ((FilePath -> f FilePath) -> ByteString -> f ByteString)
-> (FilePath -> f FilePath)
-> HttpServiceConfiguration
-> f HttpServiceConfiguration
forall b c a. (b -> c) -> (a -> b) -> a -> c
 (FilePath -> f FilePath) -> ByteString -> f ByteString
Iso' ByteString FilePath
bs (forall (f :: * -> *).
 Functor f =>
 (FilePath -> f FilePath)
 -> HttpServiceConfiguration -> f HttpServiceConfiguration)
-> Text
-> Object
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall b a.
FromJSON b =>
Lens' a b -> Text -> Object -> Parser (a -> a)
..: Text
"host" (Object
 -> Parser (HttpServiceConfiguration -> HttpServiceConfiguration))
-> Object
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall a b. (a -> b) -> a -> b
% Object
o
        Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< Lens HttpServiceConfiguration HttpServiceConfiguration Int Int
hscPort Lens HttpServiceConfiguration HttpServiceConfiguration Int Int
-> Text
-> Object
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall b a.
FromJSON b =>
Lens' a b -> Text -> Object -> Parser (a -> a)
..: Text
"port" (Object
 -> Parser (HttpServiceConfiguration -> HttpServiceConfiguration))
-> Object
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall a b. (a -> b) -> a -> b
% Object
o
        Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< (ByteString -> f ByteString)
-> HttpServiceConfiguration -> f HttpServiceConfiguration
Lens
  HttpServiceConfiguration
  HttpServiceConfiguration
  ByteString
  ByteString
hscInterface ((ByteString -> f ByteString)
 -> HttpServiceConfiguration -> f HttpServiceConfiguration)
-> ((FilePath -> f FilePath) -> ByteString -> f ByteString)
-> (FilePath -> f FilePath)
-> HttpServiceConfiguration
-> f HttpServiceConfiguration
forall b c a. (b -> c) -> (a -> b) -> a -> c
 (FilePath -> f FilePath) -> ByteString -> f ByteString
Iso' ByteString FilePath
bs (forall (f :: * -> *).
 Functor f =>
 (FilePath -> f FilePath)
 -> HttpServiceConfiguration -> f HttpServiceConfiguration)
-> Text
-> Object
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall b a.
FromJSON b =>
Lens' a b -> Text -> Object -> Parser (a -> a)
..: Text
"interface" (Object
 -> Parser (HttpServiceConfiguration -> HttpServiceConfiguration))
-> Object
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall a b. (a -> b) -> a -> b
% Object
o
        Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< Lens
  HttpServiceConfiguration
  HttpServiceConfiguration
  (Maybe HttpServiceTLSConfiguration)
  (Maybe HttpServiceTLSConfiguration)
hscUseTLS Lens
  HttpServiceConfiguration
  HttpServiceConfiguration
  (Maybe HttpServiceTLSConfiguration)
  (Maybe HttpServiceTLSConfiguration)
-> Text
-> Object
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall b a.
FromJSON (b -> b) =>
Lens' a b -> Text -> Object -> Parser (a -> a)
%.: Text
"use-tls" (Object
 -> Parser (HttpServiceConfiguration -> HttpServiceConfiguration))
-> Object
-> Parser (HttpServiceConfiguration -> HttpServiceConfiguration)
forall a b. (a -> b) -> a -> b
% Object
o
      where
        bs  Iso' B8.ByteString String
        bs :: p FilePath (f FilePath) -> p ByteString (f ByteString)
bs = (ByteString -> FilePath)
-> (FilePath -> ByteString) -> Iso' ByteString FilePath
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ByteString -> FilePath
B8.unpack FilePath -> ByteString
B8.pack

instance ToJSON HttpServiceConfiguration where
    toJSON :: HttpServiceConfiguration -> Value
toJSON HttpServiceConfiguration{Int
Maybe HttpServiceTLSConfiguration
ByteString
_hscUseTLS :: Maybe HttpServiceTLSConfiguration
_hscInterface :: ByteString
_hscPort :: Int
_hscHost :: ByteString
_hscUseTLS :: HttpServiceConfiguration -> Maybe HttpServiceTLSConfiguration
_hscInterface :: HttpServiceConfiguration -> ByteString
_hscPort :: HttpServiceConfiguration -> Int
_hscHost :: HttpServiceConfiguration -> ByteString
..} = [Pair] -> Value
object
        [ Text
"host" Text -> FilePath -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ByteString -> FilePath
B8.unpack ByteString
_hscHost
        , Text
"port" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Int
_hscPort
        , Text
"interface" Text -> FilePath -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ByteString -> FilePath
B8.unpack ByteString
_hscInterface
        , Text
"use-tls" Text -> Maybe HttpServiceTLSConfiguration -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe HttpServiceTLSConfiguration
_hscUseTLS
        ]

pHttpServiceConfiguration  String  MParser HttpServiceConfiguration
pHttpServiceConfiguration :: FilePath -> MParser HttpServiceConfiguration
pHttpServiceConfiguration FilePath
prefix = HttpServiceConfiguration -> HttpServiceConfiguration
forall a. a -> a
id
    (HttpServiceConfiguration -> HttpServiceConfiguration)
-> MParser HttpServiceConfiguration
-> MParser HttpServiceConfiguration
forall (f :: * -> *) b c a.
Functor f =>
(b -> c) -> f (a -> b) -> f (a -> c)
<$< (ByteString -> f ByteString)
-> HttpServiceConfiguration -> f HttpServiceConfiguration
Lens
  HttpServiceConfiguration
  HttpServiceConfiguration
  ByteString
  ByteString
hscHost ((ByteString -> f ByteString)
 -> HttpServiceConfiguration -> f HttpServiceConfiguration)
-> ((FilePath -> f FilePath) -> ByteString -> f ByteString)
-> (FilePath -> f FilePath)
-> HttpServiceConfiguration
-> f HttpServiceConfiguration
forall b c a. (b -> c) -> (a -> b) -> a -> c
 (FilePath -> f FilePath) -> ByteString -> f ByteString
Iso' ByteString FilePath
bs (forall (f :: * -> *).
 Functor f =>
 (FilePath -> f FilePath)
 -> HttpServiceConfiguration -> f HttpServiceConfiguration)
-> Parser FilePath -> MParser HttpServiceConfiguration
forall (f :: * -> *) a b.
(Alternative f, Applicative f) =>
Lens' a b -> f b -> f (a -> a)
.:: Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
        (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
% FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long (FilePath
prefix FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
"host")
        Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall α. Monoid α => α -> α -> α
 FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Hostname of the service"
    MParser HttpServiceConfiguration
-> MParser HttpServiceConfiguration
-> MParser HttpServiceConfiguration
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< Lens HttpServiceConfiguration HttpServiceConfiguration Int Int
hscPort Lens HttpServiceConfiguration HttpServiceConfiguration Int Int
-> Parser Int -> MParser HttpServiceConfiguration
forall (f :: * -> *) a b.
(Alternative f, Applicative f) =>
Lens' a b -> f b -> f (a -> a)
.:: ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto
        (Mod OptionFields Int -> Parser Int)
-> Mod OptionFields Int -> Parser Int
forall a b. (a -> b) -> a -> b
% FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long (FilePath
prefix FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
"port")
        Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall α. Monoid α => α -> α -> α
 FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Port of the service"
    MParser HttpServiceConfiguration
-> MParser HttpServiceConfiguration
-> MParser HttpServiceConfiguration
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< (ByteString -> f ByteString)
-> HttpServiceConfiguration -> f HttpServiceConfiguration
Lens
  HttpServiceConfiguration
  HttpServiceConfiguration
  ByteString
  ByteString
hscInterface ((ByteString -> f ByteString)
 -> HttpServiceConfiguration -> f HttpServiceConfiguration)
-> ((FilePath -> f FilePath) -> ByteString -> f ByteString)
-> (FilePath -> f FilePath)
-> HttpServiceConfiguration
-> f HttpServiceConfiguration
forall b c a. (b -> c) -> (a -> b) -> a -> c
 (FilePath -> f FilePath) -> ByteString -> f ByteString
Iso' ByteString FilePath
bs (forall (f :: * -> *).
 Functor f =>
 (FilePath -> f FilePath)
 -> HttpServiceConfiguration -> f HttpServiceConfiguration)
-> Parser FilePath -> MParser HttpServiceConfiguration
forall (f :: * -> *) a b.
(Alternative f, Applicative f) =>
Lens' a b -> f b -> f (a -> a)
.:: ReadM FilePath -> Mod OptionFields FilePath -> Parser FilePath
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM FilePath
forall a. Read a => ReadM a
auto
        (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
% FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long (FilePath
prefix FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
"interface")
        Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall α. Monoid α => α -> α -> α
 FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Interface of the service"
    MParser HttpServiceConfiguration
-> MParser HttpServiceConfiguration
-> MParser HttpServiceConfiguration
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< (Lens
  HttpServiceConfiguration
  HttpServiceConfiguration
  (Maybe HttpServiceTLSConfiguration)
  (Maybe HttpServiceTLSConfiguration)
hscUseTLS Lens
  HttpServiceConfiguration
  HttpServiceConfiguration
  (Maybe HttpServiceTLSConfiguration)
  (Maybe HttpServiceTLSConfiguration)
-> Parser
     (Maybe HttpServiceTLSConfiguration
      -> Maybe HttpServiceTLSConfiguration)
-> MParser HttpServiceConfiguration
forall (f :: * -> *) a b.
(Alternative f, Applicative f) =>
Lens' a b -> f (b -> b) -> f (a -> a)
%:: ((HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
-> Maybe HttpServiceTLSConfiguration
-> Maybe HttpServiceTLSConfiguration
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((HttpServiceTLSConfiguration -> HttpServiceTLSConfiguration)
 -> Maybe HttpServiceTLSConfiguration
 -> Maybe HttpServiceTLSConfiguration)
-> MParser HttpServiceTLSConfiguration
-> Parser
     (Maybe HttpServiceTLSConfiguration
      -> Maybe HttpServiceTLSConfiguration)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> MParser HttpServiceTLSConfiguration
pHttpServiceTLSConfiguration FilePath
prefix))
  where
    bs  Iso' B8.ByteString String
    bs :: p FilePath (f FilePath) -> p ByteString (f ByteString)
bs = (ByteString -> FilePath)
-> (FilePath -> ByteString) -> Iso' ByteString FilePath
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ByteString -> FilePath
B8.unpack FilePath -> ByteString
B8.pack

-- -------------------------------------------------------------------------- --
-- Http Client Configuration

data HttpClientConfiguration = HttpClientConfiguration
    { HttpClientConfiguration -> ByteString
_hccHost  !B8.ByteString
    , HttpClientConfiguration -> Int
_hccPort  !Int
    , HttpClientConfiguration -> Bool
_hccUseTLS  !Bool
    }
    deriving (Int -> HttpClientConfiguration -> ShowS
[HttpClientConfiguration] -> ShowS
HttpClientConfiguration -> FilePath
(Int -> HttpClientConfiguration -> ShowS)
-> (HttpClientConfiguration -> FilePath)
-> ([HttpClientConfiguration] -> ShowS)
-> Show HttpClientConfiguration
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [HttpClientConfiguration] -> ShowS
$cshowList :: [HttpClientConfiguration] -> ShowS
show :: HttpClientConfiguration -> FilePath
$cshow :: HttpClientConfiguration -> FilePath
showsPrec :: Int -> HttpClientConfiguration -> ShowS
$cshowsPrec :: Int -> HttpClientConfiguration -> ShowS
Show, ReadPrec [HttpClientConfiguration]
ReadPrec HttpClientConfiguration
Int -> ReadS HttpClientConfiguration
ReadS [HttpClientConfiguration]
(Int -> ReadS HttpClientConfiguration)
-> ReadS [HttpClientConfiguration]
-> ReadPrec HttpClientConfiguration
-> ReadPrec [HttpClientConfiguration]
-> Read HttpClientConfiguration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HttpClientConfiguration]
$creadListPrec :: ReadPrec [HttpClientConfiguration]
readPrec :: ReadPrec HttpClientConfiguration
$creadPrec :: ReadPrec HttpClientConfiguration
readList :: ReadS [HttpClientConfiguration]
$creadList :: ReadS [HttpClientConfiguration]
readsPrec :: Int -> ReadS HttpClientConfiguration
$creadsPrec :: Int -> ReadS HttpClientConfiguration
Read, HttpClientConfiguration -> HttpClientConfiguration -> Bool
(HttpClientConfiguration -> HttpClientConfiguration -> Bool)
-> (HttpClientConfiguration -> HttpClientConfiguration -> Bool)
-> Eq HttpClientConfiguration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
$c/= :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
== :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
$c== :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
Eq, Eq HttpClientConfiguration
Eq HttpClientConfiguration
-> (HttpClientConfiguration -> HttpClientConfiguration -> Ordering)
-> (HttpClientConfiguration -> HttpClientConfiguration -> Bool)
-> (HttpClientConfiguration -> HttpClientConfiguration -> Bool)
-> (HttpClientConfiguration -> HttpClientConfiguration -> Bool)
-> (HttpClientConfiguration -> HttpClientConfiguration -> Bool)
-> (HttpClientConfiguration
    -> HttpClientConfiguration -> HttpClientConfiguration)
-> (HttpClientConfiguration
    -> HttpClientConfiguration -> HttpClientConfiguration)
-> Ord HttpClientConfiguration
HttpClientConfiguration -> HttpClientConfiguration -> Bool
HttpClientConfiguration -> HttpClientConfiguration -> Ordering
HttpClientConfiguration
-> HttpClientConfiguration -> HttpClientConfiguration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HttpClientConfiguration
-> HttpClientConfiguration -> HttpClientConfiguration
$cmin :: HttpClientConfiguration
-> HttpClientConfiguration -> HttpClientConfiguration
max :: HttpClientConfiguration
-> HttpClientConfiguration -> HttpClientConfiguration
$cmax :: HttpClientConfiguration
-> HttpClientConfiguration -> HttpClientConfiguration
>= :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
$c>= :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
> :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
$c> :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
<= :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
$c<= :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
< :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
$c< :: HttpClientConfiguration -> HttpClientConfiguration -> Bool
compare :: HttpClientConfiguration -> HttpClientConfiguration -> Ordering
$ccompare :: HttpClientConfiguration -> HttpClientConfiguration -> Ordering
$cp1Ord :: Eq HttpClientConfiguration
Ord)

hccHost  Lens' HttpClientConfiguration B8.ByteString
hccHost :: (ByteString -> f ByteString)
-> HttpClientConfiguration -> f HttpClientConfiguration
hccHost = (HttpClientConfiguration -> ByteString)
-> (HttpClientConfiguration
    -> ByteString -> HttpClientConfiguration)
-> Lens
     HttpClientConfiguration
     HttpClientConfiguration
     ByteString
     ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HttpClientConfiguration -> ByteString
_hccHost ((HttpClientConfiguration -> ByteString -> HttpClientConfiguration)
 -> Lens
      HttpClientConfiguration
      HttpClientConfiguration
      ByteString
      ByteString)
-> (HttpClientConfiguration
    -> ByteString -> HttpClientConfiguration)
-> Lens
     HttpClientConfiguration
     HttpClientConfiguration
     ByteString
     ByteString
forall a b. (a -> b) -> a -> b
$ \HttpClientConfiguration
s ByteString
a  HttpClientConfiguration
s { _hccHost :: ByteString
_hccHost = ByteString
a}

hccPort  Lens' HttpClientConfiguration Int
hccPort :: (Int -> f Int)
-> HttpClientConfiguration -> f HttpClientConfiguration
hccPort = (HttpClientConfiguration -> Int)
-> (HttpClientConfiguration -> Int -> HttpClientConfiguration)
-> Lens HttpClientConfiguration HttpClientConfiguration Int Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HttpClientConfiguration -> Int
_hccPort ((HttpClientConfiguration -> Int -> HttpClientConfiguration)
 -> Lens HttpClientConfiguration HttpClientConfiguration Int Int)
-> (HttpClientConfiguration -> Int -> HttpClientConfiguration)
-> Lens HttpClientConfiguration HttpClientConfiguration Int Int
forall a b. (a -> b) -> a -> b
$ \HttpClientConfiguration
s Int
a  HttpClientConfiguration
s { _hccPort :: Int
_hccPort = Int
a}

hccUseTLS  Lens' HttpClientConfiguration Bool
hccUseTLS :: (Bool -> f Bool)
-> HttpClientConfiguration -> f HttpClientConfiguration
hccUseTLS = (HttpClientConfiguration -> Bool)
-> (HttpClientConfiguration -> Bool -> HttpClientConfiguration)
-> Lens HttpClientConfiguration HttpClientConfiguration Bool Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens HttpClientConfiguration -> Bool
_hccUseTLS ((HttpClientConfiguration -> Bool -> HttpClientConfiguration)
 -> Lens HttpClientConfiguration HttpClientConfiguration Bool Bool)
-> (HttpClientConfiguration -> Bool -> HttpClientConfiguration)
-> Lens HttpClientConfiguration HttpClientConfiguration Bool Bool
forall a b. (a -> b) -> a -> b
$ \HttpClientConfiguration
s Bool
a  HttpClientConfiguration
s { _hccUseTLS :: Bool
_hccUseTLS = Bool
a}

defaultHttpClientConfiguration  HttpClientConfiguration
defaultHttpClientConfiguration :: HttpClientConfiguration
defaultHttpClientConfiguration = HttpClientConfiguration :: ByteString -> Int -> Bool -> HttpClientConfiguration
HttpClientConfiguration
    { _hccHost :: ByteString
_hccHost = ByteString
"localhost"
    , _hccPort :: Int
_hccPort = Int
80
    , _hccUseTLS :: Bool
_hccUseTLS = Bool
False
    }

validateHttpClientConfiguration  ConfigValidation HttpClientConfiguration f
validateHttpClientConfiguration :: HttpClientConfiguration -> m ()
validateHttpClientConfiguration HttpClientConfiguration
conf = do
    Text -> Int -> m ()
forall (m :: * -> *) n.
(MonadError Text m, Integral n, Show n) =>
Text -> n -> m ()
validatePort Text
"port" (Int -> m ()) -> Int -> m ()
forall a b. (a -> b) -> a -> b
$ HttpClientConfiguration -> Int
_hccPort HttpClientConfiguration
conf
    Text -> ByteString -> m ()
forall (m :: * -> *) a.
(MonadError Text m, Eq a, Monoid a) =>
Text -> a -> m ()
validateNonEmpty Text
"host" (ByteString -> m ()) -> ByteString -> m ()
forall a b. (a -> b) -> a -> b
$ HttpClientConfiguration -> ByteString
_hccHost HttpClientConfiguration
conf

instance FromJSON (HttpClientConfiguration  HttpClientConfiguration) where
    parseJSON :: Value
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
parseJSON = FilePath
-> (Object
    -> Parser (HttpClientConfiguration -> HttpClientConfiguration))
-> Value
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall a. FilePath -> (Object -> Parser a) -> Value -> Parser a
withObject FilePath
"HttpClientConfiguration" ((Object
  -> Parser (HttpClientConfiguration -> HttpClientConfiguration))
 -> Value
 -> Parser (HttpClientConfiguration -> HttpClientConfiguration))
-> (Object
    -> Parser (HttpClientConfiguration -> HttpClientConfiguration))
-> Value
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall a b. (a -> b) -> a -> b
$ \Object
o  HttpClientConfiguration -> HttpClientConfiguration
forall a. a -> a
id
        (HttpClientConfiguration -> HttpClientConfiguration)
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall (f :: * -> *) b c a.
Functor f =>
(b -> c) -> f (a -> b) -> f (a -> c)
<$< (ByteString -> f ByteString)
-> HttpClientConfiguration -> f HttpClientConfiguration
Lens
  HttpClientConfiguration
  HttpClientConfiguration
  ByteString
  ByteString
hccHost ((ByteString -> f ByteString)
 -> HttpClientConfiguration -> f HttpClientConfiguration)
-> ((FilePath -> f FilePath) -> ByteString -> f ByteString)
-> (FilePath -> f FilePath)
-> HttpClientConfiguration
-> f HttpClientConfiguration
forall b c a. (b -> c) -> (a -> b) -> a -> c
 (FilePath -> f FilePath) -> ByteString -> f ByteString
Iso' ByteString FilePath
bs (forall (f :: * -> *).
 Functor f =>
 (FilePath -> f FilePath)
 -> HttpClientConfiguration -> f HttpClientConfiguration)
-> Text
-> Object
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall b a.
FromJSON b =>
Lens' a b -> Text -> Object -> Parser (a -> a)
..: Text
"host" (Object
 -> Parser (HttpClientConfiguration -> HttpClientConfiguration))
-> Object
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall a b. (a -> b) -> a -> b
% Object
o
        Parser (HttpClientConfiguration -> HttpClientConfiguration)
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< Lens HttpClientConfiguration HttpClientConfiguration Int Int
hccPort Lens HttpClientConfiguration HttpClientConfiguration Int Int
-> Text
-> Object
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall b a.
FromJSON b =>
Lens' a b -> Text -> Object -> Parser (a -> a)
..: Text
"port" (Object
 -> Parser (HttpClientConfiguration -> HttpClientConfiguration))
-> Object
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall a b. (a -> b) -> a -> b
% Object
o
        Parser (HttpClientConfiguration -> HttpClientConfiguration)
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< Lens HttpClientConfiguration HttpClientConfiguration Bool Bool
hccUseTLS Lens HttpClientConfiguration HttpClientConfiguration Bool Bool
-> Text
-> Object
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall b a.
FromJSON b =>
Lens' a b -> Text -> Object -> Parser (a -> a)
..: Text
"use-tls" (Object
 -> Parser (HttpClientConfiguration -> HttpClientConfiguration))
-> Object
-> Parser (HttpClientConfiguration -> HttpClientConfiguration)
forall a b. (a -> b) -> a -> b
% Object
o
      where
        bs  Iso' B8.ByteString String
        bs :: p FilePath (f FilePath) -> p ByteString (f ByteString)
bs = (ByteString -> FilePath)
-> (FilePath -> ByteString) -> Iso' ByteString FilePath
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ByteString -> FilePath
B8.unpack FilePath -> ByteString
B8.pack

instance ToJSON HttpClientConfiguration where
    toJSON :: HttpClientConfiguration -> Value
toJSON HttpClientConfiguration{Bool
Int
ByteString
_hccUseTLS :: Bool
_hccPort :: Int
_hccHost :: ByteString
_hccUseTLS :: HttpClientConfiguration -> Bool
_hccPort :: HttpClientConfiguration -> Int
_hccHost :: HttpClientConfiguration -> ByteString
..} = [Pair] -> Value
object
        [ Text
"host" Text -> FilePath -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ByteString -> FilePath
B8.unpack ByteString
_hccHost
        , Text
"port" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Int
_hccPort
        , Text
"use-tls" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
_hccUseTLS
        ]

pHttpClientConfiguration  String  MParser HttpClientConfiguration
pHttpClientConfiguration :: FilePath -> MParser HttpClientConfiguration
pHttpClientConfiguration FilePath
serviceName = HttpClientConfiguration -> HttpClientConfiguration
forall a. a -> a
id
    (HttpClientConfiguration -> HttpClientConfiguration)
-> MParser HttpClientConfiguration
-> MParser HttpClientConfiguration
forall (f :: * -> *) b c a.
Functor f =>
(b -> c) -> f (a -> b) -> f (a -> c)
<$< (ByteString -> f ByteString)
-> HttpClientConfiguration -> f HttpClientConfiguration
Lens
  HttpClientConfiguration
  HttpClientConfiguration
  ByteString
  ByteString
hccHost ((ByteString -> f ByteString)
 -> HttpClientConfiguration -> f HttpClientConfiguration)
-> ((FilePath -> f FilePath) -> ByteString -> f ByteString)
-> (FilePath -> f FilePath)
-> HttpClientConfiguration
-> f HttpClientConfiguration
forall b c a. (b -> c) -> (a -> b) -> a -> c
 (FilePath -> f FilePath) -> ByteString -> f ByteString
Iso' ByteString FilePath
bs (forall (f :: * -> *).
 Functor f =>
 (FilePath -> f FilePath)
 -> HttpClientConfiguration -> f HttpClientConfiguration)
-> Parser FilePath -> MParser HttpClientConfiguration
forall (f :: * -> *) a b.
(Alternative f, Applicative f) =>
Lens' a b -> f b -> f (a -> a)
.:: Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
        (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
% FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long (FilePath
serviceName FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
"-host")
        Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall α. Monoid α => α -> α -> α
 FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help (FilePath
"Hostname of " FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
serviceName)
    MParser HttpClientConfiguration
-> MParser HttpClientConfiguration
-> MParser HttpClientConfiguration
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< Lens HttpClientConfiguration HttpClientConfiguration Int Int
hccPort Lens HttpClientConfiguration HttpClientConfiguration Int Int
-> Parser Int -> MParser HttpClientConfiguration
forall (f :: * -> *) a b.
(Alternative f, Applicative f) =>
Lens' a b -> f b -> f (a -> a)
.:: ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto
        (Mod OptionFields Int -> Parser Int)
-> Mod OptionFields Int -> Parser Int
forall a b. (a -> b) -> a -> b
% FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long (FilePath
serviceName FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
"-port")
        Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall α. Monoid α => α -> α -> α
 FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. FilePath -> Mod f a
help (FilePath
"Port of " FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
serviceName)
    MParser HttpClientConfiguration
-> MParser HttpClientConfiguration
-> MParser HttpClientConfiguration
forall (f :: * -> *) b c a.
Applicative f =>
f (b -> c) -> f (a -> b) -> f (a -> c)
<*< Lens HttpClientConfiguration HttpClientConfiguration Bool Bool
hccUseTLS Lens HttpClientConfiguration HttpClientConfiguration Bool Bool
-> Parser Bool -> MParser HttpClientConfiguration
forall (f :: * -> *) a b.
(Alternative f, Applicative f) =>
Lens' a b -> f b -> f (a -> a)
.:: Mod FlagFields Bool -> Parser Bool
switch
        (Mod FlagFields Bool -> Parser Bool)
-> Mod FlagFields Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
% FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long (FilePath
serviceName FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
"-use-tls")
        Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall α. Monoid α => α -> α -> α
 FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help (FilePath
"Connect to " FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
serviceName FilePath -> ShowS
forall α. Monoid α => α -> α -> α
 FilePath
" via TLS")
  where
    bs  Iso' B8.ByteString String
    bs :: p FilePath (f FilePath) -> p ByteString (f ByteString)
bs = (ByteString -> FilePath)
-> (FilePath -> ByteString) -> Iso' ByteString FilePath
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ByteString -> FilePath
B8.unpack FilePath -> ByteString
B8.pack

httpService2clientConfiguration  HttpServiceConfiguration  HttpClientConfiguration
httpService2clientConfiguration :: HttpServiceConfiguration -> HttpClientConfiguration
httpService2clientConfiguration HttpServiceConfiguration{Int
Maybe HttpServiceTLSConfiguration
ByteString
_hscUseTLS :: Maybe HttpServiceTLSConfiguration
_hscInterface :: ByteString
_hscPort :: Int
_hscHost :: ByteString
_hscUseTLS :: HttpServiceConfiguration -> Maybe HttpServiceTLSConfiguration
_hscInterface :: HttpServiceConfiguration -> ByteString
_hscPort :: HttpServiceConfiguration -> Int
_hscHost :: HttpServiceConfiguration -> ByteString
..} = HttpClientConfiguration :: ByteString -> Int -> Bool -> HttpClientConfiguration
HttpClientConfiguration
    { _hccHost :: ByteString
_hccHost = ByteString
_hscHost
    , _hccPort :: Int
_hccPort = Int
_hscPort
    , _hccUseTLS :: Bool
_hccUseTLS = Maybe HttpServiceTLSConfiguration -> Bool
forall a. Maybe a -> Bool
isJust Maybe HttpServiceTLSConfiguration
_hscUseTLS
    }