{-# 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.SSM.ListCommands
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the commands requested by users of the Amazon Web Services
-- account.
--
-- This operation returns paginated results.
module Amazonka.SSM.ListCommands
  ( -- * Creating a Request
    ListCommands (..),
    newListCommands,

    -- * Request Lenses
    listCommands_commandId,
    listCommands_filters,
    listCommands_instanceId,
    listCommands_maxResults,
    listCommands_nextToken,

    -- * Destructuring the Response
    ListCommandsResponse (..),
    newListCommandsResponse,

    -- * Response Lenses
    listCommandsResponse_commands,
    listCommandsResponse_nextToken,
    listCommandsResponse_httpStatus,
  )
where

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
import Amazonka.SSM.Types

-- | /See:/ 'newListCommands' smart constructor.
data ListCommands = ListCommands'
  { -- | (Optional) If provided, lists only the specified command.
    ListCommands -> Maybe Text
commandId :: Prelude.Maybe Prelude.Text,
    -- | (Optional) One or more filters. Use a filter to return a more specific
    -- list of results.
    ListCommands -> Maybe (NonEmpty CommandFilter)
filters :: Prelude.Maybe (Prelude.NonEmpty CommandFilter),
    -- | (Optional) Lists commands issued against this managed node ID.
    --
    -- You can\'t specify a managed node ID in the same command that you
    -- specify @Status@ = @Pending@. This is because the command hasn\'t
    -- reached the managed node yet.
    ListCommands -> Maybe Text
instanceId :: Prelude.Maybe Prelude.Text,
    -- | (Optional) The maximum number of items to return for this call. The call
    -- also returns a token that you can specify in a subsequent call to get
    -- the next set of results.
    ListCommands -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | (Optional) The token for the next set of items to return. (You received
    -- this token from a previous call.)
    ListCommands -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListCommands -> ListCommands -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCommands -> ListCommands -> Bool
$c/= :: ListCommands -> ListCommands -> Bool
== :: ListCommands -> ListCommands -> Bool
$c== :: ListCommands -> ListCommands -> Bool
Prelude.Eq, ReadPrec [ListCommands]
ReadPrec ListCommands
Int -> ReadS ListCommands
ReadS [ListCommands]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCommands]
$creadListPrec :: ReadPrec [ListCommands]
readPrec :: ReadPrec ListCommands
$creadPrec :: ReadPrec ListCommands
readList :: ReadS [ListCommands]
$creadList :: ReadS [ListCommands]
readsPrec :: Int -> ReadS ListCommands
$creadsPrec :: Int -> ReadS ListCommands
Prelude.Read, Int -> ListCommands -> ShowS
[ListCommands] -> ShowS
ListCommands -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCommands] -> ShowS
$cshowList :: [ListCommands] -> ShowS
show :: ListCommands -> String
$cshow :: ListCommands -> String
showsPrec :: Int -> ListCommands -> ShowS
$cshowsPrec :: Int -> ListCommands -> ShowS
Prelude.Show, forall x. Rep ListCommands x -> ListCommands
forall x. ListCommands -> Rep ListCommands x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCommands x -> ListCommands
$cfrom :: forall x. ListCommands -> Rep ListCommands x
Prelude.Generic)

-- |
-- Create a value of 'ListCommands' 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:
--
-- 'commandId', 'listCommands_commandId' - (Optional) If provided, lists only the specified command.
--
-- 'filters', 'listCommands_filters' - (Optional) One or more filters. Use a filter to return a more specific
-- list of results.
--
-- 'instanceId', 'listCommands_instanceId' - (Optional) Lists commands issued against this managed node ID.
--
-- You can\'t specify a managed node ID in the same command that you
-- specify @Status@ = @Pending@. This is because the command hasn\'t
-- reached the managed node yet.
--
-- 'maxResults', 'listCommands_maxResults' - (Optional) The maximum number of items to return for this call. The call
-- also returns a token that you can specify in a subsequent call to get
-- the next set of results.
--
-- 'nextToken', 'listCommands_nextToken' - (Optional) The token for the next set of items to return. (You received
-- this token from a previous call.)
newListCommands ::
  ListCommands
newListCommands :: ListCommands
newListCommands =
  ListCommands'
    { $sel:commandId:ListCommands' :: Maybe Text
commandId = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:ListCommands' :: Maybe (NonEmpty CommandFilter)
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:ListCommands' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListCommands' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCommands' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | (Optional) If provided, lists only the specified command.
listCommands_commandId :: Lens.Lens' ListCommands (Prelude.Maybe Prelude.Text)
listCommands_commandId :: Lens' ListCommands (Maybe Text)
listCommands_commandId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommands' {Maybe Text
commandId :: Maybe Text
$sel:commandId:ListCommands' :: ListCommands -> Maybe Text
commandId} -> Maybe Text
commandId) (\s :: ListCommands
s@ListCommands' {} Maybe Text
a -> ListCommands
s {$sel:commandId:ListCommands' :: Maybe Text
commandId = Maybe Text
a} :: ListCommands)

-- | (Optional) One or more filters. Use a filter to return a more specific
-- list of results.
listCommands_filters :: Lens.Lens' ListCommands (Prelude.Maybe (Prelude.NonEmpty CommandFilter))
listCommands_filters :: Lens' ListCommands (Maybe (NonEmpty CommandFilter))
listCommands_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommands' {Maybe (NonEmpty CommandFilter)
filters :: Maybe (NonEmpty CommandFilter)
$sel:filters:ListCommands' :: ListCommands -> Maybe (NonEmpty CommandFilter)
filters} -> Maybe (NonEmpty CommandFilter)
filters) (\s :: ListCommands
s@ListCommands' {} Maybe (NonEmpty CommandFilter)
a -> ListCommands
s {$sel:filters:ListCommands' :: Maybe (NonEmpty CommandFilter)
filters = Maybe (NonEmpty CommandFilter)
a} :: ListCommands) 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

-- | (Optional) Lists commands issued against this managed node ID.
--
-- You can\'t specify a managed node ID in the same command that you
-- specify @Status@ = @Pending@. This is because the command hasn\'t
-- reached the managed node yet.
listCommands_instanceId :: Lens.Lens' ListCommands (Prelude.Maybe Prelude.Text)
listCommands_instanceId :: Lens' ListCommands (Maybe Text)
listCommands_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommands' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:ListCommands' :: ListCommands -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: ListCommands
s@ListCommands' {} Maybe Text
a -> ListCommands
s {$sel:instanceId:ListCommands' :: Maybe Text
instanceId = Maybe Text
a} :: ListCommands)

-- | (Optional) The maximum number of items to return for this call. The call
-- also returns a token that you can specify in a subsequent call to get
-- the next set of results.
listCommands_maxResults :: Lens.Lens' ListCommands (Prelude.Maybe Prelude.Natural)
listCommands_maxResults :: Lens' ListCommands (Maybe Natural)
listCommands_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommands' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListCommands' :: ListCommands -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListCommands
s@ListCommands' {} Maybe Natural
a -> ListCommands
s {$sel:maxResults:ListCommands' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListCommands)

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

instance Core.AWSPager ListCommands where
  page :: ListCommands -> AWSResponse ListCommands -> Maybe ListCommands
page ListCommands
rq AWSResponse ListCommands
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListCommands
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCommandsResponse (Maybe Text)
listCommandsResponse_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 ListCommands
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCommandsResponse (Maybe [Command])
listCommandsResponse_commands
            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.$ ListCommands
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListCommands (Maybe Text)
listCommands_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListCommands
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCommandsResponse (Maybe Text)
listCommandsResponse_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 ListCommands where
  type AWSResponse ListCommands = ListCommandsResponse
  request :: (Service -> Service) -> ListCommands -> Request ListCommands
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 ListCommands
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListCommands)))
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 -> ListCommandsResponse
ListCommandsResponse'
            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
"Commands" 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 ListCommands where
  hashWithSalt :: Int -> ListCommands -> Int
hashWithSalt Int
_salt ListCommands' {Maybe Natural
Maybe (NonEmpty CommandFilter)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
instanceId :: Maybe Text
filters :: Maybe (NonEmpty CommandFilter)
commandId :: Maybe Text
$sel:nextToken:ListCommands' :: ListCommands -> Maybe Text
$sel:maxResults:ListCommands' :: ListCommands -> Maybe Natural
$sel:instanceId:ListCommands' :: ListCommands -> Maybe Text
$sel:filters:ListCommands' :: ListCommands -> Maybe (NonEmpty CommandFilter)
$sel:commandId:ListCommands' :: ListCommands -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
commandId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty CommandFilter)
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListCommands where
  rnf :: ListCommands -> ()
rnf ListCommands' {Maybe Natural
Maybe (NonEmpty CommandFilter)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
instanceId :: Maybe Text
filters :: Maybe (NonEmpty CommandFilter)
commandId :: Maybe Text
$sel:nextToken:ListCommands' :: ListCommands -> Maybe Text
$sel:maxResults:ListCommands' :: ListCommands -> Maybe Natural
$sel:instanceId:ListCommands' :: ListCommands -> Maybe Text
$sel:filters:ListCommands' :: ListCommands -> Maybe (NonEmpty CommandFilter)
$sel:commandId:ListCommands' :: ListCommands -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
commandId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty CommandFilter)
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceId
      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

instance Data.ToHeaders ListCommands where
  toHeaders :: ListCommands -> 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
"AmazonSSM.ListCommands" :: 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 ListCommands where
  toJSON :: ListCommands -> Value
toJSON ListCommands' {Maybe Natural
Maybe (NonEmpty CommandFilter)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
instanceId :: Maybe Text
filters :: Maybe (NonEmpty CommandFilter)
commandId :: Maybe Text
$sel:nextToken:ListCommands' :: ListCommands -> Maybe Text
$sel:maxResults:ListCommands' :: ListCommands -> Maybe Natural
$sel:instanceId:ListCommands' :: ListCommands -> Maybe Text
$sel:filters:ListCommands' :: ListCommands -> Maybe (NonEmpty CommandFilter)
$sel:commandId:ListCommands' :: ListCommands -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CommandId" 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
commandId,
            (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 (NonEmpty CommandFilter)
filters,
            (Key
"InstanceId" 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
instanceId,
            (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
          ]
      )

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

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

-- | /See:/ 'newListCommandsResponse' smart constructor.
data ListCommandsResponse = ListCommandsResponse'
  { -- | (Optional) The list of commands requested by the user.
    ListCommandsResponse -> Maybe [Command]
commands :: Prelude.Maybe [Command],
    -- | (Optional) The token for the next set of items to return. (You received
    -- this token from a previous call.)
    ListCommandsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListCommandsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListCommandsResponse -> ListCommandsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCommandsResponse -> ListCommandsResponse -> Bool
$c/= :: ListCommandsResponse -> ListCommandsResponse -> Bool
== :: ListCommandsResponse -> ListCommandsResponse -> Bool
$c== :: ListCommandsResponse -> ListCommandsResponse -> Bool
Prelude.Eq, Int -> ListCommandsResponse -> ShowS
[ListCommandsResponse] -> ShowS
ListCommandsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCommandsResponse] -> ShowS
$cshowList :: [ListCommandsResponse] -> ShowS
show :: ListCommandsResponse -> String
$cshow :: ListCommandsResponse -> String
showsPrec :: Int -> ListCommandsResponse -> ShowS
$cshowsPrec :: Int -> ListCommandsResponse -> ShowS
Prelude.Show, forall x. Rep ListCommandsResponse x -> ListCommandsResponse
forall x. ListCommandsResponse -> Rep ListCommandsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCommandsResponse x -> ListCommandsResponse
$cfrom :: forall x. ListCommandsResponse -> Rep ListCommandsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListCommandsResponse' 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:
--
-- 'commands', 'listCommandsResponse_commands' - (Optional) The list of commands requested by the user.
--
-- 'nextToken', 'listCommandsResponse_nextToken' - (Optional) The token for the next set of items to return. (You received
-- this token from a previous call.)
--
-- 'httpStatus', 'listCommandsResponse_httpStatus' - The response's http status code.
newListCommandsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListCommandsResponse
newListCommandsResponse :: Int -> ListCommandsResponse
newListCommandsResponse Int
pHttpStatus_ =
  ListCommandsResponse'
    { $sel:commands:ListCommandsResponse' :: Maybe [Command]
commands = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCommandsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListCommandsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | (Optional) The list of commands requested by the user.
listCommandsResponse_commands :: Lens.Lens' ListCommandsResponse (Prelude.Maybe [Command])
listCommandsResponse_commands :: Lens' ListCommandsResponse (Maybe [Command])
listCommandsResponse_commands = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommandsResponse' {Maybe [Command]
commands :: Maybe [Command]
$sel:commands:ListCommandsResponse' :: ListCommandsResponse -> Maybe [Command]
commands} -> Maybe [Command]
commands) (\s :: ListCommandsResponse
s@ListCommandsResponse' {} Maybe [Command]
a -> ListCommandsResponse
s {$sel:commands:ListCommandsResponse' :: Maybe [Command]
commands = Maybe [Command]
a} :: ListCommandsResponse) 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

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

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

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