{-# 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.DescribeLocationSmb
-- 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 and user information about an SMB
-- location.
module Amazonka.DataSync.DescribeLocationSmb
  ( -- * Creating a Request
    DescribeLocationSmb (..),
    newDescribeLocationSmb,

    -- * Request Lenses
    describeLocationSmb_locationArn,

    -- * Destructuring the Response
    DescribeLocationSmbResponse (..),
    newDescribeLocationSmbResponse,

    -- * Response Lenses
    describeLocationSmbResponse_agentArns,
    describeLocationSmbResponse_creationTime,
    describeLocationSmbResponse_domain,
    describeLocationSmbResponse_locationArn,
    describeLocationSmbResponse_locationUri,
    describeLocationSmbResponse_mountOptions,
    describeLocationSmbResponse_user,
    describeLocationSmbResponse_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

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

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

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

instance Core.AWSRequest DescribeLocationSmb where
  type
    AWSResponse DescribeLocationSmb =
      DescribeLocationSmbResponse
  request :: (Service -> Service)
-> DescribeLocationSmb -> Request DescribeLocationSmb
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 DescribeLocationSmb
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeLocationSmb)))
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 (NonEmpty Text)
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe SmbMountOptions
-> Maybe Text
-> Int
-> DescribeLocationSmbResponse
DescribeLocationSmbResponse'
            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
"AgentArns")
            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
"Domain")
            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
"User")
            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 DescribeLocationSmb where
  hashWithSalt :: Int -> DescribeLocationSmb -> Int
hashWithSalt Int
_salt DescribeLocationSmb' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationSmb' :: DescribeLocationSmb -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
locationArn

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

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

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

-- | DescribeLocationSmbResponse
--
-- /See:/ 'newDescribeLocationSmbResponse' smart constructor.
data DescribeLocationSmbResponse = DescribeLocationSmbResponse'
  { -- | The Amazon Resource Name (ARN) of the source SMB file system location
    -- that is created.
    DescribeLocationSmbResponse -> Maybe (NonEmpty Text)
agentArns :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The time that the SMB location was created.
    DescribeLocationSmbResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the Windows domain that the SMB server belongs to.
    DescribeLocationSmbResponse -> Maybe Text
domain :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the SMB location that was described.
    DescribeLocationSmbResponse -> Maybe Text
locationArn :: Prelude.Maybe Prelude.Text,
    -- | The URL of the source SMB location that was described.
    DescribeLocationSmbResponse -> Maybe Text
locationUri :: Prelude.Maybe Prelude.Text,
    -- | The mount options that are available for DataSync to use to access an
    -- SMB location.
    DescribeLocationSmbResponse -> Maybe SmbMountOptions
mountOptions :: Prelude.Maybe SmbMountOptions,
    -- | The user who can mount the share, has the permissions to access files
    -- and folders in the SMB share.
    DescribeLocationSmbResponse -> Maybe Text
user :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeLocationSmbResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeLocationSmbResponse -> DescribeLocationSmbResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationSmbResponse -> DescribeLocationSmbResponse -> Bool
$c/= :: DescribeLocationSmbResponse -> DescribeLocationSmbResponse -> Bool
== :: DescribeLocationSmbResponse -> DescribeLocationSmbResponse -> Bool
$c== :: DescribeLocationSmbResponse -> DescribeLocationSmbResponse -> Bool
Prelude.Eq, ReadPrec [DescribeLocationSmbResponse]
ReadPrec DescribeLocationSmbResponse
Int -> ReadS DescribeLocationSmbResponse
ReadS [DescribeLocationSmbResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationSmbResponse]
$creadListPrec :: ReadPrec [DescribeLocationSmbResponse]
readPrec :: ReadPrec DescribeLocationSmbResponse
$creadPrec :: ReadPrec DescribeLocationSmbResponse
readList :: ReadS [DescribeLocationSmbResponse]
$creadList :: ReadS [DescribeLocationSmbResponse]
readsPrec :: Int -> ReadS DescribeLocationSmbResponse
$creadsPrec :: Int -> ReadS DescribeLocationSmbResponse
Prelude.Read, Int -> DescribeLocationSmbResponse -> ShowS
[DescribeLocationSmbResponse] -> ShowS
DescribeLocationSmbResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationSmbResponse] -> ShowS
$cshowList :: [DescribeLocationSmbResponse] -> ShowS
show :: DescribeLocationSmbResponse -> String
$cshow :: DescribeLocationSmbResponse -> String
showsPrec :: Int -> DescribeLocationSmbResponse -> ShowS
$cshowsPrec :: Int -> DescribeLocationSmbResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationSmbResponse x -> DescribeLocationSmbResponse
forall x.
DescribeLocationSmbResponse -> Rep DescribeLocationSmbResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationSmbResponse x -> DescribeLocationSmbResponse
$cfrom :: forall x.
DescribeLocationSmbResponse -> Rep DescribeLocationSmbResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLocationSmbResponse' 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:
--
-- 'agentArns', 'describeLocationSmbResponse_agentArns' - The Amazon Resource Name (ARN) of the source SMB file system location
-- that is created.
--
-- 'creationTime', 'describeLocationSmbResponse_creationTime' - The time that the SMB location was created.
--
-- 'domain', 'describeLocationSmbResponse_domain' - The name of the Windows domain that the SMB server belongs to.
--
-- 'locationArn', 'describeLocationSmbResponse_locationArn' - The Amazon Resource Name (ARN) of the SMB location that was described.
--
-- 'locationUri', 'describeLocationSmbResponse_locationUri' - The URL of the source SMB location that was described.
--
-- 'mountOptions', 'describeLocationSmbResponse_mountOptions' - The mount options that are available for DataSync to use to access an
-- SMB location.
--
-- 'user', 'describeLocationSmbResponse_user' - The user who can mount the share, has the permissions to access files
-- and folders in the SMB share.
--
-- 'httpStatus', 'describeLocationSmbResponse_httpStatus' - The response's http status code.
newDescribeLocationSmbResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeLocationSmbResponse
newDescribeLocationSmbResponse :: Int -> DescribeLocationSmbResponse
newDescribeLocationSmbResponse Int
pHttpStatus_ =
  DescribeLocationSmbResponse'
    { $sel:agentArns:DescribeLocationSmbResponse' :: Maybe (NonEmpty Text)
agentArns =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:DescribeLocationSmbResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:domain:DescribeLocationSmbResponse' :: Maybe Text
domain = forall a. Maybe a
Prelude.Nothing,
      $sel:locationArn:DescribeLocationSmbResponse' :: Maybe Text
locationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:locationUri:DescribeLocationSmbResponse' :: Maybe Text
locationUri = forall a. Maybe a
Prelude.Nothing,
      $sel:mountOptions:DescribeLocationSmbResponse' :: Maybe SmbMountOptions
mountOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:user:DescribeLocationSmbResponse' :: Maybe Text
user = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeLocationSmbResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the source SMB file system location
-- that is created.
describeLocationSmbResponse_agentArns :: Lens.Lens' DescribeLocationSmbResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeLocationSmbResponse_agentArns :: Lens' DescribeLocationSmbResponse (Maybe (NonEmpty Text))
describeLocationSmbResponse_agentArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationSmbResponse' {Maybe (NonEmpty Text)
agentArns :: Maybe (NonEmpty Text)
$sel:agentArns:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe (NonEmpty Text)
agentArns} -> Maybe (NonEmpty Text)
agentArns) (\s :: DescribeLocationSmbResponse
s@DescribeLocationSmbResponse' {} Maybe (NonEmpty Text)
a -> DescribeLocationSmbResponse
s {$sel:agentArns:DescribeLocationSmbResponse' :: Maybe (NonEmpty Text)
agentArns = Maybe (NonEmpty Text)
a} :: DescribeLocationSmbResponse) 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 SMB location was created.
describeLocationSmbResponse_creationTime :: Lens.Lens' DescribeLocationSmbResponse (Prelude.Maybe Prelude.UTCTime)
describeLocationSmbResponse_creationTime :: Lens' DescribeLocationSmbResponse (Maybe UTCTime)
describeLocationSmbResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationSmbResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeLocationSmbResponse
s@DescribeLocationSmbResponse' {} Maybe POSIX
a -> DescribeLocationSmbResponse
s {$sel:creationTime:DescribeLocationSmbResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeLocationSmbResponse) 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 name of the Windows domain that the SMB server belongs to.
describeLocationSmbResponse_domain :: Lens.Lens' DescribeLocationSmbResponse (Prelude.Maybe Prelude.Text)
describeLocationSmbResponse_domain :: Lens' DescribeLocationSmbResponse (Maybe Text)
describeLocationSmbResponse_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationSmbResponse' {Maybe Text
domain :: Maybe Text
$sel:domain:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe Text
domain} -> Maybe Text
domain) (\s :: DescribeLocationSmbResponse
s@DescribeLocationSmbResponse' {} Maybe Text
a -> DescribeLocationSmbResponse
s {$sel:domain:DescribeLocationSmbResponse' :: Maybe Text
domain = Maybe Text
a} :: DescribeLocationSmbResponse)

-- | The Amazon Resource Name (ARN) of the SMB location that was described.
describeLocationSmbResponse_locationArn :: Lens.Lens' DescribeLocationSmbResponse (Prelude.Maybe Prelude.Text)
describeLocationSmbResponse_locationArn :: Lens' DescribeLocationSmbResponse (Maybe Text)
describeLocationSmbResponse_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationSmbResponse' {Maybe Text
locationArn :: Maybe Text
$sel:locationArn:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe Text
locationArn} -> Maybe Text
locationArn) (\s :: DescribeLocationSmbResponse
s@DescribeLocationSmbResponse' {} Maybe Text
a -> DescribeLocationSmbResponse
s {$sel:locationArn:DescribeLocationSmbResponse' :: Maybe Text
locationArn = Maybe Text
a} :: DescribeLocationSmbResponse)

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

-- | The mount options that are available for DataSync to use to access an
-- SMB location.
describeLocationSmbResponse_mountOptions :: Lens.Lens' DescribeLocationSmbResponse (Prelude.Maybe SmbMountOptions)
describeLocationSmbResponse_mountOptions :: Lens' DescribeLocationSmbResponse (Maybe SmbMountOptions)
describeLocationSmbResponse_mountOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationSmbResponse' {Maybe SmbMountOptions
mountOptions :: Maybe SmbMountOptions
$sel:mountOptions:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe SmbMountOptions
mountOptions} -> Maybe SmbMountOptions
mountOptions) (\s :: DescribeLocationSmbResponse
s@DescribeLocationSmbResponse' {} Maybe SmbMountOptions
a -> DescribeLocationSmbResponse
s {$sel:mountOptions:DescribeLocationSmbResponse' :: Maybe SmbMountOptions
mountOptions = Maybe SmbMountOptions
a} :: DescribeLocationSmbResponse)

-- | The user who can mount the share, has the permissions to access files
-- and folders in the SMB share.
describeLocationSmbResponse_user :: Lens.Lens' DescribeLocationSmbResponse (Prelude.Maybe Prelude.Text)
describeLocationSmbResponse_user :: Lens' DescribeLocationSmbResponse (Maybe Text)
describeLocationSmbResponse_user = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationSmbResponse' {Maybe Text
user :: Maybe Text
$sel:user:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe Text
user} -> Maybe Text
user) (\s :: DescribeLocationSmbResponse
s@DescribeLocationSmbResponse' {} Maybe Text
a -> DescribeLocationSmbResponse
s {$sel:user:DescribeLocationSmbResponse' :: Maybe Text
user = Maybe Text
a} :: DescribeLocationSmbResponse)

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

instance Prelude.NFData DescribeLocationSmbResponse where
  rnf :: DescribeLocationSmbResponse -> ()
rnf DescribeLocationSmbResponse' {Int
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe SmbMountOptions
httpStatus :: Int
user :: Maybe Text
mountOptions :: Maybe SmbMountOptions
locationUri :: Maybe Text
locationArn :: Maybe Text
domain :: Maybe Text
creationTime :: Maybe POSIX
agentArns :: Maybe (NonEmpty Text)
$sel:httpStatus:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Int
$sel:user:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe Text
$sel:mountOptions:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe SmbMountOptions
$sel:locationUri:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe Text
$sel:locationArn:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe Text
$sel:domain:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe Text
$sel:creationTime:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe POSIX
$sel:agentArns:DescribeLocationSmbResponse' :: DescribeLocationSmbResponse -> Maybe (NonEmpty Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
agentArns
      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
domain
      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 SmbMountOptions
mountOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
user
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus