{-# 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.CreateFileSystemLustreConfiguration
-- 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.CreateFileSystemLustreConfiguration 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.AutoImportPolicyType
import Amazonka.FSx.Types.DataCompressionType
import Amazonka.FSx.Types.DriveCacheType
import Amazonka.FSx.Types.LustreDeploymentType
import Amazonka.FSx.Types.LustreLogCreateConfiguration
import Amazonka.FSx.Types.LustreRootSquashConfiguration
import qualified Amazonka.Prelude as Prelude

-- | The Lustre configuration for the file system being created.
--
-- The following parameters are not supported for file systems with the
-- @Persistent_2@ deployment type. Instead, use
-- @CreateDataRepositoryAssociation@ to create a data repository
-- association to link your Lustre file system to a data repository.
--
-- -   @AutoImportPolicy@
--
-- -   @ExportPath@
--
-- -   @ImportedChunkSize@
--
-- -   @ImportPath@
--
-- /See:/ 'newCreateFileSystemLustreConfiguration' smart constructor.
data CreateFileSystemLustreConfiguration = CreateFileSystemLustreConfiguration'
  { -- | (Optional) Available with @Scratch@ and @Persistent_1@ deployment types.
    -- When you create your file system, your existing S3 objects appear as
    -- file and directory listings. Use this property to choose how Amazon FSx
    -- keeps your file and directory listings up to date as you add or modify
    -- objects in your linked S3 bucket. @AutoImportPolicy@ can have the
    -- following values:
    --
    -- -   @NONE@ - (Default) AutoImport is off. Amazon FSx only updates file
    --     and directory listings from the linked S3 bucket when the file
    --     system is created. FSx does not update file and directory listings
    --     for any new or changed objects after choosing this option.
    --
    -- -   @NEW@ - AutoImport is on. Amazon FSx automatically imports directory
    --     listings of any new objects added to the linked S3 bucket that do
    --     not currently exist in the FSx file system.
    --
    -- -   @NEW_CHANGED@ - AutoImport is on. Amazon FSx automatically imports
    --     file and directory listings of any new objects added to the S3
    --     bucket and any existing objects that are changed in the S3 bucket
    --     after you choose this option.
    --
    -- -   @NEW_CHANGED_DELETED@ - AutoImport is on. Amazon FSx automatically
    --     imports file and directory listings of any new objects added to the
    --     S3 bucket, any existing objects that are changed in the S3 bucket,
    --     and any objects that were deleted in the S3 bucket.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/older-deployment-types.html#legacy-auto-import-from-s3 Automatically import updates from your S3 bucket>.
    --
    -- This parameter is not supported for file systems with the @Persistent_2@
    -- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
    -- create a data repository association to link your Lustre file system to
    -- a data repository.
    CreateFileSystemLustreConfiguration -> Maybe AutoImportPolicyType
autoImportPolicy :: Prelude.Maybe AutoImportPolicyType,
    CreateFileSystemLustreConfiguration -> Maybe Natural
automaticBackupRetentionDays :: Prelude.Maybe Prelude.Natural,
    -- | (Optional) Not available for use with file systems that are linked to a
    -- data repository. A boolean flag indicating whether tags for the file
    -- system should be copied to backups. The default value is false. If
    -- @CopyTagsToBackups@ is set to true, all file system tags are copied to
    -- all automatic and user-initiated backups when the user doesn\'t specify
    -- any backup-specific tags. If @CopyTagsToBackups@ is set to true and you
    -- specify one or more backup tags, only the specified tags are copied to
    -- backups. If you specify one or more tags when creating a user-initiated
    -- backup, no tags are copied from the file system, regardless of this
    -- value.
    --
    -- (Default = @false@)
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/using-backups-fsx.html Working with backups>
    -- in the /Amazon FSx for Lustre User Guide/.
    CreateFileSystemLustreConfiguration -> Maybe Bool
copyTagsToBackups :: Prelude.Maybe Prelude.Bool,
    CreateFileSystemLustreConfiguration -> Maybe Text
dailyAutomaticBackupStartTime :: Prelude.Maybe Prelude.Text,
    -- | Sets the data compression configuration for the file system.
    -- @DataCompressionType@ can have the following values:
    --
    -- -   @NONE@ - (Default) Data compression is turned off when the file
    --     system is created.
    --
    -- -   @LZ4@ - Data compression is turned on with the LZ4 algorithm.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/data-compression.html Lustre data compression>
    -- in the /Amazon FSx for Lustre User Guide/.
    CreateFileSystemLustreConfiguration -> Maybe DataCompressionType
dataCompressionType :: Prelude.Maybe DataCompressionType,
    -- | (Optional) Choose @SCRATCH_1@ and @SCRATCH_2@ deployment types when you
    -- need temporary storage and shorter-term processing of data. The
    -- @SCRATCH_2@ deployment type provides in-transit encryption of data and
    -- higher burst throughput capacity than @SCRATCH_1@.
    --
    -- Choose @PERSISTENT_1@ for longer-term storage and for throughput-focused
    -- workloads that aren’t latency-sensitive. @PERSISTENT_1@ supports
    -- encryption of data in transit, and is available in all Amazon Web
    -- Services Regions in which FSx for Lustre is available.
    --
    -- Choose @PERSISTENT_2@ for longer-term storage and for latency-sensitive
    -- workloads that require the highest levels of IOPS\/throughput.
    -- @PERSISTENT_2@ supports SSD storage, and offers higher
    -- @PerUnitStorageThroughput@ (up to 1000 MB\/s\/TiB). @PERSISTENT_2@ is
    -- available in a limited number of Amazon Web Services Regions. For more
    -- information, and an up-to-date list of Amazon Web Services Regions in
    -- which @PERSISTENT_2@ is available, see
    -- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/using-fsx-lustre.html#lustre-deployment-types File system deployment options for FSx for Lustre>
    -- in the /Amazon FSx for Lustre User Guide/.
    --
    -- If you choose @PERSISTENT_2@, and you set @FileSystemTypeVersion@ to
    -- @2.10@, the @CreateFileSystem@ operation fails.
    --
    -- Encryption of data in transit is automatically turned on when you access
    -- @SCRATCH_2@, @PERSISTENT_1@ and @PERSISTENT_2@ file systems from Amazon
    -- EC2 instances that
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/data-%20protection.html support automatic encryption>
    -- in the Amazon Web Services Regions where they are available. For more
    -- information about encryption in transit for FSx for Lustre file systems,
    -- see
    -- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/encryption-in-transit-fsxl.html Encrypting data in transit>
    -- in the /Amazon FSx for Lustre User Guide/.
    --
    -- (Default = @SCRATCH_1@)
    CreateFileSystemLustreConfiguration -> Maybe LustreDeploymentType
deploymentType :: Prelude.Maybe LustreDeploymentType,
    -- | The type of drive cache used by @PERSISTENT_1@ file systems that are
    -- provisioned with HDD storage devices. This parameter is required when
    -- storage type is HDD. Set this property to @READ@ to improve the
    -- performance for frequently accessed files by caching up to 20% of the
    -- total storage capacity of the file system.
    --
    -- This parameter is required when @StorageType@ is set to @HDD@.
    CreateFileSystemLustreConfiguration -> Maybe DriveCacheType
driveCacheType :: Prelude.Maybe DriveCacheType,
    -- | (Optional) Available with @Scratch@ and @Persistent_1@ deployment types.
    -- Specifies the path in the Amazon S3 bucket where the root of your Amazon
    -- FSx file system is exported. The path must use the same Amazon S3 bucket
    -- as specified in ImportPath. You can provide an optional prefix to which
    -- new and changed data is to be exported from your Amazon FSx for Lustre
    -- file system. If an @ExportPath@ value is not provided, Amazon FSx sets a
    -- default export path,
    -- @s3:\/\/import-bucket\/FSxLustre[creation-timestamp]@. The timestamp is
    -- in UTC format, for example
    -- @s3:\/\/import-bucket\/FSxLustre20181105T222312Z@.
    --
    -- The Amazon S3 export bucket must be the same as the import bucket
    -- specified by @ImportPath@. If you specify only a bucket name, such as
    -- @s3:\/\/import-bucket@, you get a 1:1 mapping of file system objects to
    -- S3 bucket objects. This mapping means that the input data in S3 is
    -- overwritten on export. If you provide a custom prefix in the export
    -- path, such as @s3:\/\/import-bucket\/[custom-optional-prefix]@, Amazon
    -- FSx exports the contents of your file system to that export prefix in
    -- the Amazon S3 bucket.
    --
    -- This parameter is not supported for file systems with the @Persistent_2@
    -- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
    -- create a data repository association to link your Lustre file system to
    -- a data repository.
    CreateFileSystemLustreConfiguration -> Maybe Text
exportPath :: Prelude.Maybe Prelude.Text,
    -- | (Optional) The path to the Amazon S3 bucket (including the optional
    -- prefix) that you\'re using as the data repository for your Amazon FSx
    -- for Lustre file system. The root of your FSx for Lustre file system will
    -- be mapped to the root of the Amazon S3 bucket you select. An example is
    -- @s3:\/\/import-bucket\/optional-prefix@. If you specify a prefix after
    -- the Amazon S3 bucket name, only object keys with that prefix are loaded
    -- into the file system.
    --
    -- This parameter is not supported for file systems with the @Persistent_2@
    -- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
    -- create a data repository association to link your Lustre file system to
    -- a data repository.
    CreateFileSystemLustreConfiguration -> Maybe Text
importPath :: Prelude.Maybe Prelude.Text,
    -- | (Optional) For files imported from a data repository, this value
    -- determines the stripe count and maximum amount of data per file (in MiB)
    -- stored on a single physical disk. The maximum number of disks that a
    -- single file can be striped across is limited by the total number of
    -- disks that make up the file system.
    --
    -- The default chunk size is 1,024 MiB (1 GiB) and can go as high as
    -- 512,000 MiB (500 GiB). Amazon S3 objects have a maximum size of 5 TB.
    --
    -- This parameter is not supported for file systems with the @Persistent_2@
    -- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
    -- create a data repository association to link your Lustre file system to
    -- a data repository.
    CreateFileSystemLustreConfiguration -> Maybe Natural
importedFileChunkSize :: Prelude.Maybe Prelude.Natural,
    -- | The Lustre logging configuration used when creating an Amazon FSx for
    -- Lustre file system. When logging is enabled, Lustre logs error and
    -- warning events for data repositories associated with your file system to
    -- Amazon CloudWatch Logs.
    CreateFileSystemLustreConfiguration
-> Maybe LustreLogCreateConfiguration
logConfiguration :: Prelude.Maybe LustreLogCreateConfiguration,
    -- | Required with @PERSISTENT_1@ and @PERSISTENT_2@ deployment types,
    -- provisions the amount of read and write throughput for each 1 tebibyte
    -- (TiB) of file system storage capacity, in MB\/s\/TiB. File system
    -- throughput capacity is calculated by multiplying file system storage
    -- capacity (TiB) by the @PerUnitStorageThroughput@ (MB\/s\/TiB). For a
    -- 2.4-TiB file system, provisioning 50 MB\/s\/TiB of
    -- @PerUnitStorageThroughput@ yields 120 MB\/s of file system throughput.
    -- You pay for the amount of throughput that you provision.
    --
    -- Valid values:
    --
    -- -   For @PERSISTENT_1@ SSD storage: 50, 100, 200 MB\/s\/TiB.
    --
    -- -   For @PERSISTENT_1@ HDD storage: 12, 40 MB\/s\/TiB.
    --
    -- -   For @PERSISTENT_2@ SSD storage: 125, 250, 500, 1000 MB\/s\/TiB.
    CreateFileSystemLustreConfiguration -> Maybe Natural
perUnitStorageThroughput :: Prelude.Maybe Prelude.Natural,
    -- | The Lustre root squash configuration used when creating an Amazon FSx
    -- for Lustre file system. When enabled, root squash restricts root-level
    -- access from clients that try to access your file system as a root user.
    CreateFileSystemLustreConfiguration
-> Maybe LustreRootSquashConfiguration
rootSquashConfiguration :: Prelude.Maybe LustreRootSquashConfiguration,
    -- | (Optional) The preferred start time to perform weekly maintenance,
    -- formatted d:HH:MM in the UTC time zone, where d is the weekday number,
    -- from 1 through 7, beginning with Monday and ending with Sunday.
    CreateFileSystemLustreConfiguration -> Maybe Text
weeklyMaintenanceStartTime :: Prelude.Maybe Prelude.Text
  }
  deriving (CreateFileSystemLustreConfiguration
-> CreateFileSystemLustreConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFileSystemLustreConfiguration
-> CreateFileSystemLustreConfiguration -> Bool
$c/= :: CreateFileSystemLustreConfiguration
-> CreateFileSystemLustreConfiguration -> Bool
== :: CreateFileSystemLustreConfiguration
-> CreateFileSystemLustreConfiguration -> Bool
$c== :: CreateFileSystemLustreConfiguration
-> CreateFileSystemLustreConfiguration -> Bool
Prelude.Eq, ReadPrec [CreateFileSystemLustreConfiguration]
ReadPrec CreateFileSystemLustreConfiguration
Int -> ReadS CreateFileSystemLustreConfiguration
ReadS [CreateFileSystemLustreConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFileSystemLustreConfiguration]
$creadListPrec :: ReadPrec [CreateFileSystemLustreConfiguration]
readPrec :: ReadPrec CreateFileSystemLustreConfiguration
$creadPrec :: ReadPrec CreateFileSystemLustreConfiguration
readList :: ReadS [CreateFileSystemLustreConfiguration]
$creadList :: ReadS [CreateFileSystemLustreConfiguration]
readsPrec :: Int -> ReadS CreateFileSystemLustreConfiguration
$creadsPrec :: Int -> ReadS CreateFileSystemLustreConfiguration
Prelude.Read, Int -> CreateFileSystemLustreConfiguration -> ShowS
[CreateFileSystemLustreConfiguration] -> ShowS
CreateFileSystemLustreConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFileSystemLustreConfiguration] -> ShowS
$cshowList :: [CreateFileSystemLustreConfiguration] -> ShowS
show :: CreateFileSystemLustreConfiguration -> String
$cshow :: CreateFileSystemLustreConfiguration -> String
showsPrec :: Int -> CreateFileSystemLustreConfiguration -> ShowS
$cshowsPrec :: Int -> CreateFileSystemLustreConfiguration -> ShowS
Prelude.Show, forall x.
Rep CreateFileSystemLustreConfiguration x
-> CreateFileSystemLustreConfiguration
forall x.
CreateFileSystemLustreConfiguration
-> Rep CreateFileSystemLustreConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateFileSystemLustreConfiguration x
-> CreateFileSystemLustreConfiguration
$cfrom :: forall x.
CreateFileSystemLustreConfiguration
-> Rep CreateFileSystemLustreConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'CreateFileSystemLustreConfiguration' 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:
--
-- 'autoImportPolicy', 'createFileSystemLustreConfiguration_autoImportPolicy' - (Optional) Available with @Scratch@ and @Persistent_1@ deployment types.
-- When you create your file system, your existing S3 objects appear as
-- file and directory listings. Use this property to choose how Amazon FSx
-- keeps your file and directory listings up to date as you add or modify
-- objects in your linked S3 bucket. @AutoImportPolicy@ can have the
-- following values:
--
-- -   @NONE@ - (Default) AutoImport is off. Amazon FSx only updates file
--     and directory listings from the linked S3 bucket when the file
--     system is created. FSx does not update file and directory listings
--     for any new or changed objects after choosing this option.
--
-- -   @NEW@ - AutoImport is on. Amazon FSx automatically imports directory
--     listings of any new objects added to the linked S3 bucket that do
--     not currently exist in the FSx file system.
--
-- -   @NEW_CHANGED@ - AutoImport is on. Amazon FSx automatically imports
--     file and directory listings of any new objects added to the S3
--     bucket and any existing objects that are changed in the S3 bucket
--     after you choose this option.
--
-- -   @NEW_CHANGED_DELETED@ - AutoImport is on. Amazon FSx automatically
--     imports file and directory listings of any new objects added to the
--     S3 bucket, any existing objects that are changed in the S3 bucket,
--     and any objects that were deleted in the S3 bucket.
--
-- For more information, see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/older-deployment-types.html#legacy-auto-import-from-s3 Automatically import updates from your S3 bucket>.
--
-- This parameter is not supported for file systems with the @Persistent_2@
-- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
-- create a data repository association to link your Lustre file system to
-- a data repository.
--
-- 'automaticBackupRetentionDays', 'createFileSystemLustreConfiguration_automaticBackupRetentionDays' - Undocumented member.
--
-- 'copyTagsToBackups', 'createFileSystemLustreConfiguration_copyTagsToBackups' - (Optional) Not available for use with file systems that are linked to a
-- data repository. A boolean flag indicating whether tags for the file
-- system should be copied to backups. The default value is false. If
-- @CopyTagsToBackups@ is set to true, all file system tags are copied to
-- all automatic and user-initiated backups when the user doesn\'t specify
-- any backup-specific tags. If @CopyTagsToBackups@ is set to true and you
-- specify one or more backup tags, only the specified tags are copied to
-- backups. If you specify one or more tags when creating a user-initiated
-- backup, no tags are copied from the file system, regardless of this
-- value.
--
-- (Default = @false@)
--
-- For more information, see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/using-backups-fsx.html Working with backups>
-- in the /Amazon FSx for Lustre User Guide/.
--
-- 'dailyAutomaticBackupStartTime', 'createFileSystemLustreConfiguration_dailyAutomaticBackupStartTime' - Undocumented member.
--
-- 'dataCompressionType', 'createFileSystemLustreConfiguration_dataCompressionType' - Sets the data compression configuration for the file system.
-- @DataCompressionType@ can have the following values:
--
-- -   @NONE@ - (Default) Data compression is turned off when the file
--     system is created.
--
-- -   @LZ4@ - Data compression is turned on with the LZ4 algorithm.
--
-- For more information, see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/data-compression.html Lustre data compression>
-- in the /Amazon FSx for Lustre User Guide/.
--
-- 'deploymentType', 'createFileSystemLustreConfiguration_deploymentType' - (Optional) Choose @SCRATCH_1@ and @SCRATCH_2@ deployment types when you
-- need temporary storage and shorter-term processing of data. The
-- @SCRATCH_2@ deployment type provides in-transit encryption of data and
-- higher burst throughput capacity than @SCRATCH_1@.
--
-- Choose @PERSISTENT_1@ for longer-term storage and for throughput-focused
-- workloads that aren’t latency-sensitive. @PERSISTENT_1@ supports
-- encryption of data in transit, and is available in all Amazon Web
-- Services Regions in which FSx for Lustre is available.
--
-- Choose @PERSISTENT_2@ for longer-term storage and for latency-sensitive
-- workloads that require the highest levels of IOPS\/throughput.
-- @PERSISTENT_2@ supports SSD storage, and offers higher
-- @PerUnitStorageThroughput@ (up to 1000 MB\/s\/TiB). @PERSISTENT_2@ is
-- available in a limited number of Amazon Web Services Regions. For more
-- information, and an up-to-date list of Amazon Web Services Regions in
-- which @PERSISTENT_2@ is available, see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/using-fsx-lustre.html#lustre-deployment-types File system deployment options for FSx for Lustre>
-- in the /Amazon FSx for Lustre User Guide/.
--
-- If you choose @PERSISTENT_2@, and you set @FileSystemTypeVersion@ to
-- @2.10@, the @CreateFileSystem@ operation fails.
--
-- Encryption of data in transit is automatically turned on when you access
-- @SCRATCH_2@, @PERSISTENT_1@ and @PERSISTENT_2@ file systems from Amazon
-- EC2 instances that
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/data-%20protection.html support automatic encryption>
-- in the Amazon Web Services Regions where they are available. For more
-- information about encryption in transit for FSx for Lustre file systems,
-- see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/encryption-in-transit-fsxl.html Encrypting data in transit>
-- in the /Amazon FSx for Lustre User Guide/.
--
-- (Default = @SCRATCH_1@)
--
-- 'driveCacheType', 'createFileSystemLustreConfiguration_driveCacheType' - The type of drive cache used by @PERSISTENT_1@ file systems that are
-- provisioned with HDD storage devices. This parameter is required when
-- storage type is HDD. Set this property to @READ@ to improve the
-- performance for frequently accessed files by caching up to 20% of the
-- total storage capacity of the file system.
--
-- This parameter is required when @StorageType@ is set to @HDD@.
--
-- 'exportPath', 'createFileSystemLustreConfiguration_exportPath' - (Optional) Available with @Scratch@ and @Persistent_1@ deployment types.
-- Specifies the path in the Amazon S3 bucket where the root of your Amazon
-- FSx file system is exported. The path must use the same Amazon S3 bucket
-- as specified in ImportPath. You can provide an optional prefix to which
-- new and changed data is to be exported from your Amazon FSx for Lustre
-- file system. If an @ExportPath@ value is not provided, Amazon FSx sets a
-- default export path,
-- @s3:\/\/import-bucket\/FSxLustre[creation-timestamp]@. The timestamp is
-- in UTC format, for example
-- @s3:\/\/import-bucket\/FSxLustre20181105T222312Z@.
--
-- The Amazon S3 export bucket must be the same as the import bucket
-- specified by @ImportPath@. If you specify only a bucket name, such as
-- @s3:\/\/import-bucket@, you get a 1:1 mapping of file system objects to
-- S3 bucket objects. This mapping means that the input data in S3 is
-- overwritten on export. If you provide a custom prefix in the export
-- path, such as @s3:\/\/import-bucket\/[custom-optional-prefix]@, Amazon
-- FSx exports the contents of your file system to that export prefix in
-- the Amazon S3 bucket.
--
-- This parameter is not supported for file systems with the @Persistent_2@
-- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
-- create a data repository association to link your Lustre file system to
-- a data repository.
--
-- 'importPath', 'createFileSystemLustreConfiguration_importPath' - (Optional) The path to the Amazon S3 bucket (including the optional
-- prefix) that you\'re using as the data repository for your Amazon FSx
-- for Lustre file system. The root of your FSx for Lustre file system will
-- be mapped to the root of the Amazon S3 bucket you select. An example is
-- @s3:\/\/import-bucket\/optional-prefix@. If you specify a prefix after
-- the Amazon S3 bucket name, only object keys with that prefix are loaded
-- into the file system.
--
-- This parameter is not supported for file systems with the @Persistent_2@
-- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
-- create a data repository association to link your Lustre file system to
-- a data repository.
--
-- 'importedFileChunkSize', 'createFileSystemLustreConfiguration_importedFileChunkSize' - (Optional) For files imported from a data repository, this value
-- determines the stripe count and maximum amount of data per file (in MiB)
-- stored on a single physical disk. The maximum number of disks that a
-- single file can be striped across is limited by the total number of
-- disks that make up the file system.
--
-- The default chunk size is 1,024 MiB (1 GiB) and can go as high as
-- 512,000 MiB (500 GiB). Amazon S3 objects have a maximum size of 5 TB.
--
-- This parameter is not supported for file systems with the @Persistent_2@
-- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
-- create a data repository association to link your Lustre file system to
-- a data repository.
--
-- 'logConfiguration', 'createFileSystemLustreConfiguration_logConfiguration' - The Lustre logging configuration used when creating an Amazon FSx for
-- Lustre file system. When logging is enabled, Lustre logs error and
-- warning events for data repositories associated with your file system to
-- Amazon CloudWatch Logs.
--
-- 'perUnitStorageThroughput', 'createFileSystemLustreConfiguration_perUnitStorageThroughput' - Required with @PERSISTENT_1@ and @PERSISTENT_2@ deployment types,
-- provisions the amount of read and write throughput for each 1 tebibyte
-- (TiB) of file system storage capacity, in MB\/s\/TiB. File system
-- throughput capacity is calculated by multiplying file system storage
-- capacity (TiB) by the @PerUnitStorageThroughput@ (MB\/s\/TiB). For a
-- 2.4-TiB file system, provisioning 50 MB\/s\/TiB of
-- @PerUnitStorageThroughput@ yields 120 MB\/s of file system throughput.
-- You pay for the amount of throughput that you provision.
--
-- Valid values:
--
-- -   For @PERSISTENT_1@ SSD storage: 50, 100, 200 MB\/s\/TiB.
--
-- -   For @PERSISTENT_1@ HDD storage: 12, 40 MB\/s\/TiB.
--
-- -   For @PERSISTENT_2@ SSD storage: 125, 250, 500, 1000 MB\/s\/TiB.
--
-- 'rootSquashConfiguration', 'createFileSystemLustreConfiguration_rootSquashConfiguration' - The Lustre root squash configuration used when creating an Amazon FSx
-- for Lustre file system. When enabled, root squash restricts root-level
-- access from clients that try to access your file system as a root user.
--
-- 'weeklyMaintenanceStartTime', 'createFileSystemLustreConfiguration_weeklyMaintenanceStartTime' - (Optional) The preferred start time to perform weekly maintenance,
-- formatted d:HH:MM in the UTC time zone, where d is the weekday number,
-- from 1 through 7, beginning with Monday and ending with Sunday.
newCreateFileSystemLustreConfiguration ::
  CreateFileSystemLustreConfiguration
newCreateFileSystemLustreConfiguration :: CreateFileSystemLustreConfiguration
newCreateFileSystemLustreConfiguration =
  CreateFileSystemLustreConfiguration'
    { $sel:autoImportPolicy:CreateFileSystemLustreConfiguration' :: Maybe AutoImportPolicyType
autoImportPolicy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:automaticBackupRetentionDays:CreateFileSystemLustreConfiguration' :: Maybe Natural
automaticBackupRetentionDays =
        forall a. Maybe a
Prelude.Nothing,
      $sel:copyTagsToBackups:CreateFileSystemLustreConfiguration' :: Maybe Bool
copyTagsToBackups = forall a. Maybe a
Prelude.Nothing,
      $sel:dailyAutomaticBackupStartTime:CreateFileSystemLustreConfiguration' :: Maybe Text
dailyAutomaticBackupStartTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dataCompressionType:CreateFileSystemLustreConfiguration' :: Maybe DataCompressionType
dataCompressionType = forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentType:CreateFileSystemLustreConfiguration' :: Maybe LustreDeploymentType
deploymentType = forall a. Maybe a
Prelude.Nothing,
      $sel:driveCacheType:CreateFileSystemLustreConfiguration' :: Maybe DriveCacheType
driveCacheType = forall a. Maybe a
Prelude.Nothing,
      $sel:exportPath:CreateFileSystemLustreConfiguration' :: Maybe Text
exportPath = forall a. Maybe a
Prelude.Nothing,
      $sel:importPath:CreateFileSystemLustreConfiguration' :: Maybe Text
importPath = forall a. Maybe a
Prelude.Nothing,
      $sel:importedFileChunkSize:CreateFileSystemLustreConfiguration' :: Maybe Natural
importedFileChunkSize =
        forall a. Maybe a
Prelude.Nothing,
      $sel:logConfiguration:CreateFileSystemLustreConfiguration' :: Maybe LustreLogCreateConfiguration
logConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:perUnitStorageThroughput:CreateFileSystemLustreConfiguration' :: Maybe Natural
perUnitStorageThroughput =
        forall a. Maybe a
Prelude.Nothing,
      $sel:rootSquashConfiguration:CreateFileSystemLustreConfiguration' :: Maybe LustreRootSquashConfiguration
rootSquashConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:weeklyMaintenanceStartTime:CreateFileSystemLustreConfiguration' :: Maybe Text
weeklyMaintenanceStartTime =
        forall a. Maybe a
Prelude.Nothing
    }

-- | (Optional) Available with @Scratch@ and @Persistent_1@ deployment types.
-- When you create your file system, your existing S3 objects appear as
-- file and directory listings. Use this property to choose how Amazon FSx
-- keeps your file and directory listings up to date as you add or modify
-- objects in your linked S3 bucket. @AutoImportPolicy@ can have the
-- following values:
--
-- -   @NONE@ - (Default) AutoImport is off. Amazon FSx only updates file
--     and directory listings from the linked S3 bucket when the file
--     system is created. FSx does not update file and directory listings
--     for any new or changed objects after choosing this option.
--
-- -   @NEW@ - AutoImport is on. Amazon FSx automatically imports directory
--     listings of any new objects added to the linked S3 bucket that do
--     not currently exist in the FSx file system.
--
-- -   @NEW_CHANGED@ - AutoImport is on. Amazon FSx automatically imports
--     file and directory listings of any new objects added to the S3
--     bucket and any existing objects that are changed in the S3 bucket
--     after you choose this option.
--
-- -   @NEW_CHANGED_DELETED@ - AutoImport is on. Amazon FSx automatically
--     imports file and directory listings of any new objects added to the
--     S3 bucket, any existing objects that are changed in the S3 bucket,
--     and any objects that were deleted in the S3 bucket.
--
-- For more information, see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/older-deployment-types.html#legacy-auto-import-from-s3 Automatically import updates from your S3 bucket>.
--
-- This parameter is not supported for file systems with the @Persistent_2@
-- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
-- create a data repository association to link your Lustre file system to
-- a data repository.
createFileSystemLustreConfiguration_autoImportPolicy :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe AutoImportPolicyType)
createFileSystemLustreConfiguration_autoImportPolicy :: Lens'
  CreateFileSystemLustreConfiguration (Maybe AutoImportPolicyType)
createFileSystemLustreConfiguration_autoImportPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe AutoImportPolicyType
autoImportPolicy :: Maybe AutoImportPolicyType
$sel:autoImportPolicy:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe AutoImportPolicyType
autoImportPolicy} -> Maybe AutoImportPolicyType
autoImportPolicy) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe AutoImportPolicyType
a -> CreateFileSystemLustreConfiguration
s {$sel:autoImportPolicy:CreateFileSystemLustreConfiguration' :: Maybe AutoImportPolicyType
autoImportPolicy = Maybe AutoImportPolicyType
a} :: CreateFileSystemLustreConfiguration)

-- | Undocumented member.
createFileSystemLustreConfiguration_automaticBackupRetentionDays :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe Prelude.Natural)
createFileSystemLustreConfiguration_automaticBackupRetentionDays :: Lens' CreateFileSystemLustreConfiguration (Maybe Natural)
createFileSystemLustreConfiguration_automaticBackupRetentionDays = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe Natural
automaticBackupRetentionDays :: Maybe Natural
$sel:automaticBackupRetentionDays:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
automaticBackupRetentionDays} -> Maybe Natural
automaticBackupRetentionDays) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe Natural
a -> CreateFileSystemLustreConfiguration
s {$sel:automaticBackupRetentionDays:CreateFileSystemLustreConfiguration' :: Maybe Natural
automaticBackupRetentionDays = Maybe Natural
a} :: CreateFileSystemLustreConfiguration)

-- | (Optional) Not available for use with file systems that are linked to a
-- data repository. A boolean flag indicating whether tags for the file
-- system should be copied to backups. The default value is false. If
-- @CopyTagsToBackups@ is set to true, all file system tags are copied to
-- all automatic and user-initiated backups when the user doesn\'t specify
-- any backup-specific tags. If @CopyTagsToBackups@ is set to true and you
-- specify one or more backup tags, only the specified tags are copied to
-- backups. If you specify one or more tags when creating a user-initiated
-- backup, no tags are copied from the file system, regardless of this
-- value.
--
-- (Default = @false@)
--
-- For more information, see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/using-backups-fsx.html Working with backups>
-- in the /Amazon FSx for Lustre User Guide/.
createFileSystemLustreConfiguration_copyTagsToBackups :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe Prelude.Bool)
createFileSystemLustreConfiguration_copyTagsToBackups :: Lens' CreateFileSystemLustreConfiguration (Maybe Bool)
createFileSystemLustreConfiguration_copyTagsToBackups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe Bool
copyTagsToBackups :: Maybe Bool
$sel:copyTagsToBackups:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Bool
copyTagsToBackups} -> Maybe Bool
copyTagsToBackups) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe Bool
a -> CreateFileSystemLustreConfiguration
s {$sel:copyTagsToBackups:CreateFileSystemLustreConfiguration' :: Maybe Bool
copyTagsToBackups = Maybe Bool
a} :: CreateFileSystemLustreConfiguration)

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

-- | Sets the data compression configuration for the file system.
-- @DataCompressionType@ can have the following values:
--
-- -   @NONE@ - (Default) Data compression is turned off when the file
--     system is created.
--
-- -   @LZ4@ - Data compression is turned on with the LZ4 algorithm.
--
-- For more information, see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/data-compression.html Lustre data compression>
-- in the /Amazon FSx for Lustre User Guide/.
createFileSystemLustreConfiguration_dataCompressionType :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe DataCompressionType)
createFileSystemLustreConfiguration_dataCompressionType :: Lens'
  CreateFileSystemLustreConfiguration (Maybe DataCompressionType)
createFileSystemLustreConfiguration_dataCompressionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe DataCompressionType
dataCompressionType :: Maybe DataCompressionType
$sel:dataCompressionType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe DataCompressionType
dataCompressionType} -> Maybe DataCompressionType
dataCompressionType) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe DataCompressionType
a -> CreateFileSystemLustreConfiguration
s {$sel:dataCompressionType:CreateFileSystemLustreConfiguration' :: Maybe DataCompressionType
dataCompressionType = Maybe DataCompressionType
a} :: CreateFileSystemLustreConfiguration)

-- | (Optional) Choose @SCRATCH_1@ and @SCRATCH_2@ deployment types when you
-- need temporary storage and shorter-term processing of data. The
-- @SCRATCH_2@ deployment type provides in-transit encryption of data and
-- higher burst throughput capacity than @SCRATCH_1@.
--
-- Choose @PERSISTENT_1@ for longer-term storage and for throughput-focused
-- workloads that aren’t latency-sensitive. @PERSISTENT_1@ supports
-- encryption of data in transit, and is available in all Amazon Web
-- Services Regions in which FSx for Lustre is available.
--
-- Choose @PERSISTENT_2@ for longer-term storage and for latency-sensitive
-- workloads that require the highest levels of IOPS\/throughput.
-- @PERSISTENT_2@ supports SSD storage, and offers higher
-- @PerUnitStorageThroughput@ (up to 1000 MB\/s\/TiB). @PERSISTENT_2@ is
-- available in a limited number of Amazon Web Services Regions. For more
-- information, and an up-to-date list of Amazon Web Services Regions in
-- which @PERSISTENT_2@ is available, see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/using-fsx-lustre.html#lustre-deployment-types File system deployment options for FSx for Lustre>
-- in the /Amazon FSx for Lustre User Guide/.
--
-- If you choose @PERSISTENT_2@, and you set @FileSystemTypeVersion@ to
-- @2.10@, the @CreateFileSystem@ operation fails.
--
-- Encryption of data in transit is automatically turned on when you access
-- @SCRATCH_2@, @PERSISTENT_1@ and @PERSISTENT_2@ file systems from Amazon
-- EC2 instances that
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/data-%20protection.html support automatic encryption>
-- in the Amazon Web Services Regions where they are available. For more
-- information about encryption in transit for FSx for Lustre file systems,
-- see
-- <https://docs.aws.amazon.com/fsx/latest/LustreGuide/encryption-in-transit-fsxl.html Encrypting data in transit>
-- in the /Amazon FSx for Lustre User Guide/.
--
-- (Default = @SCRATCH_1@)
createFileSystemLustreConfiguration_deploymentType :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe LustreDeploymentType)
createFileSystemLustreConfiguration_deploymentType :: Lens'
  CreateFileSystemLustreConfiguration (Maybe LustreDeploymentType)
createFileSystemLustreConfiguration_deploymentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe LustreDeploymentType
deploymentType :: Maybe LustreDeploymentType
$sel:deploymentType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe LustreDeploymentType
deploymentType} -> Maybe LustreDeploymentType
deploymentType) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe LustreDeploymentType
a -> CreateFileSystemLustreConfiguration
s {$sel:deploymentType:CreateFileSystemLustreConfiguration' :: Maybe LustreDeploymentType
deploymentType = Maybe LustreDeploymentType
a} :: CreateFileSystemLustreConfiguration)

-- | The type of drive cache used by @PERSISTENT_1@ file systems that are
-- provisioned with HDD storage devices. This parameter is required when
-- storage type is HDD. Set this property to @READ@ to improve the
-- performance for frequently accessed files by caching up to 20% of the
-- total storage capacity of the file system.
--
-- This parameter is required when @StorageType@ is set to @HDD@.
createFileSystemLustreConfiguration_driveCacheType :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe DriveCacheType)
createFileSystemLustreConfiguration_driveCacheType :: Lens' CreateFileSystemLustreConfiguration (Maybe DriveCacheType)
createFileSystemLustreConfiguration_driveCacheType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe DriveCacheType
driveCacheType :: Maybe DriveCacheType
$sel:driveCacheType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe DriveCacheType
driveCacheType} -> Maybe DriveCacheType
driveCacheType) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe DriveCacheType
a -> CreateFileSystemLustreConfiguration
s {$sel:driveCacheType:CreateFileSystemLustreConfiguration' :: Maybe DriveCacheType
driveCacheType = Maybe DriveCacheType
a} :: CreateFileSystemLustreConfiguration)

-- | (Optional) Available with @Scratch@ and @Persistent_1@ deployment types.
-- Specifies the path in the Amazon S3 bucket where the root of your Amazon
-- FSx file system is exported. The path must use the same Amazon S3 bucket
-- as specified in ImportPath. You can provide an optional prefix to which
-- new and changed data is to be exported from your Amazon FSx for Lustre
-- file system. If an @ExportPath@ value is not provided, Amazon FSx sets a
-- default export path,
-- @s3:\/\/import-bucket\/FSxLustre[creation-timestamp]@. The timestamp is
-- in UTC format, for example
-- @s3:\/\/import-bucket\/FSxLustre20181105T222312Z@.
--
-- The Amazon S3 export bucket must be the same as the import bucket
-- specified by @ImportPath@. If you specify only a bucket name, such as
-- @s3:\/\/import-bucket@, you get a 1:1 mapping of file system objects to
-- S3 bucket objects. This mapping means that the input data in S3 is
-- overwritten on export. If you provide a custom prefix in the export
-- path, such as @s3:\/\/import-bucket\/[custom-optional-prefix]@, Amazon
-- FSx exports the contents of your file system to that export prefix in
-- the Amazon S3 bucket.
--
-- This parameter is not supported for file systems with the @Persistent_2@
-- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
-- create a data repository association to link your Lustre file system to
-- a data repository.
createFileSystemLustreConfiguration_exportPath :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe Prelude.Text)
createFileSystemLustreConfiguration_exportPath :: Lens' CreateFileSystemLustreConfiguration (Maybe Text)
createFileSystemLustreConfiguration_exportPath = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe Text
exportPath :: Maybe Text
$sel:exportPath:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
exportPath} -> Maybe Text
exportPath) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe Text
a -> CreateFileSystemLustreConfiguration
s {$sel:exportPath:CreateFileSystemLustreConfiguration' :: Maybe Text
exportPath = Maybe Text
a} :: CreateFileSystemLustreConfiguration)

-- | (Optional) The path to the Amazon S3 bucket (including the optional
-- prefix) that you\'re using as the data repository for your Amazon FSx
-- for Lustre file system. The root of your FSx for Lustre file system will
-- be mapped to the root of the Amazon S3 bucket you select. An example is
-- @s3:\/\/import-bucket\/optional-prefix@. If you specify a prefix after
-- the Amazon S3 bucket name, only object keys with that prefix are loaded
-- into the file system.
--
-- This parameter is not supported for file systems with the @Persistent_2@
-- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
-- create a data repository association to link your Lustre file system to
-- a data repository.
createFileSystemLustreConfiguration_importPath :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe Prelude.Text)
createFileSystemLustreConfiguration_importPath :: Lens' CreateFileSystemLustreConfiguration (Maybe Text)
createFileSystemLustreConfiguration_importPath = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe Text
importPath :: Maybe Text
$sel:importPath:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
importPath} -> Maybe Text
importPath) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe Text
a -> CreateFileSystemLustreConfiguration
s {$sel:importPath:CreateFileSystemLustreConfiguration' :: Maybe Text
importPath = Maybe Text
a} :: CreateFileSystemLustreConfiguration)

-- | (Optional) For files imported from a data repository, this value
-- determines the stripe count and maximum amount of data per file (in MiB)
-- stored on a single physical disk. The maximum number of disks that a
-- single file can be striped across is limited by the total number of
-- disks that make up the file system.
--
-- The default chunk size is 1,024 MiB (1 GiB) and can go as high as
-- 512,000 MiB (500 GiB). Amazon S3 objects have a maximum size of 5 TB.
--
-- This parameter is not supported for file systems with the @Persistent_2@
-- deployment type. Instead, use @CreateDataRepositoryAssociation@ to
-- create a data repository association to link your Lustre file system to
-- a data repository.
createFileSystemLustreConfiguration_importedFileChunkSize :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe Prelude.Natural)
createFileSystemLustreConfiguration_importedFileChunkSize :: Lens' CreateFileSystemLustreConfiguration (Maybe Natural)
createFileSystemLustreConfiguration_importedFileChunkSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe Natural
importedFileChunkSize :: Maybe Natural
$sel:importedFileChunkSize:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
importedFileChunkSize} -> Maybe Natural
importedFileChunkSize) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe Natural
a -> CreateFileSystemLustreConfiguration
s {$sel:importedFileChunkSize:CreateFileSystemLustreConfiguration' :: Maybe Natural
importedFileChunkSize = Maybe Natural
a} :: CreateFileSystemLustreConfiguration)

-- | The Lustre logging configuration used when creating an Amazon FSx for
-- Lustre file system. When logging is enabled, Lustre logs error and
-- warning events for data repositories associated with your file system to
-- Amazon CloudWatch Logs.
createFileSystemLustreConfiguration_logConfiguration :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe LustreLogCreateConfiguration)
createFileSystemLustreConfiguration_logConfiguration :: Lens'
  CreateFileSystemLustreConfiguration
  (Maybe LustreLogCreateConfiguration)
createFileSystemLustreConfiguration_logConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe LustreLogCreateConfiguration
logConfiguration :: Maybe LustreLogCreateConfiguration
$sel:logConfiguration:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration
-> Maybe LustreLogCreateConfiguration
logConfiguration} -> Maybe LustreLogCreateConfiguration
logConfiguration) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe LustreLogCreateConfiguration
a -> CreateFileSystemLustreConfiguration
s {$sel:logConfiguration:CreateFileSystemLustreConfiguration' :: Maybe LustreLogCreateConfiguration
logConfiguration = Maybe LustreLogCreateConfiguration
a} :: CreateFileSystemLustreConfiguration)

-- | Required with @PERSISTENT_1@ and @PERSISTENT_2@ deployment types,
-- provisions the amount of read and write throughput for each 1 tebibyte
-- (TiB) of file system storage capacity, in MB\/s\/TiB. File system
-- throughput capacity is calculated by multiplying file system storage
-- capacity (TiB) by the @PerUnitStorageThroughput@ (MB\/s\/TiB). For a
-- 2.4-TiB file system, provisioning 50 MB\/s\/TiB of
-- @PerUnitStorageThroughput@ yields 120 MB\/s of file system throughput.
-- You pay for the amount of throughput that you provision.
--
-- Valid values:
--
-- -   For @PERSISTENT_1@ SSD storage: 50, 100, 200 MB\/s\/TiB.
--
-- -   For @PERSISTENT_1@ HDD storage: 12, 40 MB\/s\/TiB.
--
-- -   For @PERSISTENT_2@ SSD storage: 125, 250, 500, 1000 MB\/s\/TiB.
createFileSystemLustreConfiguration_perUnitStorageThroughput :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe Prelude.Natural)
createFileSystemLustreConfiguration_perUnitStorageThroughput :: Lens' CreateFileSystemLustreConfiguration (Maybe Natural)
createFileSystemLustreConfiguration_perUnitStorageThroughput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe Natural
perUnitStorageThroughput :: Maybe Natural
$sel:perUnitStorageThroughput:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
perUnitStorageThroughput} -> Maybe Natural
perUnitStorageThroughput) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe Natural
a -> CreateFileSystemLustreConfiguration
s {$sel:perUnitStorageThroughput:CreateFileSystemLustreConfiguration' :: Maybe Natural
perUnitStorageThroughput = Maybe Natural
a} :: CreateFileSystemLustreConfiguration)

-- | The Lustre root squash configuration used when creating an Amazon FSx
-- for Lustre file system. When enabled, root squash restricts root-level
-- access from clients that try to access your file system as a root user.
createFileSystemLustreConfiguration_rootSquashConfiguration :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe LustreRootSquashConfiguration)
createFileSystemLustreConfiguration_rootSquashConfiguration :: Lens'
  CreateFileSystemLustreConfiguration
  (Maybe LustreRootSquashConfiguration)
createFileSystemLustreConfiguration_rootSquashConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe LustreRootSquashConfiguration
rootSquashConfiguration :: Maybe LustreRootSquashConfiguration
$sel:rootSquashConfiguration:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration
-> Maybe LustreRootSquashConfiguration
rootSquashConfiguration} -> Maybe LustreRootSquashConfiguration
rootSquashConfiguration) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe LustreRootSquashConfiguration
a -> CreateFileSystemLustreConfiguration
s {$sel:rootSquashConfiguration:CreateFileSystemLustreConfiguration' :: Maybe LustreRootSquashConfiguration
rootSquashConfiguration = Maybe LustreRootSquashConfiguration
a} :: CreateFileSystemLustreConfiguration)

-- | (Optional) The preferred start time to perform weekly maintenance,
-- formatted d:HH:MM in the UTC time zone, where d is the weekday number,
-- from 1 through 7, beginning with Monday and ending with Sunday.
createFileSystemLustreConfiguration_weeklyMaintenanceStartTime :: Lens.Lens' CreateFileSystemLustreConfiguration (Prelude.Maybe Prelude.Text)
createFileSystemLustreConfiguration_weeklyMaintenanceStartTime :: Lens' CreateFileSystemLustreConfiguration (Maybe Text)
createFileSystemLustreConfiguration_weeklyMaintenanceStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFileSystemLustreConfiguration' {Maybe Text
weeklyMaintenanceStartTime :: Maybe Text
$sel:weeklyMaintenanceStartTime:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
weeklyMaintenanceStartTime} -> Maybe Text
weeklyMaintenanceStartTime) (\s :: CreateFileSystemLustreConfiguration
s@CreateFileSystemLustreConfiguration' {} Maybe Text
a -> CreateFileSystemLustreConfiguration
s {$sel:weeklyMaintenanceStartTime:CreateFileSystemLustreConfiguration' :: Maybe Text
weeklyMaintenanceStartTime = Maybe Text
a} :: CreateFileSystemLustreConfiguration)

instance
  Prelude.Hashable
    CreateFileSystemLustreConfiguration
  where
  hashWithSalt :: Int -> CreateFileSystemLustreConfiguration -> Int
hashWithSalt
    Int
_salt
    CreateFileSystemLustreConfiguration' {Maybe Bool
Maybe Natural
Maybe Text
Maybe AutoImportPolicyType
Maybe DataCompressionType
Maybe DriveCacheType
Maybe LustreDeploymentType
Maybe LustreLogCreateConfiguration
Maybe LustreRootSquashConfiguration
weeklyMaintenanceStartTime :: Maybe Text
rootSquashConfiguration :: Maybe LustreRootSquashConfiguration
perUnitStorageThroughput :: Maybe Natural
logConfiguration :: Maybe LustreLogCreateConfiguration
importedFileChunkSize :: Maybe Natural
importPath :: Maybe Text
exportPath :: Maybe Text
driveCacheType :: Maybe DriveCacheType
deploymentType :: Maybe LustreDeploymentType
dataCompressionType :: Maybe DataCompressionType
dailyAutomaticBackupStartTime :: Maybe Text
copyTagsToBackups :: Maybe Bool
automaticBackupRetentionDays :: Maybe Natural
autoImportPolicy :: Maybe AutoImportPolicyType
$sel:weeklyMaintenanceStartTime:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:rootSquashConfiguration:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration
-> Maybe LustreRootSquashConfiguration
$sel:perUnitStorageThroughput:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
$sel:logConfiguration:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration
-> Maybe LustreLogCreateConfiguration
$sel:importedFileChunkSize:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
$sel:importPath:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:exportPath:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:driveCacheType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe DriveCacheType
$sel:deploymentType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe LustreDeploymentType
$sel:dataCompressionType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe DataCompressionType
$sel:dailyAutomaticBackupStartTime:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:copyTagsToBackups:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Bool
$sel:automaticBackupRetentionDays:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
$sel:autoImportPolicy:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe AutoImportPolicyType
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutoImportPolicyType
autoImportPolicy
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
automaticBackupRetentionDays
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
copyTagsToBackups
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dailyAutomaticBackupStartTime
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataCompressionType
dataCompressionType
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LustreDeploymentType
deploymentType
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DriveCacheType
driveCacheType
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
exportPath
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
importPath
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
importedFileChunkSize
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LustreLogCreateConfiguration
logConfiguration
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
perUnitStorageThroughput
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LustreRootSquashConfiguration
rootSquashConfiguration
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
weeklyMaintenanceStartTime

instance
  Prelude.NFData
    CreateFileSystemLustreConfiguration
  where
  rnf :: CreateFileSystemLustreConfiguration -> ()
rnf CreateFileSystemLustreConfiguration' {Maybe Bool
Maybe Natural
Maybe Text
Maybe AutoImportPolicyType
Maybe DataCompressionType
Maybe DriveCacheType
Maybe LustreDeploymentType
Maybe LustreLogCreateConfiguration
Maybe LustreRootSquashConfiguration
weeklyMaintenanceStartTime :: Maybe Text
rootSquashConfiguration :: Maybe LustreRootSquashConfiguration
perUnitStorageThroughput :: Maybe Natural
logConfiguration :: Maybe LustreLogCreateConfiguration
importedFileChunkSize :: Maybe Natural
importPath :: Maybe Text
exportPath :: Maybe Text
driveCacheType :: Maybe DriveCacheType
deploymentType :: Maybe LustreDeploymentType
dataCompressionType :: Maybe DataCompressionType
dailyAutomaticBackupStartTime :: Maybe Text
copyTagsToBackups :: Maybe Bool
automaticBackupRetentionDays :: Maybe Natural
autoImportPolicy :: Maybe AutoImportPolicyType
$sel:weeklyMaintenanceStartTime:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:rootSquashConfiguration:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration
-> Maybe LustreRootSquashConfiguration
$sel:perUnitStorageThroughput:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
$sel:logConfiguration:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration
-> Maybe LustreLogCreateConfiguration
$sel:importedFileChunkSize:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
$sel:importPath:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:exportPath:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:driveCacheType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe DriveCacheType
$sel:deploymentType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe LustreDeploymentType
$sel:dataCompressionType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe DataCompressionType
$sel:dailyAutomaticBackupStartTime:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:copyTagsToBackups:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Bool
$sel:automaticBackupRetentionDays:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
$sel:autoImportPolicy:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe AutoImportPolicyType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AutoImportPolicyType
autoImportPolicy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
automaticBackupRetentionDays
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
copyTagsToBackups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dailyAutomaticBackupStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataCompressionType
dataCompressionType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LustreDeploymentType
deploymentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DriveCacheType
driveCacheType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
exportPath
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
importPath
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
importedFileChunkSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LustreLogCreateConfiguration
logConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
perUnitStorageThroughput
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LustreRootSquashConfiguration
rootSquashConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
weeklyMaintenanceStartTime

instance
  Data.ToJSON
    CreateFileSystemLustreConfiguration
  where
  toJSON :: CreateFileSystemLustreConfiguration -> Value
toJSON CreateFileSystemLustreConfiguration' {Maybe Bool
Maybe Natural
Maybe Text
Maybe AutoImportPolicyType
Maybe DataCompressionType
Maybe DriveCacheType
Maybe LustreDeploymentType
Maybe LustreLogCreateConfiguration
Maybe LustreRootSquashConfiguration
weeklyMaintenanceStartTime :: Maybe Text
rootSquashConfiguration :: Maybe LustreRootSquashConfiguration
perUnitStorageThroughput :: Maybe Natural
logConfiguration :: Maybe LustreLogCreateConfiguration
importedFileChunkSize :: Maybe Natural
importPath :: Maybe Text
exportPath :: Maybe Text
driveCacheType :: Maybe DriveCacheType
deploymentType :: Maybe LustreDeploymentType
dataCompressionType :: Maybe DataCompressionType
dailyAutomaticBackupStartTime :: Maybe Text
copyTagsToBackups :: Maybe Bool
automaticBackupRetentionDays :: Maybe Natural
autoImportPolicy :: Maybe AutoImportPolicyType
$sel:weeklyMaintenanceStartTime:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:rootSquashConfiguration:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration
-> Maybe LustreRootSquashConfiguration
$sel:perUnitStorageThroughput:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
$sel:logConfiguration:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration
-> Maybe LustreLogCreateConfiguration
$sel:importedFileChunkSize:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
$sel:importPath:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:exportPath:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:driveCacheType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe DriveCacheType
$sel:deploymentType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe LustreDeploymentType
$sel:dataCompressionType:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe DataCompressionType
$sel:dailyAutomaticBackupStartTime:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Text
$sel:copyTagsToBackups:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Bool
$sel:automaticBackupRetentionDays:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe Natural
$sel:autoImportPolicy:CreateFileSystemLustreConfiguration' :: CreateFileSystemLustreConfiguration -> Maybe AutoImportPolicyType
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AutoImportPolicy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AutoImportPolicyType
autoImportPolicy,
            (Key
"AutomaticBackupRetentionDays" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
automaticBackupRetentionDays,
            (Key
"CopyTagsToBackups" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
copyTagsToBackups,
            (Key
"DailyAutomaticBackupStartTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
dailyAutomaticBackupStartTime,
            (Key
"DataCompressionType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DataCompressionType
dataCompressionType,
            (Key
"DeploymentType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LustreDeploymentType
deploymentType,
            (Key
"DriveCacheType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DriveCacheType
driveCacheType,
            (Key
"ExportPath" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
exportPath,
            (Key
"ImportPath" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
importPath,
            (Key
"ImportedFileChunkSize" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
importedFileChunkSize,
            (Key
"LogConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LustreLogCreateConfiguration
logConfiguration,
            (Key
"PerUnitStorageThroughput" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
perUnitStorageThroughput,
            (Key
"RootSquashConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LustreRootSquashConfiguration
rootSquashConfiguration,
            (Key
"WeeklyMaintenanceStartTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
weeklyMaintenanceStartTime
          ]
      )