{-# 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.AutoScaling.DescribeLaunchConfigurations
-- 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 information about the launch configurations in the account and
-- Region.
--
-- This operation returns paginated results.
module Amazonka.AutoScaling.DescribeLaunchConfigurations
  ( -- * Creating a Request
    DescribeLaunchConfigurations (..),
    newDescribeLaunchConfigurations,

    -- * Request Lenses
    describeLaunchConfigurations_launchConfigurationNames,
    describeLaunchConfigurations_maxRecords,
    describeLaunchConfigurations_nextToken,

    -- * Destructuring the Response
    DescribeLaunchConfigurationsResponse (..),
    newDescribeLaunchConfigurationsResponse,

    -- * Response Lenses
    describeLaunchConfigurationsResponse_nextToken,
    describeLaunchConfigurationsResponse_httpStatus,
    describeLaunchConfigurationsResponse_launchConfigurations,
  )
where

import Amazonka.AutoScaling.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:/ 'newDescribeLaunchConfigurations' smart constructor.
data DescribeLaunchConfigurations = DescribeLaunchConfigurations'
  { -- | The launch configuration names. If you omit this property, all launch
    -- configurations are described.
    --
    -- Array Members: Maximum number of 50 items.
    DescribeLaunchConfigurations -> Maybe [Text]
launchConfigurationNames :: Prelude.Maybe [Prelude.Text],
    -- | The maximum number of items to return with this call. The default value
    -- is @50@ and the maximum value is @100@.
    DescribeLaunchConfigurations -> Maybe Int
maxRecords :: Prelude.Maybe Prelude.Int,
    -- | The token for the next set of items to return. (You received this token
    -- from a previous call.)
    DescribeLaunchConfigurations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeLaunchConfigurations
-> DescribeLaunchConfigurations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLaunchConfigurations
-> DescribeLaunchConfigurations -> Bool
$c/= :: DescribeLaunchConfigurations
-> DescribeLaunchConfigurations -> Bool
== :: DescribeLaunchConfigurations
-> DescribeLaunchConfigurations -> Bool
$c== :: DescribeLaunchConfigurations
-> DescribeLaunchConfigurations -> Bool
Prelude.Eq, ReadPrec [DescribeLaunchConfigurations]
ReadPrec DescribeLaunchConfigurations
Int -> ReadS DescribeLaunchConfigurations
ReadS [DescribeLaunchConfigurations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLaunchConfigurations]
$creadListPrec :: ReadPrec [DescribeLaunchConfigurations]
readPrec :: ReadPrec DescribeLaunchConfigurations
$creadPrec :: ReadPrec DescribeLaunchConfigurations
readList :: ReadS [DescribeLaunchConfigurations]
$creadList :: ReadS [DescribeLaunchConfigurations]
readsPrec :: Int -> ReadS DescribeLaunchConfigurations
$creadsPrec :: Int -> ReadS DescribeLaunchConfigurations
Prelude.Read, Int -> DescribeLaunchConfigurations -> ShowS
[DescribeLaunchConfigurations] -> ShowS
DescribeLaunchConfigurations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLaunchConfigurations] -> ShowS
$cshowList :: [DescribeLaunchConfigurations] -> ShowS
show :: DescribeLaunchConfigurations -> String
$cshow :: DescribeLaunchConfigurations -> String
showsPrec :: Int -> DescribeLaunchConfigurations -> ShowS
$cshowsPrec :: Int -> DescribeLaunchConfigurations -> ShowS
Prelude.Show, forall x.
Rep DescribeLaunchConfigurations x -> DescribeLaunchConfigurations
forall x.
DescribeLaunchConfigurations -> Rep DescribeLaunchConfigurations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLaunchConfigurations x -> DescribeLaunchConfigurations
$cfrom :: forall x.
DescribeLaunchConfigurations -> Rep DescribeLaunchConfigurations x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLaunchConfigurations' 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:
--
-- 'launchConfigurationNames', 'describeLaunchConfigurations_launchConfigurationNames' - The launch configuration names. If you omit this property, all launch
-- configurations are described.
--
-- Array Members: Maximum number of 50 items.
--
-- 'maxRecords', 'describeLaunchConfigurations_maxRecords' - The maximum number of items to return with this call. The default value
-- is @50@ and the maximum value is @100@.
--
-- 'nextToken', 'describeLaunchConfigurations_nextToken' - The token for the next set of items to return. (You received this token
-- from a previous call.)
newDescribeLaunchConfigurations ::
  DescribeLaunchConfigurations
newDescribeLaunchConfigurations :: DescribeLaunchConfigurations
newDescribeLaunchConfigurations =
  DescribeLaunchConfigurations'
    { $sel:launchConfigurationNames:DescribeLaunchConfigurations' :: Maybe [Text]
launchConfigurationNames =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxRecords:DescribeLaunchConfigurations' :: Maybe Int
maxRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeLaunchConfigurations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The launch configuration names. If you omit this property, all launch
-- configurations are described.
--
-- Array Members: Maximum number of 50 items.
describeLaunchConfigurations_launchConfigurationNames :: Lens.Lens' DescribeLaunchConfigurations (Prelude.Maybe [Prelude.Text])
describeLaunchConfigurations_launchConfigurationNames :: Lens' DescribeLaunchConfigurations (Maybe [Text])
describeLaunchConfigurations_launchConfigurationNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLaunchConfigurations' {Maybe [Text]
launchConfigurationNames :: Maybe [Text]
$sel:launchConfigurationNames:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe [Text]
launchConfigurationNames} -> Maybe [Text]
launchConfigurationNames) (\s :: DescribeLaunchConfigurations
s@DescribeLaunchConfigurations' {} Maybe [Text]
a -> DescribeLaunchConfigurations
s {$sel:launchConfigurationNames:DescribeLaunchConfigurations' :: Maybe [Text]
launchConfigurationNames = Maybe [Text]
a} :: DescribeLaunchConfigurations) 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 items to return with this call. The default value
-- is @50@ and the maximum value is @100@.
describeLaunchConfigurations_maxRecords :: Lens.Lens' DescribeLaunchConfigurations (Prelude.Maybe Prelude.Int)
describeLaunchConfigurations_maxRecords :: Lens' DescribeLaunchConfigurations (Maybe Int)
describeLaunchConfigurations_maxRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLaunchConfigurations' {Maybe Int
maxRecords :: Maybe Int
$sel:maxRecords:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe Int
maxRecords} -> Maybe Int
maxRecords) (\s :: DescribeLaunchConfigurations
s@DescribeLaunchConfigurations' {} Maybe Int
a -> DescribeLaunchConfigurations
s {$sel:maxRecords:DescribeLaunchConfigurations' :: Maybe Int
maxRecords = Maybe Int
a} :: DescribeLaunchConfigurations)

-- | The token for the next set of items to return. (You received this token
-- from a previous call.)
describeLaunchConfigurations_nextToken :: Lens.Lens' DescribeLaunchConfigurations (Prelude.Maybe Prelude.Text)
describeLaunchConfigurations_nextToken :: Lens' DescribeLaunchConfigurations (Maybe Text)
describeLaunchConfigurations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLaunchConfigurations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeLaunchConfigurations
s@DescribeLaunchConfigurations' {} Maybe Text
a -> DescribeLaunchConfigurations
s {$sel:nextToken:DescribeLaunchConfigurations' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeLaunchConfigurations)

instance Core.AWSPager DescribeLaunchConfigurations where
  page :: DescribeLaunchConfigurations
-> AWSResponse DescribeLaunchConfigurations
-> Maybe DescribeLaunchConfigurations
page DescribeLaunchConfigurations
rq AWSResponse DescribeLaunchConfigurations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeLaunchConfigurations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeLaunchConfigurationsResponse (Maybe Text)
describeLaunchConfigurationsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeLaunchConfigurations
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens' DescribeLaunchConfigurationsResponse [LaunchConfiguration]
describeLaunchConfigurationsResponse_launchConfigurations
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeLaunchConfigurations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeLaunchConfigurations (Maybe Text)
describeLaunchConfigurations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeLaunchConfigurations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeLaunchConfigurationsResponse (Maybe Text)
describeLaunchConfigurationsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest DescribeLaunchConfigurations where
  type
    AWSResponse DescribeLaunchConfigurations =
      DescribeLaunchConfigurationsResponse
  request :: (Service -> Service)
-> DescribeLaunchConfigurations
-> Request DescribeLaunchConfigurations
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeLaunchConfigurations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeLaunchConfigurations)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DescribeLaunchConfigurationsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Int
-> [LaunchConfiguration]
-> DescribeLaunchConfigurationsResponse
DescribeLaunchConfigurationsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"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.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"LaunchConfigurations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member"
                        )
      )

instance
  Prelude.Hashable
    DescribeLaunchConfigurations
  where
  hashWithSalt :: Int -> DescribeLaunchConfigurations -> Int
hashWithSalt Int
_salt DescribeLaunchConfigurations' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxRecords :: Maybe Int
launchConfigurationNames :: Maybe [Text]
$sel:nextToken:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe Text
$sel:maxRecords:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe Int
$sel:launchConfigurationNames:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
launchConfigurationNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxRecords
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData DescribeLaunchConfigurations where
  rnf :: DescribeLaunchConfigurations -> ()
rnf DescribeLaunchConfigurations' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxRecords :: Maybe Int
launchConfigurationNames :: Maybe [Text]
$sel:nextToken:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe Text
$sel:maxRecords:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe Int
$sel:launchConfigurationNames:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
launchConfigurationNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxRecords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders DescribeLaunchConfigurations where
  toHeaders :: DescribeLaunchConfigurations -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DescribeLaunchConfigurations where
  toQuery :: DescribeLaunchConfigurations -> QueryString
toQuery DescribeLaunchConfigurations' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxRecords :: Maybe Int
launchConfigurationNames :: Maybe [Text]
$sel:nextToken:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe Text
$sel:maxRecords:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe Int
$sel:launchConfigurationNames:DescribeLaunchConfigurations' :: DescribeLaunchConfigurations -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DescribeLaunchConfigurations" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"LaunchConfigurationNames"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
launchConfigurationNames
            ),
        ByteString
"MaxRecords" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxRecords,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newDescribeLaunchConfigurationsResponse' smart constructor.
data DescribeLaunchConfigurationsResponse = DescribeLaunchConfigurationsResponse'
  { -- | A string that indicates that the response contains more items than can
    -- be returned in a single response. To receive additional items, specify
    -- this string for the @NextToken@ value when requesting the next set of
    -- items. This value is null when there are no more items to return.
    DescribeLaunchConfigurationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeLaunchConfigurationsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The launch configurations.
    DescribeLaunchConfigurationsResponse -> [LaunchConfiguration]
launchConfigurations :: [LaunchConfiguration]
  }
  deriving (DescribeLaunchConfigurationsResponse
-> DescribeLaunchConfigurationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLaunchConfigurationsResponse
-> DescribeLaunchConfigurationsResponse -> Bool
$c/= :: DescribeLaunchConfigurationsResponse
-> DescribeLaunchConfigurationsResponse -> Bool
== :: DescribeLaunchConfigurationsResponse
-> DescribeLaunchConfigurationsResponse -> Bool
$c== :: DescribeLaunchConfigurationsResponse
-> DescribeLaunchConfigurationsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeLaunchConfigurationsResponse]
ReadPrec DescribeLaunchConfigurationsResponse
Int -> ReadS DescribeLaunchConfigurationsResponse
ReadS [DescribeLaunchConfigurationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLaunchConfigurationsResponse]
$creadListPrec :: ReadPrec [DescribeLaunchConfigurationsResponse]
readPrec :: ReadPrec DescribeLaunchConfigurationsResponse
$creadPrec :: ReadPrec DescribeLaunchConfigurationsResponse
readList :: ReadS [DescribeLaunchConfigurationsResponse]
$creadList :: ReadS [DescribeLaunchConfigurationsResponse]
readsPrec :: Int -> ReadS DescribeLaunchConfigurationsResponse
$creadsPrec :: Int -> ReadS DescribeLaunchConfigurationsResponse
Prelude.Read, Int -> DescribeLaunchConfigurationsResponse -> ShowS
[DescribeLaunchConfigurationsResponse] -> ShowS
DescribeLaunchConfigurationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLaunchConfigurationsResponse] -> ShowS
$cshowList :: [DescribeLaunchConfigurationsResponse] -> ShowS
show :: DescribeLaunchConfigurationsResponse -> String
$cshow :: DescribeLaunchConfigurationsResponse -> String
showsPrec :: Int -> DescribeLaunchConfigurationsResponse -> ShowS
$cshowsPrec :: Int -> DescribeLaunchConfigurationsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLaunchConfigurationsResponse x
-> DescribeLaunchConfigurationsResponse
forall x.
DescribeLaunchConfigurationsResponse
-> Rep DescribeLaunchConfigurationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLaunchConfigurationsResponse x
-> DescribeLaunchConfigurationsResponse
$cfrom :: forall x.
DescribeLaunchConfigurationsResponse
-> Rep DescribeLaunchConfigurationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLaunchConfigurationsResponse' 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', 'describeLaunchConfigurationsResponse_nextToken' - A string that indicates that the response contains more items than can
-- be returned in a single response. To receive additional items, specify
-- this string for the @NextToken@ value when requesting the next set of
-- items. This value is null when there are no more items to return.
--
-- 'httpStatus', 'describeLaunchConfigurationsResponse_httpStatus' - The response's http status code.
--
-- 'launchConfigurations', 'describeLaunchConfigurationsResponse_launchConfigurations' - The launch configurations.
newDescribeLaunchConfigurationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeLaunchConfigurationsResponse
newDescribeLaunchConfigurationsResponse :: Int -> DescribeLaunchConfigurationsResponse
newDescribeLaunchConfigurationsResponse Int
pHttpStatus_ =
  DescribeLaunchConfigurationsResponse'
    { $sel:nextToken:DescribeLaunchConfigurationsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeLaunchConfigurationsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:launchConfigurations:DescribeLaunchConfigurationsResponse' :: [LaunchConfiguration]
launchConfigurations = forall a. Monoid a => a
Prelude.mempty
    }

-- | A string that indicates that the response contains more items than can
-- be returned in a single response. To receive additional items, specify
-- this string for the @NextToken@ value when requesting the next set of
-- items. This value is null when there are no more items to return.
describeLaunchConfigurationsResponse_nextToken :: Lens.Lens' DescribeLaunchConfigurationsResponse (Prelude.Maybe Prelude.Text)
describeLaunchConfigurationsResponse_nextToken :: Lens' DescribeLaunchConfigurationsResponse (Maybe Text)
describeLaunchConfigurationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLaunchConfigurationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeLaunchConfigurationsResponse' :: DescribeLaunchConfigurationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeLaunchConfigurationsResponse
s@DescribeLaunchConfigurationsResponse' {} Maybe Text
a -> DescribeLaunchConfigurationsResponse
s {$sel:nextToken:DescribeLaunchConfigurationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeLaunchConfigurationsResponse)

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

-- | The launch configurations.
describeLaunchConfigurationsResponse_launchConfigurations :: Lens.Lens' DescribeLaunchConfigurationsResponse [LaunchConfiguration]
describeLaunchConfigurationsResponse_launchConfigurations :: Lens' DescribeLaunchConfigurationsResponse [LaunchConfiguration]
describeLaunchConfigurationsResponse_launchConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLaunchConfigurationsResponse' {[LaunchConfiguration]
launchConfigurations :: [LaunchConfiguration]
$sel:launchConfigurations:DescribeLaunchConfigurationsResponse' :: DescribeLaunchConfigurationsResponse -> [LaunchConfiguration]
launchConfigurations} -> [LaunchConfiguration]
launchConfigurations) (\s :: DescribeLaunchConfigurationsResponse
s@DescribeLaunchConfigurationsResponse' {} [LaunchConfiguration]
a -> DescribeLaunchConfigurationsResponse
s {$sel:launchConfigurations:DescribeLaunchConfigurationsResponse' :: [LaunchConfiguration]
launchConfigurations = [LaunchConfiguration]
a} :: DescribeLaunchConfigurationsResponse) 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
    DescribeLaunchConfigurationsResponse
  where
  rnf :: DescribeLaunchConfigurationsResponse -> ()
rnf DescribeLaunchConfigurationsResponse' {Int
[LaunchConfiguration]
Maybe Text
launchConfigurations :: [LaunchConfiguration]
httpStatus :: Int
nextToken :: Maybe Text
$sel:launchConfigurations:DescribeLaunchConfigurationsResponse' :: DescribeLaunchConfigurationsResponse -> [LaunchConfiguration]
$sel:httpStatus:DescribeLaunchConfigurationsResponse' :: DescribeLaunchConfigurationsResponse -> Int
$sel:nextToken:DescribeLaunchConfigurationsResponse' :: DescribeLaunchConfigurationsResponse -> 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 [LaunchConfiguration]
launchConfigurations