{-# 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 #-}
module Amazonka.DataSync.DescribeLocationFsxOntap
(
DescribeLocationFsxOntap (..),
newDescribeLocationFsxOntap,
describeLocationFsxOntap_locationArn,
DescribeLocationFsxOntapResponse (..),
newDescribeLocationFsxOntapResponse,
describeLocationFsxOntapResponse_creationTime,
describeLocationFsxOntapResponse_fsxFilesystemArn,
describeLocationFsxOntapResponse_locationArn,
describeLocationFsxOntapResponse_locationUri,
describeLocationFsxOntapResponse_protocol,
describeLocationFsxOntapResponse_securityGroupArns,
describeLocationFsxOntapResponse_storageVirtualMachineArn,
describeLocationFsxOntapResponse_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
data DescribeLocationFsxOntap = DescribeLocationFsxOntap'
{
DescribeLocationFsxOntap -> Text
locationArn :: Prelude.Text
}
deriving (DescribeLocationFsxOntap -> DescribeLocationFsxOntap -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationFsxOntap -> DescribeLocationFsxOntap -> Bool
$c/= :: DescribeLocationFsxOntap -> DescribeLocationFsxOntap -> Bool
== :: DescribeLocationFsxOntap -> DescribeLocationFsxOntap -> Bool
$c== :: DescribeLocationFsxOntap -> DescribeLocationFsxOntap -> Bool
Prelude.Eq, ReadPrec [DescribeLocationFsxOntap]
ReadPrec DescribeLocationFsxOntap
Int -> ReadS DescribeLocationFsxOntap
ReadS [DescribeLocationFsxOntap]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationFsxOntap]
$creadListPrec :: ReadPrec [DescribeLocationFsxOntap]
readPrec :: ReadPrec DescribeLocationFsxOntap
$creadPrec :: ReadPrec DescribeLocationFsxOntap
readList :: ReadS [DescribeLocationFsxOntap]
$creadList :: ReadS [DescribeLocationFsxOntap]
readsPrec :: Int -> ReadS DescribeLocationFsxOntap
$creadsPrec :: Int -> ReadS DescribeLocationFsxOntap
Prelude.Read, Int -> DescribeLocationFsxOntap -> ShowS
[DescribeLocationFsxOntap] -> ShowS
DescribeLocationFsxOntap -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationFsxOntap] -> ShowS
$cshowList :: [DescribeLocationFsxOntap] -> ShowS
show :: DescribeLocationFsxOntap -> String
$cshow :: DescribeLocationFsxOntap -> String
showsPrec :: Int -> DescribeLocationFsxOntap -> ShowS
$cshowsPrec :: Int -> DescribeLocationFsxOntap -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationFsxOntap x -> DescribeLocationFsxOntap
forall x.
DescribeLocationFsxOntap -> Rep DescribeLocationFsxOntap x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationFsxOntap x -> DescribeLocationFsxOntap
$cfrom :: forall x.
DescribeLocationFsxOntap -> Rep DescribeLocationFsxOntap x
Prelude.Generic)
newDescribeLocationFsxOntap ::
Prelude.Text ->
DescribeLocationFsxOntap
newDescribeLocationFsxOntap :: Text -> DescribeLocationFsxOntap
newDescribeLocationFsxOntap Text
pLocationArn_ =
DescribeLocationFsxOntap'
{ $sel:locationArn:DescribeLocationFsxOntap' :: Text
locationArn =
Text
pLocationArn_
}
describeLocationFsxOntap_locationArn :: Lens.Lens' DescribeLocationFsxOntap Prelude.Text
describeLocationFsxOntap_locationArn :: Lens' DescribeLocationFsxOntap Text
describeLocationFsxOntap_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOntap' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationFsxOntap' :: DescribeLocationFsxOntap -> Text
locationArn} -> Text
locationArn) (\s :: DescribeLocationFsxOntap
s@DescribeLocationFsxOntap' {} Text
a -> DescribeLocationFsxOntap
s {$sel:locationArn:DescribeLocationFsxOntap' :: Text
locationArn = Text
a} :: DescribeLocationFsxOntap)
instance Core.AWSRequest DescribeLocationFsxOntap where
type
AWSResponse DescribeLocationFsxOntap =
DescribeLocationFsxOntapResponse
request :: (Service -> Service)
-> DescribeLocationFsxOntap -> Request DescribeLocationFsxOntap
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 DescribeLocationFsxOntap
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DescribeLocationFsxOntap)))
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 FsxProtocol
-> Maybe (NonEmpty Text)
-> Maybe Text
-> Int
-> DescribeLocationFsxOntapResponse
DescribeLocationFsxOntapResponse'
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
"FsxFilesystemArn")
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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"StorageVirtualMachineArn")
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 DescribeLocationFsxOntap where
hashWithSalt :: Int -> DescribeLocationFsxOntap -> Int
hashWithSalt Int
_salt DescribeLocationFsxOntap' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationFsxOntap' :: DescribeLocationFsxOntap -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
locationArn
instance Prelude.NFData DescribeLocationFsxOntap where
rnf :: DescribeLocationFsxOntap -> ()
rnf DescribeLocationFsxOntap' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationFsxOntap' :: DescribeLocationFsxOntap -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
locationArn
instance Data.ToHeaders DescribeLocationFsxOntap where
toHeaders :: DescribeLocationFsxOntap -> 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.DescribeLocationFsxOntap" ::
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 DescribeLocationFsxOntap where
toJSON :: DescribeLocationFsxOntap -> Value
toJSON DescribeLocationFsxOntap' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationFsxOntap' :: DescribeLocationFsxOntap -> 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 DescribeLocationFsxOntap where
toPath :: DescribeLocationFsxOntap -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DescribeLocationFsxOntap where
toQuery :: DescribeLocationFsxOntap -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DescribeLocationFsxOntapResponse = DescribeLocationFsxOntapResponse'
{
DescribeLocationFsxOntapResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
DescribeLocationFsxOntapResponse -> Maybe Text
fsxFilesystemArn :: Prelude.Maybe Prelude.Text,
DescribeLocationFsxOntapResponse -> Maybe Text
locationArn :: Prelude.Maybe Prelude.Text,
DescribeLocationFsxOntapResponse -> Maybe Text
locationUri :: Prelude.Maybe Prelude.Text,
DescribeLocationFsxOntapResponse -> Maybe FsxProtocol
protocol :: Prelude.Maybe FsxProtocol,
DescribeLocationFsxOntapResponse -> Maybe (NonEmpty Text)
securityGroupArns :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
DescribeLocationFsxOntapResponse -> Maybe Text
storageVirtualMachineArn :: Prelude.Maybe Prelude.Text,
DescribeLocationFsxOntapResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DescribeLocationFsxOntapResponse
-> DescribeLocationFsxOntapResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationFsxOntapResponse
-> DescribeLocationFsxOntapResponse -> Bool
$c/= :: DescribeLocationFsxOntapResponse
-> DescribeLocationFsxOntapResponse -> Bool
== :: DescribeLocationFsxOntapResponse
-> DescribeLocationFsxOntapResponse -> Bool
$c== :: DescribeLocationFsxOntapResponse
-> DescribeLocationFsxOntapResponse -> Bool
Prelude.Eq, Int -> DescribeLocationFsxOntapResponse -> ShowS
[DescribeLocationFsxOntapResponse] -> ShowS
DescribeLocationFsxOntapResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationFsxOntapResponse] -> ShowS
$cshowList :: [DescribeLocationFsxOntapResponse] -> ShowS
show :: DescribeLocationFsxOntapResponse -> String
$cshow :: DescribeLocationFsxOntapResponse -> String
showsPrec :: Int -> DescribeLocationFsxOntapResponse -> ShowS
$cshowsPrec :: Int -> DescribeLocationFsxOntapResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationFsxOntapResponse x
-> DescribeLocationFsxOntapResponse
forall x.
DescribeLocationFsxOntapResponse
-> Rep DescribeLocationFsxOntapResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationFsxOntapResponse x
-> DescribeLocationFsxOntapResponse
$cfrom :: forall x.
DescribeLocationFsxOntapResponse
-> Rep DescribeLocationFsxOntapResponse x
Prelude.Generic)
newDescribeLocationFsxOntapResponse ::
Prelude.Int ->
DescribeLocationFsxOntapResponse
newDescribeLocationFsxOntapResponse :: Int -> DescribeLocationFsxOntapResponse
newDescribeLocationFsxOntapResponse Int
pHttpStatus_ =
DescribeLocationFsxOntapResponse'
{ $sel:creationTime:DescribeLocationFsxOntapResponse' :: Maybe POSIX
creationTime =
forall a. Maybe a
Prelude.Nothing,
$sel:fsxFilesystemArn:DescribeLocationFsxOntapResponse' :: Maybe Text
fsxFilesystemArn = forall a. Maybe a
Prelude.Nothing,
$sel:locationArn:DescribeLocationFsxOntapResponse' :: Maybe Text
locationArn = forall a. Maybe a
Prelude.Nothing,
$sel:locationUri:DescribeLocationFsxOntapResponse' :: Maybe Text
locationUri = forall a. Maybe a
Prelude.Nothing,
$sel:protocol:DescribeLocationFsxOntapResponse' :: Maybe FsxProtocol
protocol = forall a. Maybe a
Prelude.Nothing,
$sel:securityGroupArns:DescribeLocationFsxOntapResponse' :: Maybe (NonEmpty Text)
securityGroupArns = forall a. Maybe a
Prelude.Nothing,
$sel:storageVirtualMachineArn:DescribeLocationFsxOntapResponse' :: Maybe Text
storageVirtualMachineArn =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:DescribeLocationFsxOntapResponse' :: Int
httpStatus = Int
pHttpStatus_
}
describeLocationFsxOntapResponse_creationTime :: Lens.Lens' DescribeLocationFsxOntapResponse (Prelude.Maybe Prelude.UTCTime)
describeLocationFsxOntapResponse_creationTime :: Lens' DescribeLocationFsxOntapResponse (Maybe UTCTime)
describeLocationFsxOntapResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOntapResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeLocationFsxOntapResponse
s@DescribeLocationFsxOntapResponse' {} Maybe POSIX
a -> DescribeLocationFsxOntapResponse
s {$sel:creationTime:DescribeLocationFsxOntapResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeLocationFsxOntapResponse) 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
describeLocationFsxOntapResponse_fsxFilesystemArn :: Lens.Lens' DescribeLocationFsxOntapResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxOntapResponse_fsxFilesystemArn :: Lens' DescribeLocationFsxOntapResponse (Maybe Text)
describeLocationFsxOntapResponse_fsxFilesystemArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOntapResponse' {Maybe Text
fsxFilesystemArn :: Maybe Text
$sel:fsxFilesystemArn:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe Text
fsxFilesystemArn} -> Maybe Text
fsxFilesystemArn) (\s :: DescribeLocationFsxOntapResponse
s@DescribeLocationFsxOntapResponse' {} Maybe Text
a -> DescribeLocationFsxOntapResponse
s {$sel:fsxFilesystemArn:DescribeLocationFsxOntapResponse' :: Maybe Text
fsxFilesystemArn = Maybe Text
a} :: DescribeLocationFsxOntapResponse)
describeLocationFsxOntapResponse_locationArn :: Lens.Lens' DescribeLocationFsxOntapResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxOntapResponse_locationArn :: Lens' DescribeLocationFsxOntapResponse (Maybe Text)
describeLocationFsxOntapResponse_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOntapResponse' {Maybe Text
locationArn :: Maybe Text
$sel:locationArn:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe Text
locationArn} -> Maybe Text
locationArn) (\s :: DescribeLocationFsxOntapResponse
s@DescribeLocationFsxOntapResponse' {} Maybe Text
a -> DescribeLocationFsxOntapResponse
s {$sel:locationArn:DescribeLocationFsxOntapResponse' :: Maybe Text
locationArn = Maybe Text
a} :: DescribeLocationFsxOntapResponse)
describeLocationFsxOntapResponse_locationUri :: Lens.Lens' DescribeLocationFsxOntapResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxOntapResponse_locationUri :: Lens' DescribeLocationFsxOntapResponse (Maybe Text)
describeLocationFsxOntapResponse_locationUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOntapResponse' {Maybe Text
locationUri :: Maybe Text
$sel:locationUri:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe Text
locationUri} -> Maybe Text
locationUri) (\s :: DescribeLocationFsxOntapResponse
s@DescribeLocationFsxOntapResponse' {} Maybe Text
a -> DescribeLocationFsxOntapResponse
s {$sel:locationUri:DescribeLocationFsxOntapResponse' :: Maybe Text
locationUri = Maybe Text
a} :: DescribeLocationFsxOntapResponse)
describeLocationFsxOntapResponse_protocol :: Lens.Lens' DescribeLocationFsxOntapResponse (Prelude.Maybe FsxProtocol)
describeLocationFsxOntapResponse_protocol :: Lens' DescribeLocationFsxOntapResponse (Maybe FsxProtocol)
describeLocationFsxOntapResponse_protocol = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOntapResponse' {Maybe FsxProtocol
protocol :: Maybe FsxProtocol
$sel:protocol:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe FsxProtocol
protocol} -> Maybe FsxProtocol
protocol) (\s :: DescribeLocationFsxOntapResponse
s@DescribeLocationFsxOntapResponse' {} Maybe FsxProtocol
a -> DescribeLocationFsxOntapResponse
s {$sel:protocol:DescribeLocationFsxOntapResponse' :: Maybe FsxProtocol
protocol = Maybe FsxProtocol
a} :: DescribeLocationFsxOntapResponse)
describeLocationFsxOntapResponse_securityGroupArns :: Lens.Lens' DescribeLocationFsxOntapResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeLocationFsxOntapResponse_securityGroupArns :: Lens' DescribeLocationFsxOntapResponse (Maybe (NonEmpty Text))
describeLocationFsxOntapResponse_securityGroupArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOntapResponse' {Maybe (NonEmpty Text)
securityGroupArns :: Maybe (NonEmpty Text)
$sel:securityGroupArns:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe (NonEmpty Text)
securityGroupArns} -> Maybe (NonEmpty Text)
securityGroupArns) (\s :: DescribeLocationFsxOntapResponse
s@DescribeLocationFsxOntapResponse' {} Maybe (NonEmpty Text)
a -> DescribeLocationFsxOntapResponse
s {$sel:securityGroupArns:DescribeLocationFsxOntapResponse' :: Maybe (NonEmpty Text)
securityGroupArns = Maybe (NonEmpty Text)
a} :: DescribeLocationFsxOntapResponse) 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
describeLocationFsxOntapResponse_storageVirtualMachineArn :: Lens.Lens' DescribeLocationFsxOntapResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxOntapResponse_storageVirtualMachineArn :: Lens' DescribeLocationFsxOntapResponse (Maybe Text)
describeLocationFsxOntapResponse_storageVirtualMachineArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOntapResponse' {Maybe Text
storageVirtualMachineArn :: Maybe Text
$sel:storageVirtualMachineArn:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe Text
storageVirtualMachineArn} -> Maybe Text
storageVirtualMachineArn) (\s :: DescribeLocationFsxOntapResponse
s@DescribeLocationFsxOntapResponse' {} Maybe Text
a -> DescribeLocationFsxOntapResponse
s {$sel:storageVirtualMachineArn:DescribeLocationFsxOntapResponse' :: Maybe Text
storageVirtualMachineArn = Maybe Text
a} :: DescribeLocationFsxOntapResponse)
describeLocationFsxOntapResponse_httpStatus :: Lens.Lens' DescribeLocationFsxOntapResponse Prelude.Int
describeLocationFsxOntapResponse_httpStatus :: Lens' DescribeLocationFsxOntapResponse Int
describeLocationFsxOntapResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxOntapResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeLocationFsxOntapResponse
s@DescribeLocationFsxOntapResponse' {} Int
a -> DescribeLocationFsxOntapResponse
s {$sel:httpStatus:DescribeLocationFsxOntapResponse' :: Int
httpStatus = Int
a} :: DescribeLocationFsxOntapResponse)
instance
Prelude.NFData
DescribeLocationFsxOntapResponse
where
rnf :: DescribeLocationFsxOntapResponse -> ()
rnf DescribeLocationFsxOntapResponse' {Int
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe FsxProtocol
httpStatus :: Int
storageVirtualMachineArn :: Maybe Text
securityGroupArns :: Maybe (NonEmpty Text)
protocol :: Maybe FsxProtocol
locationUri :: Maybe Text
locationArn :: Maybe Text
fsxFilesystemArn :: Maybe Text
creationTime :: Maybe POSIX
$sel:httpStatus:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Int
$sel:storageVirtualMachineArn:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe Text
$sel:securityGroupArns:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe (NonEmpty Text)
$sel:protocol:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe FsxProtocol
$sel:locationUri:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe Text
$sel:locationArn:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe Text
$sel:fsxFilesystemArn:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> Maybe Text
$sel:creationTime:DescribeLocationFsxOntapResponse' :: DescribeLocationFsxOntapResponse -> 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
fsxFilesystemArn
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 Maybe Text
storageVirtualMachineArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus