{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.UserData
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Connect.Types.UserData where

import Amazonka.Connect.Types.AgentContactReference
import Amazonka.Connect.Types.AgentStatusReference
import Amazonka.Connect.Types.Channel
import Amazonka.Connect.Types.HierarchyPathReference
import Amazonka.Connect.Types.RoutingProfileReference
import Amazonka.Connect.Types.UserReference
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

-- | Data for a user.
--
-- /See:/ 'newUserData' smart constructor.
data UserData = UserData'
  { -- | A map of active slots by channel. The key is a channel name. The value
    -- is an integer: the number of active slots.
    UserData -> Maybe (HashMap Channel Natural)
activeSlotsByChannel :: Prelude.Maybe (Prelude.HashMap Channel Prelude.Natural),
    -- | A map of available slots by channel. The key is a channel name. The
    -- value is an integer: the available number of slots.
    UserData -> Maybe (HashMap Channel Natural)
availableSlotsByChannel :: Prelude.Maybe (Prelude.HashMap Channel Prelude.Natural),
    -- | A list of contact reference information.
    UserData -> Maybe [AgentContactReference]
contacts :: Prelude.Maybe [AgentContactReference],
    -- | Contains information about the levels of a hierarchy group assigned to a
    -- user.
    UserData -> Maybe HierarchyPathReference
hierarchyPath :: Prelude.Maybe HierarchyPathReference,
    -- | A map of maximum slots by channel. The key is a channel name. The value
    -- is an integer: the maximum number of slots. This is calculated from
    -- <https://docs.aws.amazon.com/connect/latest/APIReference/API_MediaConcurrency.html MediaConcurrency>
    -- of the @RoutingProfile@ assigned to the agent.
    UserData -> Maybe (HashMap Channel Natural)
maxSlotsByChannel :: Prelude.Maybe (Prelude.HashMap Channel Prelude.Natural),
    -- | The Next status of the agent.
    UserData -> Maybe Text
nextStatus :: Prelude.Maybe Prelude.Text,
    -- | Information about the routing profile that is assigned to the user.
    UserData -> Maybe RoutingProfileReference
routingProfile :: Prelude.Maybe RoutingProfileReference,
    -- | The status of the agent that they manually set in their Contact Control
    -- Panel (CCP), or that the supervisor manually changes in the real-time
    -- metrics report.
    UserData -> Maybe AgentStatusReference
status :: Prelude.Maybe AgentStatusReference,
    -- | Information about the user for the data that is returned. It contains
    -- the @resourceId@ and ARN of the user.
    UserData -> Maybe UserReference
user :: Prelude.Maybe UserReference
  }
  deriving (UserData -> UserData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserData -> UserData -> Bool
$c/= :: UserData -> UserData -> Bool
== :: UserData -> UserData -> Bool
$c== :: UserData -> UserData -> Bool
Prelude.Eq, ReadPrec [UserData]
ReadPrec UserData
Int -> ReadS UserData
ReadS [UserData]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UserData]
$creadListPrec :: ReadPrec [UserData]
readPrec :: ReadPrec UserData
$creadPrec :: ReadPrec UserData
readList :: ReadS [UserData]
$creadList :: ReadS [UserData]
readsPrec :: Int -> ReadS UserData
$creadsPrec :: Int -> ReadS UserData
Prelude.Read, Int -> UserData -> ShowS
[UserData] -> ShowS
UserData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserData] -> ShowS
$cshowList :: [UserData] -> ShowS
show :: UserData -> String
$cshow :: UserData -> String
showsPrec :: Int -> UserData -> ShowS
$cshowsPrec :: Int -> UserData -> ShowS
Prelude.Show, forall x. Rep UserData x -> UserData
forall x. UserData -> Rep UserData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserData x -> UserData
$cfrom :: forall x. UserData -> Rep UserData x
Prelude.Generic)

-- |
-- Create a value of 'UserData' 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:
--
-- 'activeSlotsByChannel', 'userData_activeSlotsByChannel' - A map of active slots by channel. The key is a channel name. The value
-- is an integer: the number of active slots.
--
-- 'availableSlotsByChannel', 'userData_availableSlotsByChannel' - A map of available slots by channel. The key is a channel name. The
-- value is an integer: the available number of slots.
--
-- 'contacts', 'userData_contacts' - A list of contact reference information.
--
-- 'hierarchyPath', 'userData_hierarchyPath' - Contains information about the levels of a hierarchy group assigned to a
-- user.
--
-- 'maxSlotsByChannel', 'userData_maxSlotsByChannel' - A map of maximum slots by channel. The key is a channel name. The value
-- is an integer: the maximum number of slots. This is calculated from
-- <https://docs.aws.amazon.com/connect/latest/APIReference/API_MediaConcurrency.html MediaConcurrency>
-- of the @RoutingProfile@ assigned to the agent.
--
-- 'nextStatus', 'userData_nextStatus' - The Next status of the agent.
--
-- 'routingProfile', 'userData_routingProfile' - Information about the routing profile that is assigned to the user.
--
-- 'status', 'userData_status' - The status of the agent that they manually set in their Contact Control
-- Panel (CCP), or that the supervisor manually changes in the real-time
-- metrics report.
--
-- 'user', 'userData_user' - Information about the user for the data that is returned. It contains
-- the @resourceId@ and ARN of the user.
newUserData ::
  UserData
newUserData :: UserData
newUserData =
  UserData'
    { $sel:activeSlotsByChannel:UserData' :: Maybe (HashMap Channel Natural)
activeSlotsByChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:availableSlotsByChannel:UserData' :: Maybe (HashMap Channel Natural)
availableSlotsByChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:contacts:UserData' :: Maybe [AgentContactReference]
contacts = forall a. Maybe a
Prelude.Nothing,
      $sel:hierarchyPath:UserData' :: Maybe HierarchyPathReference
hierarchyPath = forall a. Maybe a
Prelude.Nothing,
      $sel:maxSlotsByChannel:UserData' :: Maybe (HashMap Channel Natural)
maxSlotsByChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:nextStatus:UserData' :: Maybe Text
nextStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:routingProfile:UserData' :: Maybe RoutingProfileReference
routingProfile = forall a. Maybe a
Prelude.Nothing,
      $sel:status:UserData' :: Maybe AgentStatusReference
status = forall a. Maybe a
Prelude.Nothing,
      $sel:user:UserData' :: Maybe UserReference
user = forall a. Maybe a
Prelude.Nothing
    }

-- | A map of active slots by channel. The key is a channel name. The value
-- is an integer: the number of active slots.
userData_activeSlotsByChannel :: Lens.Lens' UserData (Prelude.Maybe (Prelude.HashMap Channel Prelude.Natural))
userData_activeSlotsByChannel :: Lens' UserData (Maybe (HashMap Channel Natural))
userData_activeSlotsByChannel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UserData' {Maybe (HashMap Channel Natural)
activeSlotsByChannel :: Maybe (HashMap Channel Natural)
$sel:activeSlotsByChannel:UserData' :: UserData -> Maybe (HashMap Channel Natural)
activeSlotsByChannel} -> Maybe (HashMap Channel Natural)
activeSlotsByChannel) (\s :: UserData
s@UserData' {} Maybe (HashMap Channel Natural)
a -> UserData
s {$sel:activeSlotsByChannel:UserData' :: Maybe (HashMap Channel Natural)
activeSlotsByChannel = Maybe (HashMap Channel Natural)
a} :: UserData) 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

-- | A map of available slots by channel. The key is a channel name. The
-- value is an integer: the available number of slots.
userData_availableSlotsByChannel :: Lens.Lens' UserData (Prelude.Maybe (Prelude.HashMap Channel Prelude.Natural))
userData_availableSlotsByChannel :: Lens' UserData (Maybe (HashMap Channel Natural))
userData_availableSlotsByChannel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UserData' {Maybe (HashMap Channel Natural)
availableSlotsByChannel :: Maybe (HashMap Channel Natural)
$sel:availableSlotsByChannel:UserData' :: UserData -> Maybe (HashMap Channel Natural)
availableSlotsByChannel} -> Maybe (HashMap Channel Natural)
availableSlotsByChannel) (\s :: UserData
s@UserData' {} Maybe (HashMap Channel Natural)
a -> UserData
s {$sel:availableSlotsByChannel:UserData' :: Maybe (HashMap Channel Natural)
availableSlotsByChannel = Maybe (HashMap Channel Natural)
a} :: UserData) 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

-- | A list of contact reference information.
userData_contacts :: Lens.Lens' UserData (Prelude.Maybe [AgentContactReference])
userData_contacts :: Lens' UserData (Maybe [AgentContactReference])
userData_contacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UserData' {Maybe [AgentContactReference]
contacts :: Maybe [AgentContactReference]
$sel:contacts:UserData' :: UserData -> Maybe [AgentContactReference]
contacts} -> Maybe [AgentContactReference]
contacts) (\s :: UserData
s@UserData' {} Maybe [AgentContactReference]
a -> UserData
s {$sel:contacts:UserData' :: Maybe [AgentContactReference]
contacts = Maybe [AgentContactReference]
a} :: UserData) 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

-- | Contains information about the levels of a hierarchy group assigned to a
-- user.
userData_hierarchyPath :: Lens.Lens' UserData (Prelude.Maybe HierarchyPathReference)
userData_hierarchyPath :: Lens' UserData (Maybe HierarchyPathReference)
userData_hierarchyPath = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UserData' {Maybe HierarchyPathReference
hierarchyPath :: Maybe HierarchyPathReference
$sel:hierarchyPath:UserData' :: UserData -> Maybe HierarchyPathReference
hierarchyPath} -> Maybe HierarchyPathReference
hierarchyPath) (\s :: UserData
s@UserData' {} Maybe HierarchyPathReference
a -> UserData
s {$sel:hierarchyPath:UserData' :: Maybe HierarchyPathReference
hierarchyPath = Maybe HierarchyPathReference
a} :: UserData)

-- | A map of maximum slots by channel. The key is a channel name. The value
-- is an integer: the maximum number of slots. This is calculated from
-- <https://docs.aws.amazon.com/connect/latest/APIReference/API_MediaConcurrency.html MediaConcurrency>
-- of the @RoutingProfile@ assigned to the agent.
userData_maxSlotsByChannel :: Lens.Lens' UserData (Prelude.Maybe (Prelude.HashMap Channel Prelude.Natural))
userData_maxSlotsByChannel :: Lens' UserData (Maybe (HashMap Channel Natural))
userData_maxSlotsByChannel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UserData' {Maybe (HashMap Channel Natural)
maxSlotsByChannel :: Maybe (HashMap Channel Natural)
$sel:maxSlotsByChannel:UserData' :: UserData -> Maybe (HashMap Channel Natural)
maxSlotsByChannel} -> Maybe (HashMap Channel Natural)
maxSlotsByChannel) (\s :: UserData
s@UserData' {} Maybe (HashMap Channel Natural)
a -> UserData
s {$sel:maxSlotsByChannel:UserData' :: Maybe (HashMap Channel Natural)
maxSlotsByChannel = Maybe (HashMap Channel Natural)
a} :: UserData) 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 Next status of the agent.
userData_nextStatus :: Lens.Lens' UserData (Prelude.Maybe Prelude.Text)
userData_nextStatus :: Lens' UserData (Maybe Text)
userData_nextStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UserData' {Maybe Text
nextStatus :: Maybe Text
$sel:nextStatus:UserData' :: UserData -> Maybe Text
nextStatus} -> Maybe Text
nextStatus) (\s :: UserData
s@UserData' {} Maybe Text
a -> UserData
s {$sel:nextStatus:UserData' :: Maybe Text
nextStatus = Maybe Text
a} :: UserData)

-- | Information about the routing profile that is assigned to the user.
userData_routingProfile :: Lens.Lens' UserData (Prelude.Maybe RoutingProfileReference)
userData_routingProfile :: Lens' UserData (Maybe RoutingProfileReference)
userData_routingProfile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UserData' {Maybe RoutingProfileReference
routingProfile :: Maybe RoutingProfileReference
$sel:routingProfile:UserData' :: UserData -> Maybe RoutingProfileReference
routingProfile} -> Maybe RoutingProfileReference
routingProfile) (\s :: UserData
s@UserData' {} Maybe RoutingProfileReference
a -> UserData
s {$sel:routingProfile:UserData' :: Maybe RoutingProfileReference
routingProfile = Maybe RoutingProfileReference
a} :: UserData)

-- | The status of the agent that they manually set in their Contact Control
-- Panel (CCP), or that the supervisor manually changes in the real-time
-- metrics report.
userData_status :: Lens.Lens' UserData (Prelude.Maybe AgentStatusReference)
userData_status :: Lens' UserData (Maybe AgentStatusReference)
userData_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UserData' {Maybe AgentStatusReference
status :: Maybe AgentStatusReference
$sel:status:UserData' :: UserData -> Maybe AgentStatusReference
status} -> Maybe AgentStatusReference
status) (\s :: UserData
s@UserData' {} Maybe AgentStatusReference
a -> UserData
s {$sel:status:UserData' :: Maybe AgentStatusReference
status = Maybe AgentStatusReference
a} :: UserData)

-- | Information about the user for the data that is returned. It contains
-- the @resourceId@ and ARN of the user.
userData_user :: Lens.Lens' UserData (Prelude.Maybe UserReference)
userData_user :: Lens' UserData (Maybe UserReference)
userData_user = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UserData' {Maybe UserReference
user :: Maybe UserReference
$sel:user:UserData' :: UserData -> Maybe UserReference
user} -> Maybe UserReference
user) (\s :: UserData
s@UserData' {} Maybe UserReference
a -> UserData
s {$sel:user:UserData' :: Maybe UserReference
user = Maybe UserReference
a} :: UserData)

instance Data.FromJSON UserData where
  parseJSON :: Value -> Parser UserData
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"UserData"
      ( \Object
x ->
          Maybe (HashMap Channel Natural)
-> Maybe (HashMap Channel Natural)
-> Maybe [AgentContactReference]
-> Maybe HierarchyPathReference
-> Maybe (HashMap Channel Natural)
-> Maybe Text
-> Maybe RoutingProfileReference
-> Maybe AgentStatusReference
-> Maybe UserReference
-> UserData
UserData'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ActiveSlotsByChannel"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AvailableSlotsByChannel"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Contacts" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"HierarchyPath")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MaxSlotsByChannel"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"NextStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RoutingProfile")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"User")
      )

instance Prelude.Hashable UserData where
  hashWithSalt :: Int -> UserData -> Int
hashWithSalt Int
_salt UserData' {Maybe [AgentContactReference]
Maybe Text
Maybe (HashMap Channel Natural)
Maybe AgentStatusReference
Maybe HierarchyPathReference
Maybe RoutingProfileReference
Maybe UserReference
user :: Maybe UserReference
status :: Maybe AgentStatusReference
routingProfile :: Maybe RoutingProfileReference
nextStatus :: Maybe Text
maxSlotsByChannel :: Maybe (HashMap Channel Natural)
hierarchyPath :: Maybe HierarchyPathReference
contacts :: Maybe [AgentContactReference]
availableSlotsByChannel :: Maybe (HashMap Channel Natural)
activeSlotsByChannel :: Maybe (HashMap Channel Natural)
$sel:user:UserData' :: UserData -> Maybe UserReference
$sel:status:UserData' :: UserData -> Maybe AgentStatusReference
$sel:routingProfile:UserData' :: UserData -> Maybe RoutingProfileReference
$sel:nextStatus:UserData' :: UserData -> Maybe Text
$sel:maxSlotsByChannel:UserData' :: UserData -> Maybe (HashMap Channel Natural)
$sel:hierarchyPath:UserData' :: UserData -> Maybe HierarchyPathReference
$sel:contacts:UserData' :: UserData -> Maybe [AgentContactReference]
$sel:availableSlotsByChannel:UserData' :: UserData -> Maybe (HashMap Channel Natural)
$sel:activeSlotsByChannel:UserData' :: UserData -> Maybe (HashMap Channel Natural)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Channel Natural)
activeSlotsByChannel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Channel Natural)
availableSlotsByChannel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AgentContactReference]
contacts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HierarchyPathReference
hierarchyPath
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Channel Natural)
maxSlotsByChannel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RoutingProfileReference
routingProfile
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AgentStatusReference
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserReference
user

instance Prelude.NFData UserData where
  rnf :: UserData -> ()
rnf UserData' {Maybe [AgentContactReference]
Maybe Text
Maybe (HashMap Channel Natural)
Maybe AgentStatusReference
Maybe HierarchyPathReference
Maybe RoutingProfileReference
Maybe UserReference
user :: Maybe UserReference
status :: Maybe AgentStatusReference
routingProfile :: Maybe RoutingProfileReference
nextStatus :: Maybe Text
maxSlotsByChannel :: Maybe (HashMap Channel Natural)
hierarchyPath :: Maybe HierarchyPathReference
contacts :: Maybe [AgentContactReference]
availableSlotsByChannel :: Maybe (HashMap Channel Natural)
activeSlotsByChannel :: Maybe (HashMap Channel Natural)
$sel:user:UserData' :: UserData -> Maybe UserReference
$sel:status:UserData' :: UserData -> Maybe AgentStatusReference
$sel:routingProfile:UserData' :: UserData -> Maybe RoutingProfileReference
$sel:nextStatus:UserData' :: UserData -> Maybe Text
$sel:maxSlotsByChannel:UserData' :: UserData -> Maybe (HashMap Channel Natural)
$sel:hierarchyPath:UserData' :: UserData -> Maybe HierarchyPathReference
$sel:contacts:UserData' :: UserData -> Maybe [AgentContactReference]
$sel:availableSlotsByChannel:UserData' :: UserData -> Maybe (HashMap Channel Natural)
$sel:activeSlotsByChannel:UserData' :: UserData -> Maybe (HashMap Channel Natural)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Channel Natural)
activeSlotsByChannel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Channel Natural)
availableSlotsByChannel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AgentContactReference]
contacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HierarchyPathReference
hierarchyPath
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Channel Natural)
maxSlotsByChannel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RoutingProfileReference
routingProfile
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AgentStatusReference
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserReference
user