{-# 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.ListCommandInvocations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- An invocation is copy of a command sent to a specific managed node. A
-- command can apply to one or more managed nodes. A command invocation
-- applies to one managed node. For example, if a user runs @SendCommand@
-- against three managed nodes, then a command invocation is created for
-- each requested managed node ID. @ListCommandInvocations@ provide status
-- about command execution.
--
-- This operation returns paginated results.
module Amazonka.SSM.ListCommandInvocations
  ( -- * Creating a Request
    ListCommandInvocations (..),
    newListCommandInvocations,

    -- * Request Lenses
    listCommandInvocations_commandId,
    listCommandInvocations_details,
    listCommandInvocations_filters,
    listCommandInvocations_instanceId,
    listCommandInvocations_maxResults,
    listCommandInvocations_nextToken,

    -- * Destructuring the Response
    ListCommandInvocationsResponse (..),
    newListCommandInvocationsResponse,

    -- * Response Lenses
    listCommandInvocationsResponse_commandInvocations,
    listCommandInvocationsResponse_nextToken,
    listCommandInvocationsResponse_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:/ 'newListCommandInvocations' smart constructor.
data ListCommandInvocations = ListCommandInvocations'
  { -- | (Optional) The invocations for a specific command ID.
    ListCommandInvocations -> Maybe Text
commandId :: Prelude.Maybe Prelude.Text,
    -- | (Optional) If set this returns the response of the command executions
    -- and any command output. The default value is @false@.
    ListCommandInvocations -> Maybe Bool
details :: Prelude.Maybe Prelude.Bool,
    -- | (Optional) One or more filters. Use a filter to return a more specific
    -- list of results.
    ListCommandInvocations -> Maybe (NonEmpty CommandFilter)
filters :: Prelude.Maybe (Prelude.NonEmpty CommandFilter),
    -- | (Optional) The command execution details for a specific managed node ID.
    ListCommandInvocations -> 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.
    ListCommandInvocations -> 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.)
    ListCommandInvocations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListCommandInvocations -> ListCommandInvocations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCommandInvocations -> ListCommandInvocations -> Bool
$c/= :: ListCommandInvocations -> ListCommandInvocations -> Bool
== :: ListCommandInvocations -> ListCommandInvocations -> Bool
$c== :: ListCommandInvocations -> ListCommandInvocations -> Bool
Prelude.Eq, ReadPrec [ListCommandInvocations]
ReadPrec ListCommandInvocations
Int -> ReadS ListCommandInvocations
ReadS [ListCommandInvocations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCommandInvocations]
$creadListPrec :: ReadPrec [ListCommandInvocations]
readPrec :: ReadPrec ListCommandInvocations
$creadPrec :: ReadPrec ListCommandInvocations
readList :: ReadS [ListCommandInvocations]
$creadList :: ReadS [ListCommandInvocations]
readsPrec :: Int -> ReadS ListCommandInvocations
$creadsPrec :: Int -> ReadS ListCommandInvocations
Prelude.Read, Int -> ListCommandInvocations -> ShowS
[ListCommandInvocations] -> ShowS
ListCommandInvocations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCommandInvocations] -> ShowS
$cshowList :: [ListCommandInvocations] -> ShowS
show :: ListCommandInvocations -> String
$cshow :: ListCommandInvocations -> String
showsPrec :: Int -> ListCommandInvocations -> ShowS
$cshowsPrec :: Int -> ListCommandInvocations -> ShowS
Prelude.Show, forall x. Rep ListCommandInvocations x -> ListCommandInvocations
forall x. ListCommandInvocations -> Rep ListCommandInvocations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCommandInvocations x -> ListCommandInvocations
$cfrom :: forall x. ListCommandInvocations -> Rep ListCommandInvocations x
Prelude.Generic)

-- |
-- Create a value of 'ListCommandInvocations' 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', 'listCommandInvocations_commandId' - (Optional) The invocations for a specific command ID.
--
-- 'details', 'listCommandInvocations_details' - (Optional) If set this returns the response of the command executions
-- and any command output. The default value is @false@.
--
-- 'filters', 'listCommandInvocations_filters' - (Optional) One or more filters. Use a filter to return a more specific
-- list of results.
--
-- 'instanceId', 'listCommandInvocations_instanceId' - (Optional) The command execution details for a specific managed node ID.
--
-- 'maxResults', 'listCommandInvocations_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', 'listCommandInvocations_nextToken' - (Optional) The token for the next set of items to return. (You received
-- this token from a previous call.)
newListCommandInvocations ::
  ListCommandInvocations
newListCommandInvocations :: ListCommandInvocations
newListCommandInvocations =
  ListCommandInvocations'
    { $sel:commandId:ListCommandInvocations' :: Maybe Text
commandId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:details:ListCommandInvocations' :: Maybe Bool
details = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:ListCommandInvocations' :: Maybe (NonEmpty CommandFilter)
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:ListCommandInvocations' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListCommandInvocations' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCommandInvocations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | (Optional) The invocations for a specific command ID.
listCommandInvocations_commandId :: Lens.Lens' ListCommandInvocations (Prelude.Maybe Prelude.Text)
listCommandInvocations_commandId :: Lens' ListCommandInvocations (Maybe Text)
listCommandInvocations_commandId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommandInvocations' {Maybe Text
commandId :: Maybe Text
$sel:commandId:ListCommandInvocations' :: ListCommandInvocations -> Maybe Text
commandId} -> Maybe Text
commandId) (\s :: ListCommandInvocations
s@ListCommandInvocations' {} Maybe Text
a -> ListCommandInvocations
s {$sel:commandId:ListCommandInvocations' :: Maybe Text
commandId = Maybe Text
a} :: ListCommandInvocations)

-- | (Optional) If set this returns the response of the command executions
-- and any command output. The default value is @false@.
listCommandInvocations_details :: Lens.Lens' ListCommandInvocations (Prelude.Maybe Prelude.Bool)
listCommandInvocations_details :: Lens' ListCommandInvocations (Maybe Bool)
listCommandInvocations_details = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommandInvocations' {Maybe Bool
details :: Maybe Bool
$sel:details:ListCommandInvocations' :: ListCommandInvocations -> Maybe Bool
details} -> Maybe Bool
details) (\s :: ListCommandInvocations
s@ListCommandInvocations' {} Maybe Bool
a -> ListCommandInvocations
s {$sel:details:ListCommandInvocations' :: Maybe Bool
details = Maybe Bool
a} :: ListCommandInvocations)

-- | (Optional) One or more filters. Use a filter to return a more specific
-- list of results.
listCommandInvocations_filters :: Lens.Lens' ListCommandInvocations (Prelude.Maybe (Prelude.NonEmpty CommandFilter))
listCommandInvocations_filters :: Lens' ListCommandInvocations (Maybe (NonEmpty CommandFilter))
listCommandInvocations_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommandInvocations' {Maybe (NonEmpty CommandFilter)
filters :: Maybe (NonEmpty CommandFilter)
$sel:filters:ListCommandInvocations' :: ListCommandInvocations -> Maybe (NonEmpty CommandFilter)
filters} -> Maybe (NonEmpty CommandFilter)
filters) (\s :: ListCommandInvocations
s@ListCommandInvocations' {} Maybe (NonEmpty CommandFilter)
a -> ListCommandInvocations
s {$sel:filters:ListCommandInvocations' :: Maybe (NonEmpty CommandFilter)
filters = Maybe (NonEmpty CommandFilter)
a} :: ListCommandInvocations) 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 command execution details for a specific managed node ID.
listCommandInvocations_instanceId :: Lens.Lens' ListCommandInvocations (Prelude.Maybe Prelude.Text)
listCommandInvocations_instanceId :: Lens' ListCommandInvocations (Maybe Text)
listCommandInvocations_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommandInvocations' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:ListCommandInvocations' :: ListCommandInvocations -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: ListCommandInvocations
s@ListCommandInvocations' {} Maybe Text
a -> ListCommandInvocations
s {$sel:instanceId:ListCommandInvocations' :: Maybe Text
instanceId = Maybe Text
a} :: ListCommandInvocations)

-- | (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.
listCommandInvocations_maxResults :: Lens.Lens' ListCommandInvocations (Prelude.Maybe Prelude.Natural)
listCommandInvocations_maxResults :: Lens' ListCommandInvocations (Maybe Natural)
listCommandInvocations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommandInvocations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListCommandInvocations' :: ListCommandInvocations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListCommandInvocations
s@ListCommandInvocations' {} Maybe Natural
a -> ListCommandInvocations
s {$sel:maxResults:ListCommandInvocations' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListCommandInvocations)

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

instance Core.AWSPager ListCommandInvocations where
  page :: ListCommandInvocations
-> AWSResponse ListCommandInvocations
-> Maybe ListCommandInvocations
page ListCommandInvocations
rq AWSResponse ListCommandInvocations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListCommandInvocations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCommandInvocationsResponse (Maybe Text)
listCommandInvocationsResponse_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 ListCommandInvocations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCommandInvocationsResponse (Maybe [CommandInvocation])
listCommandInvocationsResponse_commandInvocations
            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.$ ListCommandInvocations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListCommandInvocations (Maybe Text)
listCommandInvocations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListCommandInvocations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCommandInvocationsResponse (Maybe Text)
listCommandInvocationsResponse_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 ListCommandInvocations where
  type
    AWSResponse ListCommandInvocations =
      ListCommandInvocationsResponse
  request :: (Service -> Service)
-> ListCommandInvocations -> Request ListCommandInvocations
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 ListCommandInvocations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListCommandInvocations)))
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 [CommandInvocation]
-> Maybe Text -> Int -> ListCommandInvocationsResponse
ListCommandInvocationsResponse'
            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
"CommandInvocations"
                            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 ListCommandInvocations where
  hashWithSalt :: Int -> ListCommandInvocations -> Int
hashWithSalt Int
_salt ListCommandInvocations' {Maybe Bool
Maybe Natural
Maybe (NonEmpty CommandFilter)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
instanceId :: Maybe Text
filters :: Maybe (NonEmpty CommandFilter)
details :: Maybe Bool
commandId :: Maybe Text
$sel:nextToken:ListCommandInvocations' :: ListCommandInvocations -> Maybe Text
$sel:maxResults:ListCommandInvocations' :: ListCommandInvocations -> Maybe Natural
$sel:instanceId:ListCommandInvocations' :: ListCommandInvocations -> Maybe Text
$sel:filters:ListCommandInvocations' :: ListCommandInvocations -> Maybe (NonEmpty CommandFilter)
$sel:details:ListCommandInvocations' :: ListCommandInvocations -> Maybe Bool
$sel:commandId:ListCommandInvocations' :: ListCommandInvocations -> 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 Bool
details
      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 ListCommandInvocations where
  rnf :: ListCommandInvocations -> ()
rnf ListCommandInvocations' {Maybe Bool
Maybe Natural
Maybe (NonEmpty CommandFilter)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
instanceId :: Maybe Text
filters :: Maybe (NonEmpty CommandFilter)
details :: Maybe Bool
commandId :: Maybe Text
$sel:nextToken:ListCommandInvocations' :: ListCommandInvocations -> Maybe Text
$sel:maxResults:ListCommandInvocations' :: ListCommandInvocations -> Maybe Natural
$sel:instanceId:ListCommandInvocations' :: ListCommandInvocations -> Maybe Text
$sel:filters:ListCommandInvocations' :: ListCommandInvocations -> Maybe (NonEmpty CommandFilter)
$sel:details:ListCommandInvocations' :: ListCommandInvocations -> Maybe Bool
$sel:commandId:ListCommandInvocations' :: ListCommandInvocations -> 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 Bool
details
      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 ListCommandInvocations where
  toHeaders :: ListCommandInvocations -> 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.ListCommandInvocations" ::
                          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 ListCommandInvocations where
  toJSON :: ListCommandInvocations -> Value
toJSON ListCommandInvocations' {Maybe Bool
Maybe Natural
Maybe (NonEmpty CommandFilter)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
instanceId :: Maybe Text
filters :: Maybe (NonEmpty CommandFilter)
details :: Maybe Bool
commandId :: Maybe Text
$sel:nextToken:ListCommandInvocations' :: ListCommandInvocations -> Maybe Text
$sel:maxResults:ListCommandInvocations' :: ListCommandInvocations -> Maybe Natural
$sel:instanceId:ListCommandInvocations' :: ListCommandInvocations -> Maybe Text
$sel:filters:ListCommandInvocations' :: ListCommandInvocations -> Maybe (NonEmpty CommandFilter)
$sel:details:ListCommandInvocations' :: ListCommandInvocations -> Maybe Bool
$sel:commandId:ListCommandInvocations' :: ListCommandInvocations -> 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
"Details" 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 Bool
details,
            (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 ListCommandInvocations where
  toPath :: ListCommandInvocations -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newListCommandInvocationsResponse' smart constructor.
data ListCommandInvocationsResponse = ListCommandInvocationsResponse'
  { -- | (Optional) A list of all invocations.
    ListCommandInvocationsResponse -> Maybe [CommandInvocation]
commandInvocations :: Prelude.Maybe [CommandInvocation],
    -- | (Optional) The token for the next set of items to return. (You received
    -- this token from a previous call.)
    ListCommandInvocationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListCommandInvocationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListCommandInvocationsResponse
-> ListCommandInvocationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCommandInvocationsResponse
-> ListCommandInvocationsResponse -> Bool
$c/= :: ListCommandInvocationsResponse
-> ListCommandInvocationsResponse -> Bool
== :: ListCommandInvocationsResponse
-> ListCommandInvocationsResponse -> Bool
$c== :: ListCommandInvocationsResponse
-> ListCommandInvocationsResponse -> Bool
Prelude.Eq, ReadPrec [ListCommandInvocationsResponse]
ReadPrec ListCommandInvocationsResponse
Int -> ReadS ListCommandInvocationsResponse
ReadS [ListCommandInvocationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCommandInvocationsResponse]
$creadListPrec :: ReadPrec [ListCommandInvocationsResponse]
readPrec :: ReadPrec ListCommandInvocationsResponse
$creadPrec :: ReadPrec ListCommandInvocationsResponse
readList :: ReadS [ListCommandInvocationsResponse]
$creadList :: ReadS [ListCommandInvocationsResponse]
readsPrec :: Int -> ReadS ListCommandInvocationsResponse
$creadsPrec :: Int -> ReadS ListCommandInvocationsResponse
Prelude.Read, Int -> ListCommandInvocationsResponse -> ShowS
[ListCommandInvocationsResponse] -> ShowS
ListCommandInvocationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCommandInvocationsResponse] -> ShowS
$cshowList :: [ListCommandInvocationsResponse] -> ShowS
show :: ListCommandInvocationsResponse -> String
$cshow :: ListCommandInvocationsResponse -> String
showsPrec :: Int -> ListCommandInvocationsResponse -> ShowS
$cshowsPrec :: Int -> ListCommandInvocationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListCommandInvocationsResponse x
-> ListCommandInvocationsResponse
forall x.
ListCommandInvocationsResponse
-> Rep ListCommandInvocationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListCommandInvocationsResponse x
-> ListCommandInvocationsResponse
$cfrom :: forall x.
ListCommandInvocationsResponse
-> Rep ListCommandInvocationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListCommandInvocationsResponse' 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:
--
-- 'commandInvocations', 'listCommandInvocationsResponse_commandInvocations' - (Optional) A list of all invocations.
--
-- 'nextToken', 'listCommandInvocationsResponse_nextToken' - (Optional) The token for the next set of items to return. (You received
-- this token from a previous call.)
--
-- 'httpStatus', 'listCommandInvocationsResponse_httpStatus' - The response's http status code.
newListCommandInvocationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListCommandInvocationsResponse
newListCommandInvocationsResponse :: Int -> ListCommandInvocationsResponse
newListCommandInvocationsResponse Int
pHttpStatus_ =
  ListCommandInvocationsResponse'
    { $sel:commandInvocations:ListCommandInvocationsResponse' :: Maybe [CommandInvocation]
commandInvocations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCommandInvocationsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListCommandInvocationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | (Optional) A list of all invocations.
listCommandInvocationsResponse_commandInvocations :: Lens.Lens' ListCommandInvocationsResponse (Prelude.Maybe [CommandInvocation])
listCommandInvocationsResponse_commandInvocations :: Lens' ListCommandInvocationsResponse (Maybe [CommandInvocation])
listCommandInvocationsResponse_commandInvocations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommandInvocationsResponse' {Maybe [CommandInvocation]
commandInvocations :: Maybe [CommandInvocation]
$sel:commandInvocations:ListCommandInvocationsResponse' :: ListCommandInvocationsResponse -> Maybe [CommandInvocation]
commandInvocations} -> Maybe [CommandInvocation]
commandInvocations) (\s :: ListCommandInvocationsResponse
s@ListCommandInvocationsResponse' {} Maybe [CommandInvocation]
a -> ListCommandInvocationsResponse
s {$sel:commandInvocations:ListCommandInvocationsResponse' :: Maybe [CommandInvocation]
commandInvocations = Maybe [CommandInvocation]
a} :: ListCommandInvocationsResponse) 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.)
listCommandInvocationsResponse_nextToken :: Lens.Lens' ListCommandInvocationsResponse (Prelude.Maybe Prelude.Text)
listCommandInvocationsResponse_nextToken :: Lens' ListCommandInvocationsResponse (Maybe Text)
listCommandInvocationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCommandInvocationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCommandInvocationsResponse' :: ListCommandInvocationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCommandInvocationsResponse
s@ListCommandInvocationsResponse' {} Maybe Text
a -> ListCommandInvocationsResponse
s {$sel:nextToken:ListCommandInvocationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListCommandInvocationsResponse)

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

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