{-# 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.DescribeLocationFsxOpenZfs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides details about how an DataSync location for an Amazon FSx for
-- OpenZFS file system is configured.
--
-- Response elements related to @SMB@ aren\'t supported with the
-- @DescribeLocationFsxOpenZfs@ operation.
module Amazonka.DataSync.DescribeLocationFsxOpenZfs
  ( -- * Creating a Request
    DescribeLocationFsxOpenZfs (..),
    newDescribeLocationFsxOpenZfs,

    -- * Request Lenses
    describeLocationFsxOpenZfs_locationArn,

    -- * Destructuring the Response
    DescribeLocationFsxOpenZfsResponse (..),
    newDescribeLocationFsxOpenZfsResponse,

    -- * Response Lenses
    describeLocationFsxOpenZfsResponse_creationTime,
    describeLocationFsxOpenZfsResponse_locationArn,
    describeLocationFsxOpenZfsResponse_locationUri,
    describeLocationFsxOpenZfsResponse_protocol,
    describeLocationFsxOpenZfsResponse_securityGroupArns,
    describeLocationFsxOpenZfsResponse_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:/ 'newDescribeLocationFsxOpenZfs' smart constructor.
data DescribeLocationFsxOpenZfs = DescribeLocationFsxOpenZfs'
  { -- | The Amazon Resource Name (ARN) of the FSx for OpenZFS location to
    -- describe.
    DescribeLocationFsxOpenZfs -> Text
locationArn :: Prelude.Text
  }
  deriving (DescribeLocationFsxOpenZfs -> DescribeLocationFsxOpenZfs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationFsxOpenZfs -> DescribeLocationFsxOpenZfs -> Bool
$c/= :: DescribeLocationFsxOpenZfs -> DescribeLocationFsxOpenZfs -> Bool
== :: DescribeLocationFsxOpenZfs -> DescribeLocationFsxOpenZfs -> Bool
$c== :: DescribeLocationFsxOpenZfs -> DescribeLocationFsxOpenZfs -> Bool
Prelude.Eq, ReadPrec [DescribeLocationFsxOpenZfs]
ReadPrec DescribeLocationFsxOpenZfs
Int -> ReadS DescribeLocationFsxOpenZfs
ReadS [DescribeLocationFsxOpenZfs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationFsxOpenZfs]
$creadListPrec :: ReadPrec [DescribeLocationFsxOpenZfs]
readPrec :: ReadPrec DescribeLocationFsxOpenZfs
$creadPrec :: ReadPrec DescribeLocationFsxOpenZfs
readList :: ReadS [DescribeLocationFsxOpenZfs]
$creadList :: ReadS [DescribeLocationFsxOpenZfs]
readsPrec :: Int -> ReadS DescribeLocationFsxOpenZfs
$creadsPrec :: Int -> ReadS DescribeLocationFsxOpenZfs
Prelude.Read, Int -> DescribeLocationFsxOpenZfs -> ShowS
[DescribeLocationFsxOpenZfs] -> ShowS
DescribeLocationFsxOpenZfs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationFsxOpenZfs] -> ShowS
$cshowList :: [DescribeLocationFsxOpenZfs] -> ShowS
show :: DescribeLocationFsxOpenZfs -> String
$cshow :: DescribeLocationFsxOpenZfs -> String
showsPrec :: Int -> DescribeLocationFsxOpenZfs -> ShowS
$cshowsPrec :: Int -> DescribeLocationFsxOpenZfs -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationFsxOpenZfs x -> DescribeLocationFsxOpenZfs
forall x.
DescribeLocationFsxOpenZfs -> Rep DescribeLocationFsxOpenZfs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationFsxOpenZfs x -> DescribeLocationFsxOpenZfs
$cfrom :: forall x.
DescribeLocationFsxOpenZfs -> Rep DescribeLocationFsxOpenZfs x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLocationFsxOpenZfs' 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', 'describeLocationFsxOpenZfs_locationArn' - The Amazon Resource Name (ARN) of the FSx for OpenZFS location to
-- describe.
newDescribeLocationFsxOpenZfs ::
  -- | 'locationArn'
  Prelude.Text ->
  DescribeLocationFsxOpenZfs
newDescribeLocationFsxOpenZfs :: Text -> DescribeLocationFsxOpenZfs
newDescribeLocationFsxOpenZfs Text
pLocationArn_ =
  DescribeLocationFsxOpenZfs'
    { $sel:locationArn:DescribeLocationFsxOpenZfs' :: Text
locationArn =
        Text
pLocationArn_
    }

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

instance Core.AWSRequest DescribeLocationFsxOpenZfs where
  type
    AWSResponse DescribeLocationFsxOpenZfs =
      DescribeLocationFsxOpenZfsResponse
  request :: (Service -> Service)
-> DescribeLocationFsxOpenZfs -> Request DescribeLocationFsxOpenZfs
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 DescribeLocationFsxOpenZfs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeLocationFsxOpenZfs)))
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 FsxProtocol
-> Maybe (NonEmpty Text)
-> Int
-> DescribeLocationFsxOpenZfsResponse
DescribeLocationFsxOpenZfsResponse'
            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
"Protocol")
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

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

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

-- | /See:/ 'newDescribeLocationFsxOpenZfsResponse' smart constructor.
data DescribeLocationFsxOpenZfsResponse = DescribeLocationFsxOpenZfsResponse'
  { -- | The time that the FSx for OpenZFS location was created.
    DescribeLocationFsxOpenZfsResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The ARN of the FSx for OpenZFS location that was described.
    DescribeLocationFsxOpenZfsResponse -> Maybe Text
locationArn :: Prelude.Maybe Prelude.Text,
    -- | The uniform resource identifier (URI) of the FSx for OpenZFS location
    -- that was described.
    --
    -- Example:
    -- @fsxz:\/\/us-west-2.fs-1234567890abcdef02\/fsx\/folderA\/folder@
    DescribeLocationFsxOpenZfsResponse -> Maybe Text
locationUri :: Prelude.Maybe Prelude.Text,
    -- | The type of protocol that DataSync uses to access your file system.
    DescribeLocationFsxOpenZfsResponse -> Maybe FsxProtocol
protocol :: Prelude.Maybe FsxProtocol,
    -- | The ARNs of the security groups that are configured for the FSx for
    -- OpenZFS file system.
    DescribeLocationFsxOpenZfsResponse -> Maybe (NonEmpty Text)
securityGroupArns :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The response's http status code.
    DescribeLocationFsxOpenZfsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeLocationFsxOpenZfsResponse
-> DescribeLocationFsxOpenZfsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationFsxOpenZfsResponse
-> DescribeLocationFsxOpenZfsResponse -> Bool
$c/= :: DescribeLocationFsxOpenZfsResponse
-> DescribeLocationFsxOpenZfsResponse -> Bool
== :: DescribeLocationFsxOpenZfsResponse
-> DescribeLocationFsxOpenZfsResponse -> Bool
$c== :: DescribeLocationFsxOpenZfsResponse
-> DescribeLocationFsxOpenZfsResponse -> Bool
Prelude.Eq, Int -> DescribeLocationFsxOpenZfsResponse -> ShowS
[DescribeLocationFsxOpenZfsResponse] -> ShowS
DescribeLocationFsxOpenZfsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationFsxOpenZfsResponse] -> ShowS
$cshowList :: [DescribeLocationFsxOpenZfsResponse] -> ShowS
show :: DescribeLocationFsxOpenZfsResponse -> String
$cshow :: DescribeLocationFsxOpenZfsResponse -> String
showsPrec :: Int -> DescribeLocationFsxOpenZfsResponse -> ShowS
$cshowsPrec :: Int -> DescribeLocationFsxOpenZfsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationFsxOpenZfsResponse x
-> DescribeLocationFsxOpenZfsResponse
forall x.
DescribeLocationFsxOpenZfsResponse
-> Rep DescribeLocationFsxOpenZfsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationFsxOpenZfsResponse x
-> DescribeLocationFsxOpenZfsResponse
$cfrom :: forall x.
DescribeLocationFsxOpenZfsResponse
-> Rep DescribeLocationFsxOpenZfsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLocationFsxOpenZfsResponse' 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', 'describeLocationFsxOpenZfsResponse_creationTime' - The time that the FSx for OpenZFS location was created.
--
-- 'locationArn', 'describeLocationFsxOpenZfsResponse_locationArn' - The ARN of the FSx for OpenZFS location that was described.
--
-- 'locationUri', 'describeLocationFsxOpenZfsResponse_locationUri' - The uniform resource identifier (URI) of the FSx for OpenZFS location
-- that was described.
--
-- Example:
-- @fsxz:\/\/us-west-2.fs-1234567890abcdef02\/fsx\/folderA\/folder@
--
-- 'protocol', 'describeLocationFsxOpenZfsResponse_protocol' - The type of protocol that DataSync uses to access your file system.
--
-- 'securityGroupArns', 'describeLocationFsxOpenZfsResponse_securityGroupArns' - The ARNs of the security groups that are configured for the FSx for
-- OpenZFS file system.
--
-- 'httpStatus', 'describeLocationFsxOpenZfsResponse_httpStatus' - The response's http status code.
newDescribeLocationFsxOpenZfsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeLocationFsxOpenZfsResponse
newDescribeLocationFsxOpenZfsResponse :: Int -> DescribeLocationFsxOpenZfsResponse
newDescribeLocationFsxOpenZfsResponse Int
pHttpStatus_ =
  DescribeLocationFsxOpenZfsResponse'
    { $sel:creationTime:DescribeLocationFsxOpenZfsResponse' :: Maybe POSIX
creationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:locationArn:DescribeLocationFsxOpenZfsResponse' :: Maybe Text
locationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:locationUri:DescribeLocationFsxOpenZfsResponse' :: Maybe Text
locationUri = forall a. Maybe a
Prelude.Nothing,
      $sel:protocol:DescribeLocationFsxOpenZfsResponse' :: Maybe FsxProtocol
protocol = forall a. Maybe a
Prelude.Nothing,
      $sel:securityGroupArns:DescribeLocationFsxOpenZfsResponse' :: Maybe (NonEmpty Text)
securityGroupArns = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeLocationFsxOpenZfsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The time that the FSx for OpenZFS location was created.
describeLocationFsxOpenZfsResponse_creationTime :: Lens.Lens' DescribeLocationFsxOpenZfsResponse (Prelude.Maybe Prelude.UTCTime)
describeLocationFsxOpenZfsResponse_creationTime :: Lens' DescribeLocationFsxOpenZfsResponse (Maybe UTCTime)
describeLocationFsxOpenZfsResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOpenZfsResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeLocationFsxOpenZfsResponse' :: DescribeLocationFsxOpenZfsResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeLocationFsxOpenZfsResponse
s@DescribeLocationFsxOpenZfsResponse' {} Maybe POSIX
a -> DescribeLocationFsxOpenZfsResponse
s {$sel:creationTime:DescribeLocationFsxOpenZfsResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeLocationFsxOpenZfsResponse) 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 ARN of the FSx for OpenZFS location that was described.
describeLocationFsxOpenZfsResponse_locationArn :: Lens.Lens' DescribeLocationFsxOpenZfsResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxOpenZfsResponse_locationArn :: Lens' DescribeLocationFsxOpenZfsResponse (Maybe Text)
describeLocationFsxOpenZfsResponse_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOpenZfsResponse' {Maybe Text
locationArn :: Maybe Text
$sel:locationArn:DescribeLocationFsxOpenZfsResponse' :: DescribeLocationFsxOpenZfsResponse -> Maybe Text
locationArn} -> Maybe Text
locationArn) (\s :: DescribeLocationFsxOpenZfsResponse
s@DescribeLocationFsxOpenZfsResponse' {} Maybe Text
a -> DescribeLocationFsxOpenZfsResponse
s {$sel:locationArn:DescribeLocationFsxOpenZfsResponse' :: Maybe Text
locationArn = Maybe Text
a} :: DescribeLocationFsxOpenZfsResponse)

-- | The uniform resource identifier (URI) of the FSx for OpenZFS location
-- that was described.
--
-- Example:
-- @fsxz:\/\/us-west-2.fs-1234567890abcdef02\/fsx\/folderA\/folder@
describeLocationFsxOpenZfsResponse_locationUri :: Lens.Lens' DescribeLocationFsxOpenZfsResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxOpenZfsResponse_locationUri :: Lens' DescribeLocationFsxOpenZfsResponse (Maybe Text)
describeLocationFsxOpenZfsResponse_locationUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOpenZfsResponse' {Maybe Text
locationUri :: Maybe Text
$sel:locationUri:DescribeLocationFsxOpenZfsResponse' :: DescribeLocationFsxOpenZfsResponse -> Maybe Text
locationUri} -> Maybe Text
locationUri) (\s :: DescribeLocationFsxOpenZfsResponse
s@DescribeLocationFsxOpenZfsResponse' {} Maybe Text
a -> DescribeLocationFsxOpenZfsResponse
s {$sel:locationUri:DescribeLocationFsxOpenZfsResponse' :: Maybe Text
locationUri = Maybe Text
a} :: DescribeLocationFsxOpenZfsResponse)

-- | The type of protocol that DataSync uses to access your file system.
describeLocationFsxOpenZfsResponse_protocol :: Lens.Lens' DescribeLocationFsxOpenZfsResponse (Prelude.Maybe FsxProtocol)
describeLocationFsxOpenZfsResponse_protocol :: Lens' DescribeLocationFsxOpenZfsResponse (Maybe FsxProtocol)
describeLocationFsxOpenZfsResponse_protocol = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOpenZfsResponse' {Maybe FsxProtocol
protocol :: Maybe FsxProtocol
$sel:protocol:DescribeLocationFsxOpenZfsResponse' :: DescribeLocationFsxOpenZfsResponse -> Maybe FsxProtocol
protocol} -> Maybe FsxProtocol
protocol) (\s :: DescribeLocationFsxOpenZfsResponse
s@DescribeLocationFsxOpenZfsResponse' {} Maybe FsxProtocol
a -> DescribeLocationFsxOpenZfsResponse
s {$sel:protocol:DescribeLocationFsxOpenZfsResponse' :: Maybe FsxProtocol
protocol = Maybe FsxProtocol
a} :: DescribeLocationFsxOpenZfsResponse)

-- | The ARNs of the security groups that are configured for the FSx for
-- OpenZFS file system.
describeLocationFsxOpenZfsResponse_securityGroupArns :: Lens.Lens' DescribeLocationFsxOpenZfsResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeLocationFsxOpenZfsResponse_securityGroupArns :: Lens' DescribeLocationFsxOpenZfsResponse (Maybe (NonEmpty Text))
describeLocationFsxOpenZfsResponse_securityGroupArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOpenZfsResponse' {Maybe (NonEmpty Text)
securityGroupArns :: Maybe (NonEmpty Text)
$sel:securityGroupArns:DescribeLocationFsxOpenZfsResponse' :: DescribeLocationFsxOpenZfsResponse -> Maybe (NonEmpty Text)
securityGroupArns} -> Maybe (NonEmpty Text)
securityGroupArns) (\s :: DescribeLocationFsxOpenZfsResponse
s@DescribeLocationFsxOpenZfsResponse' {} Maybe (NonEmpty Text)
a -> DescribeLocationFsxOpenZfsResponse
s {$sel:securityGroupArns:DescribeLocationFsxOpenZfsResponse' :: Maybe (NonEmpty Text)
securityGroupArns = Maybe (NonEmpty Text)
a} :: DescribeLocationFsxOpenZfsResponse) 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 response's http status code.
describeLocationFsxOpenZfsResponse_httpStatus :: Lens.Lens' DescribeLocationFsxOpenZfsResponse Prelude.Int
describeLocationFsxOpenZfsResponse_httpStatus :: Lens' DescribeLocationFsxOpenZfsResponse Int
describeLocationFsxOpenZfsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOpenZfsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeLocationFsxOpenZfsResponse' :: DescribeLocationFsxOpenZfsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeLocationFsxOpenZfsResponse
s@DescribeLocationFsxOpenZfsResponse' {} Int
a -> DescribeLocationFsxOpenZfsResponse
s {$sel:httpStatus:DescribeLocationFsxOpenZfsResponse' :: Int
httpStatus = Int
a} :: DescribeLocationFsxOpenZfsResponse)

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