{-# 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.APIGateway.GetBasePathMapping
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describe a BasePathMapping resource.
module Amazonka.APIGateway.GetBasePathMapping
  ( -- * Creating a Request
    GetBasePathMapping (..),
    newGetBasePathMapping,

    -- * Request Lenses
    getBasePathMapping_domainName,
    getBasePathMapping_basePath,

    -- * Destructuring the Response
    BasePathMapping (..),
    newBasePathMapping,

    -- * Response Lenses
    basePathMapping_basePath,
    basePathMapping_restApiId,
    basePathMapping_stage,
  )
where

import Amazonka.APIGateway.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Request to describe a BasePathMapping resource.
--
-- /See:/ 'newGetBasePathMapping' smart constructor.
data GetBasePathMapping = GetBasePathMapping'
  { -- | The domain name of the BasePathMapping resource to be described.
    GetBasePathMapping -> Text
domainName :: Prelude.Text,
    -- | The base path name that callers of the API must provide as part of the
    -- URL after the domain name. This value must be unique for all of the
    -- mappings across a single API. Specify \'(none)\' if you do not want
    -- callers to specify any base path name after the domain name.
    GetBasePathMapping -> Text
basePath :: Prelude.Text
  }
  deriving (GetBasePathMapping -> GetBasePathMapping -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBasePathMapping -> GetBasePathMapping -> Bool
$c/= :: GetBasePathMapping -> GetBasePathMapping -> Bool
== :: GetBasePathMapping -> GetBasePathMapping -> Bool
$c== :: GetBasePathMapping -> GetBasePathMapping -> Bool
Prelude.Eq, ReadPrec [GetBasePathMapping]
ReadPrec GetBasePathMapping
Int -> ReadS GetBasePathMapping
ReadS [GetBasePathMapping]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBasePathMapping]
$creadListPrec :: ReadPrec [GetBasePathMapping]
readPrec :: ReadPrec GetBasePathMapping
$creadPrec :: ReadPrec GetBasePathMapping
readList :: ReadS [GetBasePathMapping]
$creadList :: ReadS [GetBasePathMapping]
readsPrec :: Int -> ReadS GetBasePathMapping
$creadsPrec :: Int -> ReadS GetBasePathMapping
Prelude.Read, Int -> GetBasePathMapping -> ShowS
[GetBasePathMapping] -> ShowS
GetBasePathMapping -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBasePathMapping] -> ShowS
$cshowList :: [GetBasePathMapping] -> ShowS
show :: GetBasePathMapping -> String
$cshow :: GetBasePathMapping -> String
showsPrec :: Int -> GetBasePathMapping -> ShowS
$cshowsPrec :: Int -> GetBasePathMapping -> ShowS
Prelude.Show, forall x. Rep GetBasePathMapping x -> GetBasePathMapping
forall x. GetBasePathMapping -> Rep GetBasePathMapping x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBasePathMapping x -> GetBasePathMapping
$cfrom :: forall x. GetBasePathMapping -> Rep GetBasePathMapping x
Prelude.Generic)

-- |
-- Create a value of 'GetBasePathMapping' 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:
--
-- 'domainName', 'getBasePathMapping_domainName' - The domain name of the BasePathMapping resource to be described.
--
-- 'basePath', 'getBasePathMapping_basePath' - The base path name that callers of the API must provide as part of the
-- URL after the domain name. This value must be unique for all of the
-- mappings across a single API. Specify \'(none)\' if you do not want
-- callers to specify any base path name after the domain name.
newGetBasePathMapping ::
  -- | 'domainName'
  Prelude.Text ->
  -- | 'basePath'
  Prelude.Text ->
  GetBasePathMapping
newGetBasePathMapping :: Text -> Text -> GetBasePathMapping
newGetBasePathMapping Text
pDomainName_ Text
pBasePath_ =
  GetBasePathMapping'
    { $sel:domainName:GetBasePathMapping' :: Text
domainName = Text
pDomainName_,
      $sel:basePath:GetBasePathMapping' :: Text
basePath = Text
pBasePath_
    }

-- | The domain name of the BasePathMapping resource to be described.
getBasePathMapping_domainName :: Lens.Lens' GetBasePathMapping Prelude.Text
getBasePathMapping_domainName :: Lens' GetBasePathMapping Text
getBasePathMapping_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBasePathMapping' {Text
domainName :: Text
$sel:domainName:GetBasePathMapping' :: GetBasePathMapping -> Text
domainName} -> Text
domainName) (\s :: GetBasePathMapping
s@GetBasePathMapping' {} Text
a -> GetBasePathMapping
s {$sel:domainName:GetBasePathMapping' :: Text
domainName = Text
a} :: GetBasePathMapping)

-- | The base path name that callers of the API must provide as part of the
-- URL after the domain name. This value must be unique for all of the
-- mappings across a single API. Specify \'(none)\' if you do not want
-- callers to specify any base path name after the domain name.
getBasePathMapping_basePath :: Lens.Lens' GetBasePathMapping Prelude.Text
getBasePathMapping_basePath :: Lens' GetBasePathMapping Text
getBasePathMapping_basePath = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBasePathMapping' {Text
basePath :: Text
$sel:basePath:GetBasePathMapping' :: GetBasePathMapping -> Text
basePath} -> Text
basePath) (\s :: GetBasePathMapping
s@GetBasePathMapping' {} Text
a -> GetBasePathMapping
s {$sel:basePath:GetBasePathMapping' :: Text
basePath = Text
a} :: GetBasePathMapping)

instance Core.AWSRequest GetBasePathMapping where
  type AWSResponse GetBasePathMapping = BasePathMapping
  request :: (Service -> Service)
-> GetBasePathMapping -> Request GetBasePathMapping
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 GetBasePathMapping
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetBasePathMapping)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

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

instance Prelude.NFData GetBasePathMapping where
  rnf :: GetBasePathMapping -> ()
rnf GetBasePathMapping' {Text
basePath :: Text
domainName :: Text
$sel:basePath:GetBasePathMapping' :: GetBasePathMapping -> Text
$sel:domainName:GetBasePathMapping' :: GetBasePathMapping -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
basePath

instance Data.ToHeaders GetBasePathMapping where
  toHeaders :: GetBasePathMapping -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Accept"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/json" :: Prelude.ByteString)
          ]
      )

instance Data.ToPath GetBasePathMapping where
  toPath :: GetBasePathMapping -> ByteString
toPath GetBasePathMapping' {Text
basePath :: Text
domainName :: Text
$sel:basePath:GetBasePathMapping' :: GetBasePathMapping -> Text
$sel:domainName:GetBasePathMapping' :: GetBasePathMapping -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/domainnames/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
domainName,
        ByteString
"/basepathmappings/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
basePath
      ]

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