{-# 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.WorkSpaces.CreateTags
-- 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 the specified tags for the specified WorkSpaces resource.
module Amazonka.WorkSpaces.CreateTags
  ( -- * Creating a Request
    CreateTags (..),
    newCreateTags,

    -- * Request Lenses
    createTags_resourceId,
    createTags_tags,

    -- * Destructuring the Response
    CreateTagsResponse (..),
    newCreateTagsResponse,

    -- * Response Lenses
    createTagsResponse_httpStatus,
  )
where

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
import Amazonka.WorkSpaces.Types

-- | /See:/ 'newCreateTags' smart constructor.
data CreateTags = CreateTags'
  { -- | The identifier of the WorkSpaces resource. The supported resource types
    -- are WorkSpaces, registered directories, images, custom bundles, IP
    -- access control groups, and connection aliases.
    CreateTags -> Text
resourceId :: Prelude.Text,
    -- | The tags. Each WorkSpaces resource can have a maximum of 50 tags.
    CreateTags -> [Tag]
tags :: [Tag]
  }
  deriving (CreateTags -> CreateTags -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateTags -> CreateTags -> Bool
$c/= :: CreateTags -> CreateTags -> Bool
== :: CreateTags -> CreateTags -> Bool
$c== :: CreateTags -> CreateTags -> Bool
Prelude.Eq, ReadPrec [CreateTags]
ReadPrec CreateTags
Int -> ReadS CreateTags
ReadS [CreateTags]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateTags]
$creadListPrec :: ReadPrec [CreateTags]
readPrec :: ReadPrec CreateTags
$creadPrec :: ReadPrec CreateTags
readList :: ReadS [CreateTags]
$creadList :: ReadS [CreateTags]
readsPrec :: Int -> ReadS CreateTags
$creadsPrec :: Int -> ReadS CreateTags
Prelude.Read, Int -> CreateTags -> ShowS
[CreateTags] -> ShowS
CreateTags -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateTags] -> ShowS
$cshowList :: [CreateTags] -> ShowS
show :: CreateTags -> String
$cshow :: CreateTags -> String
showsPrec :: Int -> CreateTags -> ShowS
$cshowsPrec :: Int -> CreateTags -> ShowS
Prelude.Show, forall x. Rep CreateTags x -> CreateTags
forall x. CreateTags -> Rep CreateTags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateTags x -> CreateTags
$cfrom :: forall x. CreateTags -> Rep CreateTags x
Prelude.Generic)

-- |
-- Create a value of 'CreateTags' 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:
--
-- 'resourceId', 'createTags_resourceId' - The identifier of the WorkSpaces resource. The supported resource types
-- are WorkSpaces, registered directories, images, custom bundles, IP
-- access control groups, and connection aliases.
--
-- 'tags', 'createTags_tags' - The tags. Each WorkSpaces resource can have a maximum of 50 tags.
newCreateTags ::
  -- | 'resourceId'
  Prelude.Text ->
  CreateTags
newCreateTags :: Text -> CreateTags
newCreateTags Text
pResourceId_ =
  CreateTags'
    { $sel:resourceId:CreateTags' :: Text
resourceId = Text
pResourceId_,
      $sel:tags:CreateTags' :: [Tag]
tags = forall a. Monoid a => a
Prelude.mempty
    }

-- | The identifier of the WorkSpaces resource. The supported resource types
-- are WorkSpaces, registered directories, images, custom bundles, IP
-- access control groups, and connection aliases.
createTags_resourceId :: Lens.Lens' CreateTags Prelude.Text
createTags_resourceId :: Lens' CreateTags Text
createTags_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTags' {Text
resourceId :: Text
$sel:resourceId:CreateTags' :: CreateTags -> Text
resourceId} -> Text
resourceId) (\s :: CreateTags
s@CreateTags' {} Text
a -> CreateTags
s {$sel:resourceId:CreateTags' :: Text
resourceId = Text
a} :: CreateTags)

-- | The tags. Each WorkSpaces resource can have a maximum of 50 tags.
createTags_tags :: Lens.Lens' CreateTags [Tag]
createTags_tags :: Lens' CreateTags [Tag]
createTags_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTags' {[Tag]
tags :: [Tag]
$sel:tags:CreateTags' :: CreateTags -> [Tag]
tags} -> [Tag]
tags) (\s :: CreateTags
s@CreateTags' {} [Tag]
a -> CreateTags
s {$sel:tags:CreateTags' :: [Tag]
tags = [Tag]
a} :: CreateTags) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData CreateTags where
  rnf :: CreateTags -> ()
rnf CreateTags' {[Tag]
Text
tags :: [Tag]
resourceId :: Text
$sel:tags:CreateTags' :: CreateTags -> [Tag]
$sel:resourceId:CreateTags' :: CreateTags -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
resourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Tag]
tags

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

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

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

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

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

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

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