{-# 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.ClusterParameterStatus
-- 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.ClusterParameterStatus 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

-- | Describes the status of a parameter group.
--
-- /See:/ 'newClusterParameterStatus' smart constructor.
data ClusterParameterStatus = ClusterParameterStatus'
  { -- | The error that prevented the parameter from being applied to the
    -- database.
    ClusterParameterStatus -> Maybe Text
parameterApplyErrorDescription :: Prelude.Maybe Prelude.Text,
    -- | The status of the parameter that indicates whether the parameter is in
    -- sync with the database, waiting for a cluster reboot, or encountered an
    -- error when being applied.
    --
    -- The following are possible statuses and descriptions.
    --
    -- -   @in-sync@: The parameter value is in sync with the database.
    --
    -- -   @pending-reboot@: The parameter value will be applied after the
    --     cluster reboots.
    --
    -- -   @applying@: The parameter value is being applied to the database.
    --
    -- -   @invalid-parameter@: Cannot apply the parameter value because it has
    --     an invalid value or syntax.
    --
    -- -   @apply-deferred@: The parameter contains static property changes.
    --     The changes are deferred until the cluster reboots.
    --
    -- -   @apply-error@: Cannot connect to the cluster. The parameter change
    --     will be applied after the cluster reboots.
    --
    -- -   @unknown-error@: Cannot apply the parameter change right now. The
    --     change will be applied after the cluster reboots.
    ClusterParameterStatus -> Maybe Text
parameterApplyStatus :: Prelude.Maybe Prelude.Text,
    -- | The name of the parameter.
    ClusterParameterStatus -> Maybe Text
parameterName :: Prelude.Maybe Prelude.Text
  }
  deriving (ClusterParameterStatus -> ClusterParameterStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClusterParameterStatus -> ClusterParameterStatus -> Bool
$c/= :: ClusterParameterStatus -> ClusterParameterStatus -> Bool
== :: ClusterParameterStatus -> ClusterParameterStatus -> Bool
$c== :: ClusterParameterStatus -> ClusterParameterStatus -> Bool
Prelude.Eq, ReadPrec [ClusterParameterStatus]
ReadPrec ClusterParameterStatus
Int -> ReadS ClusterParameterStatus
ReadS [ClusterParameterStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClusterParameterStatus]
$creadListPrec :: ReadPrec [ClusterParameterStatus]
readPrec :: ReadPrec ClusterParameterStatus
$creadPrec :: ReadPrec ClusterParameterStatus
readList :: ReadS [ClusterParameterStatus]
$creadList :: ReadS [ClusterParameterStatus]
readsPrec :: Int -> ReadS ClusterParameterStatus
$creadsPrec :: Int -> ReadS ClusterParameterStatus
Prelude.Read, Int -> ClusterParameterStatus -> ShowS
[ClusterParameterStatus] -> ShowS
ClusterParameterStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClusterParameterStatus] -> ShowS
$cshowList :: [ClusterParameterStatus] -> ShowS
show :: ClusterParameterStatus -> String
$cshow :: ClusterParameterStatus -> String
showsPrec :: Int -> ClusterParameterStatus -> ShowS
$cshowsPrec :: Int -> ClusterParameterStatus -> ShowS
Prelude.Show, forall x. Rep ClusterParameterStatus x -> ClusterParameterStatus
forall x. ClusterParameterStatus -> Rep ClusterParameterStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClusterParameterStatus x -> ClusterParameterStatus
$cfrom :: forall x. ClusterParameterStatus -> Rep ClusterParameterStatus x
Prelude.Generic)

-- |
-- Create a value of 'ClusterParameterStatus' 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:
--
-- 'parameterApplyErrorDescription', 'clusterParameterStatus_parameterApplyErrorDescription' - The error that prevented the parameter from being applied to the
-- database.
--
-- 'parameterApplyStatus', 'clusterParameterStatus_parameterApplyStatus' - The status of the parameter that indicates whether the parameter is in
-- sync with the database, waiting for a cluster reboot, or encountered an
-- error when being applied.
--
-- The following are possible statuses and descriptions.
--
-- -   @in-sync@: The parameter value is in sync with the database.
--
-- -   @pending-reboot@: The parameter value will be applied after the
--     cluster reboots.
--
-- -   @applying@: The parameter value is being applied to the database.
--
-- -   @invalid-parameter@: Cannot apply the parameter value because it has
--     an invalid value or syntax.
--
-- -   @apply-deferred@: The parameter contains static property changes.
--     The changes are deferred until the cluster reboots.
--
-- -   @apply-error@: Cannot connect to the cluster. The parameter change
--     will be applied after the cluster reboots.
--
-- -   @unknown-error@: Cannot apply the parameter change right now. The
--     change will be applied after the cluster reboots.
--
-- 'parameterName', 'clusterParameterStatus_parameterName' - The name of the parameter.
newClusterParameterStatus ::
  ClusterParameterStatus
newClusterParameterStatus :: ClusterParameterStatus
newClusterParameterStatus =
  ClusterParameterStatus'
    { $sel:parameterApplyErrorDescription:ClusterParameterStatus' :: Maybe Text
parameterApplyErrorDescription =
        forall a. Maybe a
Prelude.Nothing,
      $sel:parameterApplyStatus:ClusterParameterStatus' :: Maybe Text
parameterApplyStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:parameterName:ClusterParameterStatus' :: Maybe Text
parameterName = forall a. Maybe a
Prelude.Nothing
    }

-- | The error that prevented the parameter from being applied to the
-- database.
clusterParameterStatus_parameterApplyErrorDescription :: Lens.Lens' ClusterParameterStatus (Prelude.Maybe Prelude.Text)
clusterParameterStatus_parameterApplyErrorDescription :: Lens' ClusterParameterStatus (Maybe Text)
clusterParameterStatus_parameterApplyErrorDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterParameterStatus' {Maybe Text
parameterApplyErrorDescription :: Maybe Text
$sel:parameterApplyErrorDescription:ClusterParameterStatus' :: ClusterParameterStatus -> Maybe Text
parameterApplyErrorDescription} -> Maybe Text
parameterApplyErrorDescription) (\s :: ClusterParameterStatus
s@ClusterParameterStatus' {} Maybe Text
a -> ClusterParameterStatus
s {$sel:parameterApplyErrorDescription:ClusterParameterStatus' :: Maybe Text
parameterApplyErrorDescription = Maybe Text
a} :: ClusterParameterStatus)

-- | The status of the parameter that indicates whether the parameter is in
-- sync with the database, waiting for a cluster reboot, or encountered an
-- error when being applied.
--
-- The following are possible statuses and descriptions.
--
-- -   @in-sync@: The parameter value is in sync with the database.
--
-- -   @pending-reboot@: The parameter value will be applied after the
--     cluster reboots.
--
-- -   @applying@: The parameter value is being applied to the database.
--
-- -   @invalid-parameter@: Cannot apply the parameter value because it has
--     an invalid value or syntax.
--
-- -   @apply-deferred@: The parameter contains static property changes.
--     The changes are deferred until the cluster reboots.
--
-- -   @apply-error@: Cannot connect to the cluster. The parameter change
--     will be applied after the cluster reboots.
--
-- -   @unknown-error@: Cannot apply the parameter change right now. The
--     change will be applied after the cluster reboots.
clusterParameterStatus_parameterApplyStatus :: Lens.Lens' ClusterParameterStatus (Prelude.Maybe Prelude.Text)
clusterParameterStatus_parameterApplyStatus :: Lens' ClusterParameterStatus (Maybe Text)
clusterParameterStatus_parameterApplyStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterParameterStatus' {Maybe Text
parameterApplyStatus :: Maybe Text
$sel:parameterApplyStatus:ClusterParameterStatus' :: ClusterParameterStatus -> Maybe Text
parameterApplyStatus} -> Maybe Text
parameterApplyStatus) (\s :: ClusterParameterStatus
s@ClusterParameterStatus' {} Maybe Text
a -> ClusterParameterStatus
s {$sel:parameterApplyStatus:ClusterParameterStatus' :: Maybe Text
parameterApplyStatus = Maybe Text
a} :: ClusterParameterStatus)

-- | The name of the parameter.
clusterParameterStatus_parameterName :: Lens.Lens' ClusterParameterStatus (Prelude.Maybe Prelude.Text)
clusterParameterStatus_parameterName :: Lens' ClusterParameterStatus (Maybe Text)
clusterParameterStatus_parameterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterParameterStatus' {Maybe Text
parameterName :: Maybe Text
$sel:parameterName:ClusterParameterStatus' :: ClusterParameterStatus -> Maybe Text
parameterName} -> Maybe Text
parameterName) (\s :: ClusterParameterStatus
s@ClusterParameterStatus' {} Maybe Text
a -> ClusterParameterStatus
s {$sel:parameterName:ClusterParameterStatus' :: Maybe Text
parameterName = Maybe Text
a} :: ClusterParameterStatus)

instance Data.FromXML ClusterParameterStatus where
  parseXML :: [Node] -> Either String ClusterParameterStatus
parseXML [Node]
x =
    Maybe Text -> Maybe Text -> Maybe Text -> ClusterParameterStatus
ClusterParameterStatus'
      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
"ParameterApplyErrorDescription")
      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
"ParameterApplyStatus")
      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
"ParameterName")

instance Prelude.Hashable ClusterParameterStatus where
  hashWithSalt :: Int -> ClusterParameterStatus -> Int
hashWithSalt Int
_salt ClusterParameterStatus' {Maybe Text
parameterName :: Maybe Text
parameterApplyStatus :: Maybe Text
parameterApplyErrorDescription :: Maybe Text
$sel:parameterName:ClusterParameterStatus' :: ClusterParameterStatus -> Maybe Text
$sel:parameterApplyStatus:ClusterParameterStatus' :: ClusterParameterStatus -> Maybe Text
$sel:parameterApplyErrorDescription:ClusterParameterStatus' :: ClusterParameterStatus -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parameterApplyErrorDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parameterApplyStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parameterName

instance Prelude.NFData ClusterParameterStatus where
  rnf :: ClusterParameterStatus -> ()
rnf ClusterParameterStatus' {Maybe Text
parameterName :: Maybe Text
parameterApplyStatus :: Maybe Text
parameterApplyErrorDescription :: Maybe Text
$sel:parameterName:ClusterParameterStatus' :: ClusterParameterStatus -> Maybe Text
$sel:parameterApplyStatus:ClusterParameterStatus' :: ClusterParameterStatus -> Maybe Text
$sel:parameterApplyErrorDescription:ClusterParameterStatus' :: ClusterParameterStatus -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parameterApplyErrorDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parameterApplyStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parameterName