{-# 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.DescribeLocationFsxLustre
(
DescribeLocationFsxLustre (..),
newDescribeLocationFsxLustre,
describeLocationFsxLustre_locationArn,
DescribeLocationFsxLustreResponse (..),
newDescribeLocationFsxLustreResponse,
describeLocationFsxLustreResponse_creationTime,
describeLocationFsxLustreResponse_locationArn,
describeLocationFsxLustreResponse_locationUri,
describeLocationFsxLustreResponse_securityGroupArns,
describeLocationFsxLustreResponse_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 DescribeLocationFsxLustre = DescribeLocationFsxLustre'
{
DescribeLocationFsxLustre -> Text
locationArn :: Prelude.Text
}
deriving (DescribeLocationFsxLustre -> DescribeLocationFsxLustre -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationFsxLustre -> DescribeLocationFsxLustre -> Bool
$c/= :: DescribeLocationFsxLustre -> DescribeLocationFsxLustre -> Bool
== :: DescribeLocationFsxLustre -> DescribeLocationFsxLustre -> Bool
$c== :: DescribeLocationFsxLustre -> DescribeLocationFsxLustre -> Bool
Prelude.Eq, ReadPrec [DescribeLocationFsxLustre]
ReadPrec DescribeLocationFsxLustre
Int -> ReadS DescribeLocationFsxLustre
ReadS [DescribeLocationFsxLustre]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationFsxLustre]
$creadListPrec :: ReadPrec [DescribeLocationFsxLustre]
readPrec :: ReadPrec DescribeLocationFsxLustre
$creadPrec :: ReadPrec DescribeLocationFsxLustre
readList :: ReadS [DescribeLocationFsxLustre]
$creadList :: ReadS [DescribeLocationFsxLustre]
readsPrec :: Int -> ReadS DescribeLocationFsxLustre
$creadsPrec :: Int -> ReadS DescribeLocationFsxLustre
Prelude.Read, Int -> DescribeLocationFsxLustre -> ShowS
[DescribeLocationFsxLustre] -> ShowS
DescribeLocationFsxLustre -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationFsxLustre] -> ShowS
$cshowList :: [DescribeLocationFsxLustre] -> ShowS
show :: DescribeLocationFsxLustre -> String
$cshow :: DescribeLocationFsxLustre -> String
showsPrec :: Int -> DescribeLocationFsxLustre -> ShowS
$cshowsPrec :: Int -> DescribeLocationFsxLustre -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationFsxLustre x -> DescribeLocationFsxLustre
forall x.
DescribeLocationFsxLustre -> Rep DescribeLocationFsxLustre x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationFsxLustre x -> DescribeLocationFsxLustre
$cfrom :: forall x.
DescribeLocationFsxLustre -> Rep DescribeLocationFsxLustre x
Prelude.Generic)
newDescribeLocationFsxLustre ::
Prelude.Text ->
DescribeLocationFsxLustre
newDescribeLocationFsxLustre :: Text -> DescribeLocationFsxLustre
newDescribeLocationFsxLustre Text
pLocationArn_ =
DescribeLocationFsxLustre'
{ $sel:locationArn:DescribeLocationFsxLustre' :: Text
locationArn =
Text
pLocationArn_
}
describeLocationFsxLustre_locationArn :: Lens.Lens' DescribeLocationFsxLustre Prelude.Text
describeLocationFsxLustre_locationArn :: Lens' DescribeLocationFsxLustre Text
describeLocationFsxLustre_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxLustre' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationFsxLustre' :: DescribeLocationFsxLustre -> Text
locationArn} -> Text
locationArn) (\s :: DescribeLocationFsxLustre
s@DescribeLocationFsxLustre' {} Text
a -> DescribeLocationFsxLustre
s {$sel:locationArn:DescribeLocationFsxLustre' :: Text
locationArn = Text
a} :: DescribeLocationFsxLustre)
instance Core.AWSRequest DescribeLocationFsxLustre where
type
AWSResponse DescribeLocationFsxLustre =
DescribeLocationFsxLustreResponse
request :: (Service -> Service)
-> DescribeLocationFsxLustre -> Request DescribeLocationFsxLustre
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 DescribeLocationFsxLustre
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DescribeLocationFsxLustre)))
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 (NonEmpty Text)
-> Int
-> DescribeLocationFsxLustreResponse
DescribeLocationFsxLustreResponse'
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
"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 DescribeLocationFsxLustre where
hashWithSalt :: Int -> DescribeLocationFsxLustre -> Int
hashWithSalt Int
_salt DescribeLocationFsxLustre' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationFsxLustre' :: DescribeLocationFsxLustre -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
locationArn
instance Prelude.NFData DescribeLocationFsxLustre where
rnf :: DescribeLocationFsxLustre -> ()
rnf DescribeLocationFsxLustre' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationFsxLustre' :: DescribeLocationFsxLustre -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
locationArn
instance Data.ToHeaders DescribeLocationFsxLustre where
toHeaders :: DescribeLocationFsxLustre -> 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.DescribeLocationFsxLustre" ::
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 DescribeLocationFsxLustre where
toJSON :: DescribeLocationFsxLustre -> Value
toJSON DescribeLocationFsxLustre' {Text
locationArn :: Text
$sel:locationArn:DescribeLocationFsxLustre' :: DescribeLocationFsxLustre -> 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 DescribeLocationFsxLustre where
toPath :: DescribeLocationFsxLustre -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DescribeLocationFsxLustre where
toQuery :: DescribeLocationFsxLustre -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DescribeLocationFsxLustreResponse = DescribeLocationFsxLustreResponse'
{
DescribeLocationFsxLustreResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
DescribeLocationFsxLustreResponse -> Maybe Text
locationArn :: Prelude.Maybe Prelude.Text,
DescribeLocationFsxLustreResponse -> Maybe Text
locationUri :: Prelude.Maybe Prelude.Text,
DescribeLocationFsxLustreResponse -> Maybe (NonEmpty Text)
securityGroupArns :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
DescribeLocationFsxLustreResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DescribeLocationFsxLustreResponse
-> DescribeLocationFsxLustreResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLocationFsxLustreResponse
-> DescribeLocationFsxLustreResponse -> Bool
$c/= :: DescribeLocationFsxLustreResponse
-> DescribeLocationFsxLustreResponse -> Bool
== :: DescribeLocationFsxLustreResponse
-> DescribeLocationFsxLustreResponse -> Bool
$c== :: DescribeLocationFsxLustreResponse
-> DescribeLocationFsxLustreResponse -> Bool
Prelude.Eq, ReadPrec [DescribeLocationFsxLustreResponse]
ReadPrec DescribeLocationFsxLustreResponse
Int -> ReadS DescribeLocationFsxLustreResponse
ReadS [DescribeLocationFsxLustreResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLocationFsxLustreResponse]
$creadListPrec :: ReadPrec [DescribeLocationFsxLustreResponse]
readPrec :: ReadPrec DescribeLocationFsxLustreResponse
$creadPrec :: ReadPrec DescribeLocationFsxLustreResponse
readList :: ReadS [DescribeLocationFsxLustreResponse]
$creadList :: ReadS [DescribeLocationFsxLustreResponse]
readsPrec :: Int -> ReadS DescribeLocationFsxLustreResponse
$creadsPrec :: Int -> ReadS DescribeLocationFsxLustreResponse
Prelude.Read, Int -> DescribeLocationFsxLustreResponse -> ShowS
[DescribeLocationFsxLustreResponse] -> ShowS
DescribeLocationFsxLustreResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLocationFsxLustreResponse] -> ShowS
$cshowList :: [DescribeLocationFsxLustreResponse] -> ShowS
show :: DescribeLocationFsxLustreResponse -> String
$cshow :: DescribeLocationFsxLustreResponse -> String
showsPrec :: Int -> DescribeLocationFsxLustreResponse -> ShowS
$cshowsPrec :: Int -> DescribeLocationFsxLustreResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLocationFsxLustreResponse x
-> DescribeLocationFsxLustreResponse
forall x.
DescribeLocationFsxLustreResponse
-> Rep DescribeLocationFsxLustreResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLocationFsxLustreResponse x
-> DescribeLocationFsxLustreResponse
$cfrom :: forall x.
DescribeLocationFsxLustreResponse
-> Rep DescribeLocationFsxLustreResponse x
Prelude.Generic)
newDescribeLocationFsxLustreResponse ::
Prelude.Int ->
DescribeLocationFsxLustreResponse
newDescribeLocationFsxLustreResponse :: Int -> DescribeLocationFsxLustreResponse
newDescribeLocationFsxLustreResponse Int
pHttpStatus_ =
DescribeLocationFsxLustreResponse'
{ $sel:creationTime:DescribeLocationFsxLustreResponse' :: Maybe POSIX
creationTime =
forall a. Maybe a
Prelude.Nothing,
$sel:locationArn:DescribeLocationFsxLustreResponse' :: Maybe Text
locationArn = forall a. Maybe a
Prelude.Nothing,
$sel:locationUri:DescribeLocationFsxLustreResponse' :: Maybe Text
locationUri = forall a. Maybe a
Prelude.Nothing,
$sel:securityGroupArns:DescribeLocationFsxLustreResponse' :: Maybe (NonEmpty Text)
securityGroupArns = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:DescribeLocationFsxLustreResponse' :: Int
httpStatus = Int
pHttpStatus_
}
describeLocationFsxLustreResponse_creationTime :: Lens.Lens' DescribeLocationFsxLustreResponse (Prelude.Maybe Prelude.UTCTime)
describeLocationFsxLustreResponse_creationTime :: Lens' DescribeLocationFsxLustreResponse (Maybe UTCTime)
describeLocationFsxLustreResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxLustreResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeLocationFsxLustreResponse
s@DescribeLocationFsxLustreResponse' {} Maybe POSIX
a -> DescribeLocationFsxLustreResponse
s {$sel:creationTime:DescribeLocationFsxLustreResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeLocationFsxLustreResponse) 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
describeLocationFsxLustreResponse_locationArn :: Lens.Lens' DescribeLocationFsxLustreResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxLustreResponse_locationArn :: Lens' DescribeLocationFsxLustreResponse (Maybe Text)
describeLocationFsxLustreResponse_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxLustreResponse' {Maybe Text
locationArn :: Maybe Text
$sel:locationArn:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> Maybe Text
locationArn} -> Maybe Text
locationArn) (\s :: DescribeLocationFsxLustreResponse
s@DescribeLocationFsxLustreResponse' {} Maybe Text
a -> DescribeLocationFsxLustreResponse
s {$sel:locationArn:DescribeLocationFsxLustreResponse' :: Maybe Text
locationArn = Maybe Text
a} :: DescribeLocationFsxLustreResponse)
describeLocationFsxLustreResponse_locationUri :: Lens.Lens' DescribeLocationFsxLustreResponse (Prelude.Maybe Prelude.Text)
describeLocationFsxLustreResponse_locationUri :: Lens' DescribeLocationFsxLustreResponse (Maybe Text)
describeLocationFsxLustreResponse_locationUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxLustreResponse' {Maybe Text
locationUri :: Maybe Text
$sel:locationUri:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> Maybe Text
locationUri} -> Maybe Text
locationUri) (\s :: DescribeLocationFsxLustreResponse
s@DescribeLocationFsxLustreResponse' {} Maybe Text
a -> DescribeLocationFsxLustreResponse
s {$sel:locationUri:DescribeLocationFsxLustreResponse' :: Maybe Text
locationUri = Maybe Text
a} :: DescribeLocationFsxLustreResponse)
describeLocationFsxLustreResponse_securityGroupArns :: Lens.Lens' DescribeLocationFsxLustreResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeLocationFsxLustreResponse_securityGroupArns :: Lens' DescribeLocationFsxLustreResponse (Maybe (NonEmpty Text))
describeLocationFsxLustreResponse_securityGroupArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxLustreResponse' {Maybe (NonEmpty Text)
securityGroupArns :: Maybe (NonEmpty Text)
$sel:securityGroupArns:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> Maybe (NonEmpty Text)
securityGroupArns} -> Maybe (NonEmpty Text)
securityGroupArns) (\s :: DescribeLocationFsxLustreResponse
s@DescribeLocationFsxLustreResponse' {} Maybe (NonEmpty Text)
a -> DescribeLocationFsxLustreResponse
s {$sel:securityGroupArns:DescribeLocationFsxLustreResponse' :: Maybe (NonEmpty Text)
securityGroupArns = Maybe (NonEmpty Text)
a} :: DescribeLocationFsxLustreResponse) 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
describeLocationFsxLustreResponse_httpStatus :: Lens.Lens' DescribeLocationFsxLustreResponse Prelude.Int
describeLocationFsxLustreResponse_httpStatus :: Lens' DescribeLocationFsxLustreResponse Int
describeLocationFsxLustreResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLocationFsxLustreResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeLocationFsxLustreResponse
s@DescribeLocationFsxLustreResponse' {} Int
a -> DescribeLocationFsxLustreResponse
s {$sel:httpStatus:DescribeLocationFsxLustreResponse' :: Int
httpStatus = Int
a} :: DescribeLocationFsxLustreResponse)
instance
Prelude.NFData
DescribeLocationFsxLustreResponse
where
rnf :: DescribeLocationFsxLustreResponse -> ()
rnf DescribeLocationFsxLustreResponse' {Int
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
httpStatus :: Int
securityGroupArns :: Maybe (NonEmpty Text)
locationUri :: Maybe Text
locationArn :: Maybe Text
creationTime :: Maybe POSIX
$sel:httpStatus:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> Int
$sel:securityGroupArns:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> Maybe (NonEmpty Text)
$sel:locationUri:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> Maybe Text
$sel:locationArn:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> Maybe Text
$sel:creationTime:DescribeLocationFsxLustreResponse' :: DescribeLocationFsxLustreResponse -> 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 (NonEmpty Text)
securityGroupArns
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus