{-# 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.Glue.StartWorkflowRun
-- 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 a new run of the specified workflow.
module Amazonka.Glue.StartWorkflowRun
  ( -- * Creating a Request
    StartWorkflowRun (..),
    newStartWorkflowRun,

    -- * Request Lenses
    startWorkflowRun_runProperties,
    startWorkflowRun_name,

    -- * Destructuring the Response
    StartWorkflowRunResponse (..),
    newStartWorkflowRunResponse,

    -- * Response Lenses
    startWorkflowRunResponse_runId,
    startWorkflowRunResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartWorkflowRun' smart constructor.
data StartWorkflowRun = StartWorkflowRun'
  { -- | The workflow run properties for the new workflow run.
    StartWorkflowRun -> Maybe (HashMap Text Text)
runProperties :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the workflow to start.
    StartWorkflowRun -> Text
name :: Prelude.Text
  }
  deriving (StartWorkflowRun -> StartWorkflowRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartWorkflowRun -> StartWorkflowRun -> Bool
$c/= :: StartWorkflowRun -> StartWorkflowRun -> Bool
== :: StartWorkflowRun -> StartWorkflowRun -> Bool
$c== :: StartWorkflowRun -> StartWorkflowRun -> Bool
Prelude.Eq, ReadPrec [StartWorkflowRun]
ReadPrec StartWorkflowRun
Int -> ReadS StartWorkflowRun
ReadS [StartWorkflowRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartWorkflowRun]
$creadListPrec :: ReadPrec [StartWorkflowRun]
readPrec :: ReadPrec StartWorkflowRun
$creadPrec :: ReadPrec StartWorkflowRun
readList :: ReadS [StartWorkflowRun]
$creadList :: ReadS [StartWorkflowRun]
readsPrec :: Int -> ReadS StartWorkflowRun
$creadsPrec :: Int -> ReadS StartWorkflowRun
Prelude.Read, Int -> StartWorkflowRun -> ShowS
[StartWorkflowRun] -> ShowS
StartWorkflowRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartWorkflowRun] -> ShowS
$cshowList :: [StartWorkflowRun] -> ShowS
show :: StartWorkflowRun -> String
$cshow :: StartWorkflowRun -> String
showsPrec :: Int -> StartWorkflowRun -> ShowS
$cshowsPrec :: Int -> StartWorkflowRun -> ShowS
Prelude.Show, forall x. Rep StartWorkflowRun x -> StartWorkflowRun
forall x. StartWorkflowRun -> Rep StartWorkflowRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartWorkflowRun x -> StartWorkflowRun
$cfrom :: forall x. StartWorkflowRun -> Rep StartWorkflowRun x
Prelude.Generic)

-- |
-- Create a value of 'StartWorkflowRun' 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:
--
-- 'runProperties', 'startWorkflowRun_runProperties' - The workflow run properties for the new workflow run.
--
-- 'name', 'startWorkflowRun_name' - The name of the workflow to start.
newStartWorkflowRun ::
  -- | 'name'
  Prelude.Text ->
  StartWorkflowRun
newStartWorkflowRun :: Text -> StartWorkflowRun
newStartWorkflowRun Text
pName_ =
  StartWorkflowRun'
    { $sel:runProperties:StartWorkflowRun' :: Maybe (HashMap Text Text)
runProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:name:StartWorkflowRun' :: Text
name = Text
pName_
    }

-- | The workflow run properties for the new workflow run.
startWorkflowRun_runProperties :: Lens.Lens' StartWorkflowRun (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
startWorkflowRun_runProperties :: Lens' StartWorkflowRun (Maybe (HashMap Text Text))
startWorkflowRun_runProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartWorkflowRun' {Maybe (HashMap Text Text)
runProperties :: Maybe (HashMap Text Text)
$sel:runProperties:StartWorkflowRun' :: StartWorkflowRun -> Maybe (HashMap Text Text)
runProperties} -> Maybe (HashMap Text Text)
runProperties) (\s :: StartWorkflowRun
s@StartWorkflowRun' {} Maybe (HashMap Text Text)
a -> StartWorkflowRun
s {$sel:runProperties:StartWorkflowRun' :: Maybe (HashMap Text Text)
runProperties = Maybe (HashMap Text Text)
a} :: StartWorkflowRun) 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 name of the workflow to start.
startWorkflowRun_name :: Lens.Lens' StartWorkflowRun Prelude.Text
startWorkflowRun_name :: Lens' StartWorkflowRun Text
startWorkflowRun_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartWorkflowRun' {Text
name :: Text
$sel:name:StartWorkflowRun' :: StartWorkflowRun -> Text
name} -> Text
name) (\s :: StartWorkflowRun
s@StartWorkflowRun' {} Text
a -> StartWorkflowRun
s {$sel:name:StartWorkflowRun' :: Text
name = Text
a} :: StartWorkflowRun)

instance Core.AWSRequest StartWorkflowRun where
  type
    AWSResponse StartWorkflowRun =
      StartWorkflowRunResponse
  request :: (Service -> Service)
-> StartWorkflowRun -> Request StartWorkflowRun
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 StartWorkflowRun
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartWorkflowRun)))
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 -> StartWorkflowRunResponse
StartWorkflowRunResponse'
            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
"RunId")
            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 StartWorkflowRun where
  hashWithSalt :: Int -> StartWorkflowRun -> Int
hashWithSalt Int
_salt StartWorkflowRun' {Maybe (HashMap Text Text)
Text
name :: Text
runProperties :: Maybe (HashMap Text Text)
$sel:name:StartWorkflowRun' :: StartWorkflowRun -> Text
$sel:runProperties:StartWorkflowRun' :: StartWorkflowRun -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
runProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData StartWorkflowRun where
  rnf :: StartWorkflowRun -> ()
rnf StartWorkflowRun' {Maybe (HashMap Text Text)
Text
name :: Text
runProperties :: Maybe (HashMap Text Text)
$sel:name:StartWorkflowRun' :: StartWorkflowRun -> Text
$sel:runProperties:StartWorkflowRun' :: StartWorkflowRun -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
runProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

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

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

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

-- | /See:/ 'newStartWorkflowRunResponse' smart constructor.
data StartWorkflowRunResponse = StartWorkflowRunResponse'
  { -- | An Id for the new run.
    StartWorkflowRunResponse -> Maybe Text
runId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartWorkflowRunResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartWorkflowRunResponse -> StartWorkflowRunResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartWorkflowRunResponse -> StartWorkflowRunResponse -> Bool
$c/= :: StartWorkflowRunResponse -> StartWorkflowRunResponse -> Bool
== :: StartWorkflowRunResponse -> StartWorkflowRunResponse -> Bool
$c== :: StartWorkflowRunResponse -> StartWorkflowRunResponse -> Bool
Prelude.Eq, ReadPrec [StartWorkflowRunResponse]
ReadPrec StartWorkflowRunResponse
Int -> ReadS StartWorkflowRunResponse
ReadS [StartWorkflowRunResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartWorkflowRunResponse]
$creadListPrec :: ReadPrec [StartWorkflowRunResponse]
readPrec :: ReadPrec StartWorkflowRunResponse
$creadPrec :: ReadPrec StartWorkflowRunResponse
readList :: ReadS [StartWorkflowRunResponse]
$creadList :: ReadS [StartWorkflowRunResponse]
readsPrec :: Int -> ReadS StartWorkflowRunResponse
$creadsPrec :: Int -> ReadS StartWorkflowRunResponse
Prelude.Read, Int -> StartWorkflowRunResponse -> ShowS
[StartWorkflowRunResponse] -> ShowS
StartWorkflowRunResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartWorkflowRunResponse] -> ShowS
$cshowList :: [StartWorkflowRunResponse] -> ShowS
show :: StartWorkflowRunResponse -> String
$cshow :: StartWorkflowRunResponse -> String
showsPrec :: Int -> StartWorkflowRunResponse -> ShowS
$cshowsPrec :: Int -> StartWorkflowRunResponse -> ShowS
Prelude.Show, forall x.
Rep StartWorkflowRunResponse x -> StartWorkflowRunResponse
forall x.
StartWorkflowRunResponse -> Rep StartWorkflowRunResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartWorkflowRunResponse x -> StartWorkflowRunResponse
$cfrom :: forall x.
StartWorkflowRunResponse -> Rep StartWorkflowRunResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartWorkflowRunResponse' 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:
--
-- 'runId', 'startWorkflowRunResponse_runId' - An Id for the new run.
--
-- 'httpStatus', 'startWorkflowRunResponse_httpStatus' - The response's http status code.
newStartWorkflowRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartWorkflowRunResponse
newStartWorkflowRunResponse :: Int -> StartWorkflowRunResponse
newStartWorkflowRunResponse Int
pHttpStatus_ =
  StartWorkflowRunResponse'
    { $sel:runId:StartWorkflowRunResponse' :: Maybe Text
runId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartWorkflowRunResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An Id for the new run.
startWorkflowRunResponse_runId :: Lens.Lens' StartWorkflowRunResponse (Prelude.Maybe Prelude.Text)
startWorkflowRunResponse_runId :: Lens' StartWorkflowRunResponse (Maybe Text)
startWorkflowRunResponse_runId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartWorkflowRunResponse' {Maybe Text
runId :: Maybe Text
$sel:runId:StartWorkflowRunResponse' :: StartWorkflowRunResponse -> Maybe Text
runId} -> Maybe Text
runId) (\s :: StartWorkflowRunResponse
s@StartWorkflowRunResponse' {} Maybe Text
a -> StartWorkflowRunResponse
s {$sel:runId:StartWorkflowRunResponse' :: Maybe Text
runId = Maybe Text
a} :: StartWorkflowRunResponse)

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

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