{-# 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.CreateWorkGroup
-- 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 a workgroup with the specified name. Only one of
-- @Configurations@ or @Configuration@ can be specified; @Configurations@
-- for a workgroup with multi engine support (for example, an Apache Spark
-- enabled workgroup) or @Configuration@ for an Athena SQL workgroup.
module Amazonka.Athena.CreateWorkGroup
  ( -- * Creating a Request
    CreateWorkGroup (..),
    newCreateWorkGroup,

    -- * Request Lenses
    createWorkGroup_configuration,
    createWorkGroup_description,
    createWorkGroup_tags,
    createWorkGroup_name,

    -- * Destructuring the Response
    CreateWorkGroupResponse (..),
    newCreateWorkGroupResponse,

    -- * Response Lenses
    createWorkGroupResponse_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:/ 'newCreateWorkGroup' smart constructor.
data CreateWorkGroup = CreateWorkGroup'
  { -- | Contains configuration information for creating an Athena SQL workgroup,
    -- which includes the location in Amazon S3 where query results are stored,
    -- the encryption configuration, if any, used for encrypting query results,
    -- whether the Amazon CloudWatch Metrics are enabled for the workgroup, the
    -- limit for the amount of bytes scanned (cutoff) per query, if it is
    -- specified, and whether workgroup\'s settings (specified with
    -- @EnforceWorkGroupConfiguration@) in the @WorkGroupConfiguration@
    -- override client-side settings. See
    -- WorkGroupConfiguration$EnforceWorkGroupConfiguration.
    CreateWorkGroup -> Maybe WorkGroupConfiguration
configuration :: Prelude.Maybe WorkGroupConfiguration,
    -- | The workgroup description.
    CreateWorkGroup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A list of comma separated tags to add to the workgroup that is created.
    CreateWorkGroup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The workgroup name.
    CreateWorkGroup -> Text
name :: Prelude.Text
  }
  deriving (CreateWorkGroup -> CreateWorkGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWorkGroup -> CreateWorkGroup -> Bool
$c/= :: CreateWorkGroup -> CreateWorkGroup -> Bool
== :: CreateWorkGroup -> CreateWorkGroup -> Bool
$c== :: CreateWorkGroup -> CreateWorkGroup -> Bool
Prelude.Eq, ReadPrec [CreateWorkGroup]
ReadPrec CreateWorkGroup
Int -> ReadS CreateWorkGroup
ReadS [CreateWorkGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWorkGroup]
$creadListPrec :: ReadPrec [CreateWorkGroup]
readPrec :: ReadPrec CreateWorkGroup
$creadPrec :: ReadPrec CreateWorkGroup
readList :: ReadS [CreateWorkGroup]
$creadList :: ReadS [CreateWorkGroup]
readsPrec :: Int -> ReadS CreateWorkGroup
$creadsPrec :: Int -> ReadS CreateWorkGroup
Prelude.Read, Int -> CreateWorkGroup -> ShowS
[CreateWorkGroup] -> ShowS
CreateWorkGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWorkGroup] -> ShowS
$cshowList :: [CreateWorkGroup] -> ShowS
show :: CreateWorkGroup -> String
$cshow :: CreateWorkGroup -> String
showsPrec :: Int -> CreateWorkGroup -> ShowS
$cshowsPrec :: Int -> CreateWorkGroup -> ShowS
Prelude.Show, forall x. Rep CreateWorkGroup x -> CreateWorkGroup
forall x. CreateWorkGroup -> Rep CreateWorkGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateWorkGroup x -> CreateWorkGroup
$cfrom :: forall x. CreateWorkGroup -> Rep CreateWorkGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateWorkGroup' 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:
--
-- 'configuration', 'createWorkGroup_configuration' - Contains configuration information for creating an Athena SQL workgroup,
-- which includes the location in Amazon S3 where query results are stored,
-- the encryption configuration, if any, used for encrypting query results,
-- whether the Amazon CloudWatch Metrics are enabled for the workgroup, the
-- limit for the amount of bytes scanned (cutoff) per query, if it is
-- specified, and whether workgroup\'s settings (specified with
-- @EnforceWorkGroupConfiguration@) in the @WorkGroupConfiguration@
-- override client-side settings. See
-- WorkGroupConfiguration$EnforceWorkGroupConfiguration.
--
-- 'description', 'createWorkGroup_description' - The workgroup description.
--
-- 'tags', 'createWorkGroup_tags' - A list of comma separated tags to add to the workgroup that is created.
--
-- 'name', 'createWorkGroup_name' - The workgroup name.
newCreateWorkGroup ::
  -- | 'name'
  Prelude.Text ->
  CreateWorkGroup
newCreateWorkGroup :: Text -> CreateWorkGroup
newCreateWorkGroup Text
pName_ =
  CreateWorkGroup'
    { $sel:configuration:CreateWorkGroup' :: Maybe WorkGroupConfiguration
configuration = forall a. Maybe a
Prelude.Nothing,
      $sel:description:CreateWorkGroup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateWorkGroup' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateWorkGroup' :: Text
name = Text
pName_
    }

-- | Contains configuration information for creating an Athena SQL workgroup,
-- which includes the location in Amazon S3 where query results are stored,
-- the encryption configuration, if any, used for encrypting query results,
-- whether the Amazon CloudWatch Metrics are enabled for the workgroup, the
-- limit for the amount of bytes scanned (cutoff) per query, if it is
-- specified, and whether workgroup\'s settings (specified with
-- @EnforceWorkGroupConfiguration@) in the @WorkGroupConfiguration@
-- override client-side settings. See
-- WorkGroupConfiguration$EnforceWorkGroupConfiguration.
createWorkGroup_configuration :: Lens.Lens' CreateWorkGroup (Prelude.Maybe WorkGroupConfiguration)
createWorkGroup_configuration :: Lens' CreateWorkGroup (Maybe WorkGroupConfiguration)
createWorkGroup_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkGroup' {Maybe WorkGroupConfiguration
configuration :: Maybe WorkGroupConfiguration
$sel:configuration:CreateWorkGroup' :: CreateWorkGroup -> Maybe WorkGroupConfiguration
configuration} -> Maybe WorkGroupConfiguration
configuration) (\s :: CreateWorkGroup
s@CreateWorkGroup' {} Maybe WorkGroupConfiguration
a -> CreateWorkGroup
s {$sel:configuration:CreateWorkGroup' :: Maybe WorkGroupConfiguration
configuration = Maybe WorkGroupConfiguration
a} :: CreateWorkGroup)

-- | The workgroup description.
createWorkGroup_description :: Lens.Lens' CreateWorkGroup (Prelude.Maybe Prelude.Text)
createWorkGroup_description :: Lens' CreateWorkGroup (Maybe Text)
createWorkGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkGroup' {Maybe Text
description :: Maybe Text
$sel:description:CreateWorkGroup' :: CreateWorkGroup -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateWorkGroup
s@CreateWorkGroup' {} Maybe Text
a -> CreateWorkGroup
s {$sel:description:CreateWorkGroup' :: Maybe Text
description = Maybe Text
a} :: CreateWorkGroup)

-- | A list of comma separated tags to add to the workgroup that is created.
createWorkGroup_tags :: Lens.Lens' CreateWorkGroup (Prelude.Maybe [Tag])
createWorkGroup_tags :: Lens' CreateWorkGroup (Maybe [Tag])
createWorkGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkGroup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateWorkGroup' :: CreateWorkGroup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateWorkGroup
s@CreateWorkGroup' {} Maybe [Tag]
a -> CreateWorkGroup
s {$sel:tags:CreateWorkGroup' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateWorkGroup) 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 workgroup name.
createWorkGroup_name :: Lens.Lens' CreateWorkGroup Prelude.Text
createWorkGroup_name :: Lens' CreateWorkGroup Text
createWorkGroup_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkGroup' {Text
name :: Text
$sel:name:CreateWorkGroup' :: CreateWorkGroup -> Text
name} -> Text
name) (\s :: CreateWorkGroup
s@CreateWorkGroup' {} Text
a -> CreateWorkGroup
s {$sel:name:CreateWorkGroup' :: Text
name = Text
a} :: CreateWorkGroup)

instance Core.AWSRequest CreateWorkGroup where
  type
    AWSResponse CreateWorkGroup =
      CreateWorkGroupResponse
  request :: (Service -> Service) -> CreateWorkGroup -> Request CreateWorkGroup
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 CreateWorkGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateWorkGroup)))
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 -> CreateWorkGroupResponse
CreateWorkGroupResponse'
            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 CreateWorkGroup where
  hashWithSalt :: Int -> CreateWorkGroup -> Int
hashWithSalt Int
_salt CreateWorkGroup' {Maybe [Tag]
Maybe Text
Maybe WorkGroupConfiguration
Text
name :: Text
tags :: Maybe [Tag]
description :: Maybe Text
configuration :: Maybe WorkGroupConfiguration
$sel:name:CreateWorkGroup' :: CreateWorkGroup -> Text
$sel:tags:CreateWorkGroup' :: CreateWorkGroup -> Maybe [Tag]
$sel:description:CreateWorkGroup' :: CreateWorkGroup -> Maybe Text
$sel:configuration:CreateWorkGroup' :: CreateWorkGroup -> Maybe WorkGroupConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WorkGroupConfiguration
configuration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateWorkGroup where
  rnf :: CreateWorkGroup -> ()
rnf CreateWorkGroup' {Maybe [Tag]
Maybe Text
Maybe WorkGroupConfiguration
Text
name :: Text
tags :: Maybe [Tag]
description :: Maybe Text
configuration :: Maybe WorkGroupConfiguration
$sel:name:CreateWorkGroup' :: CreateWorkGroup -> Text
$sel:tags:CreateWorkGroup' :: CreateWorkGroup -> Maybe [Tag]
$sel:description:CreateWorkGroup' :: CreateWorkGroup -> Maybe Text
$sel:configuration:CreateWorkGroup' :: CreateWorkGroup -> Maybe WorkGroupConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe WorkGroupConfiguration
configuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders CreateWorkGroup where
  toHeaders :: CreateWorkGroup -> 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.CreateWorkGroup" ::
                          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 CreateWorkGroup where
  toJSON :: CreateWorkGroup -> Value
toJSON CreateWorkGroup' {Maybe [Tag]
Maybe Text
Maybe WorkGroupConfiguration
Text
name :: Text
tags :: Maybe [Tag]
description :: Maybe Text
configuration :: Maybe WorkGroupConfiguration
$sel:name:CreateWorkGroup' :: CreateWorkGroup -> Text
$sel:tags:CreateWorkGroup' :: CreateWorkGroup -> Maybe [Tag]
$sel:description:CreateWorkGroup' :: CreateWorkGroup -> Maybe Text
$sel:configuration:CreateWorkGroup' :: CreateWorkGroup -> Maybe WorkGroupConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Configuration" 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 WorkGroupConfiguration
configuration,
            (Key
"Description" 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
description,
            (Key
"Tags" 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 [Tag]
tags,
            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 CreateWorkGroup where
  toPath :: CreateWorkGroup -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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