{-# 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.CodeStar.TagProject
-- 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 tags to a project.
module Amazonka.CodeStar.TagProject
  ( -- * Creating a Request
    TagProject (..),
    newTagProject,

    -- * Request Lenses
    tagProject_id,
    tagProject_tags,

    -- * Destructuring the Response
    TagProjectResponse (..),
    newTagProjectResponse,

    -- * Response Lenses
    tagProjectResponse_tags,
    tagProjectResponse_httpStatus,
  )
where

import Amazonka.CodeStar.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:/ 'newTagProject' smart constructor.
data TagProject = TagProject'
  { -- | The ID of the project you want to add a tag to.
    TagProject -> Text
id :: Prelude.Text,
    -- | The tags you want to add to the project.
    TagProject -> HashMap Text Text
tags :: Prelude.HashMap Prelude.Text Prelude.Text
  }
  deriving (TagProject -> TagProject -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TagProject -> TagProject -> Bool
$c/= :: TagProject -> TagProject -> Bool
== :: TagProject -> TagProject -> Bool
$c== :: TagProject -> TagProject -> Bool
Prelude.Eq, ReadPrec [TagProject]
ReadPrec TagProject
Int -> ReadS TagProject
ReadS [TagProject]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TagProject]
$creadListPrec :: ReadPrec [TagProject]
readPrec :: ReadPrec TagProject
$creadPrec :: ReadPrec TagProject
readList :: ReadS [TagProject]
$creadList :: ReadS [TagProject]
readsPrec :: Int -> ReadS TagProject
$creadsPrec :: Int -> ReadS TagProject
Prelude.Read, Int -> TagProject -> ShowS
[TagProject] -> ShowS
TagProject -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagProject] -> ShowS
$cshowList :: [TagProject] -> ShowS
show :: TagProject -> String
$cshow :: TagProject -> String
showsPrec :: Int -> TagProject -> ShowS
$cshowsPrec :: Int -> TagProject -> ShowS
Prelude.Show, forall x. Rep TagProject x -> TagProject
forall x. TagProject -> Rep TagProject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TagProject x -> TagProject
$cfrom :: forall x. TagProject -> Rep TagProject x
Prelude.Generic)

-- |
-- Create a value of 'TagProject' 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:
--
-- 'id', 'tagProject_id' - The ID of the project you want to add a tag to.
--
-- 'tags', 'tagProject_tags' - The tags you want to add to the project.
newTagProject ::
  -- | 'id'
  Prelude.Text ->
  TagProject
newTagProject :: Text -> TagProject
newTagProject Text
pId_ =
  TagProject' {$sel:id:TagProject' :: Text
id = Text
pId_, $sel:tags:TagProject' :: HashMap Text Text
tags = forall a. Monoid a => a
Prelude.mempty}

-- | The ID of the project you want to add a tag to.
tagProject_id :: Lens.Lens' TagProject Prelude.Text
tagProject_id :: Lens' TagProject Text
tagProject_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagProject' {Text
id :: Text
$sel:id:TagProject' :: TagProject -> Text
id} -> Text
id) (\s :: TagProject
s@TagProject' {} Text
a -> TagProject
s {$sel:id:TagProject' :: Text
id = Text
a} :: TagProject)

-- | The tags you want to add to the project.
tagProject_tags :: Lens.Lens' TagProject (Prelude.HashMap Prelude.Text Prelude.Text)
tagProject_tags :: Lens' TagProject (HashMap Text Text)
tagProject_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagProject' {HashMap Text Text
tags :: HashMap Text Text
$sel:tags:TagProject' :: TagProject -> HashMap Text Text
tags} -> HashMap Text Text
tags) (\s :: TagProject
s@TagProject' {} HashMap Text Text
a -> TagProject
s {$sel:tags:TagProject' :: HashMap Text Text
tags = HashMap Text Text
a} :: TagProject) 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 TagProject where
  type AWSResponse TagProject = TagProjectResponse
  request :: (Service -> Service) -> TagProject -> Request TagProject
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 TagProject
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse TagProject)))
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 (HashMap Text Text) -> Int -> TagProjectResponse
TagProjectResponse'
            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
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 TagProject where
  hashWithSalt :: Int -> TagProject -> Int
hashWithSalt Int
_salt TagProject' {Text
HashMap Text Text
tags :: HashMap Text Text
id :: Text
$sel:tags:TagProject' :: TagProject -> HashMap Text Text
$sel:id:TagProject' :: TagProject -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HashMap Text Text
tags

instance Prelude.NFData TagProject where
  rnf :: TagProject -> ()
rnf TagProject' {Text
HashMap Text Text
tags :: HashMap Text Text
id :: Text
$sel:tags:TagProject' :: TagProject -> HashMap Text Text
$sel:id:TagProject' :: TagProject -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
id seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HashMap Text Text
tags

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

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

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

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

-- |
-- Create a value of 'TagProjectResponse' 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:
--
-- 'tags', 'tagProjectResponse_tags' - The tags for the project.
--
-- 'httpStatus', 'tagProjectResponse_httpStatus' - The response's http status code.
newTagProjectResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  TagProjectResponse
newTagProjectResponse :: Int -> TagProjectResponse
newTagProjectResponse Int
pHttpStatus_ =
  TagProjectResponse'
    { $sel:tags:TagProjectResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:TagProjectResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The tags for the project.
tagProjectResponse_tags :: Lens.Lens' TagProjectResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
tagProjectResponse_tags :: Lens' TagProjectResponse (Maybe (HashMap Text Text))
tagProjectResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagProjectResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:TagProjectResponse' :: TagProjectResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: TagProjectResponse
s@TagProjectResponse' {} Maybe (HashMap Text Text)
a -> TagProjectResponse
s {$sel:tags:TagProjectResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: TagProjectResponse) 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 response's http status code.
tagProjectResponse_httpStatus :: Lens.Lens' TagProjectResponse Prelude.Int
tagProjectResponse_httpStatus :: Lens' TagProjectResponse Int
tagProjectResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagProjectResponse' {Int
httpStatus :: Int
$sel:httpStatus:TagProjectResponse' :: TagProjectResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: TagProjectResponse
s@TagProjectResponse' {} Int
a -> TagProjectResponse
s {$sel:httpStatus:TagProjectResponse' :: Int
httpStatus = Int
a} :: TagProjectResponse)

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