{-# 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.GetAutomationExecution
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Get detailed information about a particular Automation execution.
module Amazonka.SSM.GetAutomationExecution
  ( -- * Creating a Request
    GetAutomationExecution (..),
    newGetAutomationExecution,

    -- * Request Lenses
    getAutomationExecution_automationExecutionId,

    -- * Destructuring the Response
    GetAutomationExecutionResponse (..),
    newGetAutomationExecutionResponse,

    -- * Response Lenses
    getAutomationExecutionResponse_automationExecution,
    getAutomationExecutionResponse_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:/ 'newGetAutomationExecution' smart constructor.
data GetAutomationExecution = GetAutomationExecution'
  { -- | The unique identifier for an existing automation execution to examine.
    -- The execution ID is returned by StartAutomationExecution when the
    -- execution of an Automation runbook is initiated.
    GetAutomationExecution -> Text
automationExecutionId :: Prelude.Text
  }
  deriving (GetAutomationExecution -> GetAutomationExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAutomationExecution -> GetAutomationExecution -> Bool
$c/= :: GetAutomationExecution -> GetAutomationExecution -> Bool
== :: GetAutomationExecution -> GetAutomationExecution -> Bool
$c== :: GetAutomationExecution -> GetAutomationExecution -> Bool
Prelude.Eq, ReadPrec [GetAutomationExecution]
ReadPrec GetAutomationExecution
Int -> ReadS GetAutomationExecution
ReadS [GetAutomationExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAutomationExecution]
$creadListPrec :: ReadPrec [GetAutomationExecution]
readPrec :: ReadPrec GetAutomationExecution
$creadPrec :: ReadPrec GetAutomationExecution
readList :: ReadS [GetAutomationExecution]
$creadList :: ReadS [GetAutomationExecution]
readsPrec :: Int -> ReadS GetAutomationExecution
$creadsPrec :: Int -> ReadS GetAutomationExecution
Prelude.Read, Int -> GetAutomationExecution -> ShowS
[GetAutomationExecution] -> ShowS
GetAutomationExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAutomationExecution] -> ShowS
$cshowList :: [GetAutomationExecution] -> ShowS
show :: GetAutomationExecution -> String
$cshow :: GetAutomationExecution -> String
showsPrec :: Int -> GetAutomationExecution -> ShowS
$cshowsPrec :: Int -> GetAutomationExecution -> ShowS
Prelude.Show, forall x. Rep GetAutomationExecution x -> GetAutomationExecution
forall x. GetAutomationExecution -> Rep GetAutomationExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAutomationExecution x -> GetAutomationExecution
$cfrom :: forall x. GetAutomationExecution -> Rep GetAutomationExecution x
Prelude.Generic)

-- |
-- Create a value of 'GetAutomationExecution' 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:
--
-- 'automationExecutionId', 'getAutomationExecution_automationExecutionId' - The unique identifier for an existing automation execution to examine.
-- The execution ID is returned by StartAutomationExecution when the
-- execution of an Automation runbook is initiated.
newGetAutomationExecution ::
  -- | 'automationExecutionId'
  Prelude.Text ->
  GetAutomationExecution
newGetAutomationExecution :: Text -> GetAutomationExecution
newGetAutomationExecution Text
pAutomationExecutionId_ =
  GetAutomationExecution'
    { $sel:automationExecutionId:GetAutomationExecution' :: Text
automationExecutionId =
        Text
pAutomationExecutionId_
    }

-- | The unique identifier for an existing automation execution to examine.
-- The execution ID is returned by StartAutomationExecution when the
-- execution of an Automation runbook is initiated.
getAutomationExecution_automationExecutionId :: Lens.Lens' GetAutomationExecution Prelude.Text
getAutomationExecution_automationExecutionId :: Lens' GetAutomationExecution Text
getAutomationExecution_automationExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutomationExecution' {Text
automationExecutionId :: Text
$sel:automationExecutionId:GetAutomationExecution' :: GetAutomationExecution -> Text
automationExecutionId} -> Text
automationExecutionId) (\s :: GetAutomationExecution
s@GetAutomationExecution' {} Text
a -> GetAutomationExecution
s {$sel:automationExecutionId:GetAutomationExecution' :: Text
automationExecutionId = Text
a} :: GetAutomationExecution)

instance Core.AWSRequest GetAutomationExecution where
  type
    AWSResponse GetAutomationExecution =
      GetAutomationExecutionResponse
  request :: (Service -> Service)
-> GetAutomationExecution -> Request GetAutomationExecution
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 GetAutomationExecution
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetAutomationExecution)))
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 AutomationExecution -> Int -> GetAutomationExecutionResponse
GetAutomationExecutionResponse'
            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
"AutomationExecution")
            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 GetAutomationExecution where
  hashWithSalt :: Int -> GetAutomationExecution -> Int
hashWithSalt Int
_salt GetAutomationExecution' {Text
automationExecutionId :: Text
$sel:automationExecutionId:GetAutomationExecution' :: GetAutomationExecution -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
automationExecutionId

instance Prelude.NFData GetAutomationExecution where
  rnf :: GetAutomationExecution -> ()
rnf GetAutomationExecution' {Text
automationExecutionId :: Text
$sel:automationExecutionId:GetAutomationExecution' :: GetAutomationExecution -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
automationExecutionId

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

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

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

-- | /See:/ 'newGetAutomationExecutionResponse' smart constructor.
data GetAutomationExecutionResponse = GetAutomationExecutionResponse'
  { -- | Detailed information about the current state of an automation execution.
    GetAutomationExecutionResponse -> Maybe AutomationExecution
automationExecution :: Prelude.Maybe AutomationExecution,
    -- | The response's http status code.
    GetAutomationExecutionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAutomationExecutionResponse
-> GetAutomationExecutionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAutomationExecutionResponse
-> GetAutomationExecutionResponse -> Bool
$c/= :: GetAutomationExecutionResponse
-> GetAutomationExecutionResponse -> Bool
== :: GetAutomationExecutionResponse
-> GetAutomationExecutionResponse -> Bool
$c== :: GetAutomationExecutionResponse
-> GetAutomationExecutionResponse -> Bool
Prelude.Eq, ReadPrec [GetAutomationExecutionResponse]
ReadPrec GetAutomationExecutionResponse
Int -> ReadS GetAutomationExecutionResponse
ReadS [GetAutomationExecutionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAutomationExecutionResponse]
$creadListPrec :: ReadPrec [GetAutomationExecutionResponse]
readPrec :: ReadPrec GetAutomationExecutionResponse
$creadPrec :: ReadPrec GetAutomationExecutionResponse
readList :: ReadS [GetAutomationExecutionResponse]
$creadList :: ReadS [GetAutomationExecutionResponse]
readsPrec :: Int -> ReadS GetAutomationExecutionResponse
$creadsPrec :: Int -> ReadS GetAutomationExecutionResponse
Prelude.Read, Int -> GetAutomationExecutionResponse -> ShowS
[GetAutomationExecutionResponse] -> ShowS
GetAutomationExecutionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAutomationExecutionResponse] -> ShowS
$cshowList :: [GetAutomationExecutionResponse] -> ShowS
show :: GetAutomationExecutionResponse -> String
$cshow :: GetAutomationExecutionResponse -> String
showsPrec :: Int -> GetAutomationExecutionResponse -> ShowS
$cshowsPrec :: Int -> GetAutomationExecutionResponse -> ShowS
Prelude.Show, forall x.
Rep GetAutomationExecutionResponse x
-> GetAutomationExecutionResponse
forall x.
GetAutomationExecutionResponse
-> Rep GetAutomationExecutionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAutomationExecutionResponse x
-> GetAutomationExecutionResponse
$cfrom :: forall x.
GetAutomationExecutionResponse
-> Rep GetAutomationExecutionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAutomationExecutionResponse' 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:
--
-- 'automationExecution', 'getAutomationExecutionResponse_automationExecution' - Detailed information about the current state of an automation execution.
--
-- 'httpStatus', 'getAutomationExecutionResponse_httpStatus' - The response's http status code.
newGetAutomationExecutionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAutomationExecutionResponse
newGetAutomationExecutionResponse :: Int -> GetAutomationExecutionResponse
newGetAutomationExecutionResponse Int
pHttpStatus_ =
  GetAutomationExecutionResponse'
    { $sel:automationExecution:GetAutomationExecutionResponse' :: Maybe AutomationExecution
automationExecution =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAutomationExecutionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Detailed information about the current state of an automation execution.
getAutomationExecutionResponse_automationExecution :: Lens.Lens' GetAutomationExecutionResponse (Prelude.Maybe AutomationExecution)
getAutomationExecutionResponse_automationExecution :: Lens' GetAutomationExecutionResponse (Maybe AutomationExecution)
getAutomationExecutionResponse_automationExecution = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAutomationExecutionResponse' {Maybe AutomationExecution
automationExecution :: Maybe AutomationExecution
$sel:automationExecution:GetAutomationExecutionResponse' :: GetAutomationExecutionResponse -> Maybe AutomationExecution
automationExecution} -> Maybe AutomationExecution
automationExecution) (\s :: GetAutomationExecutionResponse
s@GetAutomationExecutionResponse' {} Maybe AutomationExecution
a -> GetAutomationExecutionResponse
s {$sel:automationExecution:GetAutomationExecutionResponse' :: Maybe AutomationExecution
automationExecution = Maybe AutomationExecution
a} :: GetAutomationExecutionResponse)

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

instance
  Prelude.NFData
    GetAutomationExecutionResponse
  where
  rnf :: GetAutomationExecutionResponse -> ()
rnf GetAutomationExecutionResponse' {Int
Maybe AutomationExecution
httpStatus :: Int
automationExecution :: Maybe AutomationExecution
$sel:httpStatus:GetAutomationExecutionResponse' :: GetAutomationExecutionResponse -> Int
$sel:automationExecution:GetAutomationExecutionResponse' :: GetAutomationExecutionResponse -> Maybe AutomationExecution
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AutomationExecution
automationExecution
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus