{-# 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.AppFlow.StartFlow
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Activates an existing flow. For on-demand flows, this operation runs the
-- flow immediately. For schedule and event-triggered flows, this operation
-- activates the flow.
module Amazonka.AppFlow.StartFlow
  ( -- * Creating a Request
    StartFlow (..),
    newStartFlow,

    -- * Request Lenses
    startFlow_flowName,

    -- * Destructuring the Response
    StartFlowResponse (..),
    newStartFlowResponse,

    -- * Response Lenses
    startFlowResponse_executionId,
    startFlowResponse_flowArn,
    startFlowResponse_flowStatus,
    startFlowResponse_httpStatus,
  )
where

import Amazonka.AppFlow.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:/ 'newStartFlow' smart constructor.
data StartFlow = StartFlow'
  { -- | The specified name of the flow. Spaces are not allowed. Use underscores
    -- (_) or hyphens (-) only.
    StartFlow -> Text
flowName :: Prelude.Text
  }
  deriving (StartFlow -> StartFlow -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartFlow -> StartFlow -> Bool
$c/= :: StartFlow -> StartFlow -> Bool
== :: StartFlow -> StartFlow -> Bool
$c== :: StartFlow -> StartFlow -> Bool
Prelude.Eq, ReadPrec [StartFlow]
ReadPrec StartFlow
Int -> ReadS StartFlow
ReadS [StartFlow]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartFlow]
$creadListPrec :: ReadPrec [StartFlow]
readPrec :: ReadPrec StartFlow
$creadPrec :: ReadPrec StartFlow
readList :: ReadS [StartFlow]
$creadList :: ReadS [StartFlow]
readsPrec :: Int -> ReadS StartFlow
$creadsPrec :: Int -> ReadS StartFlow
Prelude.Read, Int -> StartFlow -> ShowS
[StartFlow] -> ShowS
StartFlow -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartFlow] -> ShowS
$cshowList :: [StartFlow] -> ShowS
show :: StartFlow -> String
$cshow :: StartFlow -> String
showsPrec :: Int -> StartFlow -> ShowS
$cshowsPrec :: Int -> StartFlow -> ShowS
Prelude.Show, forall x. Rep StartFlow x -> StartFlow
forall x. StartFlow -> Rep StartFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartFlow x -> StartFlow
$cfrom :: forall x. StartFlow -> Rep StartFlow x
Prelude.Generic)

-- |
-- Create a value of 'StartFlow' 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:
--
-- 'flowName', 'startFlow_flowName' - The specified name of the flow. Spaces are not allowed. Use underscores
-- (_) or hyphens (-) only.
newStartFlow ::
  -- | 'flowName'
  Prelude.Text ->
  StartFlow
newStartFlow :: Text -> StartFlow
newStartFlow Text
pFlowName_ =
  StartFlow' {$sel:flowName:StartFlow' :: Text
flowName = Text
pFlowName_}

-- | The specified name of the flow. Spaces are not allowed. Use underscores
-- (_) or hyphens (-) only.
startFlow_flowName :: Lens.Lens' StartFlow Prelude.Text
startFlow_flowName :: Lens' StartFlow Text
startFlow_flowName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFlow' {Text
flowName :: Text
$sel:flowName:StartFlow' :: StartFlow -> Text
flowName} -> Text
flowName) (\s :: StartFlow
s@StartFlow' {} Text
a -> StartFlow
s {$sel:flowName:StartFlow' :: Text
flowName = Text
a} :: StartFlow)

instance Core.AWSRequest StartFlow where
  type AWSResponse StartFlow = StartFlowResponse
  request :: (Service -> Service) -> StartFlow -> Request StartFlow
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 StartFlow
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartFlow)))
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 Text -> Maybe FlowStatus -> Int -> StartFlowResponse
StartFlowResponse'
            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
"executionId")
            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
"flowArn")
            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
"flowStatus")
            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 StartFlow where
  hashWithSalt :: Int -> StartFlow -> Int
hashWithSalt Int
_salt StartFlow' {Text
flowName :: Text
$sel:flowName:StartFlow' :: StartFlow -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
flowName

instance Prelude.NFData StartFlow where
  rnf :: StartFlow -> ()
rnf StartFlow' {Text
flowName :: Text
$sel:flowName:StartFlow' :: StartFlow -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
flowName

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

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

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

-- | /See:/ 'newStartFlowResponse' smart constructor.
data StartFlowResponse = StartFlowResponse'
  { -- | Returns the internal execution ID of an on-demand flow when the flow is
    -- started. For scheduled or event-triggered flows, this value is null.
    StartFlowResponse -> Maybe Text
executionId :: Prelude.Maybe Prelude.Text,
    -- | The flow\'s Amazon Resource Name (ARN).
    StartFlowResponse -> Maybe Text
flowArn :: Prelude.Maybe Prelude.Text,
    -- | Indicates the current status of the flow.
    StartFlowResponse -> Maybe FlowStatus
flowStatus :: Prelude.Maybe FlowStatus,
    -- | The response's http status code.
    StartFlowResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartFlowResponse -> StartFlowResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartFlowResponse -> StartFlowResponse -> Bool
$c/= :: StartFlowResponse -> StartFlowResponse -> Bool
== :: StartFlowResponse -> StartFlowResponse -> Bool
$c== :: StartFlowResponse -> StartFlowResponse -> Bool
Prelude.Eq, ReadPrec [StartFlowResponse]
ReadPrec StartFlowResponse
Int -> ReadS StartFlowResponse
ReadS [StartFlowResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartFlowResponse]
$creadListPrec :: ReadPrec [StartFlowResponse]
readPrec :: ReadPrec StartFlowResponse
$creadPrec :: ReadPrec StartFlowResponse
readList :: ReadS [StartFlowResponse]
$creadList :: ReadS [StartFlowResponse]
readsPrec :: Int -> ReadS StartFlowResponse
$creadsPrec :: Int -> ReadS StartFlowResponse
Prelude.Read, Int -> StartFlowResponse -> ShowS
[StartFlowResponse] -> ShowS
StartFlowResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartFlowResponse] -> ShowS
$cshowList :: [StartFlowResponse] -> ShowS
show :: StartFlowResponse -> String
$cshow :: StartFlowResponse -> String
showsPrec :: Int -> StartFlowResponse -> ShowS
$cshowsPrec :: Int -> StartFlowResponse -> ShowS
Prelude.Show, forall x. Rep StartFlowResponse x -> StartFlowResponse
forall x. StartFlowResponse -> Rep StartFlowResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartFlowResponse x -> StartFlowResponse
$cfrom :: forall x. StartFlowResponse -> Rep StartFlowResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartFlowResponse' 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:
--
-- 'executionId', 'startFlowResponse_executionId' - Returns the internal execution ID of an on-demand flow when the flow is
-- started. For scheduled or event-triggered flows, this value is null.
--
-- 'flowArn', 'startFlowResponse_flowArn' - The flow\'s Amazon Resource Name (ARN).
--
-- 'flowStatus', 'startFlowResponse_flowStatus' - Indicates the current status of the flow.
--
-- 'httpStatus', 'startFlowResponse_httpStatus' - The response's http status code.
newStartFlowResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartFlowResponse
newStartFlowResponse :: Int -> StartFlowResponse
newStartFlowResponse Int
pHttpStatus_ =
  StartFlowResponse'
    { $sel:executionId:StartFlowResponse' :: Maybe Text
executionId = forall a. Maybe a
Prelude.Nothing,
      $sel:flowArn:StartFlowResponse' :: Maybe Text
flowArn = forall a. Maybe a
Prelude.Nothing,
      $sel:flowStatus:StartFlowResponse' :: Maybe FlowStatus
flowStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartFlowResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns the internal execution ID of an on-demand flow when the flow is
-- started. For scheduled or event-triggered flows, this value is null.
startFlowResponse_executionId :: Lens.Lens' StartFlowResponse (Prelude.Maybe Prelude.Text)
startFlowResponse_executionId :: Lens' StartFlowResponse (Maybe Text)
startFlowResponse_executionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFlowResponse' {Maybe Text
executionId :: Maybe Text
$sel:executionId:StartFlowResponse' :: StartFlowResponse -> Maybe Text
executionId} -> Maybe Text
executionId) (\s :: StartFlowResponse
s@StartFlowResponse' {} Maybe Text
a -> StartFlowResponse
s {$sel:executionId:StartFlowResponse' :: Maybe Text
executionId = Maybe Text
a} :: StartFlowResponse)

-- | The flow\'s Amazon Resource Name (ARN).
startFlowResponse_flowArn :: Lens.Lens' StartFlowResponse (Prelude.Maybe Prelude.Text)
startFlowResponse_flowArn :: Lens' StartFlowResponse (Maybe Text)
startFlowResponse_flowArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFlowResponse' {Maybe Text
flowArn :: Maybe Text
$sel:flowArn:StartFlowResponse' :: StartFlowResponse -> Maybe Text
flowArn} -> Maybe Text
flowArn) (\s :: StartFlowResponse
s@StartFlowResponse' {} Maybe Text
a -> StartFlowResponse
s {$sel:flowArn:StartFlowResponse' :: Maybe Text
flowArn = Maybe Text
a} :: StartFlowResponse)

-- | Indicates the current status of the flow.
startFlowResponse_flowStatus :: Lens.Lens' StartFlowResponse (Prelude.Maybe FlowStatus)
startFlowResponse_flowStatus :: Lens' StartFlowResponse (Maybe FlowStatus)
startFlowResponse_flowStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFlowResponse' {Maybe FlowStatus
flowStatus :: Maybe FlowStatus
$sel:flowStatus:StartFlowResponse' :: StartFlowResponse -> Maybe FlowStatus
flowStatus} -> Maybe FlowStatus
flowStatus) (\s :: StartFlowResponse
s@StartFlowResponse' {} Maybe FlowStatus
a -> StartFlowResponse
s {$sel:flowStatus:StartFlowResponse' :: Maybe FlowStatus
flowStatus = Maybe FlowStatus
a} :: StartFlowResponse)

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

instance Prelude.NFData StartFlowResponse where
  rnf :: StartFlowResponse -> ()
rnf StartFlowResponse' {Int
Maybe Text
Maybe FlowStatus
httpStatus :: Int
flowStatus :: Maybe FlowStatus
flowArn :: Maybe Text
executionId :: Maybe Text
$sel:httpStatus:StartFlowResponse' :: StartFlowResponse -> Int
$sel:flowStatus:StartFlowResponse' :: StartFlowResponse -> Maybe FlowStatus
$sel:flowArn:StartFlowResponse' :: StartFlowResponse -> Maybe Text
$sel:executionId:StartFlowResponse' :: StartFlowResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
flowArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FlowStatus
flowStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus