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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.FSx.Types.DiskIopsConfiguration
import Amazonka.FSx.Types.FileSystemEndpoints
import Amazonka.FSx.Types.OntapDeploymentType
import qualified Amazonka.Prelude as Prelude

-- | Configuration for the FSx for NetApp ONTAP file system.
--
-- /See:/ 'newOntapFileSystemConfiguration' smart constructor.
data OntapFileSystemConfiguration = OntapFileSystemConfiguration'
  { OntapFileSystemConfiguration -> Maybe Natural
automaticBackupRetentionDays :: Prelude.Maybe Prelude.Natural,
    OntapFileSystemConfiguration -> Maybe Text
dailyAutomaticBackupStartTime :: Prelude.Maybe Prelude.Text,
    -- | Specifies the FSx for ONTAP file system deployment type in use in the
    -- file system.
    --
    -- -   @MULTI_AZ_1@ - (Default) A high availability file system configured
    --     for Multi-AZ redundancy to tolerate temporary Availability Zone (AZ)
    --     unavailability.
    --
    -- -   @SINGLE_AZ_1@ - A file system configured for Single-AZ redundancy.
    --
    -- For information about the use cases for Multi-AZ and Single-AZ
    -- deployments, refer to
    -- <https://docs.aws.amazon.com/fsx/latest/ONTAPGuide/high-availability-multiAZ.html Choosing Multi-AZ or Single-AZ file system deployment>.
    OntapFileSystemConfiguration -> Maybe OntapDeploymentType
deploymentType :: Prelude.Maybe OntapDeploymentType,
    -- | The SSD IOPS configuration for the ONTAP file system, specifying the
    -- number of provisioned IOPS and the provision mode.
    OntapFileSystemConfiguration -> Maybe DiskIopsConfiguration
diskIopsConfiguration :: Prelude.Maybe DiskIopsConfiguration,
    -- | (Multi-AZ only) The IP address range in which the endpoints to access
    -- your file system are created.
    --
    -- The Endpoint IP address range you select for your file system must exist
    -- outside the VPC\'s CIDR range and must be at least \/30 or larger. If
    -- you do not specify this optional parameter, Amazon FSx will
    -- automatically select a CIDR block for you.
    OntapFileSystemConfiguration -> Maybe Text
endpointIpAddressRange :: Prelude.Maybe Prelude.Text,
    -- | The @Management@ and @Intercluster@ endpoints that are used to access
    -- data or to manage the file system using the NetApp ONTAP CLI, REST API,
    -- or NetApp SnapMirror.
    OntapFileSystemConfiguration -> Maybe FileSystemEndpoints
endpoints :: Prelude.Maybe FileSystemEndpoints,
    OntapFileSystemConfiguration -> Maybe Text
preferredSubnetId :: Prelude.Maybe Prelude.Text,
    -- | (Multi-AZ only) The VPC route tables in which your file system\'s
    -- endpoints are created.
    OntapFileSystemConfiguration -> Maybe [Text]
routeTableIds :: Prelude.Maybe [Prelude.Text],
    OntapFileSystemConfiguration -> Maybe Natural
throughputCapacity :: Prelude.Maybe Prelude.Natural,
    OntapFileSystemConfiguration -> Maybe Text
weeklyMaintenanceStartTime :: Prelude.Maybe Prelude.Text
  }
  deriving (OntapFileSystemConfiguration
-> OntapFileSystemConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OntapFileSystemConfiguration
-> OntapFileSystemConfiguration -> Bool
$c/= :: OntapFileSystemConfiguration
-> OntapFileSystemConfiguration -> Bool
== :: OntapFileSystemConfiguration
-> OntapFileSystemConfiguration -> Bool
$c== :: OntapFileSystemConfiguration
-> OntapFileSystemConfiguration -> Bool
Prelude.Eq, ReadPrec [OntapFileSystemConfiguration]
ReadPrec OntapFileSystemConfiguration
Int -> ReadS OntapFileSystemConfiguration
ReadS [OntapFileSystemConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OntapFileSystemConfiguration]
$creadListPrec :: ReadPrec [OntapFileSystemConfiguration]
readPrec :: ReadPrec OntapFileSystemConfiguration
$creadPrec :: ReadPrec OntapFileSystemConfiguration
readList :: ReadS [OntapFileSystemConfiguration]
$creadList :: ReadS [OntapFileSystemConfiguration]
readsPrec :: Int -> ReadS OntapFileSystemConfiguration
$creadsPrec :: Int -> ReadS OntapFileSystemConfiguration
Prelude.Read, Int -> OntapFileSystemConfiguration -> ShowS
[OntapFileSystemConfiguration] -> ShowS
OntapFileSystemConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OntapFileSystemConfiguration] -> ShowS
$cshowList :: [OntapFileSystemConfiguration] -> ShowS
show :: OntapFileSystemConfiguration -> String
$cshow :: OntapFileSystemConfiguration -> String
showsPrec :: Int -> OntapFileSystemConfiguration -> ShowS
$cshowsPrec :: Int -> OntapFileSystemConfiguration -> ShowS
Prelude.Show, forall x.
Rep OntapFileSystemConfiguration x -> OntapFileSystemConfiguration
forall x.
OntapFileSystemConfiguration -> Rep OntapFileSystemConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep OntapFileSystemConfiguration x -> OntapFileSystemConfiguration
$cfrom :: forall x.
OntapFileSystemConfiguration -> Rep OntapFileSystemConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'OntapFileSystemConfiguration' 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:
--
-- 'automaticBackupRetentionDays', 'ontapFileSystemConfiguration_automaticBackupRetentionDays' - Undocumented member.
--
-- 'dailyAutomaticBackupStartTime', 'ontapFileSystemConfiguration_dailyAutomaticBackupStartTime' - Undocumented member.
--
-- 'deploymentType', 'ontapFileSystemConfiguration_deploymentType' - Specifies the FSx for ONTAP file system deployment type in use in the
-- file system.
--
-- -   @MULTI_AZ_1@ - (Default) A high availability file system configured
--     for Multi-AZ redundancy to tolerate temporary Availability Zone (AZ)
--     unavailability.
--
-- -   @SINGLE_AZ_1@ - A file system configured for Single-AZ redundancy.
--
-- For information about the use cases for Multi-AZ and Single-AZ
-- deployments, refer to
-- <https://docs.aws.amazon.com/fsx/latest/ONTAPGuide/high-availability-multiAZ.html Choosing Multi-AZ or Single-AZ file system deployment>.
--
-- 'diskIopsConfiguration', 'ontapFileSystemConfiguration_diskIopsConfiguration' - The SSD IOPS configuration for the ONTAP file system, specifying the
-- number of provisioned IOPS and the provision mode.
--
-- 'endpointIpAddressRange', 'ontapFileSystemConfiguration_endpointIpAddressRange' - (Multi-AZ only) The IP address range in which the endpoints to access
-- your file system are created.
--
-- The Endpoint IP address range you select for your file system must exist
-- outside the VPC\'s CIDR range and must be at least \/30 or larger. If
-- you do not specify this optional parameter, Amazon FSx will
-- automatically select a CIDR block for you.
--
-- 'endpoints', 'ontapFileSystemConfiguration_endpoints' - The @Management@ and @Intercluster@ endpoints that are used to access
-- data or to manage the file system using the NetApp ONTAP CLI, REST API,
-- or NetApp SnapMirror.
--
-- 'preferredSubnetId', 'ontapFileSystemConfiguration_preferredSubnetId' - Undocumented member.
--
-- 'routeTableIds', 'ontapFileSystemConfiguration_routeTableIds' - (Multi-AZ only) The VPC route tables in which your file system\'s
-- endpoints are created.
--
-- 'throughputCapacity', 'ontapFileSystemConfiguration_throughputCapacity' - Undocumented member.
--
-- 'weeklyMaintenanceStartTime', 'ontapFileSystemConfiguration_weeklyMaintenanceStartTime' - Undocumented member.
newOntapFileSystemConfiguration ::
  OntapFileSystemConfiguration
newOntapFileSystemConfiguration :: OntapFileSystemConfiguration
newOntapFileSystemConfiguration =
  OntapFileSystemConfiguration'
    { $sel:automaticBackupRetentionDays:OntapFileSystemConfiguration' :: Maybe Natural
automaticBackupRetentionDays =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dailyAutomaticBackupStartTime:OntapFileSystemConfiguration' :: Maybe Text
dailyAutomaticBackupStartTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentType:OntapFileSystemConfiguration' :: Maybe OntapDeploymentType
deploymentType = forall a. Maybe a
Prelude.Nothing,
      $sel:diskIopsConfiguration:OntapFileSystemConfiguration' :: Maybe DiskIopsConfiguration
diskIopsConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointIpAddressRange:OntapFileSystemConfiguration' :: Maybe Text
endpointIpAddressRange = forall a. Maybe a
Prelude.Nothing,
      $sel:endpoints:OntapFileSystemConfiguration' :: Maybe FileSystemEndpoints
endpoints = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredSubnetId:OntapFileSystemConfiguration' :: Maybe Text
preferredSubnetId = forall a. Maybe a
Prelude.Nothing,
      $sel:routeTableIds:OntapFileSystemConfiguration' :: Maybe [Text]
routeTableIds = forall a. Maybe a
Prelude.Nothing,
      $sel:throughputCapacity:OntapFileSystemConfiguration' :: Maybe Natural
throughputCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:weeklyMaintenanceStartTime:OntapFileSystemConfiguration' :: Maybe Text
weeklyMaintenanceStartTime = forall a. Maybe a
Prelude.Nothing
    }

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

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

-- | Specifies the FSx for ONTAP file system deployment type in use in the
-- file system.
--
-- -   @MULTI_AZ_1@ - (Default) A high availability file system configured
--     for Multi-AZ redundancy to tolerate temporary Availability Zone (AZ)
--     unavailability.
--
-- -   @SINGLE_AZ_1@ - A file system configured for Single-AZ redundancy.
--
-- For information about the use cases for Multi-AZ and Single-AZ
-- deployments, refer to
-- <https://docs.aws.amazon.com/fsx/latest/ONTAPGuide/high-availability-multiAZ.html Choosing Multi-AZ or Single-AZ file system deployment>.
ontapFileSystemConfiguration_deploymentType :: Lens.Lens' OntapFileSystemConfiguration (Prelude.Maybe OntapDeploymentType)
ontapFileSystemConfiguration_deploymentType :: Lens' OntapFileSystemConfiguration (Maybe OntapDeploymentType)
ontapFileSystemConfiguration_deploymentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OntapFileSystemConfiguration' {Maybe OntapDeploymentType
deploymentType :: Maybe OntapDeploymentType
$sel:deploymentType:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe OntapDeploymentType
deploymentType} -> Maybe OntapDeploymentType
deploymentType) (\s :: OntapFileSystemConfiguration
s@OntapFileSystemConfiguration' {} Maybe OntapDeploymentType
a -> OntapFileSystemConfiguration
s {$sel:deploymentType:OntapFileSystemConfiguration' :: Maybe OntapDeploymentType
deploymentType = Maybe OntapDeploymentType
a} :: OntapFileSystemConfiguration)

-- | The SSD IOPS configuration for the ONTAP file system, specifying the
-- number of provisioned IOPS and the provision mode.
ontapFileSystemConfiguration_diskIopsConfiguration :: Lens.Lens' OntapFileSystemConfiguration (Prelude.Maybe DiskIopsConfiguration)
ontapFileSystemConfiguration_diskIopsConfiguration :: Lens' OntapFileSystemConfiguration (Maybe DiskIopsConfiguration)
ontapFileSystemConfiguration_diskIopsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OntapFileSystemConfiguration' {Maybe DiskIopsConfiguration
diskIopsConfiguration :: Maybe DiskIopsConfiguration
$sel:diskIopsConfiguration:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe DiskIopsConfiguration
diskIopsConfiguration} -> Maybe DiskIopsConfiguration
diskIopsConfiguration) (\s :: OntapFileSystemConfiguration
s@OntapFileSystemConfiguration' {} Maybe DiskIopsConfiguration
a -> OntapFileSystemConfiguration
s {$sel:diskIopsConfiguration:OntapFileSystemConfiguration' :: Maybe DiskIopsConfiguration
diskIopsConfiguration = Maybe DiskIopsConfiguration
a} :: OntapFileSystemConfiguration)

-- | (Multi-AZ only) The IP address range in which the endpoints to access
-- your file system are created.
--
-- The Endpoint IP address range you select for your file system must exist
-- outside the VPC\'s CIDR range and must be at least \/30 or larger. If
-- you do not specify this optional parameter, Amazon FSx will
-- automatically select a CIDR block for you.
ontapFileSystemConfiguration_endpointIpAddressRange :: Lens.Lens' OntapFileSystemConfiguration (Prelude.Maybe Prelude.Text)
ontapFileSystemConfiguration_endpointIpAddressRange :: Lens' OntapFileSystemConfiguration (Maybe Text)
ontapFileSystemConfiguration_endpointIpAddressRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OntapFileSystemConfiguration' {Maybe Text
endpointIpAddressRange :: Maybe Text
$sel:endpointIpAddressRange:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Text
endpointIpAddressRange} -> Maybe Text
endpointIpAddressRange) (\s :: OntapFileSystemConfiguration
s@OntapFileSystemConfiguration' {} Maybe Text
a -> OntapFileSystemConfiguration
s {$sel:endpointIpAddressRange:OntapFileSystemConfiguration' :: Maybe Text
endpointIpAddressRange = Maybe Text
a} :: OntapFileSystemConfiguration)

-- | The @Management@ and @Intercluster@ endpoints that are used to access
-- data or to manage the file system using the NetApp ONTAP CLI, REST API,
-- or NetApp SnapMirror.
ontapFileSystemConfiguration_endpoints :: Lens.Lens' OntapFileSystemConfiguration (Prelude.Maybe FileSystemEndpoints)
ontapFileSystemConfiguration_endpoints :: Lens' OntapFileSystemConfiguration (Maybe FileSystemEndpoints)
ontapFileSystemConfiguration_endpoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OntapFileSystemConfiguration' {Maybe FileSystemEndpoints
endpoints :: Maybe FileSystemEndpoints
$sel:endpoints:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe FileSystemEndpoints
endpoints} -> Maybe FileSystemEndpoints
endpoints) (\s :: OntapFileSystemConfiguration
s@OntapFileSystemConfiguration' {} Maybe FileSystemEndpoints
a -> OntapFileSystemConfiguration
s {$sel:endpoints:OntapFileSystemConfiguration' :: Maybe FileSystemEndpoints
endpoints = Maybe FileSystemEndpoints
a} :: OntapFileSystemConfiguration)

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

-- | (Multi-AZ only) The VPC route tables in which your file system\'s
-- endpoints are created.
ontapFileSystemConfiguration_routeTableIds :: Lens.Lens' OntapFileSystemConfiguration (Prelude.Maybe [Prelude.Text])
ontapFileSystemConfiguration_routeTableIds :: Lens' OntapFileSystemConfiguration (Maybe [Text])
ontapFileSystemConfiguration_routeTableIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OntapFileSystemConfiguration' {Maybe [Text]
routeTableIds :: Maybe [Text]
$sel:routeTableIds:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe [Text]
routeTableIds} -> Maybe [Text]
routeTableIds) (\s :: OntapFileSystemConfiguration
s@OntapFileSystemConfiguration' {} Maybe [Text]
a -> OntapFileSystemConfiguration
s {$sel:routeTableIds:OntapFileSystemConfiguration' :: Maybe [Text]
routeTableIds = Maybe [Text]
a} :: OntapFileSystemConfiguration) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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

instance Data.FromJSON OntapFileSystemConfiguration where
  parseJSON :: Value -> Parser OntapFileSystemConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"OntapFileSystemConfiguration"
      ( \Object
x ->
          Maybe Natural
-> Maybe Text
-> Maybe OntapDeploymentType
-> Maybe DiskIopsConfiguration
-> Maybe Text
-> Maybe FileSystemEndpoints
-> Maybe Text
-> Maybe [Text]
-> Maybe Natural
-> Maybe Text
-> OntapFileSystemConfiguration
OntapFileSystemConfiguration'
            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
"AutomaticBackupRetentionDays")
            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
"DailyAutomaticBackupStartTime")
            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
"DeploymentType")
            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
"DiskIopsConfiguration")
            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
"EndpointIpAddressRange")
            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
"Endpoints")
            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
"PreferredSubnetId")
            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
"RouteTableIds" 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
"ThroughputCapacity")
            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
"WeeklyMaintenanceStartTime")
      )

instance
  Prelude.Hashable
    OntapFileSystemConfiguration
  where
  hashWithSalt :: Int -> OntapFileSystemConfiguration -> Int
hashWithSalt Int
_salt OntapFileSystemConfiguration' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe DiskIopsConfiguration
Maybe FileSystemEndpoints
Maybe OntapDeploymentType
weeklyMaintenanceStartTime :: Maybe Text
throughputCapacity :: Maybe Natural
routeTableIds :: Maybe [Text]
preferredSubnetId :: Maybe Text
endpoints :: Maybe FileSystemEndpoints
endpointIpAddressRange :: Maybe Text
diskIopsConfiguration :: Maybe DiskIopsConfiguration
deploymentType :: Maybe OntapDeploymentType
dailyAutomaticBackupStartTime :: Maybe Text
automaticBackupRetentionDays :: Maybe Natural
$sel:weeklyMaintenanceStartTime:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Text
$sel:throughputCapacity:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Natural
$sel:routeTableIds:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe [Text]
$sel:preferredSubnetId:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Text
$sel:endpoints:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe FileSystemEndpoints
$sel:endpointIpAddressRange:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Text
$sel:diskIopsConfiguration:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe DiskIopsConfiguration
$sel:deploymentType:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe OntapDeploymentType
$sel:dailyAutomaticBackupStartTime:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Text
$sel:automaticBackupRetentionDays:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
automaticBackupRetentionDays
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dailyAutomaticBackupStartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OntapDeploymentType
deploymentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DiskIopsConfiguration
diskIopsConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
endpointIpAddressRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileSystemEndpoints
endpoints
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredSubnetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
routeTableIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
throughputCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
weeklyMaintenanceStartTime

instance Prelude.NFData OntapFileSystemConfiguration where
  rnf :: OntapFileSystemConfiguration -> ()
rnf OntapFileSystemConfiguration' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe DiskIopsConfiguration
Maybe FileSystemEndpoints
Maybe OntapDeploymentType
weeklyMaintenanceStartTime :: Maybe Text
throughputCapacity :: Maybe Natural
routeTableIds :: Maybe [Text]
preferredSubnetId :: Maybe Text
endpoints :: Maybe FileSystemEndpoints
endpointIpAddressRange :: Maybe Text
diskIopsConfiguration :: Maybe DiskIopsConfiguration
deploymentType :: Maybe OntapDeploymentType
dailyAutomaticBackupStartTime :: Maybe Text
automaticBackupRetentionDays :: Maybe Natural
$sel:weeklyMaintenanceStartTime:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Text
$sel:throughputCapacity:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Natural
$sel:routeTableIds:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe [Text]
$sel:preferredSubnetId:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Text
$sel:endpoints:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe FileSystemEndpoints
$sel:endpointIpAddressRange:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Text
$sel:diskIopsConfiguration:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe DiskIopsConfiguration
$sel:deploymentType:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe OntapDeploymentType
$sel:dailyAutomaticBackupStartTime:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Text
$sel:automaticBackupRetentionDays:OntapFileSystemConfiguration' :: OntapFileSystemConfiguration -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
automaticBackupRetentionDays
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dailyAutomaticBackupStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OntapDeploymentType
deploymentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DiskIopsConfiguration
diskIopsConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endpointIpAddressRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FileSystemEndpoints
endpoints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
preferredSubnetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
routeTableIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
throughputCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
weeklyMaintenanceStartTime