{-# 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.AppIntegrationS.GetEventIntegration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about the event integration.
module Amazonka.AppIntegrationS.GetEventIntegration
  ( -- * Creating a Request
    GetEventIntegration (..),
    newGetEventIntegration,

    -- * Request Lenses
    getEventIntegration_name,

    -- * Destructuring the Response
    GetEventIntegrationResponse (..),
    newGetEventIntegrationResponse,

    -- * Response Lenses
    getEventIntegrationResponse_description,
    getEventIntegrationResponse_eventBridgeBus,
    getEventIntegrationResponse_eventFilter,
    getEventIntegrationResponse_eventIntegrationArn,
    getEventIntegrationResponse_name,
    getEventIntegrationResponse_tags,
    getEventIntegrationResponse_httpStatus,
  )
where

import Amazonka.AppIntegrationS.Types
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

-- | /See:/ 'newGetEventIntegration' smart constructor.
data GetEventIntegration = GetEventIntegration'
  { -- | The name of the event integration.
    GetEventIntegration -> Text
name :: Prelude.Text
  }
  deriving (GetEventIntegration -> GetEventIntegration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEventIntegration -> GetEventIntegration -> Bool
$c/= :: GetEventIntegration -> GetEventIntegration -> Bool
== :: GetEventIntegration -> GetEventIntegration -> Bool
$c== :: GetEventIntegration -> GetEventIntegration -> Bool
Prelude.Eq, ReadPrec [GetEventIntegration]
ReadPrec GetEventIntegration
Int -> ReadS GetEventIntegration
ReadS [GetEventIntegration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEventIntegration]
$creadListPrec :: ReadPrec [GetEventIntegration]
readPrec :: ReadPrec GetEventIntegration
$creadPrec :: ReadPrec GetEventIntegration
readList :: ReadS [GetEventIntegration]
$creadList :: ReadS [GetEventIntegration]
readsPrec :: Int -> ReadS GetEventIntegration
$creadsPrec :: Int -> ReadS GetEventIntegration
Prelude.Read, Int -> GetEventIntegration -> ShowS
[GetEventIntegration] -> ShowS
GetEventIntegration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEventIntegration] -> ShowS
$cshowList :: [GetEventIntegration] -> ShowS
show :: GetEventIntegration -> String
$cshow :: GetEventIntegration -> String
showsPrec :: Int -> GetEventIntegration -> ShowS
$cshowsPrec :: Int -> GetEventIntegration -> ShowS
Prelude.Show, forall x. Rep GetEventIntegration x -> GetEventIntegration
forall x. GetEventIntegration -> Rep GetEventIntegration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEventIntegration x -> GetEventIntegration
$cfrom :: forall x. GetEventIntegration -> Rep GetEventIntegration x
Prelude.Generic)

-- |
-- Create a value of 'GetEventIntegration' 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:
--
-- 'name', 'getEventIntegration_name' - The name of the event integration.
newGetEventIntegration ::
  -- | 'name'
  Prelude.Text ->
  GetEventIntegration
newGetEventIntegration :: Text -> GetEventIntegration
newGetEventIntegration Text
pName_ =
  GetEventIntegration' {$sel:name:GetEventIntegration' :: Text
name = Text
pName_}

-- | The name of the event integration.
getEventIntegration_name :: Lens.Lens' GetEventIntegration Prelude.Text
getEventIntegration_name :: Lens' GetEventIntegration Text
getEventIntegration_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEventIntegration' {Text
name :: Text
$sel:name:GetEventIntegration' :: GetEventIntegration -> Text
name} -> Text
name) (\s :: GetEventIntegration
s@GetEventIntegration' {} Text
a -> GetEventIntegration
s {$sel:name:GetEventIntegration' :: Text
name = Text
a} :: GetEventIntegration)

instance Core.AWSRequest GetEventIntegration where
  type
    AWSResponse GetEventIntegration =
      GetEventIntegrationResponse
  request :: (Service -> Service)
-> GetEventIntegration -> Request GetEventIntegration
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 GetEventIntegration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetEventIntegration)))
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 Text
-> Maybe Text
-> Maybe EventFilter
-> Maybe Text
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Int
-> GetEventIntegrationResponse
GetEventIntegrationResponse'
            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
"Description")
            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
"EventBridgeBus")
            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
"EventFilter")
            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
"EventIntegrationArn")
            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
"Name")
            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
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 GetEventIntegration where
  hashWithSalt :: Int -> GetEventIntegration -> Int
hashWithSalt Int
_salt GetEventIntegration' {Text
name :: Text
$sel:name:GetEventIntegration' :: GetEventIntegration -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders GetEventIntegration where
  toHeaders :: GetEventIntegration -> 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 GetEventIntegration where
  toPath :: GetEventIntegration -> ByteString
toPath GetEventIntegration' {Text
name :: Text
$sel:name:GetEventIntegration' :: GetEventIntegration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/eventIntegrations/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

-- | /See:/ 'newGetEventIntegrationResponse' smart constructor.
data GetEventIntegrationResponse = GetEventIntegrationResponse'
  { -- | The description of the event integration.
    GetEventIntegrationResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The EventBridge bus.
    GetEventIntegrationResponse -> Maybe Text
eventBridgeBus :: Prelude.Maybe Prelude.Text,
    -- | The event filter.
    GetEventIntegrationResponse -> Maybe EventFilter
eventFilter :: Prelude.Maybe EventFilter,
    -- | The Amazon Resource Name (ARN) for the event integration.
    GetEventIntegrationResponse -> Maybe Text
eventIntegrationArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the event integration.
    GetEventIntegrationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | One or more tags.
    GetEventIntegrationResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    GetEventIntegrationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetEventIntegrationResponse -> GetEventIntegrationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEventIntegrationResponse -> GetEventIntegrationResponse -> Bool
$c/= :: GetEventIntegrationResponse -> GetEventIntegrationResponse -> Bool
== :: GetEventIntegrationResponse -> GetEventIntegrationResponse -> Bool
$c== :: GetEventIntegrationResponse -> GetEventIntegrationResponse -> Bool
Prelude.Eq, ReadPrec [GetEventIntegrationResponse]
ReadPrec GetEventIntegrationResponse
Int -> ReadS GetEventIntegrationResponse
ReadS [GetEventIntegrationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEventIntegrationResponse]
$creadListPrec :: ReadPrec [GetEventIntegrationResponse]
readPrec :: ReadPrec GetEventIntegrationResponse
$creadPrec :: ReadPrec GetEventIntegrationResponse
readList :: ReadS [GetEventIntegrationResponse]
$creadList :: ReadS [GetEventIntegrationResponse]
readsPrec :: Int -> ReadS GetEventIntegrationResponse
$creadsPrec :: Int -> ReadS GetEventIntegrationResponse
Prelude.Read, Int -> GetEventIntegrationResponse -> ShowS
[GetEventIntegrationResponse] -> ShowS
GetEventIntegrationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEventIntegrationResponse] -> ShowS
$cshowList :: [GetEventIntegrationResponse] -> ShowS
show :: GetEventIntegrationResponse -> String
$cshow :: GetEventIntegrationResponse -> String
showsPrec :: Int -> GetEventIntegrationResponse -> ShowS
$cshowsPrec :: Int -> GetEventIntegrationResponse -> ShowS
Prelude.Show, forall x.
Rep GetEventIntegrationResponse x -> GetEventIntegrationResponse
forall x.
GetEventIntegrationResponse -> Rep GetEventIntegrationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetEventIntegrationResponse x -> GetEventIntegrationResponse
$cfrom :: forall x.
GetEventIntegrationResponse -> Rep GetEventIntegrationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetEventIntegrationResponse' 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:
--
-- 'description', 'getEventIntegrationResponse_description' - The description of the event integration.
--
-- 'eventBridgeBus', 'getEventIntegrationResponse_eventBridgeBus' - The EventBridge bus.
--
-- 'eventFilter', 'getEventIntegrationResponse_eventFilter' - The event filter.
--
-- 'eventIntegrationArn', 'getEventIntegrationResponse_eventIntegrationArn' - The Amazon Resource Name (ARN) for the event integration.
--
-- 'name', 'getEventIntegrationResponse_name' - The name of the event integration.
--
-- 'tags', 'getEventIntegrationResponse_tags' - One or more tags.
--
-- 'httpStatus', 'getEventIntegrationResponse_httpStatus' - The response's http status code.
newGetEventIntegrationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetEventIntegrationResponse
newGetEventIntegrationResponse :: Int -> GetEventIntegrationResponse
newGetEventIntegrationResponse Int
pHttpStatus_ =
  GetEventIntegrationResponse'
    { $sel:description:GetEventIntegrationResponse' :: Maybe Text
description =
        forall a. Maybe a
Prelude.Nothing,
      $sel:eventBridgeBus:GetEventIntegrationResponse' :: Maybe Text
eventBridgeBus = forall a. Maybe a
Prelude.Nothing,
      $sel:eventFilter:GetEventIntegrationResponse' :: Maybe EventFilter
eventFilter = forall a. Maybe a
Prelude.Nothing,
      $sel:eventIntegrationArn:GetEventIntegrationResponse' :: Maybe Text
eventIntegrationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetEventIntegrationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetEventIntegrationResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetEventIntegrationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The description of the event integration.
getEventIntegrationResponse_description :: Lens.Lens' GetEventIntegrationResponse (Prelude.Maybe Prelude.Text)
getEventIntegrationResponse_description :: Lens' GetEventIntegrationResponse (Maybe Text)
getEventIntegrationResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEventIntegrationResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetEventIntegrationResponse
s@GetEventIntegrationResponse' {} Maybe Text
a -> GetEventIntegrationResponse
s {$sel:description:GetEventIntegrationResponse' :: Maybe Text
description = Maybe Text
a} :: GetEventIntegrationResponse)

-- | The EventBridge bus.
getEventIntegrationResponse_eventBridgeBus :: Lens.Lens' GetEventIntegrationResponse (Prelude.Maybe Prelude.Text)
getEventIntegrationResponse_eventBridgeBus :: Lens' GetEventIntegrationResponse (Maybe Text)
getEventIntegrationResponse_eventBridgeBus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEventIntegrationResponse' {Maybe Text
eventBridgeBus :: Maybe Text
$sel:eventBridgeBus:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe Text
eventBridgeBus} -> Maybe Text
eventBridgeBus) (\s :: GetEventIntegrationResponse
s@GetEventIntegrationResponse' {} Maybe Text
a -> GetEventIntegrationResponse
s {$sel:eventBridgeBus:GetEventIntegrationResponse' :: Maybe Text
eventBridgeBus = Maybe Text
a} :: GetEventIntegrationResponse)

-- | The event filter.
getEventIntegrationResponse_eventFilter :: Lens.Lens' GetEventIntegrationResponse (Prelude.Maybe EventFilter)
getEventIntegrationResponse_eventFilter :: Lens' GetEventIntegrationResponse (Maybe EventFilter)
getEventIntegrationResponse_eventFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEventIntegrationResponse' {Maybe EventFilter
eventFilter :: Maybe EventFilter
$sel:eventFilter:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe EventFilter
eventFilter} -> Maybe EventFilter
eventFilter) (\s :: GetEventIntegrationResponse
s@GetEventIntegrationResponse' {} Maybe EventFilter
a -> GetEventIntegrationResponse
s {$sel:eventFilter:GetEventIntegrationResponse' :: Maybe EventFilter
eventFilter = Maybe EventFilter
a} :: GetEventIntegrationResponse)

-- | The Amazon Resource Name (ARN) for the event integration.
getEventIntegrationResponse_eventIntegrationArn :: Lens.Lens' GetEventIntegrationResponse (Prelude.Maybe Prelude.Text)
getEventIntegrationResponse_eventIntegrationArn :: Lens' GetEventIntegrationResponse (Maybe Text)
getEventIntegrationResponse_eventIntegrationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEventIntegrationResponse' {Maybe Text
eventIntegrationArn :: Maybe Text
$sel:eventIntegrationArn:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe Text
eventIntegrationArn} -> Maybe Text
eventIntegrationArn) (\s :: GetEventIntegrationResponse
s@GetEventIntegrationResponse' {} Maybe Text
a -> GetEventIntegrationResponse
s {$sel:eventIntegrationArn:GetEventIntegrationResponse' :: Maybe Text
eventIntegrationArn = Maybe Text
a} :: GetEventIntegrationResponse)

-- | The name of the event integration.
getEventIntegrationResponse_name :: Lens.Lens' GetEventIntegrationResponse (Prelude.Maybe Prelude.Text)
getEventIntegrationResponse_name :: Lens' GetEventIntegrationResponse (Maybe Text)
getEventIntegrationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEventIntegrationResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetEventIntegrationResponse
s@GetEventIntegrationResponse' {} Maybe Text
a -> GetEventIntegrationResponse
s {$sel:name:GetEventIntegrationResponse' :: Maybe Text
name = Maybe Text
a} :: GetEventIntegrationResponse)

-- | One or more tags.
getEventIntegrationResponse_tags :: Lens.Lens' GetEventIntegrationResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getEventIntegrationResponse_tags :: Lens' GetEventIntegrationResponse (Maybe (HashMap Text Text))
getEventIntegrationResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEventIntegrationResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetEventIntegrationResponse
s@GetEventIntegrationResponse' {} Maybe (HashMap Text Text)
a -> GetEventIntegrationResponse
s {$sel:tags:GetEventIntegrationResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetEventIntegrationResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData GetEventIntegrationResponse where
  rnf :: GetEventIntegrationResponse -> ()
rnf GetEventIntegrationResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
Maybe EventFilter
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
name :: Maybe Text
eventIntegrationArn :: Maybe Text
eventFilter :: Maybe EventFilter
eventBridgeBus :: Maybe Text
description :: Maybe Text
$sel:httpStatus:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Int
$sel:tags:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe (HashMap Text Text)
$sel:name:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe Text
$sel:eventIntegrationArn:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe Text
$sel:eventFilter:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe EventFilter
$sel:eventBridgeBus:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe Text
$sel:description:GetEventIntegrationResponse' :: GetEventIntegrationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eventBridgeBus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EventFilter
eventFilter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eventIntegrationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus