{-# 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.DescribeTrustedAdvisorChecks
-- 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 information about all available Trusted Advisor checks,
-- including the name, ID, category, description, and metadata. You must
-- specify a language code.
--
-- The response contains a TrustedAdvisorCheckDescription object for each
-- check. You must set the Amazon Web Services Region to us-east-1.
--
-- -   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>.
--
-- -   The names and descriptions for Trusted Advisor checks are subject to
--     change. We recommend that you specify the check ID in your code to
--     uniquely identify a check.
--
-- 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.DescribeTrustedAdvisorChecks
  ( -- * Creating a Request
    DescribeTrustedAdvisorChecks (..),
    newDescribeTrustedAdvisorChecks,

    -- * Request Lenses
    describeTrustedAdvisorChecks_language,

    -- * Destructuring the Response
    DescribeTrustedAdvisorChecksResponse (..),
    newDescribeTrustedAdvisorChecksResponse,

    -- * Response Lenses
    describeTrustedAdvisorChecksResponse_httpStatus,
    describeTrustedAdvisorChecksResponse_checks,
  )
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:/ 'newDescribeTrustedAdvisorChecks' smart constructor.
data DescribeTrustedAdvisorChecks = DescribeTrustedAdvisorChecks'
  { -- | The ISO 639-1 code for the language that you want your checks 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@
    DescribeTrustedAdvisorChecks -> Text
language :: Prelude.Text
  }
  deriving (DescribeTrustedAdvisorChecks
-> DescribeTrustedAdvisorChecks -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeTrustedAdvisorChecks
-> DescribeTrustedAdvisorChecks -> Bool
$c/= :: DescribeTrustedAdvisorChecks
-> DescribeTrustedAdvisorChecks -> Bool
== :: DescribeTrustedAdvisorChecks
-> DescribeTrustedAdvisorChecks -> Bool
$c== :: DescribeTrustedAdvisorChecks
-> DescribeTrustedAdvisorChecks -> Bool
Prelude.Eq, ReadPrec [DescribeTrustedAdvisorChecks]
ReadPrec DescribeTrustedAdvisorChecks
Int -> ReadS DescribeTrustedAdvisorChecks
ReadS [DescribeTrustedAdvisorChecks]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeTrustedAdvisorChecks]
$creadListPrec :: ReadPrec [DescribeTrustedAdvisorChecks]
readPrec :: ReadPrec DescribeTrustedAdvisorChecks
$creadPrec :: ReadPrec DescribeTrustedAdvisorChecks
readList :: ReadS [DescribeTrustedAdvisorChecks]
$creadList :: ReadS [DescribeTrustedAdvisorChecks]
readsPrec :: Int -> ReadS DescribeTrustedAdvisorChecks
$creadsPrec :: Int -> ReadS DescribeTrustedAdvisorChecks
Prelude.Read, Int -> DescribeTrustedAdvisorChecks -> ShowS
[DescribeTrustedAdvisorChecks] -> ShowS
DescribeTrustedAdvisorChecks -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeTrustedAdvisorChecks] -> ShowS
$cshowList :: [DescribeTrustedAdvisorChecks] -> ShowS
show :: DescribeTrustedAdvisorChecks -> String
$cshow :: DescribeTrustedAdvisorChecks -> String
showsPrec :: Int -> DescribeTrustedAdvisorChecks -> ShowS
$cshowsPrec :: Int -> DescribeTrustedAdvisorChecks -> ShowS
Prelude.Show, forall x.
Rep DescribeTrustedAdvisorChecks x -> DescribeTrustedAdvisorChecks
forall x.
DescribeTrustedAdvisorChecks -> Rep DescribeTrustedAdvisorChecks x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeTrustedAdvisorChecks x -> DescribeTrustedAdvisorChecks
$cfrom :: forall x.
DescribeTrustedAdvisorChecks -> Rep DescribeTrustedAdvisorChecks x
Prelude.Generic)

-- |
-- Create a value of 'DescribeTrustedAdvisorChecks' 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', 'describeTrustedAdvisorChecks_language' - The ISO 639-1 code for the language that you want your checks 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@
newDescribeTrustedAdvisorChecks ::
  -- | 'language'
  Prelude.Text ->
  DescribeTrustedAdvisorChecks
newDescribeTrustedAdvisorChecks :: Text -> DescribeTrustedAdvisorChecks
newDescribeTrustedAdvisorChecks Text
pLanguage_ =
  DescribeTrustedAdvisorChecks'
    { $sel:language:DescribeTrustedAdvisorChecks' :: Text
language =
        Text
pLanguage_
    }

-- | The ISO 639-1 code for the language that you want your checks 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@
describeTrustedAdvisorChecks_language :: Lens.Lens' DescribeTrustedAdvisorChecks Prelude.Text
describeTrustedAdvisorChecks_language :: Lens' DescribeTrustedAdvisorChecks Text
describeTrustedAdvisorChecks_language = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTrustedAdvisorChecks' {Text
language :: Text
$sel:language:DescribeTrustedAdvisorChecks' :: DescribeTrustedAdvisorChecks -> Text
language} -> Text
language) (\s :: DescribeTrustedAdvisorChecks
s@DescribeTrustedAdvisorChecks' {} Text
a -> DescribeTrustedAdvisorChecks
s {$sel:language:DescribeTrustedAdvisorChecks' :: Text
language = Text
a} :: DescribeTrustedAdvisorChecks)

instance Core.AWSRequest DescribeTrustedAdvisorChecks where
  type
    AWSResponse DescribeTrustedAdvisorChecks =
      DescribeTrustedAdvisorChecksResponse
  request :: (Service -> Service)
-> DescribeTrustedAdvisorChecks
-> Request DescribeTrustedAdvisorChecks
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 DescribeTrustedAdvisorChecks
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeTrustedAdvisorChecks)))
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 ->
          Int
-> [TrustedAdvisorCheckDescription]
-> DescribeTrustedAdvisorChecksResponse
DescribeTrustedAdvisorChecksResponse'
            forall (f :: * -> *) a b. Functor 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))
            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
"checks" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

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

instance Prelude.NFData DescribeTrustedAdvisorChecks where
  rnf :: DescribeTrustedAdvisorChecks -> ()
rnf DescribeTrustedAdvisorChecks' {Text
language :: Text
$sel:language:DescribeTrustedAdvisorChecks' :: DescribeTrustedAdvisorChecks -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
language

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

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

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

-- | Information about the Trusted Advisor checks returned by the
-- DescribeTrustedAdvisorChecks operation.
--
-- /See:/ 'newDescribeTrustedAdvisorChecksResponse' smart constructor.
data DescribeTrustedAdvisorChecksResponse = DescribeTrustedAdvisorChecksResponse'
  { -- | The response's http status code.
    DescribeTrustedAdvisorChecksResponse -> Int
httpStatus :: Prelude.Int,
    -- | Information about all available Trusted Advisor checks.
    DescribeTrustedAdvisorChecksResponse
-> [TrustedAdvisorCheckDescription]
checks :: [TrustedAdvisorCheckDescription]
  }
  deriving (DescribeTrustedAdvisorChecksResponse
-> DescribeTrustedAdvisorChecksResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeTrustedAdvisorChecksResponse
-> DescribeTrustedAdvisorChecksResponse -> Bool
$c/= :: DescribeTrustedAdvisorChecksResponse
-> DescribeTrustedAdvisorChecksResponse -> Bool
== :: DescribeTrustedAdvisorChecksResponse
-> DescribeTrustedAdvisorChecksResponse -> Bool
$c== :: DescribeTrustedAdvisorChecksResponse
-> DescribeTrustedAdvisorChecksResponse -> Bool
Prelude.Eq, ReadPrec [DescribeTrustedAdvisorChecksResponse]
ReadPrec DescribeTrustedAdvisorChecksResponse
Int -> ReadS DescribeTrustedAdvisorChecksResponse
ReadS [DescribeTrustedAdvisorChecksResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeTrustedAdvisorChecksResponse]
$creadListPrec :: ReadPrec [DescribeTrustedAdvisorChecksResponse]
readPrec :: ReadPrec DescribeTrustedAdvisorChecksResponse
$creadPrec :: ReadPrec DescribeTrustedAdvisorChecksResponse
readList :: ReadS [DescribeTrustedAdvisorChecksResponse]
$creadList :: ReadS [DescribeTrustedAdvisorChecksResponse]
readsPrec :: Int -> ReadS DescribeTrustedAdvisorChecksResponse
$creadsPrec :: Int -> ReadS DescribeTrustedAdvisorChecksResponse
Prelude.Read, Int -> DescribeTrustedAdvisorChecksResponse -> ShowS
[DescribeTrustedAdvisorChecksResponse] -> ShowS
DescribeTrustedAdvisorChecksResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeTrustedAdvisorChecksResponse] -> ShowS
$cshowList :: [DescribeTrustedAdvisorChecksResponse] -> ShowS
show :: DescribeTrustedAdvisorChecksResponse -> String
$cshow :: DescribeTrustedAdvisorChecksResponse -> String
showsPrec :: Int -> DescribeTrustedAdvisorChecksResponse -> ShowS
$cshowsPrec :: Int -> DescribeTrustedAdvisorChecksResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeTrustedAdvisorChecksResponse x
-> DescribeTrustedAdvisorChecksResponse
forall x.
DescribeTrustedAdvisorChecksResponse
-> Rep DescribeTrustedAdvisorChecksResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeTrustedAdvisorChecksResponse x
-> DescribeTrustedAdvisorChecksResponse
$cfrom :: forall x.
DescribeTrustedAdvisorChecksResponse
-> Rep DescribeTrustedAdvisorChecksResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeTrustedAdvisorChecksResponse' 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:
--
-- 'httpStatus', 'describeTrustedAdvisorChecksResponse_httpStatus' - The response's http status code.
--
-- 'checks', 'describeTrustedAdvisorChecksResponse_checks' - Information about all available Trusted Advisor checks.
newDescribeTrustedAdvisorChecksResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeTrustedAdvisorChecksResponse
newDescribeTrustedAdvisorChecksResponse :: Int -> DescribeTrustedAdvisorChecksResponse
newDescribeTrustedAdvisorChecksResponse Int
pHttpStatus_ =
  DescribeTrustedAdvisorChecksResponse'
    { $sel:httpStatus:DescribeTrustedAdvisorChecksResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:checks:DescribeTrustedAdvisorChecksResponse' :: [TrustedAdvisorCheckDescription]
checks = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | Information about all available Trusted Advisor checks.
describeTrustedAdvisorChecksResponse_checks :: Lens.Lens' DescribeTrustedAdvisorChecksResponse [TrustedAdvisorCheckDescription]
describeTrustedAdvisorChecksResponse_checks :: Lens'
  DescribeTrustedAdvisorChecksResponse
  [TrustedAdvisorCheckDescription]
describeTrustedAdvisorChecksResponse_checks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTrustedAdvisorChecksResponse' {[TrustedAdvisorCheckDescription]
checks :: [TrustedAdvisorCheckDescription]
$sel:checks:DescribeTrustedAdvisorChecksResponse' :: DescribeTrustedAdvisorChecksResponse
-> [TrustedAdvisorCheckDescription]
checks} -> [TrustedAdvisorCheckDescription]
checks) (\s :: DescribeTrustedAdvisorChecksResponse
s@DescribeTrustedAdvisorChecksResponse' {} [TrustedAdvisorCheckDescription]
a -> DescribeTrustedAdvisorChecksResponse
s {$sel:checks:DescribeTrustedAdvisorChecksResponse' :: [TrustedAdvisorCheckDescription]
checks = [TrustedAdvisorCheckDescription]
a} :: DescribeTrustedAdvisorChecksResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance
  Prelude.NFData
    DescribeTrustedAdvisorChecksResponse
  where
  rnf :: DescribeTrustedAdvisorChecksResponse -> ()
rnf DescribeTrustedAdvisorChecksResponse' {Int
[TrustedAdvisorCheckDescription]
checks :: [TrustedAdvisorCheckDescription]
httpStatus :: Int
$sel:checks:DescribeTrustedAdvisorChecksResponse' :: DescribeTrustedAdvisorChecksResponse
-> [TrustedAdvisorCheckDescription]
$sel:httpStatus:DescribeTrustedAdvisorChecksResponse' :: DescribeTrustedAdvisorChecksResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [TrustedAdvisorCheckDescription]
checks