{-# 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.IAM.Types.PolicyGrantingServiceAccess
-- 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.IAM.Types.PolicyGrantingServiceAccess where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IAM.Types.PolicyOwnerEntityType
import Amazonka.IAM.Types.PolicyType
import qualified Amazonka.Prelude as Prelude

-- | Contains details about the permissions policies that are attached to the
-- specified identity (user, group, or role).
--
-- This data type is an element of the
-- ListPoliciesGrantingServiceAccessEntry object.
--
-- /See:/ 'newPolicyGrantingServiceAccess' smart constructor.
data PolicyGrantingServiceAccess = PolicyGrantingServiceAccess'
  { -- | The name of the entity (user or role) to which the inline policy is
    -- attached.
    --
    -- This field is null for managed policies. For more information about
    -- these policy types, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_managed-vs-inline.html Managed policies and inline policies>
    -- in the /IAM User Guide/.
    PolicyGrantingServiceAccess -> Maybe Text
entityName :: Prelude.Maybe Prelude.Text,
    -- | The type of entity (user or role) that used the policy to access the
    -- service to which the inline policy is attached.
    --
    -- This field is null for managed policies. For more information about
    -- these policy types, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_managed-vs-inline.html Managed policies and inline policies>
    -- in the /IAM User Guide/.
    PolicyGrantingServiceAccess -> Maybe PolicyOwnerEntityType
entityType :: Prelude.Maybe PolicyOwnerEntityType,
    PolicyGrantingServiceAccess -> Maybe Text
policyArn :: Prelude.Maybe Prelude.Text,
    -- | The policy name.
    PolicyGrantingServiceAccess -> Text
policyName :: Prelude.Text,
    -- | The policy type. For more information about these policy types, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_managed-vs-inline.html Managed policies and inline policies>
    -- in the /IAM User Guide/.
    PolicyGrantingServiceAccess -> PolicyType
policyType :: PolicyType
  }
  deriving (PolicyGrantingServiceAccess -> PolicyGrantingServiceAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PolicyGrantingServiceAccess -> PolicyGrantingServiceAccess -> Bool
$c/= :: PolicyGrantingServiceAccess -> PolicyGrantingServiceAccess -> Bool
== :: PolicyGrantingServiceAccess -> PolicyGrantingServiceAccess -> Bool
$c== :: PolicyGrantingServiceAccess -> PolicyGrantingServiceAccess -> Bool
Prelude.Eq, ReadPrec [PolicyGrantingServiceAccess]
ReadPrec PolicyGrantingServiceAccess
Int -> ReadS PolicyGrantingServiceAccess
ReadS [PolicyGrantingServiceAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PolicyGrantingServiceAccess]
$creadListPrec :: ReadPrec [PolicyGrantingServiceAccess]
readPrec :: ReadPrec PolicyGrantingServiceAccess
$creadPrec :: ReadPrec PolicyGrantingServiceAccess
readList :: ReadS [PolicyGrantingServiceAccess]
$creadList :: ReadS [PolicyGrantingServiceAccess]
readsPrec :: Int -> ReadS PolicyGrantingServiceAccess
$creadsPrec :: Int -> ReadS PolicyGrantingServiceAccess
Prelude.Read, Int -> PolicyGrantingServiceAccess -> ShowS
[PolicyGrantingServiceAccess] -> ShowS
PolicyGrantingServiceAccess -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PolicyGrantingServiceAccess] -> ShowS
$cshowList :: [PolicyGrantingServiceAccess] -> ShowS
show :: PolicyGrantingServiceAccess -> String
$cshow :: PolicyGrantingServiceAccess -> String
showsPrec :: Int -> PolicyGrantingServiceAccess -> ShowS
$cshowsPrec :: Int -> PolicyGrantingServiceAccess -> ShowS
Prelude.Show, forall x.
Rep PolicyGrantingServiceAccess x -> PolicyGrantingServiceAccess
forall x.
PolicyGrantingServiceAccess -> Rep PolicyGrantingServiceAccess x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PolicyGrantingServiceAccess x -> PolicyGrantingServiceAccess
$cfrom :: forall x.
PolicyGrantingServiceAccess -> Rep PolicyGrantingServiceAccess x
Prelude.Generic)

-- |
-- Create a value of 'PolicyGrantingServiceAccess' 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:
--
-- 'entityName', 'policyGrantingServiceAccess_entityName' - The name of the entity (user or role) to which the inline policy is
-- attached.
--
-- This field is null for managed policies. For more information about
-- these policy types, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
--
-- 'entityType', 'policyGrantingServiceAccess_entityType' - The type of entity (user or role) that used the policy to access the
-- service to which the inline policy is attached.
--
-- This field is null for managed policies. For more information about
-- these policy types, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
--
-- 'policyArn', 'policyGrantingServiceAccess_policyArn' - Undocumented member.
--
-- 'policyName', 'policyGrantingServiceAccess_policyName' - The policy name.
--
-- 'policyType', 'policyGrantingServiceAccess_policyType' - The policy type. For more information about these policy types, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
newPolicyGrantingServiceAccess ::
  -- | 'policyName'
  Prelude.Text ->
  -- | 'policyType'
  PolicyType ->
  PolicyGrantingServiceAccess
newPolicyGrantingServiceAccess :: Text -> PolicyType -> PolicyGrantingServiceAccess
newPolicyGrantingServiceAccess
  Text
pPolicyName_
  PolicyType
pPolicyType_ =
    PolicyGrantingServiceAccess'
      { $sel:entityName:PolicyGrantingServiceAccess' :: Maybe Text
entityName =
          forall a. Maybe a
Prelude.Nothing,
        $sel:entityType:PolicyGrantingServiceAccess' :: Maybe PolicyOwnerEntityType
entityType = forall a. Maybe a
Prelude.Nothing,
        $sel:policyArn:PolicyGrantingServiceAccess' :: Maybe Text
policyArn = forall a. Maybe a
Prelude.Nothing,
        $sel:policyName:PolicyGrantingServiceAccess' :: Text
policyName = Text
pPolicyName_,
        $sel:policyType:PolicyGrantingServiceAccess' :: PolicyType
policyType = PolicyType
pPolicyType_
      }

-- | The name of the entity (user or role) to which the inline policy is
-- attached.
--
-- This field is null for managed policies. For more information about
-- these policy types, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
policyGrantingServiceAccess_entityName :: Lens.Lens' PolicyGrantingServiceAccess (Prelude.Maybe Prelude.Text)
policyGrantingServiceAccess_entityName :: Lens' PolicyGrantingServiceAccess (Maybe Text)
policyGrantingServiceAccess_entityName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicyGrantingServiceAccess' {Maybe Text
entityName :: Maybe Text
$sel:entityName:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Maybe Text
entityName} -> Maybe Text
entityName) (\s :: PolicyGrantingServiceAccess
s@PolicyGrantingServiceAccess' {} Maybe Text
a -> PolicyGrantingServiceAccess
s {$sel:entityName:PolicyGrantingServiceAccess' :: Maybe Text
entityName = Maybe Text
a} :: PolicyGrantingServiceAccess)

-- | The type of entity (user or role) that used the policy to access the
-- service to which the inline policy is attached.
--
-- This field is null for managed policies. For more information about
-- these policy types, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
policyGrantingServiceAccess_entityType :: Lens.Lens' PolicyGrantingServiceAccess (Prelude.Maybe PolicyOwnerEntityType)
policyGrantingServiceAccess_entityType :: Lens' PolicyGrantingServiceAccess (Maybe PolicyOwnerEntityType)
policyGrantingServiceAccess_entityType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicyGrantingServiceAccess' {Maybe PolicyOwnerEntityType
entityType :: Maybe PolicyOwnerEntityType
$sel:entityType:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Maybe PolicyOwnerEntityType
entityType} -> Maybe PolicyOwnerEntityType
entityType) (\s :: PolicyGrantingServiceAccess
s@PolicyGrantingServiceAccess' {} Maybe PolicyOwnerEntityType
a -> PolicyGrantingServiceAccess
s {$sel:entityType:PolicyGrantingServiceAccess' :: Maybe PolicyOwnerEntityType
entityType = Maybe PolicyOwnerEntityType
a} :: PolicyGrantingServiceAccess)

-- | Undocumented member.
policyGrantingServiceAccess_policyArn :: Lens.Lens' PolicyGrantingServiceAccess (Prelude.Maybe Prelude.Text)
policyGrantingServiceAccess_policyArn :: Lens' PolicyGrantingServiceAccess (Maybe Text)
policyGrantingServiceAccess_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicyGrantingServiceAccess' {Maybe Text
policyArn :: Maybe Text
$sel:policyArn:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Maybe Text
policyArn} -> Maybe Text
policyArn) (\s :: PolicyGrantingServiceAccess
s@PolicyGrantingServiceAccess' {} Maybe Text
a -> PolicyGrantingServiceAccess
s {$sel:policyArn:PolicyGrantingServiceAccess' :: Maybe Text
policyArn = Maybe Text
a} :: PolicyGrantingServiceAccess)

-- | The policy name.
policyGrantingServiceAccess_policyName :: Lens.Lens' PolicyGrantingServiceAccess Prelude.Text
policyGrantingServiceAccess_policyName :: Lens' PolicyGrantingServiceAccess Text
policyGrantingServiceAccess_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicyGrantingServiceAccess' {Text
policyName :: Text
$sel:policyName:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Text
policyName} -> Text
policyName) (\s :: PolicyGrantingServiceAccess
s@PolicyGrantingServiceAccess' {} Text
a -> PolicyGrantingServiceAccess
s {$sel:policyName:PolicyGrantingServiceAccess' :: Text
policyName = Text
a} :: PolicyGrantingServiceAccess)

-- | The policy type. For more information about these policy types, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
policyGrantingServiceAccess_policyType :: Lens.Lens' PolicyGrantingServiceAccess PolicyType
policyGrantingServiceAccess_policyType :: Lens' PolicyGrantingServiceAccess PolicyType
policyGrantingServiceAccess_policyType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicyGrantingServiceAccess' {PolicyType
policyType :: PolicyType
$sel:policyType:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> PolicyType
policyType} -> PolicyType
policyType) (\s :: PolicyGrantingServiceAccess
s@PolicyGrantingServiceAccess' {} PolicyType
a -> PolicyGrantingServiceAccess
s {$sel:policyType:PolicyGrantingServiceAccess' :: PolicyType
policyType = PolicyType
a} :: PolicyGrantingServiceAccess)

instance Data.FromXML PolicyGrantingServiceAccess where
  parseXML :: [Node] -> Either String PolicyGrantingServiceAccess
parseXML [Node]
x =
    Maybe Text
-> Maybe PolicyOwnerEntityType
-> Maybe Text
-> Text
-> PolicyType
-> PolicyGrantingServiceAccess
PolicyGrantingServiceAccess'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"EntityName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"EntityType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PolicyArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"PolicyName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"PolicyType")

instance Prelude.Hashable PolicyGrantingServiceAccess where
  hashWithSalt :: Int -> PolicyGrantingServiceAccess -> Int
hashWithSalt Int
_salt PolicyGrantingServiceAccess' {Maybe Text
Maybe PolicyOwnerEntityType
Text
PolicyType
policyType :: PolicyType
policyName :: Text
policyArn :: Maybe Text
entityType :: Maybe PolicyOwnerEntityType
entityName :: Maybe Text
$sel:policyType:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> PolicyType
$sel:policyName:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Text
$sel:policyArn:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Maybe Text
$sel:entityType:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Maybe PolicyOwnerEntityType
$sel:entityName:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
entityName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PolicyOwnerEntityType
entityType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` PolicyType
policyType

instance Prelude.NFData PolicyGrantingServiceAccess where
  rnf :: PolicyGrantingServiceAccess -> ()
rnf PolicyGrantingServiceAccess' {Maybe Text
Maybe PolicyOwnerEntityType
Text
PolicyType
policyType :: PolicyType
policyName :: Text
policyArn :: Maybe Text
entityType :: Maybe PolicyOwnerEntityType
entityName :: Maybe Text
$sel:policyType:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> PolicyType
$sel:policyName:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Text
$sel:policyArn:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Maybe Text
$sel:entityType:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Maybe PolicyOwnerEntityType
$sel:entityName:PolicyGrantingServiceAccess' :: PolicyGrantingServiceAccess -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
entityName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PolicyOwnerEntityType
entityType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf PolicyType
policyType