{-# 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.DataPipeline.ActivatePipeline
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Validates the specified pipeline and starts processing pipeline tasks.
-- If the pipeline does not pass validation, activation fails.
--
-- If you need to pause the pipeline to investigate an issue with a
-- component, such as a data source or script, call DeactivatePipeline.
--
-- To activate a finished pipeline, modify the end date for the pipeline
-- and then activate it.
module Amazonka.DataPipeline.ActivatePipeline
  ( -- * Creating a Request
    ActivatePipeline (..),
    newActivatePipeline,

    -- * Request Lenses
    activatePipeline_parameterValues,
    activatePipeline_startTimestamp,
    activatePipeline_pipelineId,

    -- * Destructuring the Response
    ActivatePipelineResponse (..),
    newActivatePipelineResponse,

    -- * Response Lenses
    activatePipelineResponse_httpStatus,
  )
where

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

-- | Contains the parameters for ActivatePipeline.
--
-- /See:/ 'newActivatePipeline' smart constructor.
data ActivatePipeline = ActivatePipeline'
  { -- | A list of parameter values to pass to the pipeline at activation.
    ActivatePipeline -> Maybe [ParameterValue]
parameterValues :: Prelude.Maybe [ParameterValue],
    -- | The date and time to resume the pipeline. By default, the pipeline
    -- resumes from the last completed execution.
    ActivatePipeline -> Maybe POSIX
startTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The ID of the pipeline.
    ActivatePipeline -> Text
pipelineId :: Prelude.Text
  }
  deriving (ActivatePipeline -> ActivatePipeline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActivatePipeline -> ActivatePipeline -> Bool
$c/= :: ActivatePipeline -> ActivatePipeline -> Bool
== :: ActivatePipeline -> ActivatePipeline -> Bool
$c== :: ActivatePipeline -> ActivatePipeline -> Bool
Prelude.Eq, ReadPrec [ActivatePipeline]
ReadPrec ActivatePipeline
Int -> ReadS ActivatePipeline
ReadS [ActivatePipeline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ActivatePipeline]
$creadListPrec :: ReadPrec [ActivatePipeline]
readPrec :: ReadPrec ActivatePipeline
$creadPrec :: ReadPrec ActivatePipeline
readList :: ReadS [ActivatePipeline]
$creadList :: ReadS [ActivatePipeline]
readsPrec :: Int -> ReadS ActivatePipeline
$creadsPrec :: Int -> ReadS ActivatePipeline
Prelude.Read, Int -> ActivatePipeline -> ShowS
[ActivatePipeline] -> ShowS
ActivatePipeline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActivatePipeline] -> ShowS
$cshowList :: [ActivatePipeline] -> ShowS
show :: ActivatePipeline -> String
$cshow :: ActivatePipeline -> String
showsPrec :: Int -> ActivatePipeline -> ShowS
$cshowsPrec :: Int -> ActivatePipeline -> ShowS
Prelude.Show, forall x. Rep ActivatePipeline x -> ActivatePipeline
forall x. ActivatePipeline -> Rep ActivatePipeline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ActivatePipeline x -> ActivatePipeline
$cfrom :: forall x. ActivatePipeline -> Rep ActivatePipeline x
Prelude.Generic)

-- |
-- Create a value of 'ActivatePipeline' 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:
--
-- 'parameterValues', 'activatePipeline_parameterValues' - A list of parameter values to pass to the pipeline at activation.
--
-- 'startTimestamp', 'activatePipeline_startTimestamp' - The date and time to resume the pipeline. By default, the pipeline
-- resumes from the last completed execution.
--
-- 'pipelineId', 'activatePipeline_pipelineId' - The ID of the pipeline.
newActivatePipeline ::
  -- | 'pipelineId'
  Prelude.Text ->
  ActivatePipeline
newActivatePipeline :: Text -> ActivatePipeline
newActivatePipeline Text
pPipelineId_ =
  ActivatePipeline'
    { $sel:parameterValues:ActivatePipeline' :: Maybe [ParameterValue]
parameterValues =
        forall a. Maybe a
Prelude.Nothing,
      $sel:startTimestamp:ActivatePipeline' :: Maybe POSIX
startTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelineId:ActivatePipeline' :: Text
pipelineId = Text
pPipelineId_
    }

-- | A list of parameter values to pass to the pipeline at activation.
activatePipeline_parameterValues :: Lens.Lens' ActivatePipeline (Prelude.Maybe [ParameterValue])
activatePipeline_parameterValues :: Lens' ActivatePipeline (Maybe [ParameterValue])
activatePipeline_parameterValues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActivatePipeline' {Maybe [ParameterValue]
parameterValues :: Maybe [ParameterValue]
$sel:parameterValues:ActivatePipeline' :: ActivatePipeline -> Maybe [ParameterValue]
parameterValues} -> Maybe [ParameterValue]
parameterValues) (\s :: ActivatePipeline
s@ActivatePipeline' {} Maybe [ParameterValue]
a -> ActivatePipeline
s {$sel:parameterValues:ActivatePipeline' :: Maybe [ParameterValue]
parameterValues = Maybe [ParameterValue]
a} :: ActivatePipeline) 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 date and time to resume the pipeline. By default, the pipeline
-- resumes from the last completed execution.
activatePipeline_startTimestamp :: Lens.Lens' ActivatePipeline (Prelude.Maybe Prelude.UTCTime)
activatePipeline_startTimestamp :: Lens' ActivatePipeline (Maybe UTCTime)
activatePipeline_startTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActivatePipeline' {Maybe POSIX
startTimestamp :: Maybe POSIX
$sel:startTimestamp:ActivatePipeline' :: ActivatePipeline -> Maybe POSIX
startTimestamp} -> Maybe POSIX
startTimestamp) (\s :: ActivatePipeline
s@ActivatePipeline' {} Maybe POSIX
a -> ActivatePipeline
s {$sel:startTimestamp:ActivatePipeline' :: Maybe POSIX
startTimestamp = Maybe POSIX
a} :: ActivatePipeline) 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 ID of the pipeline.
activatePipeline_pipelineId :: Lens.Lens' ActivatePipeline Prelude.Text
activatePipeline_pipelineId :: Lens' ActivatePipeline Text
activatePipeline_pipelineId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActivatePipeline' {Text
pipelineId :: Text
$sel:pipelineId:ActivatePipeline' :: ActivatePipeline -> Text
pipelineId} -> Text
pipelineId) (\s :: ActivatePipeline
s@ActivatePipeline' {} Text
a -> ActivatePipeline
s {$sel:pipelineId:ActivatePipeline' :: Text
pipelineId = Text
a} :: ActivatePipeline)

instance Core.AWSRequest ActivatePipeline where
  type
    AWSResponse ActivatePipeline =
      ActivatePipelineResponse
  request :: (Service -> Service)
-> ActivatePipeline -> Request ActivatePipeline
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 ActivatePipeline
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ActivatePipeline)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> ActivatePipelineResponse
ActivatePipelineResponse'
            forall (f :: * -> *) a b. Functor 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 ActivatePipeline where
  hashWithSalt :: Int -> ActivatePipeline -> Int
hashWithSalt Int
_salt ActivatePipeline' {Maybe [ParameterValue]
Maybe POSIX
Text
pipelineId :: Text
startTimestamp :: Maybe POSIX
parameterValues :: Maybe [ParameterValue]
$sel:pipelineId:ActivatePipeline' :: ActivatePipeline -> Text
$sel:startTimestamp:ActivatePipeline' :: ActivatePipeline -> Maybe POSIX
$sel:parameterValues:ActivatePipeline' :: ActivatePipeline -> Maybe [ParameterValue]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ParameterValue]
parameterValues
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pipelineId

instance Prelude.NFData ActivatePipeline where
  rnf :: ActivatePipeline -> ()
rnf ActivatePipeline' {Maybe [ParameterValue]
Maybe POSIX
Text
pipelineId :: Text
startTimestamp :: Maybe POSIX
parameterValues :: Maybe [ParameterValue]
$sel:pipelineId:ActivatePipeline' :: ActivatePipeline -> Text
$sel:startTimestamp:ActivatePipeline' :: ActivatePipeline -> Maybe POSIX
$sel:parameterValues:ActivatePipeline' :: ActivatePipeline -> Maybe [ParameterValue]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ParameterValue]
parameterValues
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
pipelineId

instance Data.ToHeaders ActivatePipeline where
  toHeaders :: ActivatePipeline -> 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
"DataPipeline.ActivatePipeline" ::
                          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 ActivatePipeline where
  toJSON :: ActivatePipeline -> Value
toJSON ActivatePipeline' {Maybe [ParameterValue]
Maybe POSIX
Text
pipelineId :: Text
startTimestamp :: Maybe POSIX
parameterValues :: Maybe [ParameterValue]
$sel:pipelineId:ActivatePipeline' :: ActivatePipeline -> Text
$sel:startTimestamp:ActivatePipeline' :: ActivatePipeline -> Maybe POSIX
$sel:parameterValues:ActivatePipeline' :: ActivatePipeline -> Maybe [ParameterValue]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"parameterValues" 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 [ParameterValue]
parameterValues,
            (Key
"startTimestamp" 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
startTimestamp,
            forall a. a -> Maybe a
Prelude.Just (Key
"pipelineId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
pipelineId)
          ]
      )

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

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

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

-- |
-- Create a value of 'ActivatePipelineResponse' 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:
--
-- 'httpStatus', 'activatePipelineResponse_httpStatus' - The response's http status code.
newActivatePipelineResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ActivatePipelineResponse
newActivatePipelineResponse :: Int -> ActivatePipelineResponse
newActivatePipelineResponse Int
pHttpStatus_ =
  ActivatePipelineResponse'
    { $sel:httpStatus:ActivatePipelineResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData ActivatePipelineResponse where
  rnf :: ActivatePipelineResponse -> ()
rnf ActivatePipelineResponse' {Int
httpStatus :: Int
$sel:httpStatus:ActivatePipelineResponse' :: ActivatePipelineResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus