{-# 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.Redshift.Types.ClusterSubnetGroup
-- 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.Redshift.Types.ClusterSubnetGroup where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.Redshift.Internal
import Amazonka.Redshift.Types.Subnet
import Amazonka.Redshift.Types.Tag

-- | Describes a subnet group.
--
-- /See:/ 'newClusterSubnetGroup' smart constructor.
data ClusterSubnetGroup = ClusterSubnetGroup'
  { -- | The name of the cluster subnet group.
    ClusterSubnetGroup -> Maybe Text
clusterSubnetGroupName :: Prelude.Maybe Prelude.Text,
    -- | The description of the cluster subnet group.
    ClusterSubnetGroup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The status of the cluster subnet group. Possible values are @Complete@,
    -- @Incomplete@ and @Invalid@.
    ClusterSubnetGroup -> Maybe Text
subnetGroupStatus :: Prelude.Maybe Prelude.Text,
    -- | A list of the VPC Subnet elements.
    ClusterSubnetGroup -> Maybe [Subnet]
subnets :: Prelude.Maybe [Subnet],
    -- | The list of tags for the cluster subnet group.
    ClusterSubnetGroup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The VPC ID of the cluster subnet group.
    ClusterSubnetGroup -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text
  }
  deriving (ClusterSubnetGroup -> ClusterSubnetGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClusterSubnetGroup -> ClusterSubnetGroup -> Bool
$c/= :: ClusterSubnetGroup -> ClusterSubnetGroup -> Bool
== :: ClusterSubnetGroup -> ClusterSubnetGroup -> Bool
$c== :: ClusterSubnetGroup -> ClusterSubnetGroup -> Bool
Prelude.Eq, ReadPrec [ClusterSubnetGroup]
ReadPrec ClusterSubnetGroup
Int -> ReadS ClusterSubnetGroup
ReadS [ClusterSubnetGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClusterSubnetGroup]
$creadListPrec :: ReadPrec [ClusterSubnetGroup]
readPrec :: ReadPrec ClusterSubnetGroup
$creadPrec :: ReadPrec ClusterSubnetGroup
readList :: ReadS [ClusterSubnetGroup]
$creadList :: ReadS [ClusterSubnetGroup]
readsPrec :: Int -> ReadS ClusterSubnetGroup
$creadsPrec :: Int -> ReadS ClusterSubnetGroup
Prelude.Read, Int -> ClusterSubnetGroup -> ShowS
[ClusterSubnetGroup] -> ShowS
ClusterSubnetGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClusterSubnetGroup] -> ShowS
$cshowList :: [ClusterSubnetGroup] -> ShowS
show :: ClusterSubnetGroup -> String
$cshow :: ClusterSubnetGroup -> String
showsPrec :: Int -> ClusterSubnetGroup -> ShowS
$cshowsPrec :: Int -> ClusterSubnetGroup -> ShowS
Prelude.Show, forall x. Rep ClusterSubnetGroup x -> ClusterSubnetGroup
forall x. ClusterSubnetGroup -> Rep ClusterSubnetGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClusterSubnetGroup x -> ClusterSubnetGroup
$cfrom :: forall x. ClusterSubnetGroup -> Rep ClusterSubnetGroup x
Prelude.Generic)

-- |
-- Create a value of 'ClusterSubnetGroup' 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:
--
-- 'clusterSubnetGroupName', 'clusterSubnetGroup_clusterSubnetGroupName' - The name of the cluster subnet group.
--
-- 'description', 'clusterSubnetGroup_description' - The description of the cluster subnet group.
--
-- 'subnetGroupStatus', 'clusterSubnetGroup_subnetGroupStatus' - The status of the cluster subnet group. Possible values are @Complete@,
-- @Incomplete@ and @Invalid@.
--
-- 'subnets', 'clusterSubnetGroup_subnets' - A list of the VPC Subnet elements.
--
-- 'tags', 'clusterSubnetGroup_tags' - The list of tags for the cluster subnet group.
--
-- 'vpcId', 'clusterSubnetGroup_vpcId' - The VPC ID of the cluster subnet group.
newClusterSubnetGroup ::
  ClusterSubnetGroup
newClusterSubnetGroup :: ClusterSubnetGroup
newClusterSubnetGroup =
  ClusterSubnetGroup'
    { $sel:clusterSubnetGroupName:ClusterSubnetGroup' :: Maybe Text
clusterSubnetGroupName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:ClusterSubnetGroup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetGroupStatus:ClusterSubnetGroup' :: Maybe Text
subnetGroupStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:subnets:ClusterSubnetGroup' :: Maybe [Subnet]
subnets = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ClusterSubnetGroup' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:ClusterSubnetGroup' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing
    }

-- | The name of the cluster subnet group.
clusterSubnetGroup_clusterSubnetGroupName :: Lens.Lens' ClusterSubnetGroup (Prelude.Maybe Prelude.Text)
clusterSubnetGroup_clusterSubnetGroupName :: Lens' ClusterSubnetGroup (Maybe Text)
clusterSubnetGroup_clusterSubnetGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterSubnetGroup' {Maybe Text
clusterSubnetGroupName :: Maybe Text
$sel:clusterSubnetGroupName:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
clusterSubnetGroupName} -> Maybe Text
clusterSubnetGroupName) (\s :: ClusterSubnetGroup
s@ClusterSubnetGroup' {} Maybe Text
a -> ClusterSubnetGroup
s {$sel:clusterSubnetGroupName:ClusterSubnetGroup' :: Maybe Text
clusterSubnetGroupName = Maybe Text
a} :: ClusterSubnetGroup)

-- | The description of the cluster subnet group.
clusterSubnetGroup_description :: Lens.Lens' ClusterSubnetGroup (Prelude.Maybe Prelude.Text)
clusterSubnetGroup_description :: Lens' ClusterSubnetGroup (Maybe Text)
clusterSubnetGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterSubnetGroup' {Maybe Text
description :: Maybe Text
$sel:description:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
description} -> Maybe Text
description) (\s :: ClusterSubnetGroup
s@ClusterSubnetGroup' {} Maybe Text
a -> ClusterSubnetGroup
s {$sel:description:ClusterSubnetGroup' :: Maybe Text
description = Maybe Text
a} :: ClusterSubnetGroup)

-- | The status of the cluster subnet group. Possible values are @Complete@,
-- @Incomplete@ and @Invalid@.
clusterSubnetGroup_subnetGroupStatus :: Lens.Lens' ClusterSubnetGroup (Prelude.Maybe Prelude.Text)
clusterSubnetGroup_subnetGroupStatus :: Lens' ClusterSubnetGroup (Maybe Text)
clusterSubnetGroup_subnetGroupStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterSubnetGroup' {Maybe Text
subnetGroupStatus :: Maybe Text
$sel:subnetGroupStatus:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
subnetGroupStatus} -> Maybe Text
subnetGroupStatus) (\s :: ClusterSubnetGroup
s@ClusterSubnetGroup' {} Maybe Text
a -> ClusterSubnetGroup
s {$sel:subnetGroupStatus:ClusterSubnetGroup' :: Maybe Text
subnetGroupStatus = Maybe Text
a} :: ClusterSubnetGroup)

-- | A list of the VPC Subnet elements.
clusterSubnetGroup_subnets :: Lens.Lens' ClusterSubnetGroup (Prelude.Maybe [Subnet])
clusterSubnetGroup_subnets :: Lens' ClusterSubnetGroup (Maybe [Subnet])
clusterSubnetGroup_subnets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterSubnetGroup' {Maybe [Subnet]
subnets :: Maybe [Subnet]
$sel:subnets:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe [Subnet]
subnets} -> Maybe [Subnet]
subnets) (\s :: ClusterSubnetGroup
s@ClusterSubnetGroup' {} Maybe [Subnet]
a -> ClusterSubnetGroup
s {$sel:subnets:ClusterSubnetGroup' :: Maybe [Subnet]
subnets = Maybe [Subnet]
a} :: ClusterSubnetGroup) 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 list of tags for the cluster subnet group.
clusterSubnetGroup_tags :: Lens.Lens' ClusterSubnetGroup (Prelude.Maybe [Tag])
clusterSubnetGroup_tags :: Lens' ClusterSubnetGroup (Maybe [Tag])
clusterSubnetGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterSubnetGroup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: ClusterSubnetGroup
s@ClusterSubnetGroup' {} Maybe [Tag]
a -> ClusterSubnetGroup
s {$sel:tags:ClusterSubnetGroup' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: ClusterSubnetGroup) 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 VPC ID of the cluster subnet group.
clusterSubnetGroup_vpcId :: Lens.Lens' ClusterSubnetGroup (Prelude.Maybe Prelude.Text)
clusterSubnetGroup_vpcId :: Lens' ClusterSubnetGroup (Maybe Text)
clusterSubnetGroup_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterSubnetGroup' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: ClusterSubnetGroup
s@ClusterSubnetGroup' {} Maybe Text
a -> ClusterSubnetGroup
s {$sel:vpcId:ClusterSubnetGroup' :: Maybe Text
vpcId = Maybe Text
a} :: ClusterSubnetGroup)

instance Data.FromXML ClusterSubnetGroup where
  parseXML :: [Node] -> Either String ClusterSubnetGroup
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Subnet]
-> Maybe [Tag]
-> Maybe Text
-> ClusterSubnetGroup
ClusterSubnetGroup'
      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
"ClusterSubnetGroupName")
      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
"SubnetGroupStatus")
      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
"Subnets"
                      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
"Subnet")
                  )
      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
"Tag")
                  )
      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 ClusterSubnetGroup where
  hashWithSalt :: Int -> ClusterSubnetGroup -> Int
hashWithSalt Int
_salt ClusterSubnetGroup' {Maybe [Subnet]
Maybe [Tag]
Maybe Text
vpcId :: Maybe Text
tags :: Maybe [Tag]
subnets :: Maybe [Subnet]
subnetGroupStatus :: Maybe Text
description :: Maybe Text
clusterSubnetGroupName :: Maybe Text
$sel:vpcId:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
$sel:tags:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe [Tag]
$sel:subnets:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe [Subnet]
$sel:subnetGroupStatus:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
$sel:description:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
$sel:clusterSubnetGroupName:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clusterSubnetGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetGroupStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Subnet]
subnets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId

instance Prelude.NFData ClusterSubnetGroup where
  rnf :: ClusterSubnetGroup -> ()
rnf ClusterSubnetGroup' {Maybe [Subnet]
Maybe [Tag]
Maybe Text
vpcId :: Maybe Text
tags :: Maybe [Tag]
subnets :: Maybe [Subnet]
subnetGroupStatus :: Maybe Text
description :: Maybe Text
clusterSubnetGroupName :: Maybe Text
$sel:vpcId:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
$sel:tags:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe [Tag]
$sel:subnets:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe [Subnet]
$sel:subnetGroupStatus:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
$sel:description:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
$sel:clusterSubnetGroupName:ClusterSubnetGroup' :: ClusterSubnetGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterSubnetGroupName
      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 Text
subnetGroupStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Subnet]
subnets
      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 Text
vpcId