{-# 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 #-}
module Amazonka.SSM.GetCommandInvocation
(
GetCommandInvocation (..),
newGetCommandInvocation,
getCommandInvocation_pluginName,
getCommandInvocation_commandId,
getCommandInvocation_instanceId,
GetCommandInvocationResponse (..),
newGetCommandInvocationResponse,
getCommandInvocationResponse_cloudWatchOutputConfig,
getCommandInvocationResponse_commandId,
getCommandInvocationResponse_comment,
getCommandInvocationResponse_documentName,
getCommandInvocationResponse_documentVersion,
getCommandInvocationResponse_executionElapsedTime,
getCommandInvocationResponse_executionEndDateTime,
getCommandInvocationResponse_executionStartDateTime,
getCommandInvocationResponse_instanceId,
getCommandInvocationResponse_pluginName,
getCommandInvocationResponse_responseCode,
getCommandInvocationResponse_standardErrorContent,
getCommandInvocationResponse_standardErrorUrl,
getCommandInvocationResponse_standardOutputContent,
getCommandInvocationResponse_standardOutputUrl,
getCommandInvocationResponse_status,
getCommandInvocationResponse_statusDetails,
getCommandInvocationResponse_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
data GetCommandInvocation = GetCommandInvocation'
{
GetCommandInvocation -> Maybe Text
pluginName :: Prelude.Maybe Prelude.Text,
GetCommandInvocation -> Text
commandId :: Prelude.Text,
GetCommandInvocation -> Text
instanceId :: Prelude.Text
}
deriving (GetCommandInvocation -> GetCommandInvocation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCommandInvocation -> GetCommandInvocation -> Bool
$c/= :: GetCommandInvocation -> GetCommandInvocation -> Bool
== :: GetCommandInvocation -> GetCommandInvocation -> Bool
$c== :: GetCommandInvocation -> GetCommandInvocation -> Bool
Prelude.Eq, ReadPrec [GetCommandInvocation]
ReadPrec GetCommandInvocation
Int -> ReadS GetCommandInvocation
ReadS [GetCommandInvocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCommandInvocation]
$creadListPrec :: ReadPrec [GetCommandInvocation]
readPrec :: ReadPrec GetCommandInvocation
$creadPrec :: ReadPrec GetCommandInvocation
readList :: ReadS [GetCommandInvocation]
$creadList :: ReadS [GetCommandInvocation]
readsPrec :: Int -> ReadS GetCommandInvocation
$creadsPrec :: Int -> ReadS GetCommandInvocation
Prelude.Read, Int -> GetCommandInvocation -> ShowS
[GetCommandInvocation] -> ShowS
GetCommandInvocation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCommandInvocation] -> ShowS
$cshowList :: [GetCommandInvocation] -> ShowS
show :: GetCommandInvocation -> String
$cshow :: GetCommandInvocation -> String
showsPrec :: Int -> GetCommandInvocation -> ShowS
$cshowsPrec :: Int -> GetCommandInvocation -> ShowS
Prelude.Show, forall x. Rep GetCommandInvocation x -> GetCommandInvocation
forall x. GetCommandInvocation -> Rep GetCommandInvocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCommandInvocation x -> GetCommandInvocation
$cfrom :: forall x. GetCommandInvocation -> Rep GetCommandInvocation x
Prelude.Generic)
newGetCommandInvocation ::
Prelude.Text ->
Prelude.Text ->
GetCommandInvocation
newGetCommandInvocation :: Text -> Text -> GetCommandInvocation
newGetCommandInvocation Text
pCommandId_ Text
pInstanceId_ =
GetCommandInvocation'
{ $sel:pluginName:GetCommandInvocation' :: Maybe Text
pluginName = forall a. Maybe a
Prelude.Nothing,
$sel:commandId:GetCommandInvocation' :: Text
commandId = Text
pCommandId_,
$sel:instanceId:GetCommandInvocation' :: Text
instanceId = Text
pInstanceId_
}
getCommandInvocation_pluginName :: Lens.Lens' GetCommandInvocation (Prelude.Maybe Prelude.Text)
getCommandInvocation_pluginName :: Lens' GetCommandInvocation (Maybe Text)
getCommandInvocation_pluginName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocation' {Maybe Text
pluginName :: Maybe Text
$sel:pluginName:GetCommandInvocation' :: GetCommandInvocation -> Maybe Text
pluginName} -> Maybe Text
pluginName) (\s :: GetCommandInvocation
s@GetCommandInvocation' {} Maybe Text
a -> GetCommandInvocation
s {$sel:pluginName:GetCommandInvocation' :: Maybe Text
pluginName = Maybe Text
a} :: GetCommandInvocation)
getCommandInvocation_commandId :: Lens.Lens' GetCommandInvocation Prelude.Text
getCommandInvocation_commandId :: Lens' GetCommandInvocation Text
getCommandInvocation_commandId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocation' {Text
commandId :: Text
$sel:commandId:GetCommandInvocation' :: GetCommandInvocation -> Text
commandId} -> Text
commandId) (\s :: GetCommandInvocation
s@GetCommandInvocation' {} Text
a -> GetCommandInvocation
s {$sel:commandId:GetCommandInvocation' :: Text
commandId = Text
a} :: GetCommandInvocation)
getCommandInvocation_instanceId :: Lens.Lens' GetCommandInvocation Prelude.Text
getCommandInvocation_instanceId :: Lens' GetCommandInvocation Text
getCommandInvocation_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocation' {Text
instanceId :: Text
$sel:instanceId:GetCommandInvocation' :: GetCommandInvocation -> Text
instanceId} -> Text
instanceId) (\s :: GetCommandInvocation
s@GetCommandInvocation' {} Text
a -> GetCommandInvocation
s {$sel:instanceId:GetCommandInvocation' :: Text
instanceId = Text
a} :: GetCommandInvocation)
instance Core.AWSRequest GetCommandInvocation where
type
AWSResponse GetCommandInvocation =
GetCommandInvocationResponse
request :: (Service -> Service)
-> GetCommandInvocation -> Request GetCommandInvocation
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 GetCommandInvocation
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse GetCommandInvocation)))
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 CloudWatchOutputConfig
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe CommandInvocationStatus
-> Maybe Text
-> Int
-> GetCommandInvocationResponse
GetCommandInvocationResponse'
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
"CloudWatchOutputConfig")
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
"CommandId")
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
"Comment")
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
"DocumentName")
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
"DocumentVersion")
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
"ExecutionElapsedTime")
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
"ExecutionEndDateTime")
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
"ExecutionStartDateTime")
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
"InstanceId")
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
"PluginName")
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
"ResponseCode")
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
"StandardErrorContent")
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
"StandardErrorUrl")
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
"StandardOutputContent")
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
"StandardOutputUrl")
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
"Status")
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
"StatusDetails")
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 GetCommandInvocation where
hashWithSalt :: Int -> GetCommandInvocation -> Int
hashWithSalt Int
_salt GetCommandInvocation' {Maybe Text
Text
instanceId :: Text
commandId :: Text
pluginName :: Maybe Text
$sel:instanceId:GetCommandInvocation' :: GetCommandInvocation -> Text
$sel:commandId:GetCommandInvocation' :: GetCommandInvocation -> Text
$sel:pluginName:GetCommandInvocation' :: GetCommandInvocation -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pluginName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
commandId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
instance Prelude.NFData GetCommandInvocation where
rnf :: GetCommandInvocation -> ()
rnf GetCommandInvocation' {Maybe Text
Text
instanceId :: Text
commandId :: Text
pluginName :: Maybe Text
$sel:instanceId:GetCommandInvocation' :: GetCommandInvocation -> Text
$sel:commandId:GetCommandInvocation' :: GetCommandInvocation -> Text
$sel:pluginName:GetCommandInvocation' :: GetCommandInvocation -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pluginName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
commandId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
instance Data.ToHeaders GetCommandInvocation where
toHeaders :: GetCommandInvocation -> 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.GetCommandInvocation" ::
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 GetCommandInvocation where
toJSON :: GetCommandInvocation -> Value
toJSON GetCommandInvocation' {Maybe Text
Text
instanceId :: Text
commandId :: Text
pluginName :: Maybe Text
$sel:instanceId:GetCommandInvocation' :: GetCommandInvocation -> Text
$sel:commandId:GetCommandInvocation' :: GetCommandInvocation -> Text
$sel:pluginName:GetCommandInvocation' :: GetCommandInvocation -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"PluginName" 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
pluginName,
forall a. a -> Maybe a
Prelude.Just (Key
"CommandId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
commandId),
forall a. a -> Maybe a
Prelude.Just (Key
"InstanceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
instanceId)
]
)
instance Data.ToPath GetCommandInvocation where
toPath :: GetCommandInvocation -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery GetCommandInvocation where
toQuery :: GetCommandInvocation -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetCommandInvocationResponse = GetCommandInvocationResponse'
{
GetCommandInvocationResponse -> Maybe CloudWatchOutputConfig
cloudWatchOutputConfig :: Prelude.Maybe CloudWatchOutputConfig,
GetCommandInvocationResponse -> Maybe Text
commandId :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
comment :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
documentName :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
documentVersion :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
executionElapsedTime :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
executionEndDateTime :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
executionStartDateTime :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
instanceId :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
pluginName :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Int
responseCode :: Prelude.Maybe Prelude.Int,
GetCommandInvocationResponse -> Maybe Text
standardErrorContent :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
standardErrorUrl :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
standardOutputContent :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe Text
standardOutputUrl :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Maybe CommandInvocationStatus
status :: Prelude.Maybe CommandInvocationStatus,
GetCommandInvocationResponse -> Maybe Text
statusDetails :: Prelude.Maybe Prelude.Text,
GetCommandInvocationResponse -> Int
httpStatus :: Prelude.Int
}
deriving (GetCommandInvocationResponse
-> GetCommandInvocationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCommandInvocationResponse
-> GetCommandInvocationResponse -> Bool
$c/= :: GetCommandInvocationResponse
-> GetCommandInvocationResponse -> Bool
== :: GetCommandInvocationResponse
-> GetCommandInvocationResponse -> Bool
$c== :: GetCommandInvocationResponse
-> GetCommandInvocationResponse -> Bool
Prelude.Eq, ReadPrec [GetCommandInvocationResponse]
ReadPrec GetCommandInvocationResponse
Int -> ReadS GetCommandInvocationResponse
ReadS [GetCommandInvocationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCommandInvocationResponse]
$creadListPrec :: ReadPrec [GetCommandInvocationResponse]
readPrec :: ReadPrec GetCommandInvocationResponse
$creadPrec :: ReadPrec GetCommandInvocationResponse
readList :: ReadS [GetCommandInvocationResponse]
$creadList :: ReadS [GetCommandInvocationResponse]
readsPrec :: Int -> ReadS GetCommandInvocationResponse
$creadsPrec :: Int -> ReadS GetCommandInvocationResponse
Prelude.Read, Int -> GetCommandInvocationResponse -> ShowS
[GetCommandInvocationResponse] -> ShowS
GetCommandInvocationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCommandInvocationResponse] -> ShowS
$cshowList :: [GetCommandInvocationResponse] -> ShowS
show :: GetCommandInvocationResponse -> String
$cshow :: GetCommandInvocationResponse -> String
showsPrec :: Int -> GetCommandInvocationResponse -> ShowS
$cshowsPrec :: Int -> GetCommandInvocationResponse -> ShowS
Prelude.Show, forall x.
Rep GetCommandInvocationResponse x -> GetCommandInvocationResponse
forall x.
GetCommandInvocationResponse -> Rep GetCommandInvocationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCommandInvocationResponse x -> GetCommandInvocationResponse
$cfrom :: forall x.
GetCommandInvocationResponse -> Rep GetCommandInvocationResponse x
Prelude.Generic)
newGetCommandInvocationResponse ::
Prelude.Int ->
GetCommandInvocationResponse
newGetCommandInvocationResponse :: Int -> GetCommandInvocationResponse
newGetCommandInvocationResponse Int
pHttpStatus_ =
GetCommandInvocationResponse'
{ $sel:cloudWatchOutputConfig:GetCommandInvocationResponse' :: Maybe CloudWatchOutputConfig
cloudWatchOutputConfig =
forall a. Maybe a
Prelude.Nothing,
$sel:commandId:GetCommandInvocationResponse' :: Maybe Text
commandId = forall a. Maybe a
Prelude.Nothing,
$sel:comment:GetCommandInvocationResponse' :: Maybe Text
comment = forall a. Maybe a
Prelude.Nothing,
$sel:documentName:GetCommandInvocationResponse' :: Maybe Text
documentName = forall a. Maybe a
Prelude.Nothing,
$sel:documentVersion:GetCommandInvocationResponse' :: Maybe Text
documentVersion = forall a. Maybe a
Prelude.Nothing,
$sel:executionElapsedTime:GetCommandInvocationResponse' :: Maybe Text
executionElapsedTime = forall a. Maybe a
Prelude.Nothing,
$sel:executionEndDateTime:GetCommandInvocationResponse' :: Maybe Text
executionEndDateTime = forall a. Maybe a
Prelude.Nothing,
$sel:executionStartDateTime:GetCommandInvocationResponse' :: Maybe Text
executionStartDateTime = forall a. Maybe a
Prelude.Nothing,
$sel:instanceId:GetCommandInvocationResponse' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
$sel:pluginName:GetCommandInvocationResponse' :: Maybe Text
pluginName = forall a. Maybe a
Prelude.Nothing,
$sel:responseCode:GetCommandInvocationResponse' :: Maybe Int
responseCode = forall a. Maybe a
Prelude.Nothing,
$sel:standardErrorContent:GetCommandInvocationResponse' :: Maybe Text
standardErrorContent = forall a. Maybe a
Prelude.Nothing,
$sel:standardErrorUrl:GetCommandInvocationResponse' :: Maybe Text
standardErrorUrl = forall a. Maybe a
Prelude.Nothing,
$sel:standardOutputContent:GetCommandInvocationResponse' :: Maybe Text
standardOutputContent = forall a. Maybe a
Prelude.Nothing,
$sel:standardOutputUrl:GetCommandInvocationResponse' :: Maybe Text
standardOutputUrl = forall a. Maybe a
Prelude.Nothing,
$sel:status:GetCommandInvocationResponse' :: Maybe CommandInvocationStatus
status = forall a. Maybe a
Prelude.Nothing,
$sel:statusDetails:GetCommandInvocationResponse' :: Maybe Text
statusDetails = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetCommandInvocationResponse' :: Int
httpStatus = Int
pHttpStatus_
}
getCommandInvocationResponse_cloudWatchOutputConfig :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe CloudWatchOutputConfig)
getCommandInvocationResponse_cloudWatchOutputConfig :: Lens' GetCommandInvocationResponse (Maybe CloudWatchOutputConfig)
getCommandInvocationResponse_cloudWatchOutputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe CloudWatchOutputConfig
cloudWatchOutputConfig :: Maybe CloudWatchOutputConfig
$sel:cloudWatchOutputConfig:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe CloudWatchOutputConfig
cloudWatchOutputConfig} -> Maybe CloudWatchOutputConfig
cloudWatchOutputConfig) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe CloudWatchOutputConfig
a -> GetCommandInvocationResponse
s {$sel:cloudWatchOutputConfig:GetCommandInvocationResponse' :: Maybe CloudWatchOutputConfig
cloudWatchOutputConfig = Maybe CloudWatchOutputConfig
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_commandId :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_commandId :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_commandId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
commandId :: Maybe Text
$sel:commandId:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
commandId} -> Maybe Text
commandId) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:commandId:GetCommandInvocationResponse' :: Maybe Text
commandId = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_comment :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_comment :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_comment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
comment :: Maybe Text
$sel:comment:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
comment} -> Maybe Text
comment) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:comment:GetCommandInvocationResponse' :: Maybe Text
comment = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_documentName :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_documentName :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_documentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
documentName :: Maybe Text
$sel:documentName:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
documentName} -> Maybe Text
documentName) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:documentName:GetCommandInvocationResponse' :: Maybe Text
documentName = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_documentVersion :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_documentVersion :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_documentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
documentVersion :: Maybe Text
$sel:documentVersion:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
documentVersion} -> Maybe Text
documentVersion) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:documentVersion:GetCommandInvocationResponse' :: Maybe Text
documentVersion = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_executionElapsedTime :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_executionElapsedTime :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_executionElapsedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
executionElapsedTime :: Maybe Text
$sel:executionElapsedTime:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
executionElapsedTime} -> Maybe Text
executionElapsedTime) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:executionElapsedTime:GetCommandInvocationResponse' :: Maybe Text
executionElapsedTime = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_executionEndDateTime :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_executionEndDateTime :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_executionEndDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
executionEndDateTime :: Maybe Text
$sel:executionEndDateTime:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
executionEndDateTime} -> Maybe Text
executionEndDateTime) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:executionEndDateTime:GetCommandInvocationResponse' :: Maybe Text
executionEndDateTime = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_executionStartDateTime :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_executionStartDateTime :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_executionStartDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
executionStartDateTime :: Maybe Text
$sel:executionStartDateTime:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
executionStartDateTime} -> Maybe Text
executionStartDateTime) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:executionStartDateTime:GetCommandInvocationResponse' :: Maybe Text
executionStartDateTime = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_instanceId :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_instanceId :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:instanceId:GetCommandInvocationResponse' :: Maybe Text
instanceId = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_pluginName :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_pluginName :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_pluginName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
pluginName :: Maybe Text
$sel:pluginName:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
pluginName} -> Maybe Text
pluginName) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:pluginName:GetCommandInvocationResponse' :: Maybe Text
pluginName = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_responseCode :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Int)
getCommandInvocationResponse_responseCode :: Lens' GetCommandInvocationResponse (Maybe Int)
getCommandInvocationResponse_responseCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Int
responseCode :: Maybe Int
$sel:responseCode:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Int
responseCode} -> Maybe Int
responseCode) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Int
a -> GetCommandInvocationResponse
s {$sel:responseCode:GetCommandInvocationResponse' :: Maybe Int
responseCode = Maybe Int
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_standardErrorContent :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_standardErrorContent :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_standardErrorContent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
standardErrorContent :: Maybe Text
$sel:standardErrorContent:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
standardErrorContent} -> Maybe Text
standardErrorContent) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:standardErrorContent:GetCommandInvocationResponse' :: Maybe Text
standardErrorContent = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_standardErrorUrl :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_standardErrorUrl :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_standardErrorUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
standardErrorUrl :: Maybe Text
$sel:standardErrorUrl:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
standardErrorUrl} -> Maybe Text
standardErrorUrl) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:standardErrorUrl:GetCommandInvocationResponse' :: Maybe Text
standardErrorUrl = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_standardOutputContent :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_standardOutputContent :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_standardOutputContent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
standardOutputContent :: Maybe Text
$sel:standardOutputContent:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
standardOutputContent} -> Maybe Text
standardOutputContent) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:standardOutputContent:GetCommandInvocationResponse' :: Maybe Text
standardOutputContent = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_standardOutputUrl :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_standardOutputUrl :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_standardOutputUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
standardOutputUrl :: Maybe Text
$sel:standardOutputUrl:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
standardOutputUrl} -> Maybe Text
standardOutputUrl) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:standardOutputUrl:GetCommandInvocationResponse' :: Maybe Text
standardOutputUrl = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_status :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe CommandInvocationStatus)
getCommandInvocationResponse_status :: Lens' GetCommandInvocationResponse (Maybe CommandInvocationStatus)
getCommandInvocationResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe CommandInvocationStatus
status :: Maybe CommandInvocationStatus
$sel:status:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe CommandInvocationStatus
status} -> Maybe CommandInvocationStatus
status) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe CommandInvocationStatus
a -> GetCommandInvocationResponse
s {$sel:status:GetCommandInvocationResponse' :: Maybe CommandInvocationStatus
status = Maybe CommandInvocationStatus
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_statusDetails :: Lens.Lens' GetCommandInvocationResponse (Prelude.Maybe Prelude.Text)
getCommandInvocationResponse_statusDetails :: Lens' GetCommandInvocationResponse (Maybe Text)
getCommandInvocationResponse_statusDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Maybe Text
statusDetails :: Maybe Text
$sel:statusDetails:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
statusDetails} -> Maybe Text
statusDetails) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Maybe Text
a -> GetCommandInvocationResponse
s {$sel:statusDetails:GetCommandInvocationResponse' :: Maybe Text
statusDetails = Maybe Text
a} :: GetCommandInvocationResponse)
getCommandInvocationResponse_httpStatus :: Lens.Lens' GetCommandInvocationResponse Prelude.Int
getCommandInvocationResponse_httpStatus :: Lens' GetCommandInvocationResponse Int
getCommandInvocationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommandInvocationResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetCommandInvocationResponse
s@GetCommandInvocationResponse' {} Int
a -> GetCommandInvocationResponse
s {$sel:httpStatus:GetCommandInvocationResponse' :: Int
httpStatus = Int
a} :: GetCommandInvocationResponse)
instance Prelude.NFData GetCommandInvocationResponse where
rnf :: GetCommandInvocationResponse -> ()
rnf GetCommandInvocationResponse' {Int
Maybe Int
Maybe Text
Maybe CloudWatchOutputConfig
Maybe CommandInvocationStatus
httpStatus :: Int
statusDetails :: Maybe Text
status :: Maybe CommandInvocationStatus
standardOutputUrl :: Maybe Text
standardOutputContent :: Maybe Text
standardErrorUrl :: Maybe Text
standardErrorContent :: Maybe Text
responseCode :: Maybe Int
pluginName :: Maybe Text
instanceId :: Maybe Text
executionStartDateTime :: Maybe Text
executionEndDateTime :: Maybe Text
executionElapsedTime :: Maybe Text
documentVersion :: Maybe Text
documentName :: Maybe Text
comment :: Maybe Text
commandId :: Maybe Text
cloudWatchOutputConfig :: Maybe CloudWatchOutputConfig
$sel:httpStatus:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Int
$sel:statusDetails:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:status:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe CommandInvocationStatus
$sel:standardOutputUrl:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:standardOutputContent:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:standardErrorUrl:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:standardErrorContent:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:responseCode:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Int
$sel:pluginName:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:instanceId:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:executionStartDateTime:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:executionEndDateTime:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:executionElapsedTime:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:documentVersion:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:documentName:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:comment:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:commandId:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe Text
$sel:cloudWatchOutputConfig:GetCommandInvocationResponse' :: GetCommandInvocationResponse -> Maybe CloudWatchOutputConfig
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe CloudWatchOutputConfig
cloudWatchOutputConfig
seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
comment
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
documentName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
documentVersion
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionElapsedTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionEndDateTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionStartDateTime
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 Text
pluginName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
responseCode
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
standardErrorContent
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
standardErrorUrl
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
standardOutputContent
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
standardOutputUrl
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CommandInvocationStatus
status
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusDetails
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus