{-# 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.Route53RecoveryReadiness.GetArchitectureRecommendations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets recommendations about architecture designs for improving resiliency
-- for an application, based on a recovery group.
module Amazonka.Route53RecoveryReadiness.GetArchitectureRecommendations
  ( -- * Creating a Request
    GetArchitectureRecommendations (..),
    newGetArchitectureRecommendations,

    -- * Request Lenses
    getArchitectureRecommendations_maxResults,
    getArchitectureRecommendations_nextToken,
    getArchitectureRecommendations_recoveryGroupName,

    -- * Destructuring the Response
    GetArchitectureRecommendationsResponse (..),
    newGetArchitectureRecommendationsResponse,

    -- * Response Lenses
    getArchitectureRecommendationsResponse_lastAuditTimestamp,
    getArchitectureRecommendationsResponse_nextToken,
    getArchitectureRecommendationsResponse_recommendations,
    getArchitectureRecommendationsResponse_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.Route53RecoveryReadiness.Types

-- | /See:/ 'newGetArchitectureRecommendations' smart constructor.
data GetArchitectureRecommendations = GetArchitectureRecommendations'
  { -- | The number of objects that you want to return with this call.
    GetArchitectureRecommendations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token that identifies which batch of results you want to see.
    GetArchitectureRecommendations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of a recovery group.
    GetArchitectureRecommendations -> Text
recoveryGroupName :: Prelude.Text
  }
  deriving (GetArchitectureRecommendations
-> GetArchitectureRecommendations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetArchitectureRecommendations
-> GetArchitectureRecommendations -> Bool
$c/= :: GetArchitectureRecommendations
-> GetArchitectureRecommendations -> Bool
== :: GetArchitectureRecommendations
-> GetArchitectureRecommendations -> Bool
$c== :: GetArchitectureRecommendations
-> GetArchitectureRecommendations -> Bool
Prelude.Eq, ReadPrec [GetArchitectureRecommendations]
ReadPrec GetArchitectureRecommendations
Int -> ReadS GetArchitectureRecommendations
ReadS [GetArchitectureRecommendations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetArchitectureRecommendations]
$creadListPrec :: ReadPrec [GetArchitectureRecommendations]
readPrec :: ReadPrec GetArchitectureRecommendations
$creadPrec :: ReadPrec GetArchitectureRecommendations
readList :: ReadS [GetArchitectureRecommendations]
$creadList :: ReadS [GetArchitectureRecommendations]
readsPrec :: Int -> ReadS GetArchitectureRecommendations
$creadsPrec :: Int -> ReadS GetArchitectureRecommendations
Prelude.Read, Int -> GetArchitectureRecommendations -> ShowS
[GetArchitectureRecommendations] -> ShowS
GetArchitectureRecommendations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetArchitectureRecommendations] -> ShowS
$cshowList :: [GetArchitectureRecommendations] -> ShowS
show :: GetArchitectureRecommendations -> String
$cshow :: GetArchitectureRecommendations -> String
showsPrec :: Int -> GetArchitectureRecommendations -> ShowS
$cshowsPrec :: Int -> GetArchitectureRecommendations -> ShowS
Prelude.Show, forall x.
Rep GetArchitectureRecommendations x
-> GetArchitectureRecommendations
forall x.
GetArchitectureRecommendations
-> Rep GetArchitectureRecommendations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetArchitectureRecommendations x
-> GetArchitectureRecommendations
$cfrom :: forall x.
GetArchitectureRecommendations
-> Rep GetArchitectureRecommendations x
Prelude.Generic)

-- |
-- Create a value of 'GetArchitectureRecommendations' 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', 'getArchitectureRecommendations_maxResults' - The number of objects that you want to return with this call.
--
-- 'nextToken', 'getArchitectureRecommendations_nextToken' - The token that identifies which batch of results you want to see.
--
-- 'recoveryGroupName', 'getArchitectureRecommendations_recoveryGroupName' - The name of a recovery group.
newGetArchitectureRecommendations ::
  -- | 'recoveryGroupName'
  Prelude.Text ->
  GetArchitectureRecommendations
newGetArchitectureRecommendations :: Text -> GetArchitectureRecommendations
newGetArchitectureRecommendations Text
pRecoveryGroupName_ =
  GetArchitectureRecommendations'
    { $sel:maxResults:GetArchitectureRecommendations' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetArchitectureRecommendations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:recoveryGroupName:GetArchitectureRecommendations' :: Text
recoveryGroupName = Text
pRecoveryGroupName_
    }

-- | The number of objects that you want to return with this call.
getArchitectureRecommendations_maxResults :: Lens.Lens' GetArchitectureRecommendations (Prelude.Maybe Prelude.Natural)
getArchitectureRecommendations_maxResults :: Lens' GetArchitectureRecommendations (Maybe Natural)
getArchitectureRecommendations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetArchitectureRecommendations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetArchitectureRecommendations
s@GetArchitectureRecommendations' {} Maybe Natural
a -> GetArchitectureRecommendations
s {$sel:maxResults:GetArchitectureRecommendations' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetArchitectureRecommendations)

-- | The token that identifies which batch of results you want to see.
getArchitectureRecommendations_nextToken :: Lens.Lens' GetArchitectureRecommendations (Prelude.Maybe Prelude.Text)
getArchitectureRecommendations_nextToken :: Lens' GetArchitectureRecommendations (Maybe Text)
getArchitectureRecommendations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetArchitectureRecommendations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetArchitectureRecommendations
s@GetArchitectureRecommendations' {} Maybe Text
a -> GetArchitectureRecommendations
s {$sel:nextToken:GetArchitectureRecommendations' :: Maybe Text
nextToken = Maybe Text
a} :: GetArchitectureRecommendations)

-- | The name of a recovery group.
getArchitectureRecommendations_recoveryGroupName :: Lens.Lens' GetArchitectureRecommendations Prelude.Text
getArchitectureRecommendations_recoveryGroupName :: Lens' GetArchitectureRecommendations Text
getArchitectureRecommendations_recoveryGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetArchitectureRecommendations' {Text
recoveryGroupName :: Text
$sel:recoveryGroupName:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Text
recoveryGroupName} -> Text
recoveryGroupName) (\s :: GetArchitectureRecommendations
s@GetArchitectureRecommendations' {} Text
a -> GetArchitectureRecommendations
s {$sel:recoveryGroupName:GetArchitectureRecommendations' :: Text
recoveryGroupName = Text
a} :: GetArchitectureRecommendations)

instance
  Core.AWSRequest
    GetArchitectureRecommendations
  where
  type
    AWSResponse GetArchitectureRecommendations =
      GetArchitectureRecommendationsResponse
  request :: (Service -> Service)
-> GetArchitectureRecommendations
-> Request GetArchitectureRecommendations
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetArchitectureRecommendations
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetArchitectureRecommendations)))
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 ISO8601
-> Maybe Text
-> Maybe [Recommendation]
-> Int
-> GetArchitectureRecommendationsResponse
GetArchitectureRecommendationsResponse'
            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
"lastAuditTimestamp")
            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
"nextToken")
            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
"recommendations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
    GetArchitectureRecommendations
  where
  hashWithSalt :: Int -> GetArchitectureRecommendations -> Int
hashWithSalt
    Int
_salt
    GetArchitectureRecommendations' {Maybe Natural
Maybe Text
Text
recoveryGroupName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:recoveryGroupName:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Text
$sel:nextToken:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Maybe Text
$sel:maxResults:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> 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
recoveryGroupName

instance
  Prelude.NFData
    GetArchitectureRecommendations
  where
  rnf :: GetArchitectureRecommendations -> ()
rnf GetArchitectureRecommendations' {Maybe Natural
Maybe Text
Text
recoveryGroupName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:recoveryGroupName:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Text
$sel:nextToken:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Maybe Text
$sel:maxResults:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> 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
recoveryGroupName

instance
  Data.ToHeaders
    GetArchitectureRecommendations
  where
  toHeaders :: GetArchitectureRecommendations -> 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.ToPath GetArchitectureRecommendations where
  toPath :: GetArchitectureRecommendations -> ByteString
toPath GetArchitectureRecommendations' {Maybe Natural
Maybe Text
Text
recoveryGroupName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:recoveryGroupName:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Text
$sel:nextToken:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Maybe Text
$sel:maxResults:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/recoverygroups/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
recoveryGroupName,
        ByteString
"/architectureRecommendations"
      ]

instance Data.ToQuery GetArchitectureRecommendations where
  toQuery :: GetArchitectureRecommendations -> QueryString
toQuery GetArchitectureRecommendations' {Maybe Natural
Maybe Text
Text
recoveryGroupName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:recoveryGroupName:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Text
$sel:nextToken:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Maybe Text
$sel:maxResults:GetArchitectureRecommendations' :: GetArchitectureRecommendations -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newGetArchitectureRecommendationsResponse' smart constructor.
data GetArchitectureRecommendationsResponse = GetArchitectureRecommendationsResponse'
  { -- | The time that a recovery group was last assessed for recommendations, in
    -- UTC ISO-8601 format.
    GetArchitectureRecommendationsResponse -> Maybe ISO8601
lastAuditTimestamp :: Prelude.Maybe Data.ISO8601,
    -- | The token that identifies which batch of results you want to see.
    GetArchitectureRecommendationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of the recommendations for the customer\'s application.
    GetArchitectureRecommendationsResponse -> Maybe [Recommendation]
recommendations :: Prelude.Maybe [Recommendation],
    -- | The response's http status code.
    GetArchitectureRecommendationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetArchitectureRecommendationsResponse
-> GetArchitectureRecommendationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetArchitectureRecommendationsResponse
-> GetArchitectureRecommendationsResponse -> Bool
$c/= :: GetArchitectureRecommendationsResponse
-> GetArchitectureRecommendationsResponse -> Bool
== :: GetArchitectureRecommendationsResponse
-> GetArchitectureRecommendationsResponse -> Bool
$c== :: GetArchitectureRecommendationsResponse
-> GetArchitectureRecommendationsResponse -> Bool
Prelude.Eq, ReadPrec [GetArchitectureRecommendationsResponse]
ReadPrec GetArchitectureRecommendationsResponse
Int -> ReadS GetArchitectureRecommendationsResponse
ReadS [GetArchitectureRecommendationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetArchitectureRecommendationsResponse]
$creadListPrec :: ReadPrec [GetArchitectureRecommendationsResponse]
readPrec :: ReadPrec GetArchitectureRecommendationsResponse
$creadPrec :: ReadPrec GetArchitectureRecommendationsResponse
readList :: ReadS [GetArchitectureRecommendationsResponse]
$creadList :: ReadS [GetArchitectureRecommendationsResponse]
readsPrec :: Int -> ReadS GetArchitectureRecommendationsResponse
$creadsPrec :: Int -> ReadS GetArchitectureRecommendationsResponse
Prelude.Read, Int -> GetArchitectureRecommendationsResponse -> ShowS
[GetArchitectureRecommendationsResponse] -> ShowS
GetArchitectureRecommendationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetArchitectureRecommendationsResponse] -> ShowS
$cshowList :: [GetArchitectureRecommendationsResponse] -> ShowS
show :: GetArchitectureRecommendationsResponse -> String
$cshow :: GetArchitectureRecommendationsResponse -> String
showsPrec :: Int -> GetArchitectureRecommendationsResponse -> ShowS
$cshowsPrec :: Int -> GetArchitectureRecommendationsResponse -> ShowS
Prelude.Show, forall x.
Rep GetArchitectureRecommendationsResponse x
-> GetArchitectureRecommendationsResponse
forall x.
GetArchitectureRecommendationsResponse
-> Rep GetArchitectureRecommendationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetArchitectureRecommendationsResponse x
-> GetArchitectureRecommendationsResponse
$cfrom :: forall x.
GetArchitectureRecommendationsResponse
-> Rep GetArchitectureRecommendationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetArchitectureRecommendationsResponse' 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:
--
-- 'lastAuditTimestamp', 'getArchitectureRecommendationsResponse_lastAuditTimestamp' - The time that a recovery group was last assessed for recommendations, in
-- UTC ISO-8601 format.
--
-- 'nextToken', 'getArchitectureRecommendationsResponse_nextToken' - The token that identifies which batch of results you want to see.
--
-- 'recommendations', 'getArchitectureRecommendationsResponse_recommendations' - A list of the recommendations for the customer\'s application.
--
-- 'httpStatus', 'getArchitectureRecommendationsResponse_httpStatus' - The response's http status code.
newGetArchitectureRecommendationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetArchitectureRecommendationsResponse
newGetArchitectureRecommendationsResponse :: Int -> GetArchitectureRecommendationsResponse
newGetArchitectureRecommendationsResponse
  Int
pHttpStatus_ =
    GetArchitectureRecommendationsResponse'
      { $sel:lastAuditTimestamp:GetArchitectureRecommendationsResponse' :: Maybe ISO8601
lastAuditTimestamp =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetArchitectureRecommendationsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:recommendations:GetArchitectureRecommendationsResponse' :: Maybe [Recommendation]
recommendations = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetArchitectureRecommendationsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The time that a recovery group was last assessed for recommendations, in
-- UTC ISO-8601 format.
getArchitectureRecommendationsResponse_lastAuditTimestamp :: Lens.Lens' GetArchitectureRecommendationsResponse (Prelude.Maybe Prelude.UTCTime)
getArchitectureRecommendationsResponse_lastAuditTimestamp :: Lens' GetArchitectureRecommendationsResponse (Maybe UTCTime)
getArchitectureRecommendationsResponse_lastAuditTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetArchitectureRecommendationsResponse' {Maybe ISO8601
lastAuditTimestamp :: Maybe ISO8601
$sel:lastAuditTimestamp:GetArchitectureRecommendationsResponse' :: GetArchitectureRecommendationsResponse -> Maybe ISO8601
lastAuditTimestamp} -> Maybe ISO8601
lastAuditTimestamp) (\s :: GetArchitectureRecommendationsResponse
s@GetArchitectureRecommendationsResponse' {} Maybe ISO8601
a -> GetArchitectureRecommendationsResponse
s {$sel:lastAuditTimestamp:GetArchitectureRecommendationsResponse' :: Maybe ISO8601
lastAuditTimestamp = Maybe ISO8601
a} :: GetArchitectureRecommendationsResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The token that identifies which batch of results you want to see.
getArchitectureRecommendationsResponse_nextToken :: Lens.Lens' GetArchitectureRecommendationsResponse (Prelude.Maybe Prelude.Text)
getArchitectureRecommendationsResponse_nextToken :: Lens' GetArchitectureRecommendationsResponse (Maybe Text)
getArchitectureRecommendationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetArchitectureRecommendationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetArchitectureRecommendationsResponse' :: GetArchitectureRecommendationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetArchitectureRecommendationsResponse
s@GetArchitectureRecommendationsResponse' {} Maybe Text
a -> GetArchitectureRecommendationsResponse
s {$sel:nextToken:GetArchitectureRecommendationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetArchitectureRecommendationsResponse)

-- | A list of the recommendations for the customer\'s application.
getArchitectureRecommendationsResponse_recommendations :: Lens.Lens' GetArchitectureRecommendationsResponse (Prelude.Maybe [Recommendation])
getArchitectureRecommendationsResponse_recommendations :: Lens'
  GetArchitectureRecommendationsResponse (Maybe [Recommendation])
getArchitectureRecommendationsResponse_recommendations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetArchitectureRecommendationsResponse' {Maybe [Recommendation]
recommendations :: Maybe [Recommendation]
$sel:recommendations:GetArchitectureRecommendationsResponse' :: GetArchitectureRecommendationsResponse -> Maybe [Recommendation]
recommendations} -> Maybe [Recommendation]
recommendations) (\s :: GetArchitectureRecommendationsResponse
s@GetArchitectureRecommendationsResponse' {} Maybe [Recommendation]
a -> GetArchitectureRecommendationsResponse
s {$sel:recommendations:GetArchitectureRecommendationsResponse' :: Maybe [Recommendation]
recommendations = Maybe [Recommendation]
a} :: GetArchitectureRecommendationsResponse) 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 response's http status code.
getArchitectureRecommendationsResponse_httpStatus :: Lens.Lens' GetArchitectureRecommendationsResponse Prelude.Int
getArchitectureRecommendationsResponse_httpStatus :: Lens' GetArchitectureRecommendationsResponse Int
getArchitectureRecommendationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetArchitectureRecommendationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetArchitectureRecommendationsResponse' :: GetArchitectureRecommendationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetArchitectureRecommendationsResponse
s@GetArchitectureRecommendationsResponse' {} Int
a -> GetArchitectureRecommendationsResponse
s {$sel:httpStatus:GetArchitectureRecommendationsResponse' :: Int
httpStatus = Int
a} :: GetArchitectureRecommendationsResponse)

instance
  Prelude.NFData
    GetArchitectureRecommendationsResponse
  where
  rnf :: GetArchitectureRecommendationsResponse -> ()
rnf GetArchitectureRecommendationsResponse' {Int
Maybe [Recommendation]
Maybe Text
Maybe ISO8601
httpStatus :: Int
recommendations :: Maybe [Recommendation]
nextToken :: Maybe Text
lastAuditTimestamp :: Maybe ISO8601
$sel:httpStatus:GetArchitectureRecommendationsResponse' :: GetArchitectureRecommendationsResponse -> Int
$sel:recommendations:GetArchitectureRecommendationsResponse' :: GetArchitectureRecommendationsResponse -> Maybe [Recommendation]
$sel:nextToken:GetArchitectureRecommendationsResponse' :: GetArchitectureRecommendationsResponse -> Maybe Text
$sel:lastAuditTimestamp:GetArchitectureRecommendationsResponse' :: GetArchitectureRecommendationsResponse -> Maybe ISO8601
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
lastAuditTimestamp
      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 Maybe [Recommendation]
recommendations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus