{-# 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.FinSpaceData.Types.PermissionGroup
-- 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.FinSpaceData.Types.PermissionGroup where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.FinSpaceData.Types.ApplicationPermission
import Amazonka.FinSpaceData.Types.PermissionGroupMembershipStatus
import qualified Amazonka.Prelude as Prelude

-- | The structure for a permission group.
--
-- /See:/ 'newPermissionGroup' smart constructor.
data PermissionGroup = PermissionGroup'
  { -- | Indicates the permissions that are granted to a specific group for
    -- accessing the FinSpace application.
    --
    -- When assigning application permissions, be aware that the permission
    -- @ManageUsersAndGroups@ allows users to grant themselves or others access
    -- to any functionality in their FinSpace environment\'s application. It
    -- should only be granted to trusted users.
    --
    -- -   @CreateDataset@ – Group members can create new datasets.
    --
    -- -   @ManageClusters@ – Group members can manage Apache Spark clusters
    --     from FinSpace notebooks.
    --
    -- -   @ManageUsersAndGroups@ – Group members can manage users and
    --     permission groups. This is a privileged permission that allows users
    --     to grant themselves or others access to any functionality in the
    --     application. It should only be granted to trusted users.
    --
    -- -   @ManageAttributeSets@ – Group members can manage attribute sets.
    --
    -- -   @ViewAuditData@ – Group members can view audit data.
    --
    -- -   @AccessNotebooks@ – Group members will have access to FinSpace
    --     notebooks.
    --
    -- -   @GetTemporaryCredentials@ – Group members can get temporary API
    --     credentials.
    PermissionGroup -> Maybe [ApplicationPermission]
applicationPermissions :: Prelude.Maybe [ApplicationPermission],
    -- | The timestamp at which the group was created in FinSpace. The value is
    -- determined as epoch time in milliseconds.
    PermissionGroup -> Maybe Integer
createTime :: Prelude.Maybe Prelude.Integer,
    -- | A brief description for the permission group.
    PermissionGroup -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | Describes the last time the permission group was updated. The value is
    -- determined as epoch time in milliseconds.
    PermissionGroup -> Maybe Integer
lastModifiedTime :: Prelude.Maybe Prelude.Integer,
    -- | Indicates the status of the user account within a permission group.
    --
    -- -   @ADDITION_IN_PROGRESS@ – The user account is currently being added
    --     to the permission group.
    --
    -- -   @ADDITION_SUCCESS@ – The user account is successfully added to the
    --     permission group.
    --
    -- -   @REMOVAL_IN_PROGRESS@ – The user is currently being removed from the
    --     permission group.
    PermissionGroup -> Maybe PermissionGroupMembershipStatus
membershipStatus :: Prelude.Maybe PermissionGroupMembershipStatus,
    -- | The name of the permission group.
    PermissionGroup -> Maybe (Sensitive Text)
name :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The unique identifier for the permission group.
    PermissionGroup -> Maybe Text
permissionGroupId :: Prelude.Maybe Prelude.Text
  }
  deriving (PermissionGroup -> PermissionGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PermissionGroup -> PermissionGroup -> Bool
$c/= :: PermissionGroup -> PermissionGroup -> Bool
== :: PermissionGroup -> PermissionGroup -> Bool
$c== :: PermissionGroup -> PermissionGroup -> Bool
Prelude.Eq, Int -> PermissionGroup -> ShowS
[PermissionGroup] -> ShowS
PermissionGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PermissionGroup] -> ShowS
$cshowList :: [PermissionGroup] -> ShowS
show :: PermissionGroup -> String
$cshow :: PermissionGroup -> String
showsPrec :: Int -> PermissionGroup -> ShowS
$cshowsPrec :: Int -> PermissionGroup -> ShowS
Prelude.Show, forall x. Rep PermissionGroup x -> PermissionGroup
forall x. PermissionGroup -> Rep PermissionGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PermissionGroup x -> PermissionGroup
$cfrom :: forall x. PermissionGroup -> Rep PermissionGroup x
Prelude.Generic)

-- |
-- Create a value of 'PermissionGroup' 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:
--
-- 'applicationPermissions', 'permissionGroup_applicationPermissions' - Indicates the permissions that are granted to a specific group for
-- accessing the FinSpace application.
--
-- When assigning application permissions, be aware that the permission
-- @ManageUsersAndGroups@ allows users to grant themselves or others access
-- to any functionality in their FinSpace environment\'s application. It
-- should only be granted to trusted users.
--
-- -   @CreateDataset@ – Group members can create new datasets.
--
-- -   @ManageClusters@ – Group members can manage Apache Spark clusters
--     from FinSpace notebooks.
--
-- -   @ManageUsersAndGroups@ – Group members can manage users and
--     permission groups. This is a privileged permission that allows users
--     to grant themselves or others access to any functionality in the
--     application. It should only be granted to trusted users.
--
-- -   @ManageAttributeSets@ – Group members can manage attribute sets.
--
-- -   @ViewAuditData@ – Group members can view audit data.
--
-- -   @AccessNotebooks@ – Group members will have access to FinSpace
--     notebooks.
--
-- -   @GetTemporaryCredentials@ – Group members can get temporary API
--     credentials.
--
-- 'createTime', 'permissionGroup_createTime' - The timestamp at which the group was created in FinSpace. The value is
-- determined as epoch time in milliseconds.
--
-- 'description', 'permissionGroup_description' - A brief description for the permission group.
--
-- 'lastModifiedTime', 'permissionGroup_lastModifiedTime' - Describes the last time the permission group was updated. The value is
-- determined as epoch time in milliseconds.
--
-- 'membershipStatus', 'permissionGroup_membershipStatus' - Indicates the status of the user account within a permission group.
--
-- -   @ADDITION_IN_PROGRESS@ – The user account is currently being added
--     to the permission group.
--
-- -   @ADDITION_SUCCESS@ – The user account is successfully added to the
--     permission group.
--
-- -   @REMOVAL_IN_PROGRESS@ – The user is currently being removed from the
--     permission group.
--
-- 'name', 'permissionGroup_name' - The name of the permission group.
--
-- 'permissionGroupId', 'permissionGroup_permissionGroupId' - The unique identifier for the permission group.
newPermissionGroup ::
  PermissionGroup
newPermissionGroup :: PermissionGroup
newPermissionGroup =
  PermissionGroup'
    { $sel:applicationPermissions:PermissionGroup' :: Maybe [ApplicationPermission]
applicationPermissions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:createTime:PermissionGroup' :: Maybe Integer
createTime = forall a. Maybe a
Prelude.Nothing,
      $sel:description:PermissionGroup' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:PermissionGroup' :: Maybe Integer
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:membershipStatus:PermissionGroup' :: Maybe PermissionGroupMembershipStatus
membershipStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:name:PermissionGroup' :: Maybe (Sensitive Text)
name = forall a. Maybe a
Prelude.Nothing,
      $sel:permissionGroupId:PermissionGroup' :: Maybe Text
permissionGroupId = forall a. Maybe a
Prelude.Nothing
    }

-- | Indicates the permissions that are granted to a specific group for
-- accessing the FinSpace application.
--
-- When assigning application permissions, be aware that the permission
-- @ManageUsersAndGroups@ allows users to grant themselves or others access
-- to any functionality in their FinSpace environment\'s application. It
-- should only be granted to trusted users.
--
-- -   @CreateDataset@ – Group members can create new datasets.
--
-- -   @ManageClusters@ – Group members can manage Apache Spark clusters
--     from FinSpace notebooks.
--
-- -   @ManageUsersAndGroups@ – Group members can manage users and
--     permission groups. This is a privileged permission that allows users
--     to grant themselves or others access to any functionality in the
--     application. It should only be granted to trusted users.
--
-- -   @ManageAttributeSets@ – Group members can manage attribute sets.
--
-- -   @ViewAuditData@ – Group members can view audit data.
--
-- -   @AccessNotebooks@ – Group members will have access to FinSpace
--     notebooks.
--
-- -   @GetTemporaryCredentials@ – Group members can get temporary API
--     credentials.
permissionGroup_applicationPermissions :: Lens.Lens' PermissionGroup (Prelude.Maybe [ApplicationPermission])
permissionGroup_applicationPermissions :: Lens' PermissionGroup (Maybe [ApplicationPermission])
permissionGroup_applicationPermissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PermissionGroup' {Maybe [ApplicationPermission]
applicationPermissions :: Maybe [ApplicationPermission]
$sel:applicationPermissions:PermissionGroup' :: PermissionGroup -> Maybe [ApplicationPermission]
applicationPermissions} -> Maybe [ApplicationPermission]
applicationPermissions) (\s :: PermissionGroup
s@PermissionGroup' {} Maybe [ApplicationPermission]
a -> PermissionGroup
s {$sel:applicationPermissions:PermissionGroup' :: Maybe [ApplicationPermission]
applicationPermissions = Maybe [ApplicationPermission]
a} :: PermissionGroup) 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 timestamp at which the group was created in FinSpace. The value is
-- determined as epoch time in milliseconds.
permissionGroup_createTime :: Lens.Lens' PermissionGroup (Prelude.Maybe Prelude.Integer)
permissionGroup_createTime :: Lens' PermissionGroup (Maybe Integer)
permissionGroup_createTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PermissionGroup' {Maybe Integer
createTime :: Maybe Integer
$sel:createTime:PermissionGroup' :: PermissionGroup -> Maybe Integer
createTime} -> Maybe Integer
createTime) (\s :: PermissionGroup
s@PermissionGroup' {} Maybe Integer
a -> PermissionGroup
s {$sel:createTime:PermissionGroup' :: Maybe Integer
createTime = Maybe Integer
a} :: PermissionGroup)

-- | A brief description for the permission group.
permissionGroup_description :: Lens.Lens' PermissionGroup (Prelude.Maybe Prelude.Text)
permissionGroup_description :: Lens' PermissionGroup (Maybe Text)
permissionGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PermissionGroup' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:PermissionGroup' :: PermissionGroup -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: PermissionGroup
s@PermissionGroup' {} Maybe (Sensitive Text)
a -> PermissionGroup
s {$sel:description:PermissionGroup' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: PermissionGroup) 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | Describes the last time the permission group was updated. The value is
-- determined as epoch time in milliseconds.
permissionGroup_lastModifiedTime :: Lens.Lens' PermissionGroup (Prelude.Maybe Prelude.Integer)
permissionGroup_lastModifiedTime :: Lens' PermissionGroup (Maybe Integer)
permissionGroup_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PermissionGroup' {Maybe Integer
lastModifiedTime :: Maybe Integer
$sel:lastModifiedTime:PermissionGroup' :: PermissionGroup -> Maybe Integer
lastModifiedTime} -> Maybe Integer
lastModifiedTime) (\s :: PermissionGroup
s@PermissionGroup' {} Maybe Integer
a -> PermissionGroup
s {$sel:lastModifiedTime:PermissionGroup' :: Maybe Integer
lastModifiedTime = Maybe Integer
a} :: PermissionGroup)

-- | Indicates the status of the user account within a permission group.
--
-- -   @ADDITION_IN_PROGRESS@ – The user account is currently being added
--     to the permission group.
--
-- -   @ADDITION_SUCCESS@ – The user account is successfully added to the
--     permission group.
--
-- -   @REMOVAL_IN_PROGRESS@ – The user is currently being removed from the
--     permission group.
permissionGroup_membershipStatus :: Lens.Lens' PermissionGroup (Prelude.Maybe PermissionGroupMembershipStatus)
permissionGroup_membershipStatus :: Lens' PermissionGroup (Maybe PermissionGroupMembershipStatus)
permissionGroup_membershipStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PermissionGroup' {Maybe PermissionGroupMembershipStatus
membershipStatus :: Maybe PermissionGroupMembershipStatus
$sel:membershipStatus:PermissionGroup' :: PermissionGroup -> Maybe PermissionGroupMembershipStatus
membershipStatus} -> Maybe PermissionGroupMembershipStatus
membershipStatus) (\s :: PermissionGroup
s@PermissionGroup' {} Maybe PermissionGroupMembershipStatus
a -> PermissionGroup
s {$sel:membershipStatus:PermissionGroup' :: Maybe PermissionGroupMembershipStatus
membershipStatus = Maybe PermissionGroupMembershipStatus
a} :: PermissionGroup)

-- | The name of the permission group.
permissionGroup_name :: Lens.Lens' PermissionGroup (Prelude.Maybe Prelude.Text)
permissionGroup_name :: Lens' PermissionGroup (Maybe Text)
permissionGroup_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PermissionGroup' {Maybe (Sensitive Text)
name :: Maybe (Sensitive Text)
$sel:name:PermissionGroup' :: PermissionGroup -> Maybe (Sensitive Text)
name} -> Maybe (Sensitive Text)
name) (\s :: PermissionGroup
s@PermissionGroup' {} Maybe (Sensitive Text)
a -> PermissionGroup
s {$sel:name:PermissionGroup' :: Maybe (Sensitive Text)
name = Maybe (Sensitive Text)
a} :: PermissionGroup) 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The unique identifier for the permission group.
permissionGroup_permissionGroupId :: Lens.Lens' PermissionGroup (Prelude.Maybe Prelude.Text)
permissionGroup_permissionGroupId :: Lens' PermissionGroup (Maybe Text)
permissionGroup_permissionGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PermissionGroup' {Maybe Text
permissionGroupId :: Maybe Text
$sel:permissionGroupId:PermissionGroup' :: PermissionGroup -> Maybe Text
permissionGroupId} -> Maybe Text
permissionGroupId) (\s :: PermissionGroup
s@PermissionGroup' {} Maybe Text
a -> PermissionGroup
s {$sel:permissionGroupId:PermissionGroup' :: Maybe Text
permissionGroupId = Maybe Text
a} :: PermissionGroup)

instance Data.FromJSON PermissionGroup where
  parseJSON :: Value -> Parser PermissionGroup
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"PermissionGroup"
      ( \Object
x ->
          Maybe [ApplicationPermission]
-> Maybe Integer
-> Maybe (Sensitive Text)
-> Maybe Integer
-> Maybe PermissionGroupMembershipStatus
-> Maybe (Sensitive Text)
-> Maybe Text
-> PermissionGroup
PermissionGroup'
            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
"applicationPermissions"
                            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
"createTime")
            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
"description")
            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
"lastModifiedTime")
            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
"membershipStatus")
            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
"name")
            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
"permissionGroupId")
      )

instance Prelude.Hashable PermissionGroup where
  hashWithSalt :: Int -> PermissionGroup -> Int
hashWithSalt Int
_salt PermissionGroup' {Maybe Integer
Maybe [ApplicationPermission]
Maybe Text
Maybe (Sensitive Text)
Maybe PermissionGroupMembershipStatus
permissionGroupId :: Maybe Text
name :: Maybe (Sensitive Text)
membershipStatus :: Maybe PermissionGroupMembershipStatus
lastModifiedTime :: Maybe Integer
description :: Maybe (Sensitive Text)
createTime :: Maybe Integer
applicationPermissions :: Maybe [ApplicationPermission]
$sel:permissionGroupId:PermissionGroup' :: PermissionGroup -> Maybe Text
$sel:name:PermissionGroup' :: PermissionGroup -> Maybe (Sensitive Text)
$sel:membershipStatus:PermissionGroup' :: PermissionGroup -> Maybe PermissionGroupMembershipStatus
$sel:lastModifiedTime:PermissionGroup' :: PermissionGroup -> Maybe Integer
$sel:description:PermissionGroup' :: PermissionGroup -> Maybe (Sensitive Text)
$sel:createTime:PermissionGroup' :: PermissionGroup -> Maybe Integer
$sel:applicationPermissions:PermissionGroup' :: PermissionGroup -> Maybe [ApplicationPermission]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ApplicationPermission]
applicationPermissions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
createTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
lastModifiedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PermissionGroupMembershipStatus
membershipStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
permissionGroupId

instance Prelude.NFData PermissionGroup where
  rnf :: PermissionGroup -> ()
rnf PermissionGroup' {Maybe Integer
Maybe [ApplicationPermission]
Maybe Text
Maybe (Sensitive Text)
Maybe PermissionGroupMembershipStatus
permissionGroupId :: Maybe Text
name :: Maybe (Sensitive Text)
membershipStatus :: Maybe PermissionGroupMembershipStatus
lastModifiedTime :: Maybe Integer
description :: Maybe (Sensitive Text)
createTime :: Maybe Integer
applicationPermissions :: Maybe [ApplicationPermission]
$sel:permissionGroupId:PermissionGroup' :: PermissionGroup -> Maybe Text
$sel:name:PermissionGroup' :: PermissionGroup -> Maybe (Sensitive Text)
$sel:membershipStatus:PermissionGroup' :: PermissionGroup -> Maybe PermissionGroupMembershipStatus
$sel:lastModifiedTime:PermissionGroup' :: PermissionGroup -> Maybe Integer
$sel:description:PermissionGroup' :: PermissionGroup -> Maybe (Sensitive Text)
$sel:createTime:PermissionGroup' :: PermissionGroup -> Maybe Integer
$sel:applicationPermissions:PermissionGroup' :: PermissionGroup -> Maybe [ApplicationPermission]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ApplicationPermission]
applicationPermissions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
createTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PermissionGroupMembershipStatus
membershipStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
permissionGroupId