{-# 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.GetCommentReactions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about reactions to a specified comment ID. Reactions
-- from users who have been deleted will not be included in the count.
module Amazonka.CodeCommit.GetCommentReactions
  ( -- * Creating a Request
    GetCommentReactions (..),
    newGetCommentReactions,

    -- * Request Lenses
    getCommentReactions_maxResults,
    getCommentReactions_nextToken,
    getCommentReactions_reactionUserArn,
    getCommentReactions_commentId,

    -- * Destructuring the Response
    GetCommentReactionsResponse (..),
    newGetCommentReactionsResponse,

    -- * Response Lenses
    getCommentReactionsResponse_nextToken,
    getCommentReactionsResponse_httpStatus,
    getCommentReactionsResponse_reactionsForComment,
  )
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:/ 'newGetCommentReactions' smart constructor.
data GetCommentReactions = GetCommentReactions'
  { -- | A non-zero, non-negative integer used to limit the number of returned
    -- results. The default is the same as the allowed maximum, 1,000.
    GetCommentReactions -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | An enumeration token that, when provided in a request, returns the next
    -- batch of the results.
    GetCommentReactions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Optional. The Amazon Resource Name (ARN) of the user or identity for
    -- which you want to get reaction information.
    GetCommentReactions -> Maybe Text
reactionUserArn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the comment for which you want to get reactions information.
    GetCommentReactions -> Text
commentId :: Prelude.Text
  }
  deriving (GetCommentReactions -> GetCommentReactions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCommentReactions -> GetCommentReactions -> Bool
$c/= :: GetCommentReactions -> GetCommentReactions -> Bool
== :: GetCommentReactions -> GetCommentReactions -> Bool
$c== :: GetCommentReactions -> GetCommentReactions -> Bool
Prelude.Eq, ReadPrec [GetCommentReactions]
ReadPrec GetCommentReactions
Int -> ReadS GetCommentReactions
ReadS [GetCommentReactions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCommentReactions]
$creadListPrec :: ReadPrec [GetCommentReactions]
readPrec :: ReadPrec GetCommentReactions
$creadPrec :: ReadPrec GetCommentReactions
readList :: ReadS [GetCommentReactions]
$creadList :: ReadS [GetCommentReactions]
readsPrec :: Int -> ReadS GetCommentReactions
$creadsPrec :: Int -> ReadS GetCommentReactions
Prelude.Read, Int -> GetCommentReactions -> ShowS
[GetCommentReactions] -> ShowS
GetCommentReactions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCommentReactions] -> ShowS
$cshowList :: [GetCommentReactions] -> ShowS
show :: GetCommentReactions -> String
$cshow :: GetCommentReactions -> String
showsPrec :: Int -> GetCommentReactions -> ShowS
$cshowsPrec :: Int -> GetCommentReactions -> ShowS
Prelude.Show, forall x. Rep GetCommentReactions x -> GetCommentReactions
forall x. GetCommentReactions -> Rep GetCommentReactions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCommentReactions x -> GetCommentReactions
$cfrom :: forall x. GetCommentReactions -> Rep GetCommentReactions x
Prelude.Generic)

-- |
-- Create a value of 'GetCommentReactions' 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:
--
-- 'maxResults', 'getCommentReactions_maxResults' - A non-zero, non-negative integer used to limit the number of returned
-- results. The default is the same as the allowed maximum, 1,000.
--
-- 'nextToken', 'getCommentReactions_nextToken' - An enumeration token that, when provided in a request, returns the next
-- batch of the results.
--
-- 'reactionUserArn', 'getCommentReactions_reactionUserArn' - Optional. The Amazon Resource Name (ARN) of the user or identity for
-- which you want to get reaction information.
--
-- 'commentId', 'getCommentReactions_commentId' - The ID of the comment for which you want to get reactions information.
newGetCommentReactions ::
  -- | 'commentId'
  Prelude.Text ->
  GetCommentReactions
newGetCommentReactions :: Text -> GetCommentReactions
newGetCommentReactions Text
pCommentId_ =
  GetCommentReactions'
    { $sel:maxResults:GetCommentReactions' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetCommentReactions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:reactionUserArn:GetCommentReactions' :: Maybe Text
reactionUserArn = forall a. Maybe a
Prelude.Nothing,
      $sel:commentId:GetCommentReactions' :: Text
commentId = Text
pCommentId_
    }

-- | A non-zero, non-negative integer used to limit the number of returned
-- results. The default is the same as the allowed maximum, 1,000.
getCommentReactions_maxResults :: Lens.Lens' GetCommentReactions (Prelude.Maybe Prelude.Int)
getCommentReactions_maxResults :: Lens' GetCommentReactions (Maybe Int)
getCommentReactions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommentReactions' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:GetCommentReactions' :: GetCommentReactions -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: GetCommentReactions
s@GetCommentReactions' {} Maybe Int
a -> GetCommentReactions
s {$sel:maxResults:GetCommentReactions' :: Maybe Int
maxResults = Maybe Int
a} :: GetCommentReactions)

-- | An enumeration token that, when provided in a request, returns the next
-- batch of the results.
getCommentReactions_nextToken :: Lens.Lens' GetCommentReactions (Prelude.Maybe Prelude.Text)
getCommentReactions_nextToken :: Lens' GetCommentReactions (Maybe Text)
getCommentReactions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommentReactions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetCommentReactions' :: GetCommentReactions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetCommentReactions
s@GetCommentReactions' {} Maybe Text
a -> GetCommentReactions
s {$sel:nextToken:GetCommentReactions' :: Maybe Text
nextToken = Maybe Text
a} :: GetCommentReactions)

-- | Optional. The Amazon Resource Name (ARN) of the user or identity for
-- which you want to get reaction information.
getCommentReactions_reactionUserArn :: Lens.Lens' GetCommentReactions (Prelude.Maybe Prelude.Text)
getCommentReactions_reactionUserArn :: Lens' GetCommentReactions (Maybe Text)
getCommentReactions_reactionUserArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommentReactions' {Maybe Text
reactionUserArn :: Maybe Text
$sel:reactionUserArn:GetCommentReactions' :: GetCommentReactions -> Maybe Text
reactionUserArn} -> Maybe Text
reactionUserArn) (\s :: GetCommentReactions
s@GetCommentReactions' {} Maybe Text
a -> GetCommentReactions
s {$sel:reactionUserArn:GetCommentReactions' :: Maybe Text
reactionUserArn = Maybe Text
a} :: GetCommentReactions)

-- | The ID of the comment for which you want to get reactions information.
getCommentReactions_commentId :: Lens.Lens' GetCommentReactions Prelude.Text
getCommentReactions_commentId :: Lens' GetCommentReactions Text
getCommentReactions_commentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommentReactions' {Text
commentId :: Text
$sel:commentId:GetCommentReactions' :: GetCommentReactions -> Text
commentId} -> Text
commentId) (\s :: GetCommentReactions
s@GetCommentReactions' {} Text
a -> GetCommentReactions
s {$sel:commentId:GetCommentReactions' :: Text
commentId = Text
a} :: GetCommentReactions)

instance Core.AWSRequest GetCommentReactions where
  type
    AWSResponse GetCommentReactions =
      GetCommentReactionsResponse
  request :: (Service -> Service)
-> GetCommentReactions -> Request GetCommentReactions
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 GetCommentReactions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetCommentReactions)))
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 Text
-> Int -> [ReactionForComment] -> GetCommentReactionsResponse
GetCommentReactionsResponse'
            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
"nextToken")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"reactionsForComment"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable GetCommentReactions where
  hashWithSalt :: Int -> GetCommentReactions -> Int
hashWithSalt Int
_salt GetCommentReactions' {Maybe Int
Maybe Text
Text
commentId :: Text
reactionUserArn :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:commentId:GetCommentReactions' :: GetCommentReactions -> Text
$sel:reactionUserArn:GetCommentReactions' :: GetCommentReactions -> Maybe Text
$sel:nextToken:GetCommentReactions' :: GetCommentReactions -> Maybe Text
$sel:maxResults:GetCommentReactions' :: GetCommentReactions -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reactionUserArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
commentId

instance Prelude.NFData GetCommentReactions where
  rnf :: GetCommentReactions -> ()
rnf GetCommentReactions' {Maybe Int
Maybe Text
Text
commentId :: Text
reactionUserArn :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:commentId:GetCommentReactions' :: GetCommentReactions -> Text
$sel:reactionUserArn:GetCommentReactions' :: GetCommentReactions -> Maybe Text
$sel:nextToken:GetCommentReactions' :: GetCommentReactions -> Maybe Text
$sel:maxResults:GetCommentReactions' :: GetCommentReactions -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reactionUserArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
commentId

instance Data.ToHeaders GetCommentReactions where
  toHeaders :: GetCommentReactions -> 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.GetCommentReactions" ::
                          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 GetCommentReactions where
  toJSON :: GetCommentReactions -> Value
toJSON GetCommentReactions' {Maybe Int
Maybe Text
Text
commentId :: Text
reactionUserArn :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:commentId:GetCommentReactions' :: GetCommentReactions -> Text
$sel:reactionUserArn:GetCommentReactions' :: GetCommentReactions -> Maybe Text
$sel:nextToken:GetCommentReactions' :: GetCommentReactions -> Maybe Text
$sel:maxResults:GetCommentReactions' :: GetCommentReactions -> Maybe Int
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"maxResults" 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 Int
maxResults,
            (Key
"nextToken" 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
nextToken,
            (Key
"reactionUserArn" 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
reactionUserArn,
            forall a. a -> Maybe a
Prelude.Just (Key
"commentId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
commentId)
          ]
      )

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

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

-- | /See:/ 'newGetCommentReactionsResponse' smart constructor.
data GetCommentReactionsResponse = GetCommentReactionsResponse'
  { -- | An enumeration token that can be used in a request to return the next
    -- batch of the results.
    GetCommentReactionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetCommentReactionsResponse -> Int
httpStatus :: Prelude.Int,
    -- | An array of reactions to the specified comment.
    GetCommentReactionsResponse -> [ReactionForComment]
reactionsForComment :: [ReactionForComment]
  }
  deriving (GetCommentReactionsResponse -> GetCommentReactionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCommentReactionsResponse -> GetCommentReactionsResponse -> Bool
$c/= :: GetCommentReactionsResponse -> GetCommentReactionsResponse -> Bool
== :: GetCommentReactionsResponse -> GetCommentReactionsResponse -> Bool
$c== :: GetCommentReactionsResponse -> GetCommentReactionsResponse -> Bool
Prelude.Eq, ReadPrec [GetCommentReactionsResponse]
ReadPrec GetCommentReactionsResponse
Int -> ReadS GetCommentReactionsResponse
ReadS [GetCommentReactionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCommentReactionsResponse]
$creadListPrec :: ReadPrec [GetCommentReactionsResponse]
readPrec :: ReadPrec GetCommentReactionsResponse
$creadPrec :: ReadPrec GetCommentReactionsResponse
readList :: ReadS [GetCommentReactionsResponse]
$creadList :: ReadS [GetCommentReactionsResponse]
readsPrec :: Int -> ReadS GetCommentReactionsResponse
$creadsPrec :: Int -> ReadS GetCommentReactionsResponse
Prelude.Read, Int -> GetCommentReactionsResponse -> ShowS
[GetCommentReactionsResponse] -> ShowS
GetCommentReactionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCommentReactionsResponse] -> ShowS
$cshowList :: [GetCommentReactionsResponse] -> ShowS
show :: GetCommentReactionsResponse -> String
$cshow :: GetCommentReactionsResponse -> String
showsPrec :: Int -> GetCommentReactionsResponse -> ShowS
$cshowsPrec :: Int -> GetCommentReactionsResponse -> ShowS
Prelude.Show, forall x.
Rep GetCommentReactionsResponse x -> GetCommentReactionsResponse
forall x.
GetCommentReactionsResponse -> Rep GetCommentReactionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCommentReactionsResponse x -> GetCommentReactionsResponse
$cfrom :: forall x.
GetCommentReactionsResponse -> Rep GetCommentReactionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCommentReactionsResponse' 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:
--
-- 'nextToken', 'getCommentReactionsResponse_nextToken' - An enumeration token that can be used in a request to return the next
-- batch of the results.
--
-- 'httpStatus', 'getCommentReactionsResponse_httpStatus' - The response's http status code.
--
-- 'reactionsForComment', 'getCommentReactionsResponse_reactionsForComment' - An array of reactions to the specified comment.
newGetCommentReactionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCommentReactionsResponse
newGetCommentReactionsResponse :: Int -> GetCommentReactionsResponse
newGetCommentReactionsResponse Int
pHttpStatus_ =
  GetCommentReactionsResponse'
    { $sel:nextToken:GetCommentReactionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCommentReactionsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:reactionsForComment:GetCommentReactionsResponse' :: [ReactionForComment]
reactionsForComment = forall a. Monoid a => a
Prelude.mempty
    }

-- | An enumeration token that can be used in a request to return the next
-- batch of the results.
getCommentReactionsResponse_nextToken :: Lens.Lens' GetCommentReactionsResponse (Prelude.Maybe Prelude.Text)
getCommentReactionsResponse_nextToken :: Lens' GetCommentReactionsResponse (Maybe Text)
getCommentReactionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommentReactionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetCommentReactionsResponse' :: GetCommentReactionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetCommentReactionsResponse
s@GetCommentReactionsResponse' {} Maybe Text
a -> GetCommentReactionsResponse
s {$sel:nextToken:GetCommentReactionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetCommentReactionsResponse)

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

-- | An array of reactions to the specified comment.
getCommentReactionsResponse_reactionsForComment :: Lens.Lens' GetCommentReactionsResponse [ReactionForComment]
getCommentReactionsResponse_reactionsForComment :: Lens' GetCommentReactionsResponse [ReactionForComment]
getCommentReactionsResponse_reactionsForComment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCommentReactionsResponse' {[ReactionForComment]
reactionsForComment :: [ReactionForComment]
$sel:reactionsForComment:GetCommentReactionsResponse' :: GetCommentReactionsResponse -> [ReactionForComment]
reactionsForComment} -> [ReactionForComment]
reactionsForComment) (\s :: GetCommentReactionsResponse
s@GetCommentReactionsResponse' {} [ReactionForComment]
a -> GetCommentReactionsResponse
s {$sel:reactionsForComment:GetCommentReactionsResponse' :: [ReactionForComment]
reactionsForComment = [ReactionForComment]
a} :: GetCommentReactionsResponse) 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 Prelude.NFData GetCommentReactionsResponse where
  rnf :: GetCommentReactionsResponse -> ()
rnf GetCommentReactionsResponse' {Int
[ReactionForComment]
Maybe Text
reactionsForComment :: [ReactionForComment]
httpStatus :: Int
nextToken :: Maybe Text
$sel:reactionsForComment:GetCommentReactionsResponse' :: GetCommentReactionsResponse -> [ReactionForComment]
$sel:httpStatus:GetCommentReactionsResponse' :: GetCommentReactionsResponse -> Int
$sel:nextToken:GetCommentReactionsResponse' :: GetCommentReactionsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [ReactionForComment]
reactionsForComment