{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.SupportApp.Types.SlackChannelConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.SupportApp.Types.SlackChannelConfiguration 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 Amazonka.SupportApp.Types.NotificationSeverityLevel

-- | The configuration for a Slack channel that you added for your Amazon Web
-- Services account.
--
-- /See:/ 'newSlackChannelConfiguration' smart constructor.
data SlackChannelConfiguration = SlackChannelConfiguration'
  { -- | The name of the Slack channel that you configured with the Amazon Web
    -- Services Support App for your Amazon Web Services account.
    SlackChannelConfiguration -> Maybe Text
channelName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of an IAM role that you want to use to
    -- perform operations on Amazon Web Services. For more information, see
    -- <https://docs.aws.amazon.com/awssupport/latest/user/support-app-permissions.html Managing access to the Amazon Web Services Support App>
    -- in the /Amazon Web Services Support User Guide/.
    SlackChannelConfiguration -> Maybe Text
channelRoleArn :: Prelude.Maybe Prelude.Text,
    -- | Whether you want to get notified when a support case has a new
    -- correspondence.
    SlackChannelConfiguration -> Maybe Bool
notifyOnAddCorrespondenceToCase :: Prelude.Maybe Prelude.Bool,
    -- | The case severity for a support case that you want to receive
    -- notifications.
    SlackChannelConfiguration -> Maybe NotificationSeverityLevel
notifyOnCaseSeverity :: Prelude.Maybe NotificationSeverityLevel,
    -- | Whether you want to get notified when a support case is created or
    -- reopened.
    SlackChannelConfiguration -> Maybe Bool
notifyOnCreateOrReopenCase :: Prelude.Maybe Prelude.Bool,
    -- | Whether you want to get notified when a support case is resolved.
    SlackChannelConfiguration -> Maybe Bool
notifyOnResolveCase :: Prelude.Maybe Prelude.Bool,
    -- | The channel ID in Slack. This ID identifies a channel within a Slack
    -- workspace.
    SlackChannelConfiguration -> Text
channelId :: Prelude.Text,
    -- | The team ID in Slack. This ID uniquely identifies a Slack workspace,
    -- such as @T012ABCDEFG@.
    SlackChannelConfiguration -> Text
teamId :: Prelude.Text
  }
  deriving (SlackChannelConfiguration -> SlackChannelConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SlackChannelConfiguration -> SlackChannelConfiguration -> Bool
$c/= :: SlackChannelConfiguration -> SlackChannelConfiguration -> Bool
== :: SlackChannelConfiguration -> SlackChannelConfiguration -> Bool
$c== :: SlackChannelConfiguration -> SlackChannelConfiguration -> Bool
Prelude.Eq, ReadPrec [SlackChannelConfiguration]
ReadPrec SlackChannelConfiguration
Int -> ReadS SlackChannelConfiguration
ReadS [SlackChannelConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SlackChannelConfiguration]
$creadListPrec :: ReadPrec [SlackChannelConfiguration]
readPrec :: ReadPrec SlackChannelConfiguration
$creadPrec :: ReadPrec SlackChannelConfiguration
readList :: ReadS [SlackChannelConfiguration]
$creadList :: ReadS [SlackChannelConfiguration]
readsPrec :: Int -> ReadS SlackChannelConfiguration
$creadsPrec :: Int -> ReadS SlackChannelConfiguration
Prelude.Read, Int -> SlackChannelConfiguration -> ShowS
[SlackChannelConfiguration] -> ShowS
SlackChannelConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SlackChannelConfiguration] -> ShowS
$cshowList :: [SlackChannelConfiguration] -> ShowS
show :: SlackChannelConfiguration -> String
$cshow :: SlackChannelConfiguration -> String
showsPrec :: Int -> SlackChannelConfiguration -> ShowS
$cshowsPrec :: Int -> SlackChannelConfiguration -> ShowS
Prelude.Show, forall x.
Rep SlackChannelConfiguration x -> SlackChannelConfiguration
forall x.
SlackChannelConfiguration -> Rep SlackChannelConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SlackChannelConfiguration x -> SlackChannelConfiguration
$cfrom :: forall x.
SlackChannelConfiguration -> Rep SlackChannelConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'SlackChannelConfiguration' 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:
--
-- 'channelName', 'slackChannelConfiguration_channelName' - The name of the Slack channel that you configured with the Amazon Web
-- Services Support App for your Amazon Web Services account.
--
-- 'channelRoleArn', 'slackChannelConfiguration_channelRoleArn' - The Amazon Resource Name (ARN) of an IAM role that you want to use to
-- perform operations on Amazon Web Services. For more information, see
-- <https://docs.aws.amazon.com/awssupport/latest/user/support-app-permissions.html Managing access to the Amazon Web Services Support App>
-- in the /Amazon Web Services Support User Guide/.
--
-- 'notifyOnAddCorrespondenceToCase', 'slackChannelConfiguration_notifyOnAddCorrespondenceToCase' - Whether you want to get notified when a support case has a new
-- correspondence.
--
-- 'notifyOnCaseSeverity', 'slackChannelConfiguration_notifyOnCaseSeverity' - The case severity for a support case that you want to receive
-- notifications.
--
-- 'notifyOnCreateOrReopenCase', 'slackChannelConfiguration_notifyOnCreateOrReopenCase' - Whether you want to get notified when a support case is created or
-- reopened.
--
-- 'notifyOnResolveCase', 'slackChannelConfiguration_notifyOnResolveCase' - Whether you want to get notified when a support case is resolved.
--
-- 'channelId', 'slackChannelConfiguration_channelId' - The channel ID in Slack. This ID identifies a channel within a Slack
-- workspace.
--
-- 'teamId', 'slackChannelConfiguration_teamId' - The team ID in Slack. This ID uniquely identifies a Slack workspace,
-- such as @T012ABCDEFG@.
newSlackChannelConfiguration ::
  -- | 'channelId'
  Prelude.Text ->
  -- | 'teamId'
  Prelude.Text ->
  SlackChannelConfiguration
newSlackChannelConfiguration :: Text -> Text -> SlackChannelConfiguration
newSlackChannelConfiguration Text
pChannelId_ Text
pTeamId_ =
  SlackChannelConfiguration'
    { $sel:channelName:SlackChannelConfiguration' :: Maybe Text
channelName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:channelRoleArn:SlackChannelConfiguration' :: Maybe Text
channelRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:notifyOnAddCorrespondenceToCase:SlackChannelConfiguration' :: Maybe Bool
notifyOnAddCorrespondenceToCase =
        forall a. Maybe a
Prelude.Nothing,
      $sel:notifyOnCaseSeverity:SlackChannelConfiguration' :: Maybe NotificationSeverityLevel
notifyOnCaseSeverity = forall a. Maybe a
Prelude.Nothing,
      $sel:notifyOnCreateOrReopenCase:SlackChannelConfiguration' :: Maybe Bool
notifyOnCreateOrReopenCase = forall a. Maybe a
Prelude.Nothing,
      $sel:notifyOnResolveCase:SlackChannelConfiguration' :: Maybe Bool
notifyOnResolveCase = forall a. Maybe a
Prelude.Nothing,
      $sel:channelId:SlackChannelConfiguration' :: Text
channelId = Text
pChannelId_,
      $sel:teamId:SlackChannelConfiguration' :: Text
teamId = Text
pTeamId_
    }

-- | The name of the Slack channel that you configured with the Amazon Web
-- Services Support App for your Amazon Web Services account.
slackChannelConfiguration_channelName :: Lens.Lens' SlackChannelConfiguration (Prelude.Maybe Prelude.Text)
slackChannelConfiguration_channelName :: Lens' SlackChannelConfiguration (Maybe Text)
slackChannelConfiguration_channelName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SlackChannelConfiguration' {Maybe Text
channelName :: Maybe Text
$sel:channelName:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Text
channelName} -> Maybe Text
channelName) (\s :: SlackChannelConfiguration
s@SlackChannelConfiguration' {} Maybe Text
a -> SlackChannelConfiguration
s {$sel:channelName:SlackChannelConfiguration' :: Maybe Text
channelName = Maybe Text
a} :: SlackChannelConfiguration)

-- | The Amazon Resource Name (ARN) of an IAM role that you want to use to
-- perform operations on Amazon Web Services. For more information, see
-- <https://docs.aws.amazon.com/awssupport/latest/user/support-app-permissions.html Managing access to the Amazon Web Services Support App>
-- in the /Amazon Web Services Support User Guide/.
slackChannelConfiguration_channelRoleArn :: Lens.Lens' SlackChannelConfiguration (Prelude.Maybe Prelude.Text)
slackChannelConfiguration_channelRoleArn :: Lens' SlackChannelConfiguration (Maybe Text)
slackChannelConfiguration_channelRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SlackChannelConfiguration' {Maybe Text
channelRoleArn :: Maybe Text
$sel:channelRoleArn:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Text
channelRoleArn} -> Maybe Text
channelRoleArn) (\s :: SlackChannelConfiguration
s@SlackChannelConfiguration' {} Maybe Text
a -> SlackChannelConfiguration
s {$sel:channelRoleArn:SlackChannelConfiguration' :: Maybe Text
channelRoleArn = Maybe Text
a} :: SlackChannelConfiguration)

-- | Whether you want to get notified when a support case has a new
-- correspondence.
slackChannelConfiguration_notifyOnAddCorrespondenceToCase :: Lens.Lens' SlackChannelConfiguration (Prelude.Maybe Prelude.Bool)
slackChannelConfiguration_notifyOnAddCorrespondenceToCase :: Lens' SlackChannelConfiguration (Maybe Bool)
slackChannelConfiguration_notifyOnAddCorrespondenceToCase = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SlackChannelConfiguration' {Maybe Bool
notifyOnAddCorrespondenceToCase :: Maybe Bool
$sel:notifyOnAddCorrespondenceToCase:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Bool
notifyOnAddCorrespondenceToCase} -> Maybe Bool
notifyOnAddCorrespondenceToCase) (\s :: SlackChannelConfiguration
s@SlackChannelConfiguration' {} Maybe Bool
a -> SlackChannelConfiguration
s {$sel:notifyOnAddCorrespondenceToCase:SlackChannelConfiguration' :: Maybe Bool
notifyOnAddCorrespondenceToCase = Maybe Bool
a} :: SlackChannelConfiguration)

-- | The case severity for a support case that you want to receive
-- notifications.
slackChannelConfiguration_notifyOnCaseSeverity :: Lens.Lens' SlackChannelConfiguration (Prelude.Maybe NotificationSeverityLevel)
slackChannelConfiguration_notifyOnCaseSeverity :: Lens' SlackChannelConfiguration (Maybe NotificationSeverityLevel)
slackChannelConfiguration_notifyOnCaseSeverity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SlackChannelConfiguration' {Maybe NotificationSeverityLevel
notifyOnCaseSeverity :: Maybe NotificationSeverityLevel
$sel:notifyOnCaseSeverity:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe NotificationSeverityLevel
notifyOnCaseSeverity} -> Maybe NotificationSeverityLevel
notifyOnCaseSeverity) (\s :: SlackChannelConfiguration
s@SlackChannelConfiguration' {} Maybe NotificationSeverityLevel
a -> SlackChannelConfiguration
s {$sel:notifyOnCaseSeverity:SlackChannelConfiguration' :: Maybe NotificationSeverityLevel
notifyOnCaseSeverity = Maybe NotificationSeverityLevel
a} :: SlackChannelConfiguration)

-- | Whether you want to get notified when a support case is created or
-- reopened.
slackChannelConfiguration_notifyOnCreateOrReopenCase :: Lens.Lens' SlackChannelConfiguration (Prelude.Maybe Prelude.Bool)
slackChannelConfiguration_notifyOnCreateOrReopenCase :: Lens' SlackChannelConfiguration (Maybe Bool)
slackChannelConfiguration_notifyOnCreateOrReopenCase = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SlackChannelConfiguration' {Maybe Bool
notifyOnCreateOrReopenCase :: Maybe Bool
$sel:notifyOnCreateOrReopenCase:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Bool
notifyOnCreateOrReopenCase} -> Maybe Bool
notifyOnCreateOrReopenCase) (\s :: SlackChannelConfiguration
s@SlackChannelConfiguration' {} Maybe Bool
a -> SlackChannelConfiguration
s {$sel:notifyOnCreateOrReopenCase:SlackChannelConfiguration' :: Maybe Bool
notifyOnCreateOrReopenCase = Maybe Bool
a} :: SlackChannelConfiguration)

-- | Whether you want to get notified when a support case is resolved.
slackChannelConfiguration_notifyOnResolveCase :: Lens.Lens' SlackChannelConfiguration (Prelude.Maybe Prelude.Bool)
slackChannelConfiguration_notifyOnResolveCase :: Lens' SlackChannelConfiguration (Maybe Bool)
slackChannelConfiguration_notifyOnResolveCase = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SlackChannelConfiguration' {Maybe Bool
notifyOnResolveCase :: Maybe Bool
$sel:notifyOnResolveCase:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Bool
notifyOnResolveCase} -> Maybe Bool
notifyOnResolveCase) (\s :: SlackChannelConfiguration
s@SlackChannelConfiguration' {} Maybe Bool
a -> SlackChannelConfiguration
s {$sel:notifyOnResolveCase:SlackChannelConfiguration' :: Maybe Bool
notifyOnResolveCase = Maybe Bool
a} :: SlackChannelConfiguration)

-- | The channel ID in Slack. This ID identifies a channel within a Slack
-- workspace.
slackChannelConfiguration_channelId :: Lens.Lens' SlackChannelConfiguration Prelude.Text
slackChannelConfiguration_channelId :: Lens' SlackChannelConfiguration Text
slackChannelConfiguration_channelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SlackChannelConfiguration' {Text
channelId :: Text
$sel:channelId:SlackChannelConfiguration' :: SlackChannelConfiguration -> Text
channelId} -> Text
channelId) (\s :: SlackChannelConfiguration
s@SlackChannelConfiguration' {} Text
a -> SlackChannelConfiguration
s {$sel:channelId:SlackChannelConfiguration' :: Text
channelId = Text
a} :: SlackChannelConfiguration)

-- | The team ID in Slack. This ID uniquely identifies a Slack workspace,
-- such as @T012ABCDEFG@.
slackChannelConfiguration_teamId :: Lens.Lens' SlackChannelConfiguration Prelude.Text
slackChannelConfiguration_teamId :: Lens' SlackChannelConfiguration Text
slackChannelConfiguration_teamId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SlackChannelConfiguration' {Text
teamId :: Text
$sel:teamId:SlackChannelConfiguration' :: SlackChannelConfiguration -> Text
teamId} -> Text
teamId) (\s :: SlackChannelConfiguration
s@SlackChannelConfiguration' {} Text
a -> SlackChannelConfiguration
s {$sel:teamId:SlackChannelConfiguration' :: Text
teamId = Text
a} :: SlackChannelConfiguration)

instance Data.FromJSON SlackChannelConfiguration where
  parseJSON :: Value -> Parser SlackChannelConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SlackChannelConfiguration"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe NotificationSeverityLevel
-> Maybe Bool
-> Maybe Bool
-> Text
-> Text
-> SlackChannelConfiguration
SlackChannelConfiguration'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"channelName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"channelRoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"notifyOnAddCorrespondenceToCase")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"notifyOnCaseSeverity")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"notifyOnCreateOrReopenCase")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"notifyOnResolveCase")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"channelId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"teamId")
      )

instance Prelude.Hashable SlackChannelConfiguration where
  hashWithSalt :: Int -> SlackChannelConfiguration -> Int
hashWithSalt Int
_salt SlackChannelConfiguration' {Maybe Bool
Maybe Text
Maybe NotificationSeverityLevel
Text
teamId :: Text
channelId :: Text
notifyOnResolveCase :: Maybe Bool
notifyOnCreateOrReopenCase :: Maybe Bool
notifyOnCaseSeverity :: Maybe NotificationSeverityLevel
notifyOnAddCorrespondenceToCase :: Maybe Bool
channelRoleArn :: Maybe Text
channelName :: Maybe Text
$sel:teamId:SlackChannelConfiguration' :: SlackChannelConfiguration -> Text
$sel:channelId:SlackChannelConfiguration' :: SlackChannelConfiguration -> Text
$sel:notifyOnResolveCase:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Bool
$sel:notifyOnCreateOrReopenCase:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Bool
$sel:notifyOnCaseSeverity:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe NotificationSeverityLevel
$sel:notifyOnAddCorrespondenceToCase:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Bool
$sel:channelRoleArn:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Text
$sel:channelName:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
channelName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
channelRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
notifyOnAddCorrespondenceToCase
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NotificationSeverityLevel
notifyOnCaseSeverity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
notifyOnCreateOrReopenCase
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
notifyOnResolveCase
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
channelId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
teamId

instance Prelude.NFData SlackChannelConfiguration where
  rnf :: SlackChannelConfiguration -> ()
rnf SlackChannelConfiguration' {Maybe Bool
Maybe Text
Maybe NotificationSeverityLevel
Text
teamId :: Text
channelId :: Text
notifyOnResolveCase :: Maybe Bool
notifyOnCreateOrReopenCase :: Maybe Bool
notifyOnCaseSeverity :: Maybe NotificationSeverityLevel
notifyOnAddCorrespondenceToCase :: Maybe Bool
channelRoleArn :: Maybe Text
channelName :: Maybe Text
$sel:teamId:SlackChannelConfiguration' :: SlackChannelConfiguration -> Text
$sel:channelId:SlackChannelConfiguration' :: SlackChannelConfiguration -> Text
$sel:notifyOnResolveCase:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Bool
$sel:notifyOnCreateOrReopenCase:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Bool
$sel:notifyOnCaseSeverity:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe NotificationSeverityLevel
$sel:notifyOnAddCorrespondenceToCase:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Bool
$sel:channelRoleArn:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Text
$sel:channelName:SlackChannelConfiguration' :: SlackChannelConfiguration -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
channelName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
channelRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
notifyOnAddCorrespondenceToCase
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NotificationSeverityLevel
notifyOnCaseSeverity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
notifyOnCreateOrReopenCase
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
notifyOnResolveCase
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
channelId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
teamId