{-# 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.DescribeContact
-- 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 API is in preview release for Amazon Connect and is subject to
-- change.
--
-- Describes the specified contact.
--
-- Contact information remains available in Amazon Connect for 24 months,
-- and then it is deleted.
--
-- Only data from November 12, 2021, and later is returned by this API.
module Amazonka.Connect.DescribeContact
  ( -- * Creating a Request
    DescribeContact (..),
    newDescribeContact,

    -- * Request Lenses
    describeContact_instanceId,
    describeContact_contactId,

    -- * Destructuring the Response
    DescribeContactResponse (..),
    newDescribeContactResponse,

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

-- |
-- Create a value of 'DescribeContact' 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:
--
-- 'instanceId', 'describeContact_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'contactId', 'describeContact_contactId' - The identifier of the contact.
newDescribeContact ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'contactId'
  Prelude.Text ->
  DescribeContact
newDescribeContact :: Text -> Text -> DescribeContact
newDescribeContact Text
pInstanceId_ Text
pContactId_ =
  DescribeContact'
    { $sel:instanceId:DescribeContact' :: Text
instanceId = Text
pInstanceId_,
      $sel:contactId:DescribeContact' :: Text
contactId = Text
pContactId_
    }

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

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

instance Core.AWSRequest DescribeContact where
  type
    AWSResponse DescribeContact =
      DescribeContactResponse
  request :: (Service -> Service) -> DescribeContact -> Request DescribeContact
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 DescribeContact
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeContact)))
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 Contact -> Int -> DescribeContactResponse
DescribeContactResponse'
            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
"Contact")
            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 DescribeContact where
  hashWithSalt :: Int -> DescribeContact -> Int
hashWithSalt Int
_salt DescribeContact' {Text
contactId :: Text
instanceId :: Text
$sel:contactId:DescribeContact' :: DescribeContact -> Text
$sel:instanceId:DescribeContact' :: DescribeContact -> Text
..} =
    Int
_salt
      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 DescribeContact where
  rnf :: DescribeContact -> ()
rnf DescribeContact' {Text
contactId :: Text
instanceId :: Text
$sel:contactId:DescribeContact' :: DescribeContact -> Text
$sel:instanceId:DescribeContact' :: DescribeContact -> Text
..} =
    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 DescribeContact where
  toHeaders :: DescribeContact -> 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 DescribeContact where
  toPath :: DescribeContact -> ByteString
toPath DescribeContact' {Text
contactId :: Text
instanceId :: Text
$sel:contactId:DescribeContact' :: DescribeContact -> Text
$sel:instanceId:DescribeContact' :: DescribeContact -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/contacts/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
contactId
      ]

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

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

-- |
-- Create a value of 'DescribeContactResponse' 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:
--
-- 'contact', 'describeContactResponse_contact' - Information about the contact.
--
-- 'httpStatus', 'describeContactResponse_httpStatus' - The response's http status code.
newDescribeContactResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeContactResponse
newDescribeContactResponse :: Int -> DescribeContactResponse
newDescribeContactResponse Int
pHttpStatus_ =
  DescribeContactResponse'
    { $sel:contact:DescribeContactResponse' :: Maybe Contact
contact = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeContactResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the contact.
describeContactResponse_contact :: Lens.Lens' DescribeContactResponse (Prelude.Maybe Contact)
describeContactResponse_contact :: Lens' DescribeContactResponse (Maybe Contact)
describeContactResponse_contact = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeContactResponse' {Maybe Contact
contact :: Maybe Contact
$sel:contact:DescribeContactResponse' :: DescribeContactResponse -> Maybe Contact
contact} -> Maybe Contact
contact) (\s :: DescribeContactResponse
s@DescribeContactResponse' {} Maybe Contact
a -> DescribeContactResponse
s {$sel:contact:DescribeContactResponse' :: Maybe Contact
contact = Maybe Contact
a} :: DescribeContactResponse)

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

instance Prelude.NFData DescribeContactResponse where
  rnf :: DescribeContactResponse -> ()
rnf DescribeContactResponse' {Int
Maybe Contact
httpStatus :: Int
contact :: Maybe Contact
$sel:httpStatus:DescribeContactResponse' :: DescribeContactResponse -> Int
$sel:contact:DescribeContactResponse' :: DescribeContactResponse -> Maybe Contact
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Contact
contact
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus