{-# 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.EC2.DescribePlacementGroups
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the specified placement groups or all of your placement
-- groups. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/placement-groups.html Placement groups>
-- in the /Amazon EC2 User Guide/.
module Amazonka.EC2.DescribePlacementGroups
  ( -- * Creating a Request
    DescribePlacementGroups (..),
    newDescribePlacementGroups,

    -- * Request Lenses
    describePlacementGroups_dryRun,
    describePlacementGroups_filters,
    describePlacementGroups_groupIds,
    describePlacementGroups_groupNames,

    -- * Destructuring the Response
    DescribePlacementGroupsResponse (..),
    newDescribePlacementGroupsResponse,

    -- * Response Lenses
    describePlacementGroupsResponse_placementGroups,
    describePlacementGroupsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribePlacementGroups' smart constructor.
data DescribePlacementGroups = DescribePlacementGroups'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    DescribePlacementGroups -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The filters.
    --
    -- -   @group-name@ - The name of the placement group.
    --
    -- -   @group-arn@ - The Amazon Resource Name (ARN) of the placement group.
    --
    -- -   @spread-level@ - The spread level for the placement group (@host@ |
    --     @rack@).
    --
    -- -   @state@ - The state of the placement group (@pending@ | @available@
    --     | @deleting@ | @deleted@).
    --
    -- -   @strategy@ - The strategy of the placement group (@cluster@ |
    --     @spread@ | @partition@).
    --
    -- -   @tag:\<key>@ - The key\/value combination of a tag assigned to the
    --     resource. Use the tag key in the filter name and the tag value as
    --     the filter value. For example, to find all resources that have a tag
    --     with the key @Owner@ and the value @TeamA@, specify @tag:Owner@ for
    --     the filter name and @TeamA@ for the filter value.
    --
    -- -   @tag-key@ - The key of a tag assigned to the resource. Use this
    --     filter to find all resources that have a tag with a specific key,
    --     regardless of the tag value.
    DescribePlacementGroups -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | The IDs of the placement groups.
    DescribePlacementGroups -> Maybe [Text]
groupIds :: Prelude.Maybe [Prelude.Text],
    -- | The names of the placement groups.
    --
    -- Default: Describes all your placement groups, or only those otherwise
    -- specified.
    DescribePlacementGroups -> Maybe [Text]
groupNames :: Prelude.Maybe [Prelude.Text]
  }
  deriving (DescribePlacementGroups -> DescribePlacementGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribePlacementGroups -> DescribePlacementGroups -> Bool
$c/= :: DescribePlacementGroups -> DescribePlacementGroups -> Bool
== :: DescribePlacementGroups -> DescribePlacementGroups -> Bool
$c== :: DescribePlacementGroups -> DescribePlacementGroups -> Bool
Prelude.Eq, ReadPrec [DescribePlacementGroups]
ReadPrec DescribePlacementGroups
Int -> ReadS DescribePlacementGroups
ReadS [DescribePlacementGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribePlacementGroups]
$creadListPrec :: ReadPrec [DescribePlacementGroups]
readPrec :: ReadPrec DescribePlacementGroups
$creadPrec :: ReadPrec DescribePlacementGroups
readList :: ReadS [DescribePlacementGroups]
$creadList :: ReadS [DescribePlacementGroups]
readsPrec :: Int -> ReadS DescribePlacementGroups
$creadsPrec :: Int -> ReadS DescribePlacementGroups
Prelude.Read, Int -> DescribePlacementGroups -> ShowS
[DescribePlacementGroups] -> ShowS
DescribePlacementGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribePlacementGroups] -> ShowS
$cshowList :: [DescribePlacementGroups] -> ShowS
show :: DescribePlacementGroups -> String
$cshow :: DescribePlacementGroups -> String
showsPrec :: Int -> DescribePlacementGroups -> ShowS
$cshowsPrec :: Int -> DescribePlacementGroups -> ShowS
Prelude.Show, forall x. Rep DescribePlacementGroups x -> DescribePlacementGroups
forall x. DescribePlacementGroups -> Rep DescribePlacementGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribePlacementGroups x -> DescribePlacementGroups
$cfrom :: forall x. DescribePlacementGroups -> Rep DescribePlacementGroups x
Prelude.Generic)

-- |
-- Create a value of 'DescribePlacementGroups' 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:
--
-- 'dryRun', 'describePlacementGroups_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'filters', 'describePlacementGroups_filters' - The filters.
--
-- -   @group-name@ - The name of the placement group.
--
-- -   @group-arn@ - The Amazon Resource Name (ARN) of the placement group.
--
-- -   @spread-level@ - The spread level for the placement group (@host@ |
--     @rack@).
--
-- -   @state@ - The state of the placement group (@pending@ | @available@
--     | @deleting@ | @deleted@).
--
-- -   @strategy@ - The strategy of the placement group (@cluster@ |
--     @spread@ | @partition@).
--
-- -   @tag:\<key>@ - The key\/value combination of a tag assigned to the
--     resource. Use the tag key in the filter name and the tag value as
--     the filter value. For example, to find all resources that have a tag
--     with the key @Owner@ and the value @TeamA@, specify @tag:Owner@ for
--     the filter name and @TeamA@ for the filter value.
--
-- -   @tag-key@ - The key of a tag assigned to the resource. Use this
--     filter to find all resources that have a tag with a specific key,
--     regardless of the tag value.
--
-- 'groupIds', 'describePlacementGroups_groupIds' - The IDs of the placement groups.
--
-- 'groupNames', 'describePlacementGroups_groupNames' - The names of the placement groups.
--
-- Default: Describes all your placement groups, or only those otherwise
-- specified.
newDescribePlacementGroups ::
  DescribePlacementGroups
newDescribePlacementGroups :: DescribePlacementGroups
newDescribePlacementGroups =
  DescribePlacementGroups'
    { $sel:dryRun:DescribePlacementGroups' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:DescribePlacementGroups' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:groupIds:DescribePlacementGroups' :: Maybe [Text]
groupIds = forall a. Maybe a
Prelude.Nothing,
      $sel:groupNames:DescribePlacementGroups' :: Maybe [Text]
groupNames = forall a. Maybe a
Prelude.Nothing
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
describePlacementGroups_dryRun :: Lens.Lens' DescribePlacementGroups (Prelude.Maybe Prelude.Bool)
describePlacementGroups_dryRun :: Lens' DescribePlacementGroups (Maybe Bool)
describePlacementGroups_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribePlacementGroups' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DescribePlacementGroups
s@DescribePlacementGroups' {} Maybe Bool
a -> DescribePlacementGroups
s {$sel:dryRun:DescribePlacementGroups' :: Maybe Bool
dryRun = Maybe Bool
a} :: DescribePlacementGroups)

-- | The filters.
--
-- -   @group-name@ - The name of the placement group.
--
-- -   @group-arn@ - The Amazon Resource Name (ARN) of the placement group.
--
-- -   @spread-level@ - The spread level for the placement group (@host@ |
--     @rack@).
--
-- -   @state@ - The state of the placement group (@pending@ | @available@
--     | @deleting@ | @deleted@).
--
-- -   @strategy@ - The strategy of the placement group (@cluster@ |
--     @spread@ | @partition@).
--
-- -   @tag:\<key>@ - The key\/value combination of a tag assigned to the
--     resource. Use the tag key in the filter name and the tag value as
--     the filter value. For example, to find all resources that have a tag
--     with the key @Owner@ and the value @TeamA@, specify @tag:Owner@ for
--     the filter name and @TeamA@ for the filter value.
--
-- -   @tag-key@ - The key of a tag assigned to the resource. Use this
--     filter to find all resources that have a tag with a specific key,
--     regardless of the tag value.
describePlacementGroups_filters :: Lens.Lens' DescribePlacementGroups (Prelude.Maybe [Filter])
describePlacementGroups_filters :: Lens' DescribePlacementGroups (Maybe [Filter])
describePlacementGroups_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribePlacementGroups' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: DescribePlacementGroups
s@DescribePlacementGroups' {} Maybe [Filter]
a -> DescribePlacementGroups
s {$sel:filters:DescribePlacementGroups' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: DescribePlacementGroups) 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 IDs of the placement groups.
describePlacementGroups_groupIds :: Lens.Lens' DescribePlacementGroups (Prelude.Maybe [Prelude.Text])
describePlacementGroups_groupIds :: Lens' DescribePlacementGroups (Maybe [Text])
describePlacementGroups_groupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribePlacementGroups' {Maybe [Text]
groupIds :: Maybe [Text]
$sel:groupIds:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Text]
groupIds} -> Maybe [Text]
groupIds) (\s :: DescribePlacementGroups
s@DescribePlacementGroups' {} Maybe [Text]
a -> DescribePlacementGroups
s {$sel:groupIds:DescribePlacementGroups' :: Maybe [Text]
groupIds = Maybe [Text]
a} :: DescribePlacementGroups) 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 names of the placement groups.
--
-- Default: Describes all your placement groups, or only those otherwise
-- specified.
describePlacementGroups_groupNames :: Lens.Lens' DescribePlacementGroups (Prelude.Maybe [Prelude.Text])
describePlacementGroups_groupNames :: Lens' DescribePlacementGroups (Maybe [Text])
describePlacementGroups_groupNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribePlacementGroups' {Maybe [Text]
groupNames :: Maybe [Text]
$sel:groupNames:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Text]
groupNames} -> Maybe [Text]
groupNames) (\s :: DescribePlacementGroups
s@DescribePlacementGroups' {} Maybe [Text]
a -> DescribePlacementGroups
s {$sel:groupNames:DescribePlacementGroups' :: Maybe [Text]
groupNames = Maybe [Text]
a} :: DescribePlacementGroups) 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

instance Core.AWSRequest DescribePlacementGroups where
  type
    AWSResponse DescribePlacementGroups =
      DescribePlacementGroupsResponse
  request :: (Service -> Service)
-> DescribePlacementGroups -> Request DescribePlacementGroups
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 DescribePlacementGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribePlacementGroups)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [PlacementGroup] -> Int -> DescribePlacementGroupsResponse
DescribePlacementGroupsResponse'
            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
"placementGroupSet"
                            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 (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                        )
            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 DescribePlacementGroups where
  hashWithSalt :: Int -> DescribePlacementGroups -> Int
hashWithSalt Int
_salt DescribePlacementGroups' {Maybe Bool
Maybe [Text]
Maybe [Filter]
groupNames :: Maybe [Text]
groupIds :: Maybe [Text]
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:groupNames:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Text]
$sel:groupIds:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Text]
$sel:filters:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Filter]
$sel:dryRun:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
groupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
groupNames

instance Prelude.NFData DescribePlacementGroups where
  rnf :: DescribePlacementGroups -> ()
rnf DescribePlacementGroups' {Maybe Bool
Maybe [Text]
Maybe [Filter]
groupNames :: Maybe [Text]
groupIds :: Maybe [Text]
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:groupNames:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Text]
$sel:groupIds:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Text]
$sel:filters:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Filter]
$sel:dryRun:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      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 [Text]
groupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
groupNames

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

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

instance Data.ToQuery DescribePlacementGroups where
  toQuery :: DescribePlacementGroups -> QueryString
toQuery DescribePlacementGroups' {Maybe Bool
Maybe [Text]
Maybe [Filter]
groupNames :: Maybe [Text]
groupIds :: Maybe [Text]
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:groupNames:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Text]
$sel:groupIds:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Text]
$sel:filters:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe [Filter]
$sel:dryRun:DescribePlacementGroups' :: DescribePlacementGroups -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribePlacementGroups" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Filter" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Filter]
filters),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"GroupId" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
groupIds),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"GroupName"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
groupNames
          )
      ]

-- | /See:/ 'newDescribePlacementGroupsResponse' smart constructor.
data DescribePlacementGroupsResponse = DescribePlacementGroupsResponse'
  { -- | Information about the placement groups.
    DescribePlacementGroupsResponse -> Maybe [PlacementGroup]
placementGroups :: Prelude.Maybe [PlacementGroup],
    -- | The response's http status code.
    DescribePlacementGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribePlacementGroupsResponse
-> DescribePlacementGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribePlacementGroupsResponse
-> DescribePlacementGroupsResponse -> Bool
$c/= :: DescribePlacementGroupsResponse
-> DescribePlacementGroupsResponse -> Bool
== :: DescribePlacementGroupsResponse
-> DescribePlacementGroupsResponse -> Bool
$c== :: DescribePlacementGroupsResponse
-> DescribePlacementGroupsResponse -> Bool
Prelude.Eq, ReadPrec [DescribePlacementGroupsResponse]
ReadPrec DescribePlacementGroupsResponse
Int -> ReadS DescribePlacementGroupsResponse
ReadS [DescribePlacementGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribePlacementGroupsResponse]
$creadListPrec :: ReadPrec [DescribePlacementGroupsResponse]
readPrec :: ReadPrec DescribePlacementGroupsResponse
$creadPrec :: ReadPrec DescribePlacementGroupsResponse
readList :: ReadS [DescribePlacementGroupsResponse]
$creadList :: ReadS [DescribePlacementGroupsResponse]
readsPrec :: Int -> ReadS DescribePlacementGroupsResponse
$creadsPrec :: Int -> ReadS DescribePlacementGroupsResponse
Prelude.Read, Int -> DescribePlacementGroupsResponse -> ShowS
[DescribePlacementGroupsResponse] -> ShowS
DescribePlacementGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribePlacementGroupsResponse] -> ShowS
$cshowList :: [DescribePlacementGroupsResponse] -> ShowS
show :: DescribePlacementGroupsResponse -> String
$cshow :: DescribePlacementGroupsResponse -> String
showsPrec :: Int -> DescribePlacementGroupsResponse -> ShowS
$cshowsPrec :: Int -> DescribePlacementGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribePlacementGroupsResponse x
-> DescribePlacementGroupsResponse
forall x.
DescribePlacementGroupsResponse
-> Rep DescribePlacementGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribePlacementGroupsResponse x
-> DescribePlacementGroupsResponse
$cfrom :: forall x.
DescribePlacementGroupsResponse
-> Rep DescribePlacementGroupsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribePlacementGroupsResponse' 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:
--
-- 'placementGroups', 'describePlacementGroupsResponse_placementGroups' - Information about the placement groups.
--
-- 'httpStatus', 'describePlacementGroupsResponse_httpStatus' - The response's http status code.
newDescribePlacementGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribePlacementGroupsResponse
newDescribePlacementGroupsResponse :: Int -> DescribePlacementGroupsResponse
newDescribePlacementGroupsResponse Int
pHttpStatus_ =
  DescribePlacementGroupsResponse'
    { $sel:placementGroups:DescribePlacementGroupsResponse' :: Maybe [PlacementGroup]
placementGroups =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribePlacementGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the placement groups.
describePlacementGroupsResponse_placementGroups :: Lens.Lens' DescribePlacementGroupsResponse (Prelude.Maybe [PlacementGroup])
describePlacementGroupsResponse_placementGroups :: Lens' DescribePlacementGroupsResponse (Maybe [PlacementGroup])
describePlacementGroupsResponse_placementGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribePlacementGroupsResponse' {Maybe [PlacementGroup]
placementGroups :: Maybe [PlacementGroup]
$sel:placementGroups:DescribePlacementGroupsResponse' :: DescribePlacementGroupsResponse -> Maybe [PlacementGroup]
placementGroups} -> Maybe [PlacementGroup]
placementGroups) (\s :: DescribePlacementGroupsResponse
s@DescribePlacementGroupsResponse' {} Maybe [PlacementGroup]
a -> DescribePlacementGroupsResponse
s {$sel:placementGroups:DescribePlacementGroupsResponse' :: Maybe [PlacementGroup]
placementGroups = Maybe [PlacementGroup]
a} :: DescribePlacementGroupsResponse) 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.
describePlacementGroupsResponse_httpStatus :: Lens.Lens' DescribePlacementGroupsResponse Prelude.Int
describePlacementGroupsResponse_httpStatus :: Lens' DescribePlacementGroupsResponse Int
describePlacementGroupsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribePlacementGroupsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribePlacementGroupsResponse' :: DescribePlacementGroupsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribePlacementGroupsResponse
s@DescribePlacementGroupsResponse' {} Int
a -> DescribePlacementGroupsResponse
s {$sel:httpStatus:DescribePlacementGroupsResponse' :: Int
httpStatus = Int
a} :: DescribePlacementGroupsResponse)

instance
  Prelude.NFData
    DescribePlacementGroupsResponse
  where
  rnf :: DescribePlacementGroupsResponse -> ()
rnf DescribePlacementGroupsResponse' {Int
Maybe [PlacementGroup]
httpStatus :: Int
placementGroups :: Maybe [PlacementGroup]
$sel:httpStatus:DescribePlacementGroupsResponse' :: DescribePlacementGroupsResponse -> Int
$sel:placementGroups:DescribePlacementGroupsResponse' :: DescribePlacementGroupsResponse -> Maybe [PlacementGroup]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [PlacementGroup]
placementGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus