{-# 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.EC2.Types.IpamResourceCidr
-- 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.EC2.Types.IpamResourceCidr where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.IpamComplianceStatus
import Amazonka.EC2.Types.IpamManagementState
import Amazonka.EC2.Types.IpamOverlapStatus
import Amazonka.EC2.Types.IpamResourceTag
import Amazonka.EC2.Types.IpamResourceType
import qualified Amazonka.Prelude as Prelude

-- | The CIDR for an IPAM resource.
--
-- /See:/ 'newIpamResourceCidr' smart constructor.
data IpamResourceCidr = IpamResourceCidr'
  { -- | The compliance status of the IPAM resource. For more information on
    -- compliance statuses, see
    -- <https://docs.aws.amazon.com/vpc/latest/ipam/monitor-cidr-compliance-ipam.html Monitor CIDR usage by resource>
    -- in the /Amazon VPC IPAM User Guide/.
    IpamResourceCidr -> Maybe IpamComplianceStatus
complianceStatus :: Prelude.Maybe IpamComplianceStatus,
    -- | The percentage of IP address space in use. To convert the decimal to a
    -- percentage, multiply the decimal by 100. Note the following:
    --
    -- -   For a resources that are VPCs, this is the percentage of IP address
    --     space in the VPC that\'s taken up by subnet CIDRs.
    --
    -- -   For resources that are subnets, if the subnet has an IPv4 CIDR
    --     provisioned to it, this is the percentage of IPv4 address space in
    --     the subnet that\'s in use. If the subnet has an IPv6 CIDR
    --     provisioned to it, the percentage of IPv6 address space in use is
    --     not represented. The percentage of IPv6 address space in use cannot
    --     currently be calculated.
    --
    -- -   For resources that are public IPv4 pools, this is the percentage of
    --     IP address space in the pool that\'s been allocated to Elastic IP
    --     addresses (EIPs).
    IpamResourceCidr -> Maybe Double
ipUsage :: Prelude.Maybe Prelude.Double,
    -- | The IPAM ID for an IPAM resource.
    IpamResourceCidr -> Maybe Text
ipamId :: Prelude.Maybe Prelude.Text,
    -- | The pool ID for an IPAM resource.
    IpamResourceCidr -> Maybe Text
ipamPoolId :: Prelude.Maybe Prelude.Text,
    -- | The scope ID for an IPAM resource.
    IpamResourceCidr -> Maybe Text
ipamScopeId :: Prelude.Maybe Prelude.Text,
    -- | The management state of the resource. For more information about
    -- management states, see
    -- <https://docs.aws.amazon.com/vpc/latest/ipam/monitor-cidr-compliance-ipam.html Monitor CIDR usage by resource>
    -- in the /Amazon VPC IPAM User Guide/.
    IpamResourceCidr -> Maybe IpamManagementState
managementState :: Prelude.Maybe IpamManagementState,
    -- | The overlap status of an IPAM resource. The overlap status tells you if
    -- the CIDR for a resource overlaps with another CIDR in the scope. For
    -- more information on overlap statuses, see
    -- <https://docs.aws.amazon.com/vpc/latest/ipam/monitor-cidr-compliance-ipam.html Monitor CIDR usage by resource>
    -- in the /Amazon VPC IPAM User Guide/.
    IpamResourceCidr -> Maybe IpamOverlapStatus
overlapStatus :: Prelude.Maybe IpamOverlapStatus,
    -- | The CIDR for an IPAM resource.
    IpamResourceCidr -> Maybe Text
resourceCidr :: Prelude.Maybe Prelude.Text,
    -- | The ID of an IPAM resource.
    IpamResourceCidr -> Maybe Text
resourceId :: Prelude.Maybe Prelude.Text,
    -- | The name of an IPAM resource.
    IpamResourceCidr -> Maybe Text
resourceName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account number of the owner of an IPAM resource.
    IpamResourceCidr -> Maybe Text
resourceOwnerId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services Region for an IPAM resource.
    IpamResourceCidr -> Maybe Text
resourceRegion :: Prelude.Maybe Prelude.Text,
    -- | The tags for an IPAM resource.
    IpamResourceCidr -> Maybe [IpamResourceTag]
resourceTags :: Prelude.Maybe [IpamResourceTag],
    -- | The type of IPAM resource.
    IpamResourceCidr -> Maybe IpamResourceType
resourceType :: Prelude.Maybe IpamResourceType,
    -- | The ID of a VPC.
    IpamResourceCidr -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text
  }
  deriving (IpamResourceCidr -> IpamResourceCidr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IpamResourceCidr -> IpamResourceCidr -> Bool
$c/= :: IpamResourceCidr -> IpamResourceCidr -> Bool
== :: IpamResourceCidr -> IpamResourceCidr -> Bool
$c== :: IpamResourceCidr -> IpamResourceCidr -> Bool
Prelude.Eq, ReadPrec [IpamResourceCidr]
ReadPrec IpamResourceCidr
Int -> ReadS IpamResourceCidr
ReadS [IpamResourceCidr]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IpamResourceCidr]
$creadListPrec :: ReadPrec [IpamResourceCidr]
readPrec :: ReadPrec IpamResourceCidr
$creadPrec :: ReadPrec IpamResourceCidr
readList :: ReadS [IpamResourceCidr]
$creadList :: ReadS [IpamResourceCidr]
readsPrec :: Int -> ReadS IpamResourceCidr
$creadsPrec :: Int -> ReadS IpamResourceCidr
Prelude.Read, Int -> IpamResourceCidr -> ShowS
[IpamResourceCidr] -> ShowS
IpamResourceCidr -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IpamResourceCidr] -> ShowS
$cshowList :: [IpamResourceCidr] -> ShowS
show :: IpamResourceCidr -> String
$cshow :: IpamResourceCidr -> String
showsPrec :: Int -> IpamResourceCidr -> ShowS
$cshowsPrec :: Int -> IpamResourceCidr -> ShowS
Prelude.Show, forall x. Rep IpamResourceCidr x -> IpamResourceCidr
forall x. IpamResourceCidr -> Rep IpamResourceCidr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IpamResourceCidr x -> IpamResourceCidr
$cfrom :: forall x. IpamResourceCidr -> Rep IpamResourceCidr x
Prelude.Generic)

-- |
-- Create a value of 'IpamResourceCidr' 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:
--
-- 'complianceStatus', 'ipamResourceCidr_complianceStatus' - The compliance status of the IPAM resource. For more information on
-- compliance statuses, see
-- <https://docs.aws.amazon.com/vpc/latest/ipam/monitor-cidr-compliance-ipam.html Monitor CIDR usage by resource>
-- in the /Amazon VPC IPAM User Guide/.
--
-- 'ipUsage', 'ipamResourceCidr_ipUsage' - The percentage of IP address space in use. To convert the decimal to a
-- percentage, multiply the decimal by 100. Note the following:
--
-- -   For a resources that are VPCs, this is the percentage of IP address
--     space in the VPC that\'s taken up by subnet CIDRs.
--
-- -   For resources that are subnets, if the subnet has an IPv4 CIDR
--     provisioned to it, this is the percentage of IPv4 address space in
--     the subnet that\'s in use. If the subnet has an IPv6 CIDR
--     provisioned to it, the percentage of IPv6 address space in use is
--     not represented. The percentage of IPv6 address space in use cannot
--     currently be calculated.
--
-- -   For resources that are public IPv4 pools, this is the percentage of
--     IP address space in the pool that\'s been allocated to Elastic IP
--     addresses (EIPs).
--
-- 'ipamId', 'ipamResourceCidr_ipamId' - The IPAM ID for an IPAM resource.
--
-- 'ipamPoolId', 'ipamResourceCidr_ipamPoolId' - The pool ID for an IPAM resource.
--
-- 'ipamScopeId', 'ipamResourceCidr_ipamScopeId' - The scope ID for an IPAM resource.
--
-- 'managementState', 'ipamResourceCidr_managementState' - The management state of the resource. For more information about
-- management states, see
-- <https://docs.aws.amazon.com/vpc/latest/ipam/monitor-cidr-compliance-ipam.html Monitor CIDR usage by resource>
-- in the /Amazon VPC IPAM User Guide/.
--
-- 'overlapStatus', 'ipamResourceCidr_overlapStatus' - The overlap status of an IPAM resource. The overlap status tells you if
-- the CIDR for a resource overlaps with another CIDR in the scope. For
-- more information on overlap statuses, see
-- <https://docs.aws.amazon.com/vpc/latest/ipam/monitor-cidr-compliance-ipam.html Monitor CIDR usage by resource>
-- in the /Amazon VPC IPAM User Guide/.
--
-- 'resourceCidr', 'ipamResourceCidr_resourceCidr' - The CIDR for an IPAM resource.
--
-- 'resourceId', 'ipamResourceCidr_resourceId' - The ID of an IPAM resource.
--
-- 'resourceName', 'ipamResourceCidr_resourceName' - The name of an IPAM resource.
--
-- 'resourceOwnerId', 'ipamResourceCidr_resourceOwnerId' - The Amazon Web Services account number of the owner of an IPAM resource.
--
-- 'resourceRegion', 'ipamResourceCidr_resourceRegion' - The Amazon Web Services Region for an IPAM resource.
--
-- 'resourceTags', 'ipamResourceCidr_resourceTags' - The tags for an IPAM resource.
--
-- 'resourceType', 'ipamResourceCidr_resourceType' - The type of IPAM resource.
--
-- 'vpcId', 'ipamResourceCidr_vpcId' - The ID of a VPC.
newIpamResourceCidr ::
  IpamResourceCidr
newIpamResourceCidr :: IpamResourceCidr
newIpamResourceCidr =
  IpamResourceCidr'
    { $sel:complianceStatus:IpamResourceCidr' :: Maybe IpamComplianceStatus
complianceStatus =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ipUsage:IpamResourceCidr' :: Maybe Double
ipUsage = forall a. Maybe a
Prelude.Nothing,
      $sel:ipamId:IpamResourceCidr' :: Maybe Text
ipamId = forall a. Maybe a
Prelude.Nothing,
      $sel:ipamPoolId:IpamResourceCidr' :: Maybe Text
ipamPoolId = forall a. Maybe a
Prelude.Nothing,
      $sel:ipamScopeId:IpamResourceCidr' :: Maybe Text
ipamScopeId = forall a. Maybe a
Prelude.Nothing,
      $sel:managementState:IpamResourceCidr' :: Maybe IpamManagementState
managementState = forall a. Maybe a
Prelude.Nothing,
      $sel:overlapStatus:IpamResourceCidr' :: Maybe IpamOverlapStatus
overlapStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceCidr:IpamResourceCidr' :: Maybe Text
resourceCidr = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceId:IpamResourceCidr' :: Maybe Text
resourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceName:IpamResourceCidr' :: Maybe Text
resourceName = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceOwnerId:IpamResourceCidr' :: Maybe Text
resourceOwnerId = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceRegion:IpamResourceCidr' :: Maybe Text
resourceRegion = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceTags:IpamResourceCidr' :: Maybe [IpamResourceTag]
resourceTags = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:IpamResourceCidr' :: Maybe IpamResourceType
resourceType = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:IpamResourceCidr' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing
    }

-- | The compliance status of the IPAM resource. For more information on
-- compliance statuses, see
-- <https://docs.aws.amazon.com/vpc/latest/ipam/monitor-cidr-compliance-ipam.html Monitor CIDR usage by resource>
-- in the /Amazon VPC IPAM User Guide/.
ipamResourceCidr_complianceStatus :: Lens.Lens' IpamResourceCidr (Prelude.Maybe IpamComplianceStatus)
ipamResourceCidr_complianceStatus :: Lens' IpamResourceCidr (Maybe IpamComplianceStatus)
ipamResourceCidr_complianceStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe IpamComplianceStatus
complianceStatus :: Maybe IpamComplianceStatus
$sel:complianceStatus:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamComplianceStatus
complianceStatus} -> Maybe IpamComplianceStatus
complianceStatus) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe IpamComplianceStatus
a -> IpamResourceCidr
s {$sel:complianceStatus:IpamResourceCidr' :: Maybe IpamComplianceStatus
complianceStatus = Maybe IpamComplianceStatus
a} :: IpamResourceCidr)

-- | The percentage of IP address space in use. To convert the decimal to a
-- percentage, multiply the decimal by 100. Note the following:
--
-- -   For a resources that are VPCs, this is the percentage of IP address
--     space in the VPC that\'s taken up by subnet CIDRs.
--
-- -   For resources that are subnets, if the subnet has an IPv4 CIDR
--     provisioned to it, this is the percentage of IPv4 address space in
--     the subnet that\'s in use. If the subnet has an IPv6 CIDR
--     provisioned to it, the percentage of IPv6 address space in use is
--     not represented. The percentage of IPv6 address space in use cannot
--     currently be calculated.
--
-- -   For resources that are public IPv4 pools, this is the percentage of
--     IP address space in the pool that\'s been allocated to Elastic IP
--     addresses (EIPs).
ipamResourceCidr_ipUsage :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Double)
ipamResourceCidr_ipUsage :: Lens' IpamResourceCidr (Maybe Double)
ipamResourceCidr_ipUsage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Double
ipUsage :: Maybe Double
$sel:ipUsage:IpamResourceCidr' :: IpamResourceCidr -> Maybe Double
ipUsage} -> Maybe Double
ipUsage) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Double
a -> IpamResourceCidr
s {$sel:ipUsage:IpamResourceCidr' :: Maybe Double
ipUsage = Maybe Double
a} :: IpamResourceCidr)

-- | The IPAM ID for an IPAM resource.
ipamResourceCidr_ipamId :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Text)
ipamResourceCidr_ipamId :: Lens' IpamResourceCidr (Maybe Text)
ipamResourceCidr_ipamId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Text
ipamId :: Maybe Text
$sel:ipamId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
ipamId} -> Maybe Text
ipamId) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Text
a -> IpamResourceCidr
s {$sel:ipamId:IpamResourceCidr' :: Maybe Text
ipamId = Maybe Text
a} :: IpamResourceCidr)

-- | The pool ID for an IPAM resource.
ipamResourceCidr_ipamPoolId :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Text)
ipamResourceCidr_ipamPoolId :: Lens' IpamResourceCidr (Maybe Text)
ipamResourceCidr_ipamPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Text
ipamPoolId :: Maybe Text
$sel:ipamPoolId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
ipamPoolId} -> Maybe Text
ipamPoolId) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Text
a -> IpamResourceCidr
s {$sel:ipamPoolId:IpamResourceCidr' :: Maybe Text
ipamPoolId = Maybe Text
a} :: IpamResourceCidr)

-- | The scope ID for an IPAM resource.
ipamResourceCidr_ipamScopeId :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Text)
ipamResourceCidr_ipamScopeId :: Lens' IpamResourceCidr (Maybe Text)
ipamResourceCidr_ipamScopeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Text
ipamScopeId :: Maybe Text
$sel:ipamScopeId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
ipamScopeId} -> Maybe Text
ipamScopeId) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Text
a -> IpamResourceCidr
s {$sel:ipamScopeId:IpamResourceCidr' :: Maybe Text
ipamScopeId = Maybe Text
a} :: IpamResourceCidr)

-- | The management state of the resource. For more information about
-- management states, see
-- <https://docs.aws.amazon.com/vpc/latest/ipam/monitor-cidr-compliance-ipam.html Monitor CIDR usage by resource>
-- in the /Amazon VPC IPAM User Guide/.
ipamResourceCidr_managementState :: Lens.Lens' IpamResourceCidr (Prelude.Maybe IpamManagementState)
ipamResourceCidr_managementState :: Lens' IpamResourceCidr (Maybe IpamManagementState)
ipamResourceCidr_managementState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe IpamManagementState
managementState :: Maybe IpamManagementState
$sel:managementState:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamManagementState
managementState} -> Maybe IpamManagementState
managementState) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe IpamManagementState
a -> IpamResourceCidr
s {$sel:managementState:IpamResourceCidr' :: Maybe IpamManagementState
managementState = Maybe IpamManagementState
a} :: IpamResourceCidr)

-- | The overlap status of an IPAM resource. The overlap status tells you if
-- the CIDR for a resource overlaps with another CIDR in the scope. For
-- more information on overlap statuses, see
-- <https://docs.aws.amazon.com/vpc/latest/ipam/monitor-cidr-compliance-ipam.html Monitor CIDR usage by resource>
-- in the /Amazon VPC IPAM User Guide/.
ipamResourceCidr_overlapStatus :: Lens.Lens' IpamResourceCidr (Prelude.Maybe IpamOverlapStatus)
ipamResourceCidr_overlapStatus :: Lens' IpamResourceCidr (Maybe IpamOverlapStatus)
ipamResourceCidr_overlapStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe IpamOverlapStatus
overlapStatus :: Maybe IpamOverlapStatus
$sel:overlapStatus:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamOverlapStatus
overlapStatus} -> Maybe IpamOverlapStatus
overlapStatus) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe IpamOverlapStatus
a -> IpamResourceCidr
s {$sel:overlapStatus:IpamResourceCidr' :: Maybe IpamOverlapStatus
overlapStatus = Maybe IpamOverlapStatus
a} :: IpamResourceCidr)

-- | The CIDR for an IPAM resource.
ipamResourceCidr_resourceCidr :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Text)
ipamResourceCidr_resourceCidr :: Lens' IpamResourceCidr (Maybe Text)
ipamResourceCidr_resourceCidr = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Text
resourceCidr :: Maybe Text
$sel:resourceCidr:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
resourceCidr} -> Maybe Text
resourceCidr) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Text
a -> IpamResourceCidr
s {$sel:resourceCidr:IpamResourceCidr' :: Maybe Text
resourceCidr = Maybe Text
a} :: IpamResourceCidr)

-- | The ID of an IPAM resource.
ipamResourceCidr_resourceId :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Text)
ipamResourceCidr_resourceId :: Lens' IpamResourceCidr (Maybe Text)
ipamResourceCidr_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Text
resourceId :: Maybe Text
$sel:resourceId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
resourceId} -> Maybe Text
resourceId) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Text
a -> IpamResourceCidr
s {$sel:resourceId:IpamResourceCidr' :: Maybe Text
resourceId = Maybe Text
a} :: IpamResourceCidr)

-- | The name of an IPAM resource.
ipamResourceCidr_resourceName :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Text)
ipamResourceCidr_resourceName :: Lens' IpamResourceCidr (Maybe Text)
ipamResourceCidr_resourceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Text
resourceName :: Maybe Text
$sel:resourceName:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
resourceName} -> Maybe Text
resourceName) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Text
a -> IpamResourceCidr
s {$sel:resourceName:IpamResourceCidr' :: Maybe Text
resourceName = Maybe Text
a} :: IpamResourceCidr)

-- | The Amazon Web Services account number of the owner of an IPAM resource.
ipamResourceCidr_resourceOwnerId :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Text)
ipamResourceCidr_resourceOwnerId :: Lens' IpamResourceCidr (Maybe Text)
ipamResourceCidr_resourceOwnerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Text
resourceOwnerId :: Maybe Text
$sel:resourceOwnerId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
resourceOwnerId} -> Maybe Text
resourceOwnerId) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Text
a -> IpamResourceCidr
s {$sel:resourceOwnerId:IpamResourceCidr' :: Maybe Text
resourceOwnerId = Maybe Text
a} :: IpamResourceCidr)

-- | The Amazon Web Services Region for an IPAM resource.
ipamResourceCidr_resourceRegion :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Text)
ipamResourceCidr_resourceRegion :: Lens' IpamResourceCidr (Maybe Text)
ipamResourceCidr_resourceRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Text
resourceRegion :: Maybe Text
$sel:resourceRegion:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
resourceRegion} -> Maybe Text
resourceRegion) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Text
a -> IpamResourceCidr
s {$sel:resourceRegion:IpamResourceCidr' :: Maybe Text
resourceRegion = Maybe Text
a} :: IpamResourceCidr)

-- | The tags for an IPAM resource.
ipamResourceCidr_resourceTags :: Lens.Lens' IpamResourceCidr (Prelude.Maybe [IpamResourceTag])
ipamResourceCidr_resourceTags :: Lens' IpamResourceCidr (Maybe [IpamResourceTag])
ipamResourceCidr_resourceTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe [IpamResourceTag]
resourceTags :: Maybe [IpamResourceTag]
$sel:resourceTags:IpamResourceCidr' :: IpamResourceCidr -> Maybe [IpamResourceTag]
resourceTags} -> Maybe [IpamResourceTag]
resourceTags) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe [IpamResourceTag]
a -> IpamResourceCidr
s {$sel:resourceTags:IpamResourceCidr' :: Maybe [IpamResourceTag]
resourceTags = Maybe [IpamResourceTag]
a} :: IpamResourceCidr) 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 type of IPAM resource.
ipamResourceCidr_resourceType :: Lens.Lens' IpamResourceCidr (Prelude.Maybe IpamResourceType)
ipamResourceCidr_resourceType :: Lens' IpamResourceCidr (Maybe IpamResourceType)
ipamResourceCidr_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe IpamResourceType
resourceType :: Maybe IpamResourceType
$sel:resourceType:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamResourceType
resourceType} -> Maybe IpamResourceType
resourceType) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe IpamResourceType
a -> IpamResourceCidr
s {$sel:resourceType:IpamResourceCidr' :: Maybe IpamResourceType
resourceType = Maybe IpamResourceType
a} :: IpamResourceCidr)

-- | The ID of a VPC.
ipamResourceCidr_vpcId :: Lens.Lens' IpamResourceCidr (Prelude.Maybe Prelude.Text)
ipamResourceCidr_vpcId :: Lens' IpamResourceCidr (Maybe Text)
ipamResourceCidr_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpamResourceCidr' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: IpamResourceCidr
s@IpamResourceCidr' {} Maybe Text
a -> IpamResourceCidr
s {$sel:vpcId:IpamResourceCidr' :: Maybe Text
vpcId = Maybe Text
a} :: IpamResourceCidr)

instance Data.FromXML IpamResourceCidr where
  parseXML :: [Node] -> Either String IpamResourceCidr
parseXML [Node]
x =
    Maybe IpamComplianceStatus
-> Maybe Double
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe IpamManagementState
-> Maybe IpamOverlapStatus
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [IpamResourceTag]
-> Maybe IpamResourceType
-> Maybe Text
-> IpamResourceCidr
IpamResourceCidr'
      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
"complianceStatus")
      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
"ipUsage")
      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
"ipamId")
      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
"ipamPoolId")
      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
"ipamScopeId")
      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
"managementState")
      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
"overlapStatus")
      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
"resourceCidr")
      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
"resourceId")
      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
"resourceName")
      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
"resourceOwnerId")
      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
"resourceRegion")
      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
"resourceTagSet"
                      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
"item")
                  )
      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
"resourceType")
      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
"vpcId")

instance Prelude.Hashable IpamResourceCidr where
  hashWithSalt :: Int -> IpamResourceCidr -> Int
hashWithSalt Int
_salt IpamResourceCidr' {Maybe Double
Maybe [IpamResourceTag]
Maybe Text
Maybe IpamComplianceStatus
Maybe IpamManagementState
Maybe IpamOverlapStatus
Maybe IpamResourceType
vpcId :: Maybe Text
resourceType :: Maybe IpamResourceType
resourceTags :: Maybe [IpamResourceTag]
resourceRegion :: Maybe Text
resourceOwnerId :: Maybe Text
resourceName :: Maybe Text
resourceId :: Maybe Text
resourceCidr :: Maybe Text
overlapStatus :: Maybe IpamOverlapStatus
managementState :: Maybe IpamManagementState
ipamScopeId :: Maybe Text
ipamPoolId :: Maybe Text
ipamId :: Maybe Text
ipUsage :: Maybe Double
complianceStatus :: Maybe IpamComplianceStatus
$sel:vpcId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceType:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamResourceType
$sel:resourceTags:IpamResourceCidr' :: IpamResourceCidr -> Maybe [IpamResourceTag]
$sel:resourceRegion:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceOwnerId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceName:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceCidr:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:overlapStatus:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamOverlapStatus
$sel:managementState:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamManagementState
$sel:ipamScopeId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:ipamPoolId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:ipamId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:ipUsage:IpamResourceCidr' :: IpamResourceCidr -> Maybe Double
$sel:complianceStatus:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamComplianceStatus
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IpamComplianceStatus
complianceStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
ipUsage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ipamId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ipamPoolId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ipamScopeId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IpamManagementState
managementState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IpamOverlapStatus
overlapStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceCidr
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceOwnerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceRegion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [IpamResourceTag]
resourceTags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IpamResourceType
resourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId

instance Prelude.NFData IpamResourceCidr where
  rnf :: IpamResourceCidr -> ()
rnf IpamResourceCidr' {Maybe Double
Maybe [IpamResourceTag]
Maybe Text
Maybe IpamComplianceStatus
Maybe IpamManagementState
Maybe IpamOverlapStatus
Maybe IpamResourceType
vpcId :: Maybe Text
resourceType :: Maybe IpamResourceType
resourceTags :: Maybe [IpamResourceTag]
resourceRegion :: Maybe Text
resourceOwnerId :: Maybe Text
resourceName :: Maybe Text
resourceId :: Maybe Text
resourceCidr :: Maybe Text
overlapStatus :: Maybe IpamOverlapStatus
managementState :: Maybe IpamManagementState
ipamScopeId :: Maybe Text
ipamPoolId :: Maybe Text
ipamId :: Maybe Text
ipUsage :: Maybe Double
complianceStatus :: Maybe IpamComplianceStatus
$sel:vpcId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceType:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamResourceType
$sel:resourceTags:IpamResourceCidr' :: IpamResourceCidr -> Maybe [IpamResourceTag]
$sel:resourceRegion:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceOwnerId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceName:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:resourceCidr:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:overlapStatus:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamOverlapStatus
$sel:managementState:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamManagementState
$sel:ipamScopeId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:ipamPoolId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:ipamId:IpamResourceCidr' :: IpamResourceCidr -> Maybe Text
$sel:ipUsage:IpamResourceCidr' :: IpamResourceCidr -> Maybe Double
$sel:complianceStatus:IpamResourceCidr' :: IpamResourceCidr -> Maybe IpamComplianceStatus
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe IpamComplianceStatus
complianceStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
ipUsage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ipamId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ipamPoolId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ipamScopeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IpamManagementState
managementState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IpamOverlapStatus
overlapStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceCidr
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceOwnerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceRegion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [IpamResourceTag]
resourceTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IpamResourceType
resourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId