{-# 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.KMS.VerifyMac
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Verifies the hash-based message authentication code (HMAC) for a
-- specified message, HMAC KMS key, and MAC algorithm. To verify the HMAC,
-- @VerifyMac@ computes an HMAC using the message, HMAC KMS key, and MAC
-- algorithm that you specify, and compares the computed HMAC to the HMAC
-- that you specify. If the HMACs are identical, the verification succeeds;
-- otherwise, it fails. Verification indicates that the message hasn\'t
-- changed since the HMAC was calculated, and the specified key was used to
-- generate and verify the HMAC.
--
-- HMAC KMS keys and the HMAC algorithms that KMS uses conform to industry
-- standards defined in
-- <https://datatracker.ietf.org/doc/html/rfc2104 RFC 2104>.
--
-- This operation is part of KMS support for HMAC KMS keys. For details,
-- see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/hmac.html HMAC keys in KMS>
-- in the /Key Management Service Developer Guide/.
--
-- The KMS key that you use for this operation must be in a compatible key
-- state. For details, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/key-state.html Key states of KMS keys>
-- in the /Key Management Service Developer Guide/.
--
-- __Cross-account use__: Yes. To perform this operation with a KMS key in
-- a different Amazon Web Services account, specify the key ARN or alias
-- ARN in the value of the @KeyId@ parameter.
--
-- __Required permissions__:
-- <https://docs.aws.amazon.com/kms/latest/developerguide/kms-api-permissions-reference.html kms:VerifyMac>
-- (key policy)
--
-- __Related operations__: GenerateMac
module Amazonka.KMS.VerifyMac
  ( -- * Creating a Request
    VerifyMac (..),
    newVerifyMac,

    -- * Request Lenses
    verifyMac_grantTokens,
    verifyMac_message,
    verifyMac_keyId,
    verifyMac_macAlgorithm,
    verifyMac_mac,

    -- * Destructuring the Response
    VerifyMacResponse (..),
    newVerifyMacResponse,

    -- * Response Lenses
    verifyMacResponse_keyId,
    verifyMacResponse_macAlgorithm,
    verifyMacResponse_macValid,
    verifyMacResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KMS.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newVerifyMac' smart constructor.
data VerifyMac = VerifyMac'
  { -- | A list of grant tokens.
    --
    -- Use a grant token when your permission to call this operation comes from
    -- a new grant that has not yet achieved /eventual consistency/. For more
    -- information, see
    -- <https://docs.aws.amazon.com/kms/latest/developerguide/grants.html#grant_token Grant token>
    -- and
    -- <https://docs.aws.amazon.com/kms/latest/developerguide/grant-manage.html#using-grant-token Using a grant token>
    -- in the /Key Management Service Developer Guide/.
    VerifyMac -> Maybe [Text]
grantTokens :: Prelude.Maybe [Prelude.Text],
    -- | The message that will be used in the verification. Enter the same
    -- message that was used to generate the HMAC.
    --
    -- GenerateMac and @VerifyMac@ do not provide special handling for message
    -- digests. If you generated an HMAC for a hash digest of a message, you
    -- must verify the HMAC for the same hash digest.
    VerifyMac -> Sensitive Base64
message :: Data.Sensitive Data.Base64,
    -- | The KMS key that will be used in the verification.
    --
    -- Enter a key ID of the KMS key that was used to generate the HMAC. If you
    -- identify a different KMS key, the @VerifyMac@ operation fails.
    VerifyMac -> Text
keyId :: Prelude.Text,
    -- | The MAC algorithm that will be used in the verification. Enter the same
    -- MAC algorithm that was used to compute the HMAC. This algorithm must be
    -- supported by the HMAC KMS key identified by the @KeyId@ parameter.
    VerifyMac -> MacAlgorithmSpec
macAlgorithm :: MacAlgorithmSpec,
    -- | The HMAC to verify. Enter the HMAC that was generated by the GenerateMac
    -- operation when you specified the same message, HMAC KMS key, and MAC
    -- algorithm as the values specified in this request.
    VerifyMac -> Base64
mac :: Data.Base64
  }
  deriving (VerifyMac -> VerifyMac -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerifyMac -> VerifyMac -> Bool
$c/= :: VerifyMac -> VerifyMac -> Bool
== :: VerifyMac -> VerifyMac -> Bool
$c== :: VerifyMac -> VerifyMac -> Bool
Prelude.Eq, Int -> VerifyMac -> ShowS
[VerifyMac] -> ShowS
VerifyMac -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerifyMac] -> ShowS
$cshowList :: [VerifyMac] -> ShowS
show :: VerifyMac -> String
$cshow :: VerifyMac -> String
showsPrec :: Int -> VerifyMac -> ShowS
$cshowsPrec :: Int -> VerifyMac -> ShowS
Prelude.Show, forall x. Rep VerifyMac x -> VerifyMac
forall x. VerifyMac -> Rep VerifyMac x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VerifyMac x -> VerifyMac
$cfrom :: forall x. VerifyMac -> Rep VerifyMac x
Prelude.Generic)

-- |
-- Create a value of 'VerifyMac' 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:
--
-- 'grantTokens', 'verifyMac_grantTokens' - A list of grant tokens.
--
-- Use a grant token when your permission to call this operation comes from
-- a new grant that has not yet achieved /eventual consistency/. For more
-- information, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/grants.html#grant_token Grant token>
-- and
-- <https://docs.aws.amazon.com/kms/latest/developerguide/grant-manage.html#using-grant-token Using a grant token>
-- in the /Key Management Service Developer Guide/.
--
-- 'message', 'verifyMac_message' - The message that will be used in the verification. Enter the same
-- message that was used to generate the HMAC.
--
-- GenerateMac and @VerifyMac@ do not provide special handling for message
-- digests. If you generated an HMAC for a hash digest of a message, you
-- must verify the HMAC for the same hash digest.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
--
-- 'keyId', 'verifyMac_keyId' - The KMS key that will be used in the verification.
--
-- Enter a key ID of the KMS key that was used to generate the HMAC. If you
-- identify a different KMS key, the @VerifyMac@ operation fails.
--
-- 'macAlgorithm', 'verifyMac_macAlgorithm' - The MAC algorithm that will be used in the verification. Enter the same
-- MAC algorithm that was used to compute the HMAC. This algorithm must be
-- supported by the HMAC KMS key identified by the @KeyId@ parameter.
--
-- 'mac', 'verifyMac_mac' - The HMAC to verify. Enter the HMAC that was generated by the GenerateMac
-- operation when you specified the same message, HMAC KMS key, and MAC
-- algorithm as the values specified in this request.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
newVerifyMac ::
  -- | 'message'
  Prelude.ByteString ->
  -- | 'keyId'
  Prelude.Text ->
  -- | 'macAlgorithm'
  MacAlgorithmSpec ->
  -- | 'mac'
  Prelude.ByteString ->
  VerifyMac
newVerifyMac :: ByteString -> Text -> MacAlgorithmSpec -> ByteString -> VerifyMac
newVerifyMac ByteString
pMessage_ Text
pKeyId_ MacAlgorithmSpec
pMacAlgorithm_ ByteString
pMac_ =
  VerifyMac'
    { $sel:grantTokens:VerifyMac' :: Maybe [Text]
grantTokens = forall a. Maybe a
Prelude.Nothing,
      $sel:message:VerifyMac' :: Sensitive Base64
message =
        forall a. Iso' (Sensitive a) a
Data._Sensitive
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64
          forall t b. AReview t b -> b -> t
Lens.# ByteString
pMessage_,
      $sel:keyId:VerifyMac' :: Text
keyId = Text
pKeyId_,
      $sel:macAlgorithm:VerifyMac' :: MacAlgorithmSpec
macAlgorithm = MacAlgorithmSpec
pMacAlgorithm_,
      $sel:mac:VerifyMac' :: Base64
mac = Iso' Base64 ByteString
Data._Base64 forall t b. AReview t b -> b -> t
Lens.# ByteString
pMac_
    }

-- | A list of grant tokens.
--
-- Use a grant token when your permission to call this operation comes from
-- a new grant that has not yet achieved /eventual consistency/. For more
-- information, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/grants.html#grant_token Grant token>
-- and
-- <https://docs.aws.amazon.com/kms/latest/developerguide/grant-manage.html#using-grant-token Using a grant token>
-- in the /Key Management Service Developer Guide/.
verifyMac_grantTokens :: Lens.Lens' VerifyMac (Prelude.Maybe [Prelude.Text])
verifyMac_grantTokens :: Lens' VerifyMac (Maybe [Text])
verifyMac_grantTokens = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyMac' {Maybe [Text]
grantTokens :: Maybe [Text]
$sel:grantTokens:VerifyMac' :: VerifyMac -> Maybe [Text]
grantTokens} -> Maybe [Text]
grantTokens) (\s :: VerifyMac
s@VerifyMac' {} Maybe [Text]
a -> VerifyMac
s {$sel:grantTokens:VerifyMac' :: Maybe [Text]
grantTokens = Maybe [Text]
a} :: VerifyMac) 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 message that will be used in the verification. Enter the same
-- message that was used to generate the HMAC.
--
-- GenerateMac and @VerifyMac@ do not provide special handling for message
-- digests. If you generated an HMAC for a hash digest of a message, you
-- must verify the HMAC for the same hash digest.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
verifyMac_message :: Lens.Lens' VerifyMac Prelude.ByteString
verifyMac_message :: Lens' VerifyMac ByteString
verifyMac_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyMac' {Sensitive Base64
message :: Sensitive Base64
$sel:message:VerifyMac' :: VerifyMac -> Sensitive Base64
message} -> Sensitive Base64
message) (\s :: VerifyMac
s@VerifyMac' {} Sensitive Base64
a -> VerifyMac
s {$sel:message:VerifyMac' :: Sensitive Base64
message = Sensitive Base64
a} :: VerifyMac) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64

-- | The KMS key that will be used in the verification.
--
-- Enter a key ID of the KMS key that was used to generate the HMAC. If you
-- identify a different KMS key, the @VerifyMac@ operation fails.
verifyMac_keyId :: Lens.Lens' VerifyMac Prelude.Text
verifyMac_keyId :: Lens' VerifyMac Text
verifyMac_keyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyMac' {Text
keyId :: Text
$sel:keyId:VerifyMac' :: VerifyMac -> Text
keyId} -> Text
keyId) (\s :: VerifyMac
s@VerifyMac' {} Text
a -> VerifyMac
s {$sel:keyId:VerifyMac' :: Text
keyId = Text
a} :: VerifyMac)

-- | The MAC algorithm that will be used in the verification. Enter the same
-- MAC algorithm that was used to compute the HMAC. This algorithm must be
-- supported by the HMAC KMS key identified by the @KeyId@ parameter.
verifyMac_macAlgorithm :: Lens.Lens' VerifyMac MacAlgorithmSpec
verifyMac_macAlgorithm :: Lens' VerifyMac MacAlgorithmSpec
verifyMac_macAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyMac' {MacAlgorithmSpec
macAlgorithm :: MacAlgorithmSpec
$sel:macAlgorithm:VerifyMac' :: VerifyMac -> MacAlgorithmSpec
macAlgorithm} -> MacAlgorithmSpec
macAlgorithm) (\s :: VerifyMac
s@VerifyMac' {} MacAlgorithmSpec
a -> VerifyMac
s {$sel:macAlgorithm:VerifyMac' :: MacAlgorithmSpec
macAlgorithm = MacAlgorithmSpec
a} :: VerifyMac)

-- | The HMAC to verify. Enter the HMAC that was generated by the GenerateMac
-- operation when you specified the same message, HMAC KMS key, and MAC
-- algorithm as the values specified in this request.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
verifyMac_mac :: Lens.Lens' VerifyMac Prelude.ByteString
verifyMac_mac :: Lens' VerifyMac ByteString
verifyMac_mac = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyMac' {Base64
mac :: Base64
$sel:mac:VerifyMac' :: VerifyMac -> Base64
mac} -> Base64
mac) (\s :: VerifyMac
s@VerifyMac' {} Base64
a -> VerifyMac
s {$sel:mac:VerifyMac' :: Base64
mac = Base64
a} :: VerifyMac) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64

instance Core.AWSRequest VerifyMac where
  type AWSResponse VerifyMac = VerifyMacResponse
  request :: (Service -> Service) -> VerifyMac -> Request VerifyMac
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 VerifyMac
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse VerifyMac)))
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 Text
-> Maybe MacAlgorithmSpec -> Maybe Bool -> Int -> VerifyMacResponse
VerifyMacResponse'
            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
"KeyId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"MacAlgorithm")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"MacValid")
            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 VerifyMac where
  hashWithSalt :: Int -> VerifyMac -> Int
hashWithSalt Int
_salt VerifyMac' {Maybe [Text]
Text
Base64
Sensitive Base64
MacAlgorithmSpec
mac :: Base64
macAlgorithm :: MacAlgorithmSpec
keyId :: Text
message :: Sensitive Base64
grantTokens :: Maybe [Text]
$sel:mac:VerifyMac' :: VerifyMac -> Base64
$sel:macAlgorithm:VerifyMac' :: VerifyMac -> MacAlgorithmSpec
$sel:keyId:VerifyMac' :: VerifyMac -> Text
$sel:message:VerifyMac' :: VerifyMac -> Sensitive Base64
$sel:grantTokens:VerifyMac' :: VerifyMac -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
grantTokens
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Base64
message
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
keyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` MacAlgorithmSpec
macAlgorithm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Base64
mac

instance Prelude.NFData VerifyMac where
  rnf :: VerifyMac -> ()
rnf VerifyMac' {Maybe [Text]
Text
Base64
Sensitive Base64
MacAlgorithmSpec
mac :: Base64
macAlgorithm :: MacAlgorithmSpec
keyId :: Text
message :: Sensitive Base64
grantTokens :: Maybe [Text]
$sel:mac:VerifyMac' :: VerifyMac -> Base64
$sel:macAlgorithm:VerifyMac' :: VerifyMac -> MacAlgorithmSpec
$sel:keyId:VerifyMac' :: VerifyMac -> Text
$sel:message:VerifyMac' :: VerifyMac -> Sensitive Base64
$sel:grantTokens:VerifyMac' :: VerifyMac -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
grantTokens
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Base64
message
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
keyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf MacAlgorithmSpec
macAlgorithm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Base64
mac

instance Data.ToHeaders VerifyMac where
  toHeaders :: VerifyMac -> 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
"TrentService.VerifyMac" :: 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 VerifyMac where
  toJSON :: VerifyMac -> Value
toJSON VerifyMac' {Maybe [Text]
Text
Base64
Sensitive Base64
MacAlgorithmSpec
mac :: Base64
macAlgorithm :: MacAlgorithmSpec
keyId :: Text
message :: Sensitive Base64
grantTokens :: Maybe [Text]
$sel:mac:VerifyMac' :: VerifyMac -> Base64
$sel:macAlgorithm:VerifyMac' :: VerifyMac -> MacAlgorithmSpec
$sel:keyId:VerifyMac' :: VerifyMac -> Text
$sel:message:VerifyMac' :: VerifyMac -> Sensitive Base64
$sel:grantTokens:VerifyMac' :: VerifyMac -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"GrantTokens" 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]
grantTokens,
            forall a. a -> Maybe a
Prelude.Just (Key
"Message" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Base64
message),
            forall a. a -> Maybe a
Prelude.Just (Key
"KeyId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
keyId),
            forall a. a -> Maybe a
Prelude.Just (Key
"MacAlgorithm" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= MacAlgorithmSpec
macAlgorithm),
            forall a. a -> Maybe a
Prelude.Just (Key
"Mac" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Base64
mac)
          ]
      )

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

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

-- | /See:/ 'newVerifyMacResponse' smart constructor.
data VerifyMacResponse = VerifyMacResponse'
  { -- | The HMAC KMS key used in the verification.
    VerifyMacResponse -> Maybe Text
keyId :: Prelude.Maybe Prelude.Text,
    -- | The MAC algorithm used in the verification.
    VerifyMacResponse -> Maybe MacAlgorithmSpec
macAlgorithm :: Prelude.Maybe MacAlgorithmSpec,
    -- | A Boolean value that indicates whether the HMAC was verified. A value of
    -- @True@ indicates that the HMAC (@Mac@) was generated with the specified
    -- @Message@, HMAC KMS key (@KeyID@) and @MacAlgorithm.@.
    --
    -- If the HMAC is not verified, the @VerifyMac@ operation fails with a
    -- @KMSInvalidMacException@ exception. This exception indicates that one or
    -- more of the inputs changed since the HMAC was computed.
    VerifyMacResponse -> Maybe Bool
macValid :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    VerifyMacResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (VerifyMacResponse -> VerifyMacResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerifyMacResponse -> VerifyMacResponse -> Bool
$c/= :: VerifyMacResponse -> VerifyMacResponse -> Bool
== :: VerifyMacResponse -> VerifyMacResponse -> Bool
$c== :: VerifyMacResponse -> VerifyMacResponse -> Bool
Prelude.Eq, ReadPrec [VerifyMacResponse]
ReadPrec VerifyMacResponse
Int -> ReadS VerifyMacResponse
ReadS [VerifyMacResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VerifyMacResponse]
$creadListPrec :: ReadPrec [VerifyMacResponse]
readPrec :: ReadPrec VerifyMacResponse
$creadPrec :: ReadPrec VerifyMacResponse
readList :: ReadS [VerifyMacResponse]
$creadList :: ReadS [VerifyMacResponse]
readsPrec :: Int -> ReadS VerifyMacResponse
$creadsPrec :: Int -> ReadS VerifyMacResponse
Prelude.Read, Int -> VerifyMacResponse -> ShowS
[VerifyMacResponse] -> ShowS
VerifyMacResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerifyMacResponse] -> ShowS
$cshowList :: [VerifyMacResponse] -> ShowS
show :: VerifyMacResponse -> String
$cshow :: VerifyMacResponse -> String
showsPrec :: Int -> VerifyMacResponse -> ShowS
$cshowsPrec :: Int -> VerifyMacResponse -> ShowS
Prelude.Show, forall x. Rep VerifyMacResponse x -> VerifyMacResponse
forall x. VerifyMacResponse -> Rep VerifyMacResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VerifyMacResponse x -> VerifyMacResponse
$cfrom :: forall x. VerifyMacResponse -> Rep VerifyMacResponse x
Prelude.Generic)

-- |
-- Create a value of 'VerifyMacResponse' 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:
--
-- 'keyId', 'verifyMacResponse_keyId' - The HMAC KMS key used in the verification.
--
-- 'macAlgorithm', 'verifyMacResponse_macAlgorithm' - The MAC algorithm used in the verification.
--
-- 'macValid', 'verifyMacResponse_macValid' - A Boolean value that indicates whether the HMAC was verified. A value of
-- @True@ indicates that the HMAC (@Mac@) was generated with the specified
-- @Message@, HMAC KMS key (@KeyID@) and @MacAlgorithm.@.
--
-- If the HMAC is not verified, the @VerifyMac@ operation fails with a
-- @KMSInvalidMacException@ exception. This exception indicates that one or
-- more of the inputs changed since the HMAC was computed.
--
-- 'httpStatus', 'verifyMacResponse_httpStatus' - The response's http status code.
newVerifyMacResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  VerifyMacResponse
newVerifyMacResponse :: Int -> VerifyMacResponse
newVerifyMacResponse Int
pHttpStatus_ =
  VerifyMacResponse'
    { $sel:keyId:VerifyMacResponse' :: Maybe Text
keyId = forall a. Maybe a
Prelude.Nothing,
      $sel:macAlgorithm:VerifyMacResponse' :: Maybe MacAlgorithmSpec
macAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:macValid:VerifyMacResponse' :: Maybe Bool
macValid = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:VerifyMacResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The HMAC KMS key used in the verification.
verifyMacResponse_keyId :: Lens.Lens' VerifyMacResponse (Prelude.Maybe Prelude.Text)
verifyMacResponse_keyId :: Lens' VerifyMacResponse (Maybe Text)
verifyMacResponse_keyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyMacResponse' {Maybe Text
keyId :: Maybe Text
$sel:keyId:VerifyMacResponse' :: VerifyMacResponse -> Maybe Text
keyId} -> Maybe Text
keyId) (\s :: VerifyMacResponse
s@VerifyMacResponse' {} Maybe Text
a -> VerifyMacResponse
s {$sel:keyId:VerifyMacResponse' :: Maybe Text
keyId = Maybe Text
a} :: VerifyMacResponse)

-- | The MAC algorithm used in the verification.
verifyMacResponse_macAlgorithm :: Lens.Lens' VerifyMacResponse (Prelude.Maybe MacAlgorithmSpec)
verifyMacResponse_macAlgorithm :: Lens' VerifyMacResponse (Maybe MacAlgorithmSpec)
verifyMacResponse_macAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyMacResponse' {Maybe MacAlgorithmSpec
macAlgorithm :: Maybe MacAlgorithmSpec
$sel:macAlgorithm:VerifyMacResponse' :: VerifyMacResponse -> Maybe MacAlgorithmSpec
macAlgorithm} -> Maybe MacAlgorithmSpec
macAlgorithm) (\s :: VerifyMacResponse
s@VerifyMacResponse' {} Maybe MacAlgorithmSpec
a -> VerifyMacResponse
s {$sel:macAlgorithm:VerifyMacResponse' :: Maybe MacAlgorithmSpec
macAlgorithm = Maybe MacAlgorithmSpec
a} :: VerifyMacResponse)

-- | A Boolean value that indicates whether the HMAC was verified. A value of
-- @True@ indicates that the HMAC (@Mac@) was generated with the specified
-- @Message@, HMAC KMS key (@KeyID@) and @MacAlgorithm.@.
--
-- If the HMAC is not verified, the @VerifyMac@ operation fails with a
-- @KMSInvalidMacException@ exception. This exception indicates that one or
-- more of the inputs changed since the HMAC was computed.
verifyMacResponse_macValid :: Lens.Lens' VerifyMacResponse (Prelude.Maybe Prelude.Bool)
verifyMacResponse_macValid :: Lens' VerifyMacResponse (Maybe Bool)
verifyMacResponse_macValid = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyMacResponse' {Maybe Bool
macValid :: Maybe Bool
$sel:macValid:VerifyMacResponse' :: VerifyMacResponse -> Maybe Bool
macValid} -> Maybe Bool
macValid) (\s :: VerifyMacResponse
s@VerifyMacResponse' {} Maybe Bool
a -> VerifyMacResponse
s {$sel:macValid:VerifyMacResponse' :: Maybe Bool
macValid = Maybe Bool
a} :: VerifyMacResponse)

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

instance Prelude.NFData VerifyMacResponse where
  rnf :: VerifyMacResponse -> ()
rnf VerifyMacResponse' {Int
Maybe Bool
Maybe Text
Maybe MacAlgorithmSpec
httpStatus :: Int
macValid :: Maybe Bool
macAlgorithm :: Maybe MacAlgorithmSpec
keyId :: Maybe Text
$sel:httpStatus:VerifyMacResponse' :: VerifyMacResponse -> Int
$sel:macValid:VerifyMacResponse' :: VerifyMacResponse -> Maybe Bool
$sel:macAlgorithm:VerifyMacResponse' :: VerifyMacResponse -> Maybe MacAlgorithmSpec
$sel:keyId:VerifyMacResponse' :: VerifyMacResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
keyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MacAlgorithmSpec
macAlgorithm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
macValid
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus