{-# 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.StartBlueprintRun
-- 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 blueprint.
module Amazonka.Glue.StartBlueprintRun
  ( -- * Creating a Request
    StartBlueprintRun (..),
    newStartBlueprintRun,

    -- * Request Lenses
    startBlueprintRun_parameters,
    startBlueprintRun_blueprintName,
    startBlueprintRun_roleArn,

    -- * Destructuring the Response
    StartBlueprintRunResponse (..),
    newStartBlueprintRunResponse,

    -- * Response Lenses
    startBlueprintRunResponse_runId,
    startBlueprintRunResponse_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:/ 'newStartBlueprintRun' smart constructor.
data StartBlueprintRun = StartBlueprintRun'
  { -- | Specifies the parameters as a @BlueprintParameters@ object.
    StartBlueprintRun -> Maybe Text
parameters :: Prelude.Maybe Prelude.Text,
    -- | The name of the blueprint.
    StartBlueprintRun -> Text
blueprintName :: Prelude.Text,
    -- | Specifies the IAM role used to create the workflow.
    StartBlueprintRun -> Text
roleArn :: Prelude.Text
  }
  deriving (StartBlueprintRun -> StartBlueprintRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartBlueprintRun -> StartBlueprintRun -> Bool
$c/= :: StartBlueprintRun -> StartBlueprintRun -> Bool
== :: StartBlueprintRun -> StartBlueprintRun -> Bool
$c== :: StartBlueprintRun -> StartBlueprintRun -> Bool
Prelude.Eq, ReadPrec [StartBlueprintRun]
ReadPrec StartBlueprintRun
Int -> ReadS StartBlueprintRun
ReadS [StartBlueprintRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartBlueprintRun]
$creadListPrec :: ReadPrec [StartBlueprintRun]
readPrec :: ReadPrec StartBlueprintRun
$creadPrec :: ReadPrec StartBlueprintRun
readList :: ReadS [StartBlueprintRun]
$creadList :: ReadS [StartBlueprintRun]
readsPrec :: Int -> ReadS StartBlueprintRun
$creadsPrec :: Int -> ReadS StartBlueprintRun
Prelude.Read, Int -> StartBlueprintRun -> ShowS
[StartBlueprintRun] -> ShowS
StartBlueprintRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartBlueprintRun] -> ShowS
$cshowList :: [StartBlueprintRun] -> ShowS
show :: StartBlueprintRun -> String
$cshow :: StartBlueprintRun -> String
showsPrec :: Int -> StartBlueprintRun -> ShowS
$cshowsPrec :: Int -> StartBlueprintRun -> ShowS
Prelude.Show, forall x. Rep StartBlueprintRun x -> StartBlueprintRun
forall x. StartBlueprintRun -> Rep StartBlueprintRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartBlueprintRun x -> StartBlueprintRun
$cfrom :: forall x. StartBlueprintRun -> Rep StartBlueprintRun x
Prelude.Generic)

-- |
-- Create a value of 'StartBlueprintRun' 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:
--
-- 'parameters', 'startBlueprintRun_parameters' - Specifies the parameters as a @BlueprintParameters@ object.
--
-- 'blueprintName', 'startBlueprintRun_blueprintName' - The name of the blueprint.
--
-- 'roleArn', 'startBlueprintRun_roleArn' - Specifies the IAM role used to create the workflow.
newStartBlueprintRun ::
  -- | 'blueprintName'
  Prelude.Text ->
  -- | 'roleArn'
  Prelude.Text ->
  StartBlueprintRun
newStartBlueprintRun :: Text -> Text -> StartBlueprintRun
newStartBlueprintRun Text
pBlueprintName_ Text
pRoleArn_ =
  StartBlueprintRun'
    { $sel:parameters:StartBlueprintRun' :: Maybe Text
parameters = forall a. Maybe a
Prelude.Nothing,
      $sel:blueprintName:StartBlueprintRun' :: Text
blueprintName = Text
pBlueprintName_,
      $sel:roleArn:StartBlueprintRun' :: Text
roleArn = Text
pRoleArn_
    }

-- | Specifies the parameters as a @BlueprintParameters@ object.
startBlueprintRun_parameters :: Lens.Lens' StartBlueprintRun (Prelude.Maybe Prelude.Text)
startBlueprintRun_parameters :: Lens' StartBlueprintRun (Maybe Text)
startBlueprintRun_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBlueprintRun' {Maybe Text
parameters :: Maybe Text
$sel:parameters:StartBlueprintRun' :: StartBlueprintRun -> Maybe Text
parameters} -> Maybe Text
parameters) (\s :: StartBlueprintRun
s@StartBlueprintRun' {} Maybe Text
a -> StartBlueprintRun
s {$sel:parameters:StartBlueprintRun' :: Maybe Text
parameters = Maybe Text
a} :: StartBlueprintRun)

-- | The name of the blueprint.
startBlueprintRun_blueprintName :: Lens.Lens' StartBlueprintRun Prelude.Text
startBlueprintRun_blueprintName :: Lens' StartBlueprintRun Text
startBlueprintRun_blueprintName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBlueprintRun' {Text
blueprintName :: Text
$sel:blueprintName:StartBlueprintRun' :: StartBlueprintRun -> Text
blueprintName} -> Text
blueprintName) (\s :: StartBlueprintRun
s@StartBlueprintRun' {} Text
a -> StartBlueprintRun
s {$sel:blueprintName:StartBlueprintRun' :: Text
blueprintName = Text
a} :: StartBlueprintRun)

-- | Specifies the IAM role used to create the workflow.
startBlueprintRun_roleArn :: Lens.Lens' StartBlueprintRun Prelude.Text
startBlueprintRun_roleArn :: Lens' StartBlueprintRun Text
startBlueprintRun_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBlueprintRun' {Text
roleArn :: Text
$sel:roleArn:StartBlueprintRun' :: StartBlueprintRun -> Text
roleArn} -> Text
roleArn) (\s :: StartBlueprintRun
s@StartBlueprintRun' {} Text
a -> StartBlueprintRun
s {$sel:roleArn:StartBlueprintRun' :: Text
roleArn = Text
a} :: StartBlueprintRun)

instance Core.AWSRequest StartBlueprintRun where
  type
    AWSResponse StartBlueprintRun =
      StartBlueprintRunResponse
  request :: (Service -> Service)
-> StartBlueprintRun -> Request StartBlueprintRun
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 StartBlueprintRun
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartBlueprintRun)))
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 -> StartBlueprintRunResponse
StartBlueprintRunResponse'
            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 StartBlueprintRun where
  hashWithSalt :: Int -> StartBlueprintRun -> Int
hashWithSalt Int
_salt StartBlueprintRun' {Maybe Text
Text
roleArn :: Text
blueprintName :: Text
parameters :: Maybe Text
$sel:roleArn:StartBlueprintRun' :: StartBlueprintRun -> Text
$sel:blueprintName:StartBlueprintRun' :: StartBlueprintRun -> Text
$sel:parameters:StartBlueprintRun' :: StartBlueprintRun -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
blueprintName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn

instance Prelude.NFData StartBlueprintRun where
  rnf :: StartBlueprintRun -> ()
rnf StartBlueprintRun' {Maybe Text
Text
roleArn :: Text
blueprintName :: Text
parameters :: Maybe Text
$sel:roleArn:StartBlueprintRun' :: StartBlueprintRun -> Text
$sel:blueprintName:StartBlueprintRun' :: StartBlueprintRun -> Text
$sel:parameters:StartBlueprintRun' :: StartBlueprintRun -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
blueprintName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn

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

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

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

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

-- |
-- Create a value of 'StartBlueprintRunResponse' 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', 'startBlueprintRunResponse_runId' - The run ID for this blueprint run.
--
-- 'httpStatus', 'startBlueprintRunResponse_httpStatus' - The response's http status code.
newStartBlueprintRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartBlueprintRunResponse
newStartBlueprintRunResponse :: Int -> StartBlueprintRunResponse
newStartBlueprintRunResponse Int
pHttpStatus_ =
  StartBlueprintRunResponse'
    { $sel:runId:StartBlueprintRunResponse' :: Maybe Text
runId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartBlueprintRunResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The run ID for this blueprint run.
startBlueprintRunResponse_runId :: Lens.Lens' StartBlueprintRunResponse (Prelude.Maybe Prelude.Text)
startBlueprintRunResponse_runId :: Lens' StartBlueprintRunResponse (Maybe Text)
startBlueprintRunResponse_runId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBlueprintRunResponse' {Maybe Text
runId :: Maybe Text
$sel:runId:StartBlueprintRunResponse' :: StartBlueprintRunResponse -> Maybe Text
runId} -> Maybe Text
runId) (\s :: StartBlueprintRunResponse
s@StartBlueprintRunResponse' {} Maybe Text
a -> StartBlueprintRunResponse
s {$sel:runId:StartBlueprintRunResponse' :: Maybe Text
runId = Maybe Text
a} :: StartBlueprintRunResponse)

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

instance Prelude.NFData StartBlueprintRunResponse where
  rnf :: StartBlueprintRunResponse -> ()
rnf StartBlueprintRunResponse' {Int
Maybe Text
httpStatus :: Int
runId :: Maybe Text
$sel:httpStatus:StartBlueprintRunResponse' :: StartBlueprintRunResponse -> Int
$sel:runId:StartBlueprintRunResponse' :: StartBlueprintRunResponse -> 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