{-# 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 #-}
module Amazonka.ElastiCache.Types.Subnet where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ElastiCache.Types.AvailabilityZone
import Amazonka.ElastiCache.Types.NetworkType
import Amazonka.ElastiCache.Types.SubnetOutpost
import qualified Amazonka.Prelude as Prelude
data Subnet = Subnet'
{
Subnet -> Maybe AvailabilityZone
subnetAvailabilityZone :: Prelude.Maybe AvailabilityZone,
Subnet -> Maybe Text
subnetIdentifier :: Prelude.Maybe Prelude.Text,
Subnet -> Maybe SubnetOutpost
subnetOutpost :: Prelude.Maybe SubnetOutpost,
Subnet -> Maybe [NetworkType]
supportedNetworkTypes :: Prelude.Maybe [NetworkType]
}
deriving (Subnet -> Subnet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subnet -> Subnet -> Bool
$c/= :: Subnet -> Subnet -> Bool
== :: Subnet -> Subnet -> Bool
$c== :: Subnet -> Subnet -> Bool
Prelude.Eq, ReadPrec [Subnet]
ReadPrec Subnet
Int -> ReadS Subnet
ReadS [Subnet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Subnet]
$creadListPrec :: ReadPrec [Subnet]
readPrec :: ReadPrec Subnet
$creadPrec :: ReadPrec Subnet
readList :: ReadS [Subnet]
$creadList :: ReadS [Subnet]
readsPrec :: Int -> ReadS Subnet
$creadsPrec :: Int -> ReadS Subnet
Prelude.Read, Int -> Subnet -> ShowS
[Subnet] -> ShowS
Subnet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Subnet] -> ShowS
$cshowList :: [Subnet] -> ShowS
show :: Subnet -> String
$cshow :: Subnet -> String
showsPrec :: Int -> Subnet -> ShowS
$cshowsPrec :: Int -> Subnet -> ShowS
Prelude.Show, forall x. Rep Subnet x -> Subnet
forall x. Subnet -> Rep Subnet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Subnet x -> Subnet
$cfrom :: forall x. Subnet -> Rep Subnet x
Prelude.Generic)
newSubnet ::
Subnet
newSubnet :: Subnet
newSubnet =
Subnet'
{ $sel:subnetAvailabilityZone:Subnet' :: Maybe AvailabilityZone
subnetAvailabilityZone = forall a. Maybe a
Prelude.Nothing,
$sel:subnetIdentifier:Subnet' :: Maybe Text
subnetIdentifier = forall a. Maybe a
Prelude.Nothing,
$sel:subnetOutpost:Subnet' :: Maybe SubnetOutpost
subnetOutpost = forall a. Maybe a
Prelude.Nothing,
$sel:supportedNetworkTypes:Subnet' :: Maybe [NetworkType]
supportedNetworkTypes = forall a. Maybe a
Prelude.Nothing
}
subnet_subnetAvailabilityZone :: Lens.Lens' Subnet (Prelude.Maybe AvailabilityZone)
subnet_subnetAvailabilityZone :: Lens' Subnet (Maybe AvailabilityZone)
subnet_subnetAvailabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe AvailabilityZone
subnetAvailabilityZone :: Maybe AvailabilityZone
$sel:subnetAvailabilityZone:Subnet' :: Subnet -> Maybe AvailabilityZone
subnetAvailabilityZone} -> Maybe AvailabilityZone
subnetAvailabilityZone) (\s :: Subnet
s@Subnet' {} Maybe AvailabilityZone
a -> Subnet
s {$sel:subnetAvailabilityZone:Subnet' :: Maybe AvailabilityZone
subnetAvailabilityZone = Maybe AvailabilityZone
a} :: Subnet)
subnet_subnetIdentifier :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Text)
subnet_subnetIdentifier :: Lens' Subnet (Maybe Text)
subnet_subnetIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Text
subnetIdentifier :: Maybe Text
$sel:subnetIdentifier:Subnet' :: Subnet -> Maybe Text
subnetIdentifier} -> Maybe Text
subnetIdentifier) (\s :: Subnet
s@Subnet' {} Maybe Text
a -> Subnet
s {$sel:subnetIdentifier:Subnet' :: Maybe Text
subnetIdentifier = Maybe Text
a} :: Subnet)
subnet_subnetOutpost :: Lens.Lens' Subnet (Prelude.Maybe SubnetOutpost)
subnet_subnetOutpost :: Lens' Subnet (Maybe SubnetOutpost)
subnet_subnetOutpost = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe SubnetOutpost
subnetOutpost :: Maybe SubnetOutpost
$sel:subnetOutpost:Subnet' :: Subnet -> Maybe SubnetOutpost
subnetOutpost} -> Maybe SubnetOutpost
subnetOutpost) (\s :: Subnet
s@Subnet' {} Maybe SubnetOutpost
a -> Subnet
s {$sel:subnetOutpost:Subnet' :: Maybe SubnetOutpost
subnetOutpost = Maybe SubnetOutpost
a} :: Subnet)
subnet_supportedNetworkTypes :: Lens.Lens' Subnet (Prelude.Maybe [NetworkType])
subnet_supportedNetworkTypes :: Lens' Subnet (Maybe [NetworkType])
subnet_supportedNetworkTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe [NetworkType]
supportedNetworkTypes :: Maybe [NetworkType]
$sel:supportedNetworkTypes:Subnet' :: Subnet -> Maybe [NetworkType]
supportedNetworkTypes} -> Maybe [NetworkType]
supportedNetworkTypes) (\s :: Subnet
s@Subnet' {} Maybe [NetworkType]
a -> Subnet
s {$sel:supportedNetworkTypes:Subnet' :: Maybe [NetworkType]
supportedNetworkTypes = Maybe [NetworkType]
a} :: Subnet) 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
instance Data.FromXML Subnet where
parseXML :: [Node] -> Either String Subnet
parseXML [Node]
x =
Maybe AvailabilityZone
-> Maybe Text
-> Maybe SubnetOutpost
-> Maybe [NetworkType]
-> Subnet
Subnet'
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
"SubnetAvailabilityZone")
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
"SubnetIdentifier")
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
"SubnetOutpost")
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
"SupportedNetworkTypes"
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")
)
instance Prelude.Hashable Subnet where
hashWithSalt :: Int -> Subnet -> Int
hashWithSalt Int
_salt Subnet' {Maybe [NetworkType]
Maybe Text
Maybe AvailabilityZone
Maybe SubnetOutpost
supportedNetworkTypes :: Maybe [NetworkType]
subnetOutpost :: Maybe SubnetOutpost
subnetIdentifier :: Maybe Text
subnetAvailabilityZone :: Maybe AvailabilityZone
$sel:supportedNetworkTypes:Subnet' :: Subnet -> Maybe [NetworkType]
$sel:subnetOutpost:Subnet' :: Subnet -> Maybe SubnetOutpost
$sel:subnetIdentifier:Subnet' :: Subnet -> Maybe Text
$sel:subnetAvailabilityZone:Subnet' :: Subnet -> Maybe AvailabilityZone
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AvailabilityZone
subnetAvailabilityZone
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetIdentifier
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SubnetOutpost
subnetOutpost
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NetworkType]
supportedNetworkTypes
instance Prelude.NFData Subnet where
rnf :: Subnet -> ()
rnf Subnet' {Maybe [NetworkType]
Maybe Text
Maybe AvailabilityZone
Maybe SubnetOutpost
supportedNetworkTypes :: Maybe [NetworkType]
subnetOutpost :: Maybe SubnetOutpost
subnetIdentifier :: Maybe Text
subnetAvailabilityZone :: Maybe AvailabilityZone
$sel:supportedNetworkTypes:Subnet' :: Subnet -> Maybe [NetworkType]
$sel:subnetOutpost:Subnet' :: Subnet -> Maybe SubnetOutpost
$sel:subnetIdentifier:Subnet' :: Subnet -> Maybe Text
$sel:subnetAvailabilityZone:Subnet' :: Subnet -> Maybe AvailabilityZone
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe AvailabilityZone
subnetAvailabilityZone
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetIdentifier
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SubnetOutpost
subnetOutpost
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [NetworkType]
supportedNetworkTypes