{-# 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.DescribeLocationFsxWindows
-- 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 an Amazon FSx for Windows File Server location,
-- such as information about its path.
module Amazonka.DataSync.DescribeLocationFsxWindows
  ( -- * Creating a Request
    DescribeLocationFsxWindows (..),
    newDescribeLocationFsxWindows,

    -- * Request Lenses
    describeLocationFsxWindows_locationArn,

    -- * Destructuring the Response
    DescribeLocationFsxWindowsResponse (..),
    newDescribeLocationFsxWindowsResponse,

    -- * Response Lenses
    describeLocationFsxWindowsResponse_creationTime,
    describeLocationFsxWindowsResponse_domain,
    describeLocationFsxWindowsResponse_locationArn,
    describeLocationFsxWindowsResponse_locationUri,
    describeLocationFsxWindowsResponse_securityGroupArns,
    describeLocationFsxWindowsResponse_user,
    describeLocationFsxWindowsResponse_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

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

-- |
-- Create a value of 'DescribeLocationFsxWindows' 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', 'describeLocationFsxWindows_locationArn' - The Amazon Resource Name (ARN) of the FSx for Windows File Server
-- location to describe.
newDescribeLocationFsxWindows ::
  -- | 'locationArn'
  Prelude.Text ->
  DescribeLocationFsxWindows
newDescribeLocationFsxWindows :: Text -> DescribeLocationFsxWindows
newDescribeLocationFsxWindows Text
pLocationArn_ =
  DescribeLocationFsxWindows'
    { $sel:locationArn:DescribeLocationFsxWindows' :: Text
locationArn =
        Text
pLocationArn_
    }

-- | The Amazon Resource Name (ARN) of the FSx for Windows File Server
-- location to describe.
describeLocationFsxWindows_locationArn :: Lens.Lens' DescribeLocationFsxWindows Prelude.Text
describeLocationFsxWindows_locationArn :: Lens' DescribeLocationFsxWindows Text
describeLocationFsxWindows_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxWindows' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationFsxWindows' :: DescribeLocationFsxWindows -> Text
locationArn} -> Text
locationArn) (\s :: DescribeLocationFsxWindows
s@DescribeLocationFsxWindows' {} Text
a -> DescribeLocationFsxWindows
s {$sel:locationArn:DescribeLocationFsxWindows' :: Text
locationArn = Text
a} :: DescribeLocationFsxWindows)

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

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

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

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

-- | /See:/ 'newDescribeLocationFsxWindowsResponse' smart constructor.
data DescribeLocationFsxWindowsResponse = DescribeLocationFsxWindowsResponse'
  { -- | The time that the FSx for Windows File Server location was created.
    DescribeLocationFsxWindowsResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the Windows domain that the FSx for Windows File Server
    -- belongs to.
    DescribeLocationFsxWindowsResponse -> Maybe Text
domain :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the FSx for Windows File Server
    -- location that was described.
    DescribeLocationFsxWindowsResponse -> Maybe Text
locationArn :: Prelude.Maybe Prelude.Text,
    -- | The URL of the FSx for Windows File Server location that was described.
    DescribeLocationFsxWindowsResponse -> Maybe Text
locationUri :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Names (ARNs) of the security groups that are
    -- configured for the FSx for Windows File Server file system.
    DescribeLocationFsxWindowsResponse -> Maybe (NonEmpty Text)
securityGroupArns :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The user who has the permissions to access files and folders in the FSx
    -- for Windows File Server file system.
    DescribeLocationFsxWindowsResponse -> Maybe Text
user :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeLocationFsxWindowsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeLocationFsxWindowsResponse
-> DescribeLocationFsxWindowsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationFsxWindowsResponse
-> DescribeLocationFsxWindowsResponse -> Bool
$c/= :: DescribeLocationFsxWindowsResponse
-> DescribeLocationFsxWindowsResponse -> Bool
== :: DescribeLocationFsxWindowsResponse
-> DescribeLocationFsxWindowsResponse -> Bool
$c== :: DescribeLocationFsxWindowsResponse
-> DescribeLocationFsxWindowsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeLocationFsxWindowsResponse]
ReadPrec DescribeLocationFsxWindowsResponse
Int -> ReadS DescribeLocationFsxWindowsResponse
ReadS [DescribeLocationFsxWindowsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationFsxWindowsResponse]
$creadListPrec :: ReadPrec [DescribeLocationFsxWindowsResponse]
readPrec :: ReadPrec DescribeLocationFsxWindowsResponse
$creadPrec :: ReadPrec DescribeLocationFsxWindowsResponse
readList :: ReadS [DescribeLocationFsxWindowsResponse]
$creadList :: ReadS [DescribeLocationFsxWindowsResponse]
readsPrec :: Int -> ReadS DescribeLocationFsxWindowsResponse
$creadsPrec :: Int -> ReadS DescribeLocationFsxWindowsResponse
Prelude.Read, Int -> DescribeLocationFsxWindowsResponse -> ShowS
[DescribeLocationFsxWindowsResponse] -> ShowS
DescribeLocationFsxWindowsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationFsxWindowsResponse] -> ShowS
$cshowList :: [DescribeLocationFsxWindowsResponse] -> ShowS
show :: DescribeLocationFsxWindowsResponse -> String
$cshow :: DescribeLocationFsxWindowsResponse -> String
showsPrec :: Int -> DescribeLocationFsxWindowsResponse -> ShowS
$cshowsPrec :: Int -> DescribeLocationFsxWindowsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationFsxWindowsResponse x
-> DescribeLocationFsxWindowsResponse
forall x.
DescribeLocationFsxWindowsResponse
-> Rep DescribeLocationFsxWindowsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationFsxWindowsResponse x
-> DescribeLocationFsxWindowsResponse
$cfrom :: forall x.
DescribeLocationFsxWindowsResponse
-> Rep DescribeLocationFsxWindowsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLocationFsxWindowsResponse' 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', 'describeLocationFsxWindowsResponse_creationTime' - The time that the FSx for Windows File Server location was created.
--
-- 'domain', 'describeLocationFsxWindowsResponse_domain' - The name of the Windows domain that the FSx for Windows File Server
-- belongs to.
--
-- 'locationArn', 'describeLocationFsxWindowsResponse_locationArn' - The Amazon Resource Name (ARN) of the FSx for Windows File Server
-- location that was described.
--
-- 'locationUri', 'describeLocationFsxWindowsResponse_locationUri' - The URL of the FSx for Windows File Server location that was described.
--
-- 'securityGroupArns', 'describeLocationFsxWindowsResponse_securityGroupArns' - The Amazon Resource Names (ARNs) of the security groups that are
-- configured for the FSx for Windows File Server file system.
--
-- 'user', 'describeLocationFsxWindowsResponse_user' - The user who has the permissions to access files and folders in the FSx
-- for Windows File Server file system.
--
-- 'httpStatus', 'describeLocationFsxWindowsResponse_httpStatus' - The response's http status code.
newDescribeLocationFsxWindowsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeLocationFsxWindowsResponse
newDescribeLocationFsxWindowsResponse :: Int -> DescribeLocationFsxWindowsResponse
newDescribeLocationFsxWindowsResponse Int
pHttpStatus_ =
  DescribeLocationFsxWindowsResponse'
    { $sel:creationTime:DescribeLocationFsxWindowsResponse' :: Maybe POSIX
creationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:domain:DescribeLocationFsxWindowsResponse' :: Maybe Text
domain = forall a. Maybe a
Prelude.Nothing,
      $sel:locationArn:DescribeLocationFsxWindowsResponse' :: Maybe Text
locationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:locationUri:DescribeLocationFsxWindowsResponse' :: Maybe Text
locationUri = forall a. Maybe a
Prelude.Nothing,
      $sel:securityGroupArns:DescribeLocationFsxWindowsResponse' :: Maybe (NonEmpty Text)
securityGroupArns = forall a. Maybe a
Prelude.Nothing,
      $sel:user:DescribeLocationFsxWindowsResponse' :: Maybe Text
user = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeLocationFsxWindowsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The time that the FSx for Windows File Server location was created.
describeLocationFsxWindowsResponse_creationTime :: Lens.Lens' DescribeLocationFsxWindowsResponse (Prelude.Maybe Prelude.UTCTime)
describeLocationFsxWindowsResponse_creationTime :: Lens' DescribeLocationFsxWindowsResponse (Maybe UTCTime)
describeLocationFsxWindowsResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxWindowsResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeLocationFsxWindowsResponse
s@DescribeLocationFsxWindowsResponse' {} Maybe POSIX
a -> DescribeLocationFsxWindowsResponse
s {$sel:creationTime:DescribeLocationFsxWindowsResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeLocationFsxWindowsResponse) 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 FSx for Windows File Server
-- belongs to.
describeLocationFsxWindowsResponse_domain :: Lens.Lens' DescribeLocationFsxWindowsResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxWindowsResponse_domain :: Lens' DescribeLocationFsxWindowsResponse (Maybe Text)
describeLocationFsxWindowsResponse_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxWindowsResponse' {Maybe Text
domain :: Maybe Text
$sel:domain:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe Text
domain} -> Maybe Text
domain) (\s :: DescribeLocationFsxWindowsResponse
s@DescribeLocationFsxWindowsResponse' {} Maybe Text
a -> DescribeLocationFsxWindowsResponse
s {$sel:domain:DescribeLocationFsxWindowsResponse' :: Maybe Text
domain = Maybe Text
a} :: DescribeLocationFsxWindowsResponse)

-- | The Amazon Resource Name (ARN) of the FSx for Windows File Server
-- location that was described.
describeLocationFsxWindowsResponse_locationArn :: Lens.Lens' DescribeLocationFsxWindowsResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxWindowsResponse_locationArn :: Lens' DescribeLocationFsxWindowsResponse (Maybe Text)
describeLocationFsxWindowsResponse_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxWindowsResponse' {Maybe Text
locationArn :: Maybe Text
$sel:locationArn:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe Text
locationArn} -> Maybe Text
locationArn) (\s :: DescribeLocationFsxWindowsResponse
s@DescribeLocationFsxWindowsResponse' {} Maybe Text
a -> DescribeLocationFsxWindowsResponse
s {$sel:locationArn:DescribeLocationFsxWindowsResponse' :: Maybe Text
locationArn = Maybe Text
a} :: DescribeLocationFsxWindowsResponse)

-- | The URL of the FSx for Windows File Server location that was described.
describeLocationFsxWindowsResponse_locationUri :: Lens.Lens' DescribeLocationFsxWindowsResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxWindowsResponse_locationUri :: Lens' DescribeLocationFsxWindowsResponse (Maybe Text)
describeLocationFsxWindowsResponse_locationUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxWindowsResponse' {Maybe Text
locationUri :: Maybe Text
$sel:locationUri:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe Text
locationUri} -> Maybe Text
locationUri) (\s :: DescribeLocationFsxWindowsResponse
s@DescribeLocationFsxWindowsResponse' {} Maybe Text
a -> DescribeLocationFsxWindowsResponse
s {$sel:locationUri:DescribeLocationFsxWindowsResponse' :: Maybe Text
locationUri = Maybe Text
a} :: DescribeLocationFsxWindowsResponse)

-- | The Amazon Resource Names (ARNs) of the security groups that are
-- configured for the FSx for Windows File Server file system.
describeLocationFsxWindowsResponse_securityGroupArns :: Lens.Lens' DescribeLocationFsxWindowsResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeLocationFsxWindowsResponse_securityGroupArns :: Lens' DescribeLocationFsxWindowsResponse (Maybe (NonEmpty Text))
describeLocationFsxWindowsResponse_securityGroupArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxWindowsResponse' {Maybe (NonEmpty Text)
securityGroupArns :: Maybe (NonEmpty Text)
$sel:securityGroupArns:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe (NonEmpty Text)
securityGroupArns} -> Maybe (NonEmpty Text)
securityGroupArns) (\s :: DescribeLocationFsxWindowsResponse
s@DescribeLocationFsxWindowsResponse' {} Maybe (NonEmpty Text)
a -> DescribeLocationFsxWindowsResponse
s {$sel:securityGroupArns:DescribeLocationFsxWindowsResponse' :: Maybe (NonEmpty Text)
securityGroupArns = Maybe (NonEmpty Text)
a} :: DescribeLocationFsxWindowsResponse) 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 user who has the permissions to access files and folders in the FSx
-- for Windows File Server file system.
describeLocationFsxWindowsResponse_user :: Lens.Lens' DescribeLocationFsxWindowsResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxWindowsResponse_user :: Lens' DescribeLocationFsxWindowsResponse (Maybe Text)
describeLocationFsxWindowsResponse_user = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxWindowsResponse' {Maybe Text
user :: Maybe Text
$sel:user:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe Text
user} -> Maybe Text
user) (\s :: DescribeLocationFsxWindowsResponse
s@DescribeLocationFsxWindowsResponse' {} Maybe Text
a -> DescribeLocationFsxWindowsResponse
s {$sel:user:DescribeLocationFsxWindowsResponse' :: Maybe Text
user = Maybe Text
a} :: DescribeLocationFsxWindowsResponse)

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

instance
  Prelude.NFData
    DescribeLocationFsxWindowsResponse
  where
  rnf :: DescribeLocationFsxWindowsResponse -> ()
rnf DescribeLocationFsxWindowsResponse' {Int
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
httpStatus :: Int
user :: Maybe Text
securityGroupArns :: Maybe (NonEmpty Text)
locationUri :: Maybe Text
locationArn :: Maybe Text
domain :: Maybe Text
creationTime :: Maybe POSIX
$sel:httpStatus:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Int
$sel:user:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe Text
$sel:securityGroupArns:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe (NonEmpty Text)
$sel:locationUri:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe Text
$sel:locationArn:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe Text
$sel:domain:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> Maybe Text
$sel:creationTime:DescribeLocationFsxWindowsResponse' :: DescribeLocationFsxWindowsResponse -> 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
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 (NonEmpty Text)
securityGroupArns
      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