{-# 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.FileSystem
-- 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.FileSystem where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import {-# SOURCE #-} Amazonka.FSx.Types.AdministrativeAction
import Amazonka.FSx.Types.FileSystemFailureDetails
import Amazonka.FSx.Types.FileSystemLifecycle
import Amazonka.FSx.Types.FileSystemType
import Amazonka.FSx.Types.LustreFileSystemConfiguration
import Amazonka.FSx.Types.OntapFileSystemConfiguration
import Amazonka.FSx.Types.OpenZFSFileSystemConfiguration
import Amazonka.FSx.Types.StorageType
import Amazonka.FSx.Types.Tag
import Amazonka.FSx.Types.WindowsFileSystemConfiguration
import qualified Amazonka.Prelude as Prelude

-- | A description of a specific Amazon FSx file system.
--
-- /See:/ 'newFileSystem' smart constructor.
data FileSystem = FileSystem'
  { -- | A list of administrative actions for the file system that are in process
    -- or waiting to be processed. Administrative actions describe changes to
    -- the Amazon FSx system that you have initiated using the
    -- @UpdateFileSystem@ operation.
    FileSystem -> Maybe [AdministrativeAction]
administrativeActions :: Prelude.Maybe [AdministrativeAction],
    -- | The time that the file system was created, in seconds (since
    -- 1970-01-01T00:00:00Z), also known as Unix time.
    FileSystem -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The Domain Name System (DNS) name for the file system.
    FileSystem -> Maybe Text
dNSName :: Prelude.Maybe Prelude.Text,
    FileSystem -> Maybe FileSystemFailureDetails
failureDetails :: Prelude.Maybe FileSystemFailureDetails,
    -- | The system-generated, unique 17-digit ID of the file system.
    FileSystem -> Maybe Text
fileSystemId :: Prelude.Maybe Prelude.Text,
    -- | The type of Amazon FSx file system, which can be @LUSTRE@, @WINDOWS@,
    -- @ONTAP@, or @OPENZFS@.
    FileSystem -> Maybe FileSystemType
fileSystemType :: Prelude.Maybe FileSystemType,
    -- | The Lustre version of the Amazon FSx for Lustre file system, either
    -- @2.10@ or @2.12@.
    FileSystem -> Maybe Text
fileSystemTypeVersion :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Key Management Service (KMS) key used to encrypt Amazon
    -- FSx file system data. Used as follows with Amazon FSx file system types:
    --
    -- -   Amazon FSx for Lustre @PERSISTENT_1@ and @PERSISTENT_2@ deployment
    --     types only.
    --
    --     @SCRATCH_1@ and @SCRATCH_2@ types are encrypted using the Amazon FSx
    --     service KMS key for your account.
    --
    -- -   Amazon FSx for NetApp ONTAP
    --
    -- -   Amazon FSx for OpenZFS
    --
    -- -   Amazon FSx for Windows File Server
    FileSystem -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The lifecycle status of the file system. The following are the possible
    -- values and what they mean:
    --
    -- -   @AVAILABLE@ - The file system is in a healthy state, and is
    --     reachable and available for use.
    --
    -- -   @CREATING@ - Amazon FSx is creating the new file system.
    --
    -- -   @DELETING@ - Amazon FSx is deleting an existing file system.
    --
    -- -   @FAILED@ - An existing file system has experienced an unrecoverable
    --     failure. When creating a new file system, Amazon FSx was unable to
    --     create the file system.
    --
    -- -   @MISCONFIGURED@ - The file system is in a failed but recoverable
    --     state.
    --
    -- -   @MISCONFIGURED_UNAVAILABLE@ - (Amazon FSx for Windows File Server
    --     only) The file system is currently unavailable due to a change in
    --     your Active Directory configuration.
    --
    -- -   @UPDATING@ - The file system is undergoing a customer-initiated
    --     update.
    FileSystem -> Maybe FileSystemLifecycle
lifecycle :: Prelude.Maybe FileSystemLifecycle,
    FileSystem -> Maybe LustreFileSystemConfiguration
lustreConfiguration :: Prelude.Maybe LustreFileSystemConfiguration,
    -- | The IDs of the elastic network interfaces from which a specific file
    -- system is accessible. The elastic network interface is automatically
    -- created in the same virtual private cloud (VPC) that the Amazon FSx file
    -- system was created in. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-eni.html Elastic Network Interfaces>
    -- in the /Amazon EC2 User Guide./
    --
    -- For an Amazon FSx for Windows File Server file system, you can have one
    -- network interface ID. For an Amazon FSx for Lustre file system, you can
    -- have more than one.
    FileSystem -> Maybe [Text]
networkInterfaceIds :: Prelude.Maybe [Prelude.Text],
    -- | The configuration for this Amazon FSx for NetApp ONTAP file system.
    FileSystem -> Maybe OntapFileSystemConfiguration
ontapConfiguration :: Prelude.Maybe OntapFileSystemConfiguration,
    -- | The configuration for this Amazon FSx for OpenZFS file system.
    FileSystem -> Maybe OpenZFSFileSystemConfiguration
openZFSConfiguration :: Prelude.Maybe OpenZFSFileSystemConfiguration,
    -- | The Amazon Web Services account that created the file system. If the
    -- file system was created by an Identity and Access Management (IAM) user,
    -- the Amazon Web Services account to which the IAM user belongs is the
    -- owner.
    FileSystem -> Maybe Text
ownerId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the file system resource.
    FileSystem -> Maybe Text
resourceARN :: Prelude.Maybe Prelude.Text,
    -- | The storage capacity of the file system in gibibytes (GiB).
    FileSystem -> Maybe Natural
storageCapacity :: Prelude.Maybe Prelude.Natural,
    -- | The type of storage the file system is using. If set to @SSD@, the file
    -- system uses solid state drive storage. If set to @HDD@, the file system
    -- uses hard disk drive storage.
    FileSystem -> Maybe StorageType
storageType :: Prelude.Maybe StorageType,
    -- | Specifies the IDs of the subnets that the file system is accessible
    -- from. For the Amazon FSx Windows and ONTAP @MULTI_AZ_1@ file system
    -- deployment type, there are two subnet IDs, one for the preferred file
    -- server and one for the standby file server. The preferred file server
    -- subnet identified in the @PreferredSubnetID@ property. All other file
    -- systems have only one subnet ID.
    --
    -- For FSx for Lustre file systems, and Single-AZ Windows file systems,
    -- this is the ID of the subnet that contains the file system\'s endpoint.
    -- For @MULTI_AZ_1@ Windows and ONTAP file systems, the file system
    -- endpoint is available in the @PreferredSubnetID@.
    FileSystem -> Maybe [Text]
subnetIds :: Prelude.Maybe [Prelude.Text],
    -- | The tags to associate with the file system. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Using_Tags.html Tagging your Amazon EC2 resources>
    -- in the /Amazon EC2 User Guide/.
    FileSystem -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | The ID of the primary virtual private cloud (VPC) for the file system.
    FileSystem -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text,
    -- | The configuration for this Amazon FSx for Windows File Server file
    -- system.
    FileSystem -> Maybe WindowsFileSystemConfiguration
windowsConfiguration :: Prelude.Maybe WindowsFileSystemConfiguration
  }
  deriving (FileSystem -> FileSystem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileSystem -> FileSystem -> Bool
$c/= :: FileSystem -> FileSystem -> Bool
== :: FileSystem -> FileSystem -> Bool
$c== :: FileSystem -> FileSystem -> Bool
Prelude.Eq, ReadPrec [FileSystem]
ReadPrec FileSystem
Int -> ReadS FileSystem
ReadS [FileSystem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FileSystem]
$creadListPrec :: ReadPrec [FileSystem]
readPrec :: ReadPrec FileSystem
$creadPrec :: ReadPrec FileSystem
readList :: ReadS [FileSystem]
$creadList :: ReadS [FileSystem]
readsPrec :: Int -> ReadS FileSystem
$creadsPrec :: Int -> ReadS FileSystem
Prelude.Read, Int -> FileSystem -> ShowS
[FileSystem] -> ShowS
FileSystem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileSystem] -> ShowS
$cshowList :: [FileSystem] -> ShowS
show :: FileSystem -> String
$cshow :: FileSystem -> String
showsPrec :: Int -> FileSystem -> ShowS
$cshowsPrec :: Int -> FileSystem -> ShowS
Prelude.Show, forall x. Rep FileSystem x -> FileSystem
forall x. FileSystem -> Rep FileSystem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FileSystem x -> FileSystem
$cfrom :: forall x. FileSystem -> Rep FileSystem x
Prelude.Generic)

-- |
-- Create a value of 'FileSystem' 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:
--
-- 'administrativeActions', 'fileSystem_administrativeActions' - A list of administrative actions for the file system that are in process
-- or waiting to be processed. Administrative actions describe changes to
-- the Amazon FSx system that you have initiated using the
-- @UpdateFileSystem@ operation.
--
-- 'creationTime', 'fileSystem_creationTime' - The time that the file system was created, in seconds (since
-- 1970-01-01T00:00:00Z), also known as Unix time.
--
-- 'dNSName', 'fileSystem_dNSName' - The Domain Name System (DNS) name for the file system.
--
-- 'failureDetails', 'fileSystem_failureDetails' - Undocumented member.
--
-- 'fileSystemId', 'fileSystem_fileSystemId' - The system-generated, unique 17-digit ID of the file system.
--
-- 'fileSystemType', 'fileSystem_fileSystemType' - The type of Amazon FSx file system, which can be @LUSTRE@, @WINDOWS@,
-- @ONTAP@, or @OPENZFS@.
--
-- 'fileSystemTypeVersion', 'fileSystem_fileSystemTypeVersion' - The Lustre version of the Amazon FSx for Lustre file system, either
-- @2.10@ or @2.12@.
--
-- 'kmsKeyId', 'fileSystem_kmsKeyId' - The ID of the Key Management Service (KMS) key used to encrypt Amazon
-- FSx file system data. Used as follows with Amazon FSx file system types:
--
-- -   Amazon FSx for Lustre @PERSISTENT_1@ and @PERSISTENT_2@ deployment
--     types only.
--
--     @SCRATCH_1@ and @SCRATCH_2@ types are encrypted using the Amazon FSx
--     service KMS key for your account.
--
-- -   Amazon FSx for NetApp ONTAP
--
-- -   Amazon FSx for OpenZFS
--
-- -   Amazon FSx for Windows File Server
--
-- 'lifecycle', 'fileSystem_lifecycle' - The lifecycle status of the file system. The following are the possible
-- values and what they mean:
--
-- -   @AVAILABLE@ - The file system is in a healthy state, and is
--     reachable and available for use.
--
-- -   @CREATING@ - Amazon FSx is creating the new file system.
--
-- -   @DELETING@ - Amazon FSx is deleting an existing file system.
--
-- -   @FAILED@ - An existing file system has experienced an unrecoverable
--     failure. When creating a new file system, Amazon FSx was unable to
--     create the file system.
--
-- -   @MISCONFIGURED@ - The file system is in a failed but recoverable
--     state.
--
-- -   @MISCONFIGURED_UNAVAILABLE@ - (Amazon FSx for Windows File Server
--     only) The file system is currently unavailable due to a change in
--     your Active Directory configuration.
--
-- -   @UPDATING@ - The file system is undergoing a customer-initiated
--     update.
--
-- 'lustreConfiguration', 'fileSystem_lustreConfiguration' - Undocumented member.
--
-- 'networkInterfaceIds', 'fileSystem_networkInterfaceIds' - The IDs of the elastic network interfaces from which a specific file
-- system is accessible. The elastic network interface is automatically
-- created in the same virtual private cloud (VPC) that the Amazon FSx file
-- system was created in. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-eni.html Elastic Network Interfaces>
-- in the /Amazon EC2 User Guide./
--
-- For an Amazon FSx for Windows File Server file system, you can have one
-- network interface ID. For an Amazon FSx for Lustre file system, you can
-- have more than one.
--
-- 'ontapConfiguration', 'fileSystem_ontapConfiguration' - The configuration for this Amazon FSx for NetApp ONTAP file system.
--
-- 'openZFSConfiguration', 'fileSystem_openZFSConfiguration' - The configuration for this Amazon FSx for OpenZFS file system.
--
-- 'ownerId', 'fileSystem_ownerId' - The Amazon Web Services account that created the file system. If the
-- file system was created by an Identity and Access Management (IAM) user,
-- the Amazon Web Services account to which the IAM user belongs is the
-- owner.
--
-- 'resourceARN', 'fileSystem_resourceARN' - The Amazon Resource Name (ARN) of the file system resource.
--
-- 'storageCapacity', 'fileSystem_storageCapacity' - The storage capacity of the file system in gibibytes (GiB).
--
-- 'storageType', 'fileSystem_storageType' - The type of storage the file system is using. If set to @SSD@, the file
-- system uses solid state drive storage. If set to @HDD@, the file system
-- uses hard disk drive storage.
--
-- 'subnetIds', 'fileSystem_subnetIds' - Specifies the IDs of the subnets that the file system is accessible
-- from. For the Amazon FSx Windows and ONTAP @MULTI_AZ_1@ file system
-- deployment type, there are two subnet IDs, one for the preferred file
-- server and one for the standby file server. The preferred file server
-- subnet identified in the @PreferredSubnetID@ property. All other file
-- systems have only one subnet ID.
--
-- For FSx for Lustre file systems, and Single-AZ Windows file systems,
-- this is the ID of the subnet that contains the file system\'s endpoint.
-- For @MULTI_AZ_1@ Windows and ONTAP file systems, the file system
-- endpoint is available in the @PreferredSubnetID@.
--
-- 'tags', 'fileSystem_tags' - The tags to associate with the file system. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Using_Tags.html Tagging your Amazon EC2 resources>
-- in the /Amazon EC2 User Guide/.
--
-- 'vpcId', 'fileSystem_vpcId' - The ID of the primary virtual private cloud (VPC) for the file system.
--
-- 'windowsConfiguration', 'fileSystem_windowsConfiguration' - The configuration for this Amazon FSx for Windows File Server file
-- system.
newFileSystem ::
  FileSystem
newFileSystem :: FileSystem
newFileSystem =
  FileSystem'
    { $sel:administrativeActions:FileSystem' :: Maybe [AdministrativeAction]
administrativeActions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:FileSystem' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:dNSName:FileSystem' :: Maybe Text
dNSName = forall a. Maybe a
Prelude.Nothing,
      $sel:failureDetails:FileSystem' :: Maybe FileSystemFailureDetails
failureDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:fileSystemId:FileSystem' :: Maybe Text
fileSystemId = forall a. Maybe a
Prelude.Nothing,
      $sel:fileSystemType:FileSystem' :: Maybe FileSystemType
fileSystemType = forall a. Maybe a
Prelude.Nothing,
      $sel:fileSystemTypeVersion:FileSystem' :: Maybe Text
fileSystemTypeVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:FileSystem' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:lifecycle:FileSystem' :: Maybe FileSystemLifecycle
lifecycle = forall a. Maybe a
Prelude.Nothing,
      $sel:lustreConfiguration:FileSystem' :: Maybe LustreFileSystemConfiguration
lustreConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceIds:FileSystem' :: Maybe [Text]
networkInterfaceIds = forall a. Maybe a
Prelude.Nothing,
      $sel:ontapConfiguration:FileSystem' :: Maybe OntapFileSystemConfiguration
ontapConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:openZFSConfiguration:FileSystem' :: Maybe OpenZFSFileSystemConfiguration
openZFSConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerId:FileSystem' :: Maybe Text
ownerId = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceARN:FileSystem' :: Maybe Text
resourceARN = forall a. Maybe a
Prelude.Nothing,
      $sel:storageCapacity:FileSystem' :: Maybe Natural
storageCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:storageType:FileSystem' :: Maybe StorageType
storageType = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetIds:FileSystem' :: Maybe [Text]
subnetIds = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:FileSystem' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:FileSystem' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing,
      $sel:windowsConfiguration:FileSystem' :: Maybe WindowsFileSystemConfiguration
windowsConfiguration = forall a. Maybe a
Prelude.Nothing
    }

-- | A list of administrative actions for the file system that are in process
-- or waiting to be processed. Administrative actions describe changes to
-- the Amazon FSx system that you have initiated using the
-- @UpdateFileSystem@ operation.
fileSystem_administrativeActions :: Lens.Lens' FileSystem (Prelude.Maybe [AdministrativeAction])
fileSystem_administrativeActions :: Lens' FileSystem (Maybe [AdministrativeAction])
fileSystem_administrativeActions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe [AdministrativeAction]
administrativeActions :: Maybe [AdministrativeAction]
$sel:administrativeActions:FileSystem' :: FileSystem -> Maybe [AdministrativeAction]
administrativeActions} -> Maybe [AdministrativeAction]
administrativeActions) (\s :: FileSystem
s@FileSystem' {} Maybe [AdministrativeAction]
a -> FileSystem
s {$sel:administrativeActions:FileSystem' :: Maybe [AdministrativeAction]
administrativeActions = Maybe [AdministrativeAction]
a} :: FileSystem) 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 time that the file system was created, in seconds (since
-- 1970-01-01T00:00:00Z), also known as Unix time.
fileSystem_creationTime :: Lens.Lens' FileSystem (Prelude.Maybe Prelude.UTCTime)
fileSystem_creationTime :: Lens' FileSystem (Maybe UTCTime)
fileSystem_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:FileSystem' :: FileSystem -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: FileSystem
s@FileSystem' {} Maybe POSIX
a -> FileSystem
s {$sel:creationTime:FileSystem' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: FileSystem) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

-- | Undocumented member.
fileSystem_failureDetails :: Lens.Lens' FileSystem (Prelude.Maybe FileSystemFailureDetails)
fileSystem_failureDetails :: Lens' FileSystem (Maybe FileSystemFailureDetails)
fileSystem_failureDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe FileSystemFailureDetails
failureDetails :: Maybe FileSystemFailureDetails
$sel:failureDetails:FileSystem' :: FileSystem -> Maybe FileSystemFailureDetails
failureDetails} -> Maybe FileSystemFailureDetails
failureDetails) (\s :: FileSystem
s@FileSystem' {} Maybe FileSystemFailureDetails
a -> FileSystem
s {$sel:failureDetails:FileSystem' :: Maybe FileSystemFailureDetails
failureDetails = Maybe FileSystemFailureDetails
a} :: FileSystem)

-- | The system-generated, unique 17-digit ID of the file system.
fileSystem_fileSystemId :: Lens.Lens' FileSystem (Prelude.Maybe Prelude.Text)
fileSystem_fileSystemId :: Lens' FileSystem (Maybe Text)
fileSystem_fileSystemId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe Text
fileSystemId :: Maybe Text
$sel:fileSystemId:FileSystem' :: FileSystem -> Maybe Text
fileSystemId} -> Maybe Text
fileSystemId) (\s :: FileSystem
s@FileSystem' {} Maybe Text
a -> FileSystem
s {$sel:fileSystemId:FileSystem' :: Maybe Text
fileSystemId = Maybe Text
a} :: FileSystem)

-- | The type of Amazon FSx file system, which can be @LUSTRE@, @WINDOWS@,
-- @ONTAP@, or @OPENZFS@.
fileSystem_fileSystemType :: Lens.Lens' FileSystem (Prelude.Maybe FileSystemType)
fileSystem_fileSystemType :: Lens' FileSystem (Maybe FileSystemType)
fileSystem_fileSystemType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe FileSystemType
fileSystemType :: Maybe FileSystemType
$sel:fileSystemType:FileSystem' :: FileSystem -> Maybe FileSystemType
fileSystemType} -> Maybe FileSystemType
fileSystemType) (\s :: FileSystem
s@FileSystem' {} Maybe FileSystemType
a -> FileSystem
s {$sel:fileSystemType:FileSystem' :: Maybe FileSystemType
fileSystemType = Maybe FileSystemType
a} :: FileSystem)

-- | The Lustre version of the Amazon FSx for Lustre file system, either
-- @2.10@ or @2.12@.
fileSystem_fileSystemTypeVersion :: Lens.Lens' FileSystem (Prelude.Maybe Prelude.Text)
fileSystem_fileSystemTypeVersion :: Lens' FileSystem (Maybe Text)
fileSystem_fileSystemTypeVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe Text
fileSystemTypeVersion :: Maybe Text
$sel:fileSystemTypeVersion:FileSystem' :: FileSystem -> Maybe Text
fileSystemTypeVersion} -> Maybe Text
fileSystemTypeVersion) (\s :: FileSystem
s@FileSystem' {} Maybe Text
a -> FileSystem
s {$sel:fileSystemTypeVersion:FileSystem' :: Maybe Text
fileSystemTypeVersion = Maybe Text
a} :: FileSystem)

-- | The ID of the Key Management Service (KMS) key used to encrypt Amazon
-- FSx file system data. Used as follows with Amazon FSx file system types:
--
-- -   Amazon FSx for Lustre @PERSISTENT_1@ and @PERSISTENT_2@ deployment
--     types only.
--
--     @SCRATCH_1@ and @SCRATCH_2@ types are encrypted using the Amazon FSx
--     service KMS key for your account.
--
-- -   Amazon FSx for NetApp ONTAP
--
-- -   Amazon FSx for OpenZFS
--
-- -   Amazon FSx for Windows File Server
fileSystem_kmsKeyId :: Lens.Lens' FileSystem (Prelude.Maybe Prelude.Text)
fileSystem_kmsKeyId :: Lens' FileSystem (Maybe Text)
fileSystem_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:FileSystem' :: FileSystem -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: FileSystem
s@FileSystem' {} Maybe Text
a -> FileSystem
s {$sel:kmsKeyId:FileSystem' :: Maybe Text
kmsKeyId = Maybe Text
a} :: FileSystem)

-- | The lifecycle status of the file system. The following are the possible
-- values and what they mean:
--
-- -   @AVAILABLE@ - The file system is in a healthy state, and is
--     reachable and available for use.
--
-- -   @CREATING@ - Amazon FSx is creating the new file system.
--
-- -   @DELETING@ - Amazon FSx is deleting an existing file system.
--
-- -   @FAILED@ - An existing file system has experienced an unrecoverable
--     failure. When creating a new file system, Amazon FSx was unable to
--     create the file system.
--
-- -   @MISCONFIGURED@ - The file system is in a failed but recoverable
--     state.
--
-- -   @MISCONFIGURED_UNAVAILABLE@ - (Amazon FSx for Windows File Server
--     only) The file system is currently unavailable due to a change in
--     your Active Directory configuration.
--
-- -   @UPDATING@ - The file system is undergoing a customer-initiated
--     update.
fileSystem_lifecycle :: Lens.Lens' FileSystem (Prelude.Maybe FileSystemLifecycle)
fileSystem_lifecycle :: Lens' FileSystem (Maybe FileSystemLifecycle)
fileSystem_lifecycle = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe FileSystemLifecycle
lifecycle :: Maybe FileSystemLifecycle
$sel:lifecycle:FileSystem' :: FileSystem -> Maybe FileSystemLifecycle
lifecycle} -> Maybe FileSystemLifecycle
lifecycle) (\s :: FileSystem
s@FileSystem' {} Maybe FileSystemLifecycle
a -> FileSystem
s {$sel:lifecycle:FileSystem' :: Maybe FileSystemLifecycle
lifecycle = Maybe FileSystemLifecycle
a} :: FileSystem)

-- | Undocumented member.
fileSystem_lustreConfiguration :: Lens.Lens' FileSystem (Prelude.Maybe LustreFileSystemConfiguration)
fileSystem_lustreConfiguration :: Lens' FileSystem (Maybe LustreFileSystemConfiguration)
fileSystem_lustreConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe LustreFileSystemConfiguration
lustreConfiguration :: Maybe LustreFileSystemConfiguration
$sel:lustreConfiguration:FileSystem' :: FileSystem -> Maybe LustreFileSystemConfiguration
lustreConfiguration} -> Maybe LustreFileSystemConfiguration
lustreConfiguration) (\s :: FileSystem
s@FileSystem' {} Maybe LustreFileSystemConfiguration
a -> FileSystem
s {$sel:lustreConfiguration:FileSystem' :: Maybe LustreFileSystemConfiguration
lustreConfiguration = Maybe LustreFileSystemConfiguration
a} :: FileSystem)

-- | The IDs of the elastic network interfaces from which a specific file
-- system is accessible. The elastic network interface is automatically
-- created in the same virtual private cloud (VPC) that the Amazon FSx file
-- system was created in. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-eni.html Elastic Network Interfaces>
-- in the /Amazon EC2 User Guide./
--
-- For an Amazon FSx for Windows File Server file system, you can have one
-- network interface ID. For an Amazon FSx for Lustre file system, you can
-- have more than one.
fileSystem_networkInterfaceIds :: Lens.Lens' FileSystem (Prelude.Maybe [Prelude.Text])
fileSystem_networkInterfaceIds :: Lens' FileSystem (Maybe [Text])
fileSystem_networkInterfaceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe [Text]
networkInterfaceIds :: Maybe [Text]
$sel:networkInterfaceIds:FileSystem' :: FileSystem -> Maybe [Text]
networkInterfaceIds} -> Maybe [Text]
networkInterfaceIds) (\s :: FileSystem
s@FileSystem' {} Maybe [Text]
a -> FileSystem
s {$sel:networkInterfaceIds:FileSystem' :: Maybe [Text]
networkInterfaceIds = Maybe [Text]
a} :: FileSystem) 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 configuration for this Amazon FSx for NetApp ONTAP file system.
fileSystem_ontapConfiguration :: Lens.Lens' FileSystem (Prelude.Maybe OntapFileSystemConfiguration)
fileSystem_ontapConfiguration :: Lens' FileSystem (Maybe OntapFileSystemConfiguration)
fileSystem_ontapConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe OntapFileSystemConfiguration
ontapConfiguration :: Maybe OntapFileSystemConfiguration
$sel:ontapConfiguration:FileSystem' :: FileSystem -> Maybe OntapFileSystemConfiguration
ontapConfiguration} -> Maybe OntapFileSystemConfiguration
ontapConfiguration) (\s :: FileSystem
s@FileSystem' {} Maybe OntapFileSystemConfiguration
a -> FileSystem
s {$sel:ontapConfiguration:FileSystem' :: Maybe OntapFileSystemConfiguration
ontapConfiguration = Maybe OntapFileSystemConfiguration
a} :: FileSystem)

-- | The configuration for this Amazon FSx for OpenZFS file system.
fileSystem_openZFSConfiguration :: Lens.Lens' FileSystem (Prelude.Maybe OpenZFSFileSystemConfiguration)
fileSystem_openZFSConfiguration :: Lens' FileSystem (Maybe OpenZFSFileSystemConfiguration)
fileSystem_openZFSConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe OpenZFSFileSystemConfiguration
openZFSConfiguration :: Maybe OpenZFSFileSystemConfiguration
$sel:openZFSConfiguration:FileSystem' :: FileSystem -> Maybe OpenZFSFileSystemConfiguration
openZFSConfiguration} -> Maybe OpenZFSFileSystemConfiguration
openZFSConfiguration) (\s :: FileSystem
s@FileSystem' {} Maybe OpenZFSFileSystemConfiguration
a -> FileSystem
s {$sel:openZFSConfiguration:FileSystem' :: Maybe OpenZFSFileSystemConfiguration
openZFSConfiguration = Maybe OpenZFSFileSystemConfiguration
a} :: FileSystem)

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

-- | The Amazon Resource Name (ARN) of the file system resource.
fileSystem_resourceARN :: Lens.Lens' FileSystem (Prelude.Maybe Prelude.Text)
fileSystem_resourceARN :: Lens' FileSystem (Maybe Text)
fileSystem_resourceARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe Text
resourceARN :: Maybe Text
$sel:resourceARN:FileSystem' :: FileSystem -> Maybe Text
resourceARN} -> Maybe Text
resourceARN) (\s :: FileSystem
s@FileSystem' {} Maybe Text
a -> FileSystem
s {$sel:resourceARN:FileSystem' :: Maybe Text
resourceARN = Maybe Text
a} :: FileSystem)

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

-- | The type of storage the file system is using. If set to @SSD@, the file
-- system uses solid state drive storage. If set to @HDD@, the file system
-- uses hard disk drive storage.
fileSystem_storageType :: Lens.Lens' FileSystem (Prelude.Maybe StorageType)
fileSystem_storageType :: Lens' FileSystem (Maybe StorageType)
fileSystem_storageType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe StorageType
storageType :: Maybe StorageType
$sel:storageType:FileSystem' :: FileSystem -> Maybe StorageType
storageType} -> Maybe StorageType
storageType) (\s :: FileSystem
s@FileSystem' {} Maybe StorageType
a -> FileSystem
s {$sel:storageType:FileSystem' :: Maybe StorageType
storageType = Maybe StorageType
a} :: FileSystem)

-- | Specifies the IDs of the subnets that the file system is accessible
-- from. For the Amazon FSx Windows and ONTAP @MULTI_AZ_1@ file system
-- deployment type, there are two subnet IDs, one for the preferred file
-- server and one for the standby file server. The preferred file server
-- subnet identified in the @PreferredSubnetID@ property. All other file
-- systems have only one subnet ID.
--
-- For FSx for Lustre file systems, and Single-AZ Windows file systems,
-- this is the ID of the subnet that contains the file system\'s endpoint.
-- For @MULTI_AZ_1@ Windows and ONTAP file systems, the file system
-- endpoint is available in the @PreferredSubnetID@.
fileSystem_subnetIds :: Lens.Lens' FileSystem (Prelude.Maybe [Prelude.Text])
fileSystem_subnetIds :: Lens' FileSystem (Maybe [Text])
fileSystem_subnetIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe [Text]
subnetIds :: Maybe [Text]
$sel:subnetIds:FileSystem' :: FileSystem -> Maybe [Text]
subnetIds} -> Maybe [Text]
subnetIds) (\s :: FileSystem
s@FileSystem' {} Maybe [Text]
a -> FileSystem
s {$sel:subnetIds:FileSystem' :: Maybe [Text]
subnetIds = Maybe [Text]
a} :: FileSystem) 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 tags to associate with the file system. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Using_Tags.html Tagging your Amazon EC2 resources>
-- in the /Amazon EC2 User Guide/.
fileSystem_tags :: Lens.Lens' FileSystem (Prelude.Maybe (Prelude.NonEmpty Tag))
fileSystem_tags :: Lens' FileSystem (Maybe (NonEmpty Tag))
fileSystem_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:FileSystem' :: FileSystem -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: FileSystem
s@FileSystem' {} Maybe (NonEmpty Tag)
a -> FileSystem
s {$sel:tags:FileSystem' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: FileSystem) 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 ID of the primary virtual private cloud (VPC) for the file system.
fileSystem_vpcId :: Lens.Lens' FileSystem (Prelude.Maybe Prelude.Text)
fileSystem_vpcId :: Lens' FileSystem (Maybe Text)
fileSystem_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:FileSystem' :: FileSystem -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: FileSystem
s@FileSystem' {} Maybe Text
a -> FileSystem
s {$sel:vpcId:FileSystem' :: Maybe Text
vpcId = Maybe Text
a} :: FileSystem)

-- | The configuration for this Amazon FSx for Windows File Server file
-- system.
fileSystem_windowsConfiguration :: Lens.Lens' FileSystem (Prelude.Maybe WindowsFileSystemConfiguration)
fileSystem_windowsConfiguration :: Lens' FileSystem (Maybe WindowsFileSystemConfiguration)
fileSystem_windowsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FileSystem' {Maybe WindowsFileSystemConfiguration
windowsConfiguration :: Maybe WindowsFileSystemConfiguration
$sel:windowsConfiguration:FileSystem' :: FileSystem -> Maybe WindowsFileSystemConfiguration
windowsConfiguration} -> Maybe WindowsFileSystemConfiguration
windowsConfiguration) (\s :: FileSystem
s@FileSystem' {} Maybe WindowsFileSystemConfiguration
a -> FileSystem
s {$sel:windowsConfiguration:FileSystem' :: Maybe WindowsFileSystemConfiguration
windowsConfiguration = Maybe WindowsFileSystemConfiguration
a} :: FileSystem)

instance Data.FromJSON FileSystem where
  parseJSON :: Value -> Parser FileSystem
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"FileSystem"
      ( \Object
x ->
          Maybe [AdministrativeAction]
-> Maybe POSIX
-> Maybe Text
-> Maybe FileSystemFailureDetails
-> Maybe Text
-> Maybe FileSystemType
-> Maybe Text
-> Maybe Text
-> Maybe FileSystemLifecycle
-> Maybe LustreFileSystemConfiguration
-> Maybe [Text]
-> Maybe OntapFileSystemConfiguration
-> Maybe OpenZFSFileSystemConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe StorageType
-> Maybe [Text]
-> Maybe (NonEmpty Tag)
-> Maybe Text
-> Maybe WindowsFileSystemConfiguration
-> FileSystem
FileSystem'
            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
"AdministrativeActions"
                            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
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DNSName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"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
"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
"FileSystemType")
            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
"FileSystemTypeVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"KmsKeyId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Lifecycle")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"LustreConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"NetworkInterfaceIds"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"OntapConfiguration")
            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
"OpenZFSConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"OwnerId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ResourceARN")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StorageCapacity")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StorageType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"SubnetIds" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Tags")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"VpcId")
            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
"WindowsConfiguration")
      )

instance Prelude.Hashable FileSystem where
  hashWithSalt :: Int -> FileSystem -> Int
hashWithSalt Int
_salt FileSystem' {Maybe Natural
Maybe [Text]
Maybe [AdministrativeAction]
Maybe (NonEmpty Tag)
Maybe Text
Maybe POSIX
Maybe FileSystemFailureDetails
Maybe FileSystemLifecycle
Maybe FileSystemType
Maybe LustreFileSystemConfiguration
Maybe OntapFileSystemConfiguration
Maybe OpenZFSFileSystemConfiguration
Maybe StorageType
Maybe WindowsFileSystemConfiguration
windowsConfiguration :: Maybe WindowsFileSystemConfiguration
vpcId :: Maybe Text
tags :: Maybe (NonEmpty Tag)
subnetIds :: Maybe [Text]
storageType :: Maybe StorageType
storageCapacity :: Maybe Natural
resourceARN :: Maybe Text
ownerId :: Maybe Text
openZFSConfiguration :: Maybe OpenZFSFileSystemConfiguration
ontapConfiguration :: Maybe OntapFileSystemConfiguration
networkInterfaceIds :: Maybe [Text]
lustreConfiguration :: Maybe LustreFileSystemConfiguration
lifecycle :: Maybe FileSystemLifecycle
kmsKeyId :: Maybe Text
fileSystemTypeVersion :: Maybe Text
fileSystemType :: Maybe FileSystemType
fileSystemId :: Maybe Text
failureDetails :: Maybe FileSystemFailureDetails
dNSName :: Maybe Text
creationTime :: Maybe POSIX
administrativeActions :: Maybe [AdministrativeAction]
$sel:windowsConfiguration:FileSystem' :: FileSystem -> Maybe WindowsFileSystemConfiguration
$sel:vpcId:FileSystem' :: FileSystem -> Maybe Text
$sel:tags:FileSystem' :: FileSystem -> Maybe (NonEmpty Tag)
$sel:subnetIds:FileSystem' :: FileSystem -> Maybe [Text]
$sel:storageType:FileSystem' :: FileSystem -> Maybe StorageType
$sel:storageCapacity:FileSystem' :: FileSystem -> Maybe Natural
$sel:resourceARN:FileSystem' :: FileSystem -> Maybe Text
$sel:ownerId:FileSystem' :: FileSystem -> Maybe Text
$sel:openZFSConfiguration:FileSystem' :: FileSystem -> Maybe OpenZFSFileSystemConfiguration
$sel:ontapConfiguration:FileSystem' :: FileSystem -> Maybe OntapFileSystemConfiguration
$sel:networkInterfaceIds:FileSystem' :: FileSystem -> Maybe [Text]
$sel:lustreConfiguration:FileSystem' :: FileSystem -> Maybe LustreFileSystemConfiguration
$sel:lifecycle:FileSystem' :: FileSystem -> Maybe FileSystemLifecycle
$sel:kmsKeyId:FileSystem' :: FileSystem -> Maybe Text
$sel:fileSystemTypeVersion:FileSystem' :: FileSystem -> Maybe Text
$sel:fileSystemType:FileSystem' :: FileSystem -> Maybe FileSystemType
$sel:fileSystemId:FileSystem' :: FileSystem -> Maybe Text
$sel:failureDetails:FileSystem' :: FileSystem -> Maybe FileSystemFailureDetails
$sel:dNSName:FileSystem' :: FileSystem -> Maybe Text
$sel:creationTime:FileSystem' :: FileSystem -> Maybe POSIX
$sel:administrativeActions:FileSystem' :: FileSystem -> Maybe [AdministrativeAction]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AdministrativeAction]
administrativeActions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dNSName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileSystemFailureDetails
failureDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fileSystemId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileSystemType
fileSystemType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fileSystemTypeVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileSystemLifecycle
lifecycle
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LustreFileSystemConfiguration
lustreConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
networkInterfaceIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OntapFileSystemConfiguration
ontapConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OpenZFSFileSystemConfiguration
openZFSConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ownerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
storageCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StorageType
storageType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
subnetIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WindowsFileSystemConfiguration
windowsConfiguration

instance Prelude.NFData FileSystem where
  rnf :: FileSystem -> ()
rnf FileSystem' {Maybe Natural
Maybe [Text]
Maybe [AdministrativeAction]
Maybe (NonEmpty Tag)
Maybe Text
Maybe POSIX
Maybe FileSystemFailureDetails
Maybe FileSystemLifecycle
Maybe FileSystemType
Maybe LustreFileSystemConfiguration
Maybe OntapFileSystemConfiguration
Maybe OpenZFSFileSystemConfiguration
Maybe StorageType
Maybe WindowsFileSystemConfiguration
windowsConfiguration :: Maybe WindowsFileSystemConfiguration
vpcId :: Maybe Text
tags :: Maybe (NonEmpty Tag)
subnetIds :: Maybe [Text]
storageType :: Maybe StorageType
storageCapacity :: Maybe Natural
resourceARN :: Maybe Text
ownerId :: Maybe Text
openZFSConfiguration :: Maybe OpenZFSFileSystemConfiguration
ontapConfiguration :: Maybe OntapFileSystemConfiguration
networkInterfaceIds :: Maybe [Text]
lustreConfiguration :: Maybe LustreFileSystemConfiguration
lifecycle :: Maybe FileSystemLifecycle
kmsKeyId :: Maybe Text
fileSystemTypeVersion :: Maybe Text
fileSystemType :: Maybe FileSystemType
fileSystemId :: Maybe Text
failureDetails :: Maybe FileSystemFailureDetails
dNSName :: Maybe Text
creationTime :: Maybe POSIX
administrativeActions :: Maybe [AdministrativeAction]
$sel:windowsConfiguration:FileSystem' :: FileSystem -> Maybe WindowsFileSystemConfiguration
$sel:vpcId:FileSystem' :: FileSystem -> Maybe Text
$sel:tags:FileSystem' :: FileSystem -> Maybe (NonEmpty Tag)
$sel:subnetIds:FileSystem' :: FileSystem -> Maybe [Text]
$sel:storageType:FileSystem' :: FileSystem -> Maybe StorageType
$sel:storageCapacity:FileSystem' :: FileSystem -> Maybe Natural
$sel:resourceARN:FileSystem' :: FileSystem -> Maybe Text
$sel:ownerId:FileSystem' :: FileSystem -> Maybe Text
$sel:openZFSConfiguration:FileSystem' :: FileSystem -> Maybe OpenZFSFileSystemConfiguration
$sel:ontapConfiguration:FileSystem' :: FileSystem -> Maybe OntapFileSystemConfiguration
$sel:networkInterfaceIds:FileSystem' :: FileSystem -> Maybe [Text]
$sel:lustreConfiguration:FileSystem' :: FileSystem -> Maybe LustreFileSystemConfiguration
$sel:lifecycle:FileSystem' :: FileSystem -> Maybe FileSystemLifecycle
$sel:kmsKeyId:FileSystem' :: FileSystem -> Maybe Text
$sel:fileSystemTypeVersion:FileSystem' :: FileSystem -> Maybe Text
$sel:fileSystemType:FileSystem' :: FileSystem -> Maybe FileSystemType
$sel:fileSystemId:FileSystem' :: FileSystem -> Maybe Text
$sel:failureDetails:FileSystem' :: FileSystem -> Maybe FileSystemFailureDetails
$sel:dNSName:FileSystem' :: FileSystem -> Maybe Text
$sel:creationTime:FileSystem' :: FileSystem -> Maybe POSIX
$sel:administrativeActions:FileSystem' :: FileSystem -> Maybe [AdministrativeAction]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AdministrativeAction]
administrativeActions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dNSName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FileSystemFailureDetails
failureDetails
      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 FileSystemType
fileSystemType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileSystemTypeVersion
      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 FileSystemLifecycle
lifecycle
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LustreFileSystemConfiguration
lustreConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
networkInterfaceIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OntapFileSystemConfiguration
ontapConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OpenZFSFileSystemConfiguration
openZFSConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
storageCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StorageType
storageType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
subnetIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe WindowsFileSystemConfiguration
windowsConfiguration