{-# 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.GetContactAttributes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the contact attributes for the specified contact.
module Amazonka.Connect.GetContactAttributes
  ( -- * Creating a Request
    GetContactAttributes (..),
    newGetContactAttributes,

    -- * Request Lenses
    getContactAttributes_instanceId,
    getContactAttributes_initialContactId,

    -- * Destructuring the Response
    GetContactAttributesResponse (..),
    newGetContactAttributesResponse,

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

-- |
-- Create a value of 'GetContactAttributes' 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', 'getContactAttributes_instanceId' - The identifier of the Amazon Connect instance.
--
-- 'initialContactId', 'getContactAttributes_initialContactId' - The identifier of the initial contact.
newGetContactAttributes ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'initialContactId'
  Prelude.Text ->
  GetContactAttributes
newGetContactAttributes :: Text -> Text -> GetContactAttributes
newGetContactAttributes
  Text
pInstanceId_
  Text
pInitialContactId_ =
    GetContactAttributes'
      { $sel:instanceId:GetContactAttributes' :: Text
instanceId = Text
pInstanceId_,
        $sel:initialContactId:GetContactAttributes' :: Text
initialContactId = Text
pInitialContactId_
      }

-- | The identifier of the Amazon Connect instance.
getContactAttributes_instanceId :: Lens.Lens' GetContactAttributes Prelude.Text
getContactAttributes_instanceId :: Lens' GetContactAttributes Text
getContactAttributes_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetContactAttributes' {Text
instanceId :: Text
$sel:instanceId:GetContactAttributes' :: GetContactAttributes -> Text
instanceId} -> Text
instanceId) (\s :: GetContactAttributes
s@GetContactAttributes' {} Text
a -> GetContactAttributes
s {$sel:instanceId:GetContactAttributes' :: Text
instanceId = Text
a} :: GetContactAttributes)

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

instance Core.AWSRequest GetContactAttributes where
  type
    AWSResponse GetContactAttributes =
      GetContactAttributesResponse
  request :: (Service -> Service)
-> GetContactAttributes -> Request GetContactAttributes
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 GetContactAttributes
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetContactAttributes)))
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 (HashMap Text Text) -> Int -> GetContactAttributesResponse
GetContactAttributesResponse'
            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
"Attributes" 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 GetContactAttributes where
  hashWithSalt :: Int -> GetContactAttributes -> Int
hashWithSalt Int
_salt GetContactAttributes' {Text
initialContactId :: Text
instanceId :: Text
$sel:initialContactId:GetContactAttributes' :: GetContactAttributes -> Text
$sel:instanceId:GetContactAttributes' :: GetContactAttributes -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
initialContactId

instance Prelude.NFData GetContactAttributes where
  rnf :: GetContactAttributes -> ()
rnf GetContactAttributes' {Text
initialContactId :: Text
instanceId :: Text
$sel:initialContactId:GetContactAttributes' :: GetContactAttributes -> Text
$sel:instanceId:GetContactAttributes' :: GetContactAttributes -> 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
initialContactId

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

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

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

-- |
-- Create a value of 'GetContactAttributesResponse' 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:
--
-- 'attributes', 'getContactAttributesResponse_attributes' - Information about the attributes.
--
-- 'httpStatus', 'getContactAttributesResponse_httpStatus' - The response's http status code.
newGetContactAttributesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetContactAttributesResponse
newGetContactAttributesResponse :: Int -> GetContactAttributesResponse
newGetContactAttributesResponse Int
pHttpStatus_ =
  GetContactAttributesResponse'
    { $sel:attributes:GetContactAttributesResponse' :: Maybe (HashMap Text Text)
attributes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetContactAttributesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the attributes.
getContactAttributesResponse_attributes :: Lens.Lens' GetContactAttributesResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getContactAttributesResponse_attributes :: Lens' GetContactAttributesResponse (Maybe (HashMap Text Text))
getContactAttributesResponse_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetContactAttributesResponse' {Maybe (HashMap Text Text)
attributes :: Maybe (HashMap Text Text)
$sel:attributes:GetContactAttributesResponse' :: GetContactAttributesResponse -> Maybe (HashMap Text Text)
attributes} -> Maybe (HashMap Text Text)
attributes) (\s :: GetContactAttributesResponse
s@GetContactAttributesResponse' {} Maybe (HashMap Text Text)
a -> GetContactAttributesResponse
s {$sel:attributes:GetContactAttributesResponse' :: Maybe (HashMap Text Text)
attributes = Maybe (HashMap Text Text)
a} :: GetContactAttributesResponse) 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.
getContactAttributesResponse_httpStatus :: Lens.Lens' GetContactAttributesResponse Prelude.Int
getContactAttributesResponse_httpStatus :: Lens' GetContactAttributesResponse Int
getContactAttributesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetContactAttributesResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetContactAttributesResponse' :: GetContactAttributesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetContactAttributesResponse
s@GetContactAttributesResponse' {} Int
a -> GetContactAttributesResponse
s {$sel:httpStatus:GetContactAttributesResponse' :: Int
httpStatus = Int
a} :: GetContactAttributesResponse)

instance Prelude.NFData GetContactAttributesResponse where
  rnf :: GetContactAttributesResponse -> ()
rnf GetContactAttributesResponse' {Int
Maybe (HashMap Text Text)
httpStatus :: Int
attributes :: Maybe (HashMap Text Text)
$sel:httpStatus:GetContactAttributesResponse' :: GetContactAttributesResponse -> Int
$sel:attributes:GetContactAttributesResponse' :: GetContactAttributesResponse -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
attributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus