{-# 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.Route53.Types.HostedZoneSummary 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.Route53.Internal
import Amazonka.Route53.Types.HostedZoneOwner
data HostedZoneSummary = HostedZoneSummary'
{
HostedZoneSummary -> ResourceId
hostedZoneId :: ResourceId,
HostedZoneSummary -> Text
name :: Prelude.Text,
HostedZoneSummary -> HostedZoneOwner
owner :: HostedZoneOwner
}
deriving (HostedZoneSummary -> HostedZoneSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HostedZoneSummary -> HostedZoneSummary -> Bool
$c/= :: HostedZoneSummary -> HostedZoneSummary -> Bool
== :: HostedZoneSummary -> HostedZoneSummary -> Bool
$c== :: HostedZoneSummary -> HostedZoneSummary -> Bool
Prelude.Eq, ReadPrec [HostedZoneSummary]
ReadPrec HostedZoneSummary
Int -> ReadS HostedZoneSummary
ReadS [HostedZoneSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HostedZoneSummary]
$creadListPrec :: ReadPrec [HostedZoneSummary]
readPrec :: ReadPrec HostedZoneSummary
$creadPrec :: ReadPrec HostedZoneSummary
readList :: ReadS [HostedZoneSummary]
$creadList :: ReadS [HostedZoneSummary]
readsPrec :: Int -> ReadS HostedZoneSummary
$creadsPrec :: Int -> ReadS HostedZoneSummary
Prelude.Read, Int -> HostedZoneSummary -> ShowS
[HostedZoneSummary] -> ShowS
HostedZoneSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HostedZoneSummary] -> ShowS
$cshowList :: [HostedZoneSummary] -> ShowS
show :: HostedZoneSummary -> String
$cshow :: HostedZoneSummary -> String
showsPrec :: Int -> HostedZoneSummary -> ShowS
$cshowsPrec :: Int -> HostedZoneSummary -> ShowS
Prelude.Show, forall x. Rep HostedZoneSummary x -> HostedZoneSummary
forall x. HostedZoneSummary -> Rep HostedZoneSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HostedZoneSummary x -> HostedZoneSummary
$cfrom :: forall x. HostedZoneSummary -> Rep HostedZoneSummary x
Prelude.Generic)
newHostedZoneSummary ::
ResourceId ->
Prelude.Text ->
HostedZoneOwner ->
HostedZoneSummary
newHostedZoneSummary :: ResourceId -> Text -> HostedZoneOwner -> HostedZoneSummary
newHostedZoneSummary ResourceId
pHostedZoneId_ Text
pName_ HostedZoneOwner
pOwner_ =
HostedZoneSummary'
{ $sel:hostedZoneId:HostedZoneSummary' :: ResourceId
hostedZoneId = ResourceId
pHostedZoneId_,
$sel:name:HostedZoneSummary' :: Text
name = Text
pName_,
$sel:owner:HostedZoneSummary' :: HostedZoneOwner
owner = HostedZoneOwner
pOwner_
}
hostedZoneSummary_hostedZoneId :: Lens.Lens' HostedZoneSummary ResourceId
hostedZoneSummary_hostedZoneId :: Lens' HostedZoneSummary ResourceId
hostedZoneSummary_hostedZoneId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HostedZoneSummary' {ResourceId
hostedZoneId :: ResourceId
$sel:hostedZoneId:HostedZoneSummary' :: HostedZoneSummary -> ResourceId
hostedZoneId} -> ResourceId
hostedZoneId) (\s :: HostedZoneSummary
s@HostedZoneSummary' {} ResourceId
a -> HostedZoneSummary
s {$sel:hostedZoneId:HostedZoneSummary' :: ResourceId
hostedZoneId = ResourceId
a} :: HostedZoneSummary)
hostedZoneSummary_name :: Lens.Lens' HostedZoneSummary Prelude.Text
hostedZoneSummary_name :: Lens' HostedZoneSummary Text
hostedZoneSummary_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HostedZoneSummary' {Text
name :: Text
$sel:name:HostedZoneSummary' :: HostedZoneSummary -> Text
name} -> Text
name) (\s :: HostedZoneSummary
s@HostedZoneSummary' {} Text
a -> HostedZoneSummary
s {$sel:name:HostedZoneSummary' :: Text
name = Text
a} :: HostedZoneSummary)
hostedZoneSummary_owner :: Lens.Lens' HostedZoneSummary HostedZoneOwner
hostedZoneSummary_owner :: Lens' HostedZoneSummary HostedZoneOwner
hostedZoneSummary_owner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HostedZoneSummary' {HostedZoneOwner
owner :: HostedZoneOwner
$sel:owner:HostedZoneSummary' :: HostedZoneSummary -> HostedZoneOwner
owner} -> HostedZoneOwner
owner) (\s :: HostedZoneSummary
s@HostedZoneSummary' {} HostedZoneOwner
a -> HostedZoneSummary
s {$sel:owner:HostedZoneSummary' :: HostedZoneOwner
owner = HostedZoneOwner
a} :: HostedZoneSummary)
instance Data.FromXML HostedZoneSummary where
parseXML :: [Node] -> Either String HostedZoneSummary
parseXML [Node]
x =
ResourceId -> Text -> HostedZoneOwner -> HostedZoneSummary
HostedZoneSummary'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"HostedZoneId")
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
"Name")
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
"Owner")
instance Prelude.Hashable HostedZoneSummary where
hashWithSalt :: Int -> HostedZoneSummary -> Int
hashWithSalt Int
_salt HostedZoneSummary' {Text
ResourceId
HostedZoneOwner
owner :: HostedZoneOwner
name :: Text
hostedZoneId :: ResourceId
$sel:owner:HostedZoneSummary' :: HostedZoneSummary -> HostedZoneOwner
$sel:name:HostedZoneSummary' :: HostedZoneSummary -> Text
$sel:hostedZoneId:HostedZoneSummary' :: HostedZoneSummary -> ResourceId
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ResourceId
hostedZoneId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HostedZoneOwner
owner
instance Prelude.NFData HostedZoneSummary where
rnf :: HostedZoneSummary -> ()
rnf HostedZoneSummary' {Text
ResourceId
HostedZoneOwner
owner :: HostedZoneOwner
name :: Text
hostedZoneId :: ResourceId
$sel:owner:HostedZoneSummary' :: HostedZoneSummary -> HostedZoneOwner
$sel:name:HostedZoneSummary' :: HostedZoneSummary -> Text
$sel:hostedZoneId:HostedZoneSummary' :: HostedZoneSummary -> ResourceId
..} =
forall a. NFData a => a -> ()
Prelude.rnf ResourceId
hostedZoneId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HostedZoneOwner
owner