{-# 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.GetTransitGatewayRouteTableAttachment
-- 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 a transit gateway route table attachment.
module Amazonka.NetworkManager.GetTransitGatewayRouteTableAttachment
  ( -- * Creating a Request
    GetTransitGatewayRouteTableAttachment (..),
    newGetTransitGatewayRouteTableAttachment,

    -- * Request Lenses
    getTransitGatewayRouteTableAttachment_attachmentId,

    -- * Destructuring the Response
    GetTransitGatewayRouteTableAttachmentResponse (..),
    newGetTransitGatewayRouteTableAttachmentResponse,

    -- * Response Lenses
    getTransitGatewayRouteTableAttachmentResponse_transitGatewayRouteTableAttachment,
    getTransitGatewayRouteTableAttachmentResponse_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:/ 'newGetTransitGatewayRouteTableAttachment' smart constructor.
data GetTransitGatewayRouteTableAttachment = GetTransitGatewayRouteTableAttachment'
  { -- | The ID of the transit gateway route table attachment.
    GetTransitGatewayRouteTableAttachment -> Text
attachmentId :: Prelude.Text
  }
  deriving (GetTransitGatewayRouteTableAttachment
-> GetTransitGatewayRouteTableAttachment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTransitGatewayRouteTableAttachment
-> GetTransitGatewayRouteTableAttachment -> Bool
$c/= :: GetTransitGatewayRouteTableAttachment
-> GetTransitGatewayRouteTableAttachment -> Bool
== :: GetTransitGatewayRouteTableAttachment
-> GetTransitGatewayRouteTableAttachment -> Bool
$c== :: GetTransitGatewayRouteTableAttachment
-> GetTransitGatewayRouteTableAttachment -> Bool
Prelude.Eq, ReadPrec [GetTransitGatewayRouteTableAttachment]
ReadPrec GetTransitGatewayRouteTableAttachment
Int -> ReadS GetTransitGatewayRouteTableAttachment
ReadS [GetTransitGatewayRouteTableAttachment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTransitGatewayRouteTableAttachment]
$creadListPrec :: ReadPrec [GetTransitGatewayRouteTableAttachment]
readPrec :: ReadPrec GetTransitGatewayRouteTableAttachment
$creadPrec :: ReadPrec GetTransitGatewayRouteTableAttachment
readList :: ReadS [GetTransitGatewayRouteTableAttachment]
$creadList :: ReadS [GetTransitGatewayRouteTableAttachment]
readsPrec :: Int -> ReadS GetTransitGatewayRouteTableAttachment
$creadsPrec :: Int -> ReadS GetTransitGatewayRouteTableAttachment
Prelude.Read, Int -> GetTransitGatewayRouteTableAttachment -> ShowS
[GetTransitGatewayRouteTableAttachment] -> ShowS
GetTransitGatewayRouteTableAttachment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTransitGatewayRouteTableAttachment] -> ShowS
$cshowList :: [GetTransitGatewayRouteTableAttachment] -> ShowS
show :: GetTransitGatewayRouteTableAttachment -> String
$cshow :: GetTransitGatewayRouteTableAttachment -> String
showsPrec :: Int -> GetTransitGatewayRouteTableAttachment -> ShowS
$cshowsPrec :: Int -> GetTransitGatewayRouteTableAttachment -> ShowS
Prelude.Show, forall x.
Rep GetTransitGatewayRouteTableAttachment x
-> GetTransitGatewayRouteTableAttachment
forall x.
GetTransitGatewayRouteTableAttachment
-> Rep GetTransitGatewayRouteTableAttachment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetTransitGatewayRouteTableAttachment x
-> GetTransitGatewayRouteTableAttachment
$cfrom :: forall x.
GetTransitGatewayRouteTableAttachment
-> Rep GetTransitGatewayRouteTableAttachment x
Prelude.Generic)

-- |
-- Create a value of 'GetTransitGatewayRouteTableAttachment' 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:
--
-- 'attachmentId', 'getTransitGatewayRouteTableAttachment_attachmentId' - The ID of the transit gateway route table attachment.
newGetTransitGatewayRouteTableAttachment ::
  -- | 'attachmentId'
  Prelude.Text ->
  GetTransitGatewayRouteTableAttachment
newGetTransitGatewayRouteTableAttachment :: Text -> GetTransitGatewayRouteTableAttachment
newGetTransitGatewayRouteTableAttachment
  Text
pAttachmentId_ =
    GetTransitGatewayRouteTableAttachment'
      { $sel:attachmentId:GetTransitGatewayRouteTableAttachment' :: Text
attachmentId =
          Text
pAttachmentId_
      }

-- | The ID of the transit gateway route table attachment.
getTransitGatewayRouteTableAttachment_attachmentId :: Lens.Lens' GetTransitGatewayRouteTableAttachment Prelude.Text
getTransitGatewayRouteTableAttachment_attachmentId :: Lens' GetTransitGatewayRouteTableAttachment Text
getTransitGatewayRouteTableAttachment_attachmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTransitGatewayRouteTableAttachment' {Text
attachmentId :: Text
$sel:attachmentId:GetTransitGatewayRouteTableAttachment' :: GetTransitGatewayRouteTableAttachment -> Text
attachmentId} -> Text
attachmentId) (\s :: GetTransitGatewayRouteTableAttachment
s@GetTransitGatewayRouteTableAttachment' {} Text
a -> GetTransitGatewayRouteTableAttachment
s {$sel:attachmentId:GetTransitGatewayRouteTableAttachment' :: Text
attachmentId = Text
a} :: GetTransitGatewayRouteTableAttachment)

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

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

instance
  Data.ToHeaders
    GetTransitGatewayRouteTableAttachment
  where
  toHeaders :: GetTransitGatewayRouteTableAttachment -> 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
    GetTransitGatewayRouteTableAttachment
  where
  toPath :: GetTransitGatewayRouteTableAttachment -> ByteString
toPath GetTransitGatewayRouteTableAttachment' {Text
attachmentId :: Text
$sel:attachmentId:GetTransitGatewayRouteTableAttachment' :: GetTransitGatewayRouteTableAttachment -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/transit-gateway-route-table-attachments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
attachmentId
      ]

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

-- | /See:/ 'newGetTransitGatewayRouteTableAttachmentResponse' smart constructor.
data GetTransitGatewayRouteTableAttachmentResponse = GetTransitGatewayRouteTableAttachmentResponse'
  { -- | Returns information about the transit gateway route table attachment.
    GetTransitGatewayRouteTableAttachmentResponse
-> Maybe TransitGatewayRouteTableAttachment
transitGatewayRouteTableAttachment :: Prelude.Maybe TransitGatewayRouteTableAttachment,
    -- | The response's http status code.
    GetTransitGatewayRouteTableAttachmentResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetTransitGatewayRouteTableAttachmentResponse
-> GetTransitGatewayRouteTableAttachmentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTransitGatewayRouteTableAttachmentResponse
-> GetTransitGatewayRouteTableAttachmentResponse -> Bool
$c/= :: GetTransitGatewayRouteTableAttachmentResponse
-> GetTransitGatewayRouteTableAttachmentResponse -> Bool
== :: GetTransitGatewayRouteTableAttachmentResponse
-> GetTransitGatewayRouteTableAttachmentResponse -> Bool
$c== :: GetTransitGatewayRouteTableAttachmentResponse
-> GetTransitGatewayRouteTableAttachmentResponse -> Bool
Prelude.Eq, ReadPrec [GetTransitGatewayRouteTableAttachmentResponse]
ReadPrec GetTransitGatewayRouteTableAttachmentResponse
Int -> ReadS GetTransitGatewayRouteTableAttachmentResponse
ReadS [GetTransitGatewayRouteTableAttachmentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTransitGatewayRouteTableAttachmentResponse]
$creadListPrec :: ReadPrec [GetTransitGatewayRouteTableAttachmentResponse]
readPrec :: ReadPrec GetTransitGatewayRouteTableAttachmentResponse
$creadPrec :: ReadPrec GetTransitGatewayRouteTableAttachmentResponse
readList :: ReadS [GetTransitGatewayRouteTableAttachmentResponse]
$creadList :: ReadS [GetTransitGatewayRouteTableAttachmentResponse]
readsPrec :: Int -> ReadS GetTransitGatewayRouteTableAttachmentResponse
$creadsPrec :: Int -> ReadS GetTransitGatewayRouteTableAttachmentResponse
Prelude.Read, Int -> GetTransitGatewayRouteTableAttachmentResponse -> ShowS
[GetTransitGatewayRouteTableAttachmentResponse] -> ShowS
GetTransitGatewayRouteTableAttachmentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTransitGatewayRouteTableAttachmentResponse] -> ShowS
$cshowList :: [GetTransitGatewayRouteTableAttachmentResponse] -> ShowS
show :: GetTransitGatewayRouteTableAttachmentResponse -> String
$cshow :: GetTransitGatewayRouteTableAttachmentResponse -> String
showsPrec :: Int -> GetTransitGatewayRouteTableAttachmentResponse -> ShowS
$cshowsPrec :: Int -> GetTransitGatewayRouteTableAttachmentResponse -> ShowS
Prelude.Show, forall x.
Rep GetTransitGatewayRouteTableAttachmentResponse x
-> GetTransitGatewayRouteTableAttachmentResponse
forall x.
GetTransitGatewayRouteTableAttachmentResponse
-> Rep GetTransitGatewayRouteTableAttachmentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetTransitGatewayRouteTableAttachmentResponse x
-> GetTransitGatewayRouteTableAttachmentResponse
$cfrom :: forall x.
GetTransitGatewayRouteTableAttachmentResponse
-> Rep GetTransitGatewayRouteTableAttachmentResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetTransitGatewayRouteTableAttachmentResponse' 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:
--
-- 'transitGatewayRouteTableAttachment', 'getTransitGatewayRouteTableAttachmentResponse_transitGatewayRouteTableAttachment' - Returns information about the transit gateway route table attachment.
--
-- 'httpStatus', 'getTransitGatewayRouteTableAttachmentResponse_httpStatus' - The response's http status code.
newGetTransitGatewayRouteTableAttachmentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetTransitGatewayRouteTableAttachmentResponse
newGetTransitGatewayRouteTableAttachmentResponse :: Int -> GetTransitGatewayRouteTableAttachmentResponse
newGetTransitGatewayRouteTableAttachmentResponse
  Int
pHttpStatus_ =
    GetTransitGatewayRouteTableAttachmentResponse'
      { $sel:transitGatewayRouteTableAttachment:GetTransitGatewayRouteTableAttachmentResponse' :: Maybe TransitGatewayRouteTableAttachment
transitGatewayRouteTableAttachment =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetTransitGatewayRouteTableAttachmentResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Returns information about the transit gateway route table attachment.
getTransitGatewayRouteTableAttachmentResponse_transitGatewayRouteTableAttachment :: Lens.Lens' GetTransitGatewayRouteTableAttachmentResponse (Prelude.Maybe TransitGatewayRouteTableAttachment)
getTransitGatewayRouteTableAttachmentResponse_transitGatewayRouteTableAttachment :: Lens'
  GetTransitGatewayRouteTableAttachmentResponse
  (Maybe TransitGatewayRouteTableAttachment)
getTransitGatewayRouteTableAttachmentResponse_transitGatewayRouteTableAttachment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTransitGatewayRouteTableAttachmentResponse' {Maybe TransitGatewayRouteTableAttachment
transitGatewayRouteTableAttachment :: Maybe TransitGatewayRouteTableAttachment
$sel:transitGatewayRouteTableAttachment:GetTransitGatewayRouteTableAttachmentResponse' :: GetTransitGatewayRouteTableAttachmentResponse
-> Maybe TransitGatewayRouteTableAttachment
transitGatewayRouteTableAttachment} -> Maybe TransitGatewayRouteTableAttachment
transitGatewayRouteTableAttachment) (\s :: GetTransitGatewayRouteTableAttachmentResponse
s@GetTransitGatewayRouteTableAttachmentResponse' {} Maybe TransitGatewayRouteTableAttachment
a -> GetTransitGatewayRouteTableAttachmentResponse
s {$sel:transitGatewayRouteTableAttachment:GetTransitGatewayRouteTableAttachmentResponse' :: Maybe TransitGatewayRouteTableAttachment
transitGatewayRouteTableAttachment = Maybe TransitGatewayRouteTableAttachment
a} :: GetTransitGatewayRouteTableAttachmentResponse)

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

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