{-# 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.ValidStorageOptions
-- 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.ValidStorageOptions 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.DoubleRange
import Amazonka.RDS.Types.Range

-- | Information about valid modifications that you can make to your DB
-- instance. Contains the result of a successful call to the
-- @DescribeValidDBInstanceModifications@ action.
--
-- /See:/ 'newValidStorageOptions' smart constructor.
data ValidStorageOptions = ValidStorageOptions'
  { -- | The valid range of Provisioned IOPS to gibibytes of storage multiplier.
    -- For example, 3-10, which means that provisioned IOPS can be between 3
    -- and 10 times storage.
    ValidStorageOptions -> Maybe [DoubleRange]
iopsToStorageRatio :: Prelude.Maybe [DoubleRange],
    -- | The valid range of provisioned IOPS. For example, 1000-256,000.
    ValidStorageOptions -> Maybe [Range]
provisionedIops :: Prelude.Maybe [Range],
    -- | The valid range of provisioned storage throughput. For example,
    -- 500-4,000 mebibytes per second (MiBps).
    ValidStorageOptions -> Maybe [Range]
provisionedStorageThroughput :: Prelude.Maybe [Range],
    -- | The valid range of storage in gibibytes (GiB). For example, 100 to
    -- 16,384.
    ValidStorageOptions -> Maybe [Range]
storageSize :: Prelude.Maybe [Range],
    -- | The valid range of storage throughput to provisioned IOPS ratios. For
    -- example, 0-0.25.
    ValidStorageOptions -> Maybe [DoubleRange]
storageThroughputToIopsRatio :: Prelude.Maybe [DoubleRange],
    -- | The valid storage types for your DB instance. For example: gp2, gp3,
    -- io1.
    ValidStorageOptions -> Maybe Text
storageType :: Prelude.Maybe Prelude.Text,
    -- | Whether or not Amazon RDS can automatically scale storage for DB
    -- instances that use the new instance class.
    ValidStorageOptions -> Maybe Bool
supportsStorageAutoscaling :: Prelude.Maybe Prelude.Bool
  }
  deriving (ValidStorageOptions -> ValidStorageOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidStorageOptions -> ValidStorageOptions -> Bool
$c/= :: ValidStorageOptions -> ValidStorageOptions -> Bool
== :: ValidStorageOptions -> ValidStorageOptions -> Bool
$c== :: ValidStorageOptions -> ValidStorageOptions -> Bool
Prelude.Eq, ReadPrec [ValidStorageOptions]
ReadPrec ValidStorageOptions
Int -> ReadS ValidStorageOptions
ReadS [ValidStorageOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ValidStorageOptions]
$creadListPrec :: ReadPrec [ValidStorageOptions]
readPrec :: ReadPrec ValidStorageOptions
$creadPrec :: ReadPrec ValidStorageOptions
readList :: ReadS [ValidStorageOptions]
$creadList :: ReadS [ValidStorageOptions]
readsPrec :: Int -> ReadS ValidStorageOptions
$creadsPrec :: Int -> ReadS ValidStorageOptions
Prelude.Read, Int -> ValidStorageOptions -> ShowS
[ValidStorageOptions] -> ShowS
ValidStorageOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValidStorageOptions] -> ShowS
$cshowList :: [ValidStorageOptions] -> ShowS
show :: ValidStorageOptions -> String
$cshow :: ValidStorageOptions -> String
showsPrec :: Int -> ValidStorageOptions -> ShowS
$cshowsPrec :: Int -> ValidStorageOptions -> ShowS
Prelude.Show, forall x. Rep ValidStorageOptions x -> ValidStorageOptions
forall x. ValidStorageOptions -> Rep ValidStorageOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ValidStorageOptions x -> ValidStorageOptions
$cfrom :: forall x. ValidStorageOptions -> Rep ValidStorageOptions x
Prelude.Generic)

-- |
-- Create a value of 'ValidStorageOptions' 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:
--
-- 'iopsToStorageRatio', 'validStorageOptions_iopsToStorageRatio' - The valid range of Provisioned IOPS to gibibytes of storage multiplier.
-- For example, 3-10, which means that provisioned IOPS can be between 3
-- and 10 times storage.
--
-- 'provisionedIops', 'validStorageOptions_provisionedIops' - The valid range of provisioned IOPS. For example, 1000-256,000.
--
-- 'provisionedStorageThroughput', 'validStorageOptions_provisionedStorageThroughput' - The valid range of provisioned storage throughput. For example,
-- 500-4,000 mebibytes per second (MiBps).
--
-- 'storageSize', 'validStorageOptions_storageSize' - The valid range of storage in gibibytes (GiB). For example, 100 to
-- 16,384.
--
-- 'storageThroughputToIopsRatio', 'validStorageOptions_storageThroughputToIopsRatio' - The valid range of storage throughput to provisioned IOPS ratios. For
-- example, 0-0.25.
--
-- 'storageType', 'validStorageOptions_storageType' - The valid storage types for your DB instance. For example: gp2, gp3,
-- io1.
--
-- 'supportsStorageAutoscaling', 'validStorageOptions_supportsStorageAutoscaling' - Whether or not Amazon RDS can automatically scale storage for DB
-- instances that use the new instance class.
newValidStorageOptions ::
  ValidStorageOptions
newValidStorageOptions :: ValidStorageOptions
newValidStorageOptions =
  ValidStorageOptions'
    { $sel:iopsToStorageRatio:ValidStorageOptions' :: Maybe [DoubleRange]
iopsToStorageRatio =
        forall a. Maybe a
Prelude.Nothing,
      $sel:provisionedIops:ValidStorageOptions' :: Maybe [Range]
provisionedIops = forall a. Maybe a
Prelude.Nothing,
      $sel:provisionedStorageThroughput:ValidStorageOptions' :: Maybe [Range]
provisionedStorageThroughput = forall a. Maybe a
Prelude.Nothing,
      $sel:storageSize:ValidStorageOptions' :: Maybe [Range]
storageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:storageThroughputToIopsRatio:ValidStorageOptions' :: Maybe [DoubleRange]
storageThroughputToIopsRatio = forall a. Maybe a
Prelude.Nothing,
      $sel:storageType:ValidStorageOptions' :: Maybe Text
storageType = forall a. Maybe a
Prelude.Nothing,
      $sel:supportsStorageAutoscaling:ValidStorageOptions' :: Maybe Bool
supportsStorageAutoscaling = forall a. Maybe a
Prelude.Nothing
    }

-- | The valid range of Provisioned IOPS to gibibytes of storage multiplier.
-- For example, 3-10, which means that provisioned IOPS can be between 3
-- and 10 times storage.
validStorageOptions_iopsToStorageRatio :: Lens.Lens' ValidStorageOptions (Prelude.Maybe [DoubleRange])
validStorageOptions_iopsToStorageRatio :: Lens' ValidStorageOptions (Maybe [DoubleRange])
validStorageOptions_iopsToStorageRatio = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidStorageOptions' {Maybe [DoubleRange]
iopsToStorageRatio :: Maybe [DoubleRange]
$sel:iopsToStorageRatio:ValidStorageOptions' :: ValidStorageOptions -> Maybe [DoubleRange]
iopsToStorageRatio} -> Maybe [DoubleRange]
iopsToStorageRatio) (\s :: ValidStorageOptions
s@ValidStorageOptions' {} Maybe [DoubleRange]
a -> ValidStorageOptions
s {$sel:iopsToStorageRatio:ValidStorageOptions' :: Maybe [DoubleRange]
iopsToStorageRatio = Maybe [DoubleRange]
a} :: ValidStorageOptions) 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 valid range of provisioned IOPS. For example, 1000-256,000.
validStorageOptions_provisionedIops :: Lens.Lens' ValidStorageOptions (Prelude.Maybe [Range])
validStorageOptions_provisionedIops :: Lens' ValidStorageOptions (Maybe [Range])
validStorageOptions_provisionedIops = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidStorageOptions' {Maybe [Range]
provisionedIops :: Maybe [Range]
$sel:provisionedIops:ValidStorageOptions' :: ValidStorageOptions -> Maybe [Range]
provisionedIops} -> Maybe [Range]
provisionedIops) (\s :: ValidStorageOptions
s@ValidStorageOptions' {} Maybe [Range]
a -> ValidStorageOptions
s {$sel:provisionedIops:ValidStorageOptions' :: Maybe [Range]
provisionedIops = Maybe [Range]
a} :: ValidStorageOptions) 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 valid range of provisioned storage throughput. For example,
-- 500-4,000 mebibytes per second (MiBps).
validStorageOptions_provisionedStorageThroughput :: Lens.Lens' ValidStorageOptions (Prelude.Maybe [Range])
validStorageOptions_provisionedStorageThroughput :: Lens' ValidStorageOptions (Maybe [Range])
validStorageOptions_provisionedStorageThroughput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidStorageOptions' {Maybe [Range]
provisionedStorageThroughput :: Maybe [Range]
$sel:provisionedStorageThroughput:ValidStorageOptions' :: ValidStorageOptions -> Maybe [Range]
provisionedStorageThroughput} -> Maybe [Range]
provisionedStorageThroughput) (\s :: ValidStorageOptions
s@ValidStorageOptions' {} Maybe [Range]
a -> ValidStorageOptions
s {$sel:provisionedStorageThroughput:ValidStorageOptions' :: Maybe [Range]
provisionedStorageThroughput = Maybe [Range]
a} :: ValidStorageOptions) 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 valid range of storage in gibibytes (GiB). For example, 100 to
-- 16,384.
validStorageOptions_storageSize :: Lens.Lens' ValidStorageOptions (Prelude.Maybe [Range])
validStorageOptions_storageSize :: Lens' ValidStorageOptions (Maybe [Range])
validStorageOptions_storageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidStorageOptions' {Maybe [Range]
storageSize :: Maybe [Range]
$sel:storageSize:ValidStorageOptions' :: ValidStorageOptions -> Maybe [Range]
storageSize} -> Maybe [Range]
storageSize) (\s :: ValidStorageOptions
s@ValidStorageOptions' {} Maybe [Range]
a -> ValidStorageOptions
s {$sel:storageSize:ValidStorageOptions' :: Maybe [Range]
storageSize = Maybe [Range]
a} :: ValidStorageOptions) 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 valid range of storage throughput to provisioned IOPS ratios. For
-- example, 0-0.25.
validStorageOptions_storageThroughputToIopsRatio :: Lens.Lens' ValidStorageOptions (Prelude.Maybe [DoubleRange])
validStorageOptions_storageThroughputToIopsRatio :: Lens' ValidStorageOptions (Maybe [DoubleRange])
validStorageOptions_storageThroughputToIopsRatio = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidStorageOptions' {Maybe [DoubleRange]
storageThroughputToIopsRatio :: Maybe [DoubleRange]
$sel:storageThroughputToIopsRatio:ValidStorageOptions' :: ValidStorageOptions -> Maybe [DoubleRange]
storageThroughputToIopsRatio} -> Maybe [DoubleRange]
storageThroughputToIopsRatio) (\s :: ValidStorageOptions
s@ValidStorageOptions' {} Maybe [DoubleRange]
a -> ValidStorageOptions
s {$sel:storageThroughputToIopsRatio:ValidStorageOptions' :: Maybe [DoubleRange]
storageThroughputToIopsRatio = Maybe [DoubleRange]
a} :: ValidStorageOptions) 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 valid storage types for your DB instance. For example: gp2, gp3,
-- io1.
validStorageOptions_storageType :: Lens.Lens' ValidStorageOptions (Prelude.Maybe Prelude.Text)
validStorageOptions_storageType :: Lens' ValidStorageOptions (Maybe Text)
validStorageOptions_storageType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidStorageOptions' {Maybe Text
storageType :: Maybe Text
$sel:storageType:ValidStorageOptions' :: ValidStorageOptions -> Maybe Text
storageType} -> Maybe Text
storageType) (\s :: ValidStorageOptions
s@ValidStorageOptions' {} Maybe Text
a -> ValidStorageOptions
s {$sel:storageType:ValidStorageOptions' :: Maybe Text
storageType = Maybe Text
a} :: ValidStorageOptions)

-- | Whether or not Amazon RDS can automatically scale storage for DB
-- instances that use the new instance class.
validStorageOptions_supportsStorageAutoscaling :: Lens.Lens' ValidStorageOptions (Prelude.Maybe Prelude.Bool)
validStorageOptions_supportsStorageAutoscaling :: Lens' ValidStorageOptions (Maybe Bool)
validStorageOptions_supportsStorageAutoscaling = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidStorageOptions' {Maybe Bool
supportsStorageAutoscaling :: Maybe Bool
$sel:supportsStorageAutoscaling:ValidStorageOptions' :: ValidStorageOptions -> Maybe Bool
supportsStorageAutoscaling} -> Maybe Bool
supportsStorageAutoscaling) (\s :: ValidStorageOptions
s@ValidStorageOptions' {} Maybe Bool
a -> ValidStorageOptions
s {$sel:supportsStorageAutoscaling:ValidStorageOptions' :: Maybe Bool
supportsStorageAutoscaling = Maybe Bool
a} :: ValidStorageOptions)

instance Data.FromXML ValidStorageOptions where
  parseXML :: [Node] -> Either String ValidStorageOptions
parseXML [Node]
x =
    Maybe [DoubleRange]
-> Maybe [Range]
-> Maybe [Range]
-> Maybe [Range]
-> Maybe [DoubleRange]
-> Maybe Text
-> Maybe Bool
-> ValidStorageOptions
ValidStorageOptions'
      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
"IopsToStorageRatio"
                      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
"DoubleRange")
                  )
      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
"ProvisionedIops"
                      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
"Range")
                  )
      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
"ProvisionedStorageThroughput"
                      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
"Range")
                  )
      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
"StorageSize"
                      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
"Range")
                  )
      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
"StorageThroughputToIopsRatio"
                      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
"DoubleRange")
                  )
      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
"StorageType")
      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
"SupportsStorageAutoscaling")

instance Prelude.Hashable ValidStorageOptions where
  hashWithSalt :: Int -> ValidStorageOptions -> Int
hashWithSalt Int
_salt ValidStorageOptions' {Maybe Bool
Maybe [DoubleRange]
Maybe [Range]
Maybe Text
supportsStorageAutoscaling :: Maybe Bool
storageType :: Maybe Text
storageThroughputToIopsRatio :: Maybe [DoubleRange]
storageSize :: Maybe [Range]
provisionedStorageThroughput :: Maybe [Range]
provisionedIops :: Maybe [Range]
iopsToStorageRatio :: Maybe [DoubleRange]
$sel:supportsStorageAutoscaling:ValidStorageOptions' :: ValidStorageOptions -> Maybe Bool
$sel:storageType:ValidStorageOptions' :: ValidStorageOptions -> Maybe Text
$sel:storageThroughputToIopsRatio:ValidStorageOptions' :: ValidStorageOptions -> Maybe [DoubleRange]
$sel:storageSize:ValidStorageOptions' :: ValidStorageOptions -> Maybe [Range]
$sel:provisionedStorageThroughput:ValidStorageOptions' :: ValidStorageOptions -> Maybe [Range]
$sel:provisionedIops:ValidStorageOptions' :: ValidStorageOptions -> Maybe [Range]
$sel:iopsToStorageRatio:ValidStorageOptions' :: ValidStorageOptions -> Maybe [DoubleRange]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DoubleRange]
iopsToStorageRatio
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Range]
provisionedIops
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Range]
provisionedStorageThroughput
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Range]
storageSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DoubleRange]
storageThroughputToIopsRatio
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
storageType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
supportsStorageAutoscaling

instance Prelude.NFData ValidStorageOptions where
  rnf :: ValidStorageOptions -> ()
rnf ValidStorageOptions' {Maybe Bool
Maybe [DoubleRange]
Maybe [Range]
Maybe Text
supportsStorageAutoscaling :: Maybe Bool
storageType :: Maybe Text
storageThroughputToIopsRatio :: Maybe [DoubleRange]
storageSize :: Maybe [Range]
provisionedStorageThroughput :: Maybe [Range]
provisionedIops :: Maybe [Range]
iopsToStorageRatio :: Maybe [DoubleRange]
$sel:supportsStorageAutoscaling:ValidStorageOptions' :: ValidStorageOptions -> Maybe Bool
$sel:storageType:ValidStorageOptions' :: ValidStorageOptions -> Maybe Text
$sel:storageThroughputToIopsRatio:ValidStorageOptions' :: ValidStorageOptions -> Maybe [DoubleRange]
$sel:storageSize:ValidStorageOptions' :: ValidStorageOptions -> Maybe [Range]
$sel:provisionedStorageThroughput:ValidStorageOptions' :: ValidStorageOptions -> Maybe [Range]
$sel:provisionedIops:ValidStorageOptions' :: ValidStorageOptions -> Maybe [Range]
$sel:iopsToStorageRatio:ValidStorageOptions' :: ValidStorageOptions -> Maybe [DoubleRange]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [DoubleRange]
iopsToStorageRatio
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Range]
provisionedIops
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Range]
provisionedStorageThroughput
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Range]
storageSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DoubleRange]
storageThroughputToIopsRatio
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
storageType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
supportsStorageAutoscaling