{-# 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.ListBootstrapActions
-- 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 information about the bootstrap actions associated with a
-- cluster.
--
-- This operation returns paginated results.
module Amazonka.EMR.ListBootstrapActions
  ( -- * Creating a Request
    ListBootstrapActions (..),
    newListBootstrapActions,

    -- * Request Lenses
    listBootstrapActions_marker,
    listBootstrapActions_clusterId,

    -- * Destructuring the Response
    ListBootstrapActionsResponse (..),
    newListBootstrapActionsResponse,

    -- * Response Lenses
    listBootstrapActionsResponse_bootstrapActions,
    listBootstrapActionsResponse_marker,
    listBootstrapActionsResponse_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 bootstrap actions to retrieve.
--
-- /See:/ 'newListBootstrapActions' smart constructor.
data ListBootstrapActions = ListBootstrapActions'
  { -- | The pagination token that indicates the next set of results to retrieve.
    ListBootstrapActions -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The cluster identifier for the bootstrap actions to list.
    ListBootstrapActions -> Text
clusterId :: Prelude.Text
  }
  deriving (ListBootstrapActions -> ListBootstrapActions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBootstrapActions -> ListBootstrapActions -> Bool
$c/= :: ListBootstrapActions -> ListBootstrapActions -> Bool
== :: ListBootstrapActions -> ListBootstrapActions -> Bool
$c== :: ListBootstrapActions -> ListBootstrapActions -> Bool
Prelude.Eq, ReadPrec [ListBootstrapActions]
ReadPrec ListBootstrapActions
Int -> ReadS ListBootstrapActions
ReadS [ListBootstrapActions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBootstrapActions]
$creadListPrec :: ReadPrec [ListBootstrapActions]
readPrec :: ReadPrec ListBootstrapActions
$creadPrec :: ReadPrec ListBootstrapActions
readList :: ReadS [ListBootstrapActions]
$creadList :: ReadS [ListBootstrapActions]
readsPrec :: Int -> ReadS ListBootstrapActions
$creadsPrec :: Int -> ReadS ListBootstrapActions
Prelude.Read, Int -> ListBootstrapActions -> ShowS
[ListBootstrapActions] -> ShowS
ListBootstrapActions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBootstrapActions] -> ShowS
$cshowList :: [ListBootstrapActions] -> ShowS
show :: ListBootstrapActions -> String
$cshow :: ListBootstrapActions -> String
showsPrec :: Int -> ListBootstrapActions -> ShowS
$cshowsPrec :: Int -> ListBootstrapActions -> ShowS
Prelude.Show, forall x. Rep ListBootstrapActions x -> ListBootstrapActions
forall x. ListBootstrapActions -> Rep ListBootstrapActions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListBootstrapActions x -> ListBootstrapActions
$cfrom :: forall x. ListBootstrapActions -> Rep ListBootstrapActions x
Prelude.Generic)

-- |
-- Create a value of 'ListBootstrapActions' 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', 'listBootstrapActions_marker' - The pagination token that indicates the next set of results to retrieve.
--
-- 'clusterId', 'listBootstrapActions_clusterId' - The cluster identifier for the bootstrap actions to list.
newListBootstrapActions ::
  -- | 'clusterId'
  Prelude.Text ->
  ListBootstrapActions
newListBootstrapActions :: Text -> ListBootstrapActions
newListBootstrapActions Text
pClusterId_ =
  ListBootstrapActions'
    { $sel:marker:ListBootstrapActions' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterId:ListBootstrapActions' :: Text
clusterId = Text
pClusterId_
    }

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

-- | The cluster identifier for the bootstrap actions to list.
listBootstrapActions_clusterId :: Lens.Lens' ListBootstrapActions Prelude.Text
listBootstrapActions_clusterId :: Lens' ListBootstrapActions Text
listBootstrapActions_clusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBootstrapActions' {Text
clusterId :: Text
$sel:clusterId:ListBootstrapActions' :: ListBootstrapActions -> Text
clusterId} -> Text
clusterId) (\s :: ListBootstrapActions
s@ListBootstrapActions' {} Text
a -> ListBootstrapActions
s {$sel:clusterId:ListBootstrapActions' :: Text
clusterId = Text
a} :: ListBootstrapActions)

instance Core.AWSPager ListBootstrapActions where
  page :: ListBootstrapActions
-> AWSResponse ListBootstrapActions -> Maybe ListBootstrapActions
page ListBootstrapActions
rq AWSResponse ListBootstrapActions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListBootstrapActions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListBootstrapActionsResponse (Maybe Text)
listBootstrapActionsResponse_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 ListBootstrapActions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListBootstrapActionsResponse (Maybe [Command])
listBootstrapActionsResponse_bootstrapActions
            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.$ ListBootstrapActions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListBootstrapActions (Maybe Text)
listBootstrapActions_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListBootstrapActions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListBootstrapActionsResponse (Maybe Text)
listBootstrapActionsResponse_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 ListBootstrapActions where
  type
    AWSResponse ListBootstrapActions =
      ListBootstrapActionsResponse
  request :: (Service -> Service)
-> ListBootstrapActions -> Request ListBootstrapActions
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 ListBootstrapActions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListBootstrapActions)))
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 [Command]
-> Maybe Text -> Int -> ListBootstrapActionsResponse
ListBootstrapActionsResponse'
            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
"BootstrapActions"
                            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 ListBootstrapActions where
  hashWithSalt :: Int -> ListBootstrapActions -> Int
hashWithSalt Int
_salt ListBootstrapActions' {Maybe Text
Text
clusterId :: Text
marker :: Maybe Text
$sel:clusterId:ListBootstrapActions' :: ListBootstrapActions -> Text
$sel:marker:ListBootstrapActions' :: ListBootstrapActions -> 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 ListBootstrapActions where
  rnf :: ListBootstrapActions -> ()
rnf ListBootstrapActions' {Maybe Text
Text
clusterId :: Text
marker :: Maybe Text
$sel:clusterId:ListBootstrapActions' :: ListBootstrapActions -> Text
$sel:marker:ListBootstrapActions' :: ListBootstrapActions -> 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 ListBootstrapActions where
  toHeaders :: ListBootstrapActions -> 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.ListBootstrapActions" ::
                          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 ListBootstrapActions where
  toJSON :: ListBootstrapActions -> Value
toJSON ListBootstrapActions' {Maybe Text
Text
clusterId :: Text
marker :: Maybe Text
$sel:clusterId:ListBootstrapActions' :: ListBootstrapActions -> Text
$sel:marker:ListBootstrapActions' :: ListBootstrapActions -> 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 ListBootstrapActions where
  toPath :: ListBootstrapActions -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | This output contains the bootstrap actions detail.
--
-- /See:/ 'newListBootstrapActionsResponse' smart constructor.
data ListBootstrapActionsResponse = ListBootstrapActionsResponse'
  { -- | The bootstrap actions associated with the cluster.
    ListBootstrapActionsResponse -> Maybe [Command]
bootstrapActions :: Prelude.Maybe [Command],
    -- | The pagination token that indicates the next set of results to retrieve.
    ListBootstrapActionsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListBootstrapActionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListBootstrapActionsResponse
-> ListBootstrapActionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBootstrapActionsResponse
-> ListBootstrapActionsResponse -> Bool
$c/= :: ListBootstrapActionsResponse
-> ListBootstrapActionsResponse -> Bool
== :: ListBootstrapActionsResponse
-> ListBootstrapActionsResponse -> Bool
$c== :: ListBootstrapActionsResponse
-> ListBootstrapActionsResponse -> Bool
Prelude.Eq, ReadPrec [ListBootstrapActionsResponse]
ReadPrec ListBootstrapActionsResponse
Int -> ReadS ListBootstrapActionsResponse
ReadS [ListBootstrapActionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBootstrapActionsResponse]
$creadListPrec :: ReadPrec [ListBootstrapActionsResponse]
readPrec :: ReadPrec ListBootstrapActionsResponse
$creadPrec :: ReadPrec ListBootstrapActionsResponse
readList :: ReadS [ListBootstrapActionsResponse]
$creadList :: ReadS [ListBootstrapActionsResponse]
readsPrec :: Int -> ReadS ListBootstrapActionsResponse
$creadsPrec :: Int -> ReadS ListBootstrapActionsResponse
Prelude.Read, Int -> ListBootstrapActionsResponse -> ShowS
[ListBootstrapActionsResponse] -> ShowS
ListBootstrapActionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBootstrapActionsResponse] -> ShowS
$cshowList :: [ListBootstrapActionsResponse] -> ShowS
show :: ListBootstrapActionsResponse -> String
$cshow :: ListBootstrapActionsResponse -> String
showsPrec :: Int -> ListBootstrapActionsResponse -> ShowS
$cshowsPrec :: Int -> ListBootstrapActionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListBootstrapActionsResponse x -> ListBootstrapActionsResponse
forall x.
ListBootstrapActionsResponse -> Rep ListBootstrapActionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListBootstrapActionsResponse x -> ListBootstrapActionsResponse
$cfrom :: forall x.
ListBootstrapActionsResponse -> Rep ListBootstrapActionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListBootstrapActionsResponse' 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:
--
-- 'bootstrapActions', 'listBootstrapActionsResponse_bootstrapActions' - The bootstrap actions associated with the cluster.
--
-- 'marker', 'listBootstrapActionsResponse_marker' - The pagination token that indicates the next set of results to retrieve.
--
-- 'httpStatus', 'listBootstrapActionsResponse_httpStatus' - The response's http status code.
newListBootstrapActionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListBootstrapActionsResponse
newListBootstrapActionsResponse :: Int -> ListBootstrapActionsResponse
newListBootstrapActionsResponse Int
pHttpStatus_ =
  ListBootstrapActionsResponse'
    { $sel:bootstrapActions:ListBootstrapActionsResponse' :: Maybe [Command]
bootstrapActions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListBootstrapActionsResponse' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListBootstrapActionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The bootstrap actions associated with the cluster.
listBootstrapActionsResponse_bootstrapActions :: Lens.Lens' ListBootstrapActionsResponse (Prelude.Maybe [Command])
listBootstrapActionsResponse_bootstrapActions :: Lens' ListBootstrapActionsResponse (Maybe [Command])
listBootstrapActionsResponse_bootstrapActions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBootstrapActionsResponse' {Maybe [Command]
bootstrapActions :: Maybe [Command]
$sel:bootstrapActions:ListBootstrapActionsResponse' :: ListBootstrapActionsResponse -> Maybe [Command]
bootstrapActions} -> Maybe [Command]
bootstrapActions) (\s :: ListBootstrapActionsResponse
s@ListBootstrapActionsResponse' {} Maybe [Command]
a -> ListBootstrapActionsResponse
s {$sel:bootstrapActions:ListBootstrapActionsResponse' :: Maybe [Command]
bootstrapActions = Maybe [Command]
a} :: ListBootstrapActionsResponse) 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.
listBootstrapActionsResponse_marker :: Lens.Lens' ListBootstrapActionsResponse (Prelude.Maybe Prelude.Text)
listBootstrapActionsResponse_marker :: Lens' ListBootstrapActionsResponse (Maybe Text)
listBootstrapActionsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBootstrapActionsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:ListBootstrapActionsResponse' :: ListBootstrapActionsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListBootstrapActionsResponse
s@ListBootstrapActionsResponse' {} Maybe Text
a -> ListBootstrapActionsResponse
s {$sel:marker:ListBootstrapActionsResponse' :: Maybe Text
marker = Maybe Text
a} :: ListBootstrapActionsResponse)

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

instance Prelude.NFData ListBootstrapActionsResponse where
  rnf :: ListBootstrapActionsResponse -> ()
rnf ListBootstrapActionsResponse' {Int
Maybe [Command]
Maybe Text
httpStatus :: Int
marker :: Maybe Text
bootstrapActions :: Maybe [Command]
$sel:httpStatus:ListBootstrapActionsResponse' :: ListBootstrapActionsResponse -> Int
$sel:marker:ListBootstrapActionsResponse' :: ListBootstrapActionsResponse -> Maybe Text
$sel:bootstrapActions:ListBootstrapActionsResponse' :: ListBootstrapActionsResponse -> Maybe [Command]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Command]
bootstrapActions
      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