{-# 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.Amplify.Types.SubDomain
-- 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.Amplify.Types.SubDomain where

import Amazonka.Amplify.Types.SubDomainSetting
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

-- | The subdomain for the domain association.
--
-- /See:/ 'newSubDomain' smart constructor.
data SubDomain = SubDomain'
  { -- | Describes the settings for the subdomain.
    SubDomain -> SubDomainSetting
subDomainSetting :: SubDomainSetting,
    -- | The verified status of the subdomain
    SubDomain -> Bool
verified :: Prelude.Bool,
    -- | The DNS record for the subdomain.
    SubDomain -> Text
dnsRecord :: Prelude.Text
  }
  deriving (SubDomain -> SubDomain -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubDomain -> SubDomain -> Bool
$c/= :: SubDomain -> SubDomain -> Bool
== :: SubDomain -> SubDomain -> Bool
$c== :: SubDomain -> SubDomain -> Bool
Prelude.Eq, ReadPrec [SubDomain]
ReadPrec SubDomain
Int -> ReadS SubDomain
ReadS [SubDomain]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SubDomain]
$creadListPrec :: ReadPrec [SubDomain]
readPrec :: ReadPrec SubDomain
$creadPrec :: ReadPrec SubDomain
readList :: ReadS [SubDomain]
$creadList :: ReadS [SubDomain]
readsPrec :: Int -> ReadS SubDomain
$creadsPrec :: Int -> ReadS SubDomain
Prelude.Read, Int -> SubDomain -> ShowS
[SubDomain] -> ShowS
SubDomain -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubDomain] -> ShowS
$cshowList :: [SubDomain] -> ShowS
show :: SubDomain -> String
$cshow :: SubDomain -> String
showsPrec :: Int -> SubDomain -> ShowS
$cshowsPrec :: Int -> SubDomain -> ShowS
Prelude.Show, forall x. Rep SubDomain x -> SubDomain
forall x. SubDomain -> Rep SubDomain x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubDomain x -> SubDomain
$cfrom :: forall x. SubDomain -> Rep SubDomain x
Prelude.Generic)

-- |
-- Create a value of 'SubDomain' 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:
--
-- 'subDomainSetting', 'subDomain_subDomainSetting' - Describes the settings for the subdomain.
--
-- 'verified', 'subDomain_verified' - The verified status of the subdomain
--
-- 'dnsRecord', 'subDomain_dnsRecord' - The DNS record for the subdomain.
newSubDomain ::
  -- | 'subDomainSetting'
  SubDomainSetting ->
  -- | 'verified'
  Prelude.Bool ->
  -- | 'dnsRecord'
  Prelude.Text ->
  SubDomain
newSubDomain :: SubDomainSetting -> Bool -> Text -> SubDomain
newSubDomain
  SubDomainSetting
pSubDomainSetting_
  Bool
pVerified_
  Text
pDnsRecord_ =
    SubDomain'
      { $sel:subDomainSetting:SubDomain' :: SubDomainSetting
subDomainSetting = SubDomainSetting
pSubDomainSetting_,
        $sel:verified:SubDomain' :: Bool
verified = Bool
pVerified_,
        $sel:dnsRecord:SubDomain' :: Text
dnsRecord = Text
pDnsRecord_
      }

-- | Describes the settings for the subdomain.
subDomain_subDomainSetting :: Lens.Lens' SubDomain SubDomainSetting
subDomain_subDomainSetting :: Lens' SubDomain SubDomainSetting
subDomain_subDomainSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SubDomain' {SubDomainSetting
subDomainSetting :: SubDomainSetting
$sel:subDomainSetting:SubDomain' :: SubDomain -> SubDomainSetting
subDomainSetting} -> SubDomainSetting
subDomainSetting) (\s :: SubDomain
s@SubDomain' {} SubDomainSetting
a -> SubDomain
s {$sel:subDomainSetting:SubDomain' :: SubDomainSetting
subDomainSetting = SubDomainSetting
a} :: SubDomain)

-- | The verified status of the subdomain
subDomain_verified :: Lens.Lens' SubDomain Prelude.Bool
subDomain_verified :: Lens' SubDomain Bool
subDomain_verified = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SubDomain' {Bool
verified :: Bool
$sel:verified:SubDomain' :: SubDomain -> Bool
verified} -> Bool
verified) (\s :: SubDomain
s@SubDomain' {} Bool
a -> SubDomain
s {$sel:verified:SubDomain' :: Bool
verified = Bool
a} :: SubDomain)

-- | The DNS record for the subdomain.
subDomain_dnsRecord :: Lens.Lens' SubDomain Prelude.Text
subDomain_dnsRecord :: Lens' SubDomain Text
subDomain_dnsRecord = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SubDomain' {Text
dnsRecord :: Text
$sel:dnsRecord:SubDomain' :: SubDomain -> Text
dnsRecord} -> Text
dnsRecord) (\s :: SubDomain
s@SubDomain' {} Text
a -> SubDomain
s {$sel:dnsRecord:SubDomain' :: Text
dnsRecord = Text
a} :: SubDomain)

instance Data.FromJSON SubDomain where
  parseJSON :: Value -> Parser SubDomain
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SubDomain"
      ( \Object
x ->
          SubDomainSetting -> Bool -> Text -> SubDomain
SubDomain'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"subDomainSetting")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"verified")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"dnsRecord")
      )

instance Prelude.Hashable SubDomain where
  hashWithSalt :: Int -> SubDomain -> Int
hashWithSalt Int
_salt SubDomain' {Bool
Text
SubDomainSetting
dnsRecord :: Text
verified :: Bool
subDomainSetting :: SubDomainSetting
$sel:dnsRecord:SubDomain' :: SubDomain -> Text
$sel:verified:SubDomain' :: SubDomain -> Bool
$sel:subDomainSetting:SubDomain' :: SubDomain -> SubDomainSetting
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SubDomainSetting
subDomainSetting
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
verified
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dnsRecord

instance Prelude.NFData SubDomain where
  rnf :: SubDomain -> ()
rnf SubDomain' {Bool
Text
SubDomainSetting
dnsRecord :: Text
verified :: Bool
subDomainSetting :: SubDomainSetting
$sel:dnsRecord:SubDomain' :: SubDomain -> Text
$sel:verified:SubDomain' :: SubDomain -> Bool
$sel:subDomainSetting:SubDomain' :: SubDomain -> SubDomainSetting
..} =
    forall a. NFData a => a -> ()
Prelude.rnf SubDomainSetting
subDomainSetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
verified
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dnsRecord