{-# 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.EFS.Types.FileSystemDescription
-- 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.EFS.Types.FileSystemDescription where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EFS.Types.FileSystemSize
import Amazonka.EFS.Types.LifeCycleState
import Amazonka.EFS.Types.PerformanceMode
import Amazonka.EFS.Types.Tag
import Amazonka.EFS.Types.ThroughputMode
import qualified Amazonka.Prelude as Prelude

-- | A description of the file system.
--
-- /See:/ 'newFileSystemDescription' smart constructor.
data FileSystemDescription = FileSystemDescription'
  { -- | The unique and consistent identifier of the Availability Zone in which
    -- the file system\'s One Zone storage classes exist. For example,
    -- @use1-az1@ is an Availability Zone ID for the us-east-1 Amazon Web
    -- Services Region, and it has the same location in every Amazon Web
    -- Services account.
    FileSystemDescription -> Maybe Text
availabilityZoneId :: Prelude.Maybe Prelude.Text,
    -- | Describes the Amazon Web Services Availability Zone in which the file
    -- system is located, and is valid only for file systems using One Zone
    -- storage classes. For more information, see
    -- <https://docs.aws.amazon.com/efs/latest/ug/storage-classes.html Using EFS storage classes>
    -- in the /Amazon EFS User Guide/.
    FileSystemDescription -> Maybe Text
availabilityZoneName :: Prelude.Maybe Prelude.Text,
    -- | A Boolean value that, if true, indicates that the file system is
    -- encrypted.
    FileSystemDescription -> Maybe Bool
encrypted :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) for the EFS file system, in the format
    -- @arn:aws:elasticfilesystem:@/@region@/@:@/@account-id@/@:file-system\/@/@file-system-id@/@ @.
    -- Example with sample data:
    -- @arn:aws:elasticfilesystem:us-west-2:1111333322228888:file-system\/fs-01234567@
    FileSystemDescription -> Maybe Text
fileSystemArn :: Prelude.Maybe Prelude.Text,
    -- | The ID of an KMS key used to protect the encrypted file system.
    FileSystemDescription -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | You can add tags to a file system, including a @Name@ tag. For more
    -- information, see CreateFileSystem. If the file system has a @Name@ tag,
    -- Amazon EFS returns the value in this field.
    FileSystemDescription -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The amount of provisioned throughput, measured in MiB\/s, for the file
    -- system. Valid for file systems using @ThroughputMode@ set to
    -- @provisioned@.
    FileSystemDescription -> Maybe Double
provisionedThroughputInMibps :: Prelude.Maybe Prelude.Double,
    -- | Displays the file system\'s throughput mode. For more information, see
    -- <https://docs.aws.amazon.com/efs/latest/ug/performance.html#throughput-modes Throughput modes>
    -- in the /Amazon EFS User Guide/.
    FileSystemDescription -> Maybe ThroughputMode
throughputMode :: Prelude.Maybe ThroughputMode,
    -- | The Amazon Web Services account that created the file system. If the
    -- file system was created by an IAM user, the parent account to which the
    -- user belongs is the owner.
    FileSystemDescription -> Text
ownerId :: Prelude.Text,
    -- | The opaque string specified in the request.
    FileSystemDescription -> Text
creationToken :: Prelude.Text,
    -- | The ID of the file system, assigned by Amazon EFS.
    FileSystemDescription -> Text
fileSystemId :: Prelude.Text,
    -- | The time that the file system was created, in seconds (since
    -- 1970-01-01T00:00:00Z).
    FileSystemDescription -> POSIX
creationTime :: Data.POSIX,
    -- | The lifecycle phase of the file system.
    FileSystemDescription -> LifeCycleState
lifeCycleState :: LifeCycleState,
    -- | The current number of mount targets that the file system has. For more
    -- information, see CreateMountTarget.
    FileSystemDescription -> Natural
numberOfMountTargets :: Prelude.Natural,
    -- | The latest known metered size (in bytes) of data stored in the file
    -- system, in its @Value@ field, and the time at which that size was
    -- determined in its @Timestamp@ field. The @Timestamp@ value is the
    -- integer number of seconds since 1970-01-01T00:00:00Z. The @SizeInBytes@
    -- value doesn\'t represent the size of a consistent snapshot of the file
    -- system, but it is eventually consistent when there are no writes to the
    -- file system. That is, @SizeInBytes@ represents actual size only if the
    -- file system is not modified for a period longer than a couple of hours.
    -- Otherwise, the value is not the exact size that the file system was at
    -- any point in time.
    FileSystemDescription -> FileSystemSize
sizeInBytes :: FileSystemSize,
    -- | The performance mode of the file system.
    FileSystemDescription -> PerformanceMode
performanceMode :: PerformanceMode,
    -- | The tags associated with the file system, presented as an array of @Tag@
    -- objects.
    FileSystemDescription -> [Tag]
tags :: [Tag]
  }
  deriving (FileSystemDescription -> FileSystemDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileSystemDescription -> FileSystemDescription -> Bool
$c/= :: FileSystemDescription -> FileSystemDescription -> Bool
== :: FileSystemDescription -> FileSystemDescription -> Bool
$c== :: FileSystemDescription -> FileSystemDescription -> Bool
Prelude.Eq, ReadPrec [FileSystemDescription]
ReadPrec FileSystemDescription
Int -> ReadS FileSystemDescription
ReadS [FileSystemDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FileSystemDescription]
$creadListPrec :: ReadPrec [FileSystemDescription]
readPrec :: ReadPrec FileSystemDescription
$creadPrec :: ReadPrec FileSystemDescription
readList :: ReadS [FileSystemDescription]
$creadList :: ReadS [FileSystemDescription]
readsPrec :: Int -> ReadS FileSystemDescription
$creadsPrec :: Int -> ReadS FileSystemDescription
Prelude.Read, Int -> FileSystemDescription -> ShowS
[FileSystemDescription] -> ShowS
FileSystemDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileSystemDescription] -> ShowS
$cshowList :: [FileSystemDescription] -> ShowS
show :: FileSystemDescription -> String
$cshow :: FileSystemDescription -> String
showsPrec :: Int -> FileSystemDescription -> ShowS
$cshowsPrec :: Int -> FileSystemDescription -> ShowS
Prelude.Show, forall x. Rep FileSystemDescription x -> FileSystemDescription
forall x. FileSystemDescription -> Rep FileSystemDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FileSystemDescription x -> FileSystemDescription
$cfrom :: forall x. FileSystemDescription -> Rep FileSystemDescription x
Prelude.Generic)

-- |
-- Create a value of 'FileSystemDescription' 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:
--
-- 'availabilityZoneId', 'fileSystemDescription_availabilityZoneId' - The unique and consistent identifier of the Availability Zone in which
-- the file system\'s One Zone storage classes exist. For example,
-- @use1-az1@ is an Availability Zone ID for the us-east-1 Amazon Web
-- Services Region, and it has the same location in every Amazon Web
-- Services account.
--
-- 'availabilityZoneName', 'fileSystemDescription_availabilityZoneName' - Describes the Amazon Web Services Availability Zone in which the file
-- system is located, and is valid only for file systems using One Zone
-- storage classes. For more information, see
-- <https://docs.aws.amazon.com/efs/latest/ug/storage-classes.html Using EFS storage classes>
-- in the /Amazon EFS User Guide/.
--
-- 'encrypted', 'fileSystemDescription_encrypted' - A Boolean value that, if true, indicates that the file system is
-- encrypted.
--
-- 'fileSystemArn', 'fileSystemDescription_fileSystemArn' - The Amazon Resource Name (ARN) for the EFS file system, in the format
-- @arn:aws:elasticfilesystem:@/@region@/@:@/@account-id@/@:file-system\/@/@file-system-id@/@ @.
-- Example with sample data:
-- @arn:aws:elasticfilesystem:us-west-2:1111333322228888:file-system\/fs-01234567@
--
-- 'kmsKeyId', 'fileSystemDescription_kmsKeyId' - The ID of an KMS key used to protect the encrypted file system.
--
-- 'name', 'fileSystemDescription_name' - You can add tags to a file system, including a @Name@ tag. For more
-- information, see CreateFileSystem. If the file system has a @Name@ tag,
-- Amazon EFS returns the value in this field.
--
-- 'provisionedThroughputInMibps', 'fileSystemDescription_provisionedThroughputInMibps' - The amount of provisioned throughput, measured in MiB\/s, for the file
-- system. Valid for file systems using @ThroughputMode@ set to
-- @provisioned@.
--
-- 'throughputMode', 'fileSystemDescription_throughputMode' - Displays the file system\'s throughput mode. For more information, see
-- <https://docs.aws.amazon.com/efs/latest/ug/performance.html#throughput-modes Throughput modes>
-- in the /Amazon EFS User Guide/.
--
-- 'ownerId', 'fileSystemDescription_ownerId' - The Amazon Web Services account that created the file system. If the
-- file system was created by an IAM user, the parent account to which the
-- user belongs is the owner.
--
-- 'creationToken', 'fileSystemDescription_creationToken' - The opaque string specified in the request.
--
-- 'fileSystemId', 'fileSystemDescription_fileSystemId' - The ID of the file system, assigned by Amazon EFS.
--
-- 'creationTime', 'fileSystemDescription_creationTime' - The time that the file system was created, in seconds (since
-- 1970-01-01T00:00:00Z).
--
-- 'lifeCycleState', 'fileSystemDescription_lifeCycleState' - The lifecycle phase of the file system.
--
-- 'numberOfMountTargets', 'fileSystemDescription_numberOfMountTargets' - The current number of mount targets that the file system has. For more
-- information, see CreateMountTarget.
--
-- 'sizeInBytes', 'fileSystemDescription_sizeInBytes' - The latest known metered size (in bytes) of data stored in the file
-- system, in its @Value@ field, and the time at which that size was
-- determined in its @Timestamp@ field. The @Timestamp@ value is the
-- integer number of seconds since 1970-01-01T00:00:00Z. The @SizeInBytes@
-- value doesn\'t represent the size of a consistent snapshot of the file
-- system, but it is eventually consistent when there are no writes to the
-- file system. That is, @SizeInBytes@ represents actual size only if the
-- file system is not modified for a period longer than a couple of hours.
-- Otherwise, the value is not the exact size that the file system was at
-- any point in time.
--
-- 'performanceMode', 'fileSystemDescription_performanceMode' - The performance mode of the file system.
--
-- 'tags', 'fileSystemDescription_tags' - The tags associated with the file system, presented as an array of @Tag@
-- objects.
newFileSystemDescription ::
  -- | 'ownerId'
  Prelude.Text ->
  -- | 'creationToken'
  Prelude.Text ->
  -- | 'fileSystemId'
  Prelude.Text ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lifeCycleState'
  LifeCycleState ->
  -- | 'numberOfMountTargets'
  Prelude.Natural ->
  -- | 'sizeInBytes'
  FileSystemSize ->
  -- | 'performanceMode'
  PerformanceMode ->
  FileSystemDescription
newFileSystemDescription :: Text
-> Text
-> Text
-> UTCTime
-> LifeCycleState
-> Natural
-> FileSystemSize
-> PerformanceMode
-> FileSystemDescription
newFileSystemDescription
  Text
pOwnerId_
  Text
pCreationToken_
  Text
pFileSystemId_
  UTCTime
pCreationTime_
  LifeCycleState
pLifeCycleState_
  Natural
pNumberOfMountTargets_
  FileSystemSize
pSizeInBytes_
  PerformanceMode
pPerformanceMode_ =
    FileSystemDescription'
      { $sel:availabilityZoneId:FileSystemDescription' :: Maybe Text
availabilityZoneId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:availabilityZoneName:FileSystemDescription' :: Maybe Text
availabilityZoneName = forall a. Maybe a
Prelude.Nothing,
        $sel:encrypted:FileSystemDescription' :: Maybe Bool
encrypted = forall a. Maybe a
Prelude.Nothing,
        $sel:fileSystemArn:FileSystemDescription' :: Maybe Text
fileSystemArn = forall a. Maybe a
Prelude.Nothing,
        $sel:kmsKeyId:FileSystemDescription' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
        $sel:name:FileSystemDescription' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
        $sel:provisionedThroughputInMibps:FileSystemDescription' :: Maybe Double
provisionedThroughputInMibps = forall a. Maybe a
Prelude.Nothing,
        $sel:throughputMode:FileSystemDescription' :: Maybe ThroughputMode
throughputMode = forall a. Maybe a
Prelude.Nothing,
        $sel:ownerId:FileSystemDescription' :: Text
ownerId = Text
pOwnerId_,
        $sel:creationToken:FileSystemDescription' :: Text
creationToken = Text
pCreationToken_,
        $sel:fileSystemId:FileSystemDescription' :: Text
fileSystemId = Text
pFileSystemId_,
        $sel:creationTime:FileSystemDescription' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lifeCycleState:FileSystemDescription' :: LifeCycleState
lifeCycleState = LifeCycleState
pLifeCycleState_,
        $sel:numberOfMountTargets:FileSystemDescription' :: Natural
numberOfMountTargets = Natural
pNumberOfMountTargets_,
        $sel:sizeInBytes:FileSystemDescription' :: FileSystemSize
sizeInBytes = FileSystemSize
pSizeInBytes_,
        $sel:performanceMode:FileSystemDescription' :: PerformanceMode
performanceMode = PerformanceMode
pPerformanceMode_,
        $sel:tags:FileSystemDescription' :: [Tag]
tags = forall a. Monoid a => a
Prelude.mempty
      }

-- | The unique and consistent identifier of the Availability Zone in which
-- the file system\'s One Zone storage classes exist. For example,
-- @use1-az1@ is an Availability Zone ID for the us-east-1 Amazon Web
-- Services Region, and it has the same location in every Amazon Web
-- Services account.
fileSystemDescription_availabilityZoneId :: Lens.Lens' FileSystemDescription (Prelude.Maybe Prelude.Text)
fileSystemDescription_availabilityZoneId :: Lens' FileSystemDescription (Maybe Text)
fileSystemDescription_availabilityZoneId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Maybe Text
availabilityZoneId :: Maybe Text
$sel:availabilityZoneId:FileSystemDescription' :: FileSystemDescription -> Maybe Text
availabilityZoneId} -> Maybe Text
availabilityZoneId) (\s :: FileSystemDescription
s@FileSystemDescription' {} Maybe Text
a -> FileSystemDescription
s {$sel:availabilityZoneId:FileSystemDescription' :: Maybe Text
availabilityZoneId = Maybe Text
a} :: FileSystemDescription)

-- | Describes the Amazon Web Services Availability Zone in which the file
-- system is located, and is valid only for file systems using One Zone
-- storage classes. For more information, see
-- <https://docs.aws.amazon.com/efs/latest/ug/storage-classes.html Using EFS storage classes>
-- in the /Amazon EFS User Guide/.
fileSystemDescription_availabilityZoneName :: Lens.Lens' FileSystemDescription (Prelude.Maybe Prelude.Text)
fileSystemDescription_availabilityZoneName :: Lens' FileSystemDescription (Maybe Text)
fileSystemDescription_availabilityZoneName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Maybe Text
availabilityZoneName :: Maybe Text
$sel:availabilityZoneName:FileSystemDescription' :: FileSystemDescription -> Maybe Text
availabilityZoneName} -> Maybe Text
availabilityZoneName) (\s :: FileSystemDescription
s@FileSystemDescription' {} Maybe Text
a -> FileSystemDescription
s {$sel:availabilityZoneName:FileSystemDescription' :: Maybe Text
availabilityZoneName = Maybe Text
a} :: FileSystemDescription)

-- | A Boolean value that, if true, indicates that the file system is
-- encrypted.
fileSystemDescription_encrypted :: Lens.Lens' FileSystemDescription (Prelude.Maybe Prelude.Bool)
fileSystemDescription_encrypted :: Lens' FileSystemDescription (Maybe Bool)
fileSystemDescription_encrypted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Maybe Bool
encrypted :: Maybe Bool
$sel:encrypted:FileSystemDescription' :: FileSystemDescription -> Maybe Bool
encrypted} -> Maybe Bool
encrypted) (\s :: FileSystemDescription
s@FileSystemDescription' {} Maybe Bool
a -> FileSystemDescription
s {$sel:encrypted:FileSystemDescription' :: Maybe Bool
encrypted = Maybe Bool
a} :: FileSystemDescription)

-- | The Amazon Resource Name (ARN) for the EFS file system, in the format
-- @arn:aws:elasticfilesystem:@/@region@/@:@/@account-id@/@:file-system\/@/@file-system-id@/@ @.
-- Example with sample data:
-- @arn:aws:elasticfilesystem:us-west-2:1111333322228888:file-system\/fs-01234567@
fileSystemDescription_fileSystemArn :: Lens.Lens' FileSystemDescription (Prelude.Maybe Prelude.Text)
fileSystemDescription_fileSystemArn :: Lens' FileSystemDescription (Maybe Text)
fileSystemDescription_fileSystemArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Maybe Text
fileSystemArn :: Maybe Text
$sel:fileSystemArn:FileSystemDescription' :: FileSystemDescription -> Maybe Text
fileSystemArn} -> Maybe Text
fileSystemArn) (\s :: FileSystemDescription
s@FileSystemDescription' {} Maybe Text
a -> FileSystemDescription
s {$sel:fileSystemArn:FileSystemDescription' :: Maybe Text
fileSystemArn = Maybe Text
a} :: FileSystemDescription)

-- | The ID of an KMS key used to protect the encrypted file system.
fileSystemDescription_kmsKeyId :: Lens.Lens' FileSystemDescription (Prelude.Maybe Prelude.Text)
fileSystemDescription_kmsKeyId :: Lens' FileSystemDescription (Maybe Text)
fileSystemDescription_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:FileSystemDescription' :: FileSystemDescription -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: FileSystemDescription
s@FileSystemDescription' {} Maybe Text
a -> FileSystemDescription
s {$sel:kmsKeyId:FileSystemDescription' :: Maybe Text
kmsKeyId = Maybe Text
a} :: FileSystemDescription)

-- | You can add tags to a file system, including a @Name@ tag. For more
-- information, see CreateFileSystem. If the file system has a @Name@ tag,
-- Amazon EFS returns the value in this field.
fileSystemDescription_name :: Lens.Lens' FileSystemDescription (Prelude.Maybe Prelude.Text)
fileSystemDescription_name :: Lens' FileSystemDescription (Maybe Text)
fileSystemDescription_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Maybe Text
name :: Maybe Text
$sel:name:FileSystemDescription' :: FileSystemDescription -> Maybe Text
name} -> Maybe Text
name) (\s :: FileSystemDescription
s@FileSystemDescription' {} Maybe Text
a -> FileSystemDescription
s {$sel:name:FileSystemDescription' :: Maybe Text
name = Maybe Text
a} :: FileSystemDescription)

-- | The amount of provisioned throughput, measured in MiB\/s, for the file
-- system. Valid for file systems using @ThroughputMode@ set to
-- @provisioned@.
fileSystemDescription_provisionedThroughputInMibps :: Lens.Lens' FileSystemDescription (Prelude.Maybe Prelude.Double)
fileSystemDescription_provisionedThroughputInMibps :: Lens' FileSystemDescription (Maybe Double)
fileSystemDescription_provisionedThroughputInMibps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Maybe Double
provisionedThroughputInMibps :: Maybe Double
$sel:provisionedThroughputInMibps:FileSystemDescription' :: FileSystemDescription -> Maybe Double
provisionedThroughputInMibps} -> Maybe Double
provisionedThroughputInMibps) (\s :: FileSystemDescription
s@FileSystemDescription' {} Maybe Double
a -> FileSystemDescription
s {$sel:provisionedThroughputInMibps:FileSystemDescription' :: Maybe Double
provisionedThroughputInMibps = Maybe Double
a} :: FileSystemDescription)

-- | Displays the file system\'s throughput mode. For more information, see
-- <https://docs.aws.amazon.com/efs/latest/ug/performance.html#throughput-modes Throughput modes>
-- in the /Amazon EFS User Guide/.
fileSystemDescription_throughputMode :: Lens.Lens' FileSystemDescription (Prelude.Maybe ThroughputMode)
fileSystemDescription_throughputMode :: Lens' FileSystemDescription (Maybe ThroughputMode)
fileSystemDescription_throughputMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Maybe ThroughputMode
throughputMode :: Maybe ThroughputMode
$sel:throughputMode:FileSystemDescription' :: FileSystemDescription -> Maybe ThroughputMode
throughputMode} -> Maybe ThroughputMode
throughputMode) (\s :: FileSystemDescription
s@FileSystemDescription' {} Maybe ThroughputMode
a -> FileSystemDescription
s {$sel:throughputMode:FileSystemDescription' :: Maybe ThroughputMode
throughputMode = Maybe ThroughputMode
a} :: FileSystemDescription)

-- | The Amazon Web Services account that created the file system. If the
-- file system was created by an IAM user, the parent account to which the
-- user belongs is the owner.
fileSystemDescription_ownerId :: Lens.Lens' FileSystemDescription Prelude.Text
fileSystemDescription_ownerId :: Lens' FileSystemDescription Text
fileSystemDescription_ownerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Text
ownerId :: Text
$sel:ownerId:FileSystemDescription' :: FileSystemDescription -> Text
ownerId} -> Text
ownerId) (\s :: FileSystemDescription
s@FileSystemDescription' {} Text
a -> FileSystemDescription
s {$sel:ownerId:FileSystemDescription' :: Text
ownerId = Text
a} :: FileSystemDescription)

-- | The opaque string specified in the request.
fileSystemDescription_creationToken :: Lens.Lens' FileSystemDescription Prelude.Text
fileSystemDescription_creationToken :: Lens' FileSystemDescription Text
fileSystemDescription_creationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Text
creationToken :: Text
$sel:creationToken:FileSystemDescription' :: FileSystemDescription -> Text
creationToken} -> Text
creationToken) (\s :: FileSystemDescription
s@FileSystemDescription' {} Text
a -> FileSystemDescription
s {$sel:creationToken:FileSystemDescription' :: Text
creationToken = Text
a} :: FileSystemDescription)

-- | The ID of the file system, assigned by Amazon EFS.
fileSystemDescription_fileSystemId :: Lens.Lens' FileSystemDescription Prelude.Text
fileSystemDescription_fileSystemId :: Lens' FileSystemDescription Text
fileSystemDescription_fileSystemId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Text
fileSystemId :: Text
$sel:fileSystemId:FileSystemDescription' :: FileSystemDescription -> Text
fileSystemId} -> Text
fileSystemId) (\s :: FileSystemDescription
s@FileSystemDescription' {} Text
a -> FileSystemDescription
s {$sel:fileSystemId:FileSystemDescription' :: Text
fileSystemId = Text
a} :: FileSystemDescription)

-- | The time that the file system was created, in seconds (since
-- 1970-01-01T00:00:00Z).
fileSystemDescription_creationTime :: Lens.Lens' FileSystemDescription Prelude.UTCTime
fileSystemDescription_creationTime :: Lens' FileSystemDescription UTCTime
fileSystemDescription_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {POSIX
creationTime :: POSIX
$sel:creationTime:FileSystemDescription' :: FileSystemDescription -> POSIX
creationTime} -> POSIX
creationTime) (\s :: FileSystemDescription
s@FileSystemDescription' {} POSIX
a -> FileSystemDescription
s {$sel:creationTime:FileSystemDescription' :: POSIX
creationTime = POSIX
a} :: FileSystemDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The lifecycle phase of the file system.
fileSystemDescription_lifeCycleState :: Lens.Lens' FileSystemDescription LifeCycleState
fileSystemDescription_lifeCycleState :: Lens' FileSystemDescription LifeCycleState
fileSystemDescription_lifeCycleState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {LifeCycleState
lifeCycleState :: LifeCycleState
$sel:lifeCycleState:FileSystemDescription' :: FileSystemDescription -> LifeCycleState
lifeCycleState} -> LifeCycleState
lifeCycleState) (\s :: FileSystemDescription
s@FileSystemDescription' {} LifeCycleState
a -> FileSystemDescription
s {$sel:lifeCycleState:FileSystemDescription' :: LifeCycleState
lifeCycleState = LifeCycleState
a} :: FileSystemDescription)

-- | The current number of mount targets that the file system has. For more
-- information, see CreateMountTarget.
fileSystemDescription_numberOfMountTargets :: Lens.Lens' FileSystemDescription Prelude.Natural
fileSystemDescription_numberOfMountTargets :: Lens' FileSystemDescription Natural
fileSystemDescription_numberOfMountTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {Natural
numberOfMountTargets :: Natural
$sel:numberOfMountTargets:FileSystemDescription' :: FileSystemDescription -> Natural
numberOfMountTargets} -> Natural
numberOfMountTargets) (\s :: FileSystemDescription
s@FileSystemDescription' {} Natural
a -> FileSystemDescription
s {$sel:numberOfMountTargets:FileSystemDescription' :: Natural
numberOfMountTargets = Natural
a} :: FileSystemDescription)

-- | The latest known metered size (in bytes) of data stored in the file
-- system, in its @Value@ field, and the time at which that size was
-- determined in its @Timestamp@ field. The @Timestamp@ value is the
-- integer number of seconds since 1970-01-01T00:00:00Z. The @SizeInBytes@
-- value doesn\'t represent the size of a consistent snapshot of the file
-- system, but it is eventually consistent when there are no writes to the
-- file system. That is, @SizeInBytes@ represents actual size only if the
-- file system is not modified for a period longer than a couple of hours.
-- Otherwise, the value is not the exact size that the file system was at
-- any point in time.
fileSystemDescription_sizeInBytes :: Lens.Lens' FileSystemDescription FileSystemSize
fileSystemDescription_sizeInBytes :: Lens' FileSystemDescription FileSystemSize
fileSystemDescription_sizeInBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {FileSystemSize
sizeInBytes :: FileSystemSize
$sel:sizeInBytes:FileSystemDescription' :: FileSystemDescription -> FileSystemSize
sizeInBytes} -> FileSystemSize
sizeInBytes) (\s :: FileSystemDescription
s@FileSystemDescription' {} FileSystemSize
a -> FileSystemDescription
s {$sel:sizeInBytes:FileSystemDescription' :: FileSystemSize
sizeInBytes = FileSystemSize
a} :: FileSystemDescription)

-- | The performance mode of the file system.
fileSystemDescription_performanceMode :: Lens.Lens' FileSystemDescription PerformanceMode
fileSystemDescription_performanceMode :: Lens' FileSystemDescription PerformanceMode
fileSystemDescription_performanceMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {PerformanceMode
performanceMode :: PerformanceMode
$sel:performanceMode:FileSystemDescription' :: FileSystemDescription -> PerformanceMode
performanceMode} -> PerformanceMode
performanceMode) (\s :: FileSystemDescription
s@FileSystemDescription' {} PerformanceMode
a -> FileSystemDescription
s {$sel:performanceMode:FileSystemDescription' :: PerformanceMode
performanceMode = PerformanceMode
a} :: FileSystemDescription)

-- | The tags associated with the file system, presented as an array of @Tag@
-- objects.
fileSystemDescription_tags :: Lens.Lens' FileSystemDescription [Tag]
fileSystemDescription_tags :: Lens' FileSystemDescription [Tag]
fileSystemDescription_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystemDescription' {[Tag]
tags :: [Tag]
$sel:tags:FileSystemDescription' :: FileSystemDescription -> [Tag]
tags} -> [Tag]
tags) (\s :: FileSystemDescription
s@FileSystemDescription' {} [Tag]
a -> FileSystemDescription
s {$sel:tags:FileSystemDescription' :: [Tag]
tags = [Tag]
a} :: FileSystemDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Data.FromJSON FileSystemDescription where
  parseJSON :: Value -> Parser FileSystemDescription
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"FileSystemDescription"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Double
-> Maybe ThroughputMode
-> Text
-> Text
-> Text
-> POSIX
-> LifeCycleState
-> Natural
-> FileSystemSize
-> PerformanceMode
-> [Tag]
-> FileSystemDescription
FileSystemDescription'
            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
"AvailabilityZoneId")
            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
"AvailabilityZoneName")
            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
"Encrypted")
            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
"FileSystemArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"KmsKeyId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Name")
            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
"ProvisionedThroughputInMibps")
            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
"ThroughputMode")
            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
"OwnerId")
            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
"CreationToken")
            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
"FileSystemId")
            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")
            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
"LifeCycleState")
            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
"NumberOfMountTargets")
            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
"SizeInBytes")
            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
"PerformanceMode")
            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 a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable FileSystemDescription where
  hashWithSalt :: Int -> FileSystemDescription -> Int
hashWithSalt Int
_salt FileSystemDescription' {Natural
[Tag]
Maybe Bool
Maybe Double
Maybe Text
Maybe ThroughputMode
Text
POSIX
FileSystemSize
LifeCycleState
PerformanceMode
tags :: [Tag]
performanceMode :: PerformanceMode
sizeInBytes :: FileSystemSize
numberOfMountTargets :: Natural
lifeCycleState :: LifeCycleState
creationTime :: POSIX
fileSystemId :: Text
creationToken :: Text
ownerId :: Text
throughputMode :: Maybe ThroughputMode
provisionedThroughputInMibps :: Maybe Double
name :: Maybe Text
kmsKeyId :: Maybe Text
fileSystemArn :: Maybe Text
encrypted :: Maybe Bool
availabilityZoneName :: Maybe Text
availabilityZoneId :: Maybe Text
$sel:tags:FileSystemDescription' :: FileSystemDescription -> [Tag]
$sel:performanceMode:FileSystemDescription' :: FileSystemDescription -> PerformanceMode
$sel:sizeInBytes:FileSystemDescription' :: FileSystemDescription -> FileSystemSize
$sel:numberOfMountTargets:FileSystemDescription' :: FileSystemDescription -> Natural
$sel:lifeCycleState:FileSystemDescription' :: FileSystemDescription -> LifeCycleState
$sel:creationTime:FileSystemDescription' :: FileSystemDescription -> POSIX
$sel:fileSystemId:FileSystemDescription' :: FileSystemDescription -> Text
$sel:creationToken:FileSystemDescription' :: FileSystemDescription -> Text
$sel:ownerId:FileSystemDescription' :: FileSystemDescription -> Text
$sel:throughputMode:FileSystemDescription' :: FileSystemDescription -> Maybe ThroughputMode
$sel:provisionedThroughputInMibps:FileSystemDescription' :: FileSystemDescription -> Maybe Double
$sel:name:FileSystemDescription' :: FileSystemDescription -> Maybe Text
$sel:kmsKeyId:FileSystemDescription' :: FileSystemDescription -> Maybe Text
$sel:fileSystemArn:FileSystemDescription' :: FileSystemDescription -> Maybe Text
$sel:encrypted:FileSystemDescription' :: FileSystemDescription -> Maybe Bool
$sel:availabilityZoneName:FileSystemDescription' :: FileSystemDescription -> Maybe Text
$sel:availabilityZoneId:FileSystemDescription' :: FileSystemDescription -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZoneId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZoneName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
encrypted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fileSystemArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
provisionedThroughputInMibps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ThroughputMode
throughputMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ownerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
creationToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fileSystemId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` LifeCycleState
lifeCycleState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
numberOfMountTargets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` FileSystemSize
sizeInBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` PerformanceMode
performanceMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Tag]
tags

instance Prelude.NFData FileSystemDescription where
  rnf :: FileSystemDescription -> ()
rnf FileSystemDescription' {Natural
[Tag]
Maybe Bool
Maybe Double
Maybe Text
Maybe ThroughputMode
Text
POSIX
FileSystemSize
LifeCycleState
PerformanceMode
tags :: [Tag]
performanceMode :: PerformanceMode
sizeInBytes :: FileSystemSize
numberOfMountTargets :: Natural
lifeCycleState :: LifeCycleState
creationTime :: POSIX
fileSystemId :: Text
creationToken :: Text
ownerId :: Text
throughputMode :: Maybe ThroughputMode
provisionedThroughputInMibps :: Maybe Double
name :: Maybe Text
kmsKeyId :: Maybe Text
fileSystemArn :: Maybe Text
encrypted :: Maybe Bool
availabilityZoneName :: Maybe Text
availabilityZoneId :: Maybe Text
$sel:tags:FileSystemDescription' :: FileSystemDescription -> [Tag]
$sel:performanceMode:FileSystemDescription' :: FileSystemDescription -> PerformanceMode
$sel:sizeInBytes:FileSystemDescription' :: FileSystemDescription -> FileSystemSize
$sel:numberOfMountTargets:FileSystemDescription' :: FileSystemDescription -> Natural
$sel:lifeCycleState:FileSystemDescription' :: FileSystemDescription -> LifeCycleState
$sel:creationTime:FileSystemDescription' :: FileSystemDescription -> POSIX
$sel:fileSystemId:FileSystemDescription' :: FileSystemDescription -> Text
$sel:creationToken:FileSystemDescription' :: FileSystemDescription -> Text
$sel:ownerId:FileSystemDescription' :: FileSystemDescription -> Text
$sel:throughputMode:FileSystemDescription' :: FileSystemDescription -> Maybe ThroughputMode
$sel:provisionedThroughputInMibps:FileSystemDescription' :: FileSystemDescription -> Maybe Double
$sel:name:FileSystemDescription' :: FileSystemDescription -> Maybe Text
$sel:kmsKeyId:FileSystemDescription' :: FileSystemDescription -> Maybe Text
$sel:fileSystemArn:FileSystemDescription' :: FileSystemDescription -> Maybe Text
$sel:encrypted:FileSystemDescription' :: FileSystemDescription -> Maybe Bool
$sel:availabilityZoneName:FileSystemDescription' :: FileSystemDescription -> Maybe Text
$sel:availabilityZoneId:FileSystemDescription' :: FileSystemDescription -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZoneId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZoneName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
encrypted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileSystemArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
provisionedThroughputInMibps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ThroughputMode
throughputMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ownerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
creationToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
fileSystemId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf LifeCycleState
lifeCycleState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
numberOfMountTargets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf FileSystemSize
sizeInBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf PerformanceMode
performanceMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Tag]
tags