{-# 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.DataSync.Types.Options
-- 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.DataSync.Types.Options where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DataSync.Types.Atime
import Amazonka.DataSync.Types.Gid
import Amazonka.DataSync.Types.LogLevel
import Amazonka.DataSync.Types.Mtime
import Amazonka.DataSync.Types.ObjectTags
import Amazonka.DataSync.Types.OverwriteMode
import Amazonka.DataSync.Types.PosixPermissions
import Amazonka.DataSync.Types.PreserveDeletedFiles
import Amazonka.DataSync.Types.PreserveDevices
import Amazonka.DataSync.Types.SmbSecurityDescriptorCopyFlags
import Amazonka.DataSync.Types.TaskQueueing
import Amazonka.DataSync.Types.TransferMode
import Amazonka.DataSync.Types.Uid
import Amazonka.DataSync.Types.VerifyMode
import qualified Amazonka.Prelude as Prelude

-- | Configures your DataSync task settings. These options include how
-- DataSync handles files, objects, and their associated metadata. You also
-- can specify how DataSync verifies data integrity, set bandwidth limits
-- for your task, among other options.
--
-- Each task setting has a default value. Unless you need to, you don\'t
-- have to configure any of these @Options@ before starting your task.
--
-- /See:/ 'newOptions' smart constructor.
data Options = Options'
  { -- | Specifies whether to preserve metadata indicating the last time a file
    -- was read or written to. If you set @Atime@ to @BEST_EFFORT@, DataSync
    -- attempts to preserve the original @Atime@ attribute on all source files
    -- (that is, the version before the @PREPARING@ phase of the task
    -- execution).
    --
    -- The behavior of @Atime@ isn\'t fully standard across platforms, so
    -- DataSync can only do this on a best-effort basis.
    --
    -- Default value: @BEST_EFFORT@
    --
    -- @BEST_EFFORT@: Attempt to preserve the per-file @Atime@ value
    -- (recommended).
    --
    -- @NONE@: Ignore @Atime@.
    --
    -- If @Atime@ is set to @BEST_EFFORT@, @Mtime@ must be set to @PRESERVE@.
    --
    -- If @Atime@ is set to @NONE@, @Mtime@ must also be @NONE@.
    Options -> Maybe Atime
atime :: Prelude.Maybe Atime,
    -- | Limits the bandwidth used by a DataSync task. For example, if you want
    -- DataSync to use a maximum of 1 MB, set this value to @1048576@
    -- (@=1024*1024@).
    Options -> Maybe Integer
bytesPerSecond :: Prelude.Maybe Prelude.Integer,
    -- | Specifies the POSIX group ID (GID) of the file\'s owners.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html#metadata-copied Metadata copied by DataSync>.
    --
    -- Default value: @INT_VALUE@. This preserves the integer value of the ID.
    --
    -- @INT_VALUE@: Preserve the integer value of user ID (UID) and GID
    -- (recommended).
    --
    -- @NONE@: Ignore UID and GID.
    Options -> Maybe Gid
gid :: Prelude.Maybe Gid,
    -- | Specifies the type of logs that DataSync publishes to a Amazon
    -- CloudWatch Logs log group. To specify the log group, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/API_CreateTask.html#DataSync-CreateTask-request-CloudWatchLogGroupArn CloudWatchLogGroupArn>.
    --
    -- If you set @LogLevel@ to @OFF@, no logs are published. @BASIC@ publishes
    -- logs on errors for individual files transferred. @TRANSFER@ publishes
    -- logs for every file or object that is transferred and integrity checked.
    Options -> Maybe LogLevel
logLevel :: Prelude.Maybe LogLevel,
    -- | Specifies whether to preserve metadata indicating the last time that a
    -- file was written to before the @PREPARING@ phase of your task execution.
    -- This option is required when you need to run the a task more than once.
    --
    -- Default Value: @PRESERVE@
    --
    -- @PRESERVE@: Preserve original @Mtime@ (recommended)
    --
    -- @NONE@: Ignore @Mtime@.
    --
    -- If @Mtime@ is set to @PRESERVE@, @Atime@ must be set to @BEST_EFFORT@.
    --
    -- If @Mtime@ is set to @NONE@, @Atime@ must also be set to @NONE@.
    Options -> Maybe Mtime
mtime :: Prelude.Maybe Mtime,
    -- | Specifies whether object tags are preserved when transferring between
    -- object storage systems. If you want your DataSync task to ignore object
    -- tags, specify the @NONE@ value.
    --
    -- Default Value: @PRESERVE@
    Options -> Maybe ObjectTags
objectTags :: Prelude.Maybe ObjectTags,
    -- | Specifies whether data at the destination location should be overwritten
    -- or preserved. If set to @NEVER@, a destination file for example will not
    -- be replaced by a source file (even if the destination file differs from
    -- the source file). If you modify files in the destination and you sync
    -- the files, you can use this value to protect against overwriting those
    -- changes.
    --
    -- Some storage classes have specific behaviors that can affect your Amazon
    -- S3 storage cost. For detailed information, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Considerations when working with Amazon S3 storage classes in DataSync>
    -- .
    Options -> Maybe OverwriteMode
overwriteMode :: Prelude.Maybe OverwriteMode,
    -- | Specifies which users or groups can access a file for a specific purpose
    -- such as reading, writing, or execution of the file.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html#metadata-copied Metadata copied by DataSync>.
    --
    -- Default value: @PRESERVE@
    --
    -- @PRESERVE@: Preserve POSIX-style permissions (recommended).
    --
    -- @NONE@: Ignore permissions.
    --
    -- DataSync can preserve extant permissions of a source location.
    Options -> Maybe PosixPermissions
posixPermissions :: Prelude.Maybe PosixPermissions,
    -- | Specifies whether files in the destination location that don\'t exist in
    -- the source should be preserved. This option can affect your Amazon S3
    -- storage cost. If your task deletes objects, you might incur minimum
    -- storage duration charges for certain storage classes. For detailed
    -- information, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Considerations when working with Amazon S3 storage classes in DataSync>
    -- .
    --
    -- Default value: @PRESERVE@
    --
    -- @PRESERVE@: Ignore such destination files (recommended).
    --
    -- @REMOVE@: Delete destination files that aren’t present in the source.
    Options -> Maybe PreserveDeletedFiles
preserveDeletedFiles :: Prelude.Maybe PreserveDeletedFiles,
    -- | Specifies whether DataSync should preserve the metadata of block and
    -- character devices in the source location and recreate the files with
    -- that device name and metadata on the destination. DataSync copies only
    -- the name and metadata of such devices.
    --
    -- DataSync can\'t copy the actual contents of these devices because
    -- they\'re nonterminal and don\'t return an end-of-file (EOF) marker.
    --
    -- Default value: @NONE@
    --
    -- @NONE@: Ignore special devices (recommended).
    --
    -- @PRESERVE@: Preserve character and block device metadata. This option
    -- currently isn\'t supported for Amazon EFS.
    Options -> Maybe PreserveDevices
preserveDevices :: Prelude.Maybe PreserveDevices,
    -- | Specifies which components of the SMB security descriptor are copied
    -- from source to destination objects.
    --
    -- This value is only used for transfers between SMB and Amazon FSx for
    -- Windows File Server locations or between two FSx for Windows File Server
    -- locations. For more information, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html how DataSync handles metadata>.
    --
    -- Default value: @OWNER_DACL@
    --
    -- @OWNER_DACL@: For each copied object, DataSync copies the following
    -- metadata:
    --
    -- -   The object owner.
    --
    -- -   NTFS discretionary access control lists (DACLs), which determine
    --     whether to grant access to an object.
    --
    --     DataSync won\'t copy NTFS system access control lists (SACLs) with
    --     this option.
    --
    -- @OWNER_DACL_SACL@: For each copied object, DataSync copies the following
    -- metadata:
    --
    -- -   The object owner.
    --
    -- -   NTFS discretionary access control lists (DACLs), which determine
    --     whether to grant access to an object.
    --
    -- -   SACLs, which are used by administrators to log attempts to access a
    --     secured object.
    --
    --     Copying SACLs requires granting additional permissions to the
    --     Windows user that DataSync uses to access your SMB location. For
    --     information about choosing a user that ensures sufficient
    --     permissions to files, folders, and metadata, see
    --     <create-smb-location.html#SMBuser user>.
    --
    -- @NONE@: None of the SMB security descriptor components are copied.
    -- Destination objects are owned by the user that was provided for
    -- accessing the destination location. DACLs and SACLs are set based on the
    -- destination server’s configuration.
    Options -> Maybe SmbSecurityDescriptorCopyFlags
securityDescriptorCopyFlags :: Prelude.Maybe SmbSecurityDescriptorCopyFlags,
    -- | Specifies whether tasks should be queued before executing the tasks. The
    -- default is @ENABLED@, which means the tasks will be queued.
    --
    -- If you use the same agent to run multiple tasks, you can enable the
    -- tasks to run in series. For more information, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/run-task.html#queue-task-execution Queueing task executions>.
    Options -> Maybe TaskQueueing
taskQueueing :: Prelude.Maybe TaskQueueing,
    -- | Determines whether DataSync transfers only the data and metadata that
    -- differ between the source and the destination location or transfers all
    -- the content from the source (without comparing what\'s in the
    -- destination).
    --
    -- @CHANGED@: DataSync copies only data or metadata that is new or
    -- different content from the source location to the destination location.
    --
    -- @ALL@: DataSync copies all source location content to the destination
    -- (without comparing what\'s in the destination).
    Options -> Maybe TransferMode
transferMode :: Prelude.Maybe TransferMode,
    -- | Specifies the POSIX user ID (UID) of the file\'s owner.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html#metadata-copied Metadata copied by DataSync>.
    --
    -- Default value: @INT_VALUE@. This preserves the integer value of the ID.
    --
    -- @INT_VALUE@: Preserve the integer value of UID and group ID (GID)
    -- (recommended).
    --
    -- @NONE@: Ignore UID and GID.
    Options -> Maybe Uid
uid :: Prelude.Maybe Uid,
    -- | Specifies how and when DataSync checks the integrity of your data during
    -- a transfer.
    --
    -- Default value: @POINT_IN_TIME_CONSISTENT@
    --
    -- @ONLY_FILES_TRANSFERRED@ (recommended): DataSync calculates the checksum
    -- of transferred files and metadata at the source location. At the end of
    -- the transfer, DataSync then compares this checksum to the checksum
    -- calculated on those files at the destination.
    --
    -- We recommend this option when transferring to S3 Glacier Flexible
    -- Retrieval or S3 Glacier Deep Archive storage classes. For more
    -- information, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Storage class considerations with Amazon S3 locations>.
    --
    -- @POINT_IN_TIME_CONSISTENT@: At the end of the transfer, DataSync scans
    -- the entire source and destination to verify that both locations are
    -- fully synchronized.
    --
    -- You can\'t use this option when transferring to S3 Glacier Flexible
    -- Retrieval or S3 Glacier Deep Archive storage classes. For more
    -- information, see
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Storage class considerations with Amazon S3 locations>.
    --
    -- @NONE@: DataSync doesn\'t run additional verification at the end of the
    -- transfer. All data transmissions are still integrity-checked with
    -- checksum verification during the transfer.
    Options -> Maybe VerifyMode
verifyMode :: Prelude.Maybe VerifyMode
  }
  deriving (Options -> Options -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Options -> Options -> Bool
$c/= :: Options -> Options -> Bool
== :: Options -> Options -> Bool
$c== :: Options -> Options -> Bool
Prelude.Eq, ReadPrec [Options]
ReadPrec Options
Int -> ReadS Options
ReadS [Options]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Options]
$creadListPrec :: ReadPrec [Options]
readPrec :: ReadPrec Options
$creadPrec :: ReadPrec Options
readList :: ReadS [Options]
$creadList :: ReadS [Options]
readsPrec :: Int -> ReadS Options
$creadsPrec :: Int -> ReadS Options
Prelude.Read, Int -> Options -> ShowS
[Options] -> ShowS
Options -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Options] -> ShowS
$cshowList :: [Options] -> ShowS
show :: Options -> String
$cshow :: Options -> String
showsPrec :: Int -> Options -> ShowS
$cshowsPrec :: Int -> Options -> ShowS
Prelude.Show, forall x. Rep Options x -> Options
forall x. Options -> Rep Options x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Options x -> Options
$cfrom :: forall x. Options -> Rep Options x
Prelude.Generic)

-- |
-- Create a value of 'Options' 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:
--
-- 'atime', 'options_atime' - Specifies whether to preserve metadata indicating the last time a file
-- was read or written to. If you set @Atime@ to @BEST_EFFORT@, DataSync
-- attempts to preserve the original @Atime@ attribute on all source files
-- (that is, the version before the @PREPARING@ phase of the task
-- execution).
--
-- The behavior of @Atime@ isn\'t fully standard across platforms, so
-- DataSync can only do this on a best-effort basis.
--
-- Default value: @BEST_EFFORT@
--
-- @BEST_EFFORT@: Attempt to preserve the per-file @Atime@ value
-- (recommended).
--
-- @NONE@: Ignore @Atime@.
--
-- If @Atime@ is set to @BEST_EFFORT@, @Mtime@ must be set to @PRESERVE@.
--
-- If @Atime@ is set to @NONE@, @Mtime@ must also be @NONE@.
--
-- 'bytesPerSecond', 'options_bytesPerSecond' - Limits the bandwidth used by a DataSync task. For example, if you want
-- DataSync to use a maximum of 1 MB, set this value to @1048576@
-- (@=1024*1024@).
--
-- 'gid', 'options_gid' - Specifies the POSIX group ID (GID) of the file\'s owners.
--
-- For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html#metadata-copied Metadata copied by DataSync>.
--
-- Default value: @INT_VALUE@. This preserves the integer value of the ID.
--
-- @INT_VALUE@: Preserve the integer value of user ID (UID) and GID
-- (recommended).
--
-- @NONE@: Ignore UID and GID.
--
-- 'logLevel', 'options_logLevel' - Specifies the type of logs that DataSync publishes to a Amazon
-- CloudWatch Logs log group. To specify the log group, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/API_CreateTask.html#DataSync-CreateTask-request-CloudWatchLogGroupArn CloudWatchLogGroupArn>.
--
-- If you set @LogLevel@ to @OFF@, no logs are published. @BASIC@ publishes
-- logs on errors for individual files transferred. @TRANSFER@ publishes
-- logs for every file or object that is transferred and integrity checked.
--
-- 'mtime', 'options_mtime' - Specifies whether to preserve metadata indicating the last time that a
-- file was written to before the @PREPARING@ phase of your task execution.
-- This option is required when you need to run the a task more than once.
--
-- Default Value: @PRESERVE@
--
-- @PRESERVE@: Preserve original @Mtime@ (recommended)
--
-- @NONE@: Ignore @Mtime@.
--
-- If @Mtime@ is set to @PRESERVE@, @Atime@ must be set to @BEST_EFFORT@.
--
-- If @Mtime@ is set to @NONE@, @Atime@ must also be set to @NONE@.
--
-- 'objectTags', 'options_objectTags' - Specifies whether object tags are preserved when transferring between
-- object storage systems. If you want your DataSync task to ignore object
-- tags, specify the @NONE@ value.
--
-- Default Value: @PRESERVE@
--
-- 'overwriteMode', 'options_overwriteMode' - Specifies whether data at the destination location should be overwritten
-- or preserved. If set to @NEVER@, a destination file for example will not
-- be replaced by a source file (even if the destination file differs from
-- the source file). If you modify files in the destination and you sync
-- the files, you can use this value to protect against overwriting those
-- changes.
--
-- Some storage classes have specific behaviors that can affect your Amazon
-- S3 storage cost. For detailed information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Considerations when working with Amazon S3 storage classes in DataSync>
-- .
--
-- 'posixPermissions', 'options_posixPermissions' - Specifies which users or groups can access a file for a specific purpose
-- such as reading, writing, or execution of the file.
--
-- For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html#metadata-copied Metadata copied by DataSync>.
--
-- Default value: @PRESERVE@
--
-- @PRESERVE@: Preserve POSIX-style permissions (recommended).
--
-- @NONE@: Ignore permissions.
--
-- DataSync can preserve extant permissions of a source location.
--
-- 'preserveDeletedFiles', 'options_preserveDeletedFiles' - Specifies whether files in the destination location that don\'t exist in
-- the source should be preserved. This option can affect your Amazon S3
-- storage cost. If your task deletes objects, you might incur minimum
-- storage duration charges for certain storage classes. For detailed
-- information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Considerations when working with Amazon S3 storage classes in DataSync>
-- .
--
-- Default value: @PRESERVE@
--
-- @PRESERVE@: Ignore such destination files (recommended).
--
-- @REMOVE@: Delete destination files that aren’t present in the source.
--
-- 'preserveDevices', 'options_preserveDevices' - Specifies whether DataSync should preserve the metadata of block and
-- character devices in the source location and recreate the files with
-- that device name and metadata on the destination. DataSync copies only
-- the name and metadata of such devices.
--
-- DataSync can\'t copy the actual contents of these devices because
-- they\'re nonterminal and don\'t return an end-of-file (EOF) marker.
--
-- Default value: @NONE@
--
-- @NONE@: Ignore special devices (recommended).
--
-- @PRESERVE@: Preserve character and block device metadata. This option
-- currently isn\'t supported for Amazon EFS.
--
-- 'securityDescriptorCopyFlags', 'options_securityDescriptorCopyFlags' - Specifies which components of the SMB security descriptor are copied
-- from source to destination objects.
--
-- This value is only used for transfers between SMB and Amazon FSx for
-- Windows File Server locations or between two FSx for Windows File Server
-- locations. For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html how DataSync handles metadata>.
--
-- Default value: @OWNER_DACL@
--
-- @OWNER_DACL@: For each copied object, DataSync copies the following
-- metadata:
--
-- -   The object owner.
--
-- -   NTFS discretionary access control lists (DACLs), which determine
--     whether to grant access to an object.
--
--     DataSync won\'t copy NTFS system access control lists (SACLs) with
--     this option.
--
-- @OWNER_DACL_SACL@: For each copied object, DataSync copies the following
-- metadata:
--
-- -   The object owner.
--
-- -   NTFS discretionary access control lists (DACLs), which determine
--     whether to grant access to an object.
--
-- -   SACLs, which are used by administrators to log attempts to access a
--     secured object.
--
--     Copying SACLs requires granting additional permissions to the
--     Windows user that DataSync uses to access your SMB location. For
--     information about choosing a user that ensures sufficient
--     permissions to files, folders, and metadata, see
--     <create-smb-location.html#SMBuser user>.
--
-- @NONE@: None of the SMB security descriptor components are copied.
-- Destination objects are owned by the user that was provided for
-- accessing the destination location. DACLs and SACLs are set based on the
-- destination server’s configuration.
--
-- 'taskQueueing', 'options_taskQueueing' - Specifies whether tasks should be queued before executing the tasks. The
-- default is @ENABLED@, which means the tasks will be queued.
--
-- If you use the same agent to run multiple tasks, you can enable the
-- tasks to run in series. For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/run-task.html#queue-task-execution Queueing task executions>.
--
-- 'transferMode', 'options_transferMode' - Determines whether DataSync transfers only the data and metadata that
-- differ between the source and the destination location or transfers all
-- the content from the source (without comparing what\'s in the
-- destination).
--
-- @CHANGED@: DataSync copies only data or metadata that is new or
-- different content from the source location to the destination location.
--
-- @ALL@: DataSync copies all source location content to the destination
-- (without comparing what\'s in the destination).
--
-- 'uid', 'options_uid' - Specifies the POSIX user ID (UID) of the file\'s owner.
--
-- For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html#metadata-copied Metadata copied by DataSync>.
--
-- Default value: @INT_VALUE@. This preserves the integer value of the ID.
--
-- @INT_VALUE@: Preserve the integer value of UID and group ID (GID)
-- (recommended).
--
-- @NONE@: Ignore UID and GID.
--
-- 'verifyMode', 'options_verifyMode' - Specifies how and when DataSync checks the integrity of your data during
-- a transfer.
--
-- Default value: @POINT_IN_TIME_CONSISTENT@
--
-- @ONLY_FILES_TRANSFERRED@ (recommended): DataSync calculates the checksum
-- of transferred files and metadata at the source location. At the end of
-- the transfer, DataSync then compares this checksum to the checksum
-- calculated on those files at the destination.
--
-- We recommend this option when transferring to S3 Glacier Flexible
-- Retrieval or S3 Glacier Deep Archive storage classes. For more
-- information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Storage class considerations with Amazon S3 locations>.
--
-- @POINT_IN_TIME_CONSISTENT@: At the end of the transfer, DataSync scans
-- the entire source and destination to verify that both locations are
-- fully synchronized.
--
-- You can\'t use this option when transferring to S3 Glacier Flexible
-- Retrieval or S3 Glacier Deep Archive storage classes. For more
-- information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Storage class considerations with Amazon S3 locations>.
--
-- @NONE@: DataSync doesn\'t run additional verification at the end of the
-- transfer. All data transmissions are still integrity-checked with
-- checksum verification during the transfer.
newOptions ::
  Options
newOptions :: Options
newOptions =
  Options'
    { $sel:atime:Options' :: Maybe Atime
atime = forall a. Maybe a
Prelude.Nothing,
      $sel:bytesPerSecond:Options' :: Maybe Integer
bytesPerSecond = forall a. Maybe a
Prelude.Nothing,
      $sel:gid:Options' :: Maybe Gid
gid = forall a. Maybe a
Prelude.Nothing,
      $sel:logLevel:Options' :: Maybe LogLevel
logLevel = forall a. Maybe a
Prelude.Nothing,
      $sel:mtime:Options' :: Maybe Mtime
mtime = forall a. Maybe a
Prelude.Nothing,
      $sel:objectTags:Options' :: Maybe ObjectTags
objectTags = forall a. Maybe a
Prelude.Nothing,
      $sel:overwriteMode:Options' :: Maybe OverwriteMode
overwriteMode = forall a. Maybe a
Prelude.Nothing,
      $sel:posixPermissions:Options' :: Maybe PosixPermissions
posixPermissions = forall a. Maybe a
Prelude.Nothing,
      $sel:preserveDeletedFiles:Options' :: Maybe PreserveDeletedFiles
preserveDeletedFiles = forall a. Maybe a
Prelude.Nothing,
      $sel:preserveDevices:Options' :: Maybe PreserveDevices
preserveDevices = forall a. Maybe a
Prelude.Nothing,
      $sel:securityDescriptorCopyFlags:Options' :: Maybe SmbSecurityDescriptorCopyFlags
securityDescriptorCopyFlags = forall a. Maybe a
Prelude.Nothing,
      $sel:taskQueueing:Options' :: Maybe TaskQueueing
taskQueueing = forall a. Maybe a
Prelude.Nothing,
      $sel:transferMode:Options' :: Maybe TransferMode
transferMode = forall a. Maybe a
Prelude.Nothing,
      $sel:uid:Options' :: Maybe Uid
uid = forall a. Maybe a
Prelude.Nothing,
      $sel:verifyMode:Options' :: Maybe VerifyMode
verifyMode = forall a. Maybe a
Prelude.Nothing
    }

-- | Specifies whether to preserve metadata indicating the last time a file
-- was read or written to. If you set @Atime@ to @BEST_EFFORT@, DataSync
-- attempts to preserve the original @Atime@ attribute on all source files
-- (that is, the version before the @PREPARING@ phase of the task
-- execution).
--
-- The behavior of @Atime@ isn\'t fully standard across platforms, so
-- DataSync can only do this on a best-effort basis.
--
-- Default value: @BEST_EFFORT@
--
-- @BEST_EFFORT@: Attempt to preserve the per-file @Atime@ value
-- (recommended).
--
-- @NONE@: Ignore @Atime@.
--
-- If @Atime@ is set to @BEST_EFFORT@, @Mtime@ must be set to @PRESERVE@.
--
-- If @Atime@ is set to @NONE@, @Mtime@ must also be @NONE@.
options_atime :: Lens.Lens' Options (Prelude.Maybe Atime)
options_atime :: Lens' Options (Maybe Atime)
options_atime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe Atime
atime :: Maybe Atime
$sel:atime:Options' :: Options -> Maybe Atime
atime} -> Maybe Atime
atime) (\s :: Options
s@Options' {} Maybe Atime
a -> Options
s {$sel:atime:Options' :: Maybe Atime
atime = Maybe Atime
a} :: Options)

-- | Limits the bandwidth used by a DataSync task. For example, if you want
-- DataSync to use a maximum of 1 MB, set this value to @1048576@
-- (@=1024*1024@).
options_bytesPerSecond :: Lens.Lens' Options (Prelude.Maybe Prelude.Integer)
options_bytesPerSecond :: Lens' Options (Maybe Integer)
options_bytesPerSecond = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe Integer
bytesPerSecond :: Maybe Integer
$sel:bytesPerSecond:Options' :: Options -> Maybe Integer
bytesPerSecond} -> Maybe Integer
bytesPerSecond) (\s :: Options
s@Options' {} Maybe Integer
a -> Options
s {$sel:bytesPerSecond:Options' :: Maybe Integer
bytesPerSecond = Maybe Integer
a} :: Options)

-- | Specifies the POSIX group ID (GID) of the file\'s owners.
--
-- For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html#metadata-copied Metadata copied by DataSync>.
--
-- Default value: @INT_VALUE@. This preserves the integer value of the ID.
--
-- @INT_VALUE@: Preserve the integer value of user ID (UID) and GID
-- (recommended).
--
-- @NONE@: Ignore UID and GID.
options_gid :: Lens.Lens' Options (Prelude.Maybe Gid)
options_gid :: Lens' Options (Maybe Gid)
options_gid = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe Gid
gid :: Maybe Gid
$sel:gid:Options' :: Options -> Maybe Gid
gid} -> Maybe Gid
gid) (\s :: Options
s@Options' {} Maybe Gid
a -> Options
s {$sel:gid:Options' :: Maybe Gid
gid = Maybe Gid
a} :: Options)

-- | Specifies the type of logs that DataSync publishes to a Amazon
-- CloudWatch Logs log group. To specify the log group, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/API_CreateTask.html#DataSync-CreateTask-request-CloudWatchLogGroupArn CloudWatchLogGroupArn>.
--
-- If you set @LogLevel@ to @OFF@, no logs are published. @BASIC@ publishes
-- logs on errors for individual files transferred. @TRANSFER@ publishes
-- logs for every file or object that is transferred and integrity checked.
options_logLevel :: Lens.Lens' Options (Prelude.Maybe LogLevel)
options_logLevel :: Lens' Options (Maybe LogLevel)
options_logLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe LogLevel
logLevel :: Maybe LogLevel
$sel:logLevel:Options' :: Options -> Maybe LogLevel
logLevel} -> Maybe LogLevel
logLevel) (\s :: Options
s@Options' {} Maybe LogLevel
a -> Options
s {$sel:logLevel:Options' :: Maybe LogLevel
logLevel = Maybe LogLevel
a} :: Options)

-- | Specifies whether to preserve metadata indicating the last time that a
-- file was written to before the @PREPARING@ phase of your task execution.
-- This option is required when you need to run the a task more than once.
--
-- Default Value: @PRESERVE@
--
-- @PRESERVE@: Preserve original @Mtime@ (recommended)
--
-- @NONE@: Ignore @Mtime@.
--
-- If @Mtime@ is set to @PRESERVE@, @Atime@ must be set to @BEST_EFFORT@.
--
-- If @Mtime@ is set to @NONE@, @Atime@ must also be set to @NONE@.
options_mtime :: Lens.Lens' Options (Prelude.Maybe Mtime)
options_mtime :: Lens' Options (Maybe Mtime)
options_mtime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe Mtime
mtime :: Maybe Mtime
$sel:mtime:Options' :: Options -> Maybe Mtime
mtime} -> Maybe Mtime
mtime) (\s :: Options
s@Options' {} Maybe Mtime
a -> Options
s {$sel:mtime:Options' :: Maybe Mtime
mtime = Maybe Mtime
a} :: Options)

-- | Specifies whether object tags are preserved when transferring between
-- object storage systems. If you want your DataSync task to ignore object
-- tags, specify the @NONE@ value.
--
-- Default Value: @PRESERVE@
options_objectTags :: Lens.Lens' Options (Prelude.Maybe ObjectTags)
options_objectTags :: Lens' Options (Maybe ObjectTags)
options_objectTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe ObjectTags
objectTags :: Maybe ObjectTags
$sel:objectTags:Options' :: Options -> Maybe ObjectTags
objectTags} -> Maybe ObjectTags
objectTags) (\s :: Options
s@Options' {} Maybe ObjectTags
a -> Options
s {$sel:objectTags:Options' :: Maybe ObjectTags
objectTags = Maybe ObjectTags
a} :: Options)

-- | Specifies whether data at the destination location should be overwritten
-- or preserved. If set to @NEVER@, a destination file for example will not
-- be replaced by a source file (even if the destination file differs from
-- the source file). If you modify files in the destination and you sync
-- the files, you can use this value to protect against overwriting those
-- changes.
--
-- Some storage classes have specific behaviors that can affect your Amazon
-- S3 storage cost. For detailed information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Considerations when working with Amazon S3 storage classes in DataSync>
-- .
options_overwriteMode :: Lens.Lens' Options (Prelude.Maybe OverwriteMode)
options_overwriteMode :: Lens' Options (Maybe OverwriteMode)
options_overwriteMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe OverwriteMode
overwriteMode :: Maybe OverwriteMode
$sel:overwriteMode:Options' :: Options -> Maybe OverwriteMode
overwriteMode} -> Maybe OverwriteMode
overwriteMode) (\s :: Options
s@Options' {} Maybe OverwriteMode
a -> Options
s {$sel:overwriteMode:Options' :: Maybe OverwriteMode
overwriteMode = Maybe OverwriteMode
a} :: Options)

-- | Specifies which users or groups can access a file for a specific purpose
-- such as reading, writing, or execution of the file.
--
-- For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html#metadata-copied Metadata copied by DataSync>.
--
-- Default value: @PRESERVE@
--
-- @PRESERVE@: Preserve POSIX-style permissions (recommended).
--
-- @NONE@: Ignore permissions.
--
-- DataSync can preserve extant permissions of a source location.
options_posixPermissions :: Lens.Lens' Options (Prelude.Maybe PosixPermissions)
options_posixPermissions :: Lens' Options (Maybe PosixPermissions)
options_posixPermissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe PosixPermissions
posixPermissions :: Maybe PosixPermissions
$sel:posixPermissions:Options' :: Options -> Maybe PosixPermissions
posixPermissions} -> Maybe PosixPermissions
posixPermissions) (\s :: Options
s@Options' {} Maybe PosixPermissions
a -> Options
s {$sel:posixPermissions:Options' :: Maybe PosixPermissions
posixPermissions = Maybe PosixPermissions
a} :: Options)

-- | Specifies whether files in the destination location that don\'t exist in
-- the source should be preserved. This option can affect your Amazon S3
-- storage cost. If your task deletes objects, you might incur minimum
-- storage duration charges for certain storage classes. For detailed
-- information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Considerations when working with Amazon S3 storage classes in DataSync>
-- .
--
-- Default value: @PRESERVE@
--
-- @PRESERVE@: Ignore such destination files (recommended).
--
-- @REMOVE@: Delete destination files that aren’t present in the source.
options_preserveDeletedFiles :: Lens.Lens' Options (Prelude.Maybe PreserveDeletedFiles)
options_preserveDeletedFiles :: Lens' Options (Maybe PreserveDeletedFiles)
options_preserveDeletedFiles = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe PreserveDeletedFiles
preserveDeletedFiles :: Maybe PreserveDeletedFiles
$sel:preserveDeletedFiles:Options' :: Options -> Maybe PreserveDeletedFiles
preserveDeletedFiles} -> Maybe PreserveDeletedFiles
preserveDeletedFiles) (\s :: Options
s@Options' {} Maybe PreserveDeletedFiles
a -> Options
s {$sel:preserveDeletedFiles:Options' :: Maybe PreserveDeletedFiles
preserveDeletedFiles = Maybe PreserveDeletedFiles
a} :: Options)

-- | Specifies whether DataSync should preserve the metadata of block and
-- character devices in the source location and recreate the files with
-- that device name and metadata on the destination. DataSync copies only
-- the name and metadata of such devices.
--
-- DataSync can\'t copy the actual contents of these devices because
-- they\'re nonterminal and don\'t return an end-of-file (EOF) marker.
--
-- Default value: @NONE@
--
-- @NONE@: Ignore special devices (recommended).
--
-- @PRESERVE@: Preserve character and block device metadata. This option
-- currently isn\'t supported for Amazon EFS.
options_preserveDevices :: Lens.Lens' Options (Prelude.Maybe PreserveDevices)
options_preserveDevices :: Lens' Options (Maybe PreserveDevices)
options_preserveDevices = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe PreserveDevices
preserveDevices :: Maybe PreserveDevices
$sel:preserveDevices:Options' :: Options -> Maybe PreserveDevices
preserveDevices} -> Maybe PreserveDevices
preserveDevices) (\s :: Options
s@Options' {} Maybe PreserveDevices
a -> Options
s {$sel:preserveDevices:Options' :: Maybe PreserveDevices
preserveDevices = Maybe PreserveDevices
a} :: Options)

-- | Specifies which components of the SMB security descriptor are copied
-- from source to destination objects.
--
-- This value is only used for transfers between SMB and Amazon FSx for
-- Windows File Server locations or between two FSx for Windows File Server
-- locations. For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html how DataSync handles metadata>.
--
-- Default value: @OWNER_DACL@
--
-- @OWNER_DACL@: For each copied object, DataSync copies the following
-- metadata:
--
-- -   The object owner.
--
-- -   NTFS discretionary access control lists (DACLs), which determine
--     whether to grant access to an object.
--
--     DataSync won\'t copy NTFS system access control lists (SACLs) with
--     this option.
--
-- @OWNER_DACL_SACL@: For each copied object, DataSync copies the following
-- metadata:
--
-- -   The object owner.
--
-- -   NTFS discretionary access control lists (DACLs), which determine
--     whether to grant access to an object.
--
-- -   SACLs, which are used by administrators to log attempts to access a
--     secured object.
--
--     Copying SACLs requires granting additional permissions to the
--     Windows user that DataSync uses to access your SMB location. For
--     information about choosing a user that ensures sufficient
--     permissions to files, folders, and metadata, see
--     <create-smb-location.html#SMBuser user>.
--
-- @NONE@: None of the SMB security descriptor components are copied.
-- Destination objects are owned by the user that was provided for
-- accessing the destination location. DACLs and SACLs are set based on the
-- destination server’s configuration.
options_securityDescriptorCopyFlags :: Lens.Lens' Options (Prelude.Maybe SmbSecurityDescriptorCopyFlags)
options_securityDescriptorCopyFlags :: Lens' Options (Maybe SmbSecurityDescriptorCopyFlags)
options_securityDescriptorCopyFlags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe SmbSecurityDescriptorCopyFlags
securityDescriptorCopyFlags :: Maybe SmbSecurityDescriptorCopyFlags
$sel:securityDescriptorCopyFlags:Options' :: Options -> Maybe SmbSecurityDescriptorCopyFlags
securityDescriptorCopyFlags} -> Maybe SmbSecurityDescriptorCopyFlags
securityDescriptorCopyFlags) (\s :: Options
s@Options' {} Maybe SmbSecurityDescriptorCopyFlags
a -> Options
s {$sel:securityDescriptorCopyFlags:Options' :: Maybe SmbSecurityDescriptorCopyFlags
securityDescriptorCopyFlags = Maybe SmbSecurityDescriptorCopyFlags
a} :: Options)

-- | Specifies whether tasks should be queued before executing the tasks. The
-- default is @ENABLED@, which means the tasks will be queued.
--
-- If you use the same agent to run multiple tasks, you can enable the
-- tasks to run in series. For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/run-task.html#queue-task-execution Queueing task executions>.
options_taskQueueing :: Lens.Lens' Options (Prelude.Maybe TaskQueueing)
options_taskQueueing :: Lens' Options (Maybe TaskQueueing)
options_taskQueueing = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe TaskQueueing
taskQueueing :: Maybe TaskQueueing
$sel:taskQueueing:Options' :: Options -> Maybe TaskQueueing
taskQueueing} -> Maybe TaskQueueing
taskQueueing) (\s :: Options
s@Options' {} Maybe TaskQueueing
a -> Options
s {$sel:taskQueueing:Options' :: Maybe TaskQueueing
taskQueueing = Maybe TaskQueueing
a} :: Options)

-- | Determines whether DataSync transfers only the data and metadata that
-- differ between the source and the destination location or transfers all
-- the content from the source (without comparing what\'s in the
-- destination).
--
-- @CHANGED@: DataSync copies only data or metadata that is new or
-- different content from the source location to the destination location.
--
-- @ALL@: DataSync copies all source location content to the destination
-- (without comparing what\'s in the destination).
options_transferMode :: Lens.Lens' Options (Prelude.Maybe TransferMode)
options_transferMode :: Lens' Options (Maybe TransferMode)
options_transferMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe TransferMode
transferMode :: Maybe TransferMode
$sel:transferMode:Options' :: Options -> Maybe TransferMode
transferMode} -> Maybe TransferMode
transferMode) (\s :: Options
s@Options' {} Maybe TransferMode
a -> Options
s {$sel:transferMode:Options' :: Maybe TransferMode
transferMode = Maybe TransferMode
a} :: Options)

-- | Specifies the POSIX user ID (UID) of the file\'s owner.
--
-- For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/special-files.html#metadata-copied Metadata copied by DataSync>.
--
-- Default value: @INT_VALUE@. This preserves the integer value of the ID.
--
-- @INT_VALUE@: Preserve the integer value of UID and group ID (GID)
-- (recommended).
--
-- @NONE@: Ignore UID and GID.
options_uid :: Lens.Lens' Options (Prelude.Maybe Uid)
options_uid :: Lens' Options (Maybe Uid)
options_uid = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe Uid
uid :: Maybe Uid
$sel:uid:Options' :: Options -> Maybe Uid
uid} -> Maybe Uid
uid) (\s :: Options
s@Options' {} Maybe Uid
a -> Options
s {$sel:uid:Options' :: Maybe Uid
uid = Maybe Uid
a} :: Options)

-- | Specifies how and when DataSync checks the integrity of your data during
-- a transfer.
--
-- Default value: @POINT_IN_TIME_CONSISTENT@
--
-- @ONLY_FILES_TRANSFERRED@ (recommended): DataSync calculates the checksum
-- of transferred files and metadata at the source location. At the end of
-- the transfer, DataSync then compares this checksum to the checksum
-- calculated on those files at the destination.
--
-- We recommend this option when transferring to S3 Glacier Flexible
-- Retrieval or S3 Glacier Deep Archive storage classes. For more
-- information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Storage class considerations with Amazon S3 locations>.
--
-- @POINT_IN_TIME_CONSISTENT@: At the end of the transfer, DataSync scans
-- the entire source and destination to verify that both locations are
-- fully synchronized.
--
-- You can\'t use this option when transferring to S3 Glacier Flexible
-- Retrieval or S3 Glacier Deep Archive storage classes. For more
-- information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/create-s3-location.html#using-storage-classes Storage class considerations with Amazon S3 locations>.
--
-- @NONE@: DataSync doesn\'t run additional verification at the end of the
-- transfer. All data transmissions are still integrity-checked with
-- checksum verification during the transfer.
options_verifyMode :: Lens.Lens' Options (Prelude.Maybe VerifyMode)
options_verifyMode :: Lens' Options (Maybe VerifyMode)
options_verifyMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Options' {Maybe VerifyMode
verifyMode :: Maybe VerifyMode
$sel:verifyMode:Options' :: Options -> Maybe VerifyMode
verifyMode} -> Maybe VerifyMode
verifyMode) (\s :: Options
s@Options' {} Maybe VerifyMode
a -> Options
s {$sel:verifyMode:Options' :: Maybe VerifyMode
verifyMode = Maybe VerifyMode
a} :: Options)

instance Data.FromJSON Options where
  parseJSON :: Value -> Parser Options
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Options"
      ( \Object
x ->
          Maybe Atime
-> Maybe Integer
-> Maybe Gid
-> Maybe LogLevel
-> Maybe Mtime
-> Maybe ObjectTags
-> Maybe OverwriteMode
-> Maybe PosixPermissions
-> Maybe PreserveDeletedFiles
-> Maybe PreserveDevices
-> Maybe SmbSecurityDescriptorCopyFlags
-> Maybe TaskQueueing
-> Maybe TransferMode
-> Maybe Uid
-> Maybe VerifyMode
-> Options
Options'
            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
"Atime")
            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
"BytesPerSecond")
            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
"Gid")
            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
"LogLevel")
            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
"Mtime")
            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
"ObjectTags")
            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
"OverwriteMode")
            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
"PosixPermissions")
            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
"PreserveDeletedFiles")
            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
"PreserveDevices")
            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
"SecurityDescriptorCopyFlags")
            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
"TaskQueueing")
            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
"TransferMode")
            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
"Uid")
            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
"VerifyMode")
      )

instance Prelude.Hashable Options where
  hashWithSalt :: Int -> Options -> Int
hashWithSalt Int
_salt Options' {Maybe Integer
Maybe Atime
Maybe Gid
Maybe LogLevel
Maybe Mtime
Maybe ObjectTags
Maybe OverwriteMode
Maybe PosixPermissions
Maybe PreserveDeletedFiles
Maybe PreserveDevices
Maybe SmbSecurityDescriptorCopyFlags
Maybe TaskQueueing
Maybe TransferMode
Maybe Uid
Maybe VerifyMode
verifyMode :: Maybe VerifyMode
uid :: Maybe Uid
transferMode :: Maybe TransferMode
taskQueueing :: Maybe TaskQueueing
securityDescriptorCopyFlags :: Maybe SmbSecurityDescriptorCopyFlags
preserveDevices :: Maybe PreserveDevices
preserveDeletedFiles :: Maybe PreserveDeletedFiles
posixPermissions :: Maybe PosixPermissions
overwriteMode :: Maybe OverwriteMode
objectTags :: Maybe ObjectTags
mtime :: Maybe Mtime
logLevel :: Maybe LogLevel
gid :: Maybe Gid
bytesPerSecond :: Maybe Integer
atime :: Maybe Atime
$sel:verifyMode:Options' :: Options -> Maybe VerifyMode
$sel:uid:Options' :: Options -> Maybe Uid
$sel:transferMode:Options' :: Options -> Maybe TransferMode
$sel:taskQueueing:Options' :: Options -> Maybe TaskQueueing
$sel:securityDescriptorCopyFlags:Options' :: Options -> Maybe SmbSecurityDescriptorCopyFlags
$sel:preserveDevices:Options' :: Options -> Maybe PreserveDevices
$sel:preserveDeletedFiles:Options' :: Options -> Maybe PreserveDeletedFiles
$sel:posixPermissions:Options' :: Options -> Maybe PosixPermissions
$sel:overwriteMode:Options' :: Options -> Maybe OverwriteMode
$sel:objectTags:Options' :: Options -> Maybe ObjectTags
$sel:mtime:Options' :: Options -> Maybe Mtime
$sel:logLevel:Options' :: Options -> Maybe LogLevel
$sel:gid:Options' :: Options -> Maybe Gid
$sel:bytesPerSecond:Options' :: Options -> Maybe Integer
$sel:atime:Options' :: Options -> Maybe Atime
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Atime
atime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
bytesPerSecond
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Gid
gid
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogLevel
logLevel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Mtime
mtime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ObjectTags
objectTags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OverwriteMode
overwriteMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PosixPermissions
posixPermissions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PreserveDeletedFiles
preserveDeletedFiles
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PreserveDevices
preserveDevices
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SmbSecurityDescriptorCopyFlags
securityDescriptorCopyFlags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskQueueing
taskQueueing
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TransferMode
transferMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Uid
uid
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VerifyMode
verifyMode

instance Prelude.NFData Options where
  rnf :: Options -> ()
rnf Options' {Maybe Integer
Maybe Atime
Maybe Gid
Maybe LogLevel
Maybe Mtime
Maybe ObjectTags
Maybe OverwriteMode
Maybe PosixPermissions
Maybe PreserveDeletedFiles
Maybe PreserveDevices
Maybe SmbSecurityDescriptorCopyFlags
Maybe TaskQueueing
Maybe TransferMode
Maybe Uid
Maybe VerifyMode
verifyMode :: Maybe VerifyMode
uid :: Maybe Uid
transferMode :: Maybe TransferMode
taskQueueing :: Maybe TaskQueueing
securityDescriptorCopyFlags :: Maybe SmbSecurityDescriptorCopyFlags
preserveDevices :: Maybe PreserveDevices
preserveDeletedFiles :: Maybe PreserveDeletedFiles
posixPermissions :: Maybe PosixPermissions
overwriteMode :: Maybe OverwriteMode
objectTags :: Maybe ObjectTags
mtime :: Maybe Mtime
logLevel :: Maybe LogLevel
gid :: Maybe Gid
bytesPerSecond :: Maybe Integer
atime :: Maybe Atime
$sel:verifyMode:Options' :: Options -> Maybe VerifyMode
$sel:uid:Options' :: Options -> Maybe Uid
$sel:transferMode:Options' :: Options -> Maybe TransferMode
$sel:taskQueueing:Options' :: Options -> Maybe TaskQueueing
$sel:securityDescriptorCopyFlags:Options' :: Options -> Maybe SmbSecurityDescriptorCopyFlags
$sel:preserveDevices:Options' :: Options -> Maybe PreserveDevices
$sel:preserveDeletedFiles:Options' :: Options -> Maybe PreserveDeletedFiles
$sel:posixPermissions:Options' :: Options -> Maybe PosixPermissions
$sel:overwriteMode:Options' :: Options -> Maybe OverwriteMode
$sel:objectTags:Options' :: Options -> Maybe ObjectTags
$sel:mtime:Options' :: Options -> Maybe Mtime
$sel:logLevel:Options' :: Options -> Maybe LogLevel
$sel:gid:Options' :: Options -> Maybe Gid
$sel:bytesPerSecond:Options' :: Options -> Maybe Integer
$sel:atime:Options' :: Options -> Maybe Atime
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Atime
atime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
bytesPerSecond
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Gid
gid
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogLevel
logLevel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Mtime
mtime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ObjectTags
objectTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OverwriteMode
overwriteMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PosixPermissions
posixPermissions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PreserveDeletedFiles
preserveDeletedFiles
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PreserveDevices
preserveDevices
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SmbSecurityDescriptorCopyFlags
securityDescriptorCopyFlags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TaskQueueing
taskQueueing
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TransferMode
transferMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Uid
uid
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VerifyMode
verifyMode

instance Data.ToJSON Options where
  toJSON :: Options -> Value
toJSON Options' {Maybe Integer
Maybe Atime
Maybe Gid
Maybe LogLevel
Maybe Mtime
Maybe ObjectTags
Maybe OverwriteMode
Maybe PosixPermissions
Maybe PreserveDeletedFiles
Maybe PreserveDevices
Maybe SmbSecurityDescriptorCopyFlags
Maybe TaskQueueing
Maybe TransferMode
Maybe Uid
Maybe VerifyMode
verifyMode :: Maybe VerifyMode
uid :: Maybe Uid
transferMode :: Maybe TransferMode
taskQueueing :: Maybe TaskQueueing
securityDescriptorCopyFlags :: Maybe SmbSecurityDescriptorCopyFlags
preserveDevices :: Maybe PreserveDevices
preserveDeletedFiles :: Maybe PreserveDeletedFiles
posixPermissions :: Maybe PosixPermissions
overwriteMode :: Maybe OverwriteMode
objectTags :: Maybe ObjectTags
mtime :: Maybe Mtime
logLevel :: Maybe LogLevel
gid :: Maybe Gid
bytesPerSecond :: Maybe Integer
atime :: Maybe Atime
$sel:verifyMode:Options' :: Options -> Maybe VerifyMode
$sel:uid:Options' :: Options -> Maybe Uid
$sel:transferMode:Options' :: Options -> Maybe TransferMode
$sel:taskQueueing:Options' :: Options -> Maybe TaskQueueing
$sel:securityDescriptorCopyFlags:Options' :: Options -> Maybe SmbSecurityDescriptorCopyFlags
$sel:preserveDevices:Options' :: Options -> Maybe PreserveDevices
$sel:preserveDeletedFiles:Options' :: Options -> Maybe PreserveDeletedFiles
$sel:posixPermissions:Options' :: Options -> Maybe PosixPermissions
$sel:overwriteMode:Options' :: Options -> Maybe OverwriteMode
$sel:objectTags:Options' :: Options -> Maybe ObjectTags
$sel:mtime:Options' :: Options -> Maybe Mtime
$sel:logLevel:Options' :: Options -> Maybe LogLevel
$sel:gid:Options' :: Options -> Maybe Gid
$sel:bytesPerSecond:Options' :: Options -> Maybe Integer
$sel:atime:Options' :: Options -> Maybe Atime
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Atime" 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 Atime
atime,
            (Key
"BytesPerSecond" 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 Integer
bytesPerSecond,
            (Key
"Gid" 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 Gid
gid,
            (Key
"LogLevel" 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 LogLevel
logLevel,
            (Key
"Mtime" 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 Mtime
mtime,
            (Key
"ObjectTags" 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 ObjectTags
objectTags,
            (Key
"OverwriteMode" 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 OverwriteMode
overwriteMode,
            (Key
"PosixPermissions" 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 PosixPermissions
posixPermissions,
            (Key
"PreserveDeletedFiles" 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 PreserveDeletedFiles
preserveDeletedFiles,
            (Key
"PreserveDevices" 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 PreserveDevices
preserveDevices,
            (Key
"SecurityDescriptorCopyFlags" 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 SmbSecurityDescriptorCopyFlags
securityDescriptorCopyFlags,
            (Key
"TaskQueueing" 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 TaskQueueing
taskQueueing,
            (Key
"TransferMode" 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 TransferMode
transferMode,
            (Key
"Uid" 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 Uid
uid,
            (Key
"VerifyMode" 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 VerifyMode
verifyMode
          ]
      )