{-# 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.Athena.UpdateNotebookMetadata
-- 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 the metadata for a notebook.
module Amazonka.Athena.UpdateNotebookMetadata
  ( -- * Creating a Request
    UpdateNotebookMetadata (..),
    newUpdateNotebookMetadata,

    -- * Request Lenses
    updateNotebookMetadata_clientRequestToken,
    updateNotebookMetadata_notebookId,
    updateNotebookMetadata_name,

    -- * Destructuring the Response
    UpdateNotebookMetadataResponse (..),
    newUpdateNotebookMetadataResponse,

    -- * Response Lenses
    updateNotebookMetadataResponse_httpStatus,
  )
where

import Amazonka.Athena.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

-- | /See:/ 'newUpdateNotebookMetadata' smart constructor.
data UpdateNotebookMetadata = UpdateNotebookMetadata'
  { -- | A unique case-sensitive string used to ensure the request to create the
    -- notebook is idempotent (executes only once).
    --
    -- This token is listed as not required because Amazon Web Services SDKs
    -- (for example the Amazon Web Services SDK for Java) auto-generate the
    -- token for you. If you are not using the Amazon Web Services SDK or the
    -- Amazon Web Services CLI, you must provide this token or the action will
    -- fail.
    UpdateNotebookMetadata -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the notebook to update the metadata for.
    UpdateNotebookMetadata -> Text
notebookId :: Prelude.Text,
    -- | The name to update the notebook to.
    UpdateNotebookMetadata -> Text
name :: Prelude.Text
  }
  deriving (UpdateNotebookMetadata -> UpdateNotebookMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateNotebookMetadata -> UpdateNotebookMetadata -> Bool
$c/= :: UpdateNotebookMetadata -> UpdateNotebookMetadata -> Bool
== :: UpdateNotebookMetadata -> UpdateNotebookMetadata -> Bool
$c== :: UpdateNotebookMetadata -> UpdateNotebookMetadata -> Bool
Prelude.Eq, ReadPrec [UpdateNotebookMetadata]
ReadPrec UpdateNotebookMetadata
Int -> ReadS UpdateNotebookMetadata
ReadS [UpdateNotebookMetadata]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateNotebookMetadata]
$creadListPrec :: ReadPrec [UpdateNotebookMetadata]
readPrec :: ReadPrec UpdateNotebookMetadata
$creadPrec :: ReadPrec UpdateNotebookMetadata
readList :: ReadS [UpdateNotebookMetadata]
$creadList :: ReadS [UpdateNotebookMetadata]
readsPrec :: Int -> ReadS UpdateNotebookMetadata
$creadsPrec :: Int -> ReadS UpdateNotebookMetadata
Prelude.Read, Int -> UpdateNotebookMetadata -> ShowS
[UpdateNotebookMetadata] -> ShowS
UpdateNotebookMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateNotebookMetadata] -> ShowS
$cshowList :: [UpdateNotebookMetadata] -> ShowS
show :: UpdateNotebookMetadata -> String
$cshow :: UpdateNotebookMetadata -> String
showsPrec :: Int -> UpdateNotebookMetadata -> ShowS
$cshowsPrec :: Int -> UpdateNotebookMetadata -> ShowS
Prelude.Show, forall x. Rep UpdateNotebookMetadata x -> UpdateNotebookMetadata
forall x. UpdateNotebookMetadata -> Rep UpdateNotebookMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateNotebookMetadata x -> UpdateNotebookMetadata
$cfrom :: forall x. UpdateNotebookMetadata -> Rep UpdateNotebookMetadata x
Prelude.Generic)

-- |
-- Create a value of 'UpdateNotebookMetadata' 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:
--
-- 'clientRequestToken', 'updateNotebookMetadata_clientRequestToken' - A unique case-sensitive string used to ensure the request to create the
-- notebook is idempotent (executes only once).
--
-- This token is listed as not required because Amazon Web Services SDKs
-- (for example the Amazon Web Services SDK for Java) auto-generate the
-- token for you. If you are not using the Amazon Web Services SDK or the
-- Amazon Web Services CLI, you must provide this token or the action will
-- fail.
--
-- 'notebookId', 'updateNotebookMetadata_notebookId' - The ID of the notebook to update the metadata for.
--
-- 'name', 'updateNotebookMetadata_name' - The name to update the notebook to.
newUpdateNotebookMetadata ::
  -- | 'notebookId'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  UpdateNotebookMetadata
newUpdateNotebookMetadata :: Text -> Text -> UpdateNotebookMetadata
newUpdateNotebookMetadata Text
pNotebookId_ Text
pName_ =
  UpdateNotebookMetadata'
    { $sel:clientRequestToken:UpdateNotebookMetadata' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:notebookId:UpdateNotebookMetadata' :: Text
notebookId = Text
pNotebookId_,
      $sel:name:UpdateNotebookMetadata' :: Text
name = Text
pName_
    }

-- | A unique case-sensitive string used to ensure the request to create the
-- notebook is idempotent (executes only once).
--
-- This token is listed as not required because Amazon Web Services SDKs
-- (for example the Amazon Web Services SDK for Java) auto-generate the
-- token for you. If you are not using the Amazon Web Services SDK or the
-- Amazon Web Services CLI, you must provide this token or the action will
-- fail.
updateNotebookMetadata_clientRequestToken :: Lens.Lens' UpdateNotebookMetadata (Prelude.Maybe Prelude.Text)
updateNotebookMetadata_clientRequestToken :: Lens' UpdateNotebookMetadata (Maybe Text)
updateNotebookMetadata_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateNotebookMetadata' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: UpdateNotebookMetadata
s@UpdateNotebookMetadata' {} Maybe Text
a -> UpdateNotebookMetadata
s {$sel:clientRequestToken:UpdateNotebookMetadata' :: Maybe Text
clientRequestToken = Maybe Text
a} :: UpdateNotebookMetadata)

-- | The ID of the notebook to update the metadata for.
updateNotebookMetadata_notebookId :: Lens.Lens' UpdateNotebookMetadata Prelude.Text
updateNotebookMetadata_notebookId :: Lens' UpdateNotebookMetadata Text
updateNotebookMetadata_notebookId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateNotebookMetadata' {Text
notebookId :: Text
$sel:notebookId:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Text
notebookId} -> Text
notebookId) (\s :: UpdateNotebookMetadata
s@UpdateNotebookMetadata' {} Text
a -> UpdateNotebookMetadata
s {$sel:notebookId:UpdateNotebookMetadata' :: Text
notebookId = Text
a} :: UpdateNotebookMetadata)

-- | The name to update the notebook to.
updateNotebookMetadata_name :: Lens.Lens' UpdateNotebookMetadata Prelude.Text
updateNotebookMetadata_name :: Lens' UpdateNotebookMetadata Text
updateNotebookMetadata_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateNotebookMetadata' {Text
name :: Text
$sel:name:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Text
name} -> Text
name) (\s :: UpdateNotebookMetadata
s@UpdateNotebookMetadata' {} Text
a -> UpdateNotebookMetadata
s {$sel:name:UpdateNotebookMetadata' :: Text
name = Text
a} :: UpdateNotebookMetadata)

instance Core.AWSRequest UpdateNotebookMetadata where
  type
    AWSResponse UpdateNotebookMetadata =
      UpdateNotebookMetadataResponse
  request :: (Service -> Service)
-> UpdateNotebookMetadata -> Request UpdateNotebookMetadata
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateNotebookMetadata
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateNotebookMetadata)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateNotebookMetadataResponse
UpdateNotebookMetadataResponse'
            forall (f :: * -> *) a b. Functor 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 UpdateNotebookMetadata where
  hashWithSalt :: Int -> UpdateNotebookMetadata -> Int
hashWithSalt Int
_salt UpdateNotebookMetadata' {Maybe Text
Text
name :: Text
notebookId :: Text
clientRequestToken :: Maybe Text
$sel:name:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Text
$sel:notebookId:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Text
$sel:clientRequestToken:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
notebookId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData UpdateNotebookMetadata where
  rnf :: UpdateNotebookMetadata -> ()
rnf UpdateNotebookMetadata' {Maybe Text
Text
name :: Text
notebookId :: Text
clientRequestToken :: Maybe Text
$sel:name:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Text
$sel:notebookId:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Text
$sel:clientRequestToken:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
notebookId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders UpdateNotebookMetadata where
  toHeaders :: UpdateNotebookMetadata -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonAthena.UpdateNotebookMetadata" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateNotebookMetadata where
  toJSON :: UpdateNotebookMetadata -> Value
toJSON UpdateNotebookMetadata' {Maybe Text
Text
name :: Text
notebookId :: Text
clientRequestToken :: Maybe Text
$sel:name:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Text
$sel:notebookId:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Text
$sel:clientRequestToken:UpdateNotebookMetadata' :: UpdateNotebookMetadata -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientRequestToken" 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 Text
clientRequestToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"NotebookId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
notebookId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

instance Data.ToPath UpdateNotebookMetadata where
  toPath :: UpdateNotebookMetadata -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'UpdateNotebookMetadataResponse' 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:
--
-- 'httpStatus', 'updateNotebookMetadataResponse_httpStatus' - The response's http status code.
newUpdateNotebookMetadataResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateNotebookMetadataResponse
newUpdateNotebookMetadataResponse :: Int -> UpdateNotebookMetadataResponse
newUpdateNotebookMetadataResponse Int
pHttpStatus_ =
  UpdateNotebookMetadataResponse'
    { $sel:httpStatus:UpdateNotebookMetadataResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    UpdateNotebookMetadataResponse
  where
  rnf :: UpdateNotebookMetadataResponse -> ()
rnf UpdateNotebookMetadataResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateNotebookMetadataResponse' :: UpdateNotebookMetadataResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus