{-# 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.Support.DescribeTrustedAdvisorCheckResult
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the results of the Trusted Advisor check that has the specified
-- check ID. You can get the check IDs by calling the
-- DescribeTrustedAdvisorChecks operation.
--
-- The response contains a TrustedAdvisorCheckResult object, which contains
-- these three objects:
--
-- -   TrustedAdvisorCategorySpecificSummary
--
-- -   TrustedAdvisorResourceDetail
--
-- -   TrustedAdvisorResourcesSummary
--
-- In addition, the response contains these fields:
--
-- -   __status__ - The alert status of the check can be @ok@ (green),
--     @warning@ (yellow), @error@ (red), or @not_available@.
--
-- -   __timestamp__ - The time of the last refresh of the check.
--
-- -   __checkId__ - The unique identifier for the check.
--
-- -   You must have a Business, Enterprise On-Ramp, or Enterprise Support
--     plan to use the Amazon Web Services Support API.
--
-- -   If you call the Amazon Web Services Support API from an account that
--     doesn\'t have a Business, Enterprise On-Ramp, or Enterprise Support
--     plan, the @SubscriptionRequiredException@ error message appears. For
--     information about changing your support plan, see
--     <http://aws.amazon.com/premiumsupport/ Amazon Web Services Support>.
--
-- To call the Trusted Advisor operations in the Amazon Web Services
-- Support API, you must use the US East (N. Virginia) endpoint. Currently,
-- the US West (Oregon) and Europe (Ireland) endpoints don\'t support the
-- Trusted Advisor operations. For more information, see
-- <https://docs.aws.amazon.com/awssupport/latest/user/about-support-api.html#endpoint About the Amazon Web Services Support API>
-- in the /Amazon Web Services Support User Guide/.
module Amazonka.Support.DescribeTrustedAdvisorCheckResult
  ( -- * Creating a Request
    DescribeTrustedAdvisorCheckResult (..),
    newDescribeTrustedAdvisorCheckResult,

    -- * Request Lenses
    describeTrustedAdvisorCheckResult_language,
    describeTrustedAdvisorCheckResult_checkId,

    -- * Destructuring the Response
    DescribeTrustedAdvisorCheckResultResponse (..),
    newDescribeTrustedAdvisorCheckResultResponse,

    -- * Response Lenses
    describeTrustedAdvisorCheckResultResponse_result,
    describeTrustedAdvisorCheckResultResponse_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.Support.Types

-- |
--
-- /See:/ 'newDescribeTrustedAdvisorCheckResult' smart constructor.
data DescribeTrustedAdvisorCheckResult = DescribeTrustedAdvisorCheckResult'
  { -- | The ISO 639-1 code for the language that you want your check results to
    -- appear in.
    --
    -- The Amazon Web Services Support API currently supports the following
    -- languages for Trusted Advisor:
    --
    -- -   Chinese, Simplified - @zh@
    --
    -- -   Chinese, Traditional - @zh_TW@
    --
    -- -   English - @en@
    --
    -- -   French - @fr@
    --
    -- -   German - @de@
    --
    -- -   Indonesian - @id@
    --
    -- -   Italian - @it@
    --
    -- -   Japanese - @ja@
    --
    -- -   Korean - @ko@
    --
    -- -   Portuguese, Brazilian - @pt_BR@
    --
    -- -   Spanish - @es@
    DescribeTrustedAdvisorCheckResult -> Maybe Text
language :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the Trusted Advisor check.
    DescribeTrustedAdvisorCheckResult -> Text
checkId :: Prelude.Text
  }
  deriving (DescribeTrustedAdvisorCheckResult
-> DescribeTrustedAdvisorCheckResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeTrustedAdvisorCheckResult
-> DescribeTrustedAdvisorCheckResult -> Bool
$c/= :: DescribeTrustedAdvisorCheckResult
-> DescribeTrustedAdvisorCheckResult -> Bool
== :: DescribeTrustedAdvisorCheckResult
-> DescribeTrustedAdvisorCheckResult -> Bool
$c== :: DescribeTrustedAdvisorCheckResult
-> DescribeTrustedAdvisorCheckResult -> Bool
Prelude.Eq, ReadPrec [DescribeTrustedAdvisorCheckResult]
ReadPrec DescribeTrustedAdvisorCheckResult
Int -> ReadS DescribeTrustedAdvisorCheckResult
ReadS [DescribeTrustedAdvisorCheckResult]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeTrustedAdvisorCheckResult]
$creadListPrec :: ReadPrec [DescribeTrustedAdvisorCheckResult]
readPrec :: ReadPrec DescribeTrustedAdvisorCheckResult
$creadPrec :: ReadPrec DescribeTrustedAdvisorCheckResult
readList :: ReadS [DescribeTrustedAdvisorCheckResult]
$creadList :: ReadS [DescribeTrustedAdvisorCheckResult]
readsPrec :: Int -> ReadS DescribeTrustedAdvisorCheckResult
$creadsPrec :: Int -> ReadS DescribeTrustedAdvisorCheckResult
Prelude.Read, Int -> DescribeTrustedAdvisorCheckResult -> ShowS
[DescribeTrustedAdvisorCheckResult] -> ShowS
DescribeTrustedAdvisorCheckResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeTrustedAdvisorCheckResult] -> ShowS
$cshowList :: [DescribeTrustedAdvisorCheckResult] -> ShowS
show :: DescribeTrustedAdvisorCheckResult -> String
$cshow :: DescribeTrustedAdvisorCheckResult -> String
showsPrec :: Int -> DescribeTrustedAdvisorCheckResult -> ShowS
$cshowsPrec :: Int -> DescribeTrustedAdvisorCheckResult -> ShowS
Prelude.Show, forall x.
Rep DescribeTrustedAdvisorCheckResult x
-> DescribeTrustedAdvisorCheckResult
forall x.
DescribeTrustedAdvisorCheckResult
-> Rep DescribeTrustedAdvisorCheckResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeTrustedAdvisorCheckResult x
-> DescribeTrustedAdvisorCheckResult
$cfrom :: forall x.
DescribeTrustedAdvisorCheckResult
-> Rep DescribeTrustedAdvisorCheckResult x
Prelude.Generic)

-- |
-- Create a value of 'DescribeTrustedAdvisorCheckResult' 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:
--
-- 'language', 'describeTrustedAdvisorCheckResult_language' - The ISO 639-1 code for the language that you want your check results to
-- appear in.
--
-- The Amazon Web Services Support API currently supports the following
-- languages for Trusted Advisor:
--
-- -   Chinese, Simplified - @zh@
--
-- -   Chinese, Traditional - @zh_TW@
--
-- -   English - @en@
--
-- -   French - @fr@
--
-- -   German - @de@
--
-- -   Indonesian - @id@
--
-- -   Italian - @it@
--
-- -   Japanese - @ja@
--
-- -   Korean - @ko@
--
-- -   Portuguese, Brazilian - @pt_BR@
--
-- -   Spanish - @es@
--
-- 'checkId', 'describeTrustedAdvisorCheckResult_checkId' - The unique identifier for the Trusted Advisor check.
newDescribeTrustedAdvisorCheckResult ::
  -- | 'checkId'
  Prelude.Text ->
  DescribeTrustedAdvisorCheckResult
newDescribeTrustedAdvisorCheckResult :: Text -> DescribeTrustedAdvisorCheckResult
newDescribeTrustedAdvisorCheckResult Text
pCheckId_ =
  DescribeTrustedAdvisorCheckResult'
    { $sel:language:DescribeTrustedAdvisorCheckResult' :: Maybe Text
language =
        forall a. Maybe a
Prelude.Nothing,
      $sel:checkId:DescribeTrustedAdvisorCheckResult' :: Text
checkId = Text
pCheckId_
    }

-- | The ISO 639-1 code for the language that you want your check results to
-- appear in.
--
-- The Amazon Web Services Support API currently supports the following
-- languages for Trusted Advisor:
--
-- -   Chinese, Simplified - @zh@
--
-- -   Chinese, Traditional - @zh_TW@
--
-- -   English - @en@
--
-- -   French - @fr@
--
-- -   German - @de@
--
-- -   Indonesian - @id@
--
-- -   Italian - @it@
--
-- -   Japanese - @ja@
--
-- -   Korean - @ko@
--
-- -   Portuguese, Brazilian - @pt_BR@
--
-- -   Spanish - @es@
describeTrustedAdvisorCheckResult_language :: Lens.Lens' DescribeTrustedAdvisorCheckResult (Prelude.Maybe Prelude.Text)
describeTrustedAdvisorCheckResult_language :: Lens' DescribeTrustedAdvisorCheckResult (Maybe Text)
describeTrustedAdvisorCheckResult_language = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTrustedAdvisorCheckResult' {Maybe Text
language :: Maybe Text
$sel:language:DescribeTrustedAdvisorCheckResult' :: DescribeTrustedAdvisorCheckResult -> Maybe Text
language} -> Maybe Text
language) (\s :: DescribeTrustedAdvisorCheckResult
s@DescribeTrustedAdvisorCheckResult' {} Maybe Text
a -> DescribeTrustedAdvisorCheckResult
s {$sel:language:DescribeTrustedAdvisorCheckResult' :: Maybe Text
language = Maybe Text
a} :: DescribeTrustedAdvisorCheckResult)

-- | The unique identifier for the Trusted Advisor check.
describeTrustedAdvisorCheckResult_checkId :: Lens.Lens' DescribeTrustedAdvisorCheckResult Prelude.Text
describeTrustedAdvisorCheckResult_checkId :: Lens' DescribeTrustedAdvisorCheckResult Text
describeTrustedAdvisorCheckResult_checkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTrustedAdvisorCheckResult' {Text
checkId :: Text
$sel:checkId:DescribeTrustedAdvisorCheckResult' :: DescribeTrustedAdvisorCheckResult -> Text
checkId} -> Text
checkId) (\s :: DescribeTrustedAdvisorCheckResult
s@DescribeTrustedAdvisorCheckResult' {} Text
a -> DescribeTrustedAdvisorCheckResult
s {$sel:checkId:DescribeTrustedAdvisorCheckResult' :: Text
checkId = Text
a} :: DescribeTrustedAdvisorCheckResult)

instance
  Core.AWSRequest
    DescribeTrustedAdvisorCheckResult
  where
  type
    AWSResponse DescribeTrustedAdvisorCheckResult =
      DescribeTrustedAdvisorCheckResultResponse
  request :: (Service -> Service)
-> DescribeTrustedAdvisorCheckResult
-> Request DescribeTrustedAdvisorCheckResult
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 DescribeTrustedAdvisorCheckResult
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeTrustedAdvisorCheckResult)))
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 TrustedAdvisorCheckResult
-> Int -> DescribeTrustedAdvisorCheckResultResponse
DescribeTrustedAdvisorCheckResultResponse'
            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
"result")
            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
    DescribeTrustedAdvisorCheckResult
  where
  hashWithSalt :: Int -> DescribeTrustedAdvisorCheckResult -> Int
hashWithSalt
    Int
_salt
    DescribeTrustedAdvisorCheckResult' {Maybe Text
Text
checkId :: Text
language :: Maybe Text
$sel:checkId:DescribeTrustedAdvisorCheckResult' :: DescribeTrustedAdvisorCheckResult -> Text
$sel:language:DescribeTrustedAdvisorCheckResult' :: DescribeTrustedAdvisorCheckResult -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
language
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
checkId

instance
  Prelude.NFData
    DescribeTrustedAdvisorCheckResult
  where
  rnf :: DescribeTrustedAdvisorCheckResult -> ()
rnf DescribeTrustedAdvisorCheckResult' {Maybe Text
Text
checkId :: Text
language :: Maybe Text
$sel:checkId:DescribeTrustedAdvisorCheckResult' :: DescribeTrustedAdvisorCheckResult -> Text
$sel:language:DescribeTrustedAdvisorCheckResult' :: DescribeTrustedAdvisorCheckResult -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
language
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
checkId

instance
  Data.ToHeaders
    DescribeTrustedAdvisorCheckResult
  where
  toHeaders :: DescribeTrustedAdvisorCheckResult -> 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
"AWSSupport_20130415.DescribeTrustedAdvisorCheckResult" ::
                          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
    DescribeTrustedAdvisorCheckResult
  where
  toJSON :: DescribeTrustedAdvisorCheckResult -> Value
toJSON DescribeTrustedAdvisorCheckResult' {Maybe Text
Text
checkId :: Text
language :: Maybe Text
$sel:checkId:DescribeTrustedAdvisorCheckResult' :: DescribeTrustedAdvisorCheckResult -> Text
$sel:language:DescribeTrustedAdvisorCheckResult' :: DescribeTrustedAdvisorCheckResult -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"language" 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
language,
            forall a. a -> Maybe a
Prelude.Just (Key
"checkId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
checkId)
          ]
      )

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

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

-- | The result of the Trusted Advisor check returned by the
-- DescribeTrustedAdvisorCheckResult operation.
--
-- /See:/ 'newDescribeTrustedAdvisorCheckResultResponse' smart constructor.
data DescribeTrustedAdvisorCheckResultResponse = DescribeTrustedAdvisorCheckResultResponse'
  { -- | The detailed results of the Trusted Advisor check.
    DescribeTrustedAdvisorCheckResultResponse
-> Maybe TrustedAdvisorCheckResult
result :: Prelude.Maybe TrustedAdvisorCheckResult,
    -- | The response's http status code.
    DescribeTrustedAdvisorCheckResultResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeTrustedAdvisorCheckResultResponse
-> DescribeTrustedAdvisorCheckResultResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeTrustedAdvisorCheckResultResponse
-> DescribeTrustedAdvisorCheckResultResponse -> Bool
$c/= :: DescribeTrustedAdvisorCheckResultResponse
-> DescribeTrustedAdvisorCheckResultResponse -> Bool
== :: DescribeTrustedAdvisorCheckResultResponse
-> DescribeTrustedAdvisorCheckResultResponse -> Bool
$c== :: DescribeTrustedAdvisorCheckResultResponse
-> DescribeTrustedAdvisorCheckResultResponse -> Bool
Prelude.Eq, ReadPrec [DescribeTrustedAdvisorCheckResultResponse]
ReadPrec DescribeTrustedAdvisorCheckResultResponse
Int -> ReadS DescribeTrustedAdvisorCheckResultResponse
ReadS [DescribeTrustedAdvisorCheckResultResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeTrustedAdvisorCheckResultResponse]
$creadListPrec :: ReadPrec [DescribeTrustedAdvisorCheckResultResponse]
readPrec :: ReadPrec DescribeTrustedAdvisorCheckResultResponse
$creadPrec :: ReadPrec DescribeTrustedAdvisorCheckResultResponse
readList :: ReadS [DescribeTrustedAdvisorCheckResultResponse]
$creadList :: ReadS [DescribeTrustedAdvisorCheckResultResponse]
readsPrec :: Int -> ReadS DescribeTrustedAdvisorCheckResultResponse
$creadsPrec :: Int -> ReadS DescribeTrustedAdvisorCheckResultResponse
Prelude.Read, Int -> DescribeTrustedAdvisorCheckResultResponse -> ShowS
[DescribeTrustedAdvisorCheckResultResponse] -> ShowS
DescribeTrustedAdvisorCheckResultResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeTrustedAdvisorCheckResultResponse] -> ShowS
$cshowList :: [DescribeTrustedAdvisorCheckResultResponse] -> ShowS
show :: DescribeTrustedAdvisorCheckResultResponse -> String
$cshow :: DescribeTrustedAdvisorCheckResultResponse -> String
showsPrec :: Int -> DescribeTrustedAdvisorCheckResultResponse -> ShowS
$cshowsPrec :: Int -> DescribeTrustedAdvisorCheckResultResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeTrustedAdvisorCheckResultResponse x
-> DescribeTrustedAdvisorCheckResultResponse
forall x.
DescribeTrustedAdvisorCheckResultResponse
-> Rep DescribeTrustedAdvisorCheckResultResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeTrustedAdvisorCheckResultResponse x
-> DescribeTrustedAdvisorCheckResultResponse
$cfrom :: forall x.
DescribeTrustedAdvisorCheckResultResponse
-> Rep DescribeTrustedAdvisorCheckResultResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeTrustedAdvisorCheckResultResponse' 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:
--
-- 'result', 'describeTrustedAdvisorCheckResultResponse_result' - The detailed results of the Trusted Advisor check.
--
-- 'httpStatus', 'describeTrustedAdvisorCheckResultResponse_httpStatus' - The response's http status code.
newDescribeTrustedAdvisorCheckResultResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeTrustedAdvisorCheckResultResponse
newDescribeTrustedAdvisorCheckResultResponse :: Int -> DescribeTrustedAdvisorCheckResultResponse
newDescribeTrustedAdvisorCheckResultResponse
  Int
pHttpStatus_ =
    DescribeTrustedAdvisorCheckResultResponse'
      { $sel:result:DescribeTrustedAdvisorCheckResultResponse' :: Maybe TrustedAdvisorCheckResult
result =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeTrustedAdvisorCheckResultResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The detailed results of the Trusted Advisor check.
describeTrustedAdvisorCheckResultResponse_result :: Lens.Lens' DescribeTrustedAdvisorCheckResultResponse (Prelude.Maybe TrustedAdvisorCheckResult)
describeTrustedAdvisorCheckResultResponse_result :: Lens'
  DescribeTrustedAdvisorCheckResultResponse
  (Maybe TrustedAdvisorCheckResult)
describeTrustedAdvisorCheckResultResponse_result = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTrustedAdvisorCheckResultResponse' {Maybe TrustedAdvisorCheckResult
result :: Maybe TrustedAdvisorCheckResult
$sel:result:DescribeTrustedAdvisorCheckResultResponse' :: DescribeTrustedAdvisorCheckResultResponse
-> Maybe TrustedAdvisorCheckResult
result} -> Maybe TrustedAdvisorCheckResult
result) (\s :: DescribeTrustedAdvisorCheckResultResponse
s@DescribeTrustedAdvisorCheckResultResponse' {} Maybe TrustedAdvisorCheckResult
a -> DescribeTrustedAdvisorCheckResultResponse
s {$sel:result:DescribeTrustedAdvisorCheckResultResponse' :: Maybe TrustedAdvisorCheckResult
result = Maybe TrustedAdvisorCheckResult
a} :: DescribeTrustedAdvisorCheckResultResponse)

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

instance
  Prelude.NFData
    DescribeTrustedAdvisorCheckResultResponse
  where
  rnf :: DescribeTrustedAdvisorCheckResultResponse -> ()
rnf DescribeTrustedAdvisorCheckResultResponse' {Int
Maybe TrustedAdvisorCheckResult
httpStatus :: Int
result :: Maybe TrustedAdvisorCheckResult
$sel:httpStatus:DescribeTrustedAdvisorCheckResultResponse' :: DescribeTrustedAdvisorCheckResultResponse -> Int
$sel:result:DescribeTrustedAdvisorCheckResultResponse' :: DescribeTrustedAdvisorCheckResultResponse
-> Maybe TrustedAdvisorCheckResult
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe TrustedAdvisorCheckResult
result
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus