{-# 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.Wisdom.NotifyRecommendationsReceived
-- 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 the specified recommendations from the specified assistant\'s
-- queue of newly available recommendations. You can use this API in
-- conjunction with
-- <https://docs.aws.amazon.com/wisdom/latest/APIReference/API_GetRecommendations.html GetRecommendations>
-- and a @waitTimeSeconds@ input for long-polling behavior and avoiding
-- duplicate recommendations.
module Amazonka.Wisdom.NotifyRecommendationsReceived
  ( -- * Creating a Request
    NotifyRecommendationsReceived (..),
    newNotifyRecommendationsReceived,

    -- * Request Lenses
    notifyRecommendationsReceived_assistantId,
    notifyRecommendationsReceived_recommendationIds,
    notifyRecommendationsReceived_sessionId,

    -- * Destructuring the Response
    NotifyRecommendationsReceivedResponse (..),
    newNotifyRecommendationsReceivedResponse,

    -- * Response Lenses
    notifyRecommendationsReceivedResponse_errors,
    notifyRecommendationsReceivedResponse_recommendationIds,
    notifyRecommendationsReceivedResponse_httpStatus,
  )
where

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
import Amazonka.Wisdom.Types

-- | /See:/ 'newNotifyRecommendationsReceived' smart constructor.
data NotifyRecommendationsReceived = NotifyRecommendationsReceived'
  { -- | The identifier of the Wisdom assistant. Can be either the ID or the ARN.
    -- URLs cannot contain the ARN.
    NotifyRecommendationsReceived -> Text
assistantId :: Prelude.Text,
    -- | The identifiers of the recommendations.
    NotifyRecommendationsReceived -> [Text]
recommendationIds :: [Prelude.Text],
    -- | The identifier of the session. Can be either the ID or the ARN. URLs
    -- cannot contain the ARN.
    NotifyRecommendationsReceived -> Text
sessionId :: Prelude.Text
  }
  deriving (NotifyRecommendationsReceived
-> NotifyRecommendationsReceived -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotifyRecommendationsReceived
-> NotifyRecommendationsReceived -> Bool
$c/= :: NotifyRecommendationsReceived
-> NotifyRecommendationsReceived -> Bool
== :: NotifyRecommendationsReceived
-> NotifyRecommendationsReceived -> Bool
$c== :: NotifyRecommendationsReceived
-> NotifyRecommendationsReceived -> Bool
Prelude.Eq, ReadPrec [NotifyRecommendationsReceived]
ReadPrec NotifyRecommendationsReceived
Int -> ReadS NotifyRecommendationsReceived
ReadS [NotifyRecommendationsReceived]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NotifyRecommendationsReceived]
$creadListPrec :: ReadPrec [NotifyRecommendationsReceived]
readPrec :: ReadPrec NotifyRecommendationsReceived
$creadPrec :: ReadPrec NotifyRecommendationsReceived
readList :: ReadS [NotifyRecommendationsReceived]
$creadList :: ReadS [NotifyRecommendationsReceived]
readsPrec :: Int -> ReadS NotifyRecommendationsReceived
$creadsPrec :: Int -> ReadS NotifyRecommendationsReceived
Prelude.Read, Int -> NotifyRecommendationsReceived -> ShowS
[NotifyRecommendationsReceived] -> ShowS
NotifyRecommendationsReceived -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotifyRecommendationsReceived] -> ShowS
$cshowList :: [NotifyRecommendationsReceived] -> ShowS
show :: NotifyRecommendationsReceived -> String
$cshow :: NotifyRecommendationsReceived -> String
showsPrec :: Int -> NotifyRecommendationsReceived -> ShowS
$cshowsPrec :: Int -> NotifyRecommendationsReceived -> ShowS
Prelude.Show, forall x.
Rep NotifyRecommendationsReceived x
-> NotifyRecommendationsReceived
forall x.
NotifyRecommendationsReceived
-> Rep NotifyRecommendationsReceived x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep NotifyRecommendationsReceived x
-> NotifyRecommendationsReceived
$cfrom :: forall x.
NotifyRecommendationsReceived
-> Rep NotifyRecommendationsReceived x
Prelude.Generic)

-- |
-- Create a value of 'NotifyRecommendationsReceived' 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:
--
-- 'assistantId', 'notifyRecommendationsReceived_assistantId' - The identifier of the Wisdom assistant. Can be either the ID or the ARN.
-- URLs cannot contain the ARN.
--
-- 'recommendationIds', 'notifyRecommendationsReceived_recommendationIds' - The identifiers of the recommendations.
--
-- 'sessionId', 'notifyRecommendationsReceived_sessionId' - The identifier of the session. Can be either the ID or the ARN. URLs
-- cannot contain the ARN.
newNotifyRecommendationsReceived ::
  -- | 'assistantId'
  Prelude.Text ->
  -- | 'sessionId'
  Prelude.Text ->
  NotifyRecommendationsReceived
newNotifyRecommendationsReceived :: Text -> Text -> NotifyRecommendationsReceived
newNotifyRecommendationsReceived
  Text
pAssistantId_
  Text
pSessionId_ =
    NotifyRecommendationsReceived'
      { $sel:assistantId:NotifyRecommendationsReceived' :: Text
assistantId =
          Text
pAssistantId_,
        $sel:recommendationIds:NotifyRecommendationsReceived' :: [Text]
recommendationIds = forall a. Monoid a => a
Prelude.mempty,
        $sel:sessionId:NotifyRecommendationsReceived' :: Text
sessionId = Text
pSessionId_
      }

-- | The identifier of the Wisdom assistant. Can be either the ID or the ARN.
-- URLs cannot contain the ARN.
notifyRecommendationsReceived_assistantId :: Lens.Lens' NotifyRecommendationsReceived Prelude.Text
notifyRecommendationsReceived_assistantId :: Lens' NotifyRecommendationsReceived Text
notifyRecommendationsReceived_assistantId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyRecommendationsReceived' {Text
assistantId :: Text
$sel:assistantId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
assistantId} -> Text
assistantId) (\s :: NotifyRecommendationsReceived
s@NotifyRecommendationsReceived' {} Text
a -> NotifyRecommendationsReceived
s {$sel:assistantId:NotifyRecommendationsReceived' :: Text
assistantId = Text
a} :: NotifyRecommendationsReceived)

-- | The identifiers of the recommendations.
notifyRecommendationsReceived_recommendationIds :: Lens.Lens' NotifyRecommendationsReceived [Prelude.Text]
notifyRecommendationsReceived_recommendationIds :: Lens' NotifyRecommendationsReceived [Text]
notifyRecommendationsReceived_recommendationIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyRecommendationsReceived' {[Text]
recommendationIds :: [Text]
$sel:recommendationIds:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> [Text]
recommendationIds} -> [Text]
recommendationIds) (\s :: NotifyRecommendationsReceived
s@NotifyRecommendationsReceived' {} [Text]
a -> NotifyRecommendationsReceived
s {$sel:recommendationIds:NotifyRecommendationsReceived' :: [Text]
recommendationIds = [Text]
a} :: NotifyRecommendationsReceived) 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

-- | The identifier of the session. Can be either the ID or the ARN. URLs
-- cannot contain the ARN.
notifyRecommendationsReceived_sessionId :: Lens.Lens' NotifyRecommendationsReceived Prelude.Text
notifyRecommendationsReceived_sessionId :: Lens' NotifyRecommendationsReceived Text
notifyRecommendationsReceived_sessionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyRecommendationsReceived' {Text
sessionId :: Text
$sel:sessionId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
sessionId} -> Text
sessionId) (\s :: NotifyRecommendationsReceived
s@NotifyRecommendationsReceived' {} Text
a -> NotifyRecommendationsReceived
s {$sel:sessionId:NotifyRecommendationsReceived' :: Text
sessionId = Text
a} :: NotifyRecommendationsReceived)

instance
  Core.AWSRequest
    NotifyRecommendationsReceived
  where
  type
    AWSResponse NotifyRecommendationsReceived =
      NotifyRecommendationsReceivedResponse
  request :: (Service -> Service)
-> NotifyRecommendationsReceived
-> Request NotifyRecommendationsReceived
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 NotifyRecommendationsReceived
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse NotifyRecommendationsReceived)))
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 [NotifyRecommendationsReceivedError]
-> Maybe [Text] -> Int -> NotifyRecommendationsReceivedResponse
NotifyRecommendationsReceivedResponse'
            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
"errors" 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.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"recommendationIds"
                            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
    NotifyRecommendationsReceived
  where
  hashWithSalt :: Int -> NotifyRecommendationsReceived -> Int
hashWithSalt Int
_salt NotifyRecommendationsReceived' {[Text]
Text
sessionId :: Text
recommendationIds :: [Text]
assistantId :: Text
$sel:sessionId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
$sel:recommendationIds:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> [Text]
$sel:assistantId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
assistantId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
recommendationIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sessionId

instance Prelude.NFData NotifyRecommendationsReceived where
  rnf :: NotifyRecommendationsReceived -> ()
rnf NotifyRecommendationsReceived' {[Text]
Text
sessionId :: Text
recommendationIds :: [Text]
assistantId :: Text
$sel:sessionId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
$sel:recommendationIds:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> [Text]
$sel:assistantId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
assistantId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
recommendationIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sessionId

instance Data.ToHeaders NotifyRecommendationsReceived where
  toHeaders :: NotifyRecommendationsReceived -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON NotifyRecommendationsReceived where
  toJSON :: NotifyRecommendationsReceived -> Value
toJSON NotifyRecommendationsReceived' {[Text]
Text
sessionId :: Text
recommendationIds :: [Text]
assistantId :: Text
$sel:sessionId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
$sel:recommendationIds:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> [Text]
$sel:assistantId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"recommendationIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
recommendationIds)
          ]
      )

instance Data.ToPath NotifyRecommendationsReceived where
  toPath :: NotifyRecommendationsReceived -> ByteString
toPath NotifyRecommendationsReceived' {[Text]
Text
sessionId :: Text
recommendationIds :: [Text]
assistantId :: Text
$sel:sessionId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
$sel:recommendationIds:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> [Text]
$sel:assistantId:NotifyRecommendationsReceived' :: NotifyRecommendationsReceived -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/assistants/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
assistantId,
        ByteString
"/sessions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
sessionId,
        ByteString
"/recommendations/notify"
      ]

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

-- | /See:/ 'newNotifyRecommendationsReceivedResponse' smart constructor.
data NotifyRecommendationsReceivedResponse = NotifyRecommendationsReceivedResponse'
  { -- | The identifiers of recommendations that are causing errors.
    NotifyRecommendationsReceivedResponse
-> Maybe [NotifyRecommendationsReceivedError]
errors :: Prelude.Maybe [NotifyRecommendationsReceivedError],
    -- | The identifiers of the recommendations.
    NotifyRecommendationsReceivedResponse -> Maybe [Text]
recommendationIds :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    NotifyRecommendationsReceivedResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (NotifyRecommendationsReceivedResponse
-> NotifyRecommendationsReceivedResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotifyRecommendationsReceivedResponse
-> NotifyRecommendationsReceivedResponse -> Bool
$c/= :: NotifyRecommendationsReceivedResponse
-> NotifyRecommendationsReceivedResponse -> Bool
== :: NotifyRecommendationsReceivedResponse
-> NotifyRecommendationsReceivedResponse -> Bool
$c== :: NotifyRecommendationsReceivedResponse
-> NotifyRecommendationsReceivedResponse -> Bool
Prelude.Eq, ReadPrec [NotifyRecommendationsReceivedResponse]
ReadPrec NotifyRecommendationsReceivedResponse
Int -> ReadS NotifyRecommendationsReceivedResponse
ReadS [NotifyRecommendationsReceivedResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NotifyRecommendationsReceivedResponse]
$creadListPrec :: ReadPrec [NotifyRecommendationsReceivedResponse]
readPrec :: ReadPrec NotifyRecommendationsReceivedResponse
$creadPrec :: ReadPrec NotifyRecommendationsReceivedResponse
readList :: ReadS [NotifyRecommendationsReceivedResponse]
$creadList :: ReadS [NotifyRecommendationsReceivedResponse]
readsPrec :: Int -> ReadS NotifyRecommendationsReceivedResponse
$creadsPrec :: Int -> ReadS NotifyRecommendationsReceivedResponse
Prelude.Read, Int -> NotifyRecommendationsReceivedResponse -> ShowS
[NotifyRecommendationsReceivedResponse] -> ShowS
NotifyRecommendationsReceivedResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotifyRecommendationsReceivedResponse] -> ShowS
$cshowList :: [NotifyRecommendationsReceivedResponse] -> ShowS
show :: NotifyRecommendationsReceivedResponse -> String
$cshow :: NotifyRecommendationsReceivedResponse -> String
showsPrec :: Int -> NotifyRecommendationsReceivedResponse -> ShowS
$cshowsPrec :: Int -> NotifyRecommendationsReceivedResponse -> ShowS
Prelude.Show, forall x.
Rep NotifyRecommendationsReceivedResponse x
-> NotifyRecommendationsReceivedResponse
forall x.
NotifyRecommendationsReceivedResponse
-> Rep NotifyRecommendationsReceivedResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep NotifyRecommendationsReceivedResponse x
-> NotifyRecommendationsReceivedResponse
$cfrom :: forall x.
NotifyRecommendationsReceivedResponse
-> Rep NotifyRecommendationsReceivedResponse x
Prelude.Generic)

-- |
-- Create a value of 'NotifyRecommendationsReceivedResponse' 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:
--
-- 'errors', 'notifyRecommendationsReceivedResponse_errors' - The identifiers of recommendations that are causing errors.
--
-- 'recommendationIds', 'notifyRecommendationsReceivedResponse_recommendationIds' - The identifiers of the recommendations.
--
-- 'httpStatus', 'notifyRecommendationsReceivedResponse_httpStatus' - The response's http status code.
newNotifyRecommendationsReceivedResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  NotifyRecommendationsReceivedResponse
newNotifyRecommendationsReceivedResponse :: Int -> NotifyRecommendationsReceivedResponse
newNotifyRecommendationsReceivedResponse Int
pHttpStatus_ =
  NotifyRecommendationsReceivedResponse'
    { $sel:errors:NotifyRecommendationsReceivedResponse' :: Maybe [NotifyRecommendationsReceivedError]
errors =
        forall a. Maybe a
Prelude.Nothing,
      $sel:recommendationIds:NotifyRecommendationsReceivedResponse' :: Maybe [Text]
recommendationIds = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:NotifyRecommendationsReceivedResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifiers of recommendations that are causing errors.
notifyRecommendationsReceivedResponse_errors :: Lens.Lens' NotifyRecommendationsReceivedResponse (Prelude.Maybe [NotifyRecommendationsReceivedError])
notifyRecommendationsReceivedResponse_errors :: Lens'
  NotifyRecommendationsReceivedResponse
  (Maybe [NotifyRecommendationsReceivedError])
notifyRecommendationsReceivedResponse_errors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyRecommendationsReceivedResponse' {Maybe [NotifyRecommendationsReceivedError]
errors :: Maybe [NotifyRecommendationsReceivedError]
$sel:errors:NotifyRecommendationsReceivedResponse' :: NotifyRecommendationsReceivedResponse
-> Maybe [NotifyRecommendationsReceivedError]
errors} -> Maybe [NotifyRecommendationsReceivedError]
errors) (\s :: NotifyRecommendationsReceivedResponse
s@NotifyRecommendationsReceivedResponse' {} Maybe [NotifyRecommendationsReceivedError]
a -> NotifyRecommendationsReceivedResponse
s {$sel:errors:NotifyRecommendationsReceivedResponse' :: Maybe [NotifyRecommendationsReceivedError]
errors = Maybe [NotifyRecommendationsReceivedError]
a} :: NotifyRecommendationsReceivedResponse) 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 identifiers of the recommendations.
notifyRecommendationsReceivedResponse_recommendationIds :: Lens.Lens' NotifyRecommendationsReceivedResponse (Prelude.Maybe [Prelude.Text])
notifyRecommendationsReceivedResponse_recommendationIds :: Lens' NotifyRecommendationsReceivedResponse (Maybe [Text])
notifyRecommendationsReceivedResponse_recommendationIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyRecommendationsReceivedResponse' {Maybe [Text]
recommendationIds :: Maybe [Text]
$sel:recommendationIds:NotifyRecommendationsReceivedResponse' :: NotifyRecommendationsReceivedResponse -> Maybe [Text]
recommendationIds} -> Maybe [Text]
recommendationIds) (\s :: NotifyRecommendationsReceivedResponse
s@NotifyRecommendationsReceivedResponse' {} Maybe [Text]
a -> NotifyRecommendationsReceivedResponse
s {$sel:recommendationIds:NotifyRecommendationsReceivedResponse' :: Maybe [Text]
recommendationIds = Maybe [Text]
a} :: NotifyRecommendationsReceivedResponse) 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.
notifyRecommendationsReceivedResponse_httpStatus :: Lens.Lens' NotifyRecommendationsReceivedResponse Prelude.Int
notifyRecommendationsReceivedResponse_httpStatus :: Lens' NotifyRecommendationsReceivedResponse Int
notifyRecommendationsReceivedResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyRecommendationsReceivedResponse' {Int
httpStatus :: Int
$sel:httpStatus:NotifyRecommendationsReceivedResponse' :: NotifyRecommendationsReceivedResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: NotifyRecommendationsReceivedResponse
s@NotifyRecommendationsReceivedResponse' {} Int
a -> NotifyRecommendationsReceivedResponse
s {$sel:httpStatus:NotifyRecommendationsReceivedResponse' :: Int
httpStatus = Int
a} :: NotifyRecommendationsReceivedResponse)

instance
  Prelude.NFData
    NotifyRecommendationsReceivedResponse
  where
  rnf :: NotifyRecommendationsReceivedResponse -> ()
rnf NotifyRecommendationsReceivedResponse' {Int
Maybe [Text]
Maybe [NotifyRecommendationsReceivedError]
httpStatus :: Int
recommendationIds :: Maybe [Text]
errors :: Maybe [NotifyRecommendationsReceivedError]
$sel:httpStatus:NotifyRecommendationsReceivedResponse' :: NotifyRecommendationsReceivedResponse -> Int
$sel:recommendationIds:NotifyRecommendationsReceivedResponse' :: NotifyRecommendationsReceivedResponse -> Maybe [Text]
$sel:errors:NotifyRecommendationsReceivedResponse' :: NotifyRecommendationsReceivedResponse
-> Maybe [NotifyRecommendationsReceivedError]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [NotifyRecommendationsReceivedError]
errors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
recommendationIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus