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

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

-- |
-- Module      : Amazonka.CognitoIdentityProvider.DescribeRiskConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the risk configuration.
module Amazonka.CognitoIdentityProvider.DescribeRiskConfiguration
  ( -- * Creating a Request
    DescribeRiskConfiguration (..),
    newDescribeRiskConfiguration,

    -- * Request Lenses
    describeRiskConfiguration_clientId,
    describeRiskConfiguration_userPoolId,

    -- * Destructuring the Response
    DescribeRiskConfigurationResponse (..),
    newDescribeRiskConfigurationResponse,

    -- * Response Lenses
    describeRiskConfigurationResponse_httpStatus,
    describeRiskConfigurationResponse_riskConfiguration,
  )
where

import Amazonka.CognitoIdentityProvider.Types
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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeRiskConfiguration' smart constructor.
data DescribeRiskConfiguration = DescribeRiskConfiguration'
  { -- | The app client ID.
    DescribeRiskConfiguration -> Maybe (Sensitive Text)
clientId :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The user pool ID.
    DescribeRiskConfiguration -> Text
userPoolId :: Prelude.Text
  }
  deriving (DescribeRiskConfiguration -> DescribeRiskConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeRiskConfiguration -> DescribeRiskConfiguration -> Bool
$c/= :: DescribeRiskConfiguration -> DescribeRiskConfiguration -> Bool
== :: DescribeRiskConfiguration -> DescribeRiskConfiguration -> Bool
$c== :: DescribeRiskConfiguration -> DescribeRiskConfiguration -> Bool
Prelude.Eq, Int -> DescribeRiskConfiguration -> ShowS
[DescribeRiskConfiguration] -> ShowS
DescribeRiskConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeRiskConfiguration] -> ShowS
$cshowList :: [DescribeRiskConfiguration] -> ShowS
show :: DescribeRiskConfiguration -> String
$cshow :: DescribeRiskConfiguration -> String
showsPrec :: Int -> DescribeRiskConfiguration -> ShowS
$cshowsPrec :: Int -> DescribeRiskConfiguration -> ShowS
Prelude.Show, forall x.
Rep DescribeRiskConfiguration x -> DescribeRiskConfiguration
forall x.
DescribeRiskConfiguration -> Rep DescribeRiskConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeRiskConfiguration x -> DescribeRiskConfiguration
$cfrom :: forall x.
DescribeRiskConfiguration -> Rep DescribeRiskConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'DescribeRiskConfiguration' 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:
--
-- 'clientId', 'describeRiskConfiguration_clientId' - The app client ID.
--
-- 'userPoolId', 'describeRiskConfiguration_userPoolId' - The user pool ID.
newDescribeRiskConfiguration ::
  -- | 'userPoolId'
  Prelude.Text ->
  DescribeRiskConfiguration
newDescribeRiskConfiguration :: Text -> DescribeRiskConfiguration
newDescribeRiskConfiguration Text
pUserPoolId_ =
  DescribeRiskConfiguration'
    { $sel:clientId:DescribeRiskConfiguration' :: Maybe (Sensitive Text)
clientId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:userPoolId:DescribeRiskConfiguration' :: Text
userPoolId = Text
pUserPoolId_
    }

-- | The app client ID.
describeRiskConfiguration_clientId :: Lens.Lens' DescribeRiskConfiguration (Prelude.Maybe Prelude.Text)
describeRiskConfiguration_clientId :: Lens' DescribeRiskConfiguration (Maybe Text)
describeRiskConfiguration_clientId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRiskConfiguration' {Maybe (Sensitive Text)
clientId :: Maybe (Sensitive Text)
$sel:clientId:DescribeRiskConfiguration' :: DescribeRiskConfiguration -> Maybe (Sensitive Text)
clientId} -> Maybe (Sensitive Text)
clientId) (\s :: DescribeRiskConfiguration
s@DescribeRiskConfiguration' {} Maybe (Sensitive Text)
a -> DescribeRiskConfiguration
s {$sel:clientId:DescribeRiskConfiguration' :: Maybe (Sensitive Text)
clientId = Maybe (Sensitive Text)
a} :: DescribeRiskConfiguration) 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The user pool ID.
describeRiskConfiguration_userPoolId :: Lens.Lens' DescribeRiskConfiguration Prelude.Text
describeRiskConfiguration_userPoolId :: Lens' DescribeRiskConfiguration Text
describeRiskConfiguration_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRiskConfiguration' {Text
userPoolId :: Text
$sel:userPoolId:DescribeRiskConfiguration' :: DescribeRiskConfiguration -> Text
userPoolId} -> Text
userPoolId) (\s :: DescribeRiskConfiguration
s@DescribeRiskConfiguration' {} Text
a -> DescribeRiskConfiguration
s {$sel:userPoolId:DescribeRiskConfiguration' :: Text
userPoolId = Text
a} :: DescribeRiskConfiguration)

instance Core.AWSRequest DescribeRiskConfiguration where
  type
    AWSResponse DescribeRiskConfiguration =
      DescribeRiskConfigurationResponse
  request :: (Service -> Service)
-> DescribeRiskConfiguration -> Request DescribeRiskConfiguration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeRiskConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeRiskConfiguration)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Int -> RiskConfigurationType -> DescribeRiskConfigurationResponse
DescribeRiskConfigurationResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"RiskConfiguration")
      )

instance Prelude.Hashable DescribeRiskConfiguration where
  hashWithSalt :: Int -> DescribeRiskConfiguration -> Int
hashWithSalt Int
_salt DescribeRiskConfiguration' {Maybe (Sensitive Text)
Text
userPoolId :: Text
clientId :: Maybe (Sensitive Text)
$sel:userPoolId:DescribeRiskConfiguration' :: DescribeRiskConfiguration -> Text
$sel:clientId:DescribeRiskConfiguration' :: DescribeRiskConfiguration -> Maybe (Sensitive Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
clientId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId

instance Prelude.NFData DescribeRiskConfiguration where
  rnf :: DescribeRiskConfiguration -> ()
rnf DescribeRiskConfiguration' {Maybe (Sensitive Text)
Text
userPoolId :: Text
clientId :: Maybe (Sensitive Text)
$sel:userPoolId:DescribeRiskConfiguration' :: DescribeRiskConfiguration -> Text
$sel:clientId:DescribeRiskConfiguration' :: DescribeRiskConfiguration -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
clientId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId

instance Data.ToHeaders DescribeRiskConfiguration where
  toHeaders :: DescribeRiskConfiguration -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSCognitoIdentityProviderService.DescribeRiskConfiguration" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeRiskConfiguration where
  toJSON :: DescribeRiskConfiguration -> Value
toJSON DescribeRiskConfiguration' {Maybe (Sensitive Text)
Text
userPoolId :: Text
clientId :: Maybe (Sensitive Text)
$sel:userPoolId:DescribeRiskConfiguration' :: DescribeRiskConfiguration -> Text
$sel:clientId:DescribeRiskConfiguration' :: DescribeRiskConfiguration -> Maybe (Sensitive Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive Text)
clientId,
            forall a. a -> Maybe a
Prelude.Just (Key
"UserPoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userPoolId)
          ]
      )

instance Data.ToPath DescribeRiskConfiguration where
  toPath :: DescribeRiskConfiguration -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DescribeRiskConfiguration where
  toQuery :: DescribeRiskConfiguration -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDescribeRiskConfigurationResponse' smart constructor.
data DescribeRiskConfigurationResponse = DescribeRiskConfigurationResponse'
  { -- | The response's http status code.
    DescribeRiskConfigurationResponse -> Int
httpStatus :: Prelude.Int,
    -- | The risk configuration.
    DescribeRiskConfigurationResponse -> RiskConfigurationType
riskConfiguration :: RiskConfigurationType
  }
  deriving (DescribeRiskConfigurationResponse
-> DescribeRiskConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeRiskConfigurationResponse
-> DescribeRiskConfigurationResponse -> Bool
$c/= :: DescribeRiskConfigurationResponse
-> DescribeRiskConfigurationResponse -> Bool
== :: DescribeRiskConfigurationResponse
-> DescribeRiskConfigurationResponse -> Bool
$c== :: DescribeRiskConfigurationResponse
-> DescribeRiskConfigurationResponse -> Bool
Prelude.Eq, Int -> DescribeRiskConfigurationResponse -> ShowS
[DescribeRiskConfigurationResponse] -> ShowS
DescribeRiskConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeRiskConfigurationResponse] -> ShowS
$cshowList :: [DescribeRiskConfigurationResponse] -> ShowS
show :: DescribeRiskConfigurationResponse -> String
$cshow :: DescribeRiskConfigurationResponse -> String
showsPrec :: Int -> DescribeRiskConfigurationResponse -> ShowS
$cshowsPrec :: Int -> DescribeRiskConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeRiskConfigurationResponse x
-> DescribeRiskConfigurationResponse
forall x.
DescribeRiskConfigurationResponse
-> Rep DescribeRiskConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeRiskConfigurationResponse x
-> DescribeRiskConfigurationResponse
$cfrom :: forall x.
DescribeRiskConfigurationResponse
-> Rep DescribeRiskConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeRiskConfigurationResponse' 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:
--
-- 'httpStatus', 'describeRiskConfigurationResponse_httpStatus' - The response's http status code.
--
-- 'riskConfiguration', 'describeRiskConfigurationResponse_riskConfiguration' - The risk configuration.
newDescribeRiskConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'riskConfiguration'
  RiskConfigurationType ->
  DescribeRiskConfigurationResponse
newDescribeRiskConfigurationResponse :: Int -> RiskConfigurationType -> DescribeRiskConfigurationResponse
newDescribeRiskConfigurationResponse
  Int
pHttpStatus_
  RiskConfigurationType
pRiskConfiguration_ =
    DescribeRiskConfigurationResponse'
      { $sel:httpStatus:DescribeRiskConfigurationResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:riskConfiguration:DescribeRiskConfigurationResponse' :: RiskConfigurationType
riskConfiguration = RiskConfigurationType
pRiskConfiguration_
      }

-- | The response's http status code.
describeRiskConfigurationResponse_httpStatus :: Lens.Lens' DescribeRiskConfigurationResponse Prelude.Int
describeRiskConfigurationResponse_httpStatus :: Lens' DescribeRiskConfigurationResponse Int
describeRiskConfigurationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRiskConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeRiskConfigurationResponse' :: DescribeRiskConfigurationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeRiskConfigurationResponse
s@DescribeRiskConfigurationResponse' {} Int
a -> DescribeRiskConfigurationResponse
s {$sel:httpStatus:DescribeRiskConfigurationResponse' :: Int
httpStatus = Int
a} :: DescribeRiskConfigurationResponse)

-- | The risk configuration.
describeRiskConfigurationResponse_riskConfiguration :: Lens.Lens' DescribeRiskConfigurationResponse RiskConfigurationType
describeRiskConfigurationResponse_riskConfiguration :: Lens' DescribeRiskConfigurationResponse RiskConfigurationType
describeRiskConfigurationResponse_riskConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRiskConfigurationResponse' {RiskConfigurationType
riskConfiguration :: RiskConfigurationType
$sel:riskConfiguration:DescribeRiskConfigurationResponse' :: DescribeRiskConfigurationResponse -> RiskConfigurationType
riskConfiguration} -> RiskConfigurationType
riskConfiguration) (\s :: DescribeRiskConfigurationResponse
s@DescribeRiskConfigurationResponse' {} RiskConfigurationType
a -> DescribeRiskConfigurationResponse
s {$sel:riskConfiguration:DescribeRiskConfigurationResponse' :: RiskConfigurationType
riskConfiguration = RiskConfigurationType
a} :: DescribeRiskConfigurationResponse)

instance
  Prelude.NFData
    DescribeRiskConfigurationResponse
  where
  rnf :: DescribeRiskConfigurationResponse -> ()
rnf DescribeRiskConfigurationResponse' {Int
RiskConfigurationType
riskConfiguration :: RiskConfigurationType
httpStatus :: Int
$sel:riskConfiguration:DescribeRiskConfigurationResponse' :: DescribeRiskConfigurationResponse -> RiskConfigurationType
$sel:httpStatus:DescribeRiskConfigurationResponse' :: DescribeRiskConfigurationResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RiskConfigurationType
riskConfiguration