{-# 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.CreateEventAction
-- 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 creates an event action.
module Amazonka.DataExchange.CreateEventAction
  ( -- * Creating a Request
    CreateEventAction (..),
    newCreateEventAction,

    -- * Request Lenses
    createEventAction_action,
    createEventAction_event,

    -- * Destructuring the Response
    CreateEventActionResponse (..),
    newCreateEventActionResponse,

    -- * Response Lenses
    createEventActionResponse_action,
    createEventActionResponse_arn,
    createEventActionResponse_createdAt,
    createEventActionResponse_event,
    createEventActionResponse_id,
    createEventActionResponse_updatedAt,
    createEventActionResponse_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:/ 'newCreateEventAction' smart constructor.
data CreateEventAction = CreateEventAction'
  { -- | What occurs after a certain event.
    CreateEventAction -> Action
action :: Action,
    -- | What occurs to start an action.
    CreateEventAction -> Event
event :: Event
  }
  deriving (CreateEventAction -> CreateEventAction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateEventAction -> CreateEventAction -> Bool
$c/= :: CreateEventAction -> CreateEventAction -> Bool
== :: CreateEventAction -> CreateEventAction -> Bool
$c== :: CreateEventAction -> CreateEventAction -> Bool
Prelude.Eq, ReadPrec [CreateEventAction]
ReadPrec CreateEventAction
Int -> ReadS CreateEventAction
ReadS [CreateEventAction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateEventAction]
$creadListPrec :: ReadPrec [CreateEventAction]
readPrec :: ReadPrec CreateEventAction
$creadPrec :: ReadPrec CreateEventAction
readList :: ReadS [CreateEventAction]
$creadList :: ReadS [CreateEventAction]
readsPrec :: Int -> ReadS CreateEventAction
$creadsPrec :: Int -> ReadS CreateEventAction
Prelude.Read, Int -> CreateEventAction -> ShowS
[CreateEventAction] -> ShowS
CreateEventAction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateEventAction] -> ShowS
$cshowList :: [CreateEventAction] -> ShowS
show :: CreateEventAction -> String
$cshow :: CreateEventAction -> String
showsPrec :: Int -> CreateEventAction -> ShowS
$cshowsPrec :: Int -> CreateEventAction -> ShowS
Prelude.Show, forall x. Rep CreateEventAction x -> CreateEventAction
forall x. CreateEventAction -> Rep CreateEventAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateEventAction x -> CreateEventAction
$cfrom :: forall x. CreateEventAction -> Rep CreateEventAction x
Prelude.Generic)

-- |
-- Create a value of 'CreateEventAction' 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', 'createEventAction_action' - What occurs after a certain event.
--
-- 'event', 'createEventAction_event' - What occurs to start an action.
newCreateEventAction ::
  -- | 'action'
  Action ->
  -- | 'event'
  Event ->
  CreateEventAction
newCreateEventAction :: Action -> Event -> CreateEventAction
newCreateEventAction Action
pAction_ Event
pEvent_ =
  CreateEventAction'
    { $sel:action:CreateEventAction' :: Action
action = Action
pAction_,
      $sel:event:CreateEventAction' :: Event
event = Event
pEvent_
    }

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

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

instance Core.AWSRequest CreateEventAction where
  type
    AWSResponse CreateEventAction =
      CreateEventActionResponse
  request :: (Service -> Service)
-> CreateEventAction -> Request CreateEventAction
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 CreateEventAction
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateEventAction)))
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
-> CreateEventActionResponse
CreateEventActionResponse'
            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 CreateEventAction where
  hashWithSalt :: Int -> CreateEventAction -> Int
hashWithSalt Int
_salt CreateEventAction' {Event
Action
event :: Event
action :: Action
$sel:event:CreateEventAction' :: CreateEventAction -> Event
$sel:action:CreateEventAction' :: CreateEventAction -> Action
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Action
action
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Event
event

instance Prelude.NFData CreateEventAction where
  rnf :: CreateEventAction -> ()
rnf CreateEventAction' {Event
Action
event :: Event
action :: Action
$sel:event:CreateEventAction' :: CreateEventAction -> Event
$sel:action:CreateEventAction' :: CreateEventAction -> Action
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Action
action seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Event
event

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

instance Data.ToPath CreateEventAction where
  toPath :: CreateEventAction -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/event-actions"

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

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

-- |
-- Create a value of 'CreateEventActionResponse' 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', 'createEventActionResponse_action' - What occurs after a certain event.
--
-- 'arn', 'createEventActionResponse_arn' - The ARN for the event action.
--
-- 'createdAt', 'createEventActionResponse_createdAt' - The date and time that the event action was created, in ISO 8601 format.
--
-- 'event', 'createEventActionResponse_event' - What occurs to start an action.
--
-- 'id', 'createEventActionResponse_id' - The unique identifier for the event action.
--
-- 'updatedAt', 'createEventActionResponse_updatedAt' - The date and time that the event action was last updated, in ISO 8601
-- format.
--
-- 'httpStatus', 'createEventActionResponse_httpStatus' - The response's http status code.
newCreateEventActionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateEventActionResponse
newCreateEventActionResponse :: Int -> CreateEventActionResponse
newCreateEventActionResponse Int
pHttpStatus_ =
  CreateEventActionResponse'
    { $sel:action:CreateEventActionResponse' :: Maybe Action
action =
        forall a. Maybe a
Prelude.Nothing,
      $sel:arn:CreateEventActionResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:CreateEventActionResponse' :: Maybe ISO8601
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:event:CreateEventActionResponse' :: Maybe Event
event = forall a. Maybe a
Prelude.Nothing,
      $sel:id:CreateEventActionResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedAt:CreateEventActionResponse' :: Maybe ISO8601
updatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateEventActionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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

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

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

instance Prelude.NFData CreateEventActionResponse where
  rnf :: CreateEventActionResponse -> ()
rnf CreateEventActionResponse' {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:CreateEventActionResponse' :: CreateEventActionResponse -> Int
$sel:updatedAt:CreateEventActionResponse' :: CreateEventActionResponse -> Maybe ISO8601
$sel:id:CreateEventActionResponse' :: CreateEventActionResponse -> Maybe Text
$sel:event:CreateEventActionResponse' :: CreateEventActionResponse -> Maybe Event
$sel:createdAt:CreateEventActionResponse' :: CreateEventActionResponse -> Maybe ISO8601
$sel:arn:CreateEventActionResponse' :: CreateEventActionResponse -> Maybe Text
$sel:action:CreateEventActionResponse' :: CreateEventActionResponse -> 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