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

    -- * Request Lenses
    createRoutingProfile_queueConfigs,
    createRoutingProfile_tags,
    createRoutingProfile_instanceId,
    createRoutingProfile_name,
    createRoutingProfile_description,
    createRoutingProfile_defaultOutboundQueueId,
    createRoutingProfile_mediaConcurrencies,

    -- * Destructuring the Response
    CreateRoutingProfileResponse (..),
    newCreateRoutingProfileResponse,

    -- * Response Lenses
    createRoutingProfileResponse_routingProfileArn,
    createRoutingProfileResponse_routingProfileId,
    createRoutingProfileResponse_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:/ 'newCreateRoutingProfile' smart constructor.
data CreateRoutingProfile = CreateRoutingProfile'
  { -- | The inbound queues associated with the routing profile. If no queue is
    -- added, the agent can make only outbound calls.
    CreateRoutingProfile -> Maybe (NonEmpty RoutingProfileQueueConfig)
queueConfigs :: Prelude.Maybe (Prelude.NonEmpty RoutingProfileQueueConfig),
    -- | The tags used to organize, track, or control access for this resource.
    -- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
    CreateRoutingProfile -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    CreateRoutingProfile -> Text
instanceId :: Prelude.Text,
    -- | The name of the routing profile. Must not be more than 127 characters.
    CreateRoutingProfile -> Text
name :: Prelude.Text,
    -- | Description of the routing profile. Must not be more than 250
    -- characters.
    CreateRoutingProfile -> Text
description :: Prelude.Text,
    -- | The default outbound queue for the routing profile.
    CreateRoutingProfile -> Text
defaultOutboundQueueId :: Prelude.Text,
    -- | The channels that agents can handle in the Contact Control Panel (CCP)
    -- for this routing profile.
    CreateRoutingProfile -> [MediaConcurrency]
mediaConcurrencies :: [MediaConcurrency]
  }
  deriving (CreateRoutingProfile -> CreateRoutingProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRoutingProfile -> CreateRoutingProfile -> Bool
$c/= :: CreateRoutingProfile -> CreateRoutingProfile -> Bool
== :: CreateRoutingProfile -> CreateRoutingProfile -> Bool
$c== :: CreateRoutingProfile -> CreateRoutingProfile -> Bool
Prelude.Eq, ReadPrec [CreateRoutingProfile]
ReadPrec CreateRoutingProfile
Int -> ReadS CreateRoutingProfile
ReadS [CreateRoutingProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRoutingProfile]
$creadListPrec :: ReadPrec [CreateRoutingProfile]
readPrec :: ReadPrec CreateRoutingProfile
$creadPrec :: ReadPrec CreateRoutingProfile
readList :: ReadS [CreateRoutingProfile]
$creadList :: ReadS [CreateRoutingProfile]
readsPrec :: Int -> ReadS CreateRoutingProfile
$creadsPrec :: Int -> ReadS CreateRoutingProfile
Prelude.Read, Int -> CreateRoutingProfile -> ShowS
[CreateRoutingProfile] -> ShowS
CreateRoutingProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRoutingProfile] -> ShowS
$cshowList :: [CreateRoutingProfile] -> ShowS
show :: CreateRoutingProfile -> String
$cshow :: CreateRoutingProfile -> String
showsPrec :: Int -> CreateRoutingProfile -> ShowS
$cshowsPrec :: Int -> CreateRoutingProfile -> ShowS
Prelude.Show, forall x. Rep CreateRoutingProfile x -> CreateRoutingProfile
forall x. CreateRoutingProfile -> Rep CreateRoutingProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRoutingProfile x -> CreateRoutingProfile
$cfrom :: forall x. CreateRoutingProfile -> Rep CreateRoutingProfile x
Prelude.Generic)

-- |
-- Create a value of 'CreateRoutingProfile' 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:
--
-- 'queueConfigs', 'createRoutingProfile_queueConfigs' - The inbound queues associated with the routing profile. If no queue is
-- added, the agent can make only outbound calls.
--
-- 'tags', 'createRoutingProfile_tags' - The tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
--
-- 'instanceId', 'createRoutingProfile_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'name', 'createRoutingProfile_name' - The name of the routing profile. Must not be more than 127 characters.
--
-- 'description', 'createRoutingProfile_description' - Description of the routing profile. Must not be more than 250
-- characters.
--
-- 'defaultOutboundQueueId', 'createRoutingProfile_defaultOutboundQueueId' - The default outbound queue for the routing profile.
--
-- 'mediaConcurrencies', 'createRoutingProfile_mediaConcurrencies' - The channels that agents can handle in the Contact Control Panel (CCP)
-- for this routing profile.
newCreateRoutingProfile ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 'description'
  Prelude.Text ->
  -- | 'defaultOutboundQueueId'
  Prelude.Text ->
  CreateRoutingProfile
newCreateRoutingProfile :: Text -> Text -> Text -> Text -> CreateRoutingProfile
newCreateRoutingProfile
  Text
pInstanceId_
  Text
pName_
  Text
pDescription_
  Text
pDefaultOutboundQueueId_ =
    CreateRoutingProfile'
      { $sel:queueConfigs:CreateRoutingProfile' :: Maybe (NonEmpty RoutingProfileQueueConfig)
queueConfigs =
          forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateRoutingProfile' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:instanceId:CreateRoutingProfile' :: Text
instanceId = Text
pInstanceId_,
        $sel:name:CreateRoutingProfile' :: Text
name = Text
pName_,
        $sel:description:CreateRoutingProfile' :: Text
description = Text
pDescription_,
        $sel:defaultOutboundQueueId:CreateRoutingProfile' :: Text
defaultOutboundQueueId = Text
pDefaultOutboundQueueId_,
        $sel:mediaConcurrencies:CreateRoutingProfile' :: [MediaConcurrency]
mediaConcurrencies = forall a. Monoid a => a
Prelude.mempty
      }

-- | The inbound queues associated with the routing profile. If no queue is
-- added, the agent can make only outbound calls.
createRoutingProfile_queueConfigs :: Lens.Lens' CreateRoutingProfile (Prelude.Maybe (Prelude.NonEmpty RoutingProfileQueueConfig))
createRoutingProfile_queueConfigs :: Lens'
  CreateRoutingProfile (Maybe (NonEmpty RoutingProfileQueueConfig))
createRoutingProfile_queueConfigs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoutingProfile' {Maybe (NonEmpty RoutingProfileQueueConfig)
queueConfigs :: Maybe (NonEmpty RoutingProfileQueueConfig)
$sel:queueConfigs:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (NonEmpty RoutingProfileQueueConfig)
queueConfigs} -> Maybe (NonEmpty RoutingProfileQueueConfig)
queueConfigs) (\s :: CreateRoutingProfile
s@CreateRoutingProfile' {} Maybe (NonEmpty RoutingProfileQueueConfig)
a -> CreateRoutingProfile
s {$sel:queueConfigs:CreateRoutingProfile' :: Maybe (NonEmpty RoutingProfileQueueConfig)
queueConfigs = Maybe (NonEmpty RoutingProfileQueueConfig)
a} :: CreateRoutingProfile) 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 tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
createRoutingProfile_tags :: Lens.Lens' CreateRoutingProfile (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createRoutingProfile_tags :: Lens' CreateRoutingProfile (Maybe (HashMap Text Text))
createRoutingProfile_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoutingProfile' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateRoutingProfile
s@CreateRoutingProfile' {} Maybe (HashMap Text Text)
a -> CreateRoutingProfile
s {$sel:tags:CreateRoutingProfile' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateRoutingProfile) 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 identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
createRoutingProfile_instanceId :: Lens.Lens' CreateRoutingProfile Prelude.Text
createRoutingProfile_instanceId :: Lens' CreateRoutingProfile Text
createRoutingProfile_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoutingProfile' {Text
instanceId :: Text
$sel:instanceId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
instanceId} -> Text
instanceId) (\s :: CreateRoutingProfile
s@CreateRoutingProfile' {} Text
a -> CreateRoutingProfile
s {$sel:instanceId:CreateRoutingProfile' :: Text
instanceId = Text
a} :: CreateRoutingProfile)

-- | The name of the routing profile. Must not be more than 127 characters.
createRoutingProfile_name :: Lens.Lens' CreateRoutingProfile Prelude.Text
createRoutingProfile_name :: Lens' CreateRoutingProfile Text
createRoutingProfile_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoutingProfile' {Text
name :: Text
$sel:name:CreateRoutingProfile' :: CreateRoutingProfile -> Text
name} -> Text
name) (\s :: CreateRoutingProfile
s@CreateRoutingProfile' {} Text
a -> CreateRoutingProfile
s {$sel:name:CreateRoutingProfile' :: Text
name = Text
a} :: CreateRoutingProfile)

-- | Description of the routing profile. Must not be more than 250
-- characters.
createRoutingProfile_description :: Lens.Lens' CreateRoutingProfile Prelude.Text
createRoutingProfile_description :: Lens' CreateRoutingProfile Text
createRoutingProfile_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoutingProfile' {Text
description :: Text
$sel:description:CreateRoutingProfile' :: CreateRoutingProfile -> Text
description} -> Text
description) (\s :: CreateRoutingProfile
s@CreateRoutingProfile' {} Text
a -> CreateRoutingProfile
s {$sel:description:CreateRoutingProfile' :: Text
description = Text
a} :: CreateRoutingProfile)

-- | The default outbound queue for the routing profile.
createRoutingProfile_defaultOutboundQueueId :: Lens.Lens' CreateRoutingProfile Prelude.Text
createRoutingProfile_defaultOutboundQueueId :: Lens' CreateRoutingProfile Text
createRoutingProfile_defaultOutboundQueueId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoutingProfile' {Text
defaultOutboundQueueId :: Text
$sel:defaultOutboundQueueId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
defaultOutboundQueueId} -> Text
defaultOutboundQueueId) (\s :: CreateRoutingProfile
s@CreateRoutingProfile' {} Text
a -> CreateRoutingProfile
s {$sel:defaultOutboundQueueId:CreateRoutingProfile' :: Text
defaultOutboundQueueId = Text
a} :: CreateRoutingProfile)

-- | The channels that agents can handle in the Contact Control Panel (CCP)
-- for this routing profile.
createRoutingProfile_mediaConcurrencies :: Lens.Lens' CreateRoutingProfile [MediaConcurrency]
createRoutingProfile_mediaConcurrencies :: Lens' CreateRoutingProfile [MediaConcurrency]
createRoutingProfile_mediaConcurrencies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoutingProfile' {[MediaConcurrency]
mediaConcurrencies :: [MediaConcurrency]
$sel:mediaConcurrencies:CreateRoutingProfile' :: CreateRoutingProfile -> [MediaConcurrency]
mediaConcurrencies} -> [MediaConcurrency]
mediaConcurrencies) (\s :: CreateRoutingProfile
s@CreateRoutingProfile' {} [MediaConcurrency]
a -> CreateRoutingProfile
s {$sel:mediaConcurrencies:CreateRoutingProfile' :: [MediaConcurrency]
mediaConcurrencies = [MediaConcurrency]
a} :: CreateRoutingProfile) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest CreateRoutingProfile where
  type
    AWSResponse CreateRoutingProfile =
      CreateRoutingProfileResponse
  request :: (Service -> Service)
-> CreateRoutingProfile -> Request CreateRoutingProfile
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateRoutingProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateRoutingProfile)))
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 Text -> Maybe Text -> Int -> CreateRoutingProfileResponse
CreateRoutingProfileResponse'
            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
"RoutingProfileArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RoutingProfileId")
            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 CreateRoutingProfile where
  hashWithSalt :: Int -> CreateRoutingProfile -> Int
hashWithSalt Int
_salt CreateRoutingProfile' {[MediaConcurrency]
Maybe (NonEmpty RoutingProfileQueueConfig)
Maybe (HashMap Text Text)
Text
mediaConcurrencies :: [MediaConcurrency]
defaultOutboundQueueId :: Text
description :: Text
name :: Text
instanceId :: Text
tags :: Maybe (HashMap Text Text)
queueConfigs :: Maybe (NonEmpty RoutingProfileQueueConfig)
$sel:mediaConcurrencies:CreateRoutingProfile' :: CreateRoutingProfile -> [MediaConcurrency]
$sel:defaultOutboundQueueId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:description:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:name:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:instanceId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:tags:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (HashMap Text Text)
$sel:queueConfigs:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (NonEmpty RoutingProfileQueueConfig)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty RoutingProfileQueueConfig)
queueConfigs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
defaultOutboundQueueId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [MediaConcurrency]
mediaConcurrencies

instance Prelude.NFData CreateRoutingProfile where
  rnf :: CreateRoutingProfile -> ()
rnf CreateRoutingProfile' {[MediaConcurrency]
Maybe (NonEmpty RoutingProfileQueueConfig)
Maybe (HashMap Text Text)
Text
mediaConcurrencies :: [MediaConcurrency]
defaultOutboundQueueId :: Text
description :: Text
name :: Text
instanceId :: Text
tags :: Maybe (HashMap Text Text)
queueConfigs :: Maybe (NonEmpty RoutingProfileQueueConfig)
$sel:mediaConcurrencies:CreateRoutingProfile' :: CreateRoutingProfile -> [MediaConcurrency]
$sel:defaultOutboundQueueId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:description:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:name:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:instanceId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:tags:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (HashMap Text Text)
$sel:queueConfigs:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (NonEmpty RoutingProfileQueueConfig)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty RoutingProfileQueueConfig)
queueConfigs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      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
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
defaultOutboundQueueId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [MediaConcurrency]
mediaConcurrencies

instance Data.ToHeaders CreateRoutingProfile where
  toHeaders :: CreateRoutingProfile -> 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 CreateRoutingProfile where
  toJSON :: CreateRoutingProfile -> Value
toJSON CreateRoutingProfile' {[MediaConcurrency]
Maybe (NonEmpty RoutingProfileQueueConfig)
Maybe (HashMap Text Text)
Text
mediaConcurrencies :: [MediaConcurrency]
defaultOutboundQueueId :: Text
description :: Text
name :: Text
instanceId :: Text
tags :: Maybe (HashMap Text Text)
queueConfigs :: Maybe (NonEmpty RoutingProfileQueueConfig)
$sel:mediaConcurrencies:CreateRoutingProfile' :: CreateRoutingProfile -> [MediaConcurrency]
$sel:defaultOutboundQueueId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:description:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:name:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:instanceId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:tags:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (HashMap Text Text)
$sel:queueConfigs:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (NonEmpty RoutingProfileQueueConfig)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"QueueConfigs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty RoutingProfileQueueConfig)
queueConfigs,
            (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
description),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"DefaultOutboundQueueId"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
defaultOutboundQueueId
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"MediaConcurrencies" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [MediaConcurrency]
mediaConcurrencies)
          ]
      )

instance Data.ToPath CreateRoutingProfile where
  toPath :: CreateRoutingProfile -> ByteString
toPath CreateRoutingProfile' {[MediaConcurrency]
Maybe (NonEmpty RoutingProfileQueueConfig)
Maybe (HashMap Text Text)
Text
mediaConcurrencies :: [MediaConcurrency]
defaultOutboundQueueId :: Text
description :: Text
name :: Text
instanceId :: Text
tags :: Maybe (HashMap Text Text)
queueConfigs :: Maybe (NonEmpty RoutingProfileQueueConfig)
$sel:mediaConcurrencies:CreateRoutingProfile' :: CreateRoutingProfile -> [MediaConcurrency]
$sel:defaultOutboundQueueId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:description:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:name:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:instanceId:CreateRoutingProfile' :: CreateRoutingProfile -> Text
$sel:tags:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (HashMap Text Text)
$sel:queueConfigs:CreateRoutingProfile' :: CreateRoutingProfile -> Maybe (NonEmpty RoutingProfileQueueConfig)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/routing-profiles/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId]

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

-- | /See:/ 'newCreateRoutingProfileResponse' smart constructor.
data CreateRoutingProfileResponse = CreateRoutingProfileResponse'
  { -- | The Amazon Resource Name (ARN) of the routing profile.
    CreateRoutingProfileResponse -> Maybe Text
routingProfileArn :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the routing profile.
    CreateRoutingProfileResponse -> Maybe Text
routingProfileId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateRoutingProfileResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateRoutingProfileResponse
-> CreateRoutingProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRoutingProfileResponse
-> CreateRoutingProfileResponse -> Bool
$c/= :: CreateRoutingProfileResponse
-> CreateRoutingProfileResponse -> Bool
== :: CreateRoutingProfileResponse
-> CreateRoutingProfileResponse -> Bool
$c== :: CreateRoutingProfileResponse
-> CreateRoutingProfileResponse -> Bool
Prelude.Eq, ReadPrec [CreateRoutingProfileResponse]
ReadPrec CreateRoutingProfileResponse
Int -> ReadS CreateRoutingProfileResponse
ReadS [CreateRoutingProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRoutingProfileResponse]
$creadListPrec :: ReadPrec [CreateRoutingProfileResponse]
readPrec :: ReadPrec CreateRoutingProfileResponse
$creadPrec :: ReadPrec CreateRoutingProfileResponse
readList :: ReadS [CreateRoutingProfileResponse]
$creadList :: ReadS [CreateRoutingProfileResponse]
readsPrec :: Int -> ReadS CreateRoutingProfileResponse
$creadsPrec :: Int -> ReadS CreateRoutingProfileResponse
Prelude.Read, Int -> CreateRoutingProfileResponse -> ShowS
[CreateRoutingProfileResponse] -> ShowS
CreateRoutingProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRoutingProfileResponse] -> ShowS
$cshowList :: [CreateRoutingProfileResponse] -> ShowS
show :: CreateRoutingProfileResponse -> String
$cshow :: CreateRoutingProfileResponse -> String
showsPrec :: Int -> CreateRoutingProfileResponse -> ShowS
$cshowsPrec :: Int -> CreateRoutingProfileResponse -> ShowS
Prelude.Show, forall x.
Rep CreateRoutingProfileResponse x -> CreateRoutingProfileResponse
forall x.
CreateRoutingProfileResponse -> Rep CreateRoutingProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateRoutingProfileResponse x -> CreateRoutingProfileResponse
$cfrom :: forall x.
CreateRoutingProfileResponse -> Rep CreateRoutingProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateRoutingProfileResponse' 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:
--
-- 'routingProfileArn', 'createRoutingProfileResponse_routingProfileArn' - The Amazon Resource Name (ARN) of the routing profile.
--
-- 'routingProfileId', 'createRoutingProfileResponse_routingProfileId' - The identifier of the routing profile.
--
-- 'httpStatus', 'createRoutingProfileResponse_httpStatus' - The response's http status code.
newCreateRoutingProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateRoutingProfileResponse
newCreateRoutingProfileResponse :: Int -> CreateRoutingProfileResponse
newCreateRoutingProfileResponse Int
pHttpStatus_ =
  CreateRoutingProfileResponse'
    { $sel:routingProfileArn:CreateRoutingProfileResponse' :: Maybe Text
routingProfileArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:routingProfileId:CreateRoutingProfileResponse' :: Maybe Text
routingProfileId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateRoutingProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the routing profile.
createRoutingProfileResponse_routingProfileArn :: Lens.Lens' CreateRoutingProfileResponse (Prelude.Maybe Prelude.Text)
createRoutingProfileResponse_routingProfileArn :: Lens' CreateRoutingProfileResponse (Maybe Text)
createRoutingProfileResponse_routingProfileArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoutingProfileResponse' {Maybe Text
routingProfileArn :: Maybe Text
$sel:routingProfileArn:CreateRoutingProfileResponse' :: CreateRoutingProfileResponse -> Maybe Text
routingProfileArn} -> Maybe Text
routingProfileArn) (\s :: CreateRoutingProfileResponse
s@CreateRoutingProfileResponse' {} Maybe Text
a -> CreateRoutingProfileResponse
s {$sel:routingProfileArn:CreateRoutingProfileResponse' :: Maybe Text
routingProfileArn = Maybe Text
a} :: CreateRoutingProfileResponse)

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

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

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