{-# 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.UntagProject
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes tags from a project.
module Amazonka.CodeStar.UntagProject
  ( -- * Creating a Request
    UntagProject (..),
    newUntagProject,

    -- * Request Lenses
    untagProject_id,
    untagProject_tags,

    -- * Destructuring the Response
    UntagProjectResponse (..),
    newUntagProjectResponse,

    -- * Response Lenses
    untagProjectResponse_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:/ 'newUntagProject' smart constructor.
data UntagProject = UntagProject'
  { -- | The ID of the project to remove tags from.
    UntagProject -> Text
id :: Prelude.Text,
    -- | The tags to remove from the project.
    UntagProject -> [Text]
tags :: [Prelude.Text]
  }
  deriving (UntagProject -> UntagProject -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UntagProject -> UntagProject -> Bool
$c/= :: UntagProject -> UntagProject -> Bool
== :: UntagProject -> UntagProject -> Bool
$c== :: UntagProject -> UntagProject -> Bool
Prelude.Eq, ReadPrec [UntagProject]
ReadPrec UntagProject
Int -> ReadS UntagProject
ReadS [UntagProject]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UntagProject]
$creadListPrec :: ReadPrec [UntagProject]
readPrec :: ReadPrec UntagProject
$creadPrec :: ReadPrec UntagProject
readList :: ReadS [UntagProject]
$creadList :: ReadS [UntagProject]
readsPrec :: Int -> ReadS UntagProject
$creadsPrec :: Int -> ReadS UntagProject
Prelude.Read, Int -> UntagProject -> ShowS
[UntagProject] -> ShowS
UntagProject -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UntagProject] -> ShowS
$cshowList :: [UntagProject] -> ShowS
show :: UntagProject -> String
$cshow :: UntagProject -> String
showsPrec :: Int -> UntagProject -> ShowS
$cshowsPrec :: Int -> UntagProject -> ShowS
Prelude.Show, forall x. Rep UntagProject x -> UntagProject
forall x. UntagProject -> Rep UntagProject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UntagProject x -> UntagProject
$cfrom :: forall x. UntagProject -> Rep UntagProject x
Prelude.Generic)

-- |
-- Create a value of 'UntagProject' 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', 'untagProject_id' - The ID of the project to remove tags from.
--
-- 'tags', 'untagProject_tags' - The tags to remove from the project.
newUntagProject ::
  -- | 'id'
  Prelude.Text ->
  UntagProject
newUntagProject :: Text -> UntagProject
newUntagProject Text
pId_ =
  UntagProject' {$sel:id:UntagProject' :: Text
id = Text
pId_, $sel:tags:UntagProject' :: [Text]
tags = forall a. Monoid a => a
Prelude.mempty}

-- | The ID of the project to remove tags from.
untagProject_id :: Lens.Lens' UntagProject Prelude.Text
untagProject_id :: Lens' UntagProject Text
untagProject_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UntagProject' {Text
id :: Text
$sel:id:UntagProject' :: UntagProject -> Text
id} -> Text
id) (\s :: UntagProject
s@UntagProject' {} Text
a -> UntagProject
s {$sel:id:UntagProject' :: Text
id = Text
a} :: UntagProject)

-- | The tags to remove from the project.
untagProject_tags :: Lens.Lens' UntagProject [Prelude.Text]
untagProject_tags :: Lens' UntagProject [Text]
untagProject_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UntagProject' {[Text]
tags :: [Text]
$sel:tags:UntagProject' :: UntagProject -> [Text]
tags} -> [Text]
tags) (\s :: UntagProject
s@UntagProject' {} [Text]
a -> UntagProject
s {$sel:tags:UntagProject' :: [Text]
tags = [Text]
a} :: UntagProject) 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 UntagProject where
  type AWSResponse UntagProject = UntagProjectResponse
  request :: (Service -> Service) -> UntagProject -> Request UntagProject
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 UntagProject
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UntagProject)))
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 -> UntagProjectResponse
UntagProjectResponse'
            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 UntagProject where
  hashWithSalt :: Int -> UntagProject -> Int
hashWithSalt Int
_salt UntagProject' {[Text]
Text
tags :: [Text]
id :: Text
$sel:tags:UntagProject' :: UntagProject -> [Text]
$sel:id:UntagProject' :: UntagProject -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
tags

instance Prelude.NFData UntagProject where
  rnf :: UntagProject -> ()
rnf UntagProject' {[Text]
Text
tags :: [Text]
id :: Text
$sel:tags:UntagProject' :: UntagProject -> [Text]
$sel:id:UntagProject' :: UntagProject -> 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 [Text]
tags

instance Data.ToHeaders UntagProject where
  toHeaders :: UntagProject -> 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.UntagProject" ::
                          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 UntagProject where
  toJSON :: UntagProject -> Value
toJSON UntagProject' {[Text]
Text
tags :: [Text]
id :: Text
$sel:tags:UntagProject' :: UntagProject -> [Text]
$sel:id:UntagProject' :: UntagProject -> 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..= [Text]
tags)
          ]
      )

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

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

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

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

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

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