{-# 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.AlexaBusiness.GetContact
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the contact details by the contact ARN.
module Amazonka.AlexaBusiness.GetContact
  ( -- * Creating a Request
    GetContact (..),
    newGetContact,

    -- * Request Lenses
    getContact_contactArn,

    -- * Destructuring the Response
    GetContactResponse (..),
    newGetContactResponse,

    -- * Response Lenses
    getContactResponse_contact,
    getContactResponse_httpStatus,
  )
where

import Amazonka.AlexaBusiness.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:/ 'newGetContact' smart constructor.
data GetContact = GetContact'
  { -- | The ARN of the contact for which to request details.
    GetContact -> Text
contactArn :: Prelude.Text
  }
  deriving (GetContact -> GetContact -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetContact -> GetContact -> Bool
$c/= :: GetContact -> GetContact -> Bool
== :: GetContact -> GetContact -> Bool
$c== :: GetContact -> GetContact -> Bool
Prelude.Eq, ReadPrec [GetContact]
ReadPrec GetContact
Int -> ReadS GetContact
ReadS [GetContact]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetContact]
$creadListPrec :: ReadPrec [GetContact]
readPrec :: ReadPrec GetContact
$creadPrec :: ReadPrec GetContact
readList :: ReadS [GetContact]
$creadList :: ReadS [GetContact]
readsPrec :: Int -> ReadS GetContact
$creadsPrec :: Int -> ReadS GetContact
Prelude.Read, Int -> GetContact -> ShowS
[GetContact] -> ShowS
GetContact -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetContact] -> ShowS
$cshowList :: [GetContact] -> ShowS
show :: GetContact -> String
$cshow :: GetContact -> String
showsPrec :: Int -> GetContact -> ShowS
$cshowsPrec :: Int -> GetContact -> ShowS
Prelude.Show, forall x. Rep GetContact x -> GetContact
forall x. GetContact -> Rep GetContact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetContact x -> GetContact
$cfrom :: forall x. GetContact -> Rep GetContact x
Prelude.Generic)

-- |
-- Create a value of 'GetContact' 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:
--
-- 'contactArn', 'getContact_contactArn' - The ARN of the contact for which to request details.
newGetContact ::
  -- | 'contactArn'
  Prelude.Text ->
  GetContact
newGetContact :: Text -> GetContact
newGetContact Text
pContactArn_ =
  GetContact' {$sel:contactArn:GetContact' :: Text
contactArn = Text
pContactArn_}

-- | The ARN of the contact for which to request details.
getContact_contactArn :: Lens.Lens' GetContact Prelude.Text
getContact_contactArn :: Lens' GetContact Text
getContact_contactArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetContact' {Text
contactArn :: Text
$sel:contactArn:GetContact' :: GetContact -> Text
contactArn} -> Text
contactArn) (\s :: GetContact
s@GetContact' {} Text
a -> GetContact
s {$sel:contactArn:GetContact' :: Text
contactArn = Text
a} :: GetContact)

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

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

instance Data.ToHeaders GetContact where
  toHeaders :: GetContact -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AlexaForBusiness.GetContact" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetContact where
  toJSON :: GetContact -> Value
toJSON GetContact' {Text
contactArn :: Text
$sel:contactArn:GetContact' :: GetContact -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"ContactArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
contactArn)]
      )

instance Data.ToPath GetContact where
  toPath :: GetContact -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetContactResponse' smart constructor.
data GetContactResponse = GetContactResponse'
  { -- | The details of the requested contact.
    GetContactResponse -> Maybe Contact
contact :: Prelude.Maybe Contact,
    -- | The response's http status code.
    GetContactResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetContactResponse -> GetContactResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetContactResponse -> GetContactResponse -> Bool
$c/= :: GetContactResponse -> GetContactResponse -> Bool
== :: GetContactResponse -> GetContactResponse -> Bool
$c== :: GetContactResponse -> GetContactResponse -> Bool
Prelude.Eq, Int -> GetContactResponse -> ShowS
[GetContactResponse] -> ShowS
GetContactResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetContactResponse] -> ShowS
$cshowList :: [GetContactResponse] -> ShowS
show :: GetContactResponse -> String
$cshow :: GetContactResponse -> String
showsPrec :: Int -> GetContactResponse -> ShowS
$cshowsPrec :: Int -> GetContactResponse -> ShowS
Prelude.Show, forall x. Rep GetContactResponse x -> GetContactResponse
forall x. GetContactResponse -> Rep GetContactResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetContactResponse x -> GetContactResponse
$cfrom :: forall x. GetContactResponse -> Rep GetContactResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetContactResponse' 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', 'getContactResponse_contact' - The details of the requested contact.
--
-- 'httpStatus', 'getContactResponse_httpStatus' - The response's http status code.
newGetContactResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetContactResponse
newGetContactResponse :: Int -> GetContactResponse
newGetContactResponse Int
pHttpStatus_ =
  GetContactResponse'
    { $sel:contact:GetContactResponse' :: Maybe Contact
contact = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetContactResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The details of the requested contact.
getContactResponse_contact :: Lens.Lens' GetContactResponse (Prelude.Maybe Contact)
getContactResponse_contact :: Lens' GetContactResponse (Maybe Contact)
getContactResponse_contact = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetContactResponse' {Maybe Contact
contact :: Maybe Contact
$sel:contact:GetContactResponse' :: GetContactResponse -> Maybe Contact
contact} -> Maybe Contact
contact) (\s :: GetContactResponse
s@GetContactResponse' {} Maybe Contact
a -> GetContactResponse
s {$sel:contact:GetContactResponse' :: Maybe Contact
contact = Maybe Contact
a} :: GetContactResponse)

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

instance Prelude.NFData GetContactResponse where
  rnf :: GetContactResponse -> ()
rnf GetContactResponse' {Int
Maybe Contact
httpStatus :: Int
contact :: Maybe Contact
$sel:httpStatus:GetContactResponse' :: GetContactResponse -> Int
$sel:contact:GetContactResponse' :: GetContactResponse -> 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