{-# 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.DataExchange.UpdateEventAction
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This operation updates the event action.
module Amazonka.DataExchange.UpdateEventAction
  ( -- * Creating a Request
    UpdateEventAction (..),
    newUpdateEventAction,

    -- * Request Lenses
    updateEventAction_action,
    updateEventAction_eventActionId,

    -- * Destructuring the Response
    UpdateEventActionResponse (..),
    newUpdateEventActionResponse,

    -- * Response Lenses
    updateEventActionResponse_action,
    updateEventActionResponse_arn,
    updateEventActionResponse_createdAt,
    updateEventActionResponse_event,
    updateEventActionResponse_id,
    updateEventActionResponse_updatedAt,
    updateEventActionResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DataExchange.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateEventAction' smart constructor.
data UpdateEventAction = UpdateEventAction'
  { -- | What occurs after a certain event.
    UpdateEventAction -> Maybe Action
action :: Prelude.Maybe Action,
    -- | The unique identifier for the event action.
    UpdateEventAction -> Text
eventActionId :: Prelude.Text
  }
  deriving (UpdateEventAction -> UpdateEventAction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateEventAction -> UpdateEventAction -> Bool
$c/= :: UpdateEventAction -> UpdateEventAction -> Bool
== :: UpdateEventAction -> UpdateEventAction -> Bool
$c== :: UpdateEventAction -> UpdateEventAction -> Bool
Prelude.Eq, ReadPrec [UpdateEventAction]
ReadPrec UpdateEventAction
Int -> ReadS UpdateEventAction
ReadS [UpdateEventAction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateEventAction]
$creadListPrec :: ReadPrec [UpdateEventAction]
readPrec :: ReadPrec UpdateEventAction
$creadPrec :: ReadPrec UpdateEventAction
readList :: ReadS [UpdateEventAction]
$creadList :: ReadS [UpdateEventAction]
readsPrec :: Int -> ReadS UpdateEventAction
$creadsPrec :: Int -> ReadS UpdateEventAction
Prelude.Read, Int -> UpdateEventAction -> ShowS
[UpdateEventAction] -> ShowS
UpdateEventAction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateEventAction] -> ShowS
$cshowList :: [UpdateEventAction] -> ShowS
show :: UpdateEventAction -> String
$cshow :: UpdateEventAction -> String
showsPrec :: Int -> UpdateEventAction -> ShowS
$cshowsPrec :: Int -> UpdateEventAction -> ShowS
Prelude.Show, forall x. Rep UpdateEventAction x -> UpdateEventAction
forall x. UpdateEventAction -> Rep UpdateEventAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateEventAction x -> UpdateEventAction
$cfrom :: forall x. UpdateEventAction -> Rep UpdateEventAction x
Prelude.Generic)

-- |
-- Create a value of 'UpdateEventAction' 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:
--
-- 'action', 'updateEventAction_action' - What occurs after a certain event.
--
-- 'eventActionId', 'updateEventAction_eventActionId' - The unique identifier for the event action.
newUpdateEventAction ::
  -- | 'eventActionId'
  Prelude.Text ->
  UpdateEventAction
newUpdateEventAction :: Text -> UpdateEventAction
newUpdateEventAction Text
pEventActionId_ =
  UpdateEventAction'
    { $sel:action:UpdateEventAction' :: Maybe Action
action = forall a. Maybe a
Prelude.Nothing,
      $sel:eventActionId:UpdateEventAction' :: Text
eventActionId = Text
pEventActionId_
    }

-- | What occurs after a certain event.
updateEventAction_action :: Lens.Lens' UpdateEventAction (Prelude.Maybe Action)
updateEventAction_action :: Lens' UpdateEventAction (Maybe Action)
updateEventAction_action = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEventAction' {Maybe Action
action :: Maybe Action
$sel:action:UpdateEventAction' :: UpdateEventAction -> Maybe Action
action} -> Maybe Action
action) (\s :: UpdateEventAction
s@UpdateEventAction' {} Maybe Action
a -> UpdateEventAction
s {$sel:action:UpdateEventAction' :: Maybe Action
action = Maybe Action
a} :: UpdateEventAction)

-- | The unique identifier for the event action.
updateEventAction_eventActionId :: Lens.Lens' UpdateEventAction Prelude.Text
updateEventAction_eventActionId :: Lens' UpdateEventAction Text
updateEventAction_eventActionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEventAction' {Text
eventActionId :: Text
$sel:eventActionId:UpdateEventAction' :: UpdateEventAction -> Text
eventActionId} -> Text
eventActionId) (\s :: UpdateEventAction
s@UpdateEventAction' {} Text
a -> UpdateEventAction
s {$sel:eventActionId:UpdateEventAction' :: Text
eventActionId = Text
a} :: UpdateEventAction)

instance Core.AWSRequest UpdateEventAction where
  type
    AWSResponse UpdateEventAction =
      UpdateEventActionResponse
  request :: (Service -> Service)
-> UpdateEventAction -> Request UpdateEventAction
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateEventAction
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateEventAction)))
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 Action
-> Maybe Text
-> Maybe ISO8601
-> Maybe Event
-> Maybe Text
-> Maybe ISO8601
-> Int
-> UpdateEventActionResponse
UpdateEventActionResponse'
            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
"Action")
            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
"Arn")
            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
"CreatedAt")
            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
"Event")
            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
"Id")
            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
"UpdatedAt")
            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 UpdateEventAction where
  hashWithSalt :: Int -> UpdateEventAction -> Int
hashWithSalt Int
_salt UpdateEventAction' {Maybe Action
Text
eventActionId :: Text
action :: Maybe Action
$sel:eventActionId:UpdateEventAction' :: UpdateEventAction -> Text
$sel:action:UpdateEventAction' :: UpdateEventAction -> Maybe Action
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Action
action
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
eventActionId

instance Prelude.NFData UpdateEventAction where
  rnf :: UpdateEventAction -> ()
rnf UpdateEventAction' {Maybe Action
Text
eventActionId :: Text
action :: Maybe Action
$sel:eventActionId:UpdateEventAction' :: UpdateEventAction -> Text
$sel:action:UpdateEventAction' :: UpdateEventAction -> Maybe Action
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Action
action
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
eventActionId

instance Data.ToHeaders UpdateEventAction where
  toHeaders :: UpdateEventAction -> 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.ToJSON UpdateEventAction where
  toJSON :: UpdateEventAction -> Value
toJSON UpdateEventAction' {Maybe Action
Text
eventActionId :: Text
action :: Maybe Action
$sel:eventActionId:UpdateEventAction' :: UpdateEventAction -> Text
$sel:action:UpdateEventAction' :: UpdateEventAction -> Maybe Action
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"Action" 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 Action
action]
      )

instance Data.ToPath UpdateEventAction where
  toPath :: UpdateEventAction -> ByteString
toPath UpdateEventAction' {Maybe Action
Text
eventActionId :: Text
action :: Maybe Action
$sel:eventActionId:UpdateEventAction' :: UpdateEventAction -> Text
$sel:action:UpdateEventAction' :: UpdateEventAction -> Maybe Action
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/event-actions/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
eventActionId]

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

-- | /See:/ 'newUpdateEventActionResponse' smart constructor.
data UpdateEventActionResponse = UpdateEventActionResponse'
  { -- | What occurs after a certain event.
    UpdateEventActionResponse -> Maybe Action
action :: Prelude.Maybe Action,
    -- | The ARN for the event action.
    UpdateEventActionResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the event action was created, in ISO 8601 format.
    UpdateEventActionResponse -> Maybe ISO8601
createdAt :: Prelude.Maybe Data.ISO8601,
    -- | What occurs to start an action.
    UpdateEventActionResponse -> Maybe Event
event :: Prelude.Maybe Event,
    -- | The unique identifier for the event action.
    UpdateEventActionResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the event action was last updated, in ISO 8601
    -- format.
    UpdateEventActionResponse -> Maybe ISO8601
updatedAt :: Prelude.Maybe Data.ISO8601,
    -- | The response's http status code.
    UpdateEventActionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateEventActionResponse -> UpdateEventActionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateEventActionResponse -> UpdateEventActionResponse -> Bool
$c/= :: UpdateEventActionResponse -> UpdateEventActionResponse -> Bool
== :: UpdateEventActionResponse -> UpdateEventActionResponse -> Bool
$c== :: UpdateEventActionResponse -> UpdateEventActionResponse -> Bool
Prelude.Eq, ReadPrec [UpdateEventActionResponse]
ReadPrec UpdateEventActionResponse
Int -> ReadS UpdateEventActionResponse
ReadS [UpdateEventActionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateEventActionResponse]
$creadListPrec :: ReadPrec [UpdateEventActionResponse]
readPrec :: ReadPrec UpdateEventActionResponse
$creadPrec :: ReadPrec UpdateEventActionResponse
readList :: ReadS [UpdateEventActionResponse]
$creadList :: ReadS [UpdateEventActionResponse]
readsPrec :: Int -> ReadS UpdateEventActionResponse
$creadsPrec :: Int -> ReadS UpdateEventActionResponse
Prelude.Read, Int -> UpdateEventActionResponse -> ShowS
[UpdateEventActionResponse] -> ShowS
UpdateEventActionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateEventActionResponse] -> ShowS
$cshowList :: [UpdateEventActionResponse] -> ShowS
show :: UpdateEventActionResponse -> String
$cshow :: UpdateEventActionResponse -> String
showsPrec :: Int -> UpdateEventActionResponse -> ShowS
$cshowsPrec :: Int -> UpdateEventActionResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateEventActionResponse x -> UpdateEventActionResponse
forall x.
UpdateEventActionResponse -> Rep UpdateEventActionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateEventActionResponse x -> UpdateEventActionResponse
$cfrom :: forall x.
UpdateEventActionResponse -> Rep UpdateEventActionResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateEventActionResponse' 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:
--
-- 'action', 'updateEventActionResponse_action' - What occurs after a certain event.
--
-- 'arn', 'updateEventActionResponse_arn' - The ARN for the event action.
--
-- 'createdAt', 'updateEventActionResponse_createdAt' - The date and time that the event action was created, in ISO 8601 format.
--
-- 'event', 'updateEventActionResponse_event' - What occurs to start an action.
--
-- 'id', 'updateEventActionResponse_id' - The unique identifier for the event action.
--
-- 'updatedAt', 'updateEventActionResponse_updatedAt' - The date and time that the event action was last updated, in ISO 8601
-- format.
--
-- 'httpStatus', 'updateEventActionResponse_httpStatus' - The response's http status code.
newUpdateEventActionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateEventActionResponse
newUpdateEventActionResponse :: Int -> UpdateEventActionResponse
newUpdateEventActionResponse Int
pHttpStatus_ =
  UpdateEventActionResponse'
    { $sel:action:UpdateEventActionResponse' :: Maybe Action
action =
        forall a. Maybe a
Prelude.Nothing,
      $sel:arn:UpdateEventActionResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:UpdateEventActionResponse' :: Maybe ISO8601
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:event:UpdateEventActionResponse' :: Maybe Event
event = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateEventActionResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedAt:UpdateEventActionResponse' :: Maybe ISO8601
updatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateEventActionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | What occurs after a certain event.
updateEventActionResponse_action :: Lens.Lens' UpdateEventActionResponse (Prelude.Maybe Action)
updateEventActionResponse_action :: Lens' UpdateEventActionResponse (Maybe Action)
updateEventActionResponse_action = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEventActionResponse' {Maybe Action
action :: Maybe Action
$sel:action:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe Action
action} -> Maybe Action
action) (\s :: UpdateEventActionResponse
s@UpdateEventActionResponse' {} Maybe Action
a -> UpdateEventActionResponse
s {$sel:action:UpdateEventActionResponse' :: Maybe Action
action = Maybe Action
a} :: UpdateEventActionResponse)

-- | The ARN for the event action.
updateEventActionResponse_arn :: Lens.Lens' UpdateEventActionResponse (Prelude.Maybe Prelude.Text)
updateEventActionResponse_arn :: Lens' UpdateEventActionResponse (Maybe Text)
updateEventActionResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEventActionResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: UpdateEventActionResponse
s@UpdateEventActionResponse' {} Maybe Text
a -> UpdateEventActionResponse
s {$sel:arn:UpdateEventActionResponse' :: Maybe Text
arn = Maybe Text
a} :: UpdateEventActionResponse)

-- | The date and time that the event action was created, in ISO 8601 format.
updateEventActionResponse_createdAt :: Lens.Lens' UpdateEventActionResponse (Prelude.Maybe Prelude.UTCTime)
updateEventActionResponse_createdAt :: Lens' UpdateEventActionResponse (Maybe UTCTime)
updateEventActionResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEventActionResponse' {Maybe ISO8601
createdAt :: Maybe ISO8601
$sel:createdAt:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe ISO8601
createdAt} -> Maybe ISO8601
createdAt) (\s :: UpdateEventActionResponse
s@UpdateEventActionResponse' {} Maybe ISO8601
a -> UpdateEventActionResponse
s {$sel:createdAt:UpdateEventActionResponse' :: Maybe ISO8601
createdAt = Maybe ISO8601
a} :: UpdateEventActionResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | What occurs to start an action.
updateEventActionResponse_event :: Lens.Lens' UpdateEventActionResponse (Prelude.Maybe Event)
updateEventActionResponse_event :: Lens' UpdateEventActionResponse (Maybe Event)
updateEventActionResponse_event = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEventActionResponse' {Maybe Event
event :: Maybe Event
$sel:event:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe Event
event} -> Maybe Event
event) (\s :: UpdateEventActionResponse
s@UpdateEventActionResponse' {} Maybe Event
a -> UpdateEventActionResponse
s {$sel:event:UpdateEventActionResponse' :: Maybe Event
event = Maybe Event
a} :: UpdateEventActionResponse)

-- | The unique identifier for the event action.
updateEventActionResponse_id :: Lens.Lens' UpdateEventActionResponse (Prelude.Maybe Prelude.Text)
updateEventActionResponse_id :: Lens' UpdateEventActionResponse (Maybe Text)
updateEventActionResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEventActionResponse' {Maybe Text
id :: Maybe Text
$sel:id:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: UpdateEventActionResponse
s@UpdateEventActionResponse' {} Maybe Text
a -> UpdateEventActionResponse
s {$sel:id:UpdateEventActionResponse' :: Maybe Text
id = Maybe Text
a} :: UpdateEventActionResponse)

-- | The date and time that the event action was last updated, in ISO 8601
-- format.
updateEventActionResponse_updatedAt :: Lens.Lens' UpdateEventActionResponse (Prelude.Maybe Prelude.UTCTime)
updateEventActionResponse_updatedAt :: Lens' UpdateEventActionResponse (Maybe UTCTime)
updateEventActionResponse_updatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEventActionResponse' {Maybe ISO8601
updatedAt :: Maybe ISO8601
$sel:updatedAt:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe ISO8601
updatedAt} -> Maybe ISO8601
updatedAt) (\s :: UpdateEventActionResponse
s@UpdateEventActionResponse' {} Maybe ISO8601
a -> UpdateEventActionResponse
s {$sel:updatedAt:UpdateEventActionResponse' :: Maybe ISO8601
updatedAt = Maybe ISO8601
a} :: UpdateEventActionResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

instance Prelude.NFData UpdateEventActionResponse where
  rnf :: UpdateEventActionResponse -> ()
rnf UpdateEventActionResponse' {Int
Maybe Text
Maybe ISO8601
Maybe Event
Maybe Action
httpStatus :: Int
updatedAt :: Maybe ISO8601
id :: Maybe Text
event :: Maybe Event
createdAt :: Maybe ISO8601
arn :: Maybe Text
action :: Maybe Action
$sel:httpStatus:UpdateEventActionResponse' :: UpdateEventActionResponse -> Int
$sel:updatedAt:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe ISO8601
$sel:id:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe Text
$sel:event:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe Event
$sel:createdAt:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe ISO8601
$sel:arn:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe Text
$sel:action:UpdateEventActionResponse' :: UpdateEventActionResponse -> Maybe Action
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Action
action
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Event
event
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
updatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus