{-# 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.SecretsManager.GetRandomPassword
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Generates a random password. We recommend that you specify the maximum
-- length and include every character type that the system you are
-- generating a password for can support.
--
-- Secrets Manager generates a CloudTrail log entry when you call this
-- action. Do not include sensitive information in request parameters
-- because it might be logged. For more information, see
-- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/retrieve-ct-entries.html Logging Secrets Manager events with CloudTrail>.
--
-- __Required permissions:__ @secretsmanager:GetRandomPassword@. For more
-- information, see
-- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/reference_iam-permissions.html#reference_iam-permissions_actions IAM policy actions for Secrets Manager>
-- and
-- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/auth-and-access.html Authentication and access control in Secrets Manager>.
module Amazonka.SecretsManager.GetRandomPassword
  ( -- * Creating a Request
    GetRandomPassword (..),
    newGetRandomPassword,

    -- * Request Lenses
    getRandomPassword_excludeCharacters,
    getRandomPassword_excludeLowercase,
    getRandomPassword_excludeNumbers,
    getRandomPassword_excludePunctuation,
    getRandomPassword_excludeUppercase,
    getRandomPassword_includeSpace,
    getRandomPassword_passwordLength,
    getRandomPassword_requireEachIncludedType,

    -- * Destructuring the Response
    GetRandomPasswordResponse (..),
    newGetRandomPasswordResponse,

    -- * Response Lenses
    getRandomPasswordResponse_randomPassword,
    getRandomPasswordResponse_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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SecretsManager.Types

-- | /See:/ 'newGetRandomPassword' smart constructor.
data GetRandomPassword = GetRandomPassword'
  { -- | A string of the characters that you don\'t want in the password.
    GetRandomPassword -> Maybe Text
excludeCharacters :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether to exclude lowercase letters from the password. If you
    -- don\'t include this switch, the password can contain lowercase letters.
    GetRandomPassword -> Maybe Bool
excludeLowercase :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether to exclude numbers from the password. If you don\'t
    -- include this switch, the password can contain numbers.
    GetRandomPassword -> Maybe Bool
excludeNumbers :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether to exclude the following punctuation characters from
    -- the password:
    -- @! \" # $ % & \' ( ) * + , - . \/ : ; \< = > ? \@ [ \\ ] ^ _ \` { | } ~@.
    -- If you don\'t include this switch, the password can contain punctuation.
    GetRandomPassword -> Maybe Bool
excludePunctuation :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether to exclude uppercase letters from the password. If you
    -- don\'t include this switch, the password can contain uppercase letters.
    GetRandomPassword -> Maybe Bool
excludeUppercase :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether to include the space character. If you include this
    -- switch, the password can contain space characters.
    GetRandomPassword -> Maybe Bool
includeSpace :: Prelude.Maybe Prelude.Bool,
    -- | The length of the password. If you don\'t include this parameter, the
    -- default length is 32 characters.
    GetRandomPassword -> Maybe Natural
passwordLength :: Prelude.Maybe Prelude.Natural,
    -- | Specifies whether to include at least one upper and lowercase letter,
    -- one number, and one punctuation. If you don\'t include this switch, the
    -- password contains at least one of every character type.
    GetRandomPassword -> Maybe Bool
requireEachIncludedType :: Prelude.Maybe Prelude.Bool
  }
  deriving (GetRandomPassword -> GetRandomPassword -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRandomPassword -> GetRandomPassword -> Bool
$c/= :: GetRandomPassword -> GetRandomPassword -> Bool
== :: GetRandomPassword -> GetRandomPassword -> Bool
$c== :: GetRandomPassword -> GetRandomPassword -> Bool
Prelude.Eq, ReadPrec [GetRandomPassword]
ReadPrec GetRandomPassword
Int -> ReadS GetRandomPassword
ReadS [GetRandomPassword]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRandomPassword]
$creadListPrec :: ReadPrec [GetRandomPassword]
readPrec :: ReadPrec GetRandomPassword
$creadPrec :: ReadPrec GetRandomPassword
readList :: ReadS [GetRandomPassword]
$creadList :: ReadS [GetRandomPassword]
readsPrec :: Int -> ReadS GetRandomPassword
$creadsPrec :: Int -> ReadS GetRandomPassword
Prelude.Read, Int -> GetRandomPassword -> ShowS
[GetRandomPassword] -> ShowS
GetRandomPassword -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRandomPassword] -> ShowS
$cshowList :: [GetRandomPassword] -> ShowS
show :: GetRandomPassword -> String
$cshow :: GetRandomPassword -> String
showsPrec :: Int -> GetRandomPassword -> ShowS
$cshowsPrec :: Int -> GetRandomPassword -> ShowS
Prelude.Show, forall x. Rep GetRandomPassword x -> GetRandomPassword
forall x. GetRandomPassword -> Rep GetRandomPassword x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRandomPassword x -> GetRandomPassword
$cfrom :: forall x. GetRandomPassword -> Rep GetRandomPassword x
Prelude.Generic)

-- |
-- Create a value of 'GetRandomPassword' 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:
--
-- 'excludeCharacters', 'getRandomPassword_excludeCharacters' - A string of the characters that you don\'t want in the password.
--
-- 'excludeLowercase', 'getRandomPassword_excludeLowercase' - Specifies whether to exclude lowercase letters from the password. If you
-- don\'t include this switch, the password can contain lowercase letters.
--
-- 'excludeNumbers', 'getRandomPassword_excludeNumbers' - Specifies whether to exclude numbers from the password. If you don\'t
-- include this switch, the password can contain numbers.
--
-- 'excludePunctuation', 'getRandomPassword_excludePunctuation' - Specifies whether to exclude the following punctuation characters from
-- the password:
-- @! \" # $ % & \' ( ) * + , - . \/ : ; \< = > ? \@ [ \\ ] ^ _ \` { | } ~@.
-- If you don\'t include this switch, the password can contain punctuation.
--
-- 'excludeUppercase', 'getRandomPassword_excludeUppercase' - Specifies whether to exclude uppercase letters from the password. If you
-- don\'t include this switch, the password can contain uppercase letters.
--
-- 'includeSpace', 'getRandomPassword_includeSpace' - Specifies whether to include the space character. If you include this
-- switch, the password can contain space characters.
--
-- 'passwordLength', 'getRandomPassword_passwordLength' - The length of the password. If you don\'t include this parameter, the
-- default length is 32 characters.
--
-- 'requireEachIncludedType', 'getRandomPassword_requireEachIncludedType' - Specifies whether to include at least one upper and lowercase letter,
-- one number, and one punctuation. If you don\'t include this switch, the
-- password contains at least one of every character type.
newGetRandomPassword ::
  GetRandomPassword
newGetRandomPassword :: GetRandomPassword
newGetRandomPassword =
  GetRandomPassword'
    { $sel:excludeCharacters:GetRandomPassword' :: Maybe Text
excludeCharacters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:excludeLowercase:GetRandomPassword' :: Maybe Bool
excludeLowercase = forall a. Maybe a
Prelude.Nothing,
      $sel:excludeNumbers:GetRandomPassword' :: Maybe Bool
excludeNumbers = forall a. Maybe a
Prelude.Nothing,
      $sel:excludePunctuation:GetRandomPassword' :: Maybe Bool
excludePunctuation = forall a. Maybe a
Prelude.Nothing,
      $sel:excludeUppercase:GetRandomPassword' :: Maybe Bool
excludeUppercase = forall a. Maybe a
Prelude.Nothing,
      $sel:includeSpace:GetRandomPassword' :: Maybe Bool
includeSpace = forall a. Maybe a
Prelude.Nothing,
      $sel:passwordLength:GetRandomPassword' :: Maybe Natural
passwordLength = forall a. Maybe a
Prelude.Nothing,
      $sel:requireEachIncludedType:GetRandomPassword' :: Maybe Bool
requireEachIncludedType = forall a. Maybe a
Prelude.Nothing
    }

-- | A string of the characters that you don\'t want in the password.
getRandomPassword_excludeCharacters :: Lens.Lens' GetRandomPassword (Prelude.Maybe Prelude.Text)
getRandomPassword_excludeCharacters :: Lens' GetRandomPassword (Maybe Text)
getRandomPassword_excludeCharacters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPassword' {Maybe Text
excludeCharacters :: Maybe Text
$sel:excludeCharacters:GetRandomPassword' :: GetRandomPassword -> Maybe Text
excludeCharacters} -> Maybe Text
excludeCharacters) (\s :: GetRandomPassword
s@GetRandomPassword' {} Maybe Text
a -> GetRandomPassword
s {$sel:excludeCharacters:GetRandomPassword' :: Maybe Text
excludeCharacters = Maybe Text
a} :: GetRandomPassword)

-- | Specifies whether to exclude lowercase letters from the password. If you
-- don\'t include this switch, the password can contain lowercase letters.
getRandomPassword_excludeLowercase :: Lens.Lens' GetRandomPassword (Prelude.Maybe Prelude.Bool)
getRandomPassword_excludeLowercase :: Lens' GetRandomPassword (Maybe Bool)
getRandomPassword_excludeLowercase = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPassword' {Maybe Bool
excludeLowercase :: Maybe Bool
$sel:excludeLowercase:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
excludeLowercase} -> Maybe Bool
excludeLowercase) (\s :: GetRandomPassword
s@GetRandomPassword' {} Maybe Bool
a -> GetRandomPassword
s {$sel:excludeLowercase:GetRandomPassword' :: Maybe Bool
excludeLowercase = Maybe Bool
a} :: GetRandomPassword)

-- | Specifies whether to exclude numbers from the password. If you don\'t
-- include this switch, the password can contain numbers.
getRandomPassword_excludeNumbers :: Lens.Lens' GetRandomPassword (Prelude.Maybe Prelude.Bool)
getRandomPassword_excludeNumbers :: Lens' GetRandomPassword (Maybe Bool)
getRandomPassword_excludeNumbers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPassword' {Maybe Bool
excludeNumbers :: Maybe Bool
$sel:excludeNumbers:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
excludeNumbers} -> Maybe Bool
excludeNumbers) (\s :: GetRandomPassword
s@GetRandomPassword' {} Maybe Bool
a -> GetRandomPassword
s {$sel:excludeNumbers:GetRandomPassword' :: Maybe Bool
excludeNumbers = Maybe Bool
a} :: GetRandomPassword)

-- | Specifies whether to exclude the following punctuation characters from
-- the password:
-- @! \" # $ % & \' ( ) * + , - . \/ : ; \< = > ? \@ [ \\ ] ^ _ \` { | } ~@.
-- If you don\'t include this switch, the password can contain punctuation.
getRandomPassword_excludePunctuation :: Lens.Lens' GetRandomPassword (Prelude.Maybe Prelude.Bool)
getRandomPassword_excludePunctuation :: Lens' GetRandomPassword (Maybe Bool)
getRandomPassword_excludePunctuation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPassword' {Maybe Bool
excludePunctuation :: Maybe Bool
$sel:excludePunctuation:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
excludePunctuation} -> Maybe Bool
excludePunctuation) (\s :: GetRandomPassword
s@GetRandomPassword' {} Maybe Bool
a -> GetRandomPassword
s {$sel:excludePunctuation:GetRandomPassword' :: Maybe Bool
excludePunctuation = Maybe Bool
a} :: GetRandomPassword)

-- | Specifies whether to exclude uppercase letters from the password. If you
-- don\'t include this switch, the password can contain uppercase letters.
getRandomPassword_excludeUppercase :: Lens.Lens' GetRandomPassword (Prelude.Maybe Prelude.Bool)
getRandomPassword_excludeUppercase :: Lens' GetRandomPassword (Maybe Bool)
getRandomPassword_excludeUppercase = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPassword' {Maybe Bool
excludeUppercase :: Maybe Bool
$sel:excludeUppercase:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
excludeUppercase} -> Maybe Bool
excludeUppercase) (\s :: GetRandomPassword
s@GetRandomPassword' {} Maybe Bool
a -> GetRandomPassword
s {$sel:excludeUppercase:GetRandomPassword' :: Maybe Bool
excludeUppercase = Maybe Bool
a} :: GetRandomPassword)

-- | Specifies whether to include the space character. If you include this
-- switch, the password can contain space characters.
getRandomPassword_includeSpace :: Lens.Lens' GetRandomPassword (Prelude.Maybe Prelude.Bool)
getRandomPassword_includeSpace :: Lens' GetRandomPassword (Maybe Bool)
getRandomPassword_includeSpace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPassword' {Maybe Bool
includeSpace :: Maybe Bool
$sel:includeSpace:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
includeSpace} -> Maybe Bool
includeSpace) (\s :: GetRandomPassword
s@GetRandomPassword' {} Maybe Bool
a -> GetRandomPassword
s {$sel:includeSpace:GetRandomPassword' :: Maybe Bool
includeSpace = Maybe Bool
a} :: GetRandomPassword)

-- | The length of the password. If you don\'t include this parameter, the
-- default length is 32 characters.
getRandomPassword_passwordLength :: Lens.Lens' GetRandomPassword (Prelude.Maybe Prelude.Natural)
getRandomPassword_passwordLength :: Lens' GetRandomPassword (Maybe Natural)
getRandomPassword_passwordLength = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPassword' {Maybe Natural
passwordLength :: Maybe Natural
$sel:passwordLength:GetRandomPassword' :: GetRandomPassword -> Maybe Natural
passwordLength} -> Maybe Natural
passwordLength) (\s :: GetRandomPassword
s@GetRandomPassword' {} Maybe Natural
a -> GetRandomPassword
s {$sel:passwordLength:GetRandomPassword' :: Maybe Natural
passwordLength = Maybe Natural
a} :: GetRandomPassword)

-- | Specifies whether to include at least one upper and lowercase letter,
-- one number, and one punctuation. If you don\'t include this switch, the
-- password contains at least one of every character type.
getRandomPassword_requireEachIncludedType :: Lens.Lens' GetRandomPassword (Prelude.Maybe Prelude.Bool)
getRandomPassword_requireEachIncludedType :: Lens' GetRandomPassword (Maybe Bool)
getRandomPassword_requireEachIncludedType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPassword' {Maybe Bool
requireEachIncludedType :: Maybe Bool
$sel:requireEachIncludedType:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
requireEachIncludedType} -> Maybe Bool
requireEachIncludedType) (\s :: GetRandomPassword
s@GetRandomPassword' {} Maybe Bool
a -> GetRandomPassword
s {$sel:requireEachIncludedType:GetRandomPassword' :: Maybe Bool
requireEachIncludedType = Maybe Bool
a} :: GetRandomPassword)

instance Core.AWSRequest GetRandomPassword where
  type
    AWSResponse GetRandomPassword =
      GetRandomPasswordResponse
  request :: (Service -> Service)
-> GetRandomPassword -> Request GetRandomPassword
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 GetRandomPassword
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetRandomPassword)))
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 ->
          Maybe (Sensitive Text) -> Int -> GetRandomPasswordResponse
GetRandomPasswordResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RandomPassword")
            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 GetRandomPassword where
  hashWithSalt :: Int -> GetRandomPassword -> Int
hashWithSalt Int
_salt GetRandomPassword' {Maybe Bool
Maybe Natural
Maybe Text
requireEachIncludedType :: Maybe Bool
passwordLength :: Maybe Natural
includeSpace :: Maybe Bool
excludeUppercase :: Maybe Bool
excludePunctuation :: Maybe Bool
excludeNumbers :: Maybe Bool
excludeLowercase :: Maybe Bool
excludeCharacters :: Maybe Text
$sel:requireEachIncludedType:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:passwordLength:GetRandomPassword' :: GetRandomPassword -> Maybe Natural
$sel:includeSpace:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeUppercase:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludePunctuation:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeNumbers:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeLowercase:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeCharacters:GetRandomPassword' :: GetRandomPassword -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
excludeCharacters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
excludeLowercase
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
excludeNumbers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
excludePunctuation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
excludeUppercase
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
includeSpace
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
passwordLength
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
requireEachIncludedType

instance Prelude.NFData GetRandomPassword where
  rnf :: GetRandomPassword -> ()
rnf GetRandomPassword' {Maybe Bool
Maybe Natural
Maybe Text
requireEachIncludedType :: Maybe Bool
passwordLength :: Maybe Natural
includeSpace :: Maybe Bool
excludeUppercase :: Maybe Bool
excludePunctuation :: Maybe Bool
excludeNumbers :: Maybe Bool
excludeLowercase :: Maybe Bool
excludeCharacters :: Maybe Text
$sel:requireEachIncludedType:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:passwordLength:GetRandomPassword' :: GetRandomPassword -> Maybe Natural
$sel:includeSpace:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeUppercase:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludePunctuation:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeNumbers:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeLowercase:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeCharacters:GetRandomPassword' :: GetRandomPassword -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
excludeCharacters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
excludeLowercase
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
excludeNumbers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
excludePunctuation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
excludeUppercase
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeSpace
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
passwordLength
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
requireEachIncludedType

instance Data.ToHeaders GetRandomPassword where
  toHeaders :: GetRandomPassword -> 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
"secretsmanager.GetRandomPassword" ::
                          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 GetRandomPassword where
  toJSON :: GetRandomPassword -> Value
toJSON GetRandomPassword' {Maybe Bool
Maybe Natural
Maybe Text
requireEachIncludedType :: Maybe Bool
passwordLength :: Maybe Natural
includeSpace :: Maybe Bool
excludeUppercase :: Maybe Bool
excludePunctuation :: Maybe Bool
excludeNumbers :: Maybe Bool
excludeLowercase :: Maybe Bool
excludeCharacters :: Maybe Text
$sel:requireEachIncludedType:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:passwordLength:GetRandomPassword' :: GetRandomPassword -> Maybe Natural
$sel:includeSpace:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeUppercase:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludePunctuation:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeNumbers:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeLowercase:GetRandomPassword' :: GetRandomPassword -> Maybe Bool
$sel:excludeCharacters:GetRandomPassword' :: GetRandomPassword -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ExcludeCharacters" 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 Text
excludeCharacters,
            (Key
"ExcludeLowercase" 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 Bool
excludeLowercase,
            (Key
"ExcludeNumbers" 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 Bool
excludeNumbers,
            (Key
"ExcludePunctuation" 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 Bool
excludePunctuation,
            (Key
"ExcludeUppercase" 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 Bool
excludeUppercase,
            (Key
"IncludeSpace" 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 Bool
includeSpace,
            (Key
"PasswordLength" 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 Natural
passwordLength,
            (Key
"RequireEachIncludedType" 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 Bool
requireEachIncludedType
          ]
      )

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

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

-- | /See:/ 'newGetRandomPasswordResponse' smart constructor.
data GetRandomPasswordResponse = GetRandomPasswordResponse'
  { -- | A string with the password.
    GetRandomPasswordResponse -> Maybe (Sensitive Text)
randomPassword :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The response's http status code.
    GetRandomPasswordResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetRandomPasswordResponse -> GetRandomPasswordResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRandomPasswordResponse -> GetRandomPasswordResponse -> Bool
$c/= :: GetRandomPasswordResponse -> GetRandomPasswordResponse -> Bool
== :: GetRandomPasswordResponse -> GetRandomPasswordResponse -> Bool
$c== :: GetRandomPasswordResponse -> GetRandomPasswordResponse -> Bool
Prelude.Eq, Int -> GetRandomPasswordResponse -> ShowS
[GetRandomPasswordResponse] -> ShowS
GetRandomPasswordResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRandomPasswordResponse] -> ShowS
$cshowList :: [GetRandomPasswordResponse] -> ShowS
show :: GetRandomPasswordResponse -> String
$cshow :: GetRandomPasswordResponse -> String
showsPrec :: Int -> GetRandomPasswordResponse -> ShowS
$cshowsPrec :: Int -> GetRandomPasswordResponse -> ShowS
Prelude.Show, forall x.
Rep GetRandomPasswordResponse x -> GetRandomPasswordResponse
forall x.
GetRandomPasswordResponse -> Rep GetRandomPasswordResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRandomPasswordResponse x -> GetRandomPasswordResponse
$cfrom :: forall x.
GetRandomPasswordResponse -> Rep GetRandomPasswordResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRandomPasswordResponse' 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:
--
-- 'randomPassword', 'getRandomPasswordResponse_randomPassword' - A string with the password.
--
-- 'httpStatus', 'getRandomPasswordResponse_httpStatus' - The response's http status code.
newGetRandomPasswordResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetRandomPasswordResponse
newGetRandomPasswordResponse :: Int -> GetRandomPasswordResponse
newGetRandomPasswordResponse Int
pHttpStatus_ =
  GetRandomPasswordResponse'
    { $sel:randomPassword:GetRandomPasswordResponse' :: Maybe (Sensitive Text)
randomPassword =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetRandomPasswordResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A string with the password.
getRandomPasswordResponse_randomPassword :: Lens.Lens' GetRandomPasswordResponse (Prelude.Maybe Prelude.Text)
getRandomPasswordResponse_randomPassword :: Lens' GetRandomPasswordResponse (Maybe Text)
getRandomPasswordResponse_randomPassword = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPasswordResponse' {Maybe (Sensitive Text)
randomPassword :: Maybe (Sensitive Text)
$sel:randomPassword:GetRandomPasswordResponse' :: GetRandomPasswordResponse -> Maybe (Sensitive Text)
randomPassword} -> Maybe (Sensitive Text)
randomPassword) (\s :: GetRandomPasswordResponse
s@GetRandomPasswordResponse' {} Maybe (Sensitive Text)
a -> GetRandomPasswordResponse
s {$sel:randomPassword:GetRandomPasswordResponse' :: Maybe (Sensitive Text)
randomPassword = Maybe (Sensitive Text)
a} :: GetRandomPasswordResponse) 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 response's http status code.
getRandomPasswordResponse_httpStatus :: Lens.Lens' GetRandomPasswordResponse Prelude.Int
getRandomPasswordResponse_httpStatus :: Lens' GetRandomPasswordResponse Int
getRandomPasswordResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRandomPasswordResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetRandomPasswordResponse' :: GetRandomPasswordResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetRandomPasswordResponse
s@GetRandomPasswordResponse' {} Int
a -> GetRandomPasswordResponse
s {$sel:httpStatus:GetRandomPasswordResponse' :: Int
httpStatus = Int
a} :: GetRandomPasswordResponse)

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