{-# 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.EC2.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)
--
-- Adds or overwrites only the specified tags for the specified Amazon EC2
-- resource or resources. When you specify an existing tag key, the value
-- is overwritten with the new value. Each resource can have a maximum of
-- 50 tags. Each tag consists of a key and optional value. Tag keys must be
-- unique per resource.
--
-- For more information about tags, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Using_Tags.html Tag your Amazon EC2 resources>
-- in the /Amazon Elastic Compute Cloud User Guide/. For more information
-- about creating IAM policies that control users\' access to resources
-- based on tags, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ec2-supported-iam-actions-resources.html Supported resource-level permissions for Amazon EC2 API actions>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.CreateTags
  ( -- * Creating a Request
    CreateTags (..),
    newCreateTags,

    -- * Request Lenses
    createTags_dryRun,
    createTags_resources,
    createTags_tags,

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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateTags' smart constructor.
data CreateTags = CreateTags'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    CreateTags -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The IDs of the resources, separated by spaces.
    --
    -- Constraints: Up to 1000 resource IDs. We recommend breaking up this
    -- request into smaller batches.
    CreateTags -> [Text]
resources :: [Prelude.Text],
    -- | The tags. The @value@ parameter is required, but if you don\'t want the
    -- tag to have a value, specify the parameter with no value, and we set the
    -- value to an empty string.
    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:
--
-- 'dryRun', 'createTags_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'resources', 'createTags_resources' - The IDs of the resources, separated by spaces.
--
-- Constraints: Up to 1000 resource IDs. We recommend breaking up this
-- request into smaller batches.
--
-- 'tags', 'createTags_tags' - The tags. The @value@ parameter is required, but if you don\'t want the
-- tag to have a value, specify the parameter with no value, and we set the
-- value to an empty string.
newCreateTags ::
  CreateTags
newCreateTags :: CreateTags
newCreateTags =
  CreateTags'
    { $sel:dryRun:CreateTags' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:resources:CreateTags' :: [Text]
resources = forall a. Monoid a => a
Prelude.mempty,
      $sel:tags:CreateTags' :: [Tag]
tags = forall a. Monoid a => a
Prelude.mempty
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
createTags_dryRun :: Lens.Lens' CreateTags (Prelude.Maybe Prelude.Bool)
createTags_dryRun :: Lens' CreateTags (Maybe Bool)
createTags_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTags' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:CreateTags' :: CreateTags -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: CreateTags
s@CreateTags' {} Maybe Bool
a -> CreateTags
s {$sel:dryRun:CreateTags' :: Maybe Bool
dryRun = Maybe Bool
a} :: CreateTags)

-- | The IDs of the resources, separated by spaces.
--
-- Constraints: Up to 1000 resource IDs. We recommend breaking up this
-- request into smaller batches.
createTags_resources :: Lens.Lens' CreateTags [Prelude.Text]
createTags_resources :: Lens' CreateTags [Text]
createTags_resources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTags' {[Text]
resources :: [Text]
$sel:resources:CreateTags' :: CreateTags -> [Text]
resources} -> [Text]
resources) (\s :: CreateTags
s@CreateTags' {} [Text]
a -> CreateTags
s {$sel:resources:CreateTags' :: [Text]
resources = [Text]
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

-- | The tags. The @value@ parameter is required, but if you don\'t want the
-- tag to have a value, specify the parameter with no value, and we set the
-- value to an empty string.
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 => Service -> a -> Request a
Request.postQuery (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 =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull CreateTagsResponse
CreateTagsResponse'

instance Prelude.Hashable CreateTags where
  hashWithSalt :: Int -> CreateTags -> Int
hashWithSalt Int
_salt CreateTags' {[Text]
[Tag]
Maybe Bool
tags :: [Tag]
resources :: [Text]
dryRun :: Maybe Bool
$sel:tags:CreateTags' :: CreateTags -> [Tag]
$sel:resources:CreateTags' :: CreateTags -> [Text]
$sel:dryRun:CreateTags' :: CreateTags -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
resources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Tag]
tags

instance Prelude.NFData CreateTags where
  rnf :: CreateTags -> ()
rnf CreateTags' {[Text]
[Tag]
Maybe Bool
tags :: [Tag]
resources :: [Text]
dryRun :: Maybe Bool
$sel:tags:CreateTags' :: CreateTags -> [Tag]
$sel:resources:CreateTags' :: CreateTags -> [Text]
$sel:dryRun:CreateTags' :: CreateTags -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
resources
      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 -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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 CreateTags' {[Text]
[Tag]
Maybe Bool
tags :: [Tag]
resources :: [Text]
dryRun :: Maybe Bool
$sel:tags:CreateTags' :: CreateTags -> [Tag]
$sel:resources:CreateTags' :: CreateTags -> [Text]
$sel:dryRun:CreateTags' :: CreateTags -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateTags" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"ResourceId" [Text]
resources,
        forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Tag" [Tag]
tags
      ]

-- | /See:/ 'newCreateTagsResponse' smart constructor.
data CreateTagsResponse = CreateTagsResponse'
  {
  }
  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.
newCreateTagsResponse ::
  CreateTagsResponse
newCreateTagsResponse :: CreateTagsResponse
newCreateTagsResponse = CreateTagsResponse
CreateTagsResponse'

instance Prelude.NFData CreateTagsResponse where
  rnf :: CreateTagsResponse -> ()
rnf CreateTagsResponse
_ = ()