{-# 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.ComputeOptimizer.GetAutoScalingGroupRecommendations
-- 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 Auto Scaling group recommendations.
--
-- Compute Optimizer generates recommendations for Amazon EC2 Auto Scaling
-- groups that meet a specific set of requirements. For more information,
-- see the
-- <https://docs.aws.amazon.com/compute-optimizer/latest/ug/requirements.html Supported resources and requirements>
-- in the /Compute Optimizer User Guide/.
module Amazonka.ComputeOptimizer.GetAutoScalingGroupRecommendations
  ( -- * Creating a Request
    GetAutoScalingGroupRecommendations (..),
    newGetAutoScalingGroupRecommendations,

    -- * Request Lenses
    getAutoScalingGroupRecommendations_accountIds,
    getAutoScalingGroupRecommendations_autoScalingGroupArns,
    getAutoScalingGroupRecommendations_filters,
    getAutoScalingGroupRecommendations_maxResults,
    getAutoScalingGroupRecommendations_nextToken,
    getAutoScalingGroupRecommendations_recommendationPreferences,

    -- * Destructuring the Response
    GetAutoScalingGroupRecommendationsResponse (..),
    newGetAutoScalingGroupRecommendationsResponse,

    -- * Response Lenses
    getAutoScalingGroupRecommendationsResponse_autoScalingGroupRecommendations,
    getAutoScalingGroupRecommendationsResponse_errors,
    getAutoScalingGroupRecommendationsResponse_nextToken,
    getAutoScalingGroupRecommendationsResponse_httpStatus,
  )
where

import Amazonka.ComputeOptimizer.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:/ 'newGetAutoScalingGroupRecommendations' smart constructor.
data GetAutoScalingGroupRecommendations = GetAutoScalingGroupRecommendations'
  { -- | The ID of the Amazon Web Services account for which to return Auto
    -- Scaling group recommendations.
    --
    -- If your account is the management account of an organization, use this
    -- parameter to specify the member account for which you want to return
    -- Auto Scaling group recommendations.
    --
    -- Only one account ID can be specified per request.
    GetAutoScalingGroupRecommendations -> Maybe [Text]
accountIds :: Prelude.Maybe [Prelude.Text],
    -- | The Amazon Resource Name (ARN) of the Auto Scaling groups for which to
    -- return recommendations.
    GetAutoScalingGroupRecommendations -> Maybe [Text]
autoScalingGroupArns :: Prelude.Maybe [Prelude.Text],
    -- | An array of objects to specify a filter that returns a more specific
    -- list of Auto Scaling group recommendations.
    GetAutoScalingGroupRecommendations -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | The maximum number of Auto Scaling group recommendations to return with
    -- a single request.
    --
    -- To retrieve the remaining results, make another request with the
    -- returned @nextToken@ value.
    GetAutoScalingGroupRecommendations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token to advance to the next page of Auto Scaling group
    -- recommendations.
    GetAutoScalingGroupRecommendations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An object to specify the preferences for the Auto Scaling group
    -- recommendations to return in the response.
    GetAutoScalingGroupRecommendations
-> Maybe RecommendationPreferences
recommendationPreferences :: Prelude.Maybe RecommendationPreferences
  }
  deriving (GetAutoScalingGroupRecommendations
-> GetAutoScalingGroupRecommendations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAutoScalingGroupRecommendations
-> GetAutoScalingGroupRecommendations -> Bool
$c/= :: GetAutoScalingGroupRecommendations
-> GetAutoScalingGroupRecommendations -> Bool
== :: GetAutoScalingGroupRecommendations
-> GetAutoScalingGroupRecommendations -> Bool
$c== :: GetAutoScalingGroupRecommendations
-> GetAutoScalingGroupRecommendations -> Bool
Prelude.Eq, ReadPrec [GetAutoScalingGroupRecommendations]
ReadPrec GetAutoScalingGroupRecommendations
Int -> ReadS GetAutoScalingGroupRecommendations
ReadS [GetAutoScalingGroupRecommendations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAutoScalingGroupRecommendations]
$creadListPrec :: ReadPrec [GetAutoScalingGroupRecommendations]
readPrec :: ReadPrec GetAutoScalingGroupRecommendations
$creadPrec :: ReadPrec GetAutoScalingGroupRecommendations
readList :: ReadS [GetAutoScalingGroupRecommendations]
$creadList :: ReadS [GetAutoScalingGroupRecommendations]
readsPrec :: Int -> ReadS GetAutoScalingGroupRecommendations
$creadsPrec :: Int -> ReadS GetAutoScalingGroupRecommendations
Prelude.Read, Int -> GetAutoScalingGroupRecommendations -> ShowS
[GetAutoScalingGroupRecommendations] -> ShowS
GetAutoScalingGroupRecommendations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAutoScalingGroupRecommendations] -> ShowS
$cshowList :: [GetAutoScalingGroupRecommendations] -> ShowS
show :: GetAutoScalingGroupRecommendations -> String
$cshow :: GetAutoScalingGroupRecommendations -> String
showsPrec :: Int -> GetAutoScalingGroupRecommendations -> ShowS
$cshowsPrec :: Int -> GetAutoScalingGroupRecommendations -> ShowS
Prelude.Show, forall x.
Rep GetAutoScalingGroupRecommendations x
-> GetAutoScalingGroupRecommendations
forall x.
GetAutoScalingGroupRecommendations
-> Rep GetAutoScalingGroupRecommendations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAutoScalingGroupRecommendations x
-> GetAutoScalingGroupRecommendations
$cfrom :: forall x.
GetAutoScalingGroupRecommendations
-> Rep GetAutoScalingGroupRecommendations x
Prelude.Generic)

-- |
-- Create a value of 'GetAutoScalingGroupRecommendations' 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:
--
-- 'accountIds', 'getAutoScalingGroupRecommendations_accountIds' - The ID of the Amazon Web Services account for which to return Auto
-- Scaling group recommendations.
--
-- If your account is the management account of an organization, use this
-- parameter to specify the member account for which you want to return
-- Auto Scaling group recommendations.
--
-- Only one account ID can be specified per request.
--
-- 'autoScalingGroupArns', 'getAutoScalingGroupRecommendations_autoScalingGroupArns' - The Amazon Resource Name (ARN) of the Auto Scaling groups for which to
-- return recommendations.
--
-- 'filters', 'getAutoScalingGroupRecommendations_filters' - An array of objects to specify a filter that returns a more specific
-- list of Auto Scaling group recommendations.
--
-- 'maxResults', 'getAutoScalingGroupRecommendations_maxResults' - The maximum number of Auto Scaling group recommendations to return with
-- a single request.
--
-- To retrieve the remaining results, make another request with the
-- returned @nextToken@ value.
--
-- 'nextToken', 'getAutoScalingGroupRecommendations_nextToken' - The token to advance to the next page of Auto Scaling group
-- recommendations.
--
-- 'recommendationPreferences', 'getAutoScalingGroupRecommendations_recommendationPreferences' - An object to specify the preferences for the Auto Scaling group
-- recommendations to return in the response.
newGetAutoScalingGroupRecommendations ::
  GetAutoScalingGroupRecommendations
newGetAutoScalingGroupRecommendations :: GetAutoScalingGroupRecommendations
newGetAutoScalingGroupRecommendations =
  GetAutoScalingGroupRecommendations'
    { $sel:accountIds:GetAutoScalingGroupRecommendations' :: Maybe [Text]
accountIds =
        forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingGroupArns:GetAutoScalingGroupRecommendations' :: Maybe [Text]
autoScalingGroupArns = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:GetAutoScalingGroupRecommendations' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:GetAutoScalingGroupRecommendations' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetAutoScalingGroupRecommendations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:recommendationPreferences:GetAutoScalingGroupRecommendations' :: Maybe RecommendationPreferences
recommendationPreferences =
        forall a. Maybe a
Prelude.Nothing
    }

-- | The ID of the Amazon Web Services account for which to return Auto
-- Scaling group recommendations.
--
-- If your account is the management account of an organization, use this
-- parameter to specify the member account for which you want to return
-- Auto Scaling group recommendations.
--
-- Only one account ID can be specified per request.
getAutoScalingGroupRecommendations_accountIds :: Lens.Lens' GetAutoScalingGroupRecommendations (Prelude.Maybe [Prelude.Text])
getAutoScalingGroupRecommendations_accountIds :: Lens' GetAutoScalingGroupRecommendations (Maybe [Text])
getAutoScalingGroupRecommendations_accountIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutoScalingGroupRecommendations' {Maybe [Text]
accountIds :: Maybe [Text]
$sel:accountIds:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Text]
accountIds} -> Maybe [Text]
accountIds) (\s :: GetAutoScalingGroupRecommendations
s@GetAutoScalingGroupRecommendations' {} Maybe [Text]
a -> GetAutoScalingGroupRecommendations
s {$sel:accountIds:GetAutoScalingGroupRecommendations' :: Maybe [Text]
accountIds = Maybe [Text]
a} :: GetAutoScalingGroupRecommendations) 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 Amazon Resource Name (ARN) of the Auto Scaling groups for which to
-- return recommendations.
getAutoScalingGroupRecommendations_autoScalingGroupArns :: Lens.Lens' GetAutoScalingGroupRecommendations (Prelude.Maybe [Prelude.Text])
getAutoScalingGroupRecommendations_autoScalingGroupArns :: Lens' GetAutoScalingGroupRecommendations (Maybe [Text])
getAutoScalingGroupRecommendations_autoScalingGroupArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutoScalingGroupRecommendations' {Maybe [Text]
autoScalingGroupArns :: Maybe [Text]
$sel:autoScalingGroupArns:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Text]
autoScalingGroupArns} -> Maybe [Text]
autoScalingGroupArns) (\s :: GetAutoScalingGroupRecommendations
s@GetAutoScalingGroupRecommendations' {} Maybe [Text]
a -> GetAutoScalingGroupRecommendations
s {$sel:autoScalingGroupArns:GetAutoScalingGroupRecommendations' :: Maybe [Text]
autoScalingGroupArns = Maybe [Text]
a} :: GetAutoScalingGroupRecommendations) 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

-- | An array of objects to specify a filter that returns a more specific
-- list of Auto Scaling group recommendations.
getAutoScalingGroupRecommendations_filters :: Lens.Lens' GetAutoScalingGroupRecommendations (Prelude.Maybe [Filter])
getAutoScalingGroupRecommendations_filters :: Lens' GetAutoScalingGroupRecommendations (Maybe [Filter])
getAutoScalingGroupRecommendations_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutoScalingGroupRecommendations' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: GetAutoScalingGroupRecommendations
s@GetAutoScalingGroupRecommendations' {} Maybe [Filter]
a -> GetAutoScalingGroupRecommendations
s {$sel:filters:GetAutoScalingGroupRecommendations' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: GetAutoScalingGroupRecommendations) 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 maximum number of Auto Scaling group recommendations to return with
-- a single request.
--
-- To retrieve the remaining results, make another request with the
-- returned @nextToken@ value.
getAutoScalingGroupRecommendations_maxResults :: Lens.Lens' GetAutoScalingGroupRecommendations (Prelude.Maybe Prelude.Natural)
getAutoScalingGroupRecommendations_maxResults :: Lens' GetAutoScalingGroupRecommendations (Maybe Natural)
getAutoScalingGroupRecommendations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutoScalingGroupRecommendations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetAutoScalingGroupRecommendations
s@GetAutoScalingGroupRecommendations' {} Maybe Natural
a -> GetAutoScalingGroupRecommendations
s {$sel:maxResults:GetAutoScalingGroupRecommendations' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetAutoScalingGroupRecommendations)

-- | The token to advance to the next page of Auto Scaling group
-- recommendations.
getAutoScalingGroupRecommendations_nextToken :: Lens.Lens' GetAutoScalingGroupRecommendations (Prelude.Maybe Prelude.Text)
getAutoScalingGroupRecommendations_nextToken :: Lens' GetAutoScalingGroupRecommendations (Maybe Text)
getAutoScalingGroupRecommendations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutoScalingGroupRecommendations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetAutoScalingGroupRecommendations
s@GetAutoScalingGroupRecommendations' {} Maybe Text
a -> GetAutoScalingGroupRecommendations
s {$sel:nextToken:GetAutoScalingGroupRecommendations' :: Maybe Text
nextToken = Maybe Text
a} :: GetAutoScalingGroupRecommendations)

-- | An object to specify the preferences for the Auto Scaling group
-- recommendations to return in the response.
getAutoScalingGroupRecommendations_recommendationPreferences :: Lens.Lens' GetAutoScalingGroupRecommendations (Prelude.Maybe RecommendationPreferences)
getAutoScalingGroupRecommendations_recommendationPreferences :: Lens'
  GetAutoScalingGroupRecommendations
  (Maybe RecommendationPreferences)
getAutoScalingGroupRecommendations_recommendationPreferences = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutoScalingGroupRecommendations' {Maybe RecommendationPreferences
recommendationPreferences :: Maybe RecommendationPreferences
$sel:recommendationPreferences:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations
-> Maybe RecommendationPreferences
recommendationPreferences} -> Maybe RecommendationPreferences
recommendationPreferences) (\s :: GetAutoScalingGroupRecommendations
s@GetAutoScalingGroupRecommendations' {} Maybe RecommendationPreferences
a -> GetAutoScalingGroupRecommendations
s {$sel:recommendationPreferences:GetAutoScalingGroupRecommendations' :: Maybe RecommendationPreferences
recommendationPreferences = Maybe RecommendationPreferences
a} :: GetAutoScalingGroupRecommendations)

instance
  Core.AWSRequest
    GetAutoScalingGroupRecommendations
  where
  type
    AWSResponse GetAutoScalingGroupRecommendations =
      GetAutoScalingGroupRecommendationsResponse
  request :: (Service -> Service)
-> GetAutoScalingGroupRecommendations
-> Request GetAutoScalingGroupRecommendations
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 GetAutoScalingGroupRecommendations
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetAutoScalingGroupRecommendations)))
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 [AutoScalingGroupRecommendation]
-> Maybe [GetRecommendationError]
-> Maybe Text
-> Int
-> GetAutoScalingGroupRecommendationsResponse
GetAutoScalingGroupRecommendationsResponse'
            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
"autoScalingGroupRecommendations"
                            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"errors" 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.<*> (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))
      )

instance
  Prelude.Hashable
    GetAutoScalingGroupRecommendations
  where
  hashWithSalt :: Int -> GetAutoScalingGroupRecommendations -> Int
hashWithSalt
    Int
_salt
    GetAutoScalingGroupRecommendations' {Maybe Natural
Maybe [Text]
Maybe [Filter]
Maybe Text
Maybe RecommendationPreferences
recommendationPreferences :: Maybe RecommendationPreferences
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
autoScalingGroupArns :: Maybe [Text]
accountIds :: Maybe [Text]
$sel:recommendationPreferences:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations
-> Maybe RecommendationPreferences
$sel:nextToken:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe Text
$sel:maxResults:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe Natural
$sel:filters:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Filter]
$sel:autoScalingGroupArns:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Text]
$sel:accountIds:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Text]
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
accountIds
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
autoScalingGroupArns
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
        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` Maybe RecommendationPreferences
recommendationPreferences

instance
  Prelude.NFData
    GetAutoScalingGroupRecommendations
  where
  rnf :: GetAutoScalingGroupRecommendations -> ()
rnf GetAutoScalingGroupRecommendations' {Maybe Natural
Maybe [Text]
Maybe [Filter]
Maybe Text
Maybe RecommendationPreferences
recommendationPreferences :: Maybe RecommendationPreferences
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
autoScalingGroupArns :: Maybe [Text]
accountIds :: Maybe [Text]
$sel:recommendationPreferences:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations
-> Maybe RecommendationPreferences
$sel:nextToken:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe Text
$sel:maxResults:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe Natural
$sel:filters:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Filter]
$sel:autoScalingGroupArns:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Text]
$sel:accountIds:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
accountIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
autoScalingGroupArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Maybe RecommendationPreferences
recommendationPreferences

instance
  Data.ToHeaders
    GetAutoScalingGroupRecommendations
  where
  toHeaders :: GetAutoScalingGroupRecommendations -> 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
"ComputeOptimizerService.GetAutoScalingGroupRecommendations" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance
  Data.ToJSON
    GetAutoScalingGroupRecommendations
  where
  toJSON :: GetAutoScalingGroupRecommendations -> Value
toJSON GetAutoScalingGroupRecommendations' {Maybe Natural
Maybe [Text]
Maybe [Filter]
Maybe Text
Maybe RecommendationPreferences
recommendationPreferences :: Maybe RecommendationPreferences
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
autoScalingGroupArns :: Maybe [Text]
accountIds :: Maybe [Text]
$sel:recommendationPreferences:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations
-> Maybe RecommendationPreferences
$sel:nextToken:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe Text
$sel:maxResults:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe Natural
$sel:filters:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Filter]
$sel:autoScalingGroupArns:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Text]
$sel:accountIds:GetAutoScalingGroupRecommendations' :: GetAutoScalingGroupRecommendations -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"accountIds" 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]
accountIds,
            (Key
"autoScalingGroupArns" 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]
autoScalingGroupArns,
            (Key
"filters" 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 [Filter]
filters,
            (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,
            (Key
"recommendationPreferences" 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 RecommendationPreferences
recommendationPreferences
          ]
      )

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

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

-- | /See:/ 'newGetAutoScalingGroupRecommendationsResponse' smart constructor.
data GetAutoScalingGroupRecommendationsResponse = GetAutoScalingGroupRecommendationsResponse'
  { -- | An array of objects that describe Auto Scaling group recommendations.
    GetAutoScalingGroupRecommendationsResponse
-> Maybe [AutoScalingGroupRecommendation]
autoScalingGroupRecommendations :: Prelude.Maybe [AutoScalingGroupRecommendation],
    -- | An array of objects that describe errors of the request.
    --
    -- For example, an error is returned if you request recommendations for an
    -- unsupported Auto Scaling group.
    GetAutoScalingGroupRecommendationsResponse
-> Maybe [GetRecommendationError]
errors :: Prelude.Maybe [GetRecommendationError],
    -- | The token to use to advance to the next page of Auto Scaling group
    -- recommendations.
    --
    -- This value is null when there are no more pages of Auto Scaling group
    -- recommendations to return.
    GetAutoScalingGroupRecommendationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetAutoScalingGroupRecommendationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAutoScalingGroupRecommendationsResponse
-> GetAutoScalingGroupRecommendationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAutoScalingGroupRecommendationsResponse
-> GetAutoScalingGroupRecommendationsResponse -> Bool
$c/= :: GetAutoScalingGroupRecommendationsResponse
-> GetAutoScalingGroupRecommendationsResponse -> Bool
== :: GetAutoScalingGroupRecommendationsResponse
-> GetAutoScalingGroupRecommendationsResponse -> Bool
$c== :: GetAutoScalingGroupRecommendationsResponse
-> GetAutoScalingGroupRecommendationsResponse -> Bool
Prelude.Eq, ReadPrec [GetAutoScalingGroupRecommendationsResponse]
ReadPrec GetAutoScalingGroupRecommendationsResponse
Int -> ReadS GetAutoScalingGroupRecommendationsResponse
ReadS [GetAutoScalingGroupRecommendationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAutoScalingGroupRecommendationsResponse]
$creadListPrec :: ReadPrec [GetAutoScalingGroupRecommendationsResponse]
readPrec :: ReadPrec GetAutoScalingGroupRecommendationsResponse
$creadPrec :: ReadPrec GetAutoScalingGroupRecommendationsResponse
readList :: ReadS [GetAutoScalingGroupRecommendationsResponse]
$creadList :: ReadS [GetAutoScalingGroupRecommendationsResponse]
readsPrec :: Int -> ReadS GetAutoScalingGroupRecommendationsResponse
$creadsPrec :: Int -> ReadS GetAutoScalingGroupRecommendationsResponse
Prelude.Read, Int -> GetAutoScalingGroupRecommendationsResponse -> ShowS
[GetAutoScalingGroupRecommendationsResponse] -> ShowS
GetAutoScalingGroupRecommendationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAutoScalingGroupRecommendationsResponse] -> ShowS
$cshowList :: [GetAutoScalingGroupRecommendationsResponse] -> ShowS
show :: GetAutoScalingGroupRecommendationsResponse -> String
$cshow :: GetAutoScalingGroupRecommendationsResponse -> String
showsPrec :: Int -> GetAutoScalingGroupRecommendationsResponse -> ShowS
$cshowsPrec :: Int -> GetAutoScalingGroupRecommendationsResponse -> ShowS
Prelude.Show, forall x.
Rep GetAutoScalingGroupRecommendationsResponse x
-> GetAutoScalingGroupRecommendationsResponse
forall x.
GetAutoScalingGroupRecommendationsResponse
-> Rep GetAutoScalingGroupRecommendationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAutoScalingGroupRecommendationsResponse x
-> GetAutoScalingGroupRecommendationsResponse
$cfrom :: forall x.
GetAutoScalingGroupRecommendationsResponse
-> Rep GetAutoScalingGroupRecommendationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAutoScalingGroupRecommendationsResponse' 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:
--
-- 'autoScalingGroupRecommendations', 'getAutoScalingGroupRecommendationsResponse_autoScalingGroupRecommendations' - An array of objects that describe Auto Scaling group recommendations.
--
-- 'errors', 'getAutoScalingGroupRecommendationsResponse_errors' - An array of objects that describe errors of the request.
--
-- For example, an error is returned if you request recommendations for an
-- unsupported Auto Scaling group.
--
-- 'nextToken', 'getAutoScalingGroupRecommendationsResponse_nextToken' - The token to use to advance to the next page of Auto Scaling group
-- recommendations.
--
-- This value is null when there are no more pages of Auto Scaling group
-- recommendations to return.
--
-- 'httpStatus', 'getAutoScalingGroupRecommendationsResponse_httpStatus' - The response's http status code.
newGetAutoScalingGroupRecommendationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAutoScalingGroupRecommendationsResponse
newGetAutoScalingGroupRecommendationsResponse :: Int -> GetAutoScalingGroupRecommendationsResponse
newGetAutoScalingGroupRecommendationsResponse
  Int
pHttpStatus_ =
    GetAutoScalingGroupRecommendationsResponse'
      { $sel:autoScalingGroupRecommendations:GetAutoScalingGroupRecommendationsResponse' :: Maybe [AutoScalingGroupRecommendation]
autoScalingGroupRecommendations =
          forall a. Maybe a
Prelude.Nothing,
        $sel:errors:GetAutoScalingGroupRecommendationsResponse' :: Maybe [GetRecommendationError]
errors = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetAutoScalingGroupRecommendationsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetAutoScalingGroupRecommendationsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | An array of objects that describe Auto Scaling group recommendations.
getAutoScalingGroupRecommendationsResponse_autoScalingGroupRecommendations :: Lens.Lens' GetAutoScalingGroupRecommendationsResponse (Prelude.Maybe [AutoScalingGroupRecommendation])
getAutoScalingGroupRecommendationsResponse_autoScalingGroupRecommendations :: Lens'
  GetAutoScalingGroupRecommendationsResponse
  (Maybe [AutoScalingGroupRecommendation])
getAutoScalingGroupRecommendationsResponse_autoScalingGroupRecommendations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutoScalingGroupRecommendationsResponse' {Maybe [AutoScalingGroupRecommendation]
autoScalingGroupRecommendations :: Maybe [AutoScalingGroupRecommendation]
$sel:autoScalingGroupRecommendations:GetAutoScalingGroupRecommendationsResponse' :: GetAutoScalingGroupRecommendationsResponse
-> Maybe [AutoScalingGroupRecommendation]
autoScalingGroupRecommendations} -> Maybe [AutoScalingGroupRecommendation]
autoScalingGroupRecommendations) (\s :: GetAutoScalingGroupRecommendationsResponse
s@GetAutoScalingGroupRecommendationsResponse' {} Maybe [AutoScalingGroupRecommendation]
a -> GetAutoScalingGroupRecommendationsResponse
s {$sel:autoScalingGroupRecommendations:GetAutoScalingGroupRecommendationsResponse' :: Maybe [AutoScalingGroupRecommendation]
autoScalingGroupRecommendations = Maybe [AutoScalingGroupRecommendation]
a} :: GetAutoScalingGroupRecommendationsResponse) 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

-- | An array of objects that describe errors of the request.
--
-- For example, an error is returned if you request recommendations for an
-- unsupported Auto Scaling group.
getAutoScalingGroupRecommendationsResponse_errors :: Lens.Lens' GetAutoScalingGroupRecommendationsResponse (Prelude.Maybe [GetRecommendationError])
getAutoScalingGroupRecommendationsResponse_errors :: Lens'
  GetAutoScalingGroupRecommendationsResponse
  (Maybe [GetRecommendationError])
getAutoScalingGroupRecommendationsResponse_errors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutoScalingGroupRecommendationsResponse' {Maybe [GetRecommendationError]
errors :: Maybe [GetRecommendationError]
$sel:errors:GetAutoScalingGroupRecommendationsResponse' :: GetAutoScalingGroupRecommendationsResponse
-> Maybe [GetRecommendationError]
errors} -> Maybe [GetRecommendationError]
errors) (\s :: GetAutoScalingGroupRecommendationsResponse
s@GetAutoScalingGroupRecommendationsResponse' {} Maybe [GetRecommendationError]
a -> GetAutoScalingGroupRecommendationsResponse
s {$sel:errors:GetAutoScalingGroupRecommendationsResponse' :: Maybe [GetRecommendationError]
errors = Maybe [GetRecommendationError]
a} :: GetAutoScalingGroupRecommendationsResponse) 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 token to use to advance to the next page of Auto Scaling group
-- recommendations.
--
-- This value is null when there are no more pages of Auto Scaling group
-- recommendations to return.
getAutoScalingGroupRecommendationsResponse_nextToken :: Lens.Lens' GetAutoScalingGroupRecommendationsResponse (Prelude.Maybe Prelude.Text)
getAutoScalingGroupRecommendationsResponse_nextToken :: Lens' GetAutoScalingGroupRecommendationsResponse (Maybe Text)
getAutoScalingGroupRecommendationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutoScalingGroupRecommendationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetAutoScalingGroupRecommendationsResponse' :: GetAutoScalingGroupRecommendationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetAutoScalingGroupRecommendationsResponse
s@GetAutoScalingGroupRecommendationsResponse' {} Maybe Text
a -> GetAutoScalingGroupRecommendationsResponse
s {$sel:nextToken:GetAutoScalingGroupRecommendationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetAutoScalingGroupRecommendationsResponse)

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

instance
  Prelude.NFData
    GetAutoScalingGroupRecommendationsResponse
  where
  rnf :: GetAutoScalingGroupRecommendationsResponse -> ()
rnf GetAutoScalingGroupRecommendationsResponse' {Int
Maybe [GetRecommendationError]
Maybe [AutoScalingGroupRecommendation]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
errors :: Maybe [GetRecommendationError]
autoScalingGroupRecommendations :: Maybe [AutoScalingGroupRecommendation]
$sel:httpStatus:GetAutoScalingGroupRecommendationsResponse' :: GetAutoScalingGroupRecommendationsResponse -> Int
$sel:nextToken:GetAutoScalingGroupRecommendationsResponse' :: GetAutoScalingGroupRecommendationsResponse -> Maybe Text
$sel:errors:GetAutoScalingGroupRecommendationsResponse' :: GetAutoScalingGroupRecommendationsResponse
-> Maybe [GetRecommendationError]
$sel:autoScalingGroupRecommendations:GetAutoScalingGroupRecommendationsResponse' :: GetAutoScalingGroupRecommendationsResponse
-> Maybe [AutoScalingGroupRecommendation]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AutoScalingGroupRecommendation]
autoScalingGroupRecommendations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [GetRecommendationError]
errors
      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 Int
httpStatus