{-# 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.ApplicationInsights.DescribeComponentConfigurationRecommendation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the recommended monitoring configuration of the component.
module Amazonka.ApplicationInsights.DescribeComponentConfigurationRecommendation
  ( -- * Creating a Request
    DescribeComponentConfigurationRecommendation (..),
    newDescribeComponentConfigurationRecommendation,

    -- * Request Lenses
    describeComponentConfigurationRecommendation_resourceGroupName,
    describeComponentConfigurationRecommendation_componentName,
    describeComponentConfigurationRecommendation_tier,

    -- * Destructuring the Response
    DescribeComponentConfigurationRecommendationResponse (..),
    newDescribeComponentConfigurationRecommendationResponse,

    -- * Response Lenses
    describeComponentConfigurationRecommendationResponse_componentConfiguration,
    describeComponentConfigurationRecommendationResponse_httpStatus,
  )
where

import Amazonka.ApplicationInsights.Types
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

-- | /See:/ 'newDescribeComponentConfigurationRecommendation' smart constructor.
data DescribeComponentConfigurationRecommendation = DescribeComponentConfigurationRecommendation'
  { -- | The name of the resource group.
    DescribeComponentConfigurationRecommendation -> Text
resourceGroupName :: Prelude.Text,
    -- | The name of the component.
    DescribeComponentConfigurationRecommendation -> Text
componentName :: Prelude.Text,
    -- | The tier of the application component.
    DescribeComponentConfigurationRecommendation -> Tier
tier :: Tier
  }
  deriving (DescribeComponentConfigurationRecommendation
-> DescribeComponentConfigurationRecommendation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeComponentConfigurationRecommendation
-> DescribeComponentConfigurationRecommendation -> Bool
$c/= :: DescribeComponentConfigurationRecommendation
-> DescribeComponentConfigurationRecommendation -> Bool
== :: DescribeComponentConfigurationRecommendation
-> DescribeComponentConfigurationRecommendation -> Bool
$c== :: DescribeComponentConfigurationRecommendation
-> DescribeComponentConfigurationRecommendation -> Bool
Prelude.Eq, ReadPrec [DescribeComponentConfigurationRecommendation]
ReadPrec DescribeComponentConfigurationRecommendation
Int -> ReadS DescribeComponentConfigurationRecommendation
ReadS [DescribeComponentConfigurationRecommendation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeComponentConfigurationRecommendation]
$creadListPrec :: ReadPrec [DescribeComponentConfigurationRecommendation]
readPrec :: ReadPrec DescribeComponentConfigurationRecommendation
$creadPrec :: ReadPrec DescribeComponentConfigurationRecommendation
readList :: ReadS [DescribeComponentConfigurationRecommendation]
$creadList :: ReadS [DescribeComponentConfigurationRecommendation]
readsPrec :: Int -> ReadS DescribeComponentConfigurationRecommendation
$creadsPrec :: Int -> ReadS DescribeComponentConfigurationRecommendation
Prelude.Read, Int -> DescribeComponentConfigurationRecommendation -> ShowS
[DescribeComponentConfigurationRecommendation] -> ShowS
DescribeComponentConfigurationRecommendation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeComponentConfigurationRecommendation] -> ShowS
$cshowList :: [DescribeComponentConfigurationRecommendation] -> ShowS
show :: DescribeComponentConfigurationRecommendation -> String
$cshow :: DescribeComponentConfigurationRecommendation -> String
showsPrec :: Int -> DescribeComponentConfigurationRecommendation -> ShowS
$cshowsPrec :: Int -> DescribeComponentConfigurationRecommendation -> ShowS
Prelude.Show, forall x.
Rep DescribeComponentConfigurationRecommendation x
-> DescribeComponentConfigurationRecommendation
forall x.
DescribeComponentConfigurationRecommendation
-> Rep DescribeComponentConfigurationRecommendation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeComponentConfigurationRecommendation x
-> DescribeComponentConfigurationRecommendation
$cfrom :: forall x.
DescribeComponentConfigurationRecommendation
-> Rep DescribeComponentConfigurationRecommendation x
Prelude.Generic)

-- |
-- Create a value of 'DescribeComponentConfigurationRecommendation' 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:
--
-- 'resourceGroupName', 'describeComponentConfigurationRecommendation_resourceGroupName' - The name of the resource group.
--
-- 'componentName', 'describeComponentConfigurationRecommendation_componentName' - The name of the component.
--
-- 'tier', 'describeComponentConfigurationRecommendation_tier' - The tier of the application component.
newDescribeComponentConfigurationRecommendation ::
  -- | 'resourceGroupName'
  Prelude.Text ->
  -- | 'componentName'
  Prelude.Text ->
  -- | 'tier'
  Tier ->
  DescribeComponentConfigurationRecommendation
newDescribeComponentConfigurationRecommendation :: Text
-> Text -> Tier -> DescribeComponentConfigurationRecommendation
newDescribeComponentConfigurationRecommendation
  Text
pResourceGroupName_
  Text
pComponentName_
  Tier
pTier_ =
    DescribeComponentConfigurationRecommendation'
      { $sel:resourceGroupName:DescribeComponentConfigurationRecommendation' :: Text
resourceGroupName =
          Text
pResourceGroupName_,
        $sel:componentName:DescribeComponentConfigurationRecommendation' :: Text
componentName =
          Text
pComponentName_,
        $sel:tier:DescribeComponentConfigurationRecommendation' :: Tier
tier = Tier
pTier_
      }

-- | The name of the resource group.
describeComponentConfigurationRecommendation_resourceGroupName :: Lens.Lens' DescribeComponentConfigurationRecommendation Prelude.Text
describeComponentConfigurationRecommendation_resourceGroupName :: Lens' DescribeComponentConfigurationRecommendation Text
describeComponentConfigurationRecommendation_resourceGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComponentConfigurationRecommendation' {Text
resourceGroupName :: Text
$sel:resourceGroupName:DescribeComponentConfigurationRecommendation' :: DescribeComponentConfigurationRecommendation -> Text
resourceGroupName} -> Text
resourceGroupName) (\s :: DescribeComponentConfigurationRecommendation
s@DescribeComponentConfigurationRecommendation' {} Text
a -> DescribeComponentConfigurationRecommendation
s {$sel:resourceGroupName:DescribeComponentConfigurationRecommendation' :: Text
resourceGroupName = Text
a} :: DescribeComponentConfigurationRecommendation)

-- | The name of the component.
describeComponentConfigurationRecommendation_componentName :: Lens.Lens' DescribeComponentConfigurationRecommendation Prelude.Text
describeComponentConfigurationRecommendation_componentName :: Lens' DescribeComponentConfigurationRecommendation Text
describeComponentConfigurationRecommendation_componentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComponentConfigurationRecommendation' {Text
componentName :: Text
$sel:componentName:DescribeComponentConfigurationRecommendation' :: DescribeComponentConfigurationRecommendation -> Text
componentName} -> Text
componentName) (\s :: DescribeComponentConfigurationRecommendation
s@DescribeComponentConfigurationRecommendation' {} Text
a -> DescribeComponentConfigurationRecommendation
s {$sel:componentName:DescribeComponentConfigurationRecommendation' :: Text
componentName = Text
a} :: DescribeComponentConfigurationRecommendation)

-- | The tier of the application component.
describeComponentConfigurationRecommendation_tier :: Lens.Lens' DescribeComponentConfigurationRecommendation Tier
describeComponentConfigurationRecommendation_tier :: Lens' DescribeComponentConfigurationRecommendation Tier
describeComponentConfigurationRecommendation_tier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComponentConfigurationRecommendation' {Tier
tier :: Tier
$sel:tier:DescribeComponentConfigurationRecommendation' :: DescribeComponentConfigurationRecommendation -> Tier
tier} -> Tier
tier) (\s :: DescribeComponentConfigurationRecommendation
s@DescribeComponentConfigurationRecommendation' {} Tier
a -> DescribeComponentConfigurationRecommendation
s {$sel:tier:DescribeComponentConfigurationRecommendation' :: Tier
tier = Tier
a} :: DescribeComponentConfigurationRecommendation)

instance
  Core.AWSRequest
    DescribeComponentConfigurationRecommendation
  where
  type
    AWSResponse
      DescribeComponentConfigurationRecommendation =
      DescribeComponentConfigurationRecommendationResponse
  request :: (Service -> Service)
-> DescribeComponentConfigurationRecommendation
-> Request DescribeComponentConfigurationRecommendation
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 DescribeComponentConfigurationRecommendation
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse DescribeComponentConfigurationRecommendation)))
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
-> Int -> DescribeComponentConfigurationRecommendationResponse
DescribeComponentConfigurationRecommendationResponse'
            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
"ComponentConfiguration")
            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
    DescribeComponentConfigurationRecommendation
  where
  hashWithSalt :: Int -> DescribeComponentConfigurationRecommendation -> Int
hashWithSalt
    Int
_salt
    DescribeComponentConfigurationRecommendation' {Text
Tier
tier :: Tier
componentName :: Text
resourceGroupName :: Text
$sel:tier:DescribeComponentConfigurationRecommendation' :: DescribeComponentConfigurationRecommendation -> Tier
$sel:componentName:DescribeComponentConfigurationRecommendation' :: DescribeComponentConfigurationRecommendation -> Text
$sel:resourceGroupName:DescribeComponentConfigurationRecommendation' :: DescribeComponentConfigurationRecommendation -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceGroupName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
componentName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Tier
tier

instance
  Prelude.NFData
    DescribeComponentConfigurationRecommendation
  where
  rnf :: DescribeComponentConfigurationRecommendation -> ()
rnf DescribeComponentConfigurationRecommendation' {Text
Tier
tier :: Tier
componentName :: Text
resourceGroupName :: Text
$sel:tier:DescribeComponentConfigurationRecommendation' :: DescribeComponentConfigurationRecommendation -> Tier
$sel:componentName:DescribeComponentConfigurationRecommendation' :: DescribeComponentConfigurationRecommendation -> Text
$sel:resourceGroupName:DescribeComponentConfigurationRecommendation' :: DescribeComponentConfigurationRecommendation -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
resourceGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
componentName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Tier
tier

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

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

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

-- | /See:/ 'newDescribeComponentConfigurationRecommendationResponse' smart constructor.
data DescribeComponentConfigurationRecommendationResponse = DescribeComponentConfigurationRecommendationResponse'
  { -- | The recommended configuration settings of the component. The value is
    -- the escaped JSON of the configuration.
    DescribeComponentConfigurationRecommendationResponse -> Maybe Text
componentConfiguration :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeComponentConfigurationRecommendationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeComponentConfigurationRecommendationResponse
-> DescribeComponentConfigurationRecommendationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeComponentConfigurationRecommendationResponse
-> DescribeComponentConfigurationRecommendationResponse -> Bool
$c/= :: DescribeComponentConfigurationRecommendationResponse
-> DescribeComponentConfigurationRecommendationResponse -> Bool
== :: DescribeComponentConfigurationRecommendationResponse
-> DescribeComponentConfigurationRecommendationResponse -> Bool
$c== :: DescribeComponentConfigurationRecommendationResponse
-> DescribeComponentConfigurationRecommendationResponse -> Bool
Prelude.Eq, ReadPrec [DescribeComponentConfigurationRecommendationResponse]
ReadPrec DescribeComponentConfigurationRecommendationResponse
Int -> ReadS DescribeComponentConfigurationRecommendationResponse
ReadS [DescribeComponentConfigurationRecommendationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeComponentConfigurationRecommendationResponse]
$creadListPrec :: ReadPrec [DescribeComponentConfigurationRecommendationResponse]
readPrec :: ReadPrec DescribeComponentConfigurationRecommendationResponse
$creadPrec :: ReadPrec DescribeComponentConfigurationRecommendationResponse
readList :: ReadS [DescribeComponentConfigurationRecommendationResponse]
$creadList :: ReadS [DescribeComponentConfigurationRecommendationResponse]
readsPrec :: Int -> ReadS DescribeComponentConfigurationRecommendationResponse
$creadsPrec :: Int -> ReadS DescribeComponentConfigurationRecommendationResponse
Prelude.Read, Int
-> DescribeComponentConfigurationRecommendationResponse -> ShowS
[DescribeComponentConfigurationRecommendationResponse] -> ShowS
DescribeComponentConfigurationRecommendationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeComponentConfigurationRecommendationResponse] -> ShowS
$cshowList :: [DescribeComponentConfigurationRecommendationResponse] -> ShowS
show :: DescribeComponentConfigurationRecommendationResponse -> String
$cshow :: DescribeComponentConfigurationRecommendationResponse -> String
showsPrec :: Int
-> DescribeComponentConfigurationRecommendationResponse -> ShowS
$cshowsPrec :: Int
-> DescribeComponentConfigurationRecommendationResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeComponentConfigurationRecommendationResponse x
-> DescribeComponentConfigurationRecommendationResponse
forall x.
DescribeComponentConfigurationRecommendationResponse
-> Rep DescribeComponentConfigurationRecommendationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeComponentConfigurationRecommendationResponse x
-> DescribeComponentConfigurationRecommendationResponse
$cfrom :: forall x.
DescribeComponentConfigurationRecommendationResponse
-> Rep DescribeComponentConfigurationRecommendationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeComponentConfigurationRecommendationResponse' 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:
--
-- 'componentConfiguration', 'describeComponentConfigurationRecommendationResponse_componentConfiguration' - The recommended configuration settings of the component. The value is
-- the escaped JSON of the configuration.
--
-- 'httpStatus', 'describeComponentConfigurationRecommendationResponse_httpStatus' - The response's http status code.
newDescribeComponentConfigurationRecommendationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeComponentConfigurationRecommendationResponse
newDescribeComponentConfigurationRecommendationResponse :: Int -> DescribeComponentConfigurationRecommendationResponse
newDescribeComponentConfigurationRecommendationResponse
  Int
pHttpStatus_ =
    DescribeComponentConfigurationRecommendationResponse'
      { $sel:componentConfiguration:DescribeComponentConfigurationRecommendationResponse' :: Maybe Text
componentConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeComponentConfigurationRecommendationResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | The recommended configuration settings of the component. The value is
-- the escaped JSON of the configuration.
describeComponentConfigurationRecommendationResponse_componentConfiguration :: Lens.Lens' DescribeComponentConfigurationRecommendationResponse (Prelude.Maybe Prelude.Text)
describeComponentConfigurationRecommendationResponse_componentConfiguration :: Lens'
  DescribeComponentConfigurationRecommendationResponse (Maybe Text)
describeComponentConfigurationRecommendationResponse_componentConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComponentConfigurationRecommendationResponse' {Maybe Text
componentConfiguration :: Maybe Text
$sel:componentConfiguration:DescribeComponentConfigurationRecommendationResponse' :: DescribeComponentConfigurationRecommendationResponse -> Maybe Text
componentConfiguration} -> Maybe Text
componentConfiguration) (\s :: DescribeComponentConfigurationRecommendationResponse
s@DescribeComponentConfigurationRecommendationResponse' {} Maybe Text
a -> DescribeComponentConfigurationRecommendationResponse
s {$sel:componentConfiguration:DescribeComponentConfigurationRecommendationResponse' :: Maybe Text
componentConfiguration = Maybe Text
a} :: DescribeComponentConfigurationRecommendationResponse)

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

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