{-# 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.ConnectCases.GetCaseEventConfiguration
-- 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 the case event publishing configuration.
module Amazonka.ConnectCases.GetCaseEventConfiguration
  ( -- * Creating a Request
    GetCaseEventConfiguration (..),
    newGetCaseEventConfiguration,

    -- * Request Lenses
    getCaseEventConfiguration_domainId,

    -- * Destructuring the Response
    GetCaseEventConfigurationResponse (..),
    newGetCaseEventConfigurationResponse,

    -- * Response Lenses
    getCaseEventConfigurationResponse_httpStatus,
    getCaseEventConfigurationResponse_eventBridge,
  )
where

import Amazonka.ConnectCases.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:/ 'newGetCaseEventConfiguration' smart constructor.
data GetCaseEventConfiguration = GetCaseEventConfiguration'
  { -- | The unique identifier of the Cases domain.
    GetCaseEventConfiguration -> Text
domainId :: Prelude.Text
  }
  deriving (GetCaseEventConfiguration -> GetCaseEventConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCaseEventConfiguration -> GetCaseEventConfiguration -> Bool
$c/= :: GetCaseEventConfiguration -> GetCaseEventConfiguration -> Bool
== :: GetCaseEventConfiguration -> GetCaseEventConfiguration -> Bool
$c== :: GetCaseEventConfiguration -> GetCaseEventConfiguration -> Bool
Prelude.Eq, ReadPrec [GetCaseEventConfiguration]
ReadPrec GetCaseEventConfiguration
Int -> ReadS GetCaseEventConfiguration
ReadS [GetCaseEventConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCaseEventConfiguration]
$creadListPrec :: ReadPrec [GetCaseEventConfiguration]
readPrec :: ReadPrec GetCaseEventConfiguration
$creadPrec :: ReadPrec GetCaseEventConfiguration
readList :: ReadS [GetCaseEventConfiguration]
$creadList :: ReadS [GetCaseEventConfiguration]
readsPrec :: Int -> ReadS GetCaseEventConfiguration
$creadsPrec :: Int -> ReadS GetCaseEventConfiguration
Prelude.Read, Int -> GetCaseEventConfiguration -> ShowS
[GetCaseEventConfiguration] -> ShowS
GetCaseEventConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCaseEventConfiguration] -> ShowS
$cshowList :: [GetCaseEventConfiguration] -> ShowS
show :: GetCaseEventConfiguration -> String
$cshow :: GetCaseEventConfiguration -> String
showsPrec :: Int -> GetCaseEventConfiguration -> ShowS
$cshowsPrec :: Int -> GetCaseEventConfiguration -> ShowS
Prelude.Show, forall x.
Rep GetCaseEventConfiguration x -> GetCaseEventConfiguration
forall x.
GetCaseEventConfiguration -> Rep GetCaseEventConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCaseEventConfiguration x -> GetCaseEventConfiguration
$cfrom :: forall x.
GetCaseEventConfiguration -> Rep GetCaseEventConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'GetCaseEventConfiguration' 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:
--
-- 'domainId', 'getCaseEventConfiguration_domainId' - The unique identifier of the Cases domain.
newGetCaseEventConfiguration ::
  -- | 'domainId'
  Prelude.Text ->
  GetCaseEventConfiguration
newGetCaseEventConfiguration :: Text -> GetCaseEventConfiguration
newGetCaseEventConfiguration Text
pDomainId_ =
  GetCaseEventConfiguration' {$sel:domainId:GetCaseEventConfiguration' :: Text
domainId = Text
pDomainId_}

-- | The unique identifier of the Cases domain.
getCaseEventConfiguration_domainId :: Lens.Lens' GetCaseEventConfiguration Prelude.Text
getCaseEventConfiguration_domainId :: Lens' GetCaseEventConfiguration Text
getCaseEventConfiguration_domainId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCaseEventConfiguration' {Text
domainId :: Text
$sel:domainId:GetCaseEventConfiguration' :: GetCaseEventConfiguration -> Text
domainId} -> Text
domainId) (\s :: GetCaseEventConfiguration
s@GetCaseEventConfiguration' {} Text
a -> GetCaseEventConfiguration
s {$sel:domainId:GetCaseEventConfiguration' :: Text
domainId = Text
a} :: GetCaseEventConfiguration)

instance Core.AWSRequest GetCaseEventConfiguration where
  type
    AWSResponse GetCaseEventConfiguration =
      GetCaseEventConfigurationResponse
  request :: (Service -> Service)
-> GetCaseEventConfiguration -> Request GetCaseEventConfiguration
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 GetCaseEventConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetCaseEventConfiguration)))
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
-> EventBridgeConfiguration -> GetCaseEventConfigurationResponse
GetCaseEventConfigurationResponse'
            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
"eventBridge")
      )

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

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

instance Data.ToHeaders GetCaseEventConfiguration where
  toHeaders :: GetCaseEventConfiguration -> 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 GetCaseEventConfiguration where
  toJSON :: GetCaseEventConfiguration -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath GetCaseEventConfiguration where
  toPath :: GetCaseEventConfiguration -> ByteString
toPath GetCaseEventConfiguration' {Text
domainId :: Text
$sel:domainId:GetCaseEventConfiguration' :: GetCaseEventConfiguration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/domains/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
domainId,
        ByteString
"/case-event-configuration"
      ]

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

-- | /See:/ 'newGetCaseEventConfigurationResponse' smart constructor.
data GetCaseEventConfigurationResponse = GetCaseEventConfigurationResponse'
  { -- | The response's http status code.
    GetCaseEventConfigurationResponse -> Int
httpStatus :: Prelude.Int,
    -- | Configuration to enable EventBridge case event delivery and determine
    -- what data is delivered.
    GetCaseEventConfigurationResponse -> EventBridgeConfiguration
eventBridge :: EventBridgeConfiguration
  }
  deriving (GetCaseEventConfigurationResponse
-> GetCaseEventConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCaseEventConfigurationResponse
-> GetCaseEventConfigurationResponse -> Bool
$c/= :: GetCaseEventConfigurationResponse
-> GetCaseEventConfigurationResponse -> Bool
== :: GetCaseEventConfigurationResponse
-> GetCaseEventConfigurationResponse -> Bool
$c== :: GetCaseEventConfigurationResponse
-> GetCaseEventConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [GetCaseEventConfigurationResponse]
ReadPrec GetCaseEventConfigurationResponse
Int -> ReadS GetCaseEventConfigurationResponse
ReadS [GetCaseEventConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCaseEventConfigurationResponse]
$creadListPrec :: ReadPrec [GetCaseEventConfigurationResponse]
readPrec :: ReadPrec GetCaseEventConfigurationResponse
$creadPrec :: ReadPrec GetCaseEventConfigurationResponse
readList :: ReadS [GetCaseEventConfigurationResponse]
$creadList :: ReadS [GetCaseEventConfigurationResponse]
readsPrec :: Int -> ReadS GetCaseEventConfigurationResponse
$creadsPrec :: Int -> ReadS GetCaseEventConfigurationResponse
Prelude.Read, Int -> GetCaseEventConfigurationResponse -> ShowS
[GetCaseEventConfigurationResponse] -> ShowS
GetCaseEventConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCaseEventConfigurationResponse] -> ShowS
$cshowList :: [GetCaseEventConfigurationResponse] -> ShowS
show :: GetCaseEventConfigurationResponse -> String
$cshow :: GetCaseEventConfigurationResponse -> String
showsPrec :: Int -> GetCaseEventConfigurationResponse -> ShowS
$cshowsPrec :: Int -> GetCaseEventConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep GetCaseEventConfigurationResponse x
-> GetCaseEventConfigurationResponse
forall x.
GetCaseEventConfigurationResponse
-> Rep GetCaseEventConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCaseEventConfigurationResponse x
-> GetCaseEventConfigurationResponse
$cfrom :: forall x.
GetCaseEventConfigurationResponse
-> Rep GetCaseEventConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCaseEventConfigurationResponse' 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', 'getCaseEventConfigurationResponse_httpStatus' - The response's http status code.
--
-- 'eventBridge', 'getCaseEventConfigurationResponse_eventBridge' - Configuration to enable EventBridge case event delivery and determine
-- what data is delivered.
newGetCaseEventConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'eventBridge'
  EventBridgeConfiguration ->
  GetCaseEventConfigurationResponse
newGetCaseEventConfigurationResponse :: Int
-> EventBridgeConfiguration -> GetCaseEventConfigurationResponse
newGetCaseEventConfigurationResponse
  Int
pHttpStatus_
  EventBridgeConfiguration
pEventBridge_ =
    GetCaseEventConfigurationResponse'
      { $sel:httpStatus:GetCaseEventConfigurationResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:eventBridge:GetCaseEventConfigurationResponse' :: EventBridgeConfiguration
eventBridge = EventBridgeConfiguration
pEventBridge_
      }

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

-- | Configuration to enable EventBridge case event delivery and determine
-- what data is delivered.
getCaseEventConfigurationResponse_eventBridge :: Lens.Lens' GetCaseEventConfigurationResponse EventBridgeConfiguration
getCaseEventConfigurationResponse_eventBridge :: Lens' GetCaseEventConfigurationResponse EventBridgeConfiguration
getCaseEventConfigurationResponse_eventBridge = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCaseEventConfigurationResponse' {EventBridgeConfiguration
eventBridge :: EventBridgeConfiguration
$sel:eventBridge:GetCaseEventConfigurationResponse' :: GetCaseEventConfigurationResponse -> EventBridgeConfiguration
eventBridge} -> EventBridgeConfiguration
eventBridge) (\s :: GetCaseEventConfigurationResponse
s@GetCaseEventConfigurationResponse' {} EventBridgeConfiguration
a -> GetCaseEventConfigurationResponse
s {$sel:eventBridge:GetCaseEventConfigurationResponse' :: EventBridgeConfiguration
eventBridge = EventBridgeConfiguration
a} :: GetCaseEventConfigurationResponse)

instance
  Prelude.NFData
    GetCaseEventConfigurationResponse
  where
  rnf :: GetCaseEventConfigurationResponse -> ()
rnf GetCaseEventConfigurationResponse' {Int
EventBridgeConfiguration
eventBridge :: EventBridgeConfiguration
httpStatus :: Int
$sel:eventBridge:GetCaseEventConfigurationResponse' :: GetCaseEventConfigurationResponse -> EventBridgeConfiguration
$sel:httpStatus:GetCaseEventConfigurationResponse' :: GetCaseEventConfigurationResponse -> 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 EventBridgeConfiguration
eventBridge