{-# 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.RunPipelineActivity
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Simulates the results of running a pipeline activity on a message
-- payload.
module Amazonka.IoTAnalytics.RunPipelineActivity
  ( -- * Creating a Request
    RunPipelineActivity (..),
    newRunPipelineActivity,

    -- * Request Lenses
    runPipelineActivity_pipelineActivity,
    runPipelineActivity_payloads,

    -- * Destructuring the Response
    RunPipelineActivityResponse (..),
    newRunPipelineActivityResponse,

    -- * Response Lenses
    runPipelineActivityResponse_logResult,
    runPipelineActivityResponse_payloads,
    runPipelineActivityResponse_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:/ 'newRunPipelineActivity' smart constructor.
data RunPipelineActivity = RunPipelineActivity'
  { -- | The pipeline activity that is run. This must not be a channel activity
    -- or a data store activity because these activities are used in a pipeline
    -- only to load the original message and to store the (possibly)
    -- transformed message. If a Lambda activity is specified, only
    -- short-running Lambda functions (those with a timeout of less than 30
    -- seconds or less) can be used.
    RunPipelineActivity -> PipelineActivity
pipelineActivity :: PipelineActivity,
    -- | The sample message payloads on which the pipeline activity is run.
    RunPipelineActivity -> NonEmpty Base64
payloads :: Prelude.NonEmpty Data.Base64
  }
  deriving (RunPipelineActivity -> RunPipelineActivity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RunPipelineActivity -> RunPipelineActivity -> Bool
$c/= :: RunPipelineActivity -> RunPipelineActivity -> Bool
== :: RunPipelineActivity -> RunPipelineActivity -> Bool
$c== :: RunPipelineActivity -> RunPipelineActivity -> Bool
Prelude.Eq, ReadPrec [RunPipelineActivity]
ReadPrec RunPipelineActivity
Int -> ReadS RunPipelineActivity
ReadS [RunPipelineActivity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RunPipelineActivity]
$creadListPrec :: ReadPrec [RunPipelineActivity]
readPrec :: ReadPrec RunPipelineActivity
$creadPrec :: ReadPrec RunPipelineActivity
readList :: ReadS [RunPipelineActivity]
$creadList :: ReadS [RunPipelineActivity]
readsPrec :: Int -> ReadS RunPipelineActivity
$creadsPrec :: Int -> ReadS RunPipelineActivity
Prelude.Read, Int -> RunPipelineActivity -> ShowS
[RunPipelineActivity] -> ShowS
RunPipelineActivity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RunPipelineActivity] -> ShowS
$cshowList :: [RunPipelineActivity] -> ShowS
show :: RunPipelineActivity -> String
$cshow :: RunPipelineActivity -> String
showsPrec :: Int -> RunPipelineActivity -> ShowS
$cshowsPrec :: Int -> RunPipelineActivity -> ShowS
Prelude.Show, forall x. Rep RunPipelineActivity x -> RunPipelineActivity
forall x. RunPipelineActivity -> Rep RunPipelineActivity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RunPipelineActivity x -> RunPipelineActivity
$cfrom :: forall x. RunPipelineActivity -> Rep RunPipelineActivity x
Prelude.Generic)

-- |
-- Create a value of 'RunPipelineActivity' 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:
--
-- 'pipelineActivity', 'runPipelineActivity_pipelineActivity' - The pipeline activity that is run. This must not be a channel activity
-- or a data store activity because these activities are used in a pipeline
-- only to load the original message and to store the (possibly)
-- transformed message. If a Lambda activity is specified, only
-- short-running Lambda functions (those with a timeout of less than 30
-- seconds or less) can be used.
--
-- 'payloads', 'runPipelineActivity_payloads' - The sample message payloads on which the pipeline activity is run.
newRunPipelineActivity ::
  -- | 'pipelineActivity'
  PipelineActivity ->
  -- | 'payloads'
  Prelude.NonEmpty Prelude.ByteString ->
  RunPipelineActivity
newRunPipelineActivity :: PipelineActivity -> NonEmpty ByteString -> RunPipelineActivity
newRunPipelineActivity PipelineActivity
pPipelineActivity_ NonEmpty ByteString
pPayloads_ =
  RunPipelineActivity'
    { $sel:pipelineActivity:RunPipelineActivity' :: PipelineActivity
pipelineActivity =
        PipelineActivity
pPipelineActivity_,
      $sel:payloads:RunPipelineActivity' :: NonEmpty Base64
payloads = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty ByteString
pPayloads_
    }

-- | The pipeline activity that is run. This must not be a channel activity
-- or a data store activity because these activities are used in a pipeline
-- only to load the original message and to store the (possibly)
-- transformed message. If a Lambda activity is specified, only
-- short-running Lambda functions (those with a timeout of less than 30
-- seconds or less) can be used.
runPipelineActivity_pipelineActivity :: Lens.Lens' RunPipelineActivity PipelineActivity
runPipelineActivity_pipelineActivity :: Lens' RunPipelineActivity PipelineActivity
runPipelineActivity_pipelineActivity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RunPipelineActivity' {PipelineActivity
pipelineActivity :: PipelineActivity
$sel:pipelineActivity:RunPipelineActivity' :: RunPipelineActivity -> PipelineActivity
pipelineActivity} -> PipelineActivity
pipelineActivity) (\s :: RunPipelineActivity
s@RunPipelineActivity' {} PipelineActivity
a -> RunPipelineActivity
s {$sel:pipelineActivity:RunPipelineActivity' :: PipelineActivity
pipelineActivity = PipelineActivity
a} :: RunPipelineActivity)

-- | The sample message payloads on which the pipeline activity is run.
runPipelineActivity_payloads :: Lens.Lens' RunPipelineActivity (Prelude.NonEmpty Prelude.ByteString)
runPipelineActivity_payloads :: Lens' RunPipelineActivity (NonEmpty ByteString)
runPipelineActivity_payloads = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RunPipelineActivity' {NonEmpty Base64
payloads :: NonEmpty Base64
$sel:payloads:RunPipelineActivity' :: RunPipelineActivity -> NonEmpty Base64
payloads} -> NonEmpty Base64
payloads) (\s :: RunPipelineActivity
s@RunPipelineActivity' {} NonEmpty Base64
a -> RunPipelineActivity
s {$sel:payloads:RunPipelineActivity' :: NonEmpty Base64
payloads = NonEmpty Base64
a} :: RunPipelineActivity) 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 Core.AWSRequest RunPipelineActivity where
  type
    AWSResponse RunPipelineActivity =
      RunPipelineActivityResponse
  request :: (Service -> Service)
-> RunPipelineActivity -> Request RunPipelineActivity
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 RunPipelineActivity
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RunPipelineActivity)))
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
-> Maybe (NonEmpty Base64) -> Int -> RunPipelineActivityResponse
RunPipelineActivityResponse'
            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
"logResult")
            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
"payloads")
            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 RunPipelineActivity where
  hashWithSalt :: Int -> RunPipelineActivity -> Int
hashWithSalt Int
_salt RunPipelineActivity' {NonEmpty Base64
PipelineActivity
payloads :: NonEmpty Base64
pipelineActivity :: PipelineActivity
$sel:payloads:RunPipelineActivity' :: RunPipelineActivity -> NonEmpty Base64
$sel:pipelineActivity:RunPipelineActivity' :: RunPipelineActivity -> PipelineActivity
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` PipelineActivity
pipelineActivity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Base64
payloads

instance Prelude.NFData RunPipelineActivity where
  rnf :: RunPipelineActivity -> ()
rnf RunPipelineActivity' {NonEmpty Base64
PipelineActivity
payloads :: NonEmpty Base64
pipelineActivity :: PipelineActivity
$sel:payloads:RunPipelineActivity' :: RunPipelineActivity -> NonEmpty Base64
$sel:pipelineActivity:RunPipelineActivity' :: RunPipelineActivity -> PipelineActivity
..} =
    forall a. NFData a => a -> ()
Prelude.rnf PipelineActivity
pipelineActivity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Base64
payloads

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

instance Data.ToJSON RunPipelineActivity where
  toJSON :: RunPipelineActivity -> Value
toJSON RunPipelineActivity' {NonEmpty Base64
PipelineActivity
payloads :: NonEmpty Base64
pipelineActivity :: PipelineActivity
$sel:payloads:RunPipelineActivity' :: RunPipelineActivity -> NonEmpty Base64
$sel:pipelineActivity:RunPipelineActivity' :: RunPipelineActivity -> PipelineActivity
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"pipelineActivity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= PipelineActivity
pipelineActivity),
            forall a. a -> Maybe a
Prelude.Just (Key
"payloads" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Base64
payloads)
          ]
      )

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

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

-- | /See:/ 'newRunPipelineActivityResponse' smart constructor.
data RunPipelineActivityResponse = RunPipelineActivityResponse'
  { -- | In case the pipeline activity fails, the log message that is generated.
    RunPipelineActivityResponse -> Maybe Text
logResult :: Prelude.Maybe Prelude.Text,
    -- | The enriched or transformed sample message payloads as base64-encoded
    -- strings. (The results of running the pipeline activity on each input
    -- sample message payload, encoded in base64.)
    RunPipelineActivityResponse -> Maybe (NonEmpty Base64)
payloads :: Prelude.Maybe (Prelude.NonEmpty Data.Base64),
    -- | The response's http status code.
    RunPipelineActivityResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RunPipelineActivityResponse -> RunPipelineActivityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RunPipelineActivityResponse -> RunPipelineActivityResponse -> Bool
$c/= :: RunPipelineActivityResponse -> RunPipelineActivityResponse -> Bool
== :: RunPipelineActivityResponse -> RunPipelineActivityResponse -> Bool
$c== :: RunPipelineActivityResponse -> RunPipelineActivityResponse -> Bool
Prelude.Eq, ReadPrec [RunPipelineActivityResponse]
ReadPrec RunPipelineActivityResponse
Int -> ReadS RunPipelineActivityResponse
ReadS [RunPipelineActivityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RunPipelineActivityResponse]
$creadListPrec :: ReadPrec [RunPipelineActivityResponse]
readPrec :: ReadPrec RunPipelineActivityResponse
$creadPrec :: ReadPrec RunPipelineActivityResponse
readList :: ReadS [RunPipelineActivityResponse]
$creadList :: ReadS [RunPipelineActivityResponse]
readsPrec :: Int -> ReadS RunPipelineActivityResponse
$creadsPrec :: Int -> ReadS RunPipelineActivityResponse
Prelude.Read, Int -> RunPipelineActivityResponse -> ShowS
[RunPipelineActivityResponse] -> ShowS
RunPipelineActivityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RunPipelineActivityResponse] -> ShowS
$cshowList :: [RunPipelineActivityResponse] -> ShowS
show :: RunPipelineActivityResponse -> String
$cshow :: RunPipelineActivityResponse -> String
showsPrec :: Int -> RunPipelineActivityResponse -> ShowS
$cshowsPrec :: Int -> RunPipelineActivityResponse -> ShowS
Prelude.Show, forall x.
Rep RunPipelineActivityResponse x -> RunPipelineActivityResponse
forall x.
RunPipelineActivityResponse -> Rep RunPipelineActivityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RunPipelineActivityResponse x -> RunPipelineActivityResponse
$cfrom :: forall x.
RunPipelineActivityResponse -> Rep RunPipelineActivityResponse x
Prelude.Generic)

-- |
-- Create a value of 'RunPipelineActivityResponse' 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:
--
-- 'logResult', 'runPipelineActivityResponse_logResult' - In case the pipeline activity fails, the log message that is generated.
--
-- 'payloads', 'runPipelineActivityResponse_payloads' - The enriched or transformed sample message payloads as base64-encoded
-- strings. (The results of running the pipeline activity on each input
-- sample message payload, encoded in base64.)
--
-- 'httpStatus', 'runPipelineActivityResponse_httpStatus' - The response's http status code.
newRunPipelineActivityResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RunPipelineActivityResponse
newRunPipelineActivityResponse :: Int -> RunPipelineActivityResponse
newRunPipelineActivityResponse Int
pHttpStatus_ =
  RunPipelineActivityResponse'
    { $sel:logResult:RunPipelineActivityResponse' :: Maybe Text
logResult =
        forall a. Maybe a
Prelude.Nothing,
      $sel:payloads:RunPipelineActivityResponse' :: Maybe (NonEmpty Base64)
payloads = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RunPipelineActivityResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | In case the pipeline activity fails, the log message that is generated.
runPipelineActivityResponse_logResult :: Lens.Lens' RunPipelineActivityResponse (Prelude.Maybe Prelude.Text)
runPipelineActivityResponse_logResult :: Lens' RunPipelineActivityResponse (Maybe Text)
runPipelineActivityResponse_logResult = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RunPipelineActivityResponse' {Maybe Text
logResult :: Maybe Text
$sel:logResult:RunPipelineActivityResponse' :: RunPipelineActivityResponse -> Maybe Text
logResult} -> Maybe Text
logResult) (\s :: RunPipelineActivityResponse
s@RunPipelineActivityResponse' {} Maybe Text
a -> RunPipelineActivityResponse
s {$sel:logResult:RunPipelineActivityResponse' :: Maybe Text
logResult = Maybe Text
a} :: RunPipelineActivityResponse)

-- | The enriched or transformed sample message payloads as base64-encoded
-- strings. (The results of running the pipeline activity on each input
-- sample message payload, encoded in base64.)
runPipelineActivityResponse_payloads :: Lens.Lens' RunPipelineActivityResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.ByteString))
runPipelineActivityResponse_payloads :: Lens' RunPipelineActivityResponse (Maybe (NonEmpty ByteString))
runPipelineActivityResponse_payloads = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RunPipelineActivityResponse' {Maybe (NonEmpty Base64)
payloads :: Maybe (NonEmpty Base64)
$sel:payloads:RunPipelineActivityResponse' :: RunPipelineActivityResponse -> Maybe (NonEmpty Base64)
payloads} -> Maybe (NonEmpty Base64)
payloads) (\s :: RunPipelineActivityResponse
s@RunPipelineActivityResponse' {} Maybe (NonEmpty Base64)
a -> RunPipelineActivityResponse
s {$sel:payloads:RunPipelineActivityResponse' :: Maybe (NonEmpty Base64)
payloads = Maybe (NonEmpty Base64)
a} :: RunPipelineActivityResponse) 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.
runPipelineActivityResponse_httpStatus :: Lens.Lens' RunPipelineActivityResponse Prelude.Int
runPipelineActivityResponse_httpStatus :: Lens' RunPipelineActivityResponse Int
runPipelineActivityResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RunPipelineActivityResponse' {Int
httpStatus :: Int
$sel:httpStatus:RunPipelineActivityResponse' :: RunPipelineActivityResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: RunPipelineActivityResponse
s@RunPipelineActivityResponse' {} Int
a -> RunPipelineActivityResponse
s {$sel:httpStatus:RunPipelineActivityResponse' :: Int
httpStatus = Int
a} :: RunPipelineActivityResponse)

instance Prelude.NFData RunPipelineActivityResponse where
  rnf :: RunPipelineActivityResponse -> ()
rnf RunPipelineActivityResponse' {Int
Maybe (NonEmpty Base64)
Maybe Text
httpStatus :: Int
payloads :: Maybe (NonEmpty Base64)
logResult :: Maybe Text
$sel:httpStatus:RunPipelineActivityResponse' :: RunPipelineActivityResponse -> Int
$sel:payloads:RunPipelineActivityResponse' :: RunPipelineActivityResponse -> Maybe (NonEmpty Base64)
$sel:logResult:RunPipelineActivityResponse' :: RunPipelineActivityResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logResult
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Base64)
payloads
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus