{-# 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.DataRepositoryTask
-- 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.DataRepositoryTask 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.CompletionReport
import Amazonka.FSx.Types.DataRepositoryTaskFailureDetails
import Amazonka.FSx.Types.DataRepositoryTaskLifecycle
import Amazonka.FSx.Types.DataRepositoryTaskStatus
import Amazonka.FSx.Types.DataRepositoryTaskType
import Amazonka.FSx.Types.Tag
import qualified Amazonka.Prelude as Prelude

-- | A description of the data repository task. You use data repository tasks
-- to perform bulk transfer operations between an Amazon FSx for Lustre
-- file system and a linked data repository. An Amazon File Cache resource
-- uses a task to automatically release files from the cache.
--
-- /See:/ 'newDataRepositoryTask' smart constructor.
data DataRepositoryTask = DataRepositoryTask'
  { -- | Specifies the amount of data to release, in GiB, by an Amazon File Cache
    -- AUTO_RELEASE_DATA task that automatically releases files from the cache.
    DataRepositoryTask -> Maybe Natural
capacityToRelease :: Prelude.Maybe Prelude.Natural,
    -- | The time the system completed processing the task, populated after the
    -- task is complete.
    DataRepositoryTask -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | Failure message describing why the task failed, it is populated only
    -- when @Lifecycle@ is set to @FAILED@.
    DataRepositoryTask -> Maybe DataRepositoryTaskFailureDetails
failureDetails :: Prelude.Maybe DataRepositoryTaskFailureDetails,
    -- | The system-generated, unique ID of the cache.
    DataRepositoryTask -> Maybe Text
fileCacheId :: Prelude.Maybe Prelude.Text,
    -- | The globally unique ID of the file system.
    DataRepositoryTask -> Maybe Text
fileSystemId :: Prelude.Maybe Prelude.Text,
    -- | An array of paths that specify the data for the data repository task to
    -- process. For example, in an EXPORT_TO_REPOSITORY task, the paths specify
    -- which data to export to the linked data repository.
    --
    -- (Default) If @Paths@ is not specified, Amazon FSx uses the file system
    -- root directory.
    DataRepositoryTask -> Maybe [Text]
paths :: Prelude.Maybe [Prelude.Text],
    DataRepositoryTask -> Maybe CompletionReport
report :: Prelude.Maybe CompletionReport,
    DataRepositoryTask -> Maybe Text
resourceARN :: Prelude.Maybe Prelude.Text,
    -- | The time the system began processing the task.
    DataRepositoryTask -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | Provides the status of the number of files that the task has processed
    -- successfully and failed to process.
    DataRepositoryTask -> Maybe DataRepositoryTaskStatus
status :: Prelude.Maybe DataRepositoryTaskStatus,
    DataRepositoryTask -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | The system-generated, unique 17-digit ID of the data repository task.
    DataRepositoryTask -> Text
taskId :: Prelude.Text,
    -- | The lifecycle status of the data repository task, as follows:
    --
    -- -   @PENDING@ - The task has not started.
    --
    -- -   @EXECUTING@ - The task is in process.
    --
    -- -   @FAILED@ - The task was not able to be completed. For example, there
    --     may be files the task failed to process. The
    --     DataRepositoryTaskFailureDetails property provides more information
    --     about task failures.
    --
    -- -   @SUCCEEDED@ - The task has completed successfully.
    --
    -- -   @CANCELED@ - The task was canceled and it did not complete.
    --
    -- -   @CANCELING@ - The task is in process of being canceled.
    --
    -- You cannot delete an FSx for Lustre file system if there are data
    -- repository tasks for the file system in the @PENDING@ or @EXECUTING@
    -- states. Please retry when the data repository task is finished (with a
    -- status of @CANCELED@, @SUCCEEDED@, or @FAILED@). You can use the
    -- DescribeDataRepositoryTask action to monitor the task status. Contact
    -- the FSx team if you need to delete your file system immediately.
    DataRepositoryTask -> DataRepositoryTaskLifecycle
lifecycle :: DataRepositoryTaskLifecycle,
    -- | The type of data repository task.
    --
    -- -   @EXPORT_TO_REPOSITORY@ tasks export from your Amazon FSx for Lustre
    --     file system to a linked data repository.
    --
    -- -   @IMPORT_METADATA_FROM_REPOSITORY@ tasks import metadata changes from
    --     a linked S3 bucket to your Amazon FSx for Lustre file system.
    --
    -- -   @AUTO_RELEASE_DATA@ tasks automatically release files from an Amazon
    --     File Cache resource.
    DataRepositoryTask -> DataRepositoryTaskType
type' :: DataRepositoryTaskType,
    DataRepositoryTask -> POSIX
creationTime :: Data.POSIX
  }
  deriving (DataRepositoryTask -> DataRepositoryTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataRepositoryTask -> DataRepositoryTask -> Bool
$c/= :: DataRepositoryTask -> DataRepositoryTask -> Bool
== :: DataRepositoryTask -> DataRepositoryTask -> Bool
$c== :: DataRepositoryTask -> DataRepositoryTask -> Bool
Prelude.Eq, ReadPrec [DataRepositoryTask]
ReadPrec DataRepositoryTask
Int -> ReadS DataRepositoryTask
ReadS [DataRepositoryTask]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DataRepositoryTask]
$creadListPrec :: ReadPrec [DataRepositoryTask]
readPrec :: ReadPrec DataRepositoryTask
$creadPrec :: ReadPrec DataRepositoryTask
readList :: ReadS [DataRepositoryTask]
$creadList :: ReadS [DataRepositoryTask]
readsPrec :: Int -> ReadS DataRepositoryTask
$creadsPrec :: Int -> ReadS DataRepositoryTask
Prelude.Read, Int -> DataRepositoryTask -> ShowS
[DataRepositoryTask] -> ShowS
DataRepositoryTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataRepositoryTask] -> ShowS
$cshowList :: [DataRepositoryTask] -> ShowS
show :: DataRepositoryTask -> String
$cshow :: DataRepositoryTask -> String
showsPrec :: Int -> DataRepositoryTask -> ShowS
$cshowsPrec :: Int -> DataRepositoryTask -> ShowS
Prelude.Show, forall x. Rep DataRepositoryTask x -> DataRepositoryTask
forall x. DataRepositoryTask -> Rep DataRepositoryTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataRepositoryTask x -> DataRepositoryTask
$cfrom :: forall x. DataRepositoryTask -> Rep DataRepositoryTask x
Prelude.Generic)

-- |
-- Create a value of 'DataRepositoryTask' 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:
--
-- 'capacityToRelease', 'dataRepositoryTask_capacityToRelease' - Specifies the amount of data to release, in GiB, by an Amazon File Cache
-- AUTO_RELEASE_DATA task that automatically releases files from the cache.
--
-- 'endTime', 'dataRepositoryTask_endTime' - The time the system completed processing the task, populated after the
-- task is complete.
--
-- 'failureDetails', 'dataRepositoryTask_failureDetails' - Failure message describing why the task failed, it is populated only
-- when @Lifecycle@ is set to @FAILED@.
--
-- 'fileCacheId', 'dataRepositoryTask_fileCacheId' - The system-generated, unique ID of the cache.
--
-- 'fileSystemId', 'dataRepositoryTask_fileSystemId' - The globally unique ID of the file system.
--
-- 'paths', 'dataRepositoryTask_paths' - An array of paths that specify the data for the data repository task to
-- process. For example, in an EXPORT_TO_REPOSITORY task, the paths specify
-- which data to export to the linked data repository.
--
-- (Default) If @Paths@ is not specified, Amazon FSx uses the file system
-- root directory.
--
-- 'report', 'dataRepositoryTask_report' - Undocumented member.
--
-- 'resourceARN', 'dataRepositoryTask_resourceARN' - Undocumented member.
--
-- 'startTime', 'dataRepositoryTask_startTime' - The time the system began processing the task.
--
-- 'status', 'dataRepositoryTask_status' - Provides the status of the number of files that the task has processed
-- successfully and failed to process.
--
-- 'tags', 'dataRepositoryTask_tags' - Undocumented member.
--
-- 'taskId', 'dataRepositoryTask_taskId' - The system-generated, unique 17-digit ID of the data repository task.
--
-- 'lifecycle', 'dataRepositoryTask_lifecycle' - The lifecycle status of the data repository task, as follows:
--
-- -   @PENDING@ - The task has not started.
--
-- -   @EXECUTING@ - The task is in process.
--
-- -   @FAILED@ - The task was not able to be completed. For example, there
--     may be files the task failed to process. The
--     DataRepositoryTaskFailureDetails property provides more information
--     about task failures.
--
-- -   @SUCCEEDED@ - The task has completed successfully.
--
-- -   @CANCELED@ - The task was canceled and it did not complete.
--
-- -   @CANCELING@ - The task is in process of being canceled.
--
-- You cannot delete an FSx for Lustre file system if there are data
-- repository tasks for the file system in the @PENDING@ or @EXECUTING@
-- states. Please retry when the data repository task is finished (with a
-- status of @CANCELED@, @SUCCEEDED@, or @FAILED@). You can use the
-- DescribeDataRepositoryTask action to monitor the task status. Contact
-- the FSx team if you need to delete your file system immediately.
--
-- 'type'', 'dataRepositoryTask_type' - The type of data repository task.
--
-- -   @EXPORT_TO_REPOSITORY@ tasks export from your Amazon FSx for Lustre
--     file system to a linked data repository.
--
-- -   @IMPORT_METADATA_FROM_REPOSITORY@ tasks import metadata changes from
--     a linked S3 bucket to your Amazon FSx for Lustre file system.
--
-- -   @AUTO_RELEASE_DATA@ tasks automatically release files from an Amazon
--     File Cache resource.
--
-- 'creationTime', 'dataRepositoryTask_creationTime' - Undocumented member.
newDataRepositoryTask ::
  -- | 'taskId'
  Prelude.Text ->
  -- | 'lifecycle'
  DataRepositoryTaskLifecycle ->
  -- | 'type''
  DataRepositoryTaskType ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  DataRepositoryTask
newDataRepositoryTask :: Text
-> DataRepositoryTaskLifecycle
-> DataRepositoryTaskType
-> UTCTime
-> DataRepositoryTask
newDataRepositoryTask
  Text
pTaskId_
  DataRepositoryTaskLifecycle
pLifecycle_
  DataRepositoryTaskType
pType_
  UTCTime
pCreationTime_ =
    DataRepositoryTask'
      { $sel:capacityToRelease:DataRepositoryTask' :: Maybe Natural
capacityToRelease =
          forall a. Maybe a
Prelude.Nothing,
        $sel:endTime:DataRepositoryTask' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
        $sel:failureDetails:DataRepositoryTask' :: Maybe DataRepositoryTaskFailureDetails
failureDetails = forall a. Maybe a
Prelude.Nothing,
        $sel:fileCacheId:DataRepositoryTask' :: Maybe Text
fileCacheId = forall a. Maybe a
Prelude.Nothing,
        $sel:fileSystemId:DataRepositoryTask' :: Maybe Text
fileSystemId = forall a. Maybe a
Prelude.Nothing,
        $sel:paths:DataRepositoryTask' :: Maybe [Text]
paths = forall a. Maybe a
Prelude.Nothing,
        $sel:report:DataRepositoryTask' :: Maybe CompletionReport
report = forall a. Maybe a
Prelude.Nothing,
        $sel:resourceARN:DataRepositoryTask' :: Maybe Text
resourceARN = forall a. Maybe a
Prelude.Nothing,
        $sel:startTime:DataRepositoryTask' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
        $sel:status:DataRepositoryTask' :: Maybe DataRepositoryTaskStatus
status = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:DataRepositoryTask' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:taskId:DataRepositoryTask' :: Text
taskId = Text
pTaskId_,
        $sel:lifecycle:DataRepositoryTask' :: DataRepositoryTaskLifecycle
lifecycle = DataRepositoryTaskLifecycle
pLifecycle_,
        $sel:type':DataRepositoryTask' :: DataRepositoryTaskType
type' = DataRepositoryTaskType
pType_,
        $sel:creationTime:DataRepositoryTask' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_
      }

-- | Specifies the amount of data to release, in GiB, by an Amazon File Cache
-- AUTO_RELEASE_DATA task that automatically releases files from the cache.
dataRepositoryTask_capacityToRelease :: Lens.Lens' DataRepositoryTask (Prelude.Maybe Prelude.Natural)
dataRepositoryTask_capacityToRelease :: Lens' DataRepositoryTask (Maybe Natural)
dataRepositoryTask_capacityToRelease = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Maybe Natural
capacityToRelease :: Maybe Natural
$sel:capacityToRelease:DataRepositoryTask' :: DataRepositoryTask -> Maybe Natural
capacityToRelease} -> Maybe Natural
capacityToRelease) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Maybe Natural
a -> DataRepositoryTask
s {$sel:capacityToRelease:DataRepositoryTask' :: Maybe Natural
capacityToRelease = Maybe Natural
a} :: DataRepositoryTask)

-- | The time the system completed processing the task, populated after the
-- task is complete.
dataRepositoryTask_endTime :: Lens.Lens' DataRepositoryTask (Prelude.Maybe Prelude.UTCTime)
dataRepositoryTask_endTime :: Lens' DataRepositoryTask (Maybe UTCTime)
dataRepositoryTask_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:DataRepositoryTask' :: DataRepositoryTask -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Maybe POSIX
a -> DataRepositoryTask
s {$sel:endTime:DataRepositoryTask' :: Maybe POSIX
endTime = Maybe POSIX
a} :: DataRepositoryTask) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Failure message describing why the task failed, it is populated only
-- when @Lifecycle@ is set to @FAILED@.
dataRepositoryTask_failureDetails :: Lens.Lens' DataRepositoryTask (Prelude.Maybe DataRepositoryTaskFailureDetails)
dataRepositoryTask_failureDetails :: Lens' DataRepositoryTask (Maybe DataRepositoryTaskFailureDetails)
dataRepositoryTask_failureDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Maybe DataRepositoryTaskFailureDetails
failureDetails :: Maybe DataRepositoryTaskFailureDetails
$sel:failureDetails:DataRepositoryTask' :: DataRepositoryTask -> Maybe DataRepositoryTaskFailureDetails
failureDetails} -> Maybe DataRepositoryTaskFailureDetails
failureDetails) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Maybe DataRepositoryTaskFailureDetails
a -> DataRepositoryTask
s {$sel:failureDetails:DataRepositoryTask' :: Maybe DataRepositoryTaskFailureDetails
failureDetails = Maybe DataRepositoryTaskFailureDetails
a} :: DataRepositoryTask)

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

-- | The globally unique ID of the file system.
dataRepositoryTask_fileSystemId :: Lens.Lens' DataRepositoryTask (Prelude.Maybe Prelude.Text)
dataRepositoryTask_fileSystemId :: Lens' DataRepositoryTask (Maybe Text)
dataRepositoryTask_fileSystemId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Maybe Text
fileSystemId :: Maybe Text
$sel:fileSystemId:DataRepositoryTask' :: DataRepositoryTask -> Maybe Text
fileSystemId} -> Maybe Text
fileSystemId) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Maybe Text
a -> DataRepositoryTask
s {$sel:fileSystemId:DataRepositoryTask' :: Maybe Text
fileSystemId = Maybe Text
a} :: DataRepositoryTask)

-- | An array of paths that specify the data for the data repository task to
-- process. For example, in an EXPORT_TO_REPOSITORY task, the paths specify
-- which data to export to the linked data repository.
--
-- (Default) If @Paths@ is not specified, Amazon FSx uses the file system
-- root directory.
dataRepositoryTask_paths :: Lens.Lens' DataRepositoryTask (Prelude.Maybe [Prelude.Text])
dataRepositoryTask_paths :: Lens' DataRepositoryTask (Maybe [Text])
dataRepositoryTask_paths = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Maybe [Text]
paths :: Maybe [Text]
$sel:paths:DataRepositoryTask' :: DataRepositoryTask -> Maybe [Text]
paths} -> Maybe [Text]
paths) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Maybe [Text]
a -> DataRepositoryTask
s {$sel:paths:DataRepositoryTask' :: Maybe [Text]
paths = Maybe [Text]
a} :: DataRepositoryTask) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Undocumented member.
dataRepositoryTask_report :: Lens.Lens' DataRepositoryTask (Prelude.Maybe CompletionReport)
dataRepositoryTask_report :: Lens' DataRepositoryTask (Maybe CompletionReport)
dataRepositoryTask_report = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Maybe CompletionReport
report :: Maybe CompletionReport
$sel:report:DataRepositoryTask' :: DataRepositoryTask -> Maybe CompletionReport
report} -> Maybe CompletionReport
report) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Maybe CompletionReport
a -> DataRepositoryTask
s {$sel:report:DataRepositoryTask' :: Maybe CompletionReport
report = Maybe CompletionReport
a} :: DataRepositoryTask)

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

-- | The time the system began processing the task.
dataRepositoryTask_startTime :: Lens.Lens' DataRepositoryTask (Prelude.Maybe Prelude.UTCTime)
dataRepositoryTask_startTime :: Lens' DataRepositoryTask (Maybe UTCTime)
dataRepositoryTask_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:DataRepositoryTask' :: DataRepositoryTask -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Maybe POSIX
a -> DataRepositoryTask
s {$sel:startTime:DataRepositoryTask' :: Maybe POSIX
startTime = Maybe POSIX
a} :: DataRepositoryTask) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Provides the status of the number of files that the task has processed
-- successfully and failed to process.
dataRepositoryTask_status :: Lens.Lens' DataRepositoryTask (Prelude.Maybe DataRepositoryTaskStatus)
dataRepositoryTask_status :: Lens' DataRepositoryTask (Maybe DataRepositoryTaskStatus)
dataRepositoryTask_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Maybe DataRepositoryTaskStatus
status :: Maybe DataRepositoryTaskStatus
$sel:status:DataRepositoryTask' :: DataRepositoryTask -> Maybe DataRepositoryTaskStatus
status} -> Maybe DataRepositoryTaskStatus
status) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Maybe DataRepositoryTaskStatus
a -> DataRepositoryTask
s {$sel:status:DataRepositoryTask' :: Maybe DataRepositoryTaskStatus
status = Maybe DataRepositoryTaskStatus
a} :: DataRepositoryTask)

-- | Undocumented member.
dataRepositoryTask_tags :: Lens.Lens' DataRepositoryTask (Prelude.Maybe (Prelude.NonEmpty Tag))
dataRepositoryTask_tags :: Lens' DataRepositoryTask (Maybe (NonEmpty Tag))
dataRepositoryTask_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:DataRepositoryTask' :: DataRepositoryTask -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Maybe (NonEmpty Tag)
a -> DataRepositoryTask
s {$sel:tags:DataRepositoryTask' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: DataRepositoryTask) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The system-generated, unique 17-digit ID of the data repository task.
dataRepositoryTask_taskId :: Lens.Lens' DataRepositoryTask Prelude.Text
dataRepositoryTask_taskId :: Lens' DataRepositoryTask Text
dataRepositoryTask_taskId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {Text
taskId :: Text
$sel:taskId:DataRepositoryTask' :: DataRepositoryTask -> Text
taskId} -> Text
taskId) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} Text
a -> DataRepositoryTask
s {$sel:taskId:DataRepositoryTask' :: Text
taskId = Text
a} :: DataRepositoryTask)

-- | The lifecycle status of the data repository task, as follows:
--
-- -   @PENDING@ - The task has not started.
--
-- -   @EXECUTING@ - The task is in process.
--
-- -   @FAILED@ - The task was not able to be completed. For example, there
--     may be files the task failed to process. The
--     DataRepositoryTaskFailureDetails property provides more information
--     about task failures.
--
-- -   @SUCCEEDED@ - The task has completed successfully.
--
-- -   @CANCELED@ - The task was canceled and it did not complete.
--
-- -   @CANCELING@ - The task is in process of being canceled.
--
-- You cannot delete an FSx for Lustre file system if there are data
-- repository tasks for the file system in the @PENDING@ or @EXECUTING@
-- states. Please retry when the data repository task is finished (with a
-- status of @CANCELED@, @SUCCEEDED@, or @FAILED@). You can use the
-- DescribeDataRepositoryTask action to monitor the task status. Contact
-- the FSx team if you need to delete your file system immediately.
dataRepositoryTask_lifecycle :: Lens.Lens' DataRepositoryTask DataRepositoryTaskLifecycle
dataRepositoryTask_lifecycle :: Lens' DataRepositoryTask DataRepositoryTaskLifecycle
dataRepositoryTask_lifecycle = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {DataRepositoryTaskLifecycle
lifecycle :: DataRepositoryTaskLifecycle
$sel:lifecycle:DataRepositoryTask' :: DataRepositoryTask -> DataRepositoryTaskLifecycle
lifecycle} -> DataRepositoryTaskLifecycle
lifecycle) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} DataRepositoryTaskLifecycle
a -> DataRepositoryTask
s {$sel:lifecycle:DataRepositoryTask' :: DataRepositoryTaskLifecycle
lifecycle = DataRepositoryTaskLifecycle
a} :: DataRepositoryTask)

-- | The type of data repository task.
--
-- -   @EXPORT_TO_REPOSITORY@ tasks export from your Amazon FSx for Lustre
--     file system to a linked data repository.
--
-- -   @IMPORT_METADATA_FROM_REPOSITORY@ tasks import metadata changes from
--     a linked S3 bucket to your Amazon FSx for Lustre file system.
--
-- -   @AUTO_RELEASE_DATA@ tasks automatically release files from an Amazon
--     File Cache resource.
dataRepositoryTask_type :: Lens.Lens' DataRepositoryTask DataRepositoryTaskType
dataRepositoryTask_type :: Lens' DataRepositoryTask DataRepositoryTaskType
dataRepositoryTask_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {DataRepositoryTaskType
type' :: DataRepositoryTaskType
$sel:type':DataRepositoryTask' :: DataRepositoryTask -> DataRepositoryTaskType
type'} -> DataRepositoryTaskType
type') (\s :: DataRepositoryTask
s@DataRepositoryTask' {} DataRepositoryTaskType
a -> DataRepositoryTask
s {$sel:type':DataRepositoryTask' :: DataRepositoryTaskType
type' = DataRepositoryTaskType
a} :: DataRepositoryTask)

-- | Undocumented member.
dataRepositoryTask_creationTime :: Lens.Lens' DataRepositoryTask Prelude.UTCTime
dataRepositoryTask_creationTime :: Lens' DataRepositoryTask UTCTime
dataRepositoryTask_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataRepositoryTask' {POSIX
creationTime :: POSIX
$sel:creationTime:DataRepositoryTask' :: DataRepositoryTask -> POSIX
creationTime} -> POSIX
creationTime) (\s :: DataRepositoryTask
s@DataRepositoryTask' {} POSIX
a -> DataRepositoryTask
s {$sel:creationTime:DataRepositoryTask' :: POSIX
creationTime = POSIX
a} :: DataRepositoryTask) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromJSON DataRepositoryTask where
  parseJSON :: Value -> Parser DataRepositoryTask
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DataRepositoryTask"
      ( \Object
x ->
          Maybe Natural
-> Maybe POSIX
-> Maybe DataRepositoryTaskFailureDetails
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe CompletionReport
-> Maybe Text
-> Maybe POSIX
-> Maybe DataRepositoryTaskStatus
-> Maybe (NonEmpty Tag)
-> Text
-> DataRepositoryTaskLifecycle
-> DataRepositoryTaskType
-> POSIX
-> DataRepositoryTask
DataRepositoryTask'
            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
"CapacityToRelease")
            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
"EndTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FailureDetails")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FileCacheId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FileSystemId")
            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
"Paths" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Report")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ResourceARN")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StartTime")
            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
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Tags")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"TaskId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Lifecycle")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"CreationTime")
      )

instance Prelude.Hashable DataRepositoryTask where
  hashWithSalt :: Int -> DataRepositoryTask -> Int
hashWithSalt Int
_salt DataRepositoryTask' {Maybe Natural
Maybe [Text]
Maybe (NonEmpty Tag)
Maybe Text
Maybe POSIX
Maybe DataRepositoryTaskFailureDetails
Maybe DataRepositoryTaskStatus
Maybe CompletionReport
Text
POSIX
DataRepositoryTaskLifecycle
DataRepositoryTaskType
creationTime :: POSIX
type' :: DataRepositoryTaskType
lifecycle :: DataRepositoryTaskLifecycle
taskId :: Text
tags :: Maybe (NonEmpty Tag)
status :: Maybe DataRepositoryTaskStatus
startTime :: Maybe POSIX
resourceARN :: Maybe Text
report :: Maybe CompletionReport
paths :: Maybe [Text]
fileSystemId :: Maybe Text
fileCacheId :: Maybe Text
failureDetails :: Maybe DataRepositoryTaskFailureDetails
endTime :: Maybe POSIX
capacityToRelease :: Maybe Natural
$sel:creationTime:DataRepositoryTask' :: DataRepositoryTask -> POSIX
$sel:type':DataRepositoryTask' :: DataRepositoryTask -> DataRepositoryTaskType
$sel:lifecycle:DataRepositoryTask' :: DataRepositoryTask -> DataRepositoryTaskLifecycle
$sel:taskId:DataRepositoryTask' :: DataRepositoryTask -> Text
$sel:tags:DataRepositoryTask' :: DataRepositoryTask -> Maybe (NonEmpty Tag)
$sel:status:DataRepositoryTask' :: DataRepositoryTask -> Maybe DataRepositoryTaskStatus
$sel:startTime:DataRepositoryTask' :: DataRepositoryTask -> Maybe POSIX
$sel:resourceARN:DataRepositoryTask' :: DataRepositoryTask -> Maybe Text
$sel:report:DataRepositoryTask' :: DataRepositoryTask -> Maybe CompletionReport
$sel:paths:DataRepositoryTask' :: DataRepositoryTask -> Maybe [Text]
$sel:fileSystemId:DataRepositoryTask' :: DataRepositoryTask -> Maybe Text
$sel:fileCacheId:DataRepositoryTask' :: DataRepositoryTask -> Maybe Text
$sel:failureDetails:DataRepositoryTask' :: DataRepositoryTask -> Maybe DataRepositoryTaskFailureDetails
$sel:endTime:DataRepositoryTask' :: DataRepositoryTask -> Maybe POSIX
$sel:capacityToRelease:DataRepositoryTask' :: DataRepositoryTask -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
capacityToRelease
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataRepositoryTaskFailureDetails
failureDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fileCacheId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fileSystemId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
paths
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CompletionReport
report
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataRepositoryTaskStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
taskId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DataRepositoryTaskLifecycle
lifecycle
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DataRepositoryTaskType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
creationTime

instance Prelude.NFData DataRepositoryTask where
  rnf :: DataRepositoryTask -> ()
rnf DataRepositoryTask' {Maybe Natural
Maybe [Text]
Maybe (NonEmpty Tag)
Maybe Text
Maybe POSIX
Maybe DataRepositoryTaskFailureDetails
Maybe DataRepositoryTaskStatus
Maybe CompletionReport
Text
POSIX
DataRepositoryTaskLifecycle
DataRepositoryTaskType
creationTime :: POSIX
type' :: DataRepositoryTaskType
lifecycle :: DataRepositoryTaskLifecycle
taskId :: Text
tags :: Maybe (NonEmpty Tag)
status :: Maybe DataRepositoryTaskStatus
startTime :: Maybe POSIX
resourceARN :: Maybe Text
report :: Maybe CompletionReport
paths :: Maybe [Text]
fileSystemId :: Maybe Text
fileCacheId :: Maybe Text
failureDetails :: Maybe DataRepositoryTaskFailureDetails
endTime :: Maybe POSIX
capacityToRelease :: Maybe Natural
$sel:creationTime:DataRepositoryTask' :: DataRepositoryTask -> POSIX
$sel:type':DataRepositoryTask' :: DataRepositoryTask -> DataRepositoryTaskType
$sel:lifecycle:DataRepositoryTask' :: DataRepositoryTask -> DataRepositoryTaskLifecycle
$sel:taskId:DataRepositoryTask' :: DataRepositoryTask -> Text
$sel:tags:DataRepositoryTask' :: DataRepositoryTask -> Maybe (NonEmpty Tag)
$sel:status:DataRepositoryTask' :: DataRepositoryTask -> Maybe DataRepositoryTaskStatus
$sel:startTime:DataRepositoryTask' :: DataRepositoryTask -> Maybe POSIX
$sel:resourceARN:DataRepositoryTask' :: DataRepositoryTask -> Maybe Text
$sel:report:DataRepositoryTask' :: DataRepositoryTask -> Maybe CompletionReport
$sel:paths:DataRepositoryTask' :: DataRepositoryTask -> Maybe [Text]
$sel:fileSystemId:DataRepositoryTask' :: DataRepositoryTask -> Maybe Text
$sel:fileCacheId:DataRepositoryTask' :: DataRepositoryTask -> Maybe Text
$sel:failureDetails:DataRepositoryTask' :: DataRepositoryTask -> Maybe DataRepositoryTaskFailureDetails
$sel:endTime:DataRepositoryTask' :: DataRepositoryTask -> Maybe POSIX
$sel:capacityToRelease:DataRepositoryTask' :: DataRepositoryTask -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
capacityToRelease
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataRepositoryTaskFailureDetails
failureDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileCacheId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileSystemId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
paths
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CompletionReport
report
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataRepositoryTaskStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
taskId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DataRepositoryTaskLifecycle
lifecycle
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DataRepositoryTaskType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime