{-# 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.GetNotebookMetadata
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves notebook metadata for the specified notebook ID.
module Amazonka.Athena.GetNotebookMetadata
  ( -- * Creating a Request
    GetNotebookMetadata (..),
    newGetNotebookMetadata,

    -- * Request Lenses
    getNotebookMetadata_notebookId,

    -- * Destructuring the Response
    GetNotebookMetadataResponse (..),
    newGetNotebookMetadataResponse,

    -- * Response Lenses
    getNotebookMetadataResponse_notebookMetadata,
    getNotebookMetadataResponse_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:/ 'newGetNotebookMetadata' smart constructor.
data GetNotebookMetadata = GetNotebookMetadata'
  { -- | The ID of the notebook whose metadata is to be retrieved.
    GetNotebookMetadata -> Text
notebookId :: Prelude.Text
  }
  deriving (GetNotebookMetadata -> GetNotebookMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetNotebookMetadata -> GetNotebookMetadata -> Bool
$c/= :: GetNotebookMetadata -> GetNotebookMetadata -> Bool
== :: GetNotebookMetadata -> GetNotebookMetadata -> Bool
$c== :: GetNotebookMetadata -> GetNotebookMetadata -> Bool
Prelude.Eq, ReadPrec [GetNotebookMetadata]
ReadPrec GetNotebookMetadata
Int -> ReadS GetNotebookMetadata
ReadS [GetNotebookMetadata]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetNotebookMetadata]
$creadListPrec :: ReadPrec [GetNotebookMetadata]
readPrec :: ReadPrec GetNotebookMetadata
$creadPrec :: ReadPrec GetNotebookMetadata
readList :: ReadS [GetNotebookMetadata]
$creadList :: ReadS [GetNotebookMetadata]
readsPrec :: Int -> ReadS GetNotebookMetadata
$creadsPrec :: Int -> ReadS GetNotebookMetadata
Prelude.Read, Int -> GetNotebookMetadata -> ShowS
[GetNotebookMetadata] -> ShowS
GetNotebookMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetNotebookMetadata] -> ShowS
$cshowList :: [GetNotebookMetadata] -> ShowS
show :: GetNotebookMetadata -> String
$cshow :: GetNotebookMetadata -> String
showsPrec :: Int -> GetNotebookMetadata -> ShowS
$cshowsPrec :: Int -> GetNotebookMetadata -> ShowS
Prelude.Show, forall x. Rep GetNotebookMetadata x -> GetNotebookMetadata
forall x. GetNotebookMetadata -> Rep GetNotebookMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetNotebookMetadata x -> GetNotebookMetadata
$cfrom :: forall x. GetNotebookMetadata -> Rep GetNotebookMetadata x
Prelude.Generic)

-- |
-- Create a value of 'GetNotebookMetadata' 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:
--
-- 'notebookId', 'getNotebookMetadata_notebookId' - The ID of the notebook whose metadata is to be retrieved.
newGetNotebookMetadata ::
  -- | 'notebookId'
  Prelude.Text ->
  GetNotebookMetadata
newGetNotebookMetadata :: Text -> GetNotebookMetadata
newGetNotebookMetadata Text
pNotebookId_ =
  GetNotebookMetadata' {$sel:notebookId:GetNotebookMetadata' :: Text
notebookId = Text
pNotebookId_}

-- | The ID of the notebook whose metadata is to be retrieved.
getNotebookMetadata_notebookId :: Lens.Lens' GetNotebookMetadata Prelude.Text
getNotebookMetadata_notebookId :: Lens' GetNotebookMetadata Text
getNotebookMetadata_notebookId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNotebookMetadata' {Text
notebookId :: Text
$sel:notebookId:GetNotebookMetadata' :: GetNotebookMetadata -> Text
notebookId} -> Text
notebookId) (\s :: GetNotebookMetadata
s@GetNotebookMetadata' {} Text
a -> GetNotebookMetadata
s {$sel:notebookId:GetNotebookMetadata' :: Text
notebookId = Text
a} :: GetNotebookMetadata)

instance Core.AWSRequest GetNotebookMetadata where
  type
    AWSResponse GetNotebookMetadata =
      GetNotebookMetadataResponse
  request :: (Service -> Service)
-> GetNotebookMetadata -> Request GetNotebookMetadata
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 GetNotebookMetadata
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetNotebookMetadata)))
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 ->
          Maybe NotebookMetadata -> Int -> GetNotebookMetadataResponse
GetNotebookMetadataResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NotebookMetadata")
            forall (f :: * -> *) a b. Applicative f => 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 GetNotebookMetadata where
  hashWithSalt :: Int -> GetNotebookMetadata -> Int
hashWithSalt Int
_salt GetNotebookMetadata' {Text
notebookId :: Text
$sel:notebookId:GetNotebookMetadata' :: GetNotebookMetadata -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
notebookId

instance Prelude.NFData GetNotebookMetadata where
  rnf :: GetNotebookMetadata -> ()
rnf GetNotebookMetadata' {Text
notebookId :: Text
$sel:notebookId:GetNotebookMetadata' :: GetNotebookMetadata -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
notebookId

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

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

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

-- | /See:/ 'newGetNotebookMetadataResponse' smart constructor.
data GetNotebookMetadataResponse = GetNotebookMetadataResponse'
  { -- | The metadata that is returned for the specified notebook ID.
    GetNotebookMetadataResponse -> Maybe NotebookMetadata
notebookMetadata :: Prelude.Maybe NotebookMetadata,
    -- | The response's http status code.
    GetNotebookMetadataResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetNotebookMetadataResponse -> GetNotebookMetadataResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetNotebookMetadataResponse -> GetNotebookMetadataResponse -> Bool
$c/= :: GetNotebookMetadataResponse -> GetNotebookMetadataResponse -> Bool
== :: GetNotebookMetadataResponse -> GetNotebookMetadataResponse -> Bool
$c== :: GetNotebookMetadataResponse -> GetNotebookMetadataResponse -> Bool
Prelude.Eq, ReadPrec [GetNotebookMetadataResponse]
ReadPrec GetNotebookMetadataResponse
Int -> ReadS GetNotebookMetadataResponse
ReadS [GetNotebookMetadataResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetNotebookMetadataResponse]
$creadListPrec :: ReadPrec [GetNotebookMetadataResponse]
readPrec :: ReadPrec GetNotebookMetadataResponse
$creadPrec :: ReadPrec GetNotebookMetadataResponse
readList :: ReadS [GetNotebookMetadataResponse]
$creadList :: ReadS [GetNotebookMetadataResponse]
readsPrec :: Int -> ReadS GetNotebookMetadataResponse
$creadsPrec :: Int -> ReadS GetNotebookMetadataResponse
Prelude.Read, Int -> GetNotebookMetadataResponse -> ShowS
[GetNotebookMetadataResponse] -> ShowS
GetNotebookMetadataResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetNotebookMetadataResponse] -> ShowS
$cshowList :: [GetNotebookMetadataResponse] -> ShowS
show :: GetNotebookMetadataResponse -> String
$cshow :: GetNotebookMetadataResponse -> String
showsPrec :: Int -> GetNotebookMetadataResponse -> ShowS
$cshowsPrec :: Int -> GetNotebookMetadataResponse -> ShowS
Prelude.Show, forall x.
Rep GetNotebookMetadataResponse x -> GetNotebookMetadataResponse
forall x.
GetNotebookMetadataResponse -> Rep GetNotebookMetadataResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetNotebookMetadataResponse x -> GetNotebookMetadataResponse
$cfrom :: forall x.
GetNotebookMetadataResponse -> Rep GetNotebookMetadataResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetNotebookMetadataResponse' 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:
--
-- 'notebookMetadata', 'getNotebookMetadataResponse_notebookMetadata' - The metadata that is returned for the specified notebook ID.
--
-- 'httpStatus', 'getNotebookMetadataResponse_httpStatus' - The response's http status code.
newGetNotebookMetadataResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetNotebookMetadataResponse
newGetNotebookMetadataResponse :: Int -> GetNotebookMetadataResponse
newGetNotebookMetadataResponse Int
pHttpStatus_ =
  GetNotebookMetadataResponse'
    { $sel:notebookMetadata:GetNotebookMetadataResponse' :: Maybe NotebookMetadata
notebookMetadata =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetNotebookMetadataResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The metadata that is returned for the specified notebook ID.
getNotebookMetadataResponse_notebookMetadata :: Lens.Lens' GetNotebookMetadataResponse (Prelude.Maybe NotebookMetadata)
getNotebookMetadataResponse_notebookMetadata :: Lens' GetNotebookMetadataResponse (Maybe NotebookMetadata)
getNotebookMetadataResponse_notebookMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNotebookMetadataResponse' {Maybe NotebookMetadata
notebookMetadata :: Maybe NotebookMetadata
$sel:notebookMetadata:GetNotebookMetadataResponse' :: GetNotebookMetadataResponse -> Maybe NotebookMetadata
notebookMetadata} -> Maybe NotebookMetadata
notebookMetadata) (\s :: GetNotebookMetadataResponse
s@GetNotebookMetadataResponse' {} Maybe NotebookMetadata
a -> GetNotebookMetadataResponse
s {$sel:notebookMetadata:GetNotebookMetadataResponse' :: Maybe NotebookMetadata
notebookMetadata = Maybe NotebookMetadata
a} :: GetNotebookMetadataResponse)

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

instance Prelude.NFData GetNotebookMetadataResponse where
  rnf :: GetNotebookMetadataResponse -> ()
rnf GetNotebookMetadataResponse' {Int
Maybe NotebookMetadata
httpStatus :: Int
notebookMetadata :: Maybe NotebookMetadata
$sel:httpStatus:GetNotebookMetadataResponse' :: GetNotebookMetadataResponse -> Int
$sel:notebookMetadata:GetNotebookMetadataResponse' :: GetNotebookMetadataResponse -> Maybe NotebookMetadata
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe NotebookMetadata
notebookMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus