{-# 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.Lightsail.Types.DnsRecordCreationState
-- 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.Lightsail.Types.DnsRecordCreationState where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Lightsail.Types.DnsRecordCreationStateCode
import qualified Amazonka.Prelude as Prelude

-- | Describes the creation state of the canonical name (CNAME) records that
-- are automatically added by Amazon Lightsail to the DNS of a domain to
-- validate domain ownership for an SSL\/TLS certificate.
--
-- When you create an SSL\/TLS certificate for a Lightsail resource, you
-- must add a set of CNAME records to the DNS of the domains for the
-- certificate to validate that you own the domains. Lightsail can
-- automatically add the CNAME records to the DNS of the domain if the DNS
-- zone for the domain exists within your Lightsail account. If automatic
-- record addition fails, or if you manage the DNS of your domain using a
-- third-party service, then you must manually add the CNAME records to the
-- DNS of your domain. For more information, see
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/verify-tls-ssl-certificate-using-dns-cname-https Verify an SSL\/TLS certificate in Amazon Lightsail>
-- in the /Amazon Lightsail Developer Guide/.
--
-- /See:/ 'newDnsRecordCreationState' smart constructor.
data DnsRecordCreationState = DnsRecordCreationState'
  { -- | The status code for the automated DNS record creation.
    --
    -- Following are the possible values:
    --
    -- -   @SUCCEEDED@ - The validation records were successfully added to the
    --     domain.
    --
    -- -   @STARTED@ - The automatic DNS record creation has started.
    --
    -- -   @FAILED@ - The validation records failed to be added to the domain.
    DnsRecordCreationState -> Maybe DnsRecordCreationStateCode
code :: Prelude.Maybe DnsRecordCreationStateCode,
    -- | The message that describes the reason for the status code.
    DnsRecordCreationState -> Maybe Text
message :: Prelude.Maybe Prelude.Text
  }
  deriving (DnsRecordCreationState -> DnsRecordCreationState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DnsRecordCreationState -> DnsRecordCreationState -> Bool
$c/= :: DnsRecordCreationState -> DnsRecordCreationState -> Bool
== :: DnsRecordCreationState -> DnsRecordCreationState -> Bool
$c== :: DnsRecordCreationState -> DnsRecordCreationState -> Bool
Prelude.Eq, ReadPrec [DnsRecordCreationState]
ReadPrec DnsRecordCreationState
Int -> ReadS DnsRecordCreationState
ReadS [DnsRecordCreationState]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DnsRecordCreationState]
$creadListPrec :: ReadPrec [DnsRecordCreationState]
readPrec :: ReadPrec DnsRecordCreationState
$creadPrec :: ReadPrec DnsRecordCreationState
readList :: ReadS [DnsRecordCreationState]
$creadList :: ReadS [DnsRecordCreationState]
readsPrec :: Int -> ReadS DnsRecordCreationState
$creadsPrec :: Int -> ReadS DnsRecordCreationState
Prelude.Read, Int -> DnsRecordCreationState -> ShowS
[DnsRecordCreationState] -> ShowS
DnsRecordCreationState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DnsRecordCreationState] -> ShowS
$cshowList :: [DnsRecordCreationState] -> ShowS
show :: DnsRecordCreationState -> String
$cshow :: DnsRecordCreationState -> String
showsPrec :: Int -> DnsRecordCreationState -> ShowS
$cshowsPrec :: Int -> DnsRecordCreationState -> ShowS
Prelude.Show, forall x. Rep DnsRecordCreationState x -> DnsRecordCreationState
forall x. DnsRecordCreationState -> Rep DnsRecordCreationState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DnsRecordCreationState x -> DnsRecordCreationState
$cfrom :: forall x. DnsRecordCreationState -> Rep DnsRecordCreationState x
Prelude.Generic)

-- |
-- Create a value of 'DnsRecordCreationState' 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:
--
-- 'code', 'dnsRecordCreationState_code' - The status code for the automated DNS record creation.
--
-- Following are the possible values:
--
-- -   @SUCCEEDED@ - The validation records were successfully added to the
--     domain.
--
-- -   @STARTED@ - The automatic DNS record creation has started.
--
-- -   @FAILED@ - The validation records failed to be added to the domain.
--
-- 'message', 'dnsRecordCreationState_message' - The message that describes the reason for the status code.
newDnsRecordCreationState ::
  DnsRecordCreationState
newDnsRecordCreationState :: DnsRecordCreationState
newDnsRecordCreationState =
  DnsRecordCreationState'
    { $sel:code:DnsRecordCreationState' :: Maybe DnsRecordCreationStateCode
code = forall a. Maybe a
Prelude.Nothing,
      $sel:message:DnsRecordCreationState' :: Maybe Text
message = forall a. Maybe a
Prelude.Nothing
    }

-- | The status code for the automated DNS record creation.
--
-- Following are the possible values:
--
-- -   @SUCCEEDED@ - The validation records were successfully added to the
--     domain.
--
-- -   @STARTED@ - The automatic DNS record creation has started.
--
-- -   @FAILED@ - The validation records failed to be added to the domain.
dnsRecordCreationState_code :: Lens.Lens' DnsRecordCreationState (Prelude.Maybe DnsRecordCreationStateCode)
dnsRecordCreationState_code :: Lens' DnsRecordCreationState (Maybe DnsRecordCreationStateCode)
dnsRecordCreationState_code = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DnsRecordCreationState' {Maybe DnsRecordCreationStateCode
code :: Maybe DnsRecordCreationStateCode
$sel:code:DnsRecordCreationState' :: DnsRecordCreationState -> Maybe DnsRecordCreationStateCode
code} -> Maybe DnsRecordCreationStateCode
code) (\s :: DnsRecordCreationState
s@DnsRecordCreationState' {} Maybe DnsRecordCreationStateCode
a -> DnsRecordCreationState
s {$sel:code:DnsRecordCreationState' :: Maybe DnsRecordCreationStateCode
code = Maybe DnsRecordCreationStateCode
a} :: DnsRecordCreationState)

-- | The message that describes the reason for the status code.
dnsRecordCreationState_message :: Lens.Lens' DnsRecordCreationState (Prelude.Maybe Prelude.Text)
dnsRecordCreationState_message :: Lens' DnsRecordCreationState (Maybe Text)
dnsRecordCreationState_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DnsRecordCreationState' {Maybe Text
message :: Maybe Text
$sel:message:DnsRecordCreationState' :: DnsRecordCreationState -> Maybe Text
message} -> Maybe Text
message) (\s :: DnsRecordCreationState
s@DnsRecordCreationState' {} Maybe Text
a -> DnsRecordCreationState
s {$sel:message:DnsRecordCreationState' :: Maybe Text
message = Maybe Text
a} :: DnsRecordCreationState)

instance Data.FromJSON DnsRecordCreationState where
  parseJSON :: Value -> Parser DnsRecordCreationState
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DnsRecordCreationState"
      ( \Object
x ->
          Maybe DnsRecordCreationStateCode
-> Maybe Text -> DnsRecordCreationState
DnsRecordCreationState'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"code")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"message")
      )

instance Prelude.Hashable DnsRecordCreationState where
  hashWithSalt :: Int -> DnsRecordCreationState -> Int
hashWithSalt Int
_salt DnsRecordCreationState' {Maybe Text
Maybe DnsRecordCreationStateCode
message :: Maybe Text
code :: Maybe DnsRecordCreationStateCode
$sel:message:DnsRecordCreationState' :: DnsRecordCreationState -> Maybe Text
$sel:code:DnsRecordCreationState' :: DnsRecordCreationState -> Maybe DnsRecordCreationStateCode
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DnsRecordCreationStateCode
code
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
message

instance Prelude.NFData DnsRecordCreationState where
  rnf :: DnsRecordCreationState -> ()
rnf DnsRecordCreationState' {Maybe Text
Maybe DnsRecordCreationStateCode
message :: Maybe Text
code :: Maybe DnsRecordCreationStateCode
$sel:message:DnsRecordCreationState' :: DnsRecordCreationState -> Maybe Text
$sel:code:DnsRecordCreationState' :: DnsRecordCreationState -> Maybe DnsRecordCreationStateCode
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DnsRecordCreationStateCode
code seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
message