{-# 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.RDS.Types.OptionGroupOption
-- 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.RDS.Types.OptionGroupOption 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.RDS.Types.OptionGroupOptionSetting
import Amazonka.RDS.Types.OptionVersion

-- | Available option.
--
-- /See:/ 'newOptionGroupOption' smart constructor.
data OptionGroupOption = OptionGroupOption'
  { -- | Specifies whether the option can be copied across Amazon Web Services
    -- accounts.
    OptionGroupOption -> Maybe Bool
copyableCrossAccount :: Prelude.Maybe Prelude.Bool,
    -- | If the option requires a port, specifies the default port for the
    -- option.
    OptionGroupOption -> Maybe Int
defaultPort :: Prelude.Maybe Prelude.Int,
    -- | The description of the option.
    OptionGroupOption -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The name of the engine that this option can be applied to.
    OptionGroupOption -> Maybe Text
engineName :: Prelude.Maybe Prelude.Text,
    -- | Indicates the major engine version that the option is available for.
    OptionGroupOption -> Maybe Text
majorEngineVersion :: Prelude.Maybe Prelude.Text,
    -- | The minimum required engine version for the option to be applied.
    OptionGroupOption -> Maybe Text
minimumRequiredMinorEngineVersion :: Prelude.Maybe Prelude.Text,
    -- | The name of the option.
    OptionGroupOption -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The option settings that are available (and the default value) for each
    -- option in an option group.
    OptionGroupOption -> Maybe [OptionGroupOptionSetting]
optionGroupOptionSettings :: Prelude.Maybe [OptionGroupOptionSetting],
    -- | The versions that are available for the option.
    OptionGroupOption -> Maybe [OptionVersion]
optionGroupOptionVersions :: Prelude.Maybe [OptionVersion],
    -- | The options that conflict with this option.
    OptionGroupOption -> Maybe [Text]
optionsConflictsWith :: Prelude.Maybe [Prelude.Text],
    -- | The options that are prerequisites for this option.
    OptionGroupOption -> Maybe [Text]
optionsDependedOn :: Prelude.Maybe [Prelude.Text],
    -- | Permanent options can never be removed from an option group. An option
    -- group containing a permanent option can\'t be removed from a DB
    -- instance.
    OptionGroupOption -> Maybe Bool
permanent :: Prelude.Maybe Prelude.Bool,
    -- | Persistent options can\'t be removed from an option group while DB
    -- instances are associated with the option group. If you disassociate all
    -- DB instances from the option group, your can remove the persistent
    -- option from the option group.
    OptionGroupOption -> Maybe Bool
persistent :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether the option requires a port.
    OptionGroupOption -> Maybe Bool
portRequired :: Prelude.Maybe Prelude.Bool,
    -- | If true, you must enable the Auto Minor Version Upgrade setting for your
    -- DB instance before you can use this option. You can enable Auto Minor
    -- Version Upgrade when you first create your DB instance, or by modifying
    -- your DB instance later.
    OptionGroupOption -> Maybe Bool
requiresAutoMinorEngineVersionUpgrade :: Prelude.Maybe Prelude.Bool,
    -- | If true, you can change the option to an earlier version of the option.
    -- This only applies to options that have different versions available.
    OptionGroupOption -> Maybe Bool
supportsOptionVersionDowngrade :: Prelude.Maybe Prelude.Bool,
    -- | If true, you can only use this option with a DB instance that is in a
    -- VPC.
    OptionGroupOption -> Maybe Bool
vpcOnly :: Prelude.Maybe Prelude.Bool
  }
  deriving (OptionGroupOption -> OptionGroupOption -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionGroupOption -> OptionGroupOption -> Bool
$c/= :: OptionGroupOption -> OptionGroupOption -> Bool
== :: OptionGroupOption -> OptionGroupOption -> Bool
$c== :: OptionGroupOption -> OptionGroupOption -> Bool
Prelude.Eq, ReadPrec [OptionGroupOption]
ReadPrec OptionGroupOption
Int -> ReadS OptionGroupOption
ReadS [OptionGroupOption]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OptionGroupOption]
$creadListPrec :: ReadPrec [OptionGroupOption]
readPrec :: ReadPrec OptionGroupOption
$creadPrec :: ReadPrec OptionGroupOption
readList :: ReadS [OptionGroupOption]
$creadList :: ReadS [OptionGroupOption]
readsPrec :: Int -> ReadS OptionGroupOption
$creadsPrec :: Int -> ReadS OptionGroupOption
Prelude.Read, Int -> OptionGroupOption -> ShowS
[OptionGroupOption] -> ShowS
OptionGroupOption -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionGroupOption] -> ShowS
$cshowList :: [OptionGroupOption] -> ShowS
show :: OptionGroupOption -> String
$cshow :: OptionGroupOption -> String
showsPrec :: Int -> OptionGroupOption -> ShowS
$cshowsPrec :: Int -> OptionGroupOption -> ShowS
Prelude.Show, forall x. Rep OptionGroupOption x -> OptionGroupOption
forall x. OptionGroupOption -> Rep OptionGroupOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OptionGroupOption x -> OptionGroupOption
$cfrom :: forall x. OptionGroupOption -> Rep OptionGroupOption x
Prelude.Generic)

-- |
-- Create a value of 'OptionGroupOption' 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:
--
-- 'copyableCrossAccount', 'optionGroupOption_copyableCrossAccount' - Specifies whether the option can be copied across Amazon Web Services
-- accounts.
--
-- 'defaultPort', 'optionGroupOption_defaultPort' - If the option requires a port, specifies the default port for the
-- option.
--
-- 'description', 'optionGroupOption_description' - The description of the option.
--
-- 'engineName', 'optionGroupOption_engineName' - The name of the engine that this option can be applied to.
--
-- 'majorEngineVersion', 'optionGroupOption_majorEngineVersion' - Indicates the major engine version that the option is available for.
--
-- 'minimumRequiredMinorEngineVersion', 'optionGroupOption_minimumRequiredMinorEngineVersion' - The minimum required engine version for the option to be applied.
--
-- 'name', 'optionGroupOption_name' - The name of the option.
--
-- 'optionGroupOptionSettings', 'optionGroupOption_optionGroupOptionSettings' - The option settings that are available (and the default value) for each
-- option in an option group.
--
-- 'optionGroupOptionVersions', 'optionGroupOption_optionGroupOptionVersions' - The versions that are available for the option.
--
-- 'optionsConflictsWith', 'optionGroupOption_optionsConflictsWith' - The options that conflict with this option.
--
-- 'optionsDependedOn', 'optionGroupOption_optionsDependedOn' - The options that are prerequisites for this option.
--
-- 'permanent', 'optionGroupOption_permanent' - Permanent options can never be removed from an option group. An option
-- group containing a permanent option can\'t be removed from a DB
-- instance.
--
-- 'persistent', 'optionGroupOption_persistent' - Persistent options can\'t be removed from an option group while DB
-- instances are associated with the option group. If you disassociate all
-- DB instances from the option group, your can remove the persistent
-- option from the option group.
--
-- 'portRequired', 'optionGroupOption_portRequired' - Specifies whether the option requires a port.
--
-- 'requiresAutoMinorEngineVersionUpgrade', 'optionGroupOption_requiresAutoMinorEngineVersionUpgrade' - If true, you must enable the Auto Minor Version Upgrade setting for your
-- DB instance before you can use this option. You can enable Auto Minor
-- Version Upgrade when you first create your DB instance, or by modifying
-- your DB instance later.
--
-- 'supportsOptionVersionDowngrade', 'optionGroupOption_supportsOptionVersionDowngrade' - If true, you can change the option to an earlier version of the option.
-- This only applies to options that have different versions available.
--
-- 'vpcOnly', 'optionGroupOption_vpcOnly' - If true, you can only use this option with a DB instance that is in a
-- VPC.
newOptionGroupOption ::
  OptionGroupOption
newOptionGroupOption :: OptionGroupOption
newOptionGroupOption =
  OptionGroupOption'
    { $sel:copyableCrossAccount:OptionGroupOption' :: Maybe Bool
copyableCrossAccount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:defaultPort:OptionGroupOption' :: Maybe Int
defaultPort = forall a. Maybe a
Prelude.Nothing,
      $sel:description:OptionGroupOption' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:engineName:OptionGroupOption' :: Maybe Text
engineName = forall a. Maybe a
Prelude.Nothing,
      $sel:majorEngineVersion:OptionGroupOption' :: Maybe Text
majorEngineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:minimumRequiredMinorEngineVersion:OptionGroupOption' :: Maybe Text
minimumRequiredMinorEngineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:name:OptionGroupOption' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:optionGroupOptionSettings:OptionGroupOption' :: Maybe [OptionGroupOptionSetting]
optionGroupOptionSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:optionGroupOptionVersions:OptionGroupOption' :: Maybe [OptionVersion]
optionGroupOptionVersions = forall a. Maybe a
Prelude.Nothing,
      $sel:optionsConflictsWith:OptionGroupOption' :: Maybe [Text]
optionsConflictsWith = forall a. Maybe a
Prelude.Nothing,
      $sel:optionsDependedOn:OptionGroupOption' :: Maybe [Text]
optionsDependedOn = forall a. Maybe a
Prelude.Nothing,
      $sel:permanent:OptionGroupOption' :: Maybe Bool
permanent = forall a. Maybe a
Prelude.Nothing,
      $sel:persistent:OptionGroupOption' :: Maybe Bool
persistent = forall a. Maybe a
Prelude.Nothing,
      $sel:portRequired:OptionGroupOption' :: Maybe Bool
portRequired = forall a. Maybe a
Prelude.Nothing,
      $sel:requiresAutoMinorEngineVersionUpgrade:OptionGroupOption' :: Maybe Bool
requiresAutoMinorEngineVersionUpgrade =
        forall a. Maybe a
Prelude.Nothing,
      $sel:supportsOptionVersionDowngrade:OptionGroupOption' :: Maybe Bool
supportsOptionVersionDowngrade = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcOnly:OptionGroupOption' :: Maybe Bool
vpcOnly = forall a. Maybe a
Prelude.Nothing
    }

-- | Specifies whether the option can be copied across Amazon Web Services
-- accounts.
optionGroupOption_copyableCrossAccount :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Bool)
optionGroupOption_copyableCrossAccount :: Lens' OptionGroupOption (Maybe Bool)
optionGroupOption_copyableCrossAccount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Bool
copyableCrossAccount :: Maybe Bool
$sel:copyableCrossAccount:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
copyableCrossAccount} -> Maybe Bool
copyableCrossAccount) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Bool
a -> OptionGroupOption
s {$sel:copyableCrossAccount:OptionGroupOption' :: Maybe Bool
copyableCrossAccount = Maybe Bool
a} :: OptionGroupOption)

-- | If the option requires a port, specifies the default port for the
-- option.
optionGroupOption_defaultPort :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Int)
optionGroupOption_defaultPort :: Lens' OptionGroupOption (Maybe Int)
optionGroupOption_defaultPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Int
defaultPort :: Maybe Int
$sel:defaultPort:OptionGroupOption' :: OptionGroupOption -> Maybe Int
defaultPort} -> Maybe Int
defaultPort) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Int
a -> OptionGroupOption
s {$sel:defaultPort:OptionGroupOption' :: Maybe Int
defaultPort = Maybe Int
a} :: OptionGroupOption)

-- | The description of the option.
optionGroupOption_description :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Text)
optionGroupOption_description :: Lens' OptionGroupOption (Maybe Text)
optionGroupOption_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Text
description :: Maybe Text
$sel:description:OptionGroupOption' :: OptionGroupOption -> Maybe Text
description} -> Maybe Text
description) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Text
a -> OptionGroupOption
s {$sel:description:OptionGroupOption' :: Maybe Text
description = Maybe Text
a} :: OptionGroupOption)

-- | The name of the engine that this option can be applied to.
optionGroupOption_engineName :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Text)
optionGroupOption_engineName :: Lens' OptionGroupOption (Maybe Text)
optionGroupOption_engineName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Text
engineName :: Maybe Text
$sel:engineName:OptionGroupOption' :: OptionGroupOption -> Maybe Text
engineName} -> Maybe Text
engineName) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Text
a -> OptionGroupOption
s {$sel:engineName:OptionGroupOption' :: Maybe Text
engineName = Maybe Text
a} :: OptionGroupOption)

-- | Indicates the major engine version that the option is available for.
optionGroupOption_majorEngineVersion :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Text)
optionGroupOption_majorEngineVersion :: Lens' OptionGroupOption (Maybe Text)
optionGroupOption_majorEngineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Text
majorEngineVersion :: Maybe Text
$sel:majorEngineVersion:OptionGroupOption' :: OptionGroupOption -> Maybe Text
majorEngineVersion} -> Maybe Text
majorEngineVersion) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Text
a -> OptionGroupOption
s {$sel:majorEngineVersion:OptionGroupOption' :: Maybe Text
majorEngineVersion = Maybe Text
a} :: OptionGroupOption)

-- | The minimum required engine version for the option to be applied.
optionGroupOption_minimumRequiredMinorEngineVersion :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Text)
optionGroupOption_minimumRequiredMinorEngineVersion :: Lens' OptionGroupOption (Maybe Text)
optionGroupOption_minimumRequiredMinorEngineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Text
minimumRequiredMinorEngineVersion :: Maybe Text
$sel:minimumRequiredMinorEngineVersion:OptionGroupOption' :: OptionGroupOption -> Maybe Text
minimumRequiredMinorEngineVersion} -> Maybe Text
minimumRequiredMinorEngineVersion) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Text
a -> OptionGroupOption
s {$sel:minimumRequiredMinorEngineVersion:OptionGroupOption' :: Maybe Text
minimumRequiredMinorEngineVersion = Maybe Text
a} :: OptionGroupOption)

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

-- | The option settings that are available (and the default value) for each
-- option in an option group.
optionGroupOption_optionGroupOptionSettings :: Lens.Lens' OptionGroupOption (Prelude.Maybe [OptionGroupOptionSetting])
optionGroupOption_optionGroupOptionSettings :: Lens' OptionGroupOption (Maybe [OptionGroupOptionSetting])
optionGroupOption_optionGroupOptionSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe [OptionGroupOptionSetting]
optionGroupOptionSettings :: Maybe [OptionGroupOptionSetting]
$sel:optionGroupOptionSettings:OptionGroupOption' :: OptionGroupOption -> Maybe [OptionGroupOptionSetting]
optionGroupOptionSettings} -> Maybe [OptionGroupOptionSetting]
optionGroupOptionSettings) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe [OptionGroupOptionSetting]
a -> OptionGroupOption
s {$sel:optionGroupOptionSettings:OptionGroupOption' :: Maybe [OptionGroupOptionSetting]
optionGroupOptionSettings = Maybe [OptionGroupOptionSetting]
a} :: OptionGroupOption) 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

-- | The versions that are available for the option.
optionGroupOption_optionGroupOptionVersions :: Lens.Lens' OptionGroupOption (Prelude.Maybe [OptionVersion])
optionGroupOption_optionGroupOptionVersions :: Lens' OptionGroupOption (Maybe [OptionVersion])
optionGroupOption_optionGroupOptionVersions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe [OptionVersion]
optionGroupOptionVersions :: Maybe [OptionVersion]
$sel:optionGroupOptionVersions:OptionGroupOption' :: OptionGroupOption -> Maybe [OptionVersion]
optionGroupOptionVersions} -> Maybe [OptionVersion]
optionGroupOptionVersions) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe [OptionVersion]
a -> OptionGroupOption
s {$sel:optionGroupOptionVersions:OptionGroupOption' :: Maybe [OptionVersion]
optionGroupOptionVersions = Maybe [OptionVersion]
a} :: OptionGroupOption) 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

-- | The options that conflict with this option.
optionGroupOption_optionsConflictsWith :: Lens.Lens' OptionGroupOption (Prelude.Maybe [Prelude.Text])
optionGroupOption_optionsConflictsWith :: Lens' OptionGroupOption (Maybe [Text])
optionGroupOption_optionsConflictsWith = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe [Text]
optionsConflictsWith :: Maybe [Text]
$sel:optionsConflictsWith:OptionGroupOption' :: OptionGroupOption -> Maybe [Text]
optionsConflictsWith} -> Maybe [Text]
optionsConflictsWith) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe [Text]
a -> OptionGroupOption
s {$sel:optionsConflictsWith:OptionGroupOption' :: Maybe [Text]
optionsConflictsWith = Maybe [Text]
a} :: OptionGroupOption) 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

-- | The options that are prerequisites for this option.
optionGroupOption_optionsDependedOn :: Lens.Lens' OptionGroupOption (Prelude.Maybe [Prelude.Text])
optionGroupOption_optionsDependedOn :: Lens' OptionGroupOption (Maybe [Text])
optionGroupOption_optionsDependedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe [Text]
optionsDependedOn :: Maybe [Text]
$sel:optionsDependedOn:OptionGroupOption' :: OptionGroupOption -> Maybe [Text]
optionsDependedOn} -> Maybe [Text]
optionsDependedOn) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe [Text]
a -> OptionGroupOption
s {$sel:optionsDependedOn:OptionGroupOption' :: Maybe [Text]
optionsDependedOn = Maybe [Text]
a} :: OptionGroupOption) 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

-- | Permanent options can never be removed from an option group. An option
-- group containing a permanent option can\'t be removed from a DB
-- instance.
optionGroupOption_permanent :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Bool)
optionGroupOption_permanent :: Lens' OptionGroupOption (Maybe Bool)
optionGroupOption_permanent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Bool
permanent :: Maybe Bool
$sel:permanent:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
permanent} -> Maybe Bool
permanent) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Bool
a -> OptionGroupOption
s {$sel:permanent:OptionGroupOption' :: Maybe Bool
permanent = Maybe Bool
a} :: OptionGroupOption)

-- | Persistent options can\'t be removed from an option group while DB
-- instances are associated with the option group. If you disassociate all
-- DB instances from the option group, your can remove the persistent
-- option from the option group.
optionGroupOption_persistent :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Bool)
optionGroupOption_persistent :: Lens' OptionGroupOption (Maybe Bool)
optionGroupOption_persistent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Bool
persistent :: Maybe Bool
$sel:persistent:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
persistent} -> Maybe Bool
persistent) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Bool
a -> OptionGroupOption
s {$sel:persistent:OptionGroupOption' :: Maybe Bool
persistent = Maybe Bool
a} :: OptionGroupOption)

-- | Specifies whether the option requires a port.
optionGroupOption_portRequired :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Bool)
optionGroupOption_portRequired :: Lens' OptionGroupOption (Maybe Bool)
optionGroupOption_portRequired = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Bool
portRequired :: Maybe Bool
$sel:portRequired:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
portRequired} -> Maybe Bool
portRequired) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Bool
a -> OptionGroupOption
s {$sel:portRequired:OptionGroupOption' :: Maybe Bool
portRequired = Maybe Bool
a} :: OptionGroupOption)

-- | If true, you must enable the Auto Minor Version Upgrade setting for your
-- DB instance before you can use this option. You can enable Auto Minor
-- Version Upgrade when you first create your DB instance, or by modifying
-- your DB instance later.
optionGroupOption_requiresAutoMinorEngineVersionUpgrade :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Bool)
optionGroupOption_requiresAutoMinorEngineVersionUpgrade :: Lens' OptionGroupOption (Maybe Bool)
optionGroupOption_requiresAutoMinorEngineVersionUpgrade = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Bool
requiresAutoMinorEngineVersionUpgrade :: Maybe Bool
$sel:requiresAutoMinorEngineVersionUpgrade:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
requiresAutoMinorEngineVersionUpgrade} -> Maybe Bool
requiresAutoMinorEngineVersionUpgrade) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Bool
a -> OptionGroupOption
s {$sel:requiresAutoMinorEngineVersionUpgrade:OptionGroupOption' :: Maybe Bool
requiresAutoMinorEngineVersionUpgrade = Maybe Bool
a} :: OptionGroupOption)

-- | If true, you can change the option to an earlier version of the option.
-- This only applies to options that have different versions available.
optionGroupOption_supportsOptionVersionDowngrade :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Bool)
optionGroupOption_supportsOptionVersionDowngrade :: Lens' OptionGroupOption (Maybe Bool)
optionGroupOption_supportsOptionVersionDowngrade = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Bool
supportsOptionVersionDowngrade :: Maybe Bool
$sel:supportsOptionVersionDowngrade:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
supportsOptionVersionDowngrade} -> Maybe Bool
supportsOptionVersionDowngrade) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Bool
a -> OptionGroupOption
s {$sel:supportsOptionVersionDowngrade:OptionGroupOption' :: Maybe Bool
supportsOptionVersionDowngrade = Maybe Bool
a} :: OptionGroupOption)

-- | If true, you can only use this option with a DB instance that is in a
-- VPC.
optionGroupOption_vpcOnly :: Lens.Lens' OptionGroupOption (Prelude.Maybe Prelude.Bool)
optionGroupOption_vpcOnly :: Lens' OptionGroupOption (Maybe Bool)
optionGroupOption_vpcOnly = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OptionGroupOption' {Maybe Bool
vpcOnly :: Maybe Bool
$sel:vpcOnly:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
vpcOnly} -> Maybe Bool
vpcOnly) (\s :: OptionGroupOption
s@OptionGroupOption' {} Maybe Bool
a -> OptionGroupOption
s {$sel:vpcOnly:OptionGroupOption' :: Maybe Bool
vpcOnly = Maybe Bool
a} :: OptionGroupOption)

instance Data.FromXML OptionGroupOption where
  parseXML :: [Node] -> Either String OptionGroupOption
parseXML [Node]
x =
    Maybe Bool
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [OptionGroupOptionSetting]
-> Maybe [OptionVersion]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> OptionGroupOption
OptionGroupOption'
      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
"CopyableCrossAccount")
      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
"DefaultPort")
      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
"Description")
      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
"EngineName")
      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
"MajorEngineVersion")
      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
"MinimumRequiredMinorEngineVersion")
      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
"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 (Maybe a)
Data..@? Text
"OptionGroupOptionSettings"
                      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
"OptionGroupOptionSetting")
                  )
      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
"OptionGroupOptionVersions"
                      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
"OptionVersion")
                  )
      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
"OptionsConflictsWith"
                      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
"OptionConflictName")
                  )
      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
"OptionsDependedOn"
                      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
"OptionName")
                  )
      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
"Permanent")
      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
"Persistent")
      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
"PortRequired")
      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
"RequiresAutoMinorEngineVersionUpgrade")
      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
"SupportsOptionVersionDowngrade")
      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
"VpcOnly")

instance Prelude.Hashable OptionGroupOption where
  hashWithSalt :: Int -> OptionGroupOption -> Int
hashWithSalt Int
_salt OptionGroupOption' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [OptionGroupOptionSetting]
Maybe [OptionVersion]
Maybe Text
vpcOnly :: Maybe Bool
supportsOptionVersionDowngrade :: Maybe Bool
requiresAutoMinorEngineVersionUpgrade :: Maybe Bool
portRequired :: Maybe Bool
persistent :: Maybe Bool
permanent :: Maybe Bool
optionsDependedOn :: Maybe [Text]
optionsConflictsWith :: Maybe [Text]
optionGroupOptionVersions :: Maybe [OptionVersion]
optionGroupOptionSettings :: Maybe [OptionGroupOptionSetting]
name :: Maybe Text
minimumRequiredMinorEngineVersion :: Maybe Text
majorEngineVersion :: Maybe Text
engineName :: Maybe Text
description :: Maybe Text
defaultPort :: Maybe Int
copyableCrossAccount :: Maybe Bool
$sel:vpcOnly:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:supportsOptionVersionDowngrade:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:requiresAutoMinorEngineVersionUpgrade:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:portRequired:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:persistent:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:permanent:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:optionsDependedOn:OptionGroupOption' :: OptionGroupOption -> Maybe [Text]
$sel:optionsConflictsWith:OptionGroupOption' :: OptionGroupOption -> Maybe [Text]
$sel:optionGroupOptionVersions:OptionGroupOption' :: OptionGroupOption -> Maybe [OptionVersion]
$sel:optionGroupOptionSettings:OptionGroupOption' :: OptionGroupOption -> Maybe [OptionGroupOptionSetting]
$sel:name:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:minimumRequiredMinorEngineVersion:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:majorEngineVersion:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:engineName:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:description:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:defaultPort:OptionGroupOption' :: OptionGroupOption -> Maybe Int
$sel:copyableCrossAccount:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
copyableCrossAccount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
defaultPort
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engineName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
majorEngineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
minimumRequiredMinorEngineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [OptionGroupOptionSetting]
optionGroupOptionSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [OptionVersion]
optionGroupOptionVersions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
optionsConflictsWith
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
optionsDependedOn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
permanent
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
persistent
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
portRequired
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
requiresAutoMinorEngineVersionUpgrade
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
supportsOptionVersionDowngrade
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
vpcOnly

instance Prelude.NFData OptionGroupOption where
  rnf :: OptionGroupOption -> ()
rnf OptionGroupOption' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [OptionGroupOptionSetting]
Maybe [OptionVersion]
Maybe Text
vpcOnly :: Maybe Bool
supportsOptionVersionDowngrade :: Maybe Bool
requiresAutoMinorEngineVersionUpgrade :: Maybe Bool
portRequired :: Maybe Bool
persistent :: Maybe Bool
permanent :: Maybe Bool
optionsDependedOn :: Maybe [Text]
optionsConflictsWith :: Maybe [Text]
optionGroupOptionVersions :: Maybe [OptionVersion]
optionGroupOptionSettings :: Maybe [OptionGroupOptionSetting]
name :: Maybe Text
minimumRequiredMinorEngineVersion :: Maybe Text
majorEngineVersion :: Maybe Text
engineName :: Maybe Text
description :: Maybe Text
defaultPort :: Maybe Int
copyableCrossAccount :: Maybe Bool
$sel:vpcOnly:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:supportsOptionVersionDowngrade:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:requiresAutoMinorEngineVersionUpgrade:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:portRequired:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:persistent:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:permanent:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
$sel:optionsDependedOn:OptionGroupOption' :: OptionGroupOption -> Maybe [Text]
$sel:optionsConflictsWith:OptionGroupOption' :: OptionGroupOption -> Maybe [Text]
$sel:optionGroupOptionVersions:OptionGroupOption' :: OptionGroupOption -> Maybe [OptionVersion]
$sel:optionGroupOptionSettings:OptionGroupOption' :: OptionGroupOption -> Maybe [OptionGroupOptionSetting]
$sel:name:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:minimumRequiredMinorEngineVersion:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:majorEngineVersion:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:engineName:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:description:OptionGroupOption' :: OptionGroupOption -> Maybe Text
$sel:defaultPort:OptionGroupOption' :: OptionGroupOption -> Maybe Int
$sel:copyableCrossAccount:OptionGroupOption' :: OptionGroupOption -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
copyableCrossAccount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
defaultPort
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
engineName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
majorEngineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
minimumRequiredMinorEngineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OptionGroupOptionSetting]
optionGroupOptionSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OptionVersion]
optionGroupOptionVersions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
optionsConflictsWith
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
optionsDependedOn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
permanent
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
persistent
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
portRequired
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
requiresAutoMinorEngineVersionUpgrade
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
supportsOptionVersionDowngrade
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
vpcOnly