{-# 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.ResilienceHub.ListAlarmRecommendations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the alarm recommendations for a AWS Resilience Hub application.
module Amazonka.ResilienceHub.ListAlarmRecommendations
  ( -- * Creating a Request
    ListAlarmRecommendations (..),
    newListAlarmRecommendations,

    -- * Request Lenses
    listAlarmRecommendations_maxResults,
    listAlarmRecommendations_nextToken,
    listAlarmRecommendations_assessmentArn,

    -- * Destructuring the Response
    ListAlarmRecommendationsResponse (..),
    newListAlarmRecommendationsResponse,

    -- * Response Lenses
    listAlarmRecommendationsResponse_nextToken,
    listAlarmRecommendationsResponse_httpStatus,
    listAlarmRecommendationsResponse_alarmRecommendations,
  )
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 Amazonka.ResilienceHub.Types
import qualified Amazonka.Response as Response

-- | /See:/ 'newListAlarmRecommendations' smart constructor.
data ListAlarmRecommendations = ListAlarmRecommendations'
  { -- | The maximum number of results to include in the response. If more
    -- results exist than the specified @MaxResults@ value, a token is included
    -- in the response so that the remaining results can be retrieved.
    ListAlarmRecommendations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Null, or the token from a previous call to get the next set of results.
    ListAlarmRecommendations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the assessment. The format for this
    -- ARN is:
    -- arn:@partition@:resiliencehub:@region@:@account@:app-assessment\/@app-id@.
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /AWS General Reference/.
    ListAlarmRecommendations -> Text
assessmentArn :: Prelude.Text
  }
  deriving (ListAlarmRecommendations -> ListAlarmRecommendations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAlarmRecommendations -> ListAlarmRecommendations -> Bool
$c/= :: ListAlarmRecommendations -> ListAlarmRecommendations -> Bool
== :: ListAlarmRecommendations -> ListAlarmRecommendations -> Bool
$c== :: ListAlarmRecommendations -> ListAlarmRecommendations -> Bool
Prelude.Eq, ReadPrec [ListAlarmRecommendations]
ReadPrec ListAlarmRecommendations
Int -> ReadS ListAlarmRecommendations
ReadS [ListAlarmRecommendations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAlarmRecommendations]
$creadListPrec :: ReadPrec [ListAlarmRecommendations]
readPrec :: ReadPrec ListAlarmRecommendations
$creadPrec :: ReadPrec ListAlarmRecommendations
readList :: ReadS [ListAlarmRecommendations]
$creadList :: ReadS [ListAlarmRecommendations]
readsPrec :: Int -> ReadS ListAlarmRecommendations
$creadsPrec :: Int -> ReadS ListAlarmRecommendations
Prelude.Read, Int -> ListAlarmRecommendations -> ShowS
[ListAlarmRecommendations] -> ShowS
ListAlarmRecommendations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAlarmRecommendations] -> ShowS
$cshowList :: [ListAlarmRecommendations] -> ShowS
show :: ListAlarmRecommendations -> String
$cshow :: ListAlarmRecommendations -> String
showsPrec :: Int -> ListAlarmRecommendations -> ShowS
$cshowsPrec :: Int -> ListAlarmRecommendations -> ShowS
Prelude.Show, forall x.
Rep ListAlarmRecommendations x -> ListAlarmRecommendations
forall x.
ListAlarmRecommendations -> Rep ListAlarmRecommendations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAlarmRecommendations x -> ListAlarmRecommendations
$cfrom :: forall x.
ListAlarmRecommendations -> Rep ListAlarmRecommendations x
Prelude.Generic)

-- |
-- Create a value of 'ListAlarmRecommendations' 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:
--
-- 'maxResults', 'listAlarmRecommendations_maxResults' - The maximum number of results to include in the response. If more
-- results exist than the specified @MaxResults@ value, a token is included
-- in the response so that the remaining results can be retrieved.
--
-- 'nextToken', 'listAlarmRecommendations_nextToken' - Null, or the token from a previous call to get the next set of results.
--
-- 'assessmentArn', 'listAlarmRecommendations_assessmentArn' - The Amazon Resource Name (ARN) of the assessment. The format for this
-- ARN is:
-- arn:@partition@:resiliencehub:@region@:@account@:app-assessment\/@app-id@.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /AWS General Reference/.
newListAlarmRecommendations ::
  -- | 'assessmentArn'
  Prelude.Text ->
  ListAlarmRecommendations
newListAlarmRecommendations :: Text -> ListAlarmRecommendations
newListAlarmRecommendations Text
pAssessmentArn_ =
  ListAlarmRecommendations'
    { $sel:maxResults:ListAlarmRecommendations' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAlarmRecommendations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:assessmentArn:ListAlarmRecommendations' :: Text
assessmentArn = Text
pAssessmentArn_
    }

-- | The maximum number of results to include in the response. If more
-- results exist than the specified @MaxResults@ value, a token is included
-- in the response so that the remaining results can be retrieved.
listAlarmRecommendations_maxResults :: Lens.Lens' ListAlarmRecommendations (Prelude.Maybe Prelude.Natural)
listAlarmRecommendations_maxResults :: Lens' ListAlarmRecommendations (Maybe Natural)
listAlarmRecommendations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAlarmRecommendations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListAlarmRecommendations' :: ListAlarmRecommendations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListAlarmRecommendations
s@ListAlarmRecommendations' {} Maybe Natural
a -> ListAlarmRecommendations
s {$sel:maxResults:ListAlarmRecommendations' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListAlarmRecommendations)

-- | Null, or the token from a previous call to get the next set of results.
listAlarmRecommendations_nextToken :: Lens.Lens' ListAlarmRecommendations (Prelude.Maybe Prelude.Text)
listAlarmRecommendations_nextToken :: Lens' ListAlarmRecommendations (Maybe Text)
listAlarmRecommendations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAlarmRecommendations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAlarmRecommendations' :: ListAlarmRecommendations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAlarmRecommendations
s@ListAlarmRecommendations' {} Maybe Text
a -> ListAlarmRecommendations
s {$sel:nextToken:ListAlarmRecommendations' :: Maybe Text
nextToken = Maybe Text
a} :: ListAlarmRecommendations)

-- | The Amazon Resource Name (ARN) of the assessment. The format for this
-- ARN is:
-- arn:@partition@:resiliencehub:@region@:@account@:app-assessment\/@app-id@.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /AWS General Reference/.
listAlarmRecommendations_assessmentArn :: Lens.Lens' ListAlarmRecommendations Prelude.Text
listAlarmRecommendations_assessmentArn :: Lens' ListAlarmRecommendations Text
listAlarmRecommendations_assessmentArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAlarmRecommendations' {Text
assessmentArn :: Text
$sel:assessmentArn:ListAlarmRecommendations' :: ListAlarmRecommendations -> Text
assessmentArn} -> Text
assessmentArn) (\s :: ListAlarmRecommendations
s@ListAlarmRecommendations' {} Text
a -> ListAlarmRecommendations
s {$sel:assessmentArn:ListAlarmRecommendations' :: Text
assessmentArn = Text
a} :: ListAlarmRecommendations)

instance Core.AWSRequest ListAlarmRecommendations where
  type
    AWSResponse ListAlarmRecommendations =
      ListAlarmRecommendationsResponse
  request :: (Service -> Service)
-> ListAlarmRecommendations -> Request ListAlarmRecommendations
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 ListAlarmRecommendations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListAlarmRecommendations)))
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 -> [AlarmRecommendation] -> ListAlarmRecommendationsResponse
ListAlarmRecommendationsResponse'
            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
"nextToken")
            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))
            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
"alarmRecommendations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable ListAlarmRecommendations where
  hashWithSalt :: Int -> ListAlarmRecommendations -> Int
hashWithSalt Int
_salt ListAlarmRecommendations' {Maybe Natural
Maybe Text
Text
assessmentArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:assessmentArn:ListAlarmRecommendations' :: ListAlarmRecommendations -> Text
$sel:nextToken:ListAlarmRecommendations' :: ListAlarmRecommendations -> Maybe Text
$sel:maxResults:ListAlarmRecommendations' :: ListAlarmRecommendations -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
assessmentArn

instance Prelude.NFData ListAlarmRecommendations where
  rnf :: ListAlarmRecommendations -> ()
rnf ListAlarmRecommendations' {Maybe Natural
Maybe Text
Text
assessmentArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:assessmentArn:ListAlarmRecommendations' :: ListAlarmRecommendations -> Text
$sel:nextToken:ListAlarmRecommendations' :: ListAlarmRecommendations -> Maybe Text
$sel:maxResults:ListAlarmRecommendations' :: ListAlarmRecommendations -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
assessmentArn

instance Data.ToHeaders ListAlarmRecommendations where
  toHeaders :: ListAlarmRecommendations -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListAlarmRecommendations where
  toJSON :: ListAlarmRecommendations -> Value
toJSON ListAlarmRecommendations' {Maybe Natural
Maybe Text
Text
assessmentArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:assessmentArn:ListAlarmRecommendations' :: ListAlarmRecommendations -> Text
$sel:nextToken:ListAlarmRecommendations' :: ListAlarmRecommendations -> Maybe Text
$sel:maxResults:ListAlarmRecommendations' :: ListAlarmRecommendations -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"maxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"nextToken" 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
nextToken,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"assessmentArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
assessmentArn)
          ]
      )

instance Data.ToPath ListAlarmRecommendations where
  toPath :: ListAlarmRecommendations -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/list-alarm-recommendations"

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

-- | /See:/ 'newListAlarmRecommendationsResponse' smart constructor.
data ListAlarmRecommendationsResponse = ListAlarmRecommendationsResponse'
  { -- | The token for the next set of results, or null if there are no more
    -- results.
    ListAlarmRecommendationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAlarmRecommendationsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The alarm recommendations for an AWS Resilience Hub application,
    -- returned as an object. This object includes application component names,
    -- descriptions, information about whether a recommendation has already
    -- been implemented or not, prerequisites, and more.
    ListAlarmRecommendationsResponse -> [AlarmRecommendation]
alarmRecommendations :: [AlarmRecommendation]
  }
  deriving (ListAlarmRecommendationsResponse
-> ListAlarmRecommendationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAlarmRecommendationsResponse
-> ListAlarmRecommendationsResponse -> Bool
$c/= :: ListAlarmRecommendationsResponse
-> ListAlarmRecommendationsResponse -> Bool
== :: ListAlarmRecommendationsResponse
-> ListAlarmRecommendationsResponse -> Bool
$c== :: ListAlarmRecommendationsResponse
-> ListAlarmRecommendationsResponse -> Bool
Prelude.Eq, ReadPrec [ListAlarmRecommendationsResponse]
ReadPrec ListAlarmRecommendationsResponse
Int -> ReadS ListAlarmRecommendationsResponse
ReadS [ListAlarmRecommendationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAlarmRecommendationsResponse]
$creadListPrec :: ReadPrec [ListAlarmRecommendationsResponse]
readPrec :: ReadPrec ListAlarmRecommendationsResponse
$creadPrec :: ReadPrec ListAlarmRecommendationsResponse
readList :: ReadS [ListAlarmRecommendationsResponse]
$creadList :: ReadS [ListAlarmRecommendationsResponse]
readsPrec :: Int -> ReadS ListAlarmRecommendationsResponse
$creadsPrec :: Int -> ReadS ListAlarmRecommendationsResponse
Prelude.Read, Int -> ListAlarmRecommendationsResponse -> ShowS
[ListAlarmRecommendationsResponse] -> ShowS
ListAlarmRecommendationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAlarmRecommendationsResponse] -> ShowS
$cshowList :: [ListAlarmRecommendationsResponse] -> ShowS
show :: ListAlarmRecommendationsResponse -> String
$cshow :: ListAlarmRecommendationsResponse -> String
showsPrec :: Int -> ListAlarmRecommendationsResponse -> ShowS
$cshowsPrec :: Int -> ListAlarmRecommendationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListAlarmRecommendationsResponse x
-> ListAlarmRecommendationsResponse
forall x.
ListAlarmRecommendationsResponse
-> Rep ListAlarmRecommendationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAlarmRecommendationsResponse x
-> ListAlarmRecommendationsResponse
$cfrom :: forall x.
ListAlarmRecommendationsResponse
-> Rep ListAlarmRecommendationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAlarmRecommendationsResponse' 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:
--
-- 'nextToken', 'listAlarmRecommendationsResponse_nextToken' - The token for the next set of results, or null if there are no more
-- results.
--
-- 'httpStatus', 'listAlarmRecommendationsResponse_httpStatus' - The response's http status code.
--
-- 'alarmRecommendations', 'listAlarmRecommendationsResponse_alarmRecommendations' - The alarm recommendations for an AWS Resilience Hub application,
-- returned as an object. This object includes application component names,
-- descriptions, information about whether a recommendation has already
-- been implemented or not, prerequisites, and more.
newListAlarmRecommendationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAlarmRecommendationsResponse
newListAlarmRecommendationsResponse :: Int -> ListAlarmRecommendationsResponse
newListAlarmRecommendationsResponse Int
pHttpStatus_ =
  ListAlarmRecommendationsResponse'
    { $sel:nextToken:ListAlarmRecommendationsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAlarmRecommendationsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:alarmRecommendations:ListAlarmRecommendationsResponse' :: [AlarmRecommendation]
alarmRecommendations = forall a. Monoid a => a
Prelude.mempty
    }

-- | The token for the next set of results, or null if there are no more
-- results.
listAlarmRecommendationsResponse_nextToken :: Lens.Lens' ListAlarmRecommendationsResponse (Prelude.Maybe Prelude.Text)
listAlarmRecommendationsResponse_nextToken :: Lens' ListAlarmRecommendationsResponse (Maybe Text)
listAlarmRecommendationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAlarmRecommendationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAlarmRecommendationsResponse' :: ListAlarmRecommendationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAlarmRecommendationsResponse
s@ListAlarmRecommendationsResponse' {} Maybe Text
a -> ListAlarmRecommendationsResponse
s {$sel:nextToken:ListAlarmRecommendationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAlarmRecommendationsResponse)

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

-- | The alarm recommendations for an AWS Resilience Hub application,
-- returned as an object. This object includes application component names,
-- descriptions, information about whether a recommendation has already
-- been implemented or not, prerequisites, and more.
listAlarmRecommendationsResponse_alarmRecommendations :: Lens.Lens' ListAlarmRecommendationsResponse [AlarmRecommendation]
listAlarmRecommendationsResponse_alarmRecommendations :: Lens' ListAlarmRecommendationsResponse [AlarmRecommendation]
listAlarmRecommendationsResponse_alarmRecommendations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAlarmRecommendationsResponse' {[AlarmRecommendation]
alarmRecommendations :: [AlarmRecommendation]
$sel:alarmRecommendations:ListAlarmRecommendationsResponse' :: ListAlarmRecommendationsResponse -> [AlarmRecommendation]
alarmRecommendations} -> [AlarmRecommendation]
alarmRecommendations) (\s :: ListAlarmRecommendationsResponse
s@ListAlarmRecommendationsResponse' {} [AlarmRecommendation]
a -> ListAlarmRecommendationsResponse
s {$sel:alarmRecommendations:ListAlarmRecommendationsResponse' :: [AlarmRecommendation]
alarmRecommendations = [AlarmRecommendation]
a} :: ListAlarmRecommendationsResponse) 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
    ListAlarmRecommendationsResponse
  where
  rnf :: ListAlarmRecommendationsResponse -> ()
rnf ListAlarmRecommendationsResponse' {Int
[AlarmRecommendation]
Maybe Text
alarmRecommendations :: [AlarmRecommendation]
httpStatus :: Int
nextToken :: Maybe Text
$sel:alarmRecommendations:ListAlarmRecommendationsResponse' :: ListAlarmRecommendationsResponse -> [AlarmRecommendation]
$sel:httpStatus:ListAlarmRecommendationsResponse' :: ListAlarmRecommendationsResponse -> Int
$sel:nextToken:ListAlarmRecommendationsResponse' :: ListAlarmRecommendationsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 [AlarmRecommendation]
alarmRecommendations