{-# 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.FSx.Types.FileCacheCreating
-- 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.FSx.Types.FileCacheCreating where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.FSx.Types.FileCacheFailureDetails
import Amazonka.FSx.Types.FileCacheLifecycle
import Amazonka.FSx.Types.FileCacheLustreConfiguration
import Amazonka.FSx.Types.FileCacheType
import Amazonka.FSx.Types.Tag
import qualified Amazonka.Prelude as Prelude

-- | The response object for the Amazon File Cache resource being created in
-- the @CreateFileCache@ operation.
--
-- /See:/ 'newFileCacheCreating' smart constructor.
data FileCacheCreating = FileCacheCreating'
  { -- | A boolean flag indicating whether tags for the cache should be copied to
    -- data repository associations.
    FileCacheCreating -> Maybe Bool
copyTagsToDataRepositoryAssociations :: Prelude.Maybe Prelude.Bool,
    FileCacheCreating -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The Domain Name System (DNS) name for the cache.
    FileCacheCreating -> Maybe Text
dNSName :: Prelude.Maybe Prelude.Text,
    -- | A list of IDs of data repository associations that are associated with
    -- this cache.
    FileCacheCreating -> Maybe [Text]
dataRepositoryAssociationIds :: Prelude.Maybe [Prelude.Text],
    -- | A structure providing details of any failures that occurred.
    FileCacheCreating -> Maybe FileCacheFailureDetails
failureDetails :: Prelude.Maybe FileCacheFailureDetails,
    -- | The system-generated, unique ID of the cache.
    FileCacheCreating -> Maybe Text
fileCacheId :: Prelude.Maybe Prelude.Text,
    -- | The type of cache, which must be @LUSTRE@.
    FileCacheCreating -> Maybe FileCacheType
fileCacheType :: Prelude.Maybe FileCacheType,
    -- | The Lustre version of the cache, which must be @2.12@.
    FileCacheCreating -> Maybe Text
fileCacheTypeVersion :: Prelude.Maybe Prelude.Text,
    -- | Specifies the ID of the Key Management Service (KMS) key to use for
    -- encrypting data on an Amazon File Cache. If a @KmsKeyId@ isn\'t
    -- specified, the Amazon FSx-managed KMS key for your account is used. For
    -- more information, see
    -- <https://docs.aws.amazon.com/kms/latest/APIReference/API_Encrypt.html Encrypt>
    -- in the /Key Management Service API Reference/.
    FileCacheCreating -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The lifecycle status of the cache. The following are the possible values
    -- and what they mean:
    --
    -- -   @AVAILABLE@ - The cache is in a healthy state, and is reachable and
    --     available for use.
    --
    -- -   @CREATING@ - The new cache is being created.
    --
    -- -   @DELETING@ - An existing cache is being deleted.
    --
    -- -   @UPDATING@ - The cache is undergoing a customer-initiated update.
    --
    -- -   @FAILED@ - An existing cache has experienced an unrecoverable
    --     failure. When creating a new cache, the cache was unable to be
    --     created.
    FileCacheCreating -> Maybe FileCacheLifecycle
lifecycle :: Prelude.Maybe FileCacheLifecycle,
    -- | The configuration for the Amazon File Cache resource.
    FileCacheCreating -> Maybe FileCacheLustreConfiguration
lustreConfiguration :: Prelude.Maybe FileCacheLustreConfiguration,
    FileCacheCreating -> Maybe [Text]
networkInterfaceIds :: Prelude.Maybe [Prelude.Text],
    FileCacheCreating -> Maybe Text
ownerId :: Prelude.Maybe Prelude.Text,
    FileCacheCreating -> Maybe Text
resourceARN :: Prelude.Maybe Prelude.Text,
    -- | The storage capacity of the cache in gibibytes (GiB).
    FileCacheCreating -> Maybe Natural
storageCapacity :: Prelude.Maybe Prelude.Natural,
    FileCacheCreating -> Maybe [Text]
subnetIds :: Prelude.Maybe [Prelude.Text],
    FileCacheCreating -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    FileCacheCreating -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text
  }
  deriving (FileCacheCreating -> FileCacheCreating -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileCacheCreating -> FileCacheCreating -> Bool
$c/= :: FileCacheCreating -> FileCacheCreating -> Bool
== :: FileCacheCreating -> FileCacheCreating -> Bool
$c== :: FileCacheCreating -> FileCacheCreating -> Bool
Prelude.Eq, ReadPrec [FileCacheCreating]
ReadPrec FileCacheCreating
Int -> ReadS FileCacheCreating
ReadS [FileCacheCreating]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FileCacheCreating]
$creadListPrec :: ReadPrec [FileCacheCreating]
readPrec :: ReadPrec FileCacheCreating
$creadPrec :: ReadPrec FileCacheCreating
readList :: ReadS [FileCacheCreating]
$creadList :: ReadS [FileCacheCreating]
readsPrec :: Int -> ReadS FileCacheCreating
$creadsPrec :: Int -> ReadS FileCacheCreating
Prelude.Read, Int -> FileCacheCreating -> ShowS
[FileCacheCreating] -> ShowS
FileCacheCreating -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileCacheCreating] -> ShowS
$cshowList :: [FileCacheCreating] -> ShowS
show :: FileCacheCreating -> String
$cshow :: FileCacheCreating -> String
showsPrec :: Int -> FileCacheCreating -> ShowS
$cshowsPrec :: Int -> FileCacheCreating -> ShowS
Prelude.Show, forall x. Rep FileCacheCreating x -> FileCacheCreating
forall x. FileCacheCreating -> Rep FileCacheCreating x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FileCacheCreating x -> FileCacheCreating
$cfrom :: forall x. FileCacheCreating -> Rep FileCacheCreating x
Prelude.Generic)

-- |
-- Create a value of 'FileCacheCreating' 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:
--
-- 'copyTagsToDataRepositoryAssociations', 'fileCacheCreating_copyTagsToDataRepositoryAssociations' - A boolean flag indicating whether tags for the cache should be copied to
-- data repository associations.
--
-- 'creationTime', 'fileCacheCreating_creationTime' - Undocumented member.
--
-- 'dNSName', 'fileCacheCreating_dNSName' - The Domain Name System (DNS) name for the cache.
--
-- 'dataRepositoryAssociationIds', 'fileCacheCreating_dataRepositoryAssociationIds' - A list of IDs of data repository associations that are associated with
-- this cache.
--
-- 'failureDetails', 'fileCacheCreating_failureDetails' - A structure providing details of any failures that occurred.
--
-- 'fileCacheId', 'fileCacheCreating_fileCacheId' - The system-generated, unique ID of the cache.
--
-- 'fileCacheType', 'fileCacheCreating_fileCacheType' - The type of cache, which must be @LUSTRE@.
--
-- 'fileCacheTypeVersion', 'fileCacheCreating_fileCacheTypeVersion' - The Lustre version of the cache, which must be @2.12@.
--
-- 'kmsKeyId', 'fileCacheCreating_kmsKeyId' - Specifies the ID of the Key Management Service (KMS) key to use for
-- encrypting data on an Amazon File Cache. If a @KmsKeyId@ isn\'t
-- specified, the Amazon FSx-managed KMS key for your account is used. For
-- more information, see
-- <https://docs.aws.amazon.com/kms/latest/APIReference/API_Encrypt.html Encrypt>
-- in the /Key Management Service API Reference/.
--
-- 'lifecycle', 'fileCacheCreating_lifecycle' - The lifecycle status of the cache. The following are the possible values
-- and what they mean:
--
-- -   @AVAILABLE@ - The cache is in a healthy state, and is reachable and
--     available for use.
--
-- -   @CREATING@ - The new cache is being created.
--
-- -   @DELETING@ - An existing cache is being deleted.
--
-- -   @UPDATING@ - The cache is undergoing a customer-initiated update.
--
-- -   @FAILED@ - An existing cache has experienced an unrecoverable
--     failure. When creating a new cache, the cache was unable to be
--     created.
--
-- 'lustreConfiguration', 'fileCacheCreating_lustreConfiguration' - The configuration for the Amazon File Cache resource.
--
-- 'networkInterfaceIds', 'fileCacheCreating_networkInterfaceIds' - Undocumented member.
--
-- 'ownerId', 'fileCacheCreating_ownerId' - Undocumented member.
--
-- 'resourceARN', 'fileCacheCreating_resourceARN' - Undocumented member.
--
-- 'storageCapacity', 'fileCacheCreating_storageCapacity' - The storage capacity of the cache in gibibytes (GiB).
--
-- 'subnetIds', 'fileCacheCreating_subnetIds' - Undocumented member.
--
-- 'tags', 'fileCacheCreating_tags' - Undocumented member.
--
-- 'vpcId', 'fileCacheCreating_vpcId' - Undocumented member.
newFileCacheCreating ::
  FileCacheCreating
newFileCacheCreating :: FileCacheCreating
newFileCacheCreating =
  FileCacheCreating'
    { $sel:copyTagsToDataRepositoryAssociations:FileCacheCreating' :: Maybe Bool
copyTagsToDataRepositoryAssociations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:FileCacheCreating' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:dNSName:FileCacheCreating' :: Maybe Text
dNSName = forall a. Maybe a
Prelude.Nothing,
      $sel:dataRepositoryAssociationIds:FileCacheCreating' :: Maybe [Text]
dataRepositoryAssociationIds = forall a. Maybe a
Prelude.Nothing,
      $sel:failureDetails:FileCacheCreating' :: Maybe FileCacheFailureDetails
failureDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:fileCacheId:FileCacheCreating' :: Maybe Text
fileCacheId = forall a. Maybe a
Prelude.Nothing,
      $sel:fileCacheType:FileCacheCreating' :: Maybe FileCacheType
fileCacheType = forall a. Maybe a
Prelude.Nothing,
      $sel:fileCacheTypeVersion:FileCacheCreating' :: Maybe Text
fileCacheTypeVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:FileCacheCreating' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:lifecycle:FileCacheCreating' :: Maybe FileCacheLifecycle
lifecycle = forall a. Maybe a
Prelude.Nothing,
      $sel:lustreConfiguration:FileCacheCreating' :: Maybe FileCacheLustreConfiguration
lustreConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceIds:FileCacheCreating' :: Maybe [Text]
networkInterfaceIds = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerId:FileCacheCreating' :: Maybe Text
ownerId = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceARN:FileCacheCreating' :: Maybe Text
resourceARN = forall a. Maybe a
Prelude.Nothing,
      $sel:storageCapacity:FileCacheCreating' :: Maybe Natural
storageCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetIds:FileCacheCreating' :: Maybe [Text]
subnetIds = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:FileCacheCreating' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:FileCacheCreating' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing
    }

-- | A boolean flag indicating whether tags for the cache should be copied to
-- data repository associations.
fileCacheCreating_copyTagsToDataRepositoryAssociations :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.Bool)
fileCacheCreating_copyTagsToDataRepositoryAssociations :: Lens' FileCacheCreating (Maybe Bool)
fileCacheCreating_copyTagsToDataRepositoryAssociations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe Bool
copyTagsToDataRepositoryAssociations :: Maybe Bool
$sel:copyTagsToDataRepositoryAssociations:FileCacheCreating' :: FileCacheCreating -> Maybe Bool
copyTagsToDataRepositoryAssociations} -> Maybe Bool
copyTagsToDataRepositoryAssociations) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe Bool
a -> FileCacheCreating
s {$sel:copyTagsToDataRepositoryAssociations:FileCacheCreating' :: Maybe Bool
copyTagsToDataRepositoryAssociations = Maybe Bool
a} :: FileCacheCreating)

-- | Undocumented member.
fileCacheCreating_creationTime :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.UTCTime)
fileCacheCreating_creationTime :: Lens' FileCacheCreating (Maybe UTCTime)
fileCacheCreating_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:FileCacheCreating' :: FileCacheCreating -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe POSIX
a -> FileCacheCreating
s {$sel:creationTime:FileCacheCreating' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: FileCacheCreating) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The Domain Name System (DNS) name for the cache.
fileCacheCreating_dNSName :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.Text)
fileCacheCreating_dNSName :: Lens' FileCacheCreating (Maybe Text)
fileCacheCreating_dNSName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe Text
dNSName :: Maybe Text
$sel:dNSName:FileCacheCreating' :: FileCacheCreating -> Maybe Text
dNSName} -> Maybe Text
dNSName) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe Text
a -> FileCacheCreating
s {$sel:dNSName:FileCacheCreating' :: Maybe Text
dNSName = Maybe Text
a} :: FileCacheCreating)

-- | A list of IDs of data repository associations that are associated with
-- this cache.
fileCacheCreating_dataRepositoryAssociationIds :: Lens.Lens' FileCacheCreating (Prelude.Maybe [Prelude.Text])
fileCacheCreating_dataRepositoryAssociationIds :: Lens' FileCacheCreating (Maybe [Text])
fileCacheCreating_dataRepositoryAssociationIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe [Text]
dataRepositoryAssociationIds :: Maybe [Text]
$sel:dataRepositoryAssociationIds:FileCacheCreating' :: FileCacheCreating -> Maybe [Text]
dataRepositoryAssociationIds} -> Maybe [Text]
dataRepositoryAssociationIds) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe [Text]
a -> FileCacheCreating
s {$sel:dataRepositoryAssociationIds:FileCacheCreating' :: Maybe [Text]
dataRepositoryAssociationIds = Maybe [Text]
a} :: FileCacheCreating) 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

-- | A structure providing details of any failures that occurred.
fileCacheCreating_failureDetails :: Lens.Lens' FileCacheCreating (Prelude.Maybe FileCacheFailureDetails)
fileCacheCreating_failureDetails :: Lens' FileCacheCreating (Maybe FileCacheFailureDetails)
fileCacheCreating_failureDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe FileCacheFailureDetails
failureDetails :: Maybe FileCacheFailureDetails
$sel:failureDetails:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheFailureDetails
failureDetails} -> Maybe FileCacheFailureDetails
failureDetails) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe FileCacheFailureDetails
a -> FileCacheCreating
s {$sel:failureDetails:FileCacheCreating' :: Maybe FileCacheFailureDetails
failureDetails = Maybe FileCacheFailureDetails
a} :: FileCacheCreating)

-- | The system-generated, unique ID of the cache.
fileCacheCreating_fileCacheId :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.Text)
fileCacheCreating_fileCacheId :: Lens' FileCacheCreating (Maybe Text)
fileCacheCreating_fileCacheId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe Text
fileCacheId :: Maybe Text
$sel:fileCacheId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
fileCacheId} -> Maybe Text
fileCacheId) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe Text
a -> FileCacheCreating
s {$sel:fileCacheId:FileCacheCreating' :: Maybe Text
fileCacheId = Maybe Text
a} :: FileCacheCreating)

-- | The type of cache, which must be @LUSTRE@.
fileCacheCreating_fileCacheType :: Lens.Lens' FileCacheCreating (Prelude.Maybe FileCacheType)
fileCacheCreating_fileCacheType :: Lens' FileCacheCreating (Maybe FileCacheType)
fileCacheCreating_fileCacheType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe FileCacheType
fileCacheType :: Maybe FileCacheType
$sel:fileCacheType:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheType
fileCacheType} -> Maybe FileCacheType
fileCacheType) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe FileCacheType
a -> FileCacheCreating
s {$sel:fileCacheType:FileCacheCreating' :: Maybe FileCacheType
fileCacheType = Maybe FileCacheType
a} :: FileCacheCreating)

-- | The Lustre version of the cache, which must be @2.12@.
fileCacheCreating_fileCacheTypeVersion :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.Text)
fileCacheCreating_fileCacheTypeVersion :: Lens' FileCacheCreating (Maybe Text)
fileCacheCreating_fileCacheTypeVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe Text
fileCacheTypeVersion :: Maybe Text
$sel:fileCacheTypeVersion:FileCacheCreating' :: FileCacheCreating -> Maybe Text
fileCacheTypeVersion} -> Maybe Text
fileCacheTypeVersion) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe Text
a -> FileCacheCreating
s {$sel:fileCacheTypeVersion:FileCacheCreating' :: Maybe Text
fileCacheTypeVersion = Maybe Text
a} :: FileCacheCreating)

-- | Specifies the ID of the Key Management Service (KMS) key to use for
-- encrypting data on an Amazon File Cache. If a @KmsKeyId@ isn\'t
-- specified, the Amazon FSx-managed KMS key for your account is used. For
-- more information, see
-- <https://docs.aws.amazon.com/kms/latest/APIReference/API_Encrypt.html Encrypt>
-- in the /Key Management Service API Reference/.
fileCacheCreating_kmsKeyId :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.Text)
fileCacheCreating_kmsKeyId :: Lens' FileCacheCreating (Maybe Text)
fileCacheCreating_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe Text
a -> FileCacheCreating
s {$sel:kmsKeyId:FileCacheCreating' :: Maybe Text
kmsKeyId = Maybe Text
a} :: FileCacheCreating)

-- | The lifecycle status of the cache. The following are the possible values
-- and what they mean:
--
-- -   @AVAILABLE@ - The cache is in a healthy state, and is reachable and
--     available for use.
--
-- -   @CREATING@ - The new cache is being created.
--
-- -   @DELETING@ - An existing cache is being deleted.
--
-- -   @UPDATING@ - The cache is undergoing a customer-initiated update.
--
-- -   @FAILED@ - An existing cache has experienced an unrecoverable
--     failure. When creating a new cache, the cache was unable to be
--     created.
fileCacheCreating_lifecycle :: Lens.Lens' FileCacheCreating (Prelude.Maybe FileCacheLifecycle)
fileCacheCreating_lifecycle :: Lens' FileCacheCreating (Maybe FileCacheLifecycle)
fileCacheCreating_lifecycle = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe FileCacheLifecycle
lifecycle :: Maybe FileCacheLifecycle
$sel:lifecycle:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheLifecycle
lifecycle} -> Maybe FileCacheLifecycle
lifecycle) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe FileCacheLifecycle
a -> FileCacheCreating
s {$sel:lifecycle:FileCacheCreating' :: Maybe FileCacheLifecycle
lifecycle = Maybe FileCacheLifecycle
a} :: FileCacheCreating)

-- | The configuration for the Amazon File Cache resource.
fileCacheCreating_lustreConfiguration :: Lens.Lens' FileCacheCreating (Prelude.Maybe FileCacheLustreConfiguration)
fileCacheCreating_lustreConfiguration :: Lens' FileCacheCreating (Maybe FileCacheLustreConfiguration)
fileCacheCreating_lustreConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe FileCacheLustreConfiguration
lustreConfiguration :: Maybe FileCacheLustreConfiguration
$sel:lustreConfiguration:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheLustreConfiguration
lustreConfiguration} -> Maybe FileCacheLustreConfiguration
lustreConfiguration) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe FileCacheLustreConfiguration
a -> FileCacheCreating
s {$sel:lustreConfiguration:FileCacheCreating' :: Maybe FileCacheLustreConfiguration
lustreConfiguration = Maybe FileCacheLustreConfiguration
a} :: FileCacheCreating)

-- | Undocumented member.
fileCacheCreating_networkInterfaceIds :: Lens.Lens' FileCacheCreating (Prelude.Maybe [Prelude.Text])
fileCacheCreating_networkInterfaceIds :: Lens' FileCacheCreating (Maybe [Text])
fileCacheCreating_networkInterfaceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe [Text]
networkInterfaceIds :: Maybe [Text]
$sel:networkInterfaceIds:FileCacheCreating' :: FileCacheCreating -> Maybe [Text]
networkInterfaceIds} -> Maybe [Text]
networkInterfaceIds) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe [Text]
a -> FileCacheCreating
s {$sel:networkInterfaceIds:FileCacheCreating' :: Maybe [Text]
networkInterfaceIds = Maybe [Text]
a} :: FileCacheCreating) 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

-- | Undocumented member.
fileCacheCreating_ownerId :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.Text)
fileCacheCreating_ownerId :: Lens' FileCacheCreating (Maybe Text)
fileCacheCreating_ownerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe Text
ownerId :: Maybe Text
$sel:ownerId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
ownerId} -> Maybe Text
ownerId) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe Text
a -> FileCacheCreating
s {$sel:ownerId:FileCacheCreating' :: Maybe Text
ownerId = Maybe Text
a} :: FileCacheCreating)

-- | Undocumented member.
fileCacheCreating_resourceARN :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.Text)
fileCacheCreating_resourceARN :: Lens' FileCacheCreating (Maybe Text)
fileCacheCreating_resourceARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe Text
resourceARN :: Maybe Text
$sel:resourceARN:FileCacheCreating' :: FileCacheCreating -> Maybe Text
resourceARN} -> Maybe Text
resourceARN) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe Text
a -> FileCacheCreating
s {$sel:resourceARN:FileCacheCreating' :: Maybe Text
resourceARN = Maybe Text
a} :: FileCacheCreating)

-- | The storage capacity of the cache in gibibytes (GiB).
fileCacheCreating_storageCapacity :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.Natural)
fileCacheCreating_storageCapacity :: Lens' FileCacheCreating (Maybe Natural)
fileCacheCreating_storageCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe Natural
storageCapacity :: Maybe Natural
$sel:storageCapacity:FileCacheCreating' :: FileCacheCreating -> Maybe Natural
storageCapacity} -> Maybe Natural
storageCapacity) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe Natural
a -> FileCacheCreating
s {$sel:storageCapacity:FileCacheCreating' :: Maybe Natural
storageCapacity = Maybe Natural
a} :: FileCacheCreating)

-- | Undocumented member.
fileCacheCreating_subnetIds :: Lens.Lens' FileCacheCreating (Prelude.Maybe [Prelude.Text])
fileCacheCreating_subnetIds :: Lens' FileCacheCreating (Maybe [Text])
fileCacheCreating_subnetIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe [Text]
subnetIds :: Maybe [Text]
$sel:subnetIds:FileCacheCreating' :: FileCacheCreating -> Maybe [Text]
subnetIds} -> Maybe [Text]
subnetIds) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe [Text]
a -> FileCacheCreating
s {$sel:subnetIds:FileCacheCreating' :: Maybe [Text]
subnetIds = Maybe [Text]
a} :: FileCacheCreating) 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

-- | Undocumented member.
fileCacheCreating_tags :: Lens.Lens' FileCacheCreating (Prelude.Maybe (Prelude.NonEmpty Tag))
fileCacheCreating_tags :: Lens' FileCacheCreating (Maybe (NonEmpty Tag))
fileCacheCreating_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:FileCacheCreating' :: FileCacheCreating -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe (NonEmpty Tag)
a -> FileCacheCreating
s {$sel:tags:FileCacheCreating' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: FileCacheCreating) 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

-- | Undocumented member.
fileCacheCreating_vpcId :: Lens.Lens' FileCacheCreating (Prelude.Maybe Prelude.Text)
fileCacheCreating_vpcId :: Lens' FileCacheCreating (Maybe Text)
fileCacheCreating_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileCacheCreating' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: FileCacheCreating
s@FileCacheCreating' {} Maybe Text
a -> FileCacheCreating
s {$sel:vpcId:FileCacheCreating' :: Maybe Text
vpcId = Maybe Text
a} :: FileCacheCreating)

instance Data.FromJSON FileCacheCreating where
  parseJSON :: Value -> Parser FileCacheCreating
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"FileCacheCreating"
      ( \Object
x ->
          Maybe Bool
-> Maybe POSIX
-> Maybe Text
-> Maybe [Text]
-> Maybe FileCacheFailureDetails
-> Maybe Text
-> Maybe FileCacheType
-> Maybe Text
-> Maybe Text
-> Maybe FileCacheLifecycle
-> Maybe FileCacheLustreConfiguration
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe [Text]
-> Maybe (NonEmpty Tag)
-> Maybe Text
-> FileCacheCreating
FileCacheCreating'
            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
"CopyTagsToDataRepositoryAssociations")
            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
"CreationTime")
            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
"DNSName")
            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
"DataRepositoryAssociationIds"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"FailureDetails")
            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
"FileCacheId")
            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
"FileCacheType")
            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
"FileCacheTypeVersion")
            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
"KmsKeyId")
            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
"Lifecycle")
            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
"LustreConfiguration")
            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
"NetworkInterfaceIds"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"OwnerId")
            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
"ResourceARN")
            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
"StorageCapacity")
            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
"SubnetIds" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"Tags")
            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
"VpcId")
      )

instance Prelude.Hashable FileCacheCreating where
  hashWithSalt :: Int -> FileCacheCreating -> Int
hashWithSalt Int
_salt FileCacheCreating' {Maybe Bool
Maybe Natural
Maybe [Text]
Maybe (NonEmpty Tag)
Maybe Text
Maybe POSIX
Maybe FileCacheFailureDetails
Maybe FileCacheLifecycle
Maybe FileCacheType
Maybe FileCacheLustreConfiguration
vpcId :: Maybe Text
tags :: Maybe (NonEmpty Tag)
subnetIds :: Maybe [Text]
storageCapacity :: Maybe Natural
resourceARN :: Maybe Text
ownerId :: Maybe Text
networkInterfaceIds :: Maybe [Text]
lustreConfiguration :: Maybe FileCacheLustreConfiguration
lifecycle :: Maybe FileCacheLifecycle
kmsKeyId :: Maybe Text
fileCacheTypeVersion :: Maybe Text
fileCacheType :: Maybe FileCacheType
fileCacheId :: Maybe Text
failureDetails :: Maybe FileCacheFailureDetails
dataRepositoryAssociationIds :: Maybe [Text]
dNSName :: Maybe Text
creationTime :: Maybe POSIX
copyTagsToDataRepositoryAssociations :: Maybe Bool
$sel:vpcId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:tags:FileCacheCreating' :: FileCacheCreating -> Maybe (NonEmpty Tag)
$sel:subnetIds:FileCacheCreating' :: FileCacheCreating -> Maybe [Text]
$sel:storageCapacity:FileCacheCreating' :: FileCacheCreating -> Maybe Natural
$sel:resourceARN:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:ownerId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:networkInterfaceIds:FileCacheCreating' :: FileCacheCreating -> Maybe [Text]
$sel:lustreConfiguration:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheLustreConfiguration
$sel:lifecycle:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheLifecycle
$sel:kmsKeyId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:fileCacheTypeVersion:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:fileCacheType:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheType
$sel:fileCacheId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:failureDetails:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheFailureDetails
$sel:dataRepositoryAssociationIds:FileCacheCreating' :: FileCacheCreating -> Maybe [Text]
$sel:dNSName:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:creationTime:FileCacheCreating' :: FileCacheCreating -> Maybe POSIX
$sel:copyTagsToDataRepositoryAssociations:FileCacheCreating' :: FileCacheCreating -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
copyTagsToDataRepositoryAssociations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dNSName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
dataRepositoryAssociationIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileCacheFailureDetails
failureDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fileCacheId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileCacheType
fileCacheType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fileCacheTypeVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileCacheLifecycle
lifecycle
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileCacheLustreConfiguration
lustreConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
networkInterfaceIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ownerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
storageCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
subnetIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId

instance Prelude.NFData FileCacheCreating where
  rnf :: FileCacheCreating -> ()
rnf FileCacheCreating' {Maybe Bool
Maybe Natural
Maybe [Text]
Maybe (NonEmpty Tag)
Maybe Text
Maybe POSIX
Maybe FileCacheFailureDetails
Maybe FileCacheLifecycle
Maybe FileCacheType
Maybe FileCacheLustreConfiguration
vpcId :: Maybe Text
tags :: Maybe (NonEmpty Tag)
subnetIds :: Maybe [Text]
storageCapacity :: Maybe Natural
resourceARN :: Maybe Text
ownerId :: Maybe Text
networkInterfaceIds :: Maybe [Text]
lustreConfiguration :: Maybe FileCacheLustreConfiguration
lifecycle :: Maybe FileCacheLifecycle
kmsKeyId :: Maybe Text
fileCacheTypeVersion :: Maybe Text
fileCacheType :: Maybe FileCacheType
fileCacheId :: Maybe Text
failureDetails :: Maybe FileCacheFailureDetails
dataRepositoryAssociationIds :: Maybe [Text]
dNSName :: Maybe Text
creationTime :: Maybe POSIX
copyTagsToDataRepositoryAssociations :: Maybe Bool
$sel:vpcId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:tags:FileCacheCreating' :: FileCacheCreating -> Maybe (NonEmpty Tag)
$sel:subnetIds:FileCacheCreating' :: FileCacheCreating -> Maybe [Text]
$sel:storageCapacity:FileCacheCreating' :: FileCacheCreating -> Maybe Natural
$sel:resourceARN:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:ownerId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:networkInterfaceIds:FileCacheCreating' :: FileCacheCreating -> Maybe [Text]
$sel:lustreConfiguration:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheLustreConfiguration
$sel:lifecycle:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheLifecycle
$sel:kmsKeyId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:fileCacheTypeVersion:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:fileCacheType:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheType
$sel:fileCacheId:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:failureDetails:FileCacheCreating' :: FileCacheCreating -> Maybe FileCacheFailureDetails
$sel:dataRepositoryAssociationIds:FileCacheCreating' :: FileCacheCreating -> Maybe [Text]
$sel:dNSName:FileCacheCreating' :: FileCacheCreating -> Maybe Text
$sel:creationTime:FileCacheCreating' :: FileCacheCreating -> Maybe POSIX
$sel:copyTagsToDataRepositoryAssociations:FileCacheCreating' :: FileCacheCreating -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
copyTagsToDataRepositoryAssociations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dNSName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
dataRepositoryAssociationIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FileCacheFailureDetails
failureDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileCacheId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FileCacheType
fileCacheType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileCacheTypeVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FileCacheLifecycle
lifecycle
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FileCacheLustreConfiguration
lustreConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
networkInterfaceIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
storageCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
subnetIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId