{-# 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.Policy
-- 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.Policy 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.Tag
import qualified Amazonka.Prelude as Prelude

-- | Contains information about a managed policy.
--
-- This data type is used as a response element in the CreatePolicy,
-- GetPolicy, and ListPolicies operations.
--
-- For more information about managed policies, refer to
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
--
-- /See:/ 'newPolicy' smart constructor.
data Policy = Policy'
  { Policy -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The number of entities (users, groups, and roles) that the policy is
    -- attached to.
    Policy -> Maybe Int
attachmentCount :: Prelude.Maybe Prelude.Int,
    -- | The date and time, in
    -- <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
    -- policy was created.
    Policy -> Maybe ISO8601
createDate :: Prelude.Maybe Data.ISO8601,
    -- | The identifier for the version of the policy that is set as the default
    -- version.
    Policy -> Maybe Text
defaultVersionId :: Prelude.Maybe Prelude.Text,
    -- | A friendly description of the policy.
    --
    -- This element is included in the response to the GetPolicy operation. It
    -- is not included in the response to the ListPolicies operation.
    Policy -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether the policy can be attached to an IAM user, group, or
    -- role.
    Policy -> Maybe Bool
isAttachable :: Prelude.Maybe Prelude.Bool,
    -- | The path to the policy.
    --
    -- For more information about paths, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_Identifiers.html IAM identifiers>
    -- in the /IAM User Guide/.
    Policy -> Maybe Text
path :: Prelude.Maybe Prelude.Text,
    -- | The number of entities (users and roles) for which the policy is used to
    -- set the permissions boundary.
    --
    -- For more information about permissions boundaries, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_boundaries.html Permissions boundaries for IAM identities>
    -- in the /IAM User Guide/.
    Policy -> Maybe Int
permissionsBoundaryUsageCount :: Prelude.Maybe Prelude.Int,
    -- | The stable and unique string identifying the policy.
    --
    -- For more information about IDs, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_Identifiers.html IAM identifiers>
    -- in the /IAM User Guide/.
    Policy -> Maybe Text
policyId :: Prelude.Maybe Prelude.Text,
    -- | The friendly name (not ARN) identifying the policy.
    Policy -> Maybe Text
policyName :: Prelude.Maybe Prelude.Text,
    -- | A list of tags that are attached to the instance profile. For more
    -- information about tagging, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_tags.html Tagging IAM resources>
    -- in the /IAM User Guide/.
    Policy -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The date and time, in
    -- <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
    -- policy was last updated.
    --
    -- When a policy has only one version, this field contains the date and
    -- time when the policy was created. When a policy has more than one
    -- version, this field contains the date and time when the most recent
    -- policy version was created.
    Policy -> Maybe ISO8601
updateDate :: Prelude.Maybe Data.ISO8601
  }
  deriving (Policy -> Policy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Policy -> Policy -> Bool
$c/= :: Policy -> Policy -> Bool
== :: Policy -> Policy -> Bool
$c== :: Policy -> Policy -> Bool
Prelude.Eq, ReadPrec [Policy]
ReadPrec Policy
Int -> ReadS Policy
ReadS [Policy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Policy]
$creadListPrec :: ReadPrec [Policy]
readPrec :: ReadPrec Policy
$creadPrec :: ReadPrec Policy
readList :: ReadS [Policy]
$creadList :: ReadS [Policy]
readsPrec :: Int -> ReadS Policy
$creadsPrec :: Int -> ReadS Policy
Prelude.Read, Int -> Policy -> ShowS
[Policy] -> ShowS
Policy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Policy] -> ShowS
$cshowList :: [Policy] -> ShowS
show :: Policy -> String
$cshow :: Policy -> String
showsPrec :: Int -> Policy -> ShowS
$cshowsPrec :: Int -> Policy -> ShowS
Prelude.Show, forall x. Rep Policy x -> Policy
forall x. Policy -> Rep Policy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Policy x -> Policy
$cfrom :: forall x. Policy -> Rep Policy x
Prelude.Generic)

-- |
-- Create a value of 'Policy' 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:
--
-- 'arn', 'policy_arn' - Undocumented member.
--
-- 'attachmentCount', 'policy_attachmentCount' - The number of entities (users, groups, and roles) that the policy is
-- attached to.
--
-- 'createDate', 'policy_createDate' - The date and time, in
-- <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
-- policy was created.
--
-- 'defaultVersionId', 'policy_defaultVersionId' - The identifier for the version of the policy that is set as the default
-- version.
--
-- 'description', 'policy_description' - A friendly description of the policy.
--
-- This element is included in the response to the GetPolicy operation. It
-- is not included in the response to the ListPolicies operation.
--
-- 'isAttachable', 'policy_isAttachable' - Specifies whether the policy can be attached to an IAM user, group, or
-- role.
--
-- 'path', 'policy_path' - The path to the policy.
--
-- For more information about paths, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_Identifiers.html IAM identifiers>
-- in the /IAM User Guide/.
--
-- 'permissionsBoundaryUsageCount', 'policy_permissionsBoundaryUsageCount' - The number of entities (users and roles) for which the policy is used to
-- set the permissions boundary.
--
-- For more information about permissions boundaries, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_boundaries.html Permissions boundaries for IAM identities>
-- in the /IAM User Guide/.
--
-- 'policyId', 'policy_policyId' - The stable and unique string identifying the policy.
--
-- For more information about IDs, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_Identifiers.html IAM identifiers>
-- in the /IAM User Guide/.
--
-- 'policyName', 'policy_policyName' - The friendly name (not ARN) identifying the policy.
--
-- 'tags', 'policy_tags' - A list of tags that are attached to the instance profile. For more
-- information about tagging, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_tags.html Tagging IAM resources>
-- in the /IAM User Guide/.
--
-- 'updateDate', 'policy_updateDate' - The date and time, in
-- <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
-- policy was last updated.
--
-- When a policy has only one version, this field contains the date and
-- time when the policy was created. When a policy has more than one
-- version, this field contains the date and time when the most recent
-- policy version was created.
newPolicy ::
  Policy
newPolicy :: Policy
newPolicy =
  Policy'
    { $sel:arn:Policy' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:attachmentCount:Policy' :: Maybe Int
attachmentCount = forall a. Maybe a
Prelude.Nothing,
      $sel:createDate:Policy' :: Maybe ISO8601
createDate = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultVersionId:Policy' :: Maybe Text
defaultVersionId = forall a. Maybe a
Prelude.Nothing,
      $sel:description:Policy' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:isAttachable:Policy' :: Maybe Bool
isAttachable = forall a. Maybe a
Prelude.Nothing,
      $sel:path:Policy' :: Maybe Text
path = forall a. Maybe a
Prelude.Nothing,
      $sel:permissionsBoundaryUsageCount:Policy' :: Maybe Int
permissionsBoundaryUsageCount = forall a. Maybe a
Prelude.Nothing,
      $sel:policyId:Policy' :: Maybe Text
policyId = forall a. Maybe a
Prelude.Nothing,
      $sel:policyName:Policy' :: Maybe Text
policyName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:Policy' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:updateDate:Policy' :: Maybe ISO8601
updateDate = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The number of entities (users, groups, and roles) that the policy is
-- attached to.
policy_attachmentCount :: Lens.Lens' Policy (Prelude.Maybe Prelude.Int)
policy_attachmentCount :: Lens' Policy (Maybe Int)
policy_attachmentCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe Int
attachmentCount :: Maybe Int
$sel:attachmentCount:Policy' :: Policy -> Maybe Int
attachmentCount} -> Maybe Int
attachmentCount) (\s :: Policy
s@Policy' {} Maybe Int
a -> Policy
s {$sel:attachmentCount:Policy' :: Maybe Int
attachmentCount = Maybe Int
a} :: Policy)

-- | The date and time, in
-- <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
-- policy was created.
policy_createDate :: Lens.Lens' Policy (Prelude.Maybe Prelude.UTCTime)
policy_createDate :: Lens' Policy (Maybe UTCTime)
policy_createDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe ISO8601
createDate :: Maybe ISO8601
$sel:createDate:Policy' :: Policy -> Maybe ISO8601
createDate} -> Maybe ISO8601
createDate) (\s :: Policy
s@Policy' {} Maybe ISO8601
a -> Policy
s {$sel:createDate:Policy' :: Maybe ISO8601
createDate = Maybe ISO8601
a} :: Policy) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The identifier for the version of the policy that is set as the default
-- version.
policy_defaultVersionId :: Lens.Lens' Policy (Prelude.Maybe Prelude.Text)
policy_defaultVersionId :: Lens' Policy (Maybe Text)
policy_defaultVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe Text
defaultVersionId :: Maybe Text
$sel:defaultVersionId:Policy' :: Policy -> Maybe Text
defaultVersionId} -> Maybe Text
defaultVersionId) (\s :: Policy
s@Policy' {} Maybe Text
a -> Policy
s {$sel:defaultVersionId:Policy' :: Maybe Text
defaultVersionId = Maybe Text
a} :: Policy)

-- | A friendly description of the policy.
--
-- This element is included in the response to the GetPolicy operation. It
-- is not included in the response to the ListPolicies operation.
policy_description :: Lens.Lens' Policy (Prelude.Maybe Prelude.Text)
policy_description :: Lens' Policy (Maybe Text)
policy_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe Text
description :: Maybe Text
$sel:description:Policy' :: Policy -> Maybe Text
description} -> Maybe Text
description) (\s :: Policy
s@Policy' {} Maybe Text
a -> Policy
s {$sel:description:Policy' :: Maybe Text
description = Maybe Text
a} :: Policy)

-- | Specifies whether the policy can be attached to an IAM user, group, or
-- role.
policy_isAttachable :: Lens.Lens' Policy (Prelude.Maybe Prelude.Bool)
policy_isAttachable :: Lens' Policy (Maybe Bool)
policy_isAttachable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe Bool
isAttachable :: Maybe Bool
$sel:isAttachable:Policy' :: Policy -> Maybe Bool
isAttachable} -> Maybe Bool
isAttachable) (\s :: Policy
s@Policy' {} Maybe Bool
a -> Policy
s {$sel:isAttachable:Policy' :: Maybe Bool
isAttachable = Maybe Bool
a} :: Policy)

-- | The path to the policy.
--
-- For more information about paths, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_Identifiers.html IAM identifiers>
-- in the /IAM User Guide/.
policy_path :: Lens.Lens' Policy (Prelude.Maybe Prelude.Text)
policy_path :: Lens' Policy (Maybe Text)
policy_path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe Text
path :: Maybe Text
$sel:path:Policy' :: Policy -> Maybe Text
path} -> Maybe Text
path) (\s :: Policy
s@Policy' {} Maybe Text
a -> Policy
s {$sel:path:Policy' :: Maybe Text
path = Maybe Text
a} :: Policy)

-- | The number of entities (users and roles) for which the policy is used to
-- set the permissions boundary.
--
-- For more information about permissions boundaries, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_boundaries.html Permissions boundaries for IAM identities>
-- in the /IAM User Guide/.
policy_permissionsBoundaryUsageCount :: Lens.Lens' Policy (Prelude.Maybe Prelude.Int)
policy_permissionsBoundaryUsageCount :: Lens' Policy (Maybe Int)
policy_permissionsBoundaryUsageCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe Int
permissionsBoundaryUsageCount :: Maybe Int
$sel:permissionsBoundaryUsageCount:Policy' :: Policy -> Maybe Int
permissionsBoundaryUsageCount} -> Maybe Int
permissionsBoundaryUsageCount) (\s :: Policy
s@Policy' {} Maybe Int
a -> Policy
s {$sel:permissionsBoundaryUsageCount:Policy' :: Maybe Int
permissionsBoundaryUsageCount = Maybe Int
a} :: Policy)

-- | The stable and unique string identifying the policy.
--
-- For more information about IDs, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_Identifiers.html IAM identifiers>
-- in the /IAM User Guide/.
policy_policyId :: Lens.Lens' Policy (Prelude.Maybe Prelude.Text)
policy_policyId :: Lens' Policy (Maybe Text)
policy_policyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe Text
policyId :: Maybe Text
$sel:policyId:Policy' :: Policy -> Maybe Text
policyId} -> Maybe Text
policyId) (\s :: Policy
s@Policy' {} Maybe Text
a -> Policy
s {$sel:policyId:Policy' :: Maybe Text
policyId = Maybe Text
a} :: Policy)

-- | The friendly name (not ARN) identifying the policy.
policy_policyName :: Lens.Lens' Policy (Prelude.Maybe Prelude.Text)
policy_policyName :: Lens' Policy (Maybe Text)
policy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe Text
policyName :: Maybe Text
$sel:policyName:Policy' :: Policy -> Maybe Text
policyName} -> Maybe Text
policyName) (\s :: Policy
s@Policy' {} Maybe Text
a -> Policy
s {$sel:policyName:Policy' :: Maybe Text
policyName = Maybe Text
a} :: Policy)

-- | A list of tags that are attached to the instance profile. For more
-- information about tagging, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_tags.html Tagging IAM resources>
-- in the /IAM User Guide/.
policy_tags :: Lens.Lens' Policy (Prelude.Maybe [Tag])
policy_tags :: Lens' Policy (Maybe [Tag])
policy_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:Policy' :: Policy -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: Policy
s@Policy' {} Maybe [Tag]
a -> Policy
s {$sel:tags:Policy' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: Policy) 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 date and time, in
-- <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
-- policy was last updated.
--
-- When a policy has only one version, this field contains the date and
-- time when the policy was created. When a policy has more than one
-- version, this field contains the date and time when the most recent
-- policy version was created.
policy_updateDate :: Lens.Lens' Policy (Prelude.Maybe Prelude.UTCTime)
policy_updateDate :: Lens' Policy (Maybe UTCTime)
policy_updateDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Policy' {Maybe ISO8601
updateDate :: Maybe ISO8601
$sel:updateDate:Policy' :: Policy -> Maybe ISO8601
updateDate} -> Maybe ISO8601
updateDate) (\s :: Policy
s@Policy' {} Maybe ISO8601
a -> Policy
s {$sel:updateDate:Policy' :: Maybe ISO8601
updateDate = Maybe ISO8601
a} :: Policy) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromXML Policy where
  parseXML :: [Node] -> Either String Policy
parseXML [Node]
x =
    Maybe Text
-> Maybe Int
-> Maybe ISO8601
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe [Tag]
-> Maybe ISO8601
-> Policy
Policy'
      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
"Arn")
      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
"AttachmentCount")
      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
"CreateDate")
      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
"DefaultVersionId")
      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
"Description")
      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
"IsAttachable")
      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
"Path")
      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
"PermissionsBoundaryUsageCount")
      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
"PolicyId")
      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
"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 (Maybe a)
Data..@? Text
"Tags"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      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
"UpdateDate")

instance Prelude.Hashable Policy where
  hashWithSalt :: Int -> Policy -> Int
hashWithSalt Int
_salt Policy' {Maybe Bool
Maybe Int
Maybe [Tag]
Maybe Text
Maybe ISO8601
updateDate :: Maybe ISO8601
tags :: Maybe [Tag]
policyName :: Maybe Text
policyId :: Maybe Text
permissionsBoundaryUsageCount :: Maybe Int
path :: Maybe Text
isAttachable :: Maybe Bool
description :: Maybe Text
defaultVersionId :: Maybe Text
createDate :: Maybe ISO8601
attachmentCount :: Maybe Int
arn :: Maybe Text
$sel:updateDate:Policy' :: Policy -> Maybe ISO8601
$sel:tags:Policy' :: Policy -> Maybe [Tag]
$sel:policyName:Policy' :: Policy -> Maybe Text
$sel:policyId:Policy' :: Policy -> Maybe Text
$sel:permissionsBoundaryUsageCount:Policy' :: Policy -> Maybe Int
$sel:path:Policy' :: Policy -> Maybe Text
$sel:isAttachable:Policy' :: Policy -> Maybe Bool
$sel:description:Policy' :: Policy -> Maybe Text
$sel:defaultVersionId:Policy' :: Policy -> Maybe Text
$sel:createDate:Policy' :: Policy -> Maybe ISO8601
$sel:attachmentCount:Policy' :: Policy -> Maybe Int
$sel:arn:Policy' :: Policy -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
attachmentCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
createDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
defaultVersionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
isAttachable
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
path
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
permissionsBoundaryUsageCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
updateDate

instance Prelude.NFData Policy where
  rnf :: Policy -> ()
rnf Policy' {Maybe Bool
Maybe Int
Maybe [Tag]
Maybe Text
Maybe ISO8601
updateDate :: Maybe ISO8601
tags :: Maybe [Tag]
policyName :: Maybe Text
policyId :: Maybe Text
permissionsBoundaryUsageCount :: Maybe Int
path :: Maybe Text
isAttachable :: Maybe Bool
description :: Maybe Text
defaultVersionId :: Maybe Text
createDate :: Maybe ISO8601
attachmentCount :: Maybe Int
arn :: Maybe Text
$sel:updateDate:Policy' :: Policy -> Maybe ISO8601
$sel:tags:Policy' :: Policy -> Maybe [Tag]
$sel:policyName:Policy' :: Policy -> Maybe Text
$sel:policyId:Policy' :: Policy -> Maybe Text
$sel:permissionsBoundaryUsageCount:Policy' :: Policy -> Maybe Int
$sel:path:Policy' :: Policy -> Maybe Text
$sel:isAttachable:Policy' :: Policy -> Maybe Bool
$sel:description:Policy' :: Policy -> Maybe Text
$sel:defaultVersionId:Policy' :: Policy -> Maybe Text
$sel:createDate:Policy' :: Policy -> Maybe ISO8601
$sel:attachmentCount:Policy' :: Policy -> Maybe Int
$sel:arn:Policy' :: Policy -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
attachmentCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
createDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultVersionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isAttachable
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
permissionsBoundaryUsageCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
updateDate