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

    -- * Request Lenses
    deleteDocumentationVersion_restApiId,
    deleteDocumentationVersion_documentationVersion,

    -- * Destructuring the Response
    DeleteDocumentationVersionResponse (..),
    newDeleteDocumentationVersionResponse,
  )
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

-- | Deletes an existing documentation version of an API.
--
-- /See:/ 'newDeleteDocumentationVersion' smart constructor.
data DeleteDocumentationVersion = DeleteDocumentationVersion'
  { -- | The string identifier of the associated RestApi.
    DeleteDocumentationVersion -> Text
restApiId :: Prelude.Text,
    -- | The version identifier of a to-be-deleted documentation snapshot.
    DeleteDocumentationVersion -> Text
documentationVersion :: Prelude.Text
  }
  deriving (DeleteDocumentationVersion -> DeleteDocumentationVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDocumentationVersion -> DeleteDocumentationVersion -> Bool
$c/= :: DeleteDocumentationVersion -> DeleteDocumentationVersion -> Bool
== :: DeleteDocumentationVersion -> DeleteDocumentationVersion -> Bool
$c== :: DeleteDocumentationVersion -> DeleteDocumentationVersion -> Bool
Prelude.Eq, ReadPrec [DeleteDocumentationVersion]
ReadPrec DeleteDocumentationVersion
Int -> ReadS DeleteDocumentationVersion
ReadS [DeleteDocumentationVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDocumentationVersion]
$creadListPrec :: ReadPrec [DeleteDocumentationVersion]
readPrec :: ReadPrec DeleteDocumentationVersion
$creadPrec :: ReadPrec DeleteDocumentationVersion
readList :: ReadS [DeleteDocumentationVersion]
$creadList :: ReadS [DeleteDocumentationVersion]
readsPrec :: Int -> ReadS DeleteDocumentationVersion
$creadsPrec :: Int -> ReadS DeleteDocumentationVersion
Prelude.Read, Int -> DeleteDocumentationVersion -> ShowS
[DeleteDocumentationVersion] -> ShowS
DeleteDocumentationVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDocumentationVersion] -> ShowS
$cshowList :: [DeleteDocumentationVersion] -> ShowS
show :: DeleteDocumentationVersion -> String
$cshow :: DeleteDocumentationVersion -> String
showsPrec :: Int -> DeleteDocumentationVersion -> ShowS
$cshowsPrec :: Int -> DeleteDocumentationVersion -> ShowS
Prelude.Show, forall x.
Rep DeleteDocumentationVersion x -> DeleteDocumentationVersion
forall x.
DeleteDocumentationVersion -> Rep DeleteDocumentationVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteDocumentationVersion x -> DeleteDocumentationVersion
$cfrom :: forall x.
DeleteDocumentationVersion -> Rep DeleteDocumentationVersion x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDocumentationVersion' 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:
--
-- 'restApiId', 'deleteDocumentationVersion_restApiId' - The string identifier of the associated RestApi.
--
-- 'documentationVersion', 'deleteDocumentationVersion_documentationVersion' - The version identifier of a to-be-deleted documentation snapshot.
newDeleteDocumentationVersion ::
  -- | 'restApiId'
  Prelude.Text ->
  -- | 'documentationVersion'
  Prelude.Text ->
  DeleteDocumentationVersion
newDeleteDocumentationVersion :: Text -> Text -> DeleteDocumentationVersion
newDeleteDocumentationVersion
  Text
pRestApiId_
  Text
pDocumentationVersion_ =
    DeleteDocumentationVersion'
      { $sel:restApiId:DeleteDocumentationVersion' :: Text
restApiId =
          Text
pRestApiId_,
        $sel:documentationVersion:DeleteDocumentationVersion' :: Text
documentationVersion = Text
pDocumentationVersion_
      }

-- | The string identifier of the associated RestApi.
deleteDocumentationVersion_restApiId :: Lens.Lens' DeleteDocumentationVersion Prelude.Text
deleteDocumentationVersion_restApiId :: Lens' DeleteDocumentationVersion Text
deleteDocumentationVersion_restApiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDocumentationVersion' {Text
restApiId :: Text
$sel:restApiId:DeleteDocumentationVersion' :: DeleteDocumentationVersion -> Text
restApiId} -> Text
restApiId) (\s :: DeleteDocumentationVersion
s@DeleteDocumentationVersion' {} Text
a -> DeleteDocumentationVersion
s {$sel:restApiId:DeleteDocumentationVersion' :: Text
restApiId = Text
a} :: DeleteDocumentationVersion)

-- | The version identifier of a to-be-deleted documentation snapshot.
deleteDocumentationVersion_documentationVersion :: Lens.Lens' DeleteDocumentationVersion Prelude.Text
deleteDocumentationVersion_documentationVersion :: Lens' DeleteDocumentationVersion Text
deleteDocumentationVersion_documentationVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDocumentationVersion' {Text
documentationVersion :: Text
$sel:documentationVersion:DeleteDocumentationVersion' :: DeleteDocumentationVersion -> Text
documentationVersion} -> Text
documentationVersion) (\s :: DeleteDocumentationVersion
s@DeleteDocumentationVersion' {} Text
a -> DeleteDocumentationVersion
s {$sel:documentationVersion:DeleteDocumentationVersion' :: Text
documentationVersion = Text
a} :: DeleteDocumentationVersion)

instance Core.AWSRequest DeleteDocumentationVersion where
  type
    AWSResponse DeleteDocumentationVersion =
      DeleteDocumentationVersionResponse
  request :: (Service -> Service)
-> DeleteDocumentationVersion -> Request DeleteDocumentationVersion
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteDocumentationVersion
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteDocumentationVersion)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DeleteDocumentationVersionResponse
DeleteDocumentationVersionResponse'

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

instance Prelude.NFData DeleteDocumentationVersion where
  rnf :: DeleteDocumentationVersion -> ()
rnf DeleteDocumentationVersion' {Text
documentationVersion :: Text
restApiId :: Text
$sel:documentationVersion:DeleteDocumentationVersion' :: DeleteDocumentationVersion -> Text
$sel:restApiId:DeleteDocumentationVersion' :: DeleteDocumentationVersion -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
restApiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
documentationVersion

instance Data.ToHeaders DeleteDocumentationVersion where
  toHeaders :: DeleteDocumentationVersion -> [Header]
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 -> [Header]
Data.=# (ByteString
"application/json" :: Prelude.ByteString)
          ]
      )

instance Data.ToPath DeleteDocumentationVersion where
  toPath :: DeleteDocumentationVersion -> ByteString
toPath DeleteDocumentationVersion' {Text
documentationVersion :: Text
restApiId :: Text
$sel:documentationVersion:DeleteDocumentationVersion' :: DeleteDocumentationVersion -> Text
$sel:restApiId:DeleteDocumentationVersion' :: DeleteDocumentationVersion -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/restapis/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
restApiId,
        ByteString
"/documentation/versions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
documentationVersion
      ]

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

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

-- |
-- Create a value of 'DeleteDocumentationVersionResponse' 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.
newDeleteDocumentationVersionResponse ::
  DeleteDocumentationVersionResponse
newDeleteDocumentationVersionResponse :: DeleteDocumentationVersionResponse
newDeleteDocumentationVersionResponse =
  DeleteDocumentationVersionResponse
DeleteDocumentationVersionResponse'

instance
  Prelude.NFData
    DeleteDocumentationVersionResponse
  where
  rnf :: DeleteDocumentationVersionResponse -> ()
rnf DeleteDocumentationVersionResponse
_ = ()