{-# 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.PrivateNetworks.GetNetwork
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the specified network.
module Amazonka.PrivateNetworks.GetNetwork
  ( -- * Creating a Request
    GetNetwork (..),
    newGetNetwork,

    -- * Request Lenses
    getNetwork_networkArn,

    -- * Destructuring the Response
    GetNetworkResponse (..),
    newGetNetworkResponse,

    -- * Response Lenses
    getNetworkResponse_tags,
    getNetworkResponse_httpStatus,
    getNetworkResponse_network,
  )
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

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

-- |
-- Create a value of 'GetNetwork' 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:
--
-- 'networkArn', 'getNetwork_networkArn' - The Amazon Resource Name (ARN) of the network.
newGetNetwork ::
  -- | 'networkArn'
  Prelude.Text ->
  GetNetwork
newGetNetwork :: Text -> GetNetwork
newGetNetwork Text
pNetworkArn_ =
  GetNetwork' {$sel:networkArn:GetNetwork' :: Text
networkArn = Text
pNetworkArn_}

-- | The Amazon Resource Name (ARN) of the network.
getNetwork_networkArn :: Lens.Lens' GetNetwork Prelude.Text
getNetwork_networkArn :: Lens' GetNetwork Text
getNetwork_networkArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetwork' {Text
networkArn :: Text
$sel:networkArn:GetNetwork' :: GetNetwork -> Text
networkArn} -> Text
networkArn) (\s :: GetNetwork
s@GetNetwork' {} Text
a -> GetNetwork
s {$sel:networkArn:GetNetwork' :: Text
networkArn = Text
a} :: GetNetwork)

instance Core.AWSRequest GetNetwork where
  type AWSResponse GetNetwork = GetNetworkResponse
  request :: (Service -> Service) -> GetNetwork -> Request GetNetwork
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 GetNetwork
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetNetwork)))
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 (Sensitive (HashMap Text Text))
-> Int -> Network -> GetNetworkResponse
GetNetworkResponse'
            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
"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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"network")
      )

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

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

instance Data.ToHeaders GetNetwork where
  toHeaders :: GetNetwork -> 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 GetNetwork where
  toPath :: GetNetwork -> ByteString
toPath GetNetwork' {Text
networkArn :: Text
$sel:networkArn:GetNetwork' :: GetNetwork -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/networks/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
networkArn]

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

-- | /See:/ 'newGetNetworkResponse' smart constructor.
data GetNetworkResponse = GetNetworkResponse'
  { -- | The network tags.
    GetNetworkResponse -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The response's http status code.
    GetNetworkResponse -> Int
httpStatus :: Prelude.Int,
    -- | Information about the network.
    GetNetworkResponse -> Network
network :: Network
  }
  deriving (GetNetworkResponse -> GetNetworkResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetNetworkResponse -> GetNetworkResponse -> Bool
$c/= :: GetNetworkResponse -> GetNetworkResponse -> Bool
== :: GetNetworkResponse -> GetNetworkResponse -> Bool
$c== :: GetNetworkResponse -> GetNetworkResponse -> Bool
Prelude.Eq, Int -> GetNetworkResponse -> ShowS
[GetNetworkResponse] -> ShowS
GetNetworkResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetNetworkResponse] -> ShowS
$cshowList :: [GetNetworkResponse] -> ShowS
show :: GetNetworkResponse -> String
$cshow :: GetNetworkResponse -> String
showsPrec :: Int -> GetNetworkResponse -> ShowS
$cshowsPrec :: Int -> GetNetworkResponse -> ShowS
Prelude.Show, forall x. Rep GetNetworkResponse x -> GetNetworkResponse
forall x. GetNetworkResponse -> Rep GetNetworkResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetNetworkResponse x -> GetNetworkResponse
$cfrom :: forall x. GetNetworkResponse -> Rep GetNetworkResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetNetworkResponse' 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:
--
-- 'tags', 'getNetworkResponse_tags' - The network tags.
--
-- 'httpStatus', 'getNetworkResponse_httpStatus' - The response's http status code.
--
-- 'network', 'getNetworkResponse_network' - Information about the network.
newGetNetworkResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'network'
  Network ->
  GetNetworkResponse
newGetNetworkResponse :: Int -> Network -> GetNetworkResponse
newGetNetworkResponse Int
pHttpStatus_ Network
pNetwork_ =
  GetNetworkResponse'
    { $sel:tags:GetNetworkResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetNetworkResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:network:GetNetworkResponse' :: Network
network = Network
pNetwork_
    }

-- | The network tags.
getNetworkResponse_tags :: Lens.Lens' GetNetworkResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getNetworkResponse_tags :: Lens' GetNetworkResponse (Maybe (HashMap Text Text))
getNetworkResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkResponse' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:GetNetworkResponse' :: GetNetworkResponse -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: GetNetworkResponse
s@GetNetworkResponse' {} Maybe (Sensitive (HashMap Text Text))
a -> GetNetworkResponse
s {$sel:tags:GetNetworkResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: GetNetworkResponse) 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)

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

-- | Information about the network.
getNetworkResponse_network :: Lens.Lens' GetNetworkResponse Network
getNetworkResponse_network :: Lens' GetNetworkResponse Network
getNetworkResponse_network = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkResponse' {Network
network :: Network
$sel:network:GetNetworkResponse' :: GetNetworkResponse -> Network
network} -> Network
network) (\s :: GetNetworkResponse
s@GetNetworkResponse' {} Network
a -> GetNetworkResponse
s {$sel:network:GetNetworkResponse' :: Network
network = Network
a} :: GetNetworkResponse)

instance Prelude.NFData GetNetworkResponse where
  rnf :: GetNetworkResponse -> ()
rnf GetNetworkResponse' {Int
Maybe (Sensitive (HashMap Text Text))
Network
network :: Network
httpStatus :: Int
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:network:GetNetworkResponse' :: GetNetworkResponse -> Network
$sel:httpStatus:GetNetworkResponse' :: GetNetworkResponse -> Int
$sel:tags:GetNetworkResponse' :: GetNetworkResponse -> Maybe (Sensitive (HashMap Text Text))
..} =
    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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Network
network