{-# 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.DescribeLocationEfs
-- 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 about your DataSync location for an Amazon EFS file
-- system.
module Amazonka.DataSync.DescribeLocationEfs
  ( -- * Creating a Request
    DescribeLocationEfs (..),
    newDescribeLocationEfs,

    -- * Request Lenses
    describeLocationEfs_locationArn,

    -- * Destructuring the Response
    DescribeLocationEfsResponse (..),
    newDescribeLocationEfsResponse,

    -- * Response Lenses
    describeLocationEfsResponse_accessPointArn,
    describeLocationEfsResponse_creationTime,
    describeLocationEfsResponse_ec2Config,
    describeLocationEfsResponse_fileSystemAccessRoleArn,
    describeLocationEfsResponse_inTransitEncryption,
    describeLocationEfsResponse_locationArn,
    describeLocationEfsResponse_locationUri,
    describeLocationEfsResponse_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

-- | DescribeLocationEfsRequest
--
-- /See:/ 'newDescribeLocationEfs' smart constructor.
data DescribeLocationEfs = DescribeLocationEfs'
  { -- | The Amazon Resource Name (ARN) of the Amazon EFS file system location
    -- that you want information about.
    DescribeLocationEfs -> Text
locationArn :: Prelude.Text
  }
  deriving (DescribeLocationEfs -> DescribeLocationEfs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationEfs -> DescribeLocationEfs -> Bool
$c/= :: DescribeLocationEfs -> DescribeLocationEfs -> Bool
== :: DescribeLocationEfs -> DescribeLocationEfs -> Bool
$c== :: DescribeLocationEfs -> DescribeLocationEfs -> Bool
Prelude.Eq, ReadPrec [DescribeLocationEfs]
ReadPrec DescribeLocationEfs
Int -> ReadS DescribeLocationEfs
ReadS [DescribeLocationEfs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationEfs]
$creadListPrec :: ReadPrec [DescribeLocationEfs]
readPrec :: ReadPrec DescribeLocationEfs
$creadPrec :: ReadPrec DescribeLocationEfs
readList :: ReadS [DescribeLocationEfs]
$creadList :: ReadS [DescribeLocationEfs]
readsPrec :: Int -> ReadS DescribeLocationEfs
$creadsPrec :: Int -> ReadS DescribeLocationEfs
Prelude.Read, Int -> DescribeLocationEfs -> ShowS
[DescribeLocationEfs] -> ShowS
DescribeLocationEfs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationEfs] -> ShowS
$cshowList :: [DescribeLocationEfs] -> ShowS
show :: DescribeLocationEfs -> String
$cshow :: DescribeLocationEfs -> String
showsPrec :: Int -> DescribeLocationEfs -> ShowS
$cshowsPrec :: Int -> DescribeLocationEfs -> ShowS
Prelude.Show, forall x. Rep DescribeLocationEfs x -> DescribeLocationEfs
forall x. DescribeLocationEfs -> Rep DescribeLocationEfs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeLocationEfs x -> DescribeLocationEfs
$cfrom :: forall x. DescribeLocationEfs -> Rep DescribeLocationEfs x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLocationEfs' 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', 'describeLocationEfs_locationArn' - The Amazon Resource Name (ARN) of the Amazon EFS file system location
-- that you want information about.
newDescribeLocationEfs ::
  -- | 'locationArn'
  Prelude.Text ->
  DescribeLocationEfs
newDescribeLocationEfs :: Text -> DescribeLocationEfs
newDescribeLocationEfs Text
pLocationArn_ =
  DescribeLocationEfs' {$sel:locationArn:DescribeLocationEfs' :: Text
locationArn = Text
pLocationArn_}

-- | The Amazon Resource Name (ARN) of the Amazon EFS file system location
-- that you want information about.
describeLocationEfs_locationArn :: Lens.Lens' DescribeLocationEfs Prelude.Text
describeLocationEfs_locationArn :: Lens' DescribeLocationEfs Text
describeLocationEfs_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationEfs' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationEfs' :: DescribeLocationEfs -> Text
locationArn} -> Text
locationArn) (\s :: DescribeLocationEfs
s@DescribeLocationEfs' {} Text
a -> DescribeLocationEfs
s {$sel:locationArn:DescribeLocationEfs' :: Text
locationArn = Text
a} :: DescribeLocationEfs)

instance Core.AWSRequest DescribeLocationEfs where
  type
    AWSResponse DescribeLocationEfs =
      DescribeLocationEfsResponse
  request :: (Service -> Service)
-> DescribeLocationEfs -> Request DescribeLocationEfs
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 DescribeLocationEfs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeLocationEfs)))
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 Text
-> Maybe POSIX
-> Maybe Ec2Config
-> Maybe Text
-> Maybe EfsInTransitEncryption
-> Maybe Text
-> Maybe Text
-> Int
-> DescribeLocationEfsResponse
DescribeLocationEfsResponse'
            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
"AccessPointArn")
            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
"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
"Ec2Config")
            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
"FileSystemAccessRoleArn")
            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
"InTransitEncryption")
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

instance Data.ToHeaders DescribeLocationEfs where
  toHeaders :: DescribeLocationEfs -> 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.DescribeLocationEfs" ::
                          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 DescribeLocationEfs where
  toJSON :: DescribeLocationEfs -> Value
toJSON DescribeLocationEfs' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationEfs' :: DescribeLocationEfs -> 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 DescribeLocationEfs where
  toPath :: DescribeLocationEfs -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | DescribeLocationEfsResponse
--
-- /See:/ 'newDescribeLocationEfsResponse' smart constructor.
data DescribeLocationEfsResponse = DescribeLocationEfsResponse'
  { -- | The ARN of the access point that DataSync uses to access the Amazon EFS
    -- file system.
    DescribeLocationEfsResponse -> Maybe Text
accessPointArn :: Prelude.Maybe Prelude.Text,
    -- | The time that the location was created.
    DescribeLocationEfsResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    DescribeLocationEfsResponse -> Maybe Ec2Config
ec2Config :: Prelude.Maybe Ec2Config,
    -- | The Identity and Access Management (IAM) role that DataSync assumes when
    -- mounting the Amazon EFS file system.
    DescribeLocationEfsResponse -> Maybe Text
fileSystemAccessRoleArn :: Prelude.Maybe Prelude.Text,
    -- | Describes whether DataSync uses Transport Layer Security (TLS)
    -- encryption when copying data to or from the Amazon EFS file system.
    DescribeLocationEfsResponse -> Maybe EfsInTransitEncryption
inTransitEncryption :: Prelude.Maybe EfsInTransitEncryption,
    -- | The ARN of the Amazon EFS file system location.
    DescribeLocationEfsResponse -> Maybe Text
locationArn :: Prelude.Maybe Prelude.Text,
    -- | The URL of the Amazon EFS file system location.
    DescribeLocationEfsResponse -> Maybe Text
locationUri :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeLocationEfsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeLocationEfsResponse -> DescribeLocationEfsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationEfsResponse -> DescribeLocationEfsResponse -> Bool
$c/= :: DescribeLocationEfsResponse -> DescribeLocationEfsResponse -> Bool
== :: DescribeLocationEfsResponse -> DescribeLocationEfsResponse -> Bool
$c== :: DescribeLocationEfsResponse -> DescribeLocationEfsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeLocationEfsResponse]
ReadPrec DescribeLocationEfsResponse
Int -> ReadS DescribeLocationEfsResponse
ReadS [DescribeLocationEfsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationEfsResponse]
$creadListPrec :: ReadPrec [DescribeLocationEfsResponse]
readPrec :: ReadPrec DescribeLocationEfsResponse
$creadPrec :: ReadPrec DescribeLocationEfsResponse
readList :: ReadS [DescribeLocationEfsResponse]
$creadList :: ReadS [DescribeLocationEfsResponse]
readsPrec :: Int -> ReadS DescribeLocationEfsResponse
$creadsPrec :: Int -> ReadS DescribeLocationEfsResponse
Prelude.Read, Int -> DescribeLocationEfsResponse -> ShowS
[DescribeLocationEfsResponse] -> ShowS
DescribeLocationEfsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationEfsResponse] -> ShowS
$cshowList :: [DescribeLocationEfsResponse] -> ShowS
show :: DescribeLocationEfsResponse -> String
$cshow :: DescribeLocationEfsResponse -> String
showsPrec :: Int -> DescribeLocationEfsResponse -> ShowS
$cshowsPrec :: Int -> DescribeLocationEfsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationEfsResponse x -> DescribeLocationEfsResponse
forall x.
DescribeLocationEfsResponse -> Rep DescribeLocationEfsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationEfsResponse x -> DescribeLocationEfsResponse
$cfrom :: forall x.
DescribeLocationEfsResponse -> Rep DescribeLocationEfsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLocationEfsResponse' 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:
--
-- 'accessPointArn', 'describeLocationEfsResponse_accessPointArn' - The ARN of the access point that DataSync uses to access the Amazon EFS
-- file system.
--
-- 'creationTime', 'describeLocationEfsResponse_creationTime' - The time that the location was created.
--
-- 'ec2Config', 'describeLocationEfsResponse_ec2Config' - Undocumented member.
--
-- 'fileSystemAccessRoleArn', 'describeLocationEfsResponse_fileSystemAccessRoleArn' - The Identity and Access Management (IAM) role that DataSync assumes when
-- mounting the Amazon EFS file system.
--
-- 'inTransitEncryption', 'describeLocationEfsResponse_inTransitEncryption' - Describes whether DataSync uses Transport Layer Security (TLS)
-- encryption when copying data to or from the Amazon EFS file system.
--
-- 'locationArn', 'describeLocationEfsResponse_locationArn' - The ARN of the Amazon EFS file system location.
--
-- 'locationUri', 'describeLocationEfsResponse_locationUri' - The URL of the Amazon EFS file system location.
--
-- 'httpStatus', 'describeLocationEfsResponse_httpStatus' - The response's http status code.
newDescribeLocationEfsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeLocationEfsResponse
newDescribeLocationEfsResponse :: Int -> DescribeLocationEfsResponse
newDescribeLocationEfsResponse Int
pHttpStatus_ =
  DescribeLocationEfsResponse'
    { $sel:accessPointArn:DescribeLocationEfsResponse' :: Maybe Text
accessPointArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:DescribeLocationEfsResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:ec2Config:DescribeLocationEfsResponse' :: Maybe Ec2Config
ec2Config = forall a. Maybe a
Prelude.Nothing,
      $sel:fileSystemAccessRoleArn:DescribeLocationEfsResponse' :: Maybe Text
fileSystemAccessRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:inTransitEncryption:DescribeLocationEfsResponse' :: Maybe EfsInTransitEncryption
inTransitEncryption = forall a. Maybe a
Prelude.Nothing,
      $sel:locationArn:DescribeLocationEfsResponse' :: Maybe Text
locationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:locationUri:DescribeLocationEfsResponse' :: Maybe Text
locationUri = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeLocationEfsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the access point that DataSync uses to access the Amazon EFS
-- file system.
describeLocationEfsResponse_accessPointArn :: Lens.Lens' DescribeLocationEfsResponse (Prelude.Maybe Prelude.Text)
describeLocationEfsResponse_accessPointArn :: Lens' DescribeLocationEfsResponse (Maybe Text)
describeLocationEfsResponse_accessPointArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationEfsResponse' {Maybe Text
accessPointArn :: Maybe Text
$sel:accessPointArn:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Text
accessPointArn} -> Maybe Text
accessPointArn) (\s :: DescribeLocationEfsResponse
s@DescribeLocationEfsResponse' {} Maybe Text
a -> DescribeLocationEfsResponse
s {$sel:accessPointArn:DescribeLocationEfsResponse' :: Maybe Text
accessPointArn = Maybe Text
a} :: DescribeLocationEfsResponse)

-- | The time that the location was created.
describeLocationEfsResponse_creationTime :: Lens.Lens' DescribeLocationEfsResponse (Prelude.Maybe Prelude.UTCTime)
describeLocationEfsResponse_creationTime :: Lens' DescribeLocationEfsResponse (Maybe UTCTime)
describeLocationEfsResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationEfsResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeLocationEfsResponse
s@DescribeLocationEfsResponse' {} Maybe POSIX
a -> DescribeLocationEfsResponse
s {$sel:creationTime:DescribeLocationEfsResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeLocationEfsResponse) 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

-- | Undocumented member.
describeLocationEfsResponse_ec2Config :: Lens.Lens' DescribeLocationEfsResponse (Prelude.Maybe Ec2Config)
describeLocationEfsResponse_ec2Config :: Lens' DescribeLocationEfsResponse (Maybe Ec2Config)
describeLocationEfsResponse_ec2Config = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationEfsResponse' {Maybe Ec2Config
ec2Config :: Maybe Ec2Config
$sel:ec2Config:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Ec2Config
ec2Config} -> Maybe Ec2Config
ec2Config) (\s :: DescribeLocationEfsResponse
s@DescribeLocationEfsResponse' {} Maybe Ec2Config
a -> DescribeLocationEfsResponse
s {$sel:ec2Config:DescribeLocationEfsResponse' :: Maybe Ec2Config
ec2Config = Maybe Ec2Config
a} :: DescribeLocationEfsResponse)

-- | The Identity and Access Management (IAM) role that DataSync assumes when
-- mounting the Amazon EFS file system.
describeLocationEfsResponse_fileSystemAccessRoleArn :: Lens.Lens' DescribeLocationEfsResponse (Prelude.Maybe Prelude.Text)
describeLocationEfsResponse_fileSystemAccessRoleArn :: Lens' DescribeLocationEfsResponse (Maybe Text)
describeLocationEfsResponse_fileSystemAccessRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationEfsResponse' {Maybe Text
fileSystemAccessRoleArn :: Maybe Text
$sel:fileSystemAccessRoleArn:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Text
fileSystemAccessRoleArn} -> Maybe Text
fileSystemAccessRoleArn) (\s :: DescribeLocationEfsResponse
s@DescribeLocationEfsResponse' {} Maybe Text
a -> DescribeLocationEfsResponse
s {$sel:fileSystemAccessRoleArn:DescribeLocationEfsResponse' :: Maybe Text
fileSystemAccessRoleArn = Maybe Text
a} :: DescribeLocationEfsResponse)

-- | Describes whether DataSync uses Transport Layer Security (TLS)
-- encryption when copying data to or from the Amazon EFS file system.
describeLocationEfsResponse_inTransitEncryption :: Lens.Lens' DescribeLocationEfsResponse (Prelude.Maybe EfsInTransitEncryption)
describeLocationEfsResponse_inTransitEncryption :: Lens' DescribeLocationEfsResponse (Maybe EfsInTransitEncryption)
describeLocationEfsResponse_inTransitEncryption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationEfsResponse' {Maybe EfsInTransitEncryption
inTransitEncryption :: Maybe EfsInTransitEncryption
$sel:inTransitEncryption:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe EfsInTransitEncryption
inTransitEncryption} -> Maybe EfsInTransitEncryption
inTransitEncryption) (\s :: DescribeLocationEfsResponse
s@DescribeLocationEfsResponse' {} Maybe EfsInTransitEncryption
a -> DescribeLocationEfsResponse
s {$sel:inTransitEncryption:DescribeLocationEfsResponse' :: Maybe EfsInTransitEncryption
inTransitEncryption = Maybe EfsInTransitEncryption
a} :: DescribeLocationEfsResponse)

-- | The ARN of the Amazon EFS file system location.
describeLocationEfsResponse_locationArn :: Lens.Lens' DescribeLocationEfsResponse (Prelude.Maybe Prelude.Text)
describeLocationEfsResponse_locationArn :: Lens' DescribeLocationEfsResponse (Maybe Text)
describeLocationEfsResponse_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationEfsResponse' {Maybe Text
locationArn :: Maybe Text
$sel:locationArn:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Text
locationArn} -> Maybe Text
locationArn) (\s :: DescribeLocationEfsResponse
s@DescribeLocationEfsResponse' {} Maybe Text
a -> DescribeLocationEfsResponse
s {$sel:locationArn:DescribeLocationEfsResponse' :: Maybe Text
locationArn = Maybe Text
a} :: DescribeLocationEfsResponse)

-- | The URL of the Amazon EFS file system location.
describeLocationEfsResponse_locationUri :: Lens.Lens' DescribeLocationEfsResponse (Prelude.Maybe Prelude.Text)
describeLocationEfsResponse_locationUri :: Lens' DescribeLocationEfsResponse (Maybe Text)
describeLocationEfsResponse_locationUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationEfsResponse' {Maybe Text
locationUri :: Maybe Text
$sel:locationUri:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Text
locationUri} -> Maybe Text
locationUri) (\s :: DescribeLocationEfsResponse
s@DescribeLocationEfsResponse' {} Maybe Text
a -> DescribeLocationEfsResponse
s {$sel:locationUri:DescribeLocationEfsResponse' :: Maybe Text
locationUri = Maybe Text
a} :: DescribeLocationEfsResponse)

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

instance Prelude.NFData DescribeLocationEfsResponse where
  rnf :: DescribeLocationEfsResponse -> ()
rnf DescribeLocationEfsResponse' {Int
Maybe Text
Maybe POSIX
Maybe Ec2Config
Maybe EfsInTransitEncryption
httpStatus :: Int
locationUri :: Maybe Text
locationArn :: Maybe Text
inTransitEncryption :: Maybe EfsInTransitEncryption
fileSystemAccessRoleArn :: Maybe Text
ec2Config :: Maybe Ec2Config
creationTime :: Maybe POSIX
accessPointArn :: Maybe Text
$sel:httpStatus:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Int
$sel:locationUri:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Text
$sel:locationArn:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Text
$sel:inTransitEncryption:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe EfsInTransitEncryption
$sel:fileSystemAccessRoleArn:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Text
$sel:ec2Config:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Ec2Config
$sel:creationTime:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe POSIX
$sel:accessPointArn:DescribeLocationEfsResponse' :: DescribeLocationEfsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accessPointArn
      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 Ec2Config
ec2Config
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileSystemAccessRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EfsInTransitEncryption
inTransitEncryption
      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 Int
httpStatus