{-# 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.CreateNotebook
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates an empty @ipynb@ file in the specified Apache Spark enabled
-- workgroup. Throws an error if a file in the workgroup with the same name
-- already exists.
module Amazonka.Athena.CreateNotebook
  ( -- * Creating a Request
    CreateNotebook (..),
    newCreateNotebook,

    -- * Request Lenses
    createNotebook_clientRequestToken,
    createNotebook_workGroup,
    createNotebook_name,

    -- * Destructuring the Response
    CreateNotebookResponse (..),
    newCreateNotebookResponse,

    -- * Response Lenses
    createNotebookResponse_notebookId,
    createNotebookResponse_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:/ 'newCreateNotebook' smart constructor.
data CreateNotebook = CreateNotebook'
  { -- | 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.
    CreateNotebook -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the Spark enabled workgroup in which the notebook will be
    -- created.
    CreateNotebook -> Text
workGroup :: Prelude.Text,
    -- | The name of the @ipynb@ file to be created in the Spark workgroup,
    -- without the @.ipynb@ extension.
    CreateNotebook -> Text
name :: Prelude.Text
  }
  deriving (CreateNotebook -> CreateNotebook -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNotebook -> CreateNotebook -> Bool
$c/= :: CreateNotebook -> CreateNotebook -> Bool
== :: CreateNotebook -> CreateNotebook -> Bool
$c== :: CreateNotebook -> CreateNotebook -> Bool
Prelude.Eq, ReadPrec [CreateNotebook]
ReadPrec CreateNotebook
Int -> ReadS CreateNotebook
ReadS [CreateNotebook]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateNotebook]
$creadListPrec :: ReadPrec [CreateNotebook]
readPrec :: ReadPrec CreateNotebook
$creadPrec :: ReadPrec CreateNotebook
readList :: ReadS [CreateNotebook]
$creadList :: ReadS [CreateNotebook]
readsPrec :: Int -> ReadS CreateNotebook
$creadsPrec :: Int -> ReadS CreateNotebook
Prelude.Read, Int -> CreateNotebook -> ShowS
[CreateNotebook] -> ShowS
CreateNotebook -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNotebook] -> ShowS
$cshowList :: [CreateNotebook] -> ShowS
show :: CreateNotebook -> String
$cshow :: CreateNotebook -> String
showsPrec :: Int -> CreateNotebook -> ShowS
$cshowsPrec :: Int -> CreateNotebook -> ShowS
Prelude.Show, forall x. Rep CreateNotebook x -> CreateNotebook
forall x. CreateNotebook -> Rep CreateNotebook x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateNotebook x -> CreateNotebook
$cfrom :: forall x. CreateNotebook -> Rep CreateNotebook x
Prelude.Generic)

-- |
-- Create a value of 'CreateNotebook' 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', 'createNotebook_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.
--
-- 'workGroup', 'createNotebook_workGroup' - The name of the Spark enabled workgroup in which the notebook will be
-- created.
--
-- 'name', 'createNotebook_name' - The name of the @ipynb@ file to be created in the Spark workgroup,
-- without the @.ipynb@ extension.
newCreateNotebook ::
  -- | 'workGroup'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  CreateNotebook
newCreateNotebook :: Text -> Text -> CreateNotebook
newCreateNotebook Text
pWorkGroup_ Text
pName_ =
  CreateNotebook'
    { $sel:clientRequestToken:CreateNotebook' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:workGroup:CreateNotebook' :: Text
workGroup = Text
pWorkGroup_,
      $sel:name:CreateNotebook' :: 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.
createNotebook_clientRequestToken :: Lens.Lens' CreateNotebook (Prelude.Maybe Prelude.Text)
createNotebook_clientRequestToken :: Lens' CreateNotebook (Maybe Text)
createNotebook_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNotebook' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:CreateNotebook' :: CreateNotebook -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: CreateNotebook
s@CreateNotebook' {} Maybe Text
a -> CreateNotebook
s {$sel:clientRequestToken:CreateNotebook' :: Maybe Text
clientRequestToken = Maybe Text
a} :: CreateNotebook)

-- | The name of the Spark enabled workgroup in which the notebook will be
-- created.
createNotebook_workGroup :: Lens.Lens' CreateNotebook Prelude.Text
createNotebook_workGroup :: Lens' CreateNotebook Text
createNotebook_workGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNotebook' {Text
workGroup :: Text
$sel:workGroup:CreateNotebook' :: CreateNotebook -> Text
workGroup} -> Text
workGroup) (\s :: CreateNotebook
s@CreateNotebook' {} Text
a -> CreateNotebook
s {$sel:workGroup:CreateNotebook' :: Text
workGroup = Text
a} :: CreateNotebook)

-- | The name of the @ipynb@ file to be created in the Spark workgroup,
-- without the @.ipynb@ extension.
createNotebook_name :: Lens.Lens' CreateNotebook Prelude.Text
createNotebook_name :: Lens' CreateNotebook Text
createNotebook_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNotebook' {Text
name :: Text
$sel:name:CreateNotebook' :: CreateNotebook -> Text
name} -> Text
name) (\s :: CreateNotebook
s@CreateNotebook' {} Text
a -> CreateNotebook
s {$sel:name:CreateNotebook' :: Text
name = Text
a} :: CreateNotebook)

instance Core.AWSRequest CreateNotebook where
  type
    AWSResponse CreateNotebook =
      CreateNotebookResponse
  request :: (Service -> Service) -> CreateNotebook -> Request CreateNotebook
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 CreateNotebook
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateNotebook)))
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 Text -> Int -> CreateNotebookResponse
CreateNotebookResponse'
            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
"NotebookId")
            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 CreateNotebook where
  hashWithSalt :: Int -> CreateNotebook -> Int
hashWithSalt Int
_salt CreateNotebook' {Maybe Text
Text
name :: Text
workGroup :: Text
clientRequestToken :: Maybe Text
$sel:name:CreateNotebook' :: CreateNotebook -> Text
$sel:workGroup:CreateNotebook' :: CreateNotebook -> Text
$sel:clientRequestToken:CreateNotebook' :: CreateNotebook -> 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
workGroup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateNotebook where
  rnf :: CreateNotebook -> ()
rnf CreateNotebook' {Maybe Text
Text
name :: Text
workGroup :: Text
clientRequestToken :: Maybe Text
$sel:name:CreateNotebook' :: CreateNotebook -> Text
$sel:workGroup:CreateNotebook' :: CreateNotebook -> Text
$sel:clientRequestToken:CreateNotebook' :: CreateNotebook -> 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
workGroup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders CreateNotebook where
  toHeaders :: CreateNotebook -> 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.CreateNotebook" ::
                          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 CreateNotebook where
  toJSON :: CreateNotebook -> Value
toJSON CreateNotebook' {Maybe Text
Text
name :: Text
workGroup :: Text
clientRequestToken :: Maybe Text
$sel:name:CreateNotebook' :: CreateNotebook -> Text
$sel:workGroup:CreateNotebook' :: CreateNotebook -> Text
$sel:clientRequestToken:CreateNotebook' :: CreateNotebook -> 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
"WorkGroup" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
workGroup),
            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 CreateNotebook where
  toPath :: CreateNotebook -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'CreateNotebookResponse' 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', 'createNotebookResponse_notebookId' - A unique identifier for the notebook.
--
-- 'httpStatus', 'createNotebookResponse_httpStatus' - The response's http status code.
newCreateNotebookResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateNotebookResponse
newCreateNotebookResponse :: Int -> CreateNotebookResponse
newCreateNotebookResponse Int
pHttpStatus_ =
  CreateNotebookResponse'
    { $sel:notebookId:CreateNotebookResponse' :: Maybe Text
notebookId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateNotebookResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A unique identifier for the notebook.
createNotebookResponse_notebookId :: Lens.Lens' CreateNotebookResponse (Prelude.Maybe Prelude.Text)
createNotebookResponse_notebookId :: Lens' CreateNotebookResponse (Maybe Text)
createNotebookResponse_notebookId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNotebookResponse' {Maybe Text
notebookId :: Maybe Text
$sel:notebookId:CreateNotebookResponse' :: CreateNotebookResponse -> Maybe Text
notebookId} -> Maybe Text
notebookId) (\s :: CreateNotebookResponse
s@CreateNotebookResponse' {} Maybe Text
a -> CreateNotebookResponse
s {$sel:notebookId:CreateNotebookResponse' :: Maybe Text
notebookId = Maybe Text
a} :: CreateNotebookResponse)

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

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