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

    -- * Request Lenses
    updateProject_description,
    updateProject_name,
    updateProject_id,

    -- * Destructuring the Response
    UpdateProjectResponse (..),
    newUpdateProjectResponse,

    -- * Response Lenses
    updateProjectResponse_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:/ 'newUpdateProject' smart constructor.
data UpdateProject = UpdateProject'
  { -- | The description of the project, if any.
    UpdateProject -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The name of the project you want to update.
    UpdateProject -> Maybe (Sensitive Text)
name :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The ID of the project you want to update.
    UpdateProject -> Text
id :: Prelude.Text
  }
  deriving (UpdateProject -> UpdateProject -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateProject -> UpdateProject -> Bool
$c/= :: UpdateProject -> UpdateProject -> Bool
== :: UpdateProject -> UpdateProject -> Bool
$c== :: UpdateProject -> UpdateProject -> Bool
Prelude.Eq, Int -> UpdateProject -> ShowS
[UpdateProject] -> ShowS
UpdateProject -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateProject] -> ShowS
$cshowList :: [UpdateProject] -> ShowS
show :: UpdateProject -> String
$cshow :: UpdateProject -> String
showsPrec :: Int -> UpdateProject -> ShowS
$cshowsPrec :: Int -> UpdateProject -> ShowS
Prelude.Show, forall x. Rep UpdateProject x -> UpdateProject
forall x. UpdateProject -> Rep UpdateProject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateProject x -> UpdateProject
$cfrom :: forall x. UpdateProject -> Rep UpdateProject x
Prelude.Generic)

-- |
-- Create a value of 'UpdateProject' 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:
--
-- 'description', 'updateProject_description' - The description of the project, if any.
--
-- 'name', 'updateProject_name' - The name of the project you want to update.
--
-- 'id', 'updateProject_id' - The ID of the project you want to update.
newUpdateProject ::
  -- | 'id'
  Prelude.Text ->
  UpdateProject
newUpdateProject :: Text -> UpdateProject
newUpdateProject Text
pId_ =
  UpdateProject'
    { $sel:description:UpdateProject' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateProject' :: Maybe (Sensitive Text)
name = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateProject' :: Text
id = Text
pId_
    }

-- | The description of the project, if any.
updateProject_description :: Lens.Lens' UpdateProject (Prelude.Maybe Prelude.Text)
updateProject_description :: Lens' UpdateProject (Maybe Text)
updateProject_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:UpdateProject' :: UpdateProject -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: UpdateProject
s@UpdateProject' {} Maybe (Sensitive Text)
a -> UpdateProject
s {$sel:description:UpdateProject' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: UpdateProject) 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The name of the project you want to update.
updateProject_name :: Lens.Lens' UpdateProject (Prelude.Maybe Prelude.Text)
updateProject_name :: Lens' UpdateProject (Maybe Text)
updateProject_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Maybe (Sensitive Text)
name :: Maybe (Sensitive Text)
$sel:name:UpdateProject' :: UpdateProject -> Maybe (Sensitive Text)
name} -> Maybe (Sensitive Text)
name) (\s :: UpdateProject
s@UpdateProject' {} Maybe (Sensitive Text)
a -> UpdateProject
s {$sel:name:UpdateProject' :: Maybe (Sensitive Text)
name = Maybe (Sensitive Text)
a} :: UpdateProject) 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 a. Iso' (Sensitive a) a
Data._Sensitive

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

instance Core.AWSRequest UpdateProject where
  type
    AWSResponse UpdateProject =
      UpdateProjectResponse
  request :: (Service -> Service) -> UpdateProject -> Request UpdateProject
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 UpdateProject
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateProject)))
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 -> UpdateProjectResponse
UpdateProjectResponse'
            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 UpdateProject where
  hashWithSalt :: Int -> UpdateProject -> Int
hashWithSalt Int
_salt UpdateProject' {Maybe (Sensitive Text)
Text
id :: Text
name :: Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:id:UpdateProject' :: UpdateProject -> Text
$sel:name:UpdateProject' :: UpdateProject -> Maybe (Sensitive Text)
$sel:description:UpdateProject' :: UpdateProject -> Maybe (Sensitive Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData UpdateProject where
  rnf :: UpdateProject -> ()
rnf UpdateProject' {Maybe (Sensitive Text)
Text
id :: Text
name :: Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:id:UpdateProject' :: UpdateProject -> Text
$sel:name:UpdateProject' :: UpdateProject -> Maybe (Sensitive Text)
$sel:description:UpdateProject' :: UpdateProject -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

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

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

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

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

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

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

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