{-# 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.CodeCommit.PostCommentReply
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Posts a comment in reply to an existing comment on a comparison between
-- commits or a pull request.
module Amazonka.CodeCommit.PostCommentReply
  ( -- * Creating a Request
    PostCommentReply (..),
    newPostCommentReply,

    -- * Request Lenses
    postCommentReply_clientRequestToken,
    postCommentReply_inReplyTo,
    postCommentReply_content,

    -- * Destructuring the Response
    PostCommentReplyResponse (..),
    newPostCommentReplyResponse,

    -- * Response Lenses
    postCommentReplyResponse_comment,
    postCommentReplyResponse_httpStatus,
  )
where

import Amazonka.CodeCommit.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:/ 'newPostCommentReply' smart constructor.
data PostCommentReply = PostCommentReply'
  { -- | A unique, client-generated idempotency token that, when provided in a
    -- request, ensures the request cannot be repeated with a changed
    -- parameter. If a request is received with the same parameters and a token
    -- is included, the request returns information about the initial request
    -- that used that token.
    PostCommentReply -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The system-generated ID of the comment to which you want to reply. To
    -- get this ID, use GetCommentsForComparedCommit or
    -- GetCommentsForPullRequest.
    PostCommentReply -> Text
inReplyTo :: Prelude.Text,
    -- | The contents of your reply to a comment.
    PostCommentReply -> Text
content :: Prelude.Text
  }
  deriving (PostCommentReply -> PostCommentReply -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCommentReply -> PostCommentReply -> Bool
$c/= :: PostCommentReply -> PostCommentReply -> Bool
== :: PostCommentReply -> PostCommentReply -> Bool
$c== :: PostCommentReply -> PostCommentReply -> Bool
Prelude.Eq, ReadPrec [PostCommentReply]
ReadPrec PostCommentReply
Int -> ReadS PostCommentReply
ReadS [PostCommentReply]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PostCommentReply]
$creadListPrec :: ReadPrec [PostCommentReply]
readPrec :: ReadPrec PostCommentReply
$creadPrec :: ReadPrec PostCommentReply
readList :: ReadS [PostCommentReply]
$creadList :: ReadS [PostCommentReply]
readsPrec :: Int -> ReadS PostCommentReply
$creadsPrec :: Int -> ReadS PostCommentReply
Prelude.Read, Int -> PostCommentReply -> ShowS
[PostCommentReply] -> ShowS
PostCommentReply -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCommentReply] -> ShowS
$cshowList :: [PostCommentReply] -> ShowS
show :: PostCommentReply -> String
$cshow :: PostCommentReply -> String
showsPrec :: Int -> PostCommentReply -> ShowS
$cshowsPrec :: Int -> PostCommentReply -> ShowS
Prelude.Show, forall x. Rep PostCommentReply x -> PostCommentReply
forall x. PostCommentReply -> Rep PostCommentReply x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PostCommentReply x -> PostCommentReply
$cfrom :: forall x. PostCommentReply -> Rep PostCommentReply x
Prelude.Generic)

-- |
-- Create a value of 'PostCommentReply' 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:
--
-- 'clientRequestToken', 'postCommentReply_clientRequestToken' - A unique, client-generated idempotency token that, when provided in a
-- request, ensures the request cannot be repeated with a changed
-- parameter. If a request is received with the same parameters and a token
-- is included, the request returns information about the initial request
-- that used that token.
--
-- 'inReplyTo', 'postCommentReply_inReplyTo' - The system-generated ID of the comment to which you want to reply. To
-- get this ID, use GetCommentsForComparedCommit or
-- GetCommentsForPullRequest.
--
-- 'content', 'postCommentReply_content' - The contents of your reply to a comment.
newPostCommentReply ::
  -- | 'inReplyTo'
  Prelude.Text ->
  -- | 'content'
  Prelude.Text ->
  PostCommentReply
newPostCommentReply :: Text -> Text -> PostCommentReply
newPostCommentReply Text
pInReplyTo_ Text
pContent_ =
  PostCommentReply'
    { $sel:clientRequestToken:PostCommentReply' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:inReplyTo:PostCommentReply' :: Text
inReplyTo = Text
pInReplyTo_,
      $sel:content:PostCommentReply' :: Text
content = Text
pContent_
    }

-- | A unique, client-generated idempotency token that, when provided in a
-- request, ensures the request cannot be repeated with a changed
-- parameter. If a request is received with the same parameters and a token
-- is included, the request returns information about the initial request
-- that used that token.
postCommentReply_clientRequestToken :: Lens.Lens' PostCommentReply (Prelude.Maybe Prelude.Text)
postCommentReply_clientRequestToken :: Lens' PostCommentReply (Maybe Text)
postCommentReply_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PostCommentReply' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:PostCommentReply' :: PostCommentReply -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: PostCommentReply
s@PostCommentReply' {} Maybe Text
a -> PostCommentReply
s {$sel:clientRequestToken:PostCommentReply' :: Maybe Text
clientRequestToken = Maybe Text
a} :: PostCommentReply)

-- | The system-generated ID of the comment to which you want to reply. To
-- get this ID, use GetCommentsForComparedCommit or
-- GetCommentsForPullRequest.
postCommentReply_inReplyTo :: Lens.Lens' PostCommentReply Prelude.Text
postCommentReply_inReplyTo :: Lens' PostCommentReply Text
postCommentReply_inReplyTo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PostCommentReply' {Text
inReplyTo :: Text
$sel:inReplyTo:PostCommentReply' :: PostCommentReply -> Text
inReplyTo} -> Text
inReplyTo) (\s :: PostCommentReply
s@PostCommentReply' {} Text
a -> PostCommentReply
s {$sel:inReplyTo:PostCommentReply' :: Text
inReplyTo = Text
a} :: PostCommentReply)

-- | The contents of your reply to a comment.
postCommentReply_content :: Lens.Lens' PostCommentReply Prelude.Text
postCommentReply_content :: Lens' PostCommentReply Text
postCommentReply_content = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PostCommentReply' {Text
content :: Text
$sel:content:PostCommentReply' :: PostCommentReply -> Text
content} -> Text
content) (\s :: PostCommentReply
s@PostCommentReply' {} Text
a -> PostCommentReply
s {$sel:content:PostCommentReply' :: Text
content = Text
a} :: PostCommentReply)

instance Core.AWSRequest PostCommentReply where
  type
    AWSResponse PostCommentReply =
      PostCommentReplyResponse
  request :: (Service -> Service)
-> PostCommentReply -> Request PostCommentReply
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 PostCommentReply
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PostCommentReply)))
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 Comment -> Int -> PostCommentReplyResponse
PostCommentReplyResponse'
            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
"comment")
            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 PostCommentReply where
  hashWithSalt :: Int -> PostCommentReply -> Int
hashWithSalt Int
_salt PostCommentReply' {Maybe Text
Text
content :: Text
inReplyTo :: Text
clientRequestToken :: Maybe Text
$sel:content:PostCommentReply' :: PostCommentReply -> Text
$sel:inReplyTo:PostCommentReply' :: PostCommentReply -> Text
$sel:clientRequestToken:PostCommentReply' :: PostCommentReply -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
inReplyTo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
content

instance Prelude.NFData PostCommentReply where
  rnf :: PostCommentReply -> ()
rnf PostCommentReply' {Maybe Text
Text
content :: Text
inReplyTo :: Text
clientRequestToken :: Maybe Text
$sel:content:PostCommentReply' :: PostCommentReply -> Text
$sel:inReplyTo:PostCommentReply' :: PostCommentReply -> Text
$sel:clientRequestToken:PostCommentReply' :: PostCommentReply -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
inReplyTo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
content

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

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

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

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

-- |
-- Create a value of 'PostCommentReplyResponse' 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:
--
-- 'comment', 'postCommentReplyResponse_comment' - Information about the reply to a comment.
--
-- 'httpStatus', 'postCommentReplyResponse_httpStatus' - The response's http status code.
newPostCommentReplyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PostCommentReplyResponse
newPostCommentReplyResponse :: Int -> PostCommentReplyResponse
newPostCommentReplyResponse Int
pHttpStatus_ =
  PostCommentReplyResponse'
    { $sel:comment:PostCommentReplyResponse' :: Maybe Comment
comment =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PostCommentReplyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the reply to a comment.
postCommentReplyResponse_comment :: Lens.Lens' PostCommentReplyResponse (Prelude.Maybe Comment)
postCommentReplyResponse_comment :: Lens' PostCommentReplyResponse (Maybe Comment)
postCommentReplyResponse_comment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PostCommentReplyResponse' {Maybe Comment
comment :: Maybe Comment
$sel:comment:PostCommentReplyResponse' :: PostCommentReplyResponse -> Maybe Comment
comment} -> Maybe Comment
comment) (\s :: PostCommentReplyResponse
s@PostCommentReplyResponse' {} Maybe Comment
a -> PostCommentReplyResponse
s {$sel:comment:PostCommentReplyResponse' :: Maybe Comment
comment = Maybe Comment
a} :: PostCommentReplyResponse)

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

instance Prelude.NFData PostCommentReplyResponse where
  rnf :: PostCommentReplyResponse -> ()
rnf PostCommentReplyResponse' {Int
Maybe Comment
httpStatus :: Int
comment :: Maybe Comment
$sel:httpStatus:PostCommentReplyResponse' :: PostCommentReplyResponse -> Int
$sel:comment:PostCommentReplyResponse' :: PostCommentReplyResponse -> Maybe Comment
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Comment
comment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus