{-# 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.EMR.ListInstanceGroups
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides all available details about the instance groups in a cluster.
--
-- This operation returns paginated results.
module Amazonka.EMR.ListInstanceGroups
  ( -- * Creating a Request
    ListInstanceGroups (..),
    newListInstanceGroups,

    -- * Request Lenses
    listInstanceGroups_marker,
    listInstanceGroups_clusterId,

    -- * Destructuring the Response
    ListInstanceGroupsResponse (..),
    newListInstanceGroupsResponse,

    -- * Response Lenses
    listInstanceGroupsResponse_instanceGroups,
    listInstanceGroupsResponse_marker,
    listInstanceGroupsResponse_httpStatus,
  )
where

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

-- | This input determines which instance groups to retrieve.
--
-- /See:/ 'newListInstanceGroups' smart constructor.
data ListInstanceGroups = ListInstanceGroups'
  { -- | The pagination token that indicates the next set of results to retrieve.
    ListInstanceGroups -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the cluster for which to list the instance groups.
    ListInstanceGroups -> Text
clusterId :: Prelude.Text
  }
  deriving (ListInstanceGroups -> ListInstanceGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListInstanceGroups -> ListInstanceGroups -> Bool
$c/= :: ListInstanceGroups -> ListInstanceGroups -> Bool
== :: ListInstanceGroups -> ListInstanceGroups -> Bool
$c== :: ListInstanceGroups -> ListInstanceGroups -> Bool
Prelude.Eq, ReadPrec [ListInstanceGroups]
ReadPrec ListInstanceGroups
Int -> ReadS ListInstanceGroups
ReadS [ListInstanceGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListInstanceGroups]
$creadListPrec :: ReadPrec [ListInstanceGroups]
readPrec :: ReadPrec ListInstanceGroups
$creadPrec :: ReadPrec ListInstanceGroups
readList :: ReadS [ListInstanceGroups]
$creadList :: ReadS [ListInstanceGroups]
readsPrec :: Int -> ReadS ListInstanceGroups
$creadsPrec :: Int -> ReadS ListInstanceGroups
Prelude.Read, Int -> ListInstanceGroups -> ShowS
[ListInstanceGroups] -> ShowS
ListInstanceGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListInstanceGroups] -> ShowS
$cshowList :: [ListInstanceGroups] -> ShowS
show :: ListInstanceGroups -> String
$cshow :: ListInstanceGroups -> String
showsPrec :: Int -> ListInstanceGroups -> ShowS
$cshowsPrec :: Int -> ListInstanceGroups -> ShowS
Prelude.Show, forall x. Rep ListInstanceGroups x -> ListInstanceGroups
forall x. ListInstanceGroups -> Rep ListInstanceGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListInstanceGroups x -> ListInstanceGroups
$cfrom :: forall x. ListInstanceGroups -> Rep ListInstanceGroups x
Prelude.Generic)

-- |
-- Create a value of 'ListInstanceGroups' 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:
--
-- 'marker', 'listInstanceGroups_marker' - The pagination token that indicates the next set of results to retrieve.
--
-- 'clusterId', 'listInstanceGroups_clusterId' - The identifier of the cluster for which to list the instance groups.
newListInstanceGroups ::
  -- | 'clusterId'
  Prelude.Text ->
  ListInstanceGroups
newListInstanceGroups :: Text -> ListInstanceGroups
newListInstanceGroups Text
pClusterId_ =
  ListInstanceGroups'
    { $sel:marker:ListInstanceGroups' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterId:ListInstanceGroups' :: Text
clusterId = Text
pClusterId_
    }

-- | The pagination token that indicates the next set of results to retrieve.
listInstanceGroups_marker :: Lens.Lens' ListInstanceGroups (Prelude.Maybe Prelude.Text)
listInstanceGroups_marker :: Lens' ListInstanceGroups (Maybe Text)
listInstanceGroups_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInstanceGroups' {Maybe Text
marker :: Maybe Text
$sel:marker:ListInstanceGroups' :: ListInstanceGroups -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListInstanceGroups
s@ListInstanceGroups' {} Maybe Text
a -> ListInstanceGroups
s {$sel:marker:ListInstanceGroups' :: Maybe Text
marker = Maybe Text
a} :: ListInstanceGroups)

-- | The identifier of the cluster for which to list the instance groups.
listInstanceGroups_clusterId :: Lens.Lens' ListInstanceGroups Prelude.Text
listInstanceGroups_clusterId :: Lens' ListInstanceGroups Text
listInstanceGroups_clusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInstanceGroups' {Text
clusterId :: Text
$sel:clusterId:ListInstanceGroups' :: ListInstanceGroups -> Text
clusterId} -> Text
clusterId) (\s :: ListInstanceGroups
s@ListInstanceGroups' {} Text
a -> ListInstanceGroups
s {$sel:clusterId:ListInstanceGroups' :: Text
clusterId = Text
a} :: ListInstanceGroups)

instance Core.AWSPager ListInstanceGroups where
  page :: ListInstanceGroups
-> AWSResponse ListInstanceGroups -> Maybe ListInstanceGroups
page ListInstanceGroups
rq AWSResponse ListInstanceGroups
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListInstanceGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListInstanceGroupsResponse (Maybe Text)
listInstanceGroupsResponse_marker
            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 ListInstanceGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListInstanceGroupsResponse (Maybe [InstanceGroup])
listInstanceGroupsResponse_instanceGroups
            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
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListInstanceGroups
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListInstanceGroups (Maybe Text)
listInstanceGroups_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListInstanceGroups
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListInstanceGroupsResponse (Maybe Text)
listInstanceGroupsResponse_marker
          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 ListInstanceGroups where
  type
    AWSResponse ListInstanceGroups =
      ListInstanceGroupsResponse
  request :: (Service -> Service)
-> ListInstanceGroups -> Request ListInstanceGroups
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 ListInstanceGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListInstanceGroups)))
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 [InstanceGroup]
-> Maybe Text -> Int -> ListInstanceGroupsResponse
ListInstanceGroupsResponse'
            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
"InstanceGroups" 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
"Marker")
            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 ListInstanceGroups where
  hashWithSalt :: Int -> ListInstanceGroups -> Int
hashWithSalt Int
_salt ListInstanceGroups' {Maybe Text
Text
clusterId :: Text
marker :: Maybe Text
$sel:clusterId:ListInstanceGroups' :: ListInstanceGroups -> Text
$sel:marker:ListInstanceGroups' :: ListInstanceGroups -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterId

instance Prelude.NFData ListInstanceGroups where
  rnf :: ListInstanceGroups -> ()
rnf ListInstanceGroups' {Maybe Text
Text
clusterId :: Text
marker :: Maybe Text
$sel:clusterId:ListInstanceGroups' :: ListInstanceGroups -> Text
$sel:marker:ListInstanceGroups' :: ListInstanceGroups -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clusterId

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

instance Data.ToJSON ListInstanceGroups where
  toJSON :: ListInstanceGroups -> Value
toJSON ListInstanceGroups' {Maybe Text
Text
clusterId :: Text
marker :: Maybe Text
$sel:clusterId:ListInstanceGroups' :: ListInstanceGroups -> Text
$sel:marker:ListInstanceGroups' :: ListInstanceGroups -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Marker" 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
marker,
            forall a. a -> Maybe a
Prelude.Just (Key
"ClusterId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clusterId)
          ]
      )

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

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

-- | This input determines which instance groups to retrieve.
--
-- /See:/ 'newListInstanceGroupsResponse' smart constructor.
data ListInstanceGroupsResponse = ListInstanceGroupsResponse'
  { -- | The list of instance groups for the cluster and given filters.
    ListInstanceGroupsResponse -> Maybe [InstanceGroup]
instanceGroups :: Prelude.Maybe [InstanceGroup],
    -- | The pagination token that indicates the next set of results to retrieve.
    ListInstanceGroupsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListInstanceGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListInstanceGroupsResponse -> ListInstanceGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListInstanceGroupsResponse -> ListInstanceGroupsResponse -> Bool
$c/= :: ListInstanceGroupsResponse -> ListInstanceGroupsResponse -> Bool
== :: ListInstanceGroupsResponse -> ListInstanceGroupsResponse -> Bool
$c== :: ListInstanceGroupsResponse -> ListInstanceGroupsResponse -> Bool
Prelude.Eq, ReadPrec [ListInstanceGroupsResponse]
ReadPrec ListInstanceGroupsResponse
Int -> ReadS ListInstanceGroupsResponse
ReadS [ListInstanceGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListInstanceGroupsResponse]
$creadListPrec :: ReadPrec [ListInstanceGroupsResponse]
readPrec :: ReadPrec ListInstanceGroupsResponse
$creadPrec :: ReadPrec ListInstanceGroupsResponse
readList :: ReadS [ListInstanceGroupsResponse]
$creadList :: ReadS [ListInstanceGroupsResponse]
readsPrec :: Int -> ReadS ListInstanceGroupsResponse
$creadsPrec :: Int -> ReadS ListInstanceGroupsResponse
Prelude.Read, Int -> ListInstanceGroupsResponse -> ShowS
[ListInstanceGroupsResponse] -> ShowS
ListInstanceGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListInstanceGroupsResponse] -> ShowS
$cshowList :: [ListInstanceGroupsResponse] -> ShowS
show :: ListInstanceGroupsResponse -> String
$cshow :: ListInstanceGroupsResponse -> String
showsPrec :: Int -> ListInstanceGroupsResponse -> ShowS
$cshowsPrec :: Int -> ListInstanceGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep ListInstanceGroupsResponse x -> ListInstanceGroupsResponse
forall x.
ListInstanceGroupsResponse -> Rep ListInstanceGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListInstanceGroupsResponse x -> ListInstanceGroupsResponse
$cfrom :: forall x.
ListInstanceGroupsResponse -> Rep ListInstanceGroupsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListInstanceGroupsResponse' 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:
--
-- 'instanceGroups', 'listInstanceGroupsResponse_instanceGroups' - The list of instance groups for the cluster and given filters.
--
-- 'marker', 'listInstanceGroupsResponse_marker' - The pagination token that indicates the next set of results to retrieve.
--
-- 'httpStatus', 'listInstanceGroupsResponse_httpStatus' - The response's http status code.
newListInstanceGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListInstanceGroupsResponse
newListInstanceGroupsResponse :: Int -> ListInstanceGroupsResponse
newListInstanceGroupsResponse Int
pHttpStatus_ =
  ListInstanceGroupsResponse'
    { $sel:instanceGroups:ListInstanceGroupsResponse' :: Maybe [InstanceGroup]
instanceGroups =
        forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListInstanceGroupsResponse' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListInstanceGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of instance groups for the cluster and given filters.
listInstanceGroupsResponse_instanceGroups :: Lens.Lens' ListInstanceGroupsResponse (Prelude.Maybe [InstanceGroup])
listInstanceGroupsResponse_instanceGroups :: Lens' ListInstanceGroupsResponse (Maybe [InstanceGroup])
listInstanceGroupsResponse_instanceGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInstanceGroupsResponse' {Maybe [InstanceGroup]
instanceGroups :: Maybe [InstanceGroup]
$sel:instanceGroups:ListInstanceGroupsResponse' :: ListInstanceGroupsResponse -> Maybe [InstanceGroup]
instanceGroups} -> Maybe [InstanceGroup]
instanceGroups) (\s :: ListInstanceGroupsResponse
s@ListInstanceGroupsResponse' {} Maybe [InstanceGroup]
a -> ListInstanceGroupsResponse
s {$sel:instanceGroups:ListInstanceGroupsResponse' :: Maybe [InstanceGroup]
instanceGroups = Maybe [InstanceGroup]
a} :: ListInstanceGroupsResponse) 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 pagination token that indicates the next set of results to retrieve.
listInstanceGroupsResponse_marker :: Lens.Lens' ListInstanceGroupsResponse (Prelude.Maybe Prelude.Text)
listInstanceGroupsResponse_marker :: Lens' ListInstanceGroupsResponse (Maybe Text)
listInstanceGroupsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInstanceGroupsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:ListInstanceGroupsResponse' :: ListInstanceGroupsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListInstanceGroupsResponse
s@ListInstanceGroupsResponse' {} Maybe Text
a -> ListInstanceGroupsResponse
s {$sel:marker:ListInstanceGroupsResponse' :: Maybe Text
marker = Maybe Text
a} :: ListInstanceGroupsResponse)

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

instance Prelude.NFData ListInstanceGroupsResponse where
  rnf :: ListInstanceGroupsResponse -> ()
rnf ListInstanceGroupsResponse' {Int
Maybe [InstanceGroup]
Maybe Text
httpStatus :: Int
marker :: Maybe Text
instanceGroups :: Maybe [InstanceGroup]
$sel:httpStatus:ListInstanceGroupsResponse' :: ListInstanceGroupsResponse -> Int
$sel:marker:ListInstanceGroupsResponse' :: ListInstanceGroupsResponse -> Maybe Text
$sel:instanceGroups:ListInstanceGroupsResponse' :: ListInstanceGroupsResponse -> Maybe [InstanceGroup]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [InstanceGroup]
instanceGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus