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

    -- * Request Lenses
    createAuthenticationProfile_authenticationProfileName,
    createAuthenticationProfile_authenticationProfileContent,

    -- * Destructuring the Response
    CreateAuthenticationProfileResponse (..),
    newCreateAuthenticationProfileResponse,

    -- * Response Lenses
    createAuthenticationProfileResponse_authenticationProfileContent,
    createAuthenticationProfileResponse_authenticationProfileName,
    createAuthenticationProfileResponse_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:/ 'newCreateAuthenticationProfile' smart constructor.
data CreateAuthenticationProfile = CreateAuthenticationProfile'
  { -- | The name of the authentication profile to be created.
    CreateAuthenticationProfile -> Text
authenticationProfileName :: Prelude.Text,
    -- | The content of the authentication profile in JSON format. The maximum
    -- length of the JSON string is determined by a quota for your account.
    CreateAuthenticationProfile -> Text
authenticationProfileContent :: Prelude.Text
  }
  deriving (CreateAuthenticationProfile -> CreateAuthenticationProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateAuthenticationProfile -> CreateAuthenticationProfile -> Bool
$c/= :: CreateAuthenticationProfile -> CreateAuthenticationProfile -> Bool
== :: CreateAuthenticationProfile -> CreateAuthenticationProfile -> Bool
$c== :: CreateAuthenticationProfile -> CreateAuthenticationProfile -> Bool
Prelude.Eq, ReadPrec [CreateAuthenticationProfile]
ReadPrec CreateAuthenticationProfile
Int -> ReadS CreateAuthenticationProfile
ReadS [CreateAuthenticationProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateAuthenticationProfile]
$creadListPrec :: ReadPrec [CreateAuthenticationProfile]
readPrec :: ReadPrec CreateAuthenticationProfile
$creadPrec :: ReadPrec CreateAuthenticationProfile
readList :: ReadS [CreateAuthenticationProfile]
$creadList :: ReadS [CreateAuthenticationProfile]
readsPrec :: Int -> ReadS CreateAuthenticationProfile
$creadsPrec :: Int -> ReadS CreateAuthenticationProfile
Prelude.Read, Int -> CreateAuthenticationProfile -> ShowS
[CreateAuthenticationProfile] -> ShowS
CreateAuthenticationProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateAuthenticationProfile] -> ShowS
$cshowList :: [CreateAuthenticationProfile] -> ShowS
show :: CreateAuthenticationProfile -> String
$cshow :: CreateAuthenticationProfile -> String
showsPrec :: Int -> CreateAuthenticationProfile -> ShowS
$cshowsPrec :: Int -> CreateAuthenticationProfile -> ShowS
Prelude.Show, forall x.
Rep CreateAuthenticationProfile x -> CreateAuthenticationProfile
forall x.
CreateAuthenticationProfile -> Rep CreateAuthenticationProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateAuthenticationProfile x -> CreateAuthenticationProfile
$cfrom :: forall x.
CreateAuthenticationProfile -> Rep CreateAuthenticationProfile x
Prelude.Generic)

-- |
-- Create a value of 'CreateAuthenticationProfile' 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', 'createAuthenticationProfile_authenticationProfileName' - The name of the authentication profile to be created.
--
-- 'authenticationProfileContent', 'createAuthenticationProfile_authenticationProfileContent' - The content of the authentication profile in JSON format. The maximum
-- length of the JSON string is determined by a quota for your account.
newCreateAuthenticationProfile ::
  -- | 'authenticationProfileName'
  Prelude.Text ->
  -- | 'authenticationProfileContent'
  Prelude.Text ->
  CreateAuthenticationProfile
newCreateAuthenticationProfile :: Text -> Text -> CreateAuthenticationProfile
newCreateAuthenticationProfile
  Text
pAuthenticationProfileName_
  Text
pAuthenticationProfileContent_ =
    CreateAuthenticationProfile'
      { $sel:authenticationProfileName:CreateAuthenticationProfile' :: Text
authenticationProfileName =
          Text
pAuthenticationProfileName_,
        $sel:authenticationProfileContent:CreateAuthenticationProfile' :: Text
authenticationProfileContent =
          Text
pAuthenticationProfileContent_
      }

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

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

instance Core.AWSRequest CreateAuthenticationProfile where
  type
    AWSResponse CreateAuthenticationProfile =
      CreateAuthenticationProfileResponse
  request :: (Service -> Service)
-> CreateAuthenticationProfile
-> Request CreateAuthenticationProfile
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 CreateAuthenticationProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateAuthenticationProfile)))
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
"CreateAuthenticationProfileResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe Text -> Int -> CreateAuthenticationProfileResponse
CreateAuthenticationProfileResponse'
            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 CreateAuthenticationProfile where
  hashWithSalt :: Int -> CreateAuthenticationProfile -> Int
hashWithSalt Int
_salt CreateAuthenticationProfile' {Text
authenticationProfileContent :: Text
authenticationProfileName :: Text
$sel:authenticationProfileContent:CreateAuthenticationProfile' :: CreateAuthenticationProfile -> Text
$sel:authenticationProfileName:CreateAuthenticationProfile' :: CreateAuthenticationProfile -> 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 CreateAuthenticationProfile where
  rnf :: CreateAuthenticationProfile -> ()
rnf CreateAuthenticationProfile' {Text
authenticationProfileContent :: Text
authenticationProfileName :: Text
$sel:authenticationProfileContent:CreateAuthenticationProfile' :: CreateAuthenticationProfile -> Text
$sel:authenticationProfileName:CreateAuthenticationProfile' :: CreateAuthenticationProfile -> 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 CreateAuthenticationProfile where
  toHeaders :: CreateAuthenticationProfile -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery CreateAuthenticationProfile where
  toQuery :: CreateAuthenticationProfile -> QueryString
toQuery CreateAuthenticationProfile' {Text
authenticationProfileContent :: Text
authenticationProfileName :: Text
$sel:authenticationProfileContent:CreateAuthenticationProfile' :: CreateAuthenticationProfile -> Text
$sel:authenticationProfileName:CreateAuthenticationProfile' :: CreateAuthenticationProfile -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"CreateAuthenticationProfile" ::
                      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:/ 'newCreateAuthenticationProfileResponse' smart constructor.
data CreateAuthenticationProfileResponse = CreateAuthenticationProfileResponse'
  { -- | The content of the authentication profile in JSON format.
    CreateAuthenticationProfileResponse -> Maybe Text
authenticationProfileContent :: Prelude.Maybe Prelude.Text,
    -- | The name of the authentication profile that was created.
    CreateAuthenticationProfileResponse -> Maybe Text
authenticationProfileName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateAuthenticationProfileResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateAuthenticationProfileResponse
-> CreateAuthenticationProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateAuthenticationProfileResponse
-> CreateAuthenticationProfileResponse -> Bool
$c/= :: CreateAuthenticationProfileResponse
-> CreateAuthenticationProfileResponse -> Bool
== :: CreateAuthenticationProfileResponse
-> CreateAuthenticationProfileResponse -> Bool
$c== :: CreateAuthenticationProfileResponse
-> CreateAuthenticationProfileResponse -> Bool
Prelude.Eq, ReadPrec [CreateAuthenticationProfileResponse]
ReadPrec CreateAuthenticationProfileResponse
Int -> ReadS CreateAuthenticationProfileResponse
ReadS [CreateAuthenticationProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateAuthenticationProfileResponse]
$creadListPrec :: ReadPrec [CreateAuthenticationProfileResponse]
readPrec :: ReadPrec CreateAuthenticationProfileResponse
$creadPrec :: ReadPrec CreateAuthenticationProfileResponse
readList :: ReadS [CreateAuthenticationProfileResponse]
$creadList :: ReadS [CreateAuthenticationProfileResponse]
readsPrec :: Int -> ReadS CreateAuthenticationProfileResponse
$creadsPrec :: Int -> ReadS CreateAuthenticationProfileResponse
Prelude.Read, Int -> CreateAuthenticationProfileResponse -> ShowS
[CreateAuthenticationProfileResponse] -> ShowS
CreateAuthenticationProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateAuthenticationProfileResponse] -> ShowS
$cshowList :: [CreateAuthenticationProfileResponse] -> ShowS
show :: CreateAuthenticationProfileResponse -> String
$cshow :: CreateAuthenticationProfileResponse -> String
showsPrec :: Int -> CreateAuthenticationProfileResponse -> ShowS
$cshowsPrec :: Int -> CreateAuthenticationProfileResponse -> ShowS
Prelude.Show, forall x.
Rep CreateAuthenticationProfileResponse x
-> CreateAuthenticationProfileResponse
forall x.
CreateAuthenticationProfileResponse
-> Rep CreateAuthenticationProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateAuthenticationProfileResponse x
-> CreateAuthenticationProfileResponse
$cfrom :: forall x.
CreateAuthenticationProfileResponse
-> Rep CreateAuthenticationProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateAuthenticationProfileResponse' 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', 'createAuthenticationProfileResponse_authenticationProfileContent' - The content of the authentication profile in JSON format.
--
-- 'authenticationProfileName', 'createAuthenticationProfileResponse_authenticationProfileName' - The name of the authentication profile that was created.
--
-- 'httpStatus', 'createAuthenticationProfileResponse_httpStatus' - The response's http status code.
newCreateAuthenticationProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateAuthenticationProfileResponse
newCreateAuthenticationProfileResponse :: Int -> CreateAuthenticationProfileResponse
newCreateAuthenticationProfileResponse Int
pHttpStatus_ =
  CreateAuthenticationProfileResponse'
    { $sel:authenticationProfileContent:CreateAuthenticationProfileResponse' :: Maybe Text
authenticationProfileContent =
        forall a. Maybe a
Prelude.Nothing,
      $sel:authenticationProfileName:CreateAuthenticationProfileResponse' :: Maybe Text
authenticationProfileName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateAuthenticationProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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

instance
  Prelude.NFData
    CreateAuthenticationProfileResponse
  where
  rnf :: CreateAuthenticationProfileResponse -> ()
rnf CreateAuthenticationProfileResponse' {Int
Maybe Text
httpStatus :: Int
authenticationProfileName :: Maybe Text
authenticationProfileContent :: Maybe Text
$sel:httpStatus:CreateAuthenticationProfileResponse' :: CreateAuthenticationProfileResponse -> Int
$sel:authenticationProfileName:CreateAuthenticationProfileResponse' :: CreateAuthenticationProfileResponse -> Maybe Text
$sel:authenticationProfileContent:CreateAuthenticationProfileResponse' :: CreateAuthenticationProfileResponse -> 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