{-# 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.Redshift.ModifyAuthenticationProfile
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies an authentication profile.
module Amazonka.Redshift.ModifyAuthenticationProfile
  ( -- * Creating a Request
    ModifyAuthenticationProfile (..),
    newModifyAuthenticationProfile,

    -- * Request Lenses
    modifyAuthenticationProfile_authenticationProfileName,
    modifyAuthenticationProfile_authenticationProfileContent,

    -- * Destructuring the Response
    ModifyAuthenticationProfileResponse (..),
    newModifyAuthenticationProfileResponse,

    -- * Response Lenses
    modifyAuthenticationProfileResponse_authenticationProfileContent,
    modifyAuthenticationProfileResponse_authenticationProfileName,
    modifyAuthenticationProfileResponse_httpStatus,
  )
where

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

-- | /See:/ 'newModifyAuthenticationProfile' smart constructor.
data ModifyAuthenticationProfile = ModifyAuthenticationProfile'
  { -- | The name of the authentication profile to replace.
    ModifyAuthenticationProfile -> Text
authenticationProfileName :: Prelude.Text,
    -- | The new content of the authentication profile in JSON format. The
    -- maximum length of the JSON string is determined by a quota for your
    -- account.
    ModifyAuthenticationProfile -> Text
authenticationProfileContent :: Prelude.Text
  }
  deriving (ModifyAuthenticationProfile -> ModifyAuthenticationProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyAuthenticationProfile -> ModifyAuthenticationProfile -> Bool
$c/= :: ModifyAuthenticationProfile -> ModifyAuthenticationProfile -> Bool
== :: ModifyAuthenticationProfile -> ModifyAuthenticationProfile -> Bool
$c== :: ModifyAuthenticationProfile -> ModifyAuthenticationProfile -> Bool
Prelude.Eq, ReadPrec [ModifyAuthenticationProfile]
ReadPrec ModifyAuthenticationProfile
Int -> ReadS ModifyAuthenticationProfile
ReadS [ModifyAuthenticationProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyAuthenticationProfile]
$creadListPrec :: ReadPrec [ModifyAuthenticationProfile]
readPrec :: ReadPrec ModifyAuthenticationProfile
$creadPrec :: ReadPrec ModifyAuthenticationProfile
readList :: ReadS [ModifyAuthenticationProfile]
$creadList :: ReadS [ModifyAuthenticationProfile]
readsPrec :: Int -> ReadS ModifyAuthenticationProfile
$creadsPrec :: Int -> ReadS ModifyAuthenticationProfile
Prelude.Read, Int -> ModifyAuthenticationProfile -> ShowS
[ModifyAuthenticationProfile] -> ShowS
ModifyAuthenticationProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyAuthenticationProfile] -> ShowS
$cshowList :: [ModifyAuthenticationProfile] -> ShowS
show :: ModifyAuthenticationProfile -> String
$cshow :: ModifyAuthenticationProfile -> String
showsPrec :: Int -> ModifyAuthenticationProfile -> ShowS
$cshowsPrec :: Int -> ModifyAuthenticationProfile -> ShowS
Prelude.Show, forall x.
Rep ModifyAuthenticationProfile x -> ModifyAuthenticationProfile
forall x.
ModifyAuthenticationProfile -> Rep ModifyAuthenticationProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyAuthenticationProfile x -> ModifyAuthenticationProfile
$cfrom :: forall x.
ModifyAuthenticationProfile -> Rep ModifyAuthenticationProfile x
Prelude.Generic)

-- |
-- Create a value of 'ModifyAuthenticationProfile' 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:
--
-- 'authenticationProfileName', 'modifyAuthenticationProfile_authenticationProfileName' - The name of the authentication profile to replace.
--
-- 'authenticationProfileContent', 'modifyAuthenticationProfile_authenticationProfileContent' - The new content of the authentication profile in JSON format. The
-- maximum length of the JSON string is determined by a quota for your
-- account.
newModifyAuthenticationProfile ::
  -- | 'authenticationProfileName'
  Prelude.Text ->
  -- | 'authenticationProfileContent'
  Prelude.Text ->
  ModifyAuthenticationProfile
newModifyAuthenticationProfile :: Text -> Text -> ModifyAuthenticationProfile
newModifyAuthenticationProfile
  Text
pAuthenticationProfileName_
  Text
pAuthenticationProfileContent_ =
    ModifyAuthenticationProfile'
      { $sel:authenticationProfileName:ModifyAuthenticationProfile' :: Text
authenticationProfileName =
          Text
pAuthenticationProfileName_,
        $sel:authenticationProfileContent:ModifyAuthenticationProfile' :: Text
authenticationProfileContent =
          Text
pAuthenticationProfileContent_
      }

-- | The name of the authentication profile to replace.
modifyAuthenticationProfile_authenticationProfileName :: Lens.Lens' ModifyAuthenticationProfile Prelude.Text
modifyAuthenticationProfile_authenticationProfileName :: Lens' ModifyAuthenticationProfile Text
modifyAuthenticationProfile_authenticationProfileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyAuthenticationProfile' {Text
authenticationProfileName :: Text
$sel:authenticationProfileName:ModifyAuthenticationProfile' :: ModifyAuthenticationProfile -> Text
authenticationProfileName} -> Text
authenticationProfileName) (\s :: ModifyAuthenticationProfile
s@ModifyAuthenticationProfile' {} Text
a -> ModifyAuthenticationProfile
s {$sel:authenticationProfileName:ModifyAuthenticationProfile' :: Text
authenticationProfileName = Text
a} :: ModifyAuthenticationProfile)

-- | The new content of the authentication profile in JSON format. The
-- maximum length of the JSON string is determined by a quota for your
-- account.
modifyAuthenticationProfile_authenticationProfileContent :: Lens.Lens' ModifyAuthenticationProfile Prelude.Text
modifyAuthenticationProfile_authenticationProfileContent :: Lens' ModifyAuthenticationProfile Text
modifyAuthenticationProfile_authenticationProfileContent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyAuthenticationProfile' {Text
authenticationProfileContent :: Text
$sel:authenticationProfileContent:ModifyAuthenticationProfile' :: ModifyAuthenticationProfile -> Text
authenticationProfileContent} -> Text
authenticationProfileContent) (\s :: ModifyAuthenticationProfile
s@ModifyAuthenticationProfile' {} Text
a -> ModifyAuthenticationProfile
s {$sel:authenticationProfileContent:ModifyAuthenticationProfile' :: Text
authenticationProfileContent = Text
a} :: ModifyAuthenticationProfile)

instance Core.AWSRequest ModifyAuthenticationProfile where
  type
    AWSResponse ModifyAuthenticationProfile =
      ModifyAuthenticationProfileResponse
  request :: (Service -> Service)
-> ModifyAuthenticationProfile
-> Request ModifyAuthenticationProfile
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ModifyAuthenticationProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ModifyAuthenticationProfile)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"ModifyAuthenticationProfileResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe Text -> Int -> ModifyAuthenticationProfileResponse
ModifyAuthenticationProfileResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AuthenticationProfileContent")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AuthenticationProfileName")
            forall (f :: * -> *) a b. Applicative f => 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))
      )

instance Prelude.Hashable ModifyAuthenticationProfile where
  hashWithSalt :: Int -> ModifyAuthenticationProfile -> Int
hashWithSalt Int
_salt ModifyAuthenticationProfile' {Text
authenticationProfileContent :: Text
authenticationProfileName :: Text
$sel:authenticationProfileContent:ModifyAuthenticationProfile' :: ModifyAuthenticationProfile -> Text
$sel:authenticationProfileName:ModifyAuthenticationProfile' :: ModifyAuthenticationProfile -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
authenticationProfileName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
authenticationProfileContent

instance Prelude.NFData ModifyAuthenticationProfile where
  rnf :: ModifyAuthenticationProfile -> ()
rnf ModifyAuthenticationProfile' {Text
authenticationProfileContent :: Text
authenticationProfileName :: Text
$sel:authenticationProfileContent:ModifyAuthenticationProfile' :: ModifyAuthenticationProfile -> Text
$sel:authenticationProfileName:ModifyAuthenticationProfile' :: ModifyAuthenticationProfile -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
authenticationProfileName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
authenticationProfileContent

instance Data.ToHeaders ModifyAuthenticationProfile where
  toHeaders :: ModifyAuthenticationProfile -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ModifyAuthenticationProfile where
  toQuery :: ModifyAuthenticationProfile -> QueryString
toQuery ModifyAuthenticationProfile' {Text
authenticationProfileContent :: Text
authenticationProfileName :: Text
$sel:authenticationProfileContent:ModifyAuthenticationProfile' :: ModifyAuthenticationProfile -> Text
$sel:authenticationProfileName:ModifyAuthenticationProfile' :: ModifyAuthenticationProfile -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"ModifyAuthenticationProfile" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"AuthenticationProfileName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
authenticationProfileName,
        ByteString
"AuthenticationProfileContent"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
authenticationProfileContent
      ]

-- | /See:/ 'newModifyAuthenticationProfileResponse' smart constructor.
data ModifyAuthenticationProfileResponse = ModifyAuthenticationProfileResponse'
  { -- | The updated content of the authentication profile in JSON format.
    ModifyAuthenticationProfileResponse -> Maybe Text
authenticationProfileContent :: Prelude.Maybe Prelude.Text,
    -- | The name of the authentication profile that was replaced.
    ModifyAuthenticationProfileResponse -> Maybe Text
authenticationProfileName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ModifyAuthenticationProfileResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ModifyAuthenticationProfileResponse
-> ModifyAuthenticationProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyAuthenticationProfileResponse
-> ModifyAuthenticationProfileResponse -> Bool
$c/= :: ModifyAuthenticationProfileResponse
-> ModifyAuthenticationProfileResponse -> Bool
== :: ModifyAuthenticationProfileResponse
-> ModifyAuthenticationProfileResponse -> Bool
$c== :: ModifyAuthenticationProfileResponse
-> ModifyAuthenticationProfileResponse -> Bool
Prelude.Eq, ReadPrec [ModifyAuthenticationProfileResponse]
ReadPrec ModifyAuthenticationProfileResponse
Int -> ReadS ModifyAuthenticationProfileResponse
ReadS [ModifyAuthenticationProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyAuthenticationProfileResponse]
$creadListPrec :: ReadPrec [ModifyAuthenticationProfileResponse]
readPrec :: ReadPrec ModifyAuthenticationProfileResponse
$creadPrec :: ReadPrec ModifyAuthenticationProfileResponse
readList :: ReadS [ModifyAuthenticationProfileResponse]
$creadList :: ReadS [ModifyAuthenticationProfileResponse]
readsPrec :: Int -> ReadS ModifyAuthenticationProfileResponse
$creadsPrec :: Int -> ReadS ModifyAuthenticationProfileResponse
Prelude.Read, Int -> ModifyAuthenticationProfileResponse -> ShowS
[ModifyAuthenticationProfileResponse] -> ShowS
ModifyAuthenticationProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyAuthenticationProfileResponse] -> ShowS
$cshowList :: [ModifyAuthenticationProfileResponse] -> ShowS
show :: ModifyAuthenticationProfileResponse -> String
$cshow :: ModifyAuthenticationProfileResponse -> String
showsPrec :: Int -> ModifyAuthenticationProfileResponse -> ShowS
$cshowsPrec :: Int -> ModifyAuthenticationProfileResponse -> ShowS
Prelude.Show, forall x.
Rep ModifyAuthenticationProfileResponse x
-> ModifyAuthenticationProfileResponse
forall x.
ModifyAuthenticationProfileResponse
-> Rep ModifyAuthenticationProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyAuthenticationProfileResponse x
-> ModifyAuthenticationProfileResponse
$cfrom :: forall x.
ModifyAuthenticationProfileResponse
-> Rep ModifyAuthenticationProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'ModifyAuthenticationProfileResponse' 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:
--
-- 'authenticationProfileContent', 'modifyAuthenticationProfileResponse_authenticationProfileContent' - The updated content of the authentication profile in JSON format.
--
-- 'authenticationProfileName', 'modifyAuthenticationProfileResponse_authenticationProfileName' - The name of the authentication profile that was replaced.
--
-- 'httpStatus', 'modifyAuthenticationProfileResponse_httpStatus' - The response's http status code.
newModifyAuthenticationProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ModifyAuthenticationProfileResponse
newModifyAuthenticationProfileResponse :: Int -> ModifyAuthenticationProfileResponse
newModifyAuthenticationProfileResponse Int
pHttpStatus_ =
  ModifyAuthenticationProfileResponse'
    { $sel:authenticationProfileContent:ModifyAuthenticationProfileResponse' :: Maybe Text
authenticationProfileContent =
        forall a. Maybe a
Prelude.Nothing,
      $sel:authenticationProfileName:ModifyAuthenticationProfileResponse' :: Maybe Text
authenticationProfileName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ModifyAuthenticationProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The updated content of the authentication profile in JSON format.
modifyAuthenticationProfileResponse_authenticationProfileContent :: Lens.Lens' ModifyAuthenticationProfileResponse (Prelude.Maybe Prelude.Text)
modifyAuthenticationProfileResponse_authenticationProfileContent :: Lens' ModifyAuthenticationProfileResponse (Maybe Text)
modifyAuthenticationProfileResponse_authenticationProfileContent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyAuthenticationProfileResponse' {Maybe Text
authenticationProfileContent :: Maybe Text
$sel:authenticationProfileContent:ModifyAuthenticationProfileResponse' :: ModifyAuthenticationProfileResponse -> Maybe Text
authenticationProfileContent} -> Maybe Text
authenticationProfileContent) (\s :: ModifyAuthenticationProfileResponse
s@ModifyAuthenticationProfileResponse' {} Maybe Text
a -> ModifyAuthenticationProfileResponse
s {$sel:authenticationProfileContent:ModifyAuthenticationProfileResponse' :: Maybe Text
authenticationProfileContent = Maybe Text
a} :: ModifyAuthenticationProfileResponse)

-- | The name of the authentication profile that was replaced.
modifyAuthenticationProfileResponse_authenticationProfileName :: Lens.Lens' ModifyAuthenticationProfileResponse (Prelude.Maybe Prelude.Text)
modifyAuthenticationProfileResponse_authenticationProfileName :: Lens' ModifyAuthenticationProfileResponse (Maybe Text)
modifyAuthenticationProfileResponse_authenticationProfileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyAuthenticationProfileResponse' {Maybe Text
authenticationProfileName :: Maybe Text
$sel:authenticationProfileName:ModifyAuthenticationProfileResponse' :: ModifyAuthenticationProfileResponse -> Maybe Text
authenticationProfileName} -> Maybe Text
authenticationProfileName) (\s :: ModifyAuthenticationProfileResponse
s@ModifyAuthenticationProfileResponse' {} Maybe Text
a -> ModifyAuthenticationProfileResponse
s {$sel:authenticationProfileName:ModifyAuthenticationProfileResponse' :: Maybe Text
authenticationProfileName = Maybe Text
a} :: ModifyAuthenticationProfileResponse)

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

instance
  Prelude.NFData
    ModifyAuthenticationProfileResponse
  where
  rnf :: ModifyAuthenticationProfileResponse -> ()
rnf ModifyAuthenticationProfileResponse' {Int
Maybe Text
httpStatus :: Int
authenticationProfileName :: Maybe Text
authenticationProfileContent :: Maybe Text
$sel:httpStatus:ModifyAuthenticationProfileResponse' :: ModifyAuthenticationProfileResponse -> Int
$sel:authenticationProfileName:ModifyAuthenticationProfileResponse' :: ModifyAuthenticationProfileResponse -> Maybe Text
$sel:authenticationProfileContent:ModifyAuthenticationProfileResponse' :: ModifyAuthenticationProfileResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authenticationProfileContent
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authenticationProfileName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus