{-# 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.SSMIncidents.GetTimelineEvent
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a timeline event based on its ID and incident record.
module Amazonka.SSMIncidents.GetTimelineEvent
  ( -- * Creating a Request
    GetTimelineEvent (..),
    newGetTimelineEvent,

    -- * Request Lenses
    getTimelineEvent_eventId,
    getTimelineEvent_incidentRecordArn,

    -- * Destructuring the Response
    GetTimelineEventResponse (..),
    newGetTimelineEventResponse,

    -- * Response Lenses
    getTimelineEventResponse_httpStatus,
    getTimelineEventResponse_event,
  )
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.SSMIncidents.Types

-- | /See:/ 'newGetTimelineEvent' smart constructor.
data GetTimelineEvent = GetTimelineEvent'
  { -- | The ID of the event. You can get an event\'s ID when you create it, or
    -- by using @ListTimelineEvents@.
    GetTimelineEvent -> Text
eventId :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the incident that includes the
    -- timeline event.
    GetTimelineEvent -> Text
incidentRecordArn :: Prelude.Text
  }
  deriving (GetTimelineEvent -> GetTimelineEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTimelineEvent -> GetTimelineEvent -> Bool
$c/= :: GetTimelineEvent -> GetTimelineEvent -> Bool
== :: GetTimelineEvent -> GetTimelineEvent -> Bool
$c== :: GetTimelineEvent -> GetTimelineEvent -> Bool
Prelude.Eq, ReadPrec [GetTimelineEvent]
ReadPrec GetTimelineEvent
Int -> ReadS GetTimelineEvent
ReadS [GetTimelineEvent]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTimelineEvent]
$creadListPrec :: ReadPrec [GetTimelineEvent]
readPrec :: ReadPrec GetTimelineEvent
$creadPrec :: ReadPrec GetTimelineEvent
readList :: ReadS [GetTimelineEvent]
$creadList :: ReadS [GetTimelineEvent]
readsPrec :: Int -> ReadS GetTimelineEvent
$creadsPrec :: Int -> ReadS GetTimelineEvent
Prelude.Read, Int -> GetTimelineEvent -> ShowS
[GetTimelineEvent] -> ShowS
GetTimelineEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTimelineEvent] -> ShowS
$cshowList :: [GetTimelineEvent] -> ShowS
show :: GetTimelineEvent -> String
$cshow :: GetTimelineEvent -> String
showsPrec :: Int -> GetTimelineEvent -> ShowS
$cshowsPrec :: Int -> GetTimelineEvent -> ShowS
Prelude.Show, forall x. Rep GetTimelineEvent x -> GetTimelineEvent
forall x. GetTimelineEvent -> Rep GetTimelineEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTimelineEvent x -> GetTimelineEvent
$cfrom :: forall x. GetTimelineEvent -> Rep GetTimelineEvent x
Prelude.Generic)

-- |
-- Create a value of 'GetTimelineEvent' 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:
--
-- 'eventId', 'getTimelineEvent_eventId' - The ID of the event. You can get an event\'s ID when you create it, or
-- by using @ListTimelineEvents@.
--
-- 'incidentRecordArn', 'getTimelineEvent_incidentRecordArn' - The Amazon Resource Name (ARN) of the incident that includes the
-- timeline event.
newGetTimelineEvent ::
  -- | 'eventId'
  Prelude.Text ->
  -- | 'incidentRecordArn'
  Prelude.Text ->
  GetTimelineEvent
newGetTimelineEvent :: Text -> Text -> GetTimelineEvent
newGetTimelineEvent Text
pEventId_ Text
pIncidentRecordArn_ =
  GetTimelineEvent'
    { $sel:eventId:GetTimelineEvent' :: Text
eventId = Text
pEventId_,
      $sel:incidentRecordArn:GetTimelineEvent' :: Text
incidentRecordArn = Text
pIncidentRecordArn_
    }

-- | The ID of the event. You can get an event\'s ID when you create it, or
-- by using @ListTimelineEvents@.
getTimelineEvent_eventId :: Lens.Lens' GetTimelineEvent Prelude.Text
getTimelineEvent_eventId :: Lens' GetTimelineEvent Text
getTimelineEvent_eventId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTimelineEvent' {Text
eventId :: Text
$sel:eventId:GetTimelineEvent' :: GetTimelineEvent -> Text
eventId} -> Text
eventId) (\s :: GetTimelineEvent
s@GetTimelineEvent' {} Text
a -> GetTimelineEvent
s {$sel:eventId:GetTimelineEvent' :: Text
eventId = Text
a} :: GetTimelineEvent)

-- | The Amazon Resource Name (ARN) of the incident that includes the
-- timeline event.
getTimelineEvent_incidentRecordArn :: Lens.Lens' GetTimelineEvent Prelude.Text
getTimelineEvent_incidentRecordArn :: Lens' GetTimelineEvent Text
getTimelineEvent_incidentRecordArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTimelineEvent' {Text
incidentRecordArn :: Text
$sel:incidentRecordArn:GetTimelineEvent' :: GetTimelineEvent -> Text
incidentRecordArn} -> Text
incidentRecordArn) (\s :: GetTimelineEvent
s@GetTimelineEvent' {} Text
a -> GetTimelineEvent
s {$sel:incidentRecordArn:GetTimelineEvent' :: Text
incidentRecordArn = Text
a} :: GetTimelineEvent)

instance Core.AWSRequest GetTimelineEvent where
  type
    AWSResponse GetTimelineEvent =
      GetTimelineEventResponse
  request :: (Service -> Service)
-> GetTimelineEvent -> Request GetTimelineEvent
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetTimelineEvent
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetTimelineEvent)))
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 ->
          Int -> TimelineEvent -> GetTimelineEventResponse
GetTimelineEventResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"event")
      )

instance Prelude.Hashable GetTimelineEvent where
  hashWithSalt :: Int -> GetTimelineEvent -> Int
hashWithSalt Int
_salt GetTimelineEvent' {Text
incidentRecordArn :: Text
eventId :: Text
$sel:incidentRecordArn:GetTimelineEvent' :: GetTimelineEvent -> Text
$sel:eventId:GetTimelineEvent' :: GetTimelineEvent -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
eventId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
incidentRecordArn

instance Prelude.NFData GetTimelineEvent where
  rnf :: GetTimelineEvent -> ()
rnf GetTimelineEvent' {Text
incidentRecordArn :: Text
eventId :: Text
$sel:incidentRecordArn:GetTimelineEvent' :: GetTimelineEvent -> Text
$sel:eventId:GetTimelineEvent' :: GetTimelineEvent -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
eventId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
incidentRecordArn

instance Data.ToHeaders GetTimelineEvent where
  toHeaders :: GetTimelineEvent -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

instance Data.ToQuery GetTimelineEvent where
  toQuery :: GetTimelineEvent -> QueryString
toQuery GetTimelineEvent' {Text
incidentRecordArn :: Text
eventId :: Text
$sel:incidentRecordArn:GetTimelineEvent' :: GetTimelineEvent -> Text
$sel:eventId:GetTimelineEvent' :: GetTimelineEvent -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"eventId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
eventId,
        ByteString
"incidentRecordArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
incidentRecordArn
      ]

-- | /See:/ 'newGetTimelineEventResponse' smart constructor.
data GetTimelineEventResponse = GetTimelineEventResponse'
  { -- | The response's http status code.
    GetTimelineEventResponse -> Int
httpStatus :: Prelude.Int,
    -- | Details about the timeline event.
    GetTimelineEventResponse -> TimelineEvent
event :: TimelineEvent
  }
  deriving (GetTimelineEventResponse -> GetTimelineEventResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTimelineEventResponse -> GetTimelineEventResponse -> Bool
$c/= :: GetTimelineEventResponse -> GetTimelineEventResponse -> Bool
== :: GetTimelineEventResponse -> GetTimelineEventResponse -> Bool
$c== :: GetTimelineEventResponse -> GetTimelineEventResponse -> Bool
Prelude.Eq, ReadPrec [GetTimelineEventResponse]
ReadPrec GetTimelineEventResponse
Int -> ReadS GetTimelineEventResponse
ReadS [GetTimelineEventResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTimelineEventResponse]
$creadListPrec :: ReadPrec [GetTimelineEventResponse]
readPrec :: ReadPrec GetTimelineEventResponse
$creadPrec :: ReadPrec GetTimelineEventResponse
readList :: ReadS [GetTimelineEventResponse]
$creadList :: ReadS [GetTimelineEventResponse]
readsPrec :: Int -> ReadS GetTimelineEventResponse
$creadsPrec :: Int -> ReadS GetTimelineEventResponse
Prelude.Read, Int -> GetTimelineEventResponse -> ShowS
[GetTimelineEventResponse] -> ShowS
GetTimelineEventResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTimelineEventResponse] -> ShowS
$cshowList :: [GetTimelineEventResponse] -> ShowS
show :: GetTimelineEventResponse -> String
$cshow :: GetTimelineEventResponse -> String
showsPrec :: Int -> GetTimelineEventResponse -> ShowS
$cshowsPrec :: Int -> GetTimelineEventResponse -> ShowS
Prelude.Show, forall x.
Rep GetTimelineEventResponse x -> GetTimelineEventResponse
forall x.
GetTimelineEventResponse -> Rep GetTimelineEventResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetTimelineEventResponse x -> GetTimelineEventResponse
$cfrom :: forall x.
GetTimelineEventResponse -> Rep GetTimelineEventResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetTimelineEventResponse' 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:
--
-- 'httpStatus', 'getTimelineEventResponse_httpStatus' - The response's http status code.
--
-- 'event', 'getTimelineEventResponse_event' - Details about the timeline event.
newGetTimelineEventResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'event'
  TimelineEvent ->
  GetTimelineEventResponse
newGetTimelineEventResponse :: Int -> TimelineEvent -> GetTimelineEventResponse
newGetTimelineEventResponse Int
pHttpStatus_ TimelineEvent
pEvent_ =
  GetTimelineEventResponse'
    { $sel:httpStatus:GetTimelineEventResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:event:GetTimelineEventResponse' :: TimelineEvent
event = TimelineEvent
pEvent_
    }

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

-- | Details about the timeline event.
getTimelineEventResponse_event :: Lens.Lens' GetTimelineEventResponse TimelineEvent
getTimelineEventResponse_event :: Lens' GetTimelineEventResponse TimelineEvent
getTimelineEventResponse_event = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTimelineEventResponse' {TimelineEvent
event :: TimelineEvent
$sel:event:GetTimelineEventResponse' :: GetTimelineEventResponse -> TimelineEvent
event} -> TimelineEvent
event) (\s :: GetTimelineEventResponse
s@GetTimelineEventResponse' {} TimelineEvent
a -> GetTimelineEventResponse
s {$sel:event:GetTimelineEventResponse' :: TimelineEvent
event = TimelineEvent
a} :: GetTimelineEventResponse)

instance Prelude.NFData GetTimelineEventResponse where
  rnf :: GetTimelineEventResponse -> ()
rnf GetTimelineEventResponse' {Int
TimelineEvent
event :: TimelineEvent
httpStatus :: Int
$sel:event:GetTimelineEventResponse' :: GetTimelineEventResponse -> TimelineEvent
$sel:httpStatus:GetTimelineEventResponse' :: GetTimelineEventResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TimelineEvent
event