{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.DataSync.DescribeLocationNfs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns metadata, such as the path information, about an NFS location.
module Amazonka.DataSync.DescribeLocationNfs
  ( -- * Creating a Request
    DescribeLocationNfs (..),
    newDescribeLocationNfs,

    -- * Request Lenses
    describeLocationNfs_locationArn,

    -- * Destructuring the Response
    DescribeLocationNfsResponse (..),
    newDescribeLocationNfsResponse,

    -- * Response Lenses
    describeLocationNfsResponse_creationTime,
    describeLocationNfsResponse_locationArn,
    describeLocationNfsResponse_locationUri,
    describeLocationNfsResponse_mountOptions,
    describeLocationNfsResponse_onPremConfig,
    describeLocationNfsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DataSync.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | DescribeLocationNfsRequest
--
-- /See:/ 'newDescribeLocationNfs' smart constructor.
data DescribeLocationNfs = DescribeLocationNfs'
  { -- | The Amazon Resource Name (ARN) of the NFS location to describe.
    DescribeLocationNfs -> Text
locationArn :: Prelude.Text
  }
  deriving (DescribeLocationNfs -> DescribeLocationNfs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationNfs -> DescribeLocationNfs -> Bool
$c/= :: DescribeLocationNfs -> DescribeLocationNfs -> Bool
== :: DescribeLocationNfs -> DescribeLocationNfs -> Bool
$c== :: DescribeLocationNfs -> DescribeLocationNfs -> Bool
Prelude.Eq, ReadPrec [DescribeLocationNfs]
ReadPrec DescribeLocationNfs
Int -> ReadS DescribeLocationNfs
ReadS [DescribeLocationNfs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationNfs]
$creadListPrec :: ReadPrec [DescribeLocationNfs]
readPrec :: ReadPrec DescribeLocationNfs
$creadPrec :: ReadPrec DescribeLocationNfs
readList :: ReadS [DescribeLocationNfs]
$creadList :: ReadS [DescribeLocationNfs]
readsPrec :: Int -> ReadS DescribeLocationNfs
$creadsPrec :: Int -> ReadS DescribeLocationNfs
Prelude.Read, Int -> DescribeLocationNfs -> ShowS
[DescribeLocationNfs] -> ShowS
DescribeLocationNfs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationNfs] -> ShowS
$cshowList :: [DescribeLocationNfs] -> ShowS
show :: DescribeLocationNfs -> String
$cshow :: DescribeLocationNfs -> String
showsPrec :: Int -> DescribeLocationNfs -> ShowS
$cshowsPrec :: Int -> DescribeLocationNfs -> ShowS
Prelude.Show, forall x. Rep DescribeLocationNfs x -> DescribeLocationNfs
forall x. DescribeLocationNfs -> Rep DescribeLocationNfs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeLocationNfs x -> DescribeLocationNfs
$cfrom :: forall x. DescribeLocationNfs -> Rep DescribeLocationNfs x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLocationNfs' 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:
--
-- 'locationArn', 'describeLocationNfs_locationArn' - The Amazon Resource Name (ARN) of the NFS location to describe.
newDescribeLocationNfs ::
  -- | 'locationArn'
  Prelude.Text ->
  DescribeLocationNfs
newDescribeLocationNfs :: Text -> DescribeLocationNfs
newDescribeLocationNfs Text
pLocationArn_ =
  DescribeLocationNfs' {$sel:locationArn:DescribeLocationNfs' :: Text
locationArn = Text
pLocationArn_}

-- | The Amazon Resource Name (ARN) of the NFS location to describe.
describeLocationNfs_locationArn :: Lens.Lens' DescribeLocationNfs Prelude.Text
describeLocationNfs_locationArn :: Lens' DescribeLocationNfs Text
describeLocationNfs_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationNfs' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationNfs' :: DescribeLocationNfs -> Text
locationArn} -> Text
locationArn) (\s :: DescribeLocationNfs
s@DescribeLocationNfs' {} Text
a -> DescribeLocationNfs
s {$sel:locationArn:DescribeLocationNfs' :: Text
locationArn = Text
a} :: DescribeLocationNfs)

instance Core.AWSRequest DescribeLocationNfs where
  type
    AWSResponse DescribeLocationNfs =
      DescribeLocationNfsResponse
  request :: (Service -> Service)
-> DescribeLocationNfs -> Request DescribeLocationNfs
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeLocationNfs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeLocationNfs)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe NfsMountOptions
-> Maybe OnPremConfig
-> Int
-> DescribeLocationNfsResponse
DescribeLocationNfsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"LocationArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LocationUri")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"MountOptions")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"OnPremConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeLocationNfs where
  hashWithSalt :: Int -> DescribeLocationNfs -> Int
hashWithSalt Int
_salt DescribeLocationNfs' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationNfs' :: DescribeLocationNfs -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
locationArn

instance Prelude.NFData DescribeLocationNfs where
  rnf :: DescribeLocationNfs -> ()
rnf DescribeLocationNfs' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationNfs' :: DescribeLocationNfs -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
locationArn

instance Data.ToHeaders DescribeLocationNfs where
  toHeaders :: DescribeLocationNfs -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"FmrsService.DescribeLocationNfs" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeLocationNfs where
  toJSON :: DescribeLocationNfs -> Value
toJSON DescribeLocationNfs' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationNfs' :: DescribeLocationNfs -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"LocationArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
locationArn)]
      )

instance Data.ToPath DescribeLocationNfs where
  toPath :: DescribeLocationNfs -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DescribeLocationNfs where
  toQuery :: DescribeLocationNfs -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | DescribeLocationNfsResponse
--
-- /See:/ 'newDescribeLocationNfsResponse' smart constructor.
data DescribeLocationNfsResponse = DescribeLocationNfsResponse'
  { -- | The time that the NFS location was created.
    DescribeLocationNfsResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Resource Name (ARN) of the NFS location that was described.
    DescribeLocationNfsResponse -> Maybe Text
locationArn :: Prelude.Maybe Prelude.Text,
    -- | The URL of the source NFS location that was described.
    DescribeLocationNfsResponse -> Maybe Text
locationUri :: Prelude.Maybe Prelude.Text,
    -- | The NFS mount options that DataSync used to mount your NFS share.
    DescribeLocationNfsResponse -> Maybe NfsMountOptions
mountOptions :: Prelude.Maybe NfsMountOptions,
    DescribeLocationNfsResponse -> Maybe OnPremConfig
onPremConfig :: Prelude.Maybe OnPremConfig,
    -- | The response's http status code.
    DescribeLocationNfsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeLocationNfsResponse -> DescribeLocationNfsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationNfsResponse -> DescribeLocationNfsResponse -> Bool
$c/= :: DescribeLocationNfsResponse -> DescribeLocationNfsResponse -> Bool
== :: DescribeLocationNfsResponse -> DescribeLocationNfsResponse -> Bool
$c== :: DescribeLocationNfsResponse -> DescribeLocationNfsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeLocationNfsResponse]
ReadPrec DescribeLocationNfsResponse
Int -> ReadS DescribeLocationNfsResponse
ReadS [DescribeLocationNfsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationNfsResponse]
$creadListPrec :: ReadPrec [DescribeLocationNfsResponse]
readPrec :: ReadPrec DescribeLocationNfsResponse
$creadPrec :: ReadPrec DescribeLocationNfsResponse
readList :: ReadS [DescribeLocationNfsResponse]
$creadList :: ReadS [DescribeLocationNfsResponse]
readsPrec :: Int -> ReadS DescribeLocationNfsResponse
$creadsPrec :: Int -> ReadS DescribeLocationNfsResponse
Prelude.Read, Int -> DescribeLocationNfsResponse -> ShowS
[DescribeLocationNfsResponse] -> ShowS
DescribeLocationNfsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationNfsResponse] -> ShowS
$cshowList :: [DescribeLocationNfsResponse] -> ShowS
show :: DescribeLocationNfsResponse -> String
$cshow :: DescribeLocationNfsResponse -> String
showsPrec :: Int -> DescribeLocationNfsResponse -> ShowS
$cshowsPrec :: Int -> DescribeLocationNfsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationNfsResponse x -> DescribeLocationNfsResponse
forall x.
DescribeLocationNfsResponse -> Rep DescribeLocationNfsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationNfsResponse x -> DescribeLocationNfsResponse
$cfrom :: forall x.
DescribeLocationNfsResponse -> Rep DescribeLocationNfsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLocationNfsResponse' 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:
--
-- 'creationTime', 'describeLocationNfsResponse_creationTime' - The time that the NFS location was created.
--
-- 'locationArn', 'describeLocationNfsResponse_locationArn' - The Amazon Resource Name (ARN) of the NFS location that was described.
--
-- 'locationUri', 'describeLocationNfsResponse_locationUri' - The URL of the source NFS location that was described.
--
-- 'mountOptions', 'describeLocationNfsResponse_mountOptions' - The NFS mount options that DataSync used to mount your NFS share.
--
-- 'onPremConfig', 'describeLocationNfsResponse_onPremConfig' - Undocumented member.
--
-- 'httpStatus', 'describeLocationNfsResponse_httpStatus' - The response's http status code.
newDescribeLocationNfsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeLocationNfsResponse
newDescribeLocationNfsResponse :: Int -> DescribeLocationNfsResponse
newDescribeLocationNfsResponse Int
pHttpStatus_ =
  DescribeLocationNfsResponse'
    { $sel:creationTime:DescribeLocationNfsResponse' :: Maybe POSIX
creationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:locationArn:DescribeLocationNfsResponse' :: Maybe Text
locationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:locationUri:DescribeLocationNfsResponse' :: Maybe Text
locationUri = forall a. Maybe a
Prelude.Nothing,
      $sel:mountOptions:DescribeLocationNfsResponse' :: Maybe NfsMountOptions
mountOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:onPremConfig:DescribeLocationNfsResponse' :: Maybe OnPremConfig
onPremConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeLocationNfsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The time that the NFS location was created.
describeLocationNfsResponse_creationTime :: Lens.Lens' DescribeLocationNfsResponse (Prelude.Maybe Prelude.UTCTime)
describeLocationNfsResponse_creationTime :: Lens' DescribeLocationNfsResponse (Maybe UTCTime)
describeLocationNfsResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationNfsResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeLocationNfsResponse
s@DescribeLocationNfsResponse' {} Maybe POSIX
a -> DescribeLocationNfsResponse
s {$sel:creationTime:DescribeLocationNfsResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeLocationNfsResponse) 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 Amazon Resource Name (ARN) of the NFS location that was described.
describeLocationNfsResponse_locationArn :: Lens.Lens' DescribeLocationNfsResponse (Prelude.Maybe Prelude.Text)
describeLocationNfsResponse_locationArn :: Lens' DescribeLocationNfsResponse (Maybe Text)
describeLocationNfsResponse_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationNfsResponse' {Maybe Text
locationArn :: Maybe Text
$sel:locationArn:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe Text
locationArn} -> Maybe Text
locationArn) (\s :: DescribeLocationNfsResponse
s@DescribeLocationNfsResponse' {} Maybe Text
a -> DescribeLocationNfsResponse
s {$sel:locationArn:DescribeLocationNfsResponse' :: Maybe Text
locationArn = Maybe Text
a} :: DescribeLocationNfsResponse)

-- | The URL of the source NFS location that was described.
describeLocationNfsResponse_locationUri :: Lens.Lens' DescribeLocationNfsResponse (Prelude.Maybe Prelude.Text)
describeLocationNfsResponse_locationUri :: Lens' DescribeLocationNfsResponse (Maybe Text)
describeLocationNfsResponse_locationUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationNfsResponse' {Maybe Text
locationUri :: Maybe Text
$sel:locationUri:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe Text
locationUri} -> Maybe Text
locationUri) (\s :: DescribeLocationNfsResponse
s@DescribeLocationNfsResponse' {} Maybe Text
a -> DescribeLocationNfsResponse
s {$sel:locationUri:DescribeLocationNfsResponse' :: Maybe Text
locationUri = Maybe Text
a} :: DescribeLocationNfsResponse)

-- | The NFS mount options that DataSync used to mount your NFS share.
describeLocationNfsResponse_mountOptions :: Lens.Lens' DescribeLocationNfsResponse (Prelude.Maybe NfsMountOptions)
describeLocationNfsResponse_mountOptions :: Lens' DescribeLocationNfsResponse (Maybe NfsMountOptions)
describeLocationNfsResponse_mountOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationNfsResponse' {Maybe NfsMountOptions
mountOptions :: Maybe NfsMountOptions
$sel:mountOptions:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe NfsMountOptions
mountOptions} -> Maybe NfsMountOptions
mountOptions) (\s :: DescribeLocationNfsResponse
s@DescribeLocationNfsResponse' {} Maybe NfsMountOptions
a -> DescribeLocationNfsResponse
s {$sel:mountOptions:DescribeLocationNfsResponse' :: Maybe NfsMountOptions
mountOptions = Maybe NfsMountOptions
a} :: DescribeLocationNfsResponse)

-- | Undocumented member.
describeLocationNfsResponse_onPremConfig :: Lens.Lens' DescribeLocationNfsResponse (Prelude.Maybe OnPremConfig)
describeLocationNfsResponse_onPremConfig :: Lens' DescribeLocationNfsResponse (Maybe OnPremConfig)
describeLocationNfsResponse_onPremConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationNfsResponse' {Maybe OnPremConfig
onPremConfig :: Maybe OnPremConfig
$sel:onPremConfig:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe OnPremConfig
onPremConfig} -> Maybe OnPremConfig
onPremConfig) (\s :: DescribeLocationNfsResponse
s@DescribeLocationNfsResponse' {} Maybe OnPremConfig
a -> DescribeLocationNfsResponse
s {$sel:onPremConfig:DescribeLocationNfsResponse' :: Maybe OnPremConfig
onPremConfig = Maybe OnPremConfig
a} :: DescribeLocationNfsResponse)

-- | The response's http status code.
describeLocationNfsResponse_httpStatus :: Lens.Lens' DescribeLocationNfsResponse Prelude.Int
describeLocationNfsResponse_httpStatus :: Lens' DescribeLocationNfsResponse Int
describeLocationNfsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationNfsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeLocationNfsResponse
s@DescribeLocationNfsResponse' {} Int
a -> DescribeLocationNfsResponse
s {$sel:httpStatus:DescribeLocationNfsResponse' :: Int
httpStatus = Int
a} :: DescribeLocationNfsResponse)

instance Prelude.NFData DescribeLocationNfsResponse where
  rnf :: DescribeLocationNfsResponse -> ()
rnf DescribeLocationNfsResponse' {Int
Maybe Text
Maybe POSIX
Maybe NfsMountOptions
Maybe OnPremConfig
httpStatus :: Int
onPremConfig :: Maybe OnPremConfig
mountOptions :: Maybe NfsMountOptions
locationUri :: Maybe Text
locationArn :: Maybe Text
creationTime :: Maybe POSIX
$sel:httpStatus:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Int
$sel:onPremConfig:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe OnPremConfig
$sel:mountOptions:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe NfsMountOptions
$sel:locationUri:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe Text
$sel:locationArn:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe Text
$sel:creationTime:DescribeLocationNfsResponse' :: DescribeLocationNfsResponse -> Maybe POSIX
..} =
    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
locationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
locationUri
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NfsMountOptions
mountOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OnPremConfig
onPremConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus