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

    -- * Request Lenses
    updateResource_patchOperations,
    updateResource_restApiId,
    updateResource_resourceId,

    -- * Destructuring the Response
    Resource (..),
    newResource,

    -- * Response Lenses
    resource_id,
    resource_parentId,
    resource_path,
    resource_pathPart,
    resource_resourceMethods,
  )
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 change information about a Resource resource.
--
-- /See:/ 'newUpdateResource' smart constructor.
data UpdateResource = UpdateResource'
  { -- | For more information about supported patch operations, see
    -- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
    UpdateResource -> Maybe [PatchOperation]
patchOperations :: Prelude.Maybe [PatchOperation],
    -- | The string identifier of the associated RestApi.
    UpdateResource -> Text
restApiId :: Prelude.Text,
    -- | The identifier of the Resource resource.
    UpdateResource -> Text
resourceId :: Prelude.Text
  }
  deriving (UpdateResource -> UpdateResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateResource -> UpdateResource -> Bool
$c/= :: UpdateResource -> UpdateResource -> Bool
== :: UpdateResource -> UpdateResource -> Bool
$c== :: UpdateResource -> UpdateResource -> Bool
Prelude.Eq, ReadPrec [UpdateResource]
ReadPrec UpdateResource
Int -> ReadS UpdateResource
ReadS [UpdateResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateResource]
$creadListPrec :: ReadPrec [UpdateResource]
readPrec :: ReadPrec UpdateResource
$creadPrec :: ReadPrec UpdateResource
readList :: ReadS [UpdateResource]
$creadList :: ReadS [UpdateResource]
readsPrec :: Int -> ReadS UpdateResource
$creadsPrec :: Int -> ReadS UpdateResource
Prelude.Read, Int -> UpdateResource -> ShowS
[UpdateResource] -> ShowS
UpdateResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateResource] -> ShowS
$cshowList :: [UpdateResource] -> ShowS
show :: UpdateResource -> String
$cshow :: UpdateResource -> String
showsPrec :: Int -> UpdateResource -> ShowS
$cshowsPrec :: Int -> UpdateResource -> ShowS
Prelude.Show, forall x. Rep UpdateResource x -> UpdateResource
forall x. UpdateResource -> Rep UpdateResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateResource x -> UpdateResource
$cfrom :: forall x. UpdateResource -> Rep UpdateResource x
Prelude.Generic)

-- |
-- Create a value of 'UpdateResource' 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', 'updateResource_patchOperations' - For more information about supported patch operations, see
-- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
--
-- 'restApiId', 'updateResource_restApiId' - The string identifier of the associated RestApi.
--
-- 'resourceId', 'updateResource_resourceId' - The identifier of the Resource resource.
newUpdateResource ::
  -- | 'restApiId'
  Prelude.Text ->
  -- | 'resourceId'
  Prelude.Text ->
  UpdateResource
newUpdateResource :: Text -> Text -> UpdateResource
newUpdateResource Text
pRestApiId_ Text
pResourceId_ =
  UpdateResource'
    { $sel:patchOperations:UpdateResource' :: Maybe [PatchOperation]
patchOperations = forall a. Maybe a
Prelude.Nothing,
      $sel:restApiId:UpdateResource' :: Text
restApiId = Text
pRestApiId_,
      $sel:resourceId:UpdateResource' :: Text
resourceId = Text
pResourceId_
    }

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

-- | The identifier of the Resource resource.
updateResource_resourceId :: Lens.Lens' UpdateResource Prelude.Text
updateResource_resourceId :: Lens' UpdateResource Text
updateResource_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateResource' {Text
resourceId :: Text
$sel:resourceId:UpdateResource' :: UpdateResource -> Text
resourceId} -> Text
resourceId) (\s :: UpdateResource
s@UpdateResource' {} Text
a -> UpdateResource
s {$sel:resourceId:UpdateResource' :: Text
resourceId = Text
a} :: UpdateResource)

instance Core.AWSRequest UpdateResource where
  type AWSResponse UpdateResource = Resource
  request :: (Service -> Service) -> UpdateResource -> Request UpdateResource
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 UpdateResource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateResource)))
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 UpdateResource where
  hashWithSalt :: Int -> UpdateResource -> Int
hashWithSalt Int
_salt UpdateResource' {Maybe [PatchOperation]
Text
resourceId :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:resourceId:UpdateResource' :: UpdateResource -> Text
$sel:restApiId:UpdateResource' :: UpdateResource -> Text
$sel:patchOperations:UpdateResource' :: UpdateResource -> 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
resourceId

instance Prelude.NFData UpdateResource where
  rnf :: UpdateResource -> ()
rnf UpdateResource' {Maybe [PatchOperation]
Text
resourceId :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:resourceId:UpdateResource' :: UpdateResource -> Text
$sel:restApiId:UpdateResource' :: UpdateResource -> Text
$sel:patchOperations:UpdateResource' :: UpdateResource -> 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
resourceId

instance Data.ToHeaders UpdateResource where
  toHeaders :: UpdateResource -> 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 UpdateResource where
  toJSON :: UpdateResource -> Value
toJSON UpdateResource' {Maybe [PatchOperation]
Text
resourceId :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:resourceId:UpdateResource' :: UpdateResource -> Text
$sel:restApiId:UpdateResource' :: UpdateResource -> Text
$sel:patchOperations:UpdateResource' :: UpdateResource -> 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 UpdateResource where
  toPath :: UpdateResource -> ByteString
toPath UpdateResource' {Maybe [PatchOperation]
Text
resourceId :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:resourceId:UpdateResource' :: UpdateResource -> Text
$sel:restApiId:UpdateResource' :: UpdateResource -> Text
$sel:patchOperations:UpdateResource' :: UpdateResource -> Maybe [PatchOperation]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/restapis/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
restApiId,
        ByteString
"/resources/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
resourceId
      ]

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