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

    -- * Request Lenses
    updateDocumentationVersion_patchOperations,
    updateDocumentationVersion_restApiId,
    updateDocumentationVersion_documentationVersion,

    -- * Destructuring the Response
    DocumentationVersion (..),
    newDocumentationVersion,

    -- * Response Lenses
    documentationVersion_createdDate,
    documentationVersion_description,
    documentationVersion_version,
  )
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

-- | Updates an existing documentation version of an API.
--
-- /See:/ 'newUpdateDocumentationVersion' smart constructor.
data UpdateDocumentationVersion = UpdateDocumentationVersion'
  { -- | For more information about supported patch operations, see
    -- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
    UpdateDocumentationVersion -> Maybe [PatchOperation]
patchOperations :: Prelude.Maybe [PatchOperation],
    -- | The string identifier of the associated RestApi..
    UpdateDocumentationVersion -> Text
restApiId :: Prelude.Text,
    -- | The version identifier of the to-be-updated documentation version.
    UpdateDocumentationVersion -> Text
documentationVersion :: Prelude.Text
  }
  deriving (UpdateDocumentationVersion -> UpdateDocumentationVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateDocumentationVersion -> UpdateDocumentationVersion -> Bool
$c/= :: UpdateDocumentationVersion -> UpdateDocumentationVersion -> Bool
== :: UpdateDocumentationVersion -> UpdateDocumentationVersion -> Bool
$c== :: UpdateDocumentationVersion -> UpdateDocumentationVersion -> Bool
Prelude.Eq, ReadPrec [UpdateDocumentationVersion]
ReadPrec UpdateDocumentationVersion
Int -> ReadS UpdateDocumentationVersion
ReadS [UpdateDocumentationVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateDocumentationVersion]
$creadListPrec :: ReadPrec [UpdateDocumentationVersion]
readPrec :: ReadPrec UpdateDocumentationVersion
$creadPrec :: ReadPrec UpdateDocumentationVersion
readList :: ReadS [UpdateDocumentationVersion]
$creadList :: ReadS [UpdateDocumentationVersion]
readsPrec :: Int -> ReadS UpdateDocumentationVersion
$creadsPrec :: Int -> ReadS UpdateDocumentationVersion
Prelude.Read, Int -> UpdateDocumentationVersion -> ShowS
[UpdateDocumentationVersion] -> ShowS
UpdateDocumentationVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateDocumentationVersion] -> ShowS
$cshowList :: [UpdateDocumentationVersion] -> ShowS
show :: UpdateDocumentationVersion -> String
$cshow :: UpdateDocumentationVersion -> String
showsPrec :: Int -> UpdateDocumentationVersion -> ShowS
$cshowsPrec :: Int -> UpdateDocumentationVersion -> ShowS
Prelude.Show, forall x.
Rep UpdateDocumentationVersion x -> UpdateDocumentationVersion
forall x.
UpdateDocumentationVersion -> Rep UpdateDocumentationVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateDocumentationVersion x -> UpdateDocumentationVersion
$cfrom :: forall x.
UpdateDocumentationVersion -> Rep UpdateDocumentationVersion x
Prelude.Generic)

-- |
-- Create a value of 'UpdateDocumentationVersion' 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:
--
-- 'patchOperations', 'updateDocumentationVersion_patchOperations' - For more information about supported patch operations, see
-- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
--
-- 'restApiId', 'updateDocumentationVersion_restApiId' - The string identifier of the associated RestApi..
--
-- 'documentationVersion', 'updateDocumentationVersion_documentationVersion' - The version identifier of the to-be-updated documentation version.
newUpdateDocumentationVersion ::
  -- | 'restApiId'
  Prelude.Text ->
  -- | 'documentationVersion'
  Prelude.Text ->
  UpdateDocumentationVersion
newUpdateDocumentationVersion :: Text -> Text -> UpdateDocumentationVersion
newUpdateDocumentationVersion
  Text
pRestApiId_
  Text
pDocumentationVersion_ =
    UpdateDocumentationVersion'
      { $sel:patchOperations:UpdateDocumentationVersion' :: Maybe [PatchOperation]
patchOperations =
          forall a. Maybe a
Prelude.Nothing,
        $sel:restApiId:UpdateDocumentationVersion' :: Text
restApiId = Text
pRestApiId_,
        $sel:documentationVersion:UpdateDocumentationVersion' :: Text
documentationVersion = Text
pDocumentationVersion_
      }

-- | For more information about supported patch operations, see
-- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
updateDocumentationVersion_patchOperations :: Lens.Lens' UpdateDocumentationVersion (Prelude.Maybe [PatchOperation])
updateDocumentationVersion_patchOperations :: Lens' UpdateDocumentationVersion (Maybe [PatchOperation])
updateDocumentationVersion_patchOperations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDocumentationVersion' {Maybe [PatchOperation]
patchOperations :: Maybe [PatchOperation]
$sel:patchOperations:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Maybe [PatchOperation]
patchOperations} -> Maybe [PatchOperation]
patchOperations) (\s :: UpdateDocumentationVersion
s@UpdateDocumentationVersion' {} Maybe [PatchOperation]
a -> UpdateDocumentationVersion
s {$sel:patchOperations:UpdateDocumentationVersion' :: Maybe [PatchOperation]
patchOperations = Maybe [PatchOperation]
a} :: UpdateDocumentationVersion) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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

instance Core.AWSRequest UpdateDocumentationVersion where
  type
    AWSResponse UpdateDocumentationVersion =
      DocumentationVersion
  request :: (Service -> Service)
-> UpdateDocumentationVersion -> Request UpdateDocumentationVersion
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateDocumentationVersion
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateDocumentationVersion)))
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 UpdateDocumentationVersion where
  hashWithSalt :: Int -> UpdateDocumentationVersion -> Int
hashWithSalt Int
_salt UpdateDocumentationVersion' {Maybe [PatchOperation]
Text
documentationVersion :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:documentationVersion:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Text
$sel:restApiId:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Text
$sel:patchOperations:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Maybe [PatchOperation]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PatchOperation]
patchOperations
      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 UpdateDocumentationVersion where
  rnf :: UpdateDocumentationVersion -> ()
rnf UpdateDocumentationVersion' {Maybe [PatchOperation]
Text
documentationVersion :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:documentationVersion:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Text
$sel:restApiId:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Text
$sel:patchOperations:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Maybe [PatchOperation]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [PatchOperation]
patchOperations
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 UpdateDocumentationVersion where
  toHeaders :: UpdateDocumentationVersion -> 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.ToJSON UpdateDocumentationVersion where
  toJSON :: UpdateDocumentationVersion -> Value
toJSON UpdateDocumentationVersion' {Maybe [PatchOperation]
Text
documentationVersion :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:documentationVersion:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Text
$sel:restApiId:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Text
$sel:patchOperations:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Maybe [PatchOperation]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"patchOperations" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [PatchOperation]
patchOperations
          ]
      )

instance Data.ToPath UpdateDocumentationVersion where
  toPath :: UpdateDocumentationVersion -> ByteString
toPath UpdateDocumentationVersion' {Maybe [PatchOperation]
Text
documentationVersion :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:documentationVersion:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Text
$sel:restApiId:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Text
$sel:patchOperations:UpdateDocumentationVersion' :: UpdateDocumentationVersion -> Maybe [PatchOperation]
..} =
    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 UpdateDocumentationVersion where
  toQuery :: UpdateDocumentationVersion -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty