{-# 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.PrivateNetworks.GetNetworkSite
(
GetNetworkSite (..),
newGetNetworkSite,
getNetworkSite_networkSiteArn,
GetNetworkSiteResponse (..),
newGetNetworkSiteResponse,
getNetworkSiteResponse_networkSite,
getNetworkSiteResponse_tags,
getNetworkSiteResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.PrivateNetworks.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data GetNetworkSite = GetNetworkSite'
{
GetNetworkSite -> Text
networkSiteArn :: Prelude.Text
}
deriving (GetNetworkSite -> GetNetworkSite -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetNetworkSite -> GetNetworkSite -> Bool
$c/= :: GetNetworkSite -> GetNetworkSite -> Bool
== :: GetNetworkSite -> GetNetworkSite -> Bool
$c== :: GetNetworkSite -> GetNetworkSite -> Bool
Prelude.Eq, ReadPrec [GetNetworkSite]
ReadPrec GetNetworkSite
Int -> ReadS GetNetworkSite
ReadS [GetNetworkSite]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetNetworkSite]
$creadListPrec :: ReadPrec [GetNetworkSite]
readPrec :: ReadPrec GetNetworkSite
$creadPrec :: ReadPrec GetNetworkSite
readList :: ReadS [GetNetworkSite]
$creadList :: ReadS [GetNetworkSite]
readsPrec :: Int -> ReadS GetNetworkSite
$creadsPrec :: Int -> ReadS GetNetworkSite
Prelude.Read, Int -> GetNetworkSite -> ShowS
[GetNetworkSite] -> ShowS
GetNetworkSite -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetNetworkSite] -> ShowS
$cshowList :: [GetNetworkSite] -> ShowS
show :: GetNetworkSite -> String
$cshow :: GetNetworkSite -> String
showsPrec :: Int -> GetNetworkSite -> ShowS
$cshowsPrec :: Int -> GetNetworkSite -> ShowS
Prelude.Show, forall x. Rep GetNetworkSite x -> GetNetworkSite
forall x. GetNetworkSite -> Rep GetNetworkSite x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetNetworkSite x -> GetNetworkSite
$cfrom :: forall x. GetNetworkSite -> Rep GetNetworkSite x
Prelude.Generic)
newGetNetworkSite ::
Prelude.Text ->
GetNetworkSite
newGetNetworkSite :: Text -> GetNetworkSite
newGetNetworkSite Text
pNetworkSiteArn_ =
GetNetworkSite' {$sel:networkSiteArn:GetNetworkSite' :: Text
networkSiteArn = Text
pNetworkSiteArn_}
getNetworkSite_networkSiteArn :: Lens.Lens' GetNetworkSite Prelude.Text
getNetworkSite_networkSiteArn :: Lens' GetNetworkSite Text
getNetworkSite_networkSiteArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkSite' {Text
networkSiteArn :: Text
$sel:networkSiteArn:GetNetworkSite' :: GetNetworkSite -> Text
networkSiteArn} -> Text
networkSiteArn) (\s :: GetNetworkSite
s@GetNetworkSite' {} Text
a -> GetNetworkSite
s {$sel:networkSiteArn:GetNetworkSite' :: Text
networkSiteArn = Text
a} :: GetNetworkSite)
instance Core.AWSRequest GetNetworkSite where
type
AWSResponse GetNetworkSite =
GetNetworkSiteResponse
request :: (Service -> Service) -> GetNetworkSite -> Request GetNetworkSite
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetNetworkSite
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetNetworkSite)))
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 NetworkSite
-> Maybe (Sensitive (HashMap Text Text))
-> Int
-> GetNetworkSiteResponse
GetNetworkSiteResponse'
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
"networkSite")
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
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
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 GetNetworkSite where
hashWithSalt :: Int -> GetNetworkSite -> Int
hashWithSalt Int
_salt GetNetworkSite' {Text
networkSiteArn :: Text
$sel:networkSiteArn:GetNetworkSite' :: GetNetworkSite -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
networkSiteArn
instance Prelude.NFData GetNetworkSite where
rnf :: GetNetworkSite -> ()
rnf GetNetworkSite' {Text
networkSiteArn :: Text
$sel:networkSiteArn:GetNetworkSite' :: GetNetworkSite -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
networkSiteArn
instance Data.ToHeaders GetNetworkSite where
toHeaders :: GetNetworkSite -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToPath GetNetworkSite where
toPath :: GetNetworkSite -> ByteString
toPath GetNetworkSite' {Text
networkSiteArn :: Text
$sel:networkSiteArn:GetNetworkSite' :: GetNetworkSite -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/v1/network-sites/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
networkSiteArn]
instance Data.ToQuery GetNetworkSite where
toQuery :: GetNetworkSite -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetNetworkSiteResponse = GetNetworkSiteResponse'
{
GetNetworkSiteResponse -> Maybe NetworkSite
networkSite :: Prelude.Maybe NetworkSite,
GetNetworkSiteResponse -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
GetNetworkSiteResponse -> Int
httpStatus :: Prelude.Int
}
deriving (GetNetworkSiteResponse -> GetNetworkSiteResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetNetworkSiteResponse -> GetNetworkSiteResponse -> Bool
$c/= :: GetNetworkSiteResponse -> GetNetworkSiteResponse -> Bool
== :: GetNetworkSiteResponse -> GetNetworkSiteResponse -> Bool
$c== :: GetNetworkSiteResponse -> GetNetworkSiteResponse -> Bool
Prelude.Eq, Int -> GetNetworkSiteResponse -> ShowS
[GetNetworkSiteResponse] -> ShowS
GetNetworkSiteResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetNetworkSiteResponse] -> ShowS
$cshowList :: [GetNetworkSiteResponse] -> ShowS
show :: GetNetworkSiteResponse -> String
$cshow :: GetNetworkSiteResponse -> String
showsPrec :: Int -> GetNetworkSiteResponse -> ShowS
$cshowsPrec :: Int -> GetNetworkSiteResponse -> ShowS
Prelude.Show, forall x. Rep GetNetworkSiteResponse x -> GetNetworkSiteResponse
forall x. GetNetworkSiteResponse -> Rep GetNetworkSiteResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetNetworkSiteResponse x -> GetNetworkSiteResponse
$cfrom :: forall x. GetNetworkSiteResponse -> Rep GetNetworkSiteResponse x
Prelude.Generic)
newGetNetworkSiteResponse ::
Prelude.Int ->
GetNetworkSiteResponse
newGetNetworkSiteResponse :: Int -> GetNetworkSiteResponse
newGetNetworkSiteResponse Int
pHttpStatus_ =
GetNetworkSiteResponse'
{ $sel:networkSite:GetNetworkSiteResponse' :: Maybe NetworkSite
networkSite =
forall a. Maybe a
Prelude.Nothing,
$sel:tags:GetNetworkSiteResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetNetworkSiteResponse' :: Int
httpStatus = Int
pHttpStatus_
}
getNetworkSiteResponse_networkSite :: Lens.Lens' GetNetworkSiteResponse (Prelude.Maybe NetworkSite)
getNetworkSiteResponse_networkSite :: Lens' GetNetworkSiteResponse (Maybe NetworkSite)
getNetworkSiteResponse_networkSite = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkSiteResponse' {Maybe NetworkSite
networkSite :: Maybe NetworkSite
$sel:networkSite:GetNetworkSiteResponse' :: GetNetworkSiteResponse -> Maybe NetworkSite
networkSite} -> Maybe NetworkSite
networkSite) (\s :: GetNetworkSiteResponse
s@GetNetworkSiteResponse' {} Maybe NetworkSite
a -> GetNetworkSiteResponse
s {$sel:networkSite:GetNetworkSiteResponse' :: Maybe NetworkSite
networkSite = Maybe NetworkSite
a} :: GetNetworkSiteResponse)
getNetworkSiteResponse_tags :: Lens.Lens' GetNetworkSiteResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getNetworkSiteResponse_tags :: Lens' GetNetworkSiteResponse (Maybe (HashMap Text Text))
getNetworkSiteResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkSiteResponse' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:GetNetworkSiteResponse' :: GetNetworkSiteResponse -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: GetNetworkSiteResponse
s@GetNetworkSiteResponse' {} Maybe (Sensitive (HashMap Text Text))
a -> GetNetworkSiteResponse
s {$sel:tags:GetNetworkSiteResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: GetNetworkSiteResponse) 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. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)
getNetworkSiteResponse_httpStatus :: Lens.Lens' GetNetworkSiteResponse Prelude.Int
getNetworkSiteResponse_httpStatus :: Lens' GetNetworkSiteResponse Int
getNetworkSiteResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkSiteResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetNetworkSiteResponse' :: GetNetworkSiteResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetNetworkSiteResponse
s@GetNetworkSiteResponse' {} Int
a -> GetNetworkSiteResponse
s {$sel:httpStatus:GetNetworkSiteResponse' :: Int
httpStatus = Int
a} :: GetNetworkSiteResponse)
instance Prelude.NFData GetNetworkSiteResponse where
rnf :: GetNetworkSiteResponse -> ()
rnf GetNetworkSiteResponse' {Int
Maybe (Sensitive (HashMap Text Text))
Maybe NetworkSite
httpStatus :: Int
tags :: Maybe (Sensitive (HashMap Text Text))
networkSite :: Maybe NetworkSite
$sel:httpStatus:GetNetworkSiteResponse' :: GetNetworkSiteResponse -> Int
$sel:tags:GetNetworkSiteResponse' :: GetNetworkSiteResponse -> Maybe (Sensitive (HashMap Text Text))
$sel:networkSite:GetNetworkSiteResponse' :: GetNetworkSiteResponse -> Maybe NetworkSite
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkSite
networkSite
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
tags
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus