{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.AppFlow.Types.CustomAuthConfig
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.AppFlow.Types.CustomAuthConfig where

import Amazonka.AppFlow.Types.AuthParameter
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | Configuration information required for custom authentication.
--
-- /See:/ 'newCustomAuthConfig' smart constructor.
data CustomAuthConfig = CustomAuthConfig'
  { -- | Information about authentication parameters required for authentication.
    CustomAuthConfig -> Maybe [AuthParameter]
authParameters :: Prelude.Maybe [AuthParameter],
    -- | The authentication type that the custom connector uses.
    CustomAuthConfig -> Maybe Text
customAuthenticationType :: Prelude.Maybe Prelude.Text
  }
  deriving (CustomAuthConfig -> CustomAuthConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomAuthConfig -> CustomAuthConfig -> Bool
$c/= :: CustomAuthConfig -> CustomAuthConfig -> Bool
== :: CustomAuthConfig -> CustomAuthConfig -> Bool
$c== :: CustomAuthConfig -> CustomAuthConfig -> Bool
Prelude.Eq, ReadPrec [CustomAuthConfig]
ReadPrec CustomAuthConfig
Int -> ReadS CustomAuthConfig
ReadS [CustomAuthConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CustomAuthConfig]
$creadListPrec :: ReadPrec [CustomAuthConfig]
readPrec :: ReadPrec CustomAuthConfig
$creadPrec :: ReadPrec CustomAuthConfig
readList :: ReadS [CustomAuthConfig]
$creadList :: ReadS [CustomAuthConfig]
readsPrec :: Int -> ReadS CustomAuthConfig
$creadsPrec :: Int -> ReadS CustomAuthConfig
Prelude.Read, Int -> CustomAuthConfig -> ShowS
[CustomAuthConfig] -> ShowS
CustomAuthConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CustomAuthConfig] -> ShowS
$cshowList :: [CustomAuthConfig] -> ShowS
show :: CustomAuthConfig -> String
$cshow :: CustomAuthConfig -> String
showsPrec :: Int -> CustomAuthConfig -> ShowS
$cshowsPrec :: Int -> CustomAuthConfig -> ShowS
Prelude.Show, forall x. Rep CustomAuthConfig x -> CustomAuthConfig
forall x. CustomAuthConfig -> Rep CustomAuthConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CustomAuthConfig x -> CustomAuthConfig
$cfrom :: forall x. CustomAuthConfig -> Rep CustomAuthConfig x
Prelude.Generic)

-- |
-- Create a value of 'CustomAuthConfig' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'authParameters', 'customAuthConfig_authParameters' - Information about authentication parameters required for authentication.
--
-- 'customAuthenticationType', 'customAuthConfig_customAuthenticationType' - The authentication type that the custom connector uses.
newCustomAuthConfig ::
  CustomAuthConfig
newCustomAuthConfig :: CustomAuthConfig
newCustomAuthConfig =
  CustomAuthConfig'
    { $sel:authParameters:CustomAuthConfig' :: Maybe [AuthParameter]
authParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:customAuthenticationType:CustomAuthConfig' :: Maybe Text
customAuthenticationType = forall a. Maybe a
Prelude.Nothing
    }

-- | Information about authentication parameters required for authentication.
customAuthConfig_authParameters :: Lens.Lens' CustomAuthConfig (Prelude.Maybe [AuthParameter])
customAuthConfig_authParameters :: Lens' CustomAuthConfig (Maybe [AuthParameter])
customAuthConfig_authParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CustomAuthConfig' {Maybe [AuthParameter]
authParameters :: Maybe [AuthParameter]
$sel:authParameters:CustomAuthConfig' :: CustomAuthConfig -> Maybe [AuthParameter]
authParameters} -> Maybe [AuthParameter]
authParameters) (\s :: CustomAuthConfig
s@CustomAuthConfig' {} Maybe [AuthParameter]
a -> CustomAuthConfig
s {$sel:authParameters:CustomAuthConfig' :: Maybe [AuthParameter]
authParameters = Maybe [AuthParameter]
a} :: CustomAuthConfig) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The authentication type that the custom connector uses.
customAuthConfig_customAuthenticationType :: Lens.Lens' CustomAuthConfig (Prelude.Maybe Prelude.Text)
customAuthConfig_customAuthenticationType :: Lens' CustomAuthConfig (Maybe Text)
customAuthConfig_customAuthenticationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CustomAuthConfig' {Maybe Text
customAuthenticationType :: Maybe Text
$sel:customAuthenticationType:CustomAuthConfig' :: CustomAuthConfig -> Maybe Text
customAuthenticationType} -> Maybe Text
customAuthenticationType) (\s :: CustomAuthConfig
s@CustomAuthConfig' {} Maybe Text
a -> CustomAuthConfig
s {$sel:customAuthenticationType:CustomAuthConfig' :: Maybe Text
customAuthenticationType = Maybe Text
a} :: CustomAuthConfig)

instance Data.FromJSON CustomAuthConfig where
  parseJSON :: Value -> Parser CustomAuthConfig
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CustomAuthConfig"
      ( \Object
x ->
          Maybe [AuthParameter] -> Maybe Text -> CustomAuthConfig
CustomAuthConfig'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"authParameters" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"customAuthenticationType")
      )

instance Prelude.Hashable CustomAuthConfig where
  hashWithSalt :: Int -> CustomAuthConfig -> Int
hashWithSalt Int
_salt CustomAuthConfig' {Maybe [AuthParameter]
Maybe Text
customAuthenticationType :: Maybe Text
authParameters :: Maybe [AuthParameter]
$sel:customAuthenticationType:CustomAuthConfig' :: CustomAuthConfig -> Maybe Text
$sel:authParameters:CustomAuthConfig' :: CustomAuthConfig -> Maybe [AuthParameter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AuthParameter]
authParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
customAuthenticationType

instance Prelude.NFData CustomAuthConfig where
  rnf :: CustomAuthConfig -> ()
rnf CustomAuthConfig' {Maybe [AuthParameter]
Maybe Text
customAuthenticationType :: Maybe Text
authParameters :: Maybe [AuthParameter]
$sel:customAuthenticationType:CustomAuthConfig' :: CustomAuthConfig -> Maybe Text
$sel:authParameters:CustomAuthConfig' :: CustomAuthConfig -> Maybe [AuthParameter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AuthParameter]
authParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
customAuthenticationType