{-# 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.IoTAnalytics.StartPipelineReprocessing
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts the reprocessing of raw message data through the pipeline.
module Amazonka.IoTAnalytics.StartPipelineReprocessing
  ( -- * Creating a Request
    StartPipelineReprocessing (..),
    newStartPipelineReprocessing,

    -- * Request Lenses
    startPipelineReprocessing_channelMessages,
    startPipelineReprocessing_endTime,
    startPipelineReprocessing_startTime,
    startPipelineReprocessing_pipelineName,

    -- * Destructuring the Response
    StartPipelineReprocessingResponse (..),
    newStartPipelineReprocessingResponse,

    -- * Response Lenses
    startPipelineReprocessingResponse_reprocessingId,
    startPipelineReprocessingResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoTAnalytics.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newStartPipelineReprocessing' smart constructor.
data StartPipelineReprocessing = StartPipelineReprocessing'
  { -- | Specifies one or more sets of channel messages that you want to
    -- reprocess.
    --
    -- If you use the @channelMessages@ object, you must not specify a value
    -- for @startTime@ and @endTime@.
    StartPipelineReprocessing -> Maybe ChannelMessages
channelMessages :: Prelude.Maybe ChannelMessages,
    -- | The end time (exclusive) of raw message data that is reprocessed.
    --
    -- If you specify a value for the @endTime@ parameter, you must not use the
    -- @channelMessages@ object.
    StartPipelineReprocessing -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | The start time (inclusive) of raw message data that is reprocessed.
    --
    -- If you specify a value for the @startTime@ parameter, you must not use
    -- the @channelMessages@ object.
    StartPipelineReprocessing -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the pipeline on which to start reprocessing.
    StartPipelineReprocessing -> Text
pipelineName :: Prelude.Text
  }
  deriving (StartPipelineReprocessing -> StartPipelineReprocessing -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartPipelineReprocessing -> StartPipelineReprocessing -> Bool
$c/= :: StartPipelineReprocessing -> StartPipelineReprocessing -> Bool
== :: StartPipelineReprocessing -> StartPipelineReprocessing -> Bool
$c== :: StartPipelineReprocessing -> StartPipelineReprocessing -> Bool
Prelude.Eq, ReadPrec [StartPipelineReprocessing]
ReadPrec StartPipelineReprocessing
Int -> ReadS StartPipelineReprocessing
ReadS [StartPipelineReprocessing]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartPipelineReprocessing]
$creadListPrec :: ReadPrec [StartPipelineReprocessing]
readPrec :: ReadPrec StartPipelineReprocessing
$creadPrec :: ReadPrec StartPipelineReprocessing
readList :: ReadS [StartPipelineReprocessing]
$creadList :: ReadS [StartPipelineReprocessing]
readsPrec :: Int -> ReadS StartPipelineReprocessing
$creadsPrec :: Int -> ReadS StartPipelineReprocessing
Prelude.Read, Int -> StartPipelineReprocessing -> ShowS
[StartPipelineReprocessing] -> ShowS
StartPipelineReprocessing -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartPipelineReprocessing] -> ShowS
$cshowList :: [StartPipelineReprocessing] -> ShowS
show :: StartPipelineReprocessing -> String
$cshow :: StartPipelineReprocessing -> String
showsPrec :: Int -> StartPipelineReprocessing -> ShowS
$cshowsPrec :: Int -> StartPipelineReprocessing -> ShowS
Prelude.Show, forall x.
Rep StartPipelineReprocessing x -> StartPipelineReprocessing
forall x.
StartPipelineReprocessing -> Rep StartPipelineReprocessing x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartPipelineReprocessing x -> StartPipelineReprocessing
$cfrom :: forall x.
StartPipelineReprocessing -> Rep StartPipelineReprocessing x
Prelude.Generic)

-- |
-- Create a value of 'StartPipelineReprocessing' 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:
--
-- 'channelMessages', 'startPipelineReprocessing_channelMessages' - Specifies one or more sets of channel messages that you want to
-- reprocess.
--
-- If you use the @channelMessages@ object, you must not specify a value
-- for @startTime@ and @endTime@.
--
-- 'endTime', 'startPipelineReprocessing_endTime' - The end time (exclusive) of raw message data that is reprocessed.
--
-- If you specify a value for the @endTime@ parameter, you must not use the
-- @channelMessages@ object.
--
-- 'startTime', 'startPipelineReprocessing_startTime' - The start time (inclusive) of raw message data that is reprocessed.
--
-- If you specify a value for the @startTime@ parameter, you must not use
-- the @channelMessages@ object.
--
-- 'pipelineName', 'startPipelineReprocessing_pipelineName' - The name of the pipeline on which to start reprocessing.
newStartPipelineReprocessing ::
  -- | 'pipelineName'
  Prelude.Text ->
  StartPipelineReprocessing
newStartPipelineReprocessing :: Text -> StartPipelineReprocessing
newStartPipelineReprocessing Text
pPipelineName_ =
  StartPipelineReprocessing'
    { $sel:channelMessages:StartPipelineReprocessing' :: Maybe ChannelMessages
channelMessages =
        forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:StartPipelineReprocessing' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:StartPipelineReprocessing' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelineName:StartPipelineReprocessing' :: Text
pipelineName = Text
pPipelineName_
    }

-- | Specifies one or more sets of channel messages that you want to
-- reprocess.
--
-- If you use the @channelMessages@ object, you must not specify a value
-- for @startTime@ and @endTime@.
startPipelineReprocessing_channelMessages :: Lens.Lens' StartPipelineReprocessing (Prelude.Maybe ChannelMessages)
startPipelineReprocessing_channelMessages :: Lens' StartPipelineReprocessing (Maybe ChannelMessages)
startPipelineReprocessing_channelMessages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartPipelineReprocessing' {Maybe ChannelMessages
channelMessages :: Maybe ChannelMessages
$sel:channelMessages:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe ChannelMessages
channelMessages} -> Maybe ChannelMessages
channelMessages) (\s :: StartPipelineReprocessing
s@StartPipelineReprocessing' {} Maybe ChannelMessages
a -> StartPipelineReprocessing
s {$sel:channelMessages:StartPipelineReprocessing' :: Maybe ChannelMessages
channelMessages = Maybe ChannelMessages
a} :: StartPipelineReprocessing)

-- | The end time (exclusive) of raw message data that is reprocessed.
--
-- If you specify a value for the @endTime@ parameter, you must not use the
-- @channelMessages@ object.
startPipelineReprocessing_endTime :: Lens.Lens' StartPipelineReprocessing (Prelude.Maybe Prelude.UTCTime)
startPipelineReprocessing_endTime :: Lens' StartPipelineReprocessing (Maybe UTCTime)
startPipelineReprocessing_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartPipelineReprocessing' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: StartPipelineReprocessing
s@StartPipelineReprocessing' {} Maybe POSIX
a -> StartPipelineReprocessing
s {$sel:endTime:StartPipelineReprocessing' :: Maybe POSIX
endTime = Maybe POSIX
a} :: StartPipelineReprocessing) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The start time (inclusive) of raw message data that is reprocessed.
--
-- If you specify a value for the @startTime@ parameter, you must not use
-- the @channelMessages@ object.
startPipelineReprocessing_startTime :: Lens.Lens' StartPipelineReprocessing (Prelude.Maybe Prelude.UTCTime)
startPipelineReprocessing_startTime :: Lens' StartPipelineReprocessing (Maybe UTCTime)
startPipelineReprocessing_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartPipelineReprocessing' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: StartPipelineReprocessing
s@StartPipelineReprocessing' {} Maybe POSIX
a -> StartPipelineReprocessing
s {$sel:startTime:StartPipelineReprocessing' :: Maybe POSIX
startTime = Maybe POSIX
a} :: StartPipelineReprocessing) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The name of the pipeline on which to start reprocessing.
startPipelineReprocessing_pipelineName :: Lens.Lens' StartPipelineReprocessing Prelude.Text
startPipelineReprocessing_pipelineName :: Lens' StartPipelineReprocessing Text
startPipelineReprocessing_pipelineName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartPipelineReprocessing' {Text
pipelineName :: Text
$sel:pipelineName:StartPipelineReprocessing' :: StartPipelineReprocessing -> Text
pipelineName} -> Text
pipelineName) (\s :: StartPipelineReprocessing
s@StartPipelineReprocessing' {} Text
a -> StartPipelineReprocessing
s {$sel:pipelineName:StartPipelineReprocessing' :: Text
pipelineName = Text
a} :: StartPipelineReprocessing)

instance Core.AWSRequest StartPipelineReprocessing where
  type
    AWSResponse StartPipelineReprocessing =
      StartPipelineReprocessingResponse
  request :: (Service -> Service)
-> StartPipelineReprocessing -> Request StartPipelineReprocessing
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 StartPipelineReprocessing
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartPipelineReprocessing)))
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 -> StartPipelineReprocessingResponse
StartPipelineReprocessingResponse'
            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
"reprocessingId")
            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 StartPipelineReprocessing where
  hashWithSalt :: Int -> StartPipelineReprocessing -> Int
hashWithSalt Int
_salt StartPipelineReprocessing' {Maybe POSIX
Maybe ChannelMessages
Text
pipelineName :: Text
startTime :: Maybe POSIX
endTime :: Maybe POSIX
channelMessages :: Maybe ChannelMessages
$sel:pipelineName:StartPipelineReprocessing' :: StartPipelineReprocessing -> Text
$sel:startTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
$sel:endTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
$sel:channelMessages:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe ChannelMessages
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChannelMessages
channelMessages
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pipelineName

instance Prelude.NFData StartPipelineReprocessing where
  rnf :: StartPipelineReprocessing -> ()
rnf StartPipelineReprocessing' {Maybe POSIX
Maybe ChannelMessages
Text
pipelineName :: Text
startTime :: Maybe POSIX
endTime :: Maybe POSIX
channelMessages :: Maybe ChannelMessages
$sel:pipelineName:StartPipelineReprocessing' :: StartPipelineReprocessing -> Text
$sel:startTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
$sel:endTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
$sel:channelMessages:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe ChannelMessages
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelMessages
channelMessages
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
pipelineName

instance Data.ToHeaders StartPipelineReprocessing where
  toHeaders :: StartPipelineReprocessing -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON StartPipelineReprocessing where
  toJSON :: StartPipelineReprocessing -> Value
toJSON StartPipelineReprocessing' {Maybe POSIX
Maybe ChannelMessages
Text
pipelineName :: Text
startTime :: Maybe POSIX
endTime :: Maybe POSIX
channelMessages :: Maybe ChannelMessages
$sel:pipelineName:StartPipelineReprocessing' :: StartPipelineReprocessing -> Text
$sel:startTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
$sel:endTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
$sel:channelMessages:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe ChannelMessages
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"channelMessages" 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 ChannelMessages
channelMessages,
            (Key
"endTime" 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 POSIX
endTime,
            (Key
"startTime" 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 POSIX
startTime
          ]
      )

instance Data.ToPath StartPipelineReprocessing where
  toPath :: StartPipelineReprocessing -> ByteString
toPath StartPipelineReprocessing' {Maybe POSIX
Maybe ChannelMessages
Text
pipelineName :: Text
startTime :: Maybe POSIX
endTime :: Maybe POSIX
channelMessages :: Maybe ChannelMessages
$sel:pipelineName:StartPipelineReprocessing' :: StartPipelineReprocessing -> Text
$sel:startTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
$sel:endTime:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe POSIX
$sel:channelMessages:StartPipelineReprocessing' :: StartPipelineReprocessing -> Maybe ChannelMessages
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/pipelines/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
pipelineName,
        ByteString
"/reprocessing"
      ]

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

-- | /See:/ 'newStartPipelineReprocessingResponse' smart constructor.
data StartPipelineReprocessingResponse = StartPipelineReprocessingResponse'
  { -- | The ID of the pipeline reprocessing activity that was started.
    StartPipelineReprocessingResponse -> Maybe Text
reprocessingId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartPipelineReprocessingResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartPipelineReprocessingResponse
-> StartPipelineReprocessingResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartPipelineReprocessingResponse
-> StartPipelineReprocessingResponse -> Bool
$c/= :: StartPipelineReprocessingResponse
-> StartPipelineReprocessingResponse -> Bool
== :: StartPipelineReprocessingResponse
-> StartPipelineReprocessingResponse -> Bool
$c== :: StartPipelineReprocessingResponse
-> StartPipelineReprocessingResponse -> Bool
Prelude.Eq, ReadPrec [StartPipelineReprocessingResponse]
ReadPrec StartPipelineReprocessingResponse
Int -> ReadS StartPipelineReprocessingResponse
ReadS [StartPipelineReprocessingResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartPipelineReprocessingResponse]
$creadListPrec :: ReadPrec [StartPipelineReprocessingResponse]
readPrec :: ReadPrec StartPipelineReprocessingResponse
$creadPrec :: ReadPrec StartPipelineReprocessingResponse
readList :: ReadS [StartPipelineReprocessingResponse]
$creadList :: ReadS [StartPipelineReprocessingResponse]
readsPrec :: Int -> ReadS StartPipelineReprocessingResponse
$creadsPrec :: Int -> ReadS StartPipelineReprocessingResponse
Prelude.Read, Int -> StartPipelineReprocessingResponse -> ShowS
[StartPipelineReprocessingResponse] -> ShowS
StartPipelineReprocessingResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartPipelineReprocessingResponse] -> ShowS
$cshowList :: [StartPipelineReprocessingResponse] -> ShowS
show :: StartPipelineReprocessingResponse -> String
$cshow :: StartPipelineReprocessingResponse -> String
showsPrec :: Int -> StartPipelineReprocessingResponse -> ShowS
$cshowsPrec :: Int -> StartPipelineReprocessingResponse -> ShowS
Prelude.Show, forall x.
Rep StartPipelineReprocessingResponse x
-> StartPipelineReprocessingResponse
forall x.
StartPipelineReprocessingResponse
-> Rep StartPipelineReprocessingResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartPipelineReprocessingResponse x
-> StartPipelineReprocessingResponse
$cfrom :: forall x.
StartPipelineReprocessingResponse
-> Rep StartPipelineReprocessingResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartPipelineReprocessingResponse' 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:
--
-- 'reprocessingId', 'startPipelineReprocessingResponse_reprocessingId' - The ID of the pipeline reprocessing activity that was started.
--
-- 'httpStatus', 'startPipelineReprocessingResponse_httpStatus' - The response's http status code.
newStartPipelineReprocessingResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartPipelineReprocessingResponse
newStartPipelineReprocessingResponse :: Int -> StartPipelineReprocessingResponse
newStartPipelineReprocessingResponse Int
pHttpStatus_ =
  StartPipelineReprocessingResponse'
    { $sel:reprocessingId:StartPipelineReprocessingResponse' :: Maybe Text
reprocessingId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartPipelineReprocessingResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the pipeline reprocessing activity that was started.
startPipelineReprocessingResponse_reprocessingId :: Lens.Lens' StartPipelineReprocessingResponse (Prelude.Maybe Prelude.Text)
startPipelineReprocessingResponse_reprocessingId :: Lens' StartPipelineReprocessingResponse (Maybe Text)
startPipelineReprocessingResponse_reprocessingId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartPipelineReprocessingResponse' {Maybe Text
reprocessingId :: Maybe Text
$sel:reprocessingId:StartPipelineReprocessingResponse' :: StartPipelineReprocessingResponse -> Maybe Text
reprocessingId} -> Maybe Text
reprocessingId) (\s :: StartPipelineReprocessingResponse
s@StartPipelineReprocessingResponse' {} Maybe Text
a -> StartPipelineReprocessingResponse
s {$sel:reprocessingId:StartPipelineReprocessingResponse' :: Maybe Text
reprocessingId = Maybe Text
a} :: StartPipelineReprocessingResponse)

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

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