{-# 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.NetworkManager.GetCoreNetwork
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about the LIVE policy for a core network.
module Amazonka.NetworkManager.GetCoreNetwork
  ( -- * Creating a Request
    GetCoreNetwork (..),
    newGetCoreNetwork,

    -- * Request Lenses
    getCoreNetwork_coreNetworkId,

    -- * Destructuring the Response
    GetCoreNetworkResponse (..),
    newGetCoreNetworkResponse,

    -- * Response Lenses
    getCoreNetworkResponse_coreNetwork,
    getCoreNetworkResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.NetworkManager.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

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

-- |
-- Create a value of 'GetCoreNetwork' 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:
--
-- 'coreNetworkId', 'getCoreNetwork_coreNetworkId' - The ID of a core network.
newGetCoreNetwork ::
  -- | 'coreNetworkId'
  Prelude.Text ->
  GetCoreNetwork
newGetCoreNetwork :: Text -> GetCoreNetwork
newGetCoreNetwork Text
pCoreNetworkId_ =
  GetCoreNetwork' {$sel:coreNetworkId:GetCoreNetwork' :: Text
coreNetworkId = Text
pCoreNetworkId_}

-- | The ID of a core network.
getCoreNetwork_coreNetworkId :: Lens.Lens' GetCoreNetwork Prelude.Text
getCoreNetwork_coreNetworkId :: Lens' GetCoreNetwork Text
getCoreNetwork_coreNetworkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCoreNetwork' {Text
coreNetworkId :: Text
$sel:coreNetworkId:GetCoreNetwork' :: GetCoreNetwork -> Text
coreNetworkId} -> Text
coreNetworkId) (\s :: GetCoreNetwork
s@GetCoreNetwork' {} Text
a -> GetCoreNetwork
s {$sel:coreNetworkId:GetCoreNetwork' :: Text
coreNetworkId = Text
a} :: GetCoreNetwork)

instance Core.AWSRequest GetCoreNetwork where
  type
    AWSResponse GetCoreNetwork =
      GetCoreNetworkResponse
  request :: (Service -> Service) -> GetCoreNetwork -> Request GetCoreNetwork
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 GetCoreNetwork
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetCoreNetwork)))
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 CoreNetwork -> Int -> GetCoreNetworkResponse
GetCoreNetworkResponse'
            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
"CoreNetwork")
            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 GetCoreNetwork where
  hashWithSalt :: Int -> GetCoreNetwork -> Int
hashWithSalt Int
_salt GetCoreNetwork' {Text
coreNetworkId :: Text
$sel:coreNetworkId:GetCoreNetwork' :: GetCoreNetwork -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
coreNetworkId

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

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

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

-- | /See:/ 'newGetCoreNetworkResponse' smart constructor.
data GetCoreNetworkResponse = GetCoreNetworkResponse'
  { -- | Details about a core network.
    GetCoreNetworkResponse -> Maybe CoreNetwork
coreNetwork :: Prelude.Maybe CoreNetwork,
    -- | The response's http status code.
    GetCoreNetworkResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetCoreNetworkResponse -> GetCoreNetworkResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCoreNetworkResponse -> GetCoreNetworkResponse -> Bool
$c/= :: GetCoreNetworkResponse -> GetCoreNetworkResponse -> Bool
== :: GetCoreNetworkResponse -> GetCoreNetworkResponse -> Bool
$c== :: GetCoreNetworkResponse -> GetCoreNetworkResponse -> Bool
Prelude.Eq, ReadPrec [GetCoreNetworkResponse]
ReadPrec GetCoreNetworkResponse
Int -> ReadS GetCoreNetworkResponse
ReadS [GetCoreNetworkResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCoreNetworkResponse]
$creadListPrec :: ReadPrec [GetCoreNetworkResponse]
readPrec :: ReadPrec GetCoreNetworkResponse
$creadPrec :: ReadPrec GetCoreNetworkResponse
readList :: ReadS [GetCoreNetworkResponse]
$creadList :: ReadS [GetCoreNetworkResponse]
readsPrec :: Int -> ReadS GetCoreNetworkResponse
$creadsPrec :: Int -> ReadS GetCoreNetworkResponse
Prelude.Read, Int -> GetCoreNetworkResponse -> ShowS
[GetCoreNetworkResponse] -> ShowS
GetCoreNetworkResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCoreNetworkResponse] -> ShowS
$cshowList :: [GetCoreNetworkResponse] -> ShowS
show :: GetCoreNetworkResponse -> String
$cshow :: GetCoreNetworkResponse -> String
showsPrec :: Int -> GetCoreNetworkResponse -> ShowS
$cshowsPrec :: Int -> GetCoreNetworkResponse -> ShowS
Prelude.Show, forall x. Rep GetCoreNetworkResponse x -> GetCoreNetworkResponse
forall x. GetCoreNetworkResponse -> Rep GetCoreNetworkResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCoreNetworkResponse x -> GetCoreNetworkResponse
$cfrom :: forall x. GetCoreNetworkResponse -> Rep GetCoreNetworkResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCoreNetworkResponse' 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:
--
-- 'coreNetwork', 'getCoreNetworkResponse_coreNetwork' - Details about a core network.
--
-- 'httpStatus', 'getCoreNetworkResponse_httpStatus' - The response's http status code.
newGetCoreNetworkResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCoreNetworkResponse
newGetCoreNetworkResponse :: Int -> GetCoreNetworkResponse
newGetCoreNetworkResponse Int
pHttpStatus_ =
  GetCoreNetworkResponse'
    { $sel:coreNetwork:GetCoreNetworkResponse' :: Maybe CoreNetwork
coreNetwork =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCoreNetworkResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Details about a core network.
getCoreNetworkResponse_coreNetwork :: Lens.Lens' GetCoreNetworkResponse (Prelude.Maybe CoreNetwork)
getCoreNetworkResponse_coreNetwork :: Lens' GetCoreNetworkResponse (Maybe CoreNetwork)
getCoreNetworkResponse_coreNetwork = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCoreNetworkResponse' {Maybe CoreNetwork
coreNetwork :: Maybe CoreNetwork
$sel:coreNetwork:GetCoreNetworkResponse' :: GetCoreNetworkResponse -> Maybe CoreNetwork
coreNetwork} -> Maybe CoreNetwork
coreNetwork) (\s :: GetCoreNetworkResponse
s@GetCoreNetworkResponse' {} Maybe CoreNetwork
a -> GetCoreNetworkResponse
s {$sel:coreNetwork:GetCoreNetworkResponse' :: Maybe CoreNetwork
coreNetwork = Maybe CoreNetwork
a} :: GetCoreNetworkResponse)

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

instance Prelude.NFData GetCoreNetworkResponse where
  rnf :: GetCoreNetworkResponse -> ()
rnf GetCoreNetworkResponse' {Int
Maybe CoreNetwork
httpStatus :: Int
coreNetwork :: Maybe CoreNetwork
$sel:httpStatus:GetCoreNetworkResponse' :: GetCoreNetworkResponse -> Int
$sel:coreNetwork:GetCoreNetworkResponse' :: GetCoreNetworkResponse -> Maybe CoreNetwork
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CoreNetwork
coreNetwork
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus