{-# 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.Connect.DismissUserContact
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Dismisses contacts from an agent’s CCP and returns the agent to an
-- available state, which allows the agent to receive a new routed contact.
-- Contacts can only be dismissed if they are in a @MISSED@, @ERROR@,
-- @ENDED@, or @REJECTED@ state in the
-- <https://docs.aws.amazon.com/connect/latest/adminguide/about-contact-states.html Agent Event Stream>.
module Amazonka.Connect.DismissUserContact
  ( -- * Creating a Request
    DismissUserContact (..),
    newDismissUserContact,

    -- * Request Lenses
    dismissUserContact_userId,
    dismissUserContact_instanceId,
    dismissUserContact_contactId,

    -- * Destructuring the Response
    DismissUserContactResponse (..),
    newDismissUserContactResponse,

    -- * Response Lenses
    dismissUserContactResponse_httpStatus,
  )
where

import Amazonka.Connect.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:/ 'newDismissUserContact' smart constructor.
data DismissUserContact = DismissUserContact'
  { -- | The identifier of the user account.
    DismissUserContact -> Text
userId :: Prelude.Text,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    DismissUserContact -> Text
instanceId :: Prelude.Text,
    -- | The identifier of the contact.
    DismissUserContact -> Text
contactId :: Prelude.Text
  }
  deriving (DismissUserContact -> DismissUserContact -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DismissUserContact -> DismissUserContact -> Bool
$c/= :: DismissUserContact -> DismissUserContact -> Bool
== :: DismissUserContact -> DismissUserContact -> Bool
$c== :: DismissUserContact -> DismissUserContact -> Bool
Prelude.Eq, ReadPrec [DismissUserContact]
ReadPrec DismissUserContact
Int -> ReadS DismissUserContact
ReadS [DismissUserContact]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DismissUserContact]
$creadListPrec :: ReadPrec [DismissUserContact]
readPrec :: ReadPrec DismissUserContact
$creadPrec :: ReadPrec DismissUserContact
readList :: ReadS [DismissUserContact]
$creadList :: ReadS [DismissUserContact]
readsPrec :: Int -> ReadS DismissUserContact
$creadsPrec :: Int -> ReadS DismissUserContact
Prelude.Read, Int -> DismissUserContact -> ShowS
[DismissUserContact] -> ShowS
DismissUserContact -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DismissUserContact] -> ShowS
$cshowList :: [DismissUserContact] -> ShowS
show :: DismissUserContact -> String
$cshow :: DismissUserContact -> String
showsPrec :: Int -> DismissUserContact -> ShowS
$cshowsPrec :: Int -> DismissUserContact -> ShowS
Prelude.Show, forall x. Rep DismissUserContact x -> DismissUserContact
forall x. DismissUserContact -> Rep DismissUserContact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DismissUserContact x -> DismissUserContact
$cfrom :: forall x. DismissUserContact -> Rep DismissUserContact x
Prelude.Generic)

-- |
-- Create a value of 'DismissUserContact' 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:
--
-- 'userId', 'dismissUserContact_userId' - The identifier of the user account.
--
-- 'instanceId', 'dismissUserContact_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'contactId', 'dismissUserContact_contactId' - The identifier of the contact.
newDismissUserContact ::
  -- | 'userId'
  Prelude.Text ->
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'contactId'
  Prelude.Text ->
  DismissUserContact
newDismissUserContact :: Text -> Text -> Text -> DismissUserContact
newDismissUserContact
  Text
pUserId_
  Text
pInstanceId_
  Text
pContactId_ =
    DismissUserContact'
      { $sel:userId:DismissUserContact' :: Text
userId = Text
pUserId_,
        $sel:instanceId:DismissUserContact' :: Text
instanceId = Text
pInstanceId_,
        $sel:contactId:DismissUserContact' :: Text
contactId = Text
pContactId_
      }

-- | The identifier of the user account.
dismissUserContact_userId :: Lens.Lens' DismissUserContact Prelude.Text
dismissUserContact_userId :: Lens' DismissUserContact Text
dismissUserContact_userId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DismissUserContact' {Text
userId :: Text
$sel:userId:DismissUserContact' :: DismissUserContact -> Text
userId} -> Text
userId) (\s :: DismissUserContact
s@DismissUserContact' {} Text
a -> DismissUserContact
s {$sel:userId:DismissUserContact' :: Text
userId = Text
a} :: DismissUserContact)

-- | The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
dismissUserContact_instanceId :: Lens.Lens' DismissUserContact Prelude.Text
dismissUserContact_instanceId :: Lens' DismissUserContact Text
dismissUserContact_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DismissUserContact' {Text
instanceId :: Text
$sel:instanceId:DismissUserContact' :: DismissUserContact -> Text
instanceId} -> Text
instanceId) (\s :: DismissUserContact
s@DismissUserContact' {} Text
a -> DismissUserContact
s {$sel:instanceId:DismissUserContact' :: Text
instanceId = Text
a} :: DismissUserContact)

-- | The identifier of the contact.
dismissUserContact_contactId :: Lens.Lens' DismissUserContact Prelude.Text
dismissUserContact_contactId :: Lens' DismissUserContact Text
dismissUserContact_contactId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DismissUserContact' {Text
contactId :: Text
$sel:contactId:DismissUserContact' :: DismissUserContact -> Text
contactId} -> Text
contactId) (\s :: DismissUserContact
s@DismissUserContact' {} Text
a -> DismissUserContact
s {$sel:contactId:DismissUserContact' :: Text
contactId = Text
a} :: DismissUserContact)

instance Core.AWSRequest DismissUserContact where
  type
    AWSResponse DismissUserContact =
      DismissUserContactResponse
  request :: (Service -> Service)
-> DismissUserContact -> Request DismissUserContact
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 DismissUserContact
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DismissUserContact)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DismissUserContactResponse
DismissUserContactResponse'
            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))
      )

instance Prelude.Hashable DismissUserContact where
  hashWithSalt :: Int -> DismissUserContact -> Int
hashWithSalt Int
_salt DismissUserContact' {Text
contactId :: Text
instanceId :: Text
userId :: Text
$sel:contactId:DismissUserContact' :: DismissUserContact -> Text
$sel:instanceId:DismissUserContact' :: DismissUserContact -> Text
$sel:userId:DismissUserContact' :: DismissUserContact -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
contactId

instance Prelude.NFData DismissUserContact where
  rnf :: DismissUserContact -> ()
rnf DismissUserContact' {Text
contactId :: Text
instanceId :: Text
userId :: Text
$sel:contactId:DismissUserContact' :: DismissUserContact -> Text
$sel:instanceId:DismissUserContact' :: DismissUserContact -> Text
$sel:userId:DismissUserContact' :: DismissUserContact -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
userId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
contactId

instance Data.ToHeaders DismissUserContact where
  toHeaders :: DismissUserContact -> 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 DismissUserContact where
  toJSON :: DismissUserContact -> Value
toJSON DismissUserContact' {Text
contactId :: Text
instanceId :: Text
userId :: Text
$sel:contactId:DismissUserContact' :: DismissUserContact -> Text
$sel:instanceId:DismissUserContact' :: DismissUserContact -> Text
$sel:userId:DismissUserContact' :: DismissUserContact -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"ContactId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
contactId)]
      )

instance Data.ToPath DismissUserContact where
  toPath :: DismissUserContact -> ByteString
toPath DismissUserContact' {Text
contactId :: Text
instanceId :: Text
userId :: Text
$sel:contactId:DismissUserContact' :: DismissUserContact -> Text
$sel:instanceId:DismissUserContact' :: DismissUserContact -> Text
$sel:userId:DismissUserContact' :: DismissUserContact -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/users/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
userId,
        ByteString
"/contact"
      ]

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

-- | /See:/ 'newDismissUserContactResponse' smart constructor.
data DismissUserContactResponse = DismissUserContactResponse'
  { -- | The response's http status code.
    DismissUserContactResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DismissUserContactResponse -> DismissUserContactResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DismissUserContactResponse -> DismissUserContactResponse -> Bool
$c/= :: DismissUserContactResponse -> DismissUserContactResponse -> Bool
== :: DismissUserContactResponse -> DismissUserContactResponse -> Bool
$c== :: DismissUserContactResponse -> DismissUserContactResponse -> Bool
Prelude.Eq, ReadPrec [DismissUserContactResponse]
ReadPrec DismissUserContactResponse
Int -> ReadS DismissUserContactResponse
ReadS [DismissUserContactResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DismissUserContactResponse]
$creadListPrec :: ReadPrec [DismissUserContactResponse]
readPrec :: ReadPrec DismissUserContactResponse
$creadPrec :: ReadPrec DismissUserContactResponse
readList :: ReadS [DismissUserContactResponse]
$creadList :: ReadS [DismissUserContactResponse]
readsPrec :: Int -> ReadS DismissUserContactResponse
$creadsPrec :: Int -> ReadS DismissUserContactResponse
Prelude.Read, Int -> DismissUserContactResponse -> ShowS
[DismissUserContactResponse] -> ShowS
DismissUserContactResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DismissUserContactResponse] -> ShowS
$cshowList :: [DismissUserContactResponse] -> ShowS
show :: DismissUserContactResponse -> String
$cshow :: DismissUserContactResponse -> String
showsPrec :: Int -> DismissUserContactResponse -> ShowS
$cshowsPrec :: Int -> DismissUserContactResponse -> ShowS
Prelude.Show, forall x.
Rep DismissUserContactResponse x -> DismissUserContactResponse
forall x.
DismissUserContactResponse -> Rep DismissUserContactResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DismissUserContactResponse x -> DismissUserContactResponse
$cfrom :: forall x.
DismissUserContactResponse -> Rep DismissUserContactResponse x
Prelude.Generic)

-- |
-- Create a value of 'DismissUserContactResponse' 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', 'dismissUserContactResponse_httpStatus' - The response's http status code.
newDismissUserContactResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DismissUserContactResponse
newDismissUserContactResponse :: Int -> DismissUserContactResponse
newDismissUserContactResponse Int
pHttpStatus_ =
  DismissUserContactResponse'
    { $sel:httpStatus:DismissUserContactResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData DismissUserContactResponse where
  rnf :: DismissUserContactResponse -> ()
rnf DismissUserContactResponse' {Int
httpStatus :: Int
$sel:httpStatus:DismissUserContactResponse' :: DismissUserContactResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus