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

    -- * Request Lenses
    describeRoutingProfile_instanceId,
    describeRoutingProfile_routingProfileId,

    -- * Destructuring the Response
    DescribeRoutingProfileResponse (..),
    newDescribeRoutingProfileResponse,

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

-- |
-- Create a value of 'DescribeRoutingProfile' 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', 'describeRoutingProfile_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'routingProfileId', 'describeRoutingProfile_routingProfileId' - The identifier of the routing profile.
newDescribeRoutingProfile ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'routingProfileId'
  Prelude.Text ->
  DescribeRoutingProfile
newDescribeRoutingProfile :: Text -> Text -> DescribeRoutingProfile
newDescribeRoutingProfile
  Text
pInstanceId_
  Text
pRoutingProfileId_ =
    DescribeRoutingProfile'
      { $sel:instanceId:DescribeRoutingProfile' :: Text
instanceId = Text
pInstanceId_,
        $sel:routingProfileId:DescribeRoutingProfile' :: Text
routingProfileId = Text
pRoutingProfileId_
      }

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

-- | The identifier of the routing profile.
describeRoutingProfile_routingProfileId :: Lens.Lens' DescribeRoutingProfile Prelude.Text
describeRoutingProfile_routingProfileId :: Lens' DescribeRoutingProfile Text
describeRoutingProfile_routingProfileId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRoutingProfile' {Text
routingProfileId :: Text
$sel:routingProfileId:DescribeRoutingProfile' :: DescribeRoutingProfile -> Text
routingProfileId} -> Text
routingProfileId) (\s :: DescribeRoutingProfile
s@DescribeRoutingProfile' {} Text
a -> DescribeRoutingProfile
s {$sel:routingProfileId:DescribeRoutingProfile' :: Text
routingProfileId = Text
a} :: DescribeRoutingProfile)

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

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

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

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

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

-- |
-- Create a value of 'DescribeRoutingProfileResponse' 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:
--
-- 'routingProfile', 'describeRoutingProfileResponse_routingProfile' - The routing profile.
--
-- 'httpStatus', 'describeRoutingProfileResponse_httpStatus' - The response's http status code.
newDescribeRoutingProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeRoutingProfileResponse
newDescribeRoutingProfileResponse :: Int -> DescribeRoutingProfileResponse
newDescribeRoutingProfileResponse Int
pHttpStatus_ =
  DescribeRoutingProfileResponse'
    { $sel:routingProfile:DescribeRoutingProfileResponse' :: Maybe RoutingProfile
routingProfile =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeRoutingProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The routing profile.
describeRoutingProfileResponse_routingProfile :: Lens.Lens' DescribeRoutingProfileResponse (Prelude.Maybe RoutingProfile)
describeRoutingProfileResponse_routingProfile :: Lens' DescribeRoutingProfileResponse (Maybe RoutingProfile)
describeRoutingProfileResponse_routingProfile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRoutingProfileResponse' {Maybe RoutingProfile
routingProfile :: Maybe RoutingProfile
$sel:routingProfile:DescribeRoutingProfileResponse' :: DescribeRoutingProfileResponse -> Maybe RoutingProfile
routingProfile} -> Maybe RoutingProfile
routingProfile) (\s :: DescribeRoutingProfileResponse
s@DescribeRoutingProfileResponse' {} Maybe RoutingProfile
a -> DescribeRoutingProfileResponse
s {$sel:routingProfile:DescribeRoutingProfileResponse' :: Maybe RoutingProfile
routingProfile = Maybe RoutingProfile
a} :: DescribeRoutingProfileResponse)

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

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