{-# 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 #-}
module Amazonka.EMR.AddJobFlowSteps
(
AddJobFlowSteps (..),
newAddJobFlowSteps,
addJobFlowSteps_executionRoleArn,
addJobFlowSteps_jobFlowId,
addJobFlowSteps_steps,
AddJobFlowStepsResponse (..),
newAddJobFlowStepsResponse,
addJobFlowStepsResponse_stepIds,
addJobFlowStepsResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EMR.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data AddJobFlowSteps = AddJobFlowSteps'
{
AddJobFlowSteps -> Maybe Text
executionRoleArn :: Prelude.Maybe Prelude.Text,
AddJobFlowSteps -> Text
jobFlowId :: Prelude.Text,
AddJobFlowSteps -> [StepConfig]
steps :: [StepConfig]
}
deriving (AddJobFlowSteps -> AddJobFlowSteps -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddJobFlowSteps -> AddJobFlowSteps -> Bool
$c/= :: AddJobFlowSteps -> AddJobFlowSteps -> Bool
== :: AddJobFlowSteps -> AddJobFlowSteps -> Bool
$c== :: AddJobFlowSteps -> AddJobFlowSteps -> Bool
Prelude.Eq, ReadPrec [AddJobFlowSteps]
ReadPrec AddJobFlowSteps
Int -> ReadS AddJobFlowSteps
ReadS [AddJobFlowSteps]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddJobFlowSteps]
$creadListPrec :: ReadPrec [AddJobFlowSteps]
readPrec :: ReadPrec AddJobFlowSteps
$creadPrec :: ReadPrec AddJobFlowSteps
readList :: ReadS [AddJobFlowSteps]
$creadList :: ReadS [AddJobFlowSteps]
readsPrec :: Int -> ReadS AddJobFlowSteps
$creadsPrec :: Int -> ReadS AddJobFlowSteps
Prelude.Read, Int -> AddJobFlowSteps -> ShowS
[AddJobFlowSteps] -> ShowS
AddJobFlowSteps -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddJobFlowSteps] -> ShowS
$cshowList :: [AddJobFlowSteps] -> ShowS
show :: AddJobFlowSteps -> String
$cshow :: AddJobFlowSteps -> String
showsPrec :: Int -> AddJobFlowSteps -> ShowS
$cshowsPrec :: Int -> AddJobFlowSteps -> ShowS
Prelude.Show, forall x. Rep AddJobFlowSteps x -> AddJobFlowSteps
forall x. AddJobFlowSteps -> Rep AddJobFlowSteps x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddJobFlowSteps x -> AddJobFlowSteps
$cfrom :: forall x. AddJobFlowSteps -> Rep AddJobFlowSteps x
Prelude.Generic)
newAddJobFlowSteps ::
Prelude.Text ->
AddJobFlowSteps
newAddJobFlowSteps :: Text -> AddJobFlowSteps
newAddJobFlowSteps Text
pJobFlowId_ =
AddJobFlowSteps'
{ $sel:executionRoleArn:AddJobFlowSteps' :: Maybe Text
executionRoleArn =
forall a. Maybe a
Prelude.Nothing,
$sel:jobFlowId:AddJobFlowSteps' :: Text
jobFlowId = Text
pJobFlowId_,
$sel:steps:AddJobFlowSteps' :: [StepConfig]
steps = forall a. Monoid a => a
Prelude.mempty
}
addJobFlowSteps_executionRoleArn :: Lens.Lens' AddJobFlowSteps (Prelude.Maybe Prelude.Text)
addJobFlowSteps_executionRoleArn :: Lens' AddJobFlowSteps (Maybe Text)
addJobFlowSteps_executionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddJobFlowSteps' {Maybe Text
executionRoleArn :: Maybe Text
$sel:executionRoleArn:AddJobFlowSteps' :: AddJobFlowSteps -> Maybe Text
executionRoleArn} -> Maybe Text
executionRoleArn) (\s :: AddJobFlowSteps
s@AddJobFlowSteps' {} Maybe Text
a -> AddJobFlowSteps
s {$sel:executionRoleArn:AddJobFlowSteps' :: Maybe Text
executionRoleArn = Maybe Text
a} :: AddJobFlowSteps)
addJobFlowSteps_jobFlowId :: Lens.Lens' AddJobFlowSteps Prelude.Text
addJobFlowSteps_jobFlowId :: Lens' AddJobFlowSteps Text
addJobFlowSteps_jobFlowId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddJobFlowSteps' {Text
jobFlowId :: Text
$sel:jobFlowId:AddJobFlowSteps' :: AddJobFlowSteps -> Text
jobFlowId} -> Text
jobFlowId) (\s :: AddJobFlowSteps
s@AddJobFlowSteps' {} Text
a -> AddJobFlowSteps
s {$sel:jobFlowId:AddJobFlowSteps' :: Text
jobFlowId = Text
a} :: AddJobFlowSteps)
addJobFlowSteps_steps :: Lens.Lens' AddJobFlowSteps [StepConfig]
addJobFlowSteps_steps :: Lens' AddJobFlowSteps [StepConfig]
addJobFlowSteps_steps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddJobFlowSteps' {[StepConfig]
steps :: [StepConfig]
$sel:steps:AddJobFlowSteps' :: AddJobFlowSteps -> [StepConfig]
steps} -> [StepConfig]
steps) (\s :: AddJobFlowSteps
s@AddJobFlowSteps' {} [StepConfig]
a -> AddJobFlowSteps
s {$sel:steps:AddJobFlowSteps' :: [StepConfig]
steps = [StepConfig]
a} :: AddJobFlowSteps) 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 AddJobFlowSteps where
type
AWSResponse AddJobFlowSteps =
AddJobFlowStepsResponse
request :: (Service -> Service) -> AddJobFlowSteps -> Request AddJobFlowSteps
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 AddJobFlowSteps
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AddJobFlowSteps)))
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 -> AddJobFlowStepsResponse
AddJobFlowStepsResponse'
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
"StepIds" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
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 AddJobFlowSteps where
hashWithSalt :: Int -> AddJobFlowSteps -> Int
hashWithSalt Int
_salt AddJobFlowSteps' {[StepConfig]
Maybe Text
Text
steps :: [StepConfig]
jobFlowId :: Text
executionRoleArn :: Maybe Text
$sel:steps:AddJobFlowSteps' :: AddJobFlowSteps -> [StepConfig]
$sel:jobFlowId:AddJobFlowSteps' :: AddJobFlowSteps -> Text
$sel:executionRoleArn:AddJobFlowSteps' :: AddJobFlowSteps -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
executionRoleArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobFlowId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [StepConfig]
steps
instance Prelude.NFData AddJobFlowSteps where
rnf :: AddJobFlowSteps -> ()
rnf AddJobFlowSteps' {[StepConfig]
Maybe Text
Text
steps :: [StepConfig]
jobFlowId :: Text
executionRoleArn :: Maybe Text
$sel:steps:AddJobFlowSteps' :: AddJobFlowSteps -> [StepConfig]
$sel:jobFlowId:AddJobFlowSteps' :: AddJobFlowSteps -> Text
$sel:executionRoleArn:AddJobFlowSteps' :: AddJobFlowSteps -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionRoleArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobFlowId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [StepConfig]
steps
instance Data.ToHeaders AddJobFlowSteps where
toHeaders :: AddJobFlowSteps -> 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
"ElasticMapReduce.AddJobFlowSteps" ::
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 AddJobFlowSteps where
toJSON :: AddJobFlowSteps -> Value
toJSON AddJobFlowSteps' {[StepConfig]
Maybe Text
Text
steps :: [StepConfig]
jobFlowId :: Text
executionRoleArn :: Maybe Text
$sel:steps:AddJobFlowSteps' :: AddJobFlowSteps -> [StepConfig]
$sel:jobFlowId:AddJobFlowSteps' :: AddJobFlowSteps -> Text
$sel:executionRoleArn:AddJobFlowSteps' :: AddJobFlowSteps -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"ExecutionRoleArn" 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
executionRoleArn,
forall a. a -> Maybe a
Prelude.Just (Key
"JobFlowId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobFlowId),
forall a. a -> Maybe a
Prelude.Just (Key
"Steps" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [StepConfig]
steps)
]
)
instance Data.ToPath AddJobFlowSteps where
toPath :: AddJobFlowSteps -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery AddJobFlowSteps where
toQuery :: AddJobFlowSteps -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data AddJobFlowStepsResponse = AddJobFlowStepsResponse'
{
AddJobFlowStepsResponse -> Maybe [Text]
stepIds :: Prelude.Maybe [Prelude.Text],
AddJobFlowStepsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (AddJobFlowStepsResponse -> AddJobFlowStepsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddJobFlowStepsResponse -> AddJobFlowStepsResponse -> Bool
$c/= :: AddJobFlowStepsResponse -> AddJobFlowStepsResponse -> Bool
== :: AddJobFlowStepsResponse -> AddJobFlowStepsResponse -> Bool
$c== :: AddJobFlowStepsResponse -> AddJobFlowStepsResponse -> Bool
Prelude.Eq, ReadPrec [AddJobFlowStepsResponse]
ReadPrec AddJobFlowStepsResponse
Int -> ReadS AddJobFlowStepsResponse
ReadS [AddJobFlowStepsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddJobFlowStepsResponse]
$creadListPrec :: ReadPrec [AddJobFlowStepsResponse]
readPrec :: ReadPrec AddJobFlowStepsResponse
$creadPrec :: ReadPrec AddJobFlowStepsResponse
readList :: ReadS [AddJobFlowStepsResponse]
$creadList :: ReadS [AddJobFlowStepsResponse]
readsPrec :: Int -> ReadS AddJobFlowStepsResponse
$creadsPrec :: Int -> ReadS AddJobFlowStepsResponse
Prelude.Read, Int -> AddJobFlowStepsResponse -> ShowS
[AddJobFlowStepsResponse] -> ShowS
AddJobFlowStepsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddJobFlowStepsResponse] -> ShowS
$cshowList :: [AddJobFlowStepsResponse] -> ShowS
show :: AddJobFlowStepsResponse -> String
$cshow :: AddJobFlowStepsResponse -> String
showsPrec :: Int -> AddJobFlowStepsResponse -> ShowS
$cshowsPrec :: Int -> AddJobFlowStepsResponse -> ShowS
Prelude.Show, forall x. Rep AddJobFlowStepsResponse x -> AddJobFlowStepsResponse
forall x. AddJobFlowStepsResponse -> Rep AddJobFlowStepsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddJobFlowStepsResponse x -> AddJobFlowStepsResponse
$cfrom :: forall x. AddJobFlowStepsResponse -> Rep AddJobFlowStepsResponse x
Prelude.Generic)
newAddJobFlowStepsResponse ::
Prelude.Int ->
AddJobFlowStepsResponse
newAddJobFlowStepsResponse :: Int -> AddJobFlowStepsResponse
newAddJobFlowStepsResponse Int
pHttpStatus_ =
AddJobFlowStepsResponse'
{ $sel:stepIds:AddJobFlowStepsResponse' :: Maybe [Text]
stepIds = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:AddJobFlowStepsResponse' :: Int
httpStatus = Int
pHttpStatus_
}
addJobFlowStepsResponse_stepIds :: Lens.Lens' AddJobFlowStepsResponse (Prelude.Maybe [Prelude.Text])
addJobFlowStepsResponse_stepIds :: Lens' AddJobFlowStepsResponse (Maybe [Text])
addJobFlowStepsResponse_stepIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddJobFlowStepsResponse' {Maybe [Text]
stepIds :: Maybe [Text]
$sel:stepIds:AddJobFlowStepsResponse' :: AddJobFlowStepsResponse -> Maybe [Text]
stepIds} -> Maybe [Text]
stepIds) (\s :: AddJobFlowStepsResponse
s@AddJobFlowStepsResponse' {} Maybe [Text]
a -> AddJobFlowStepsResponse
s {$sel:stepIds:AddJobFlowStepsResponse' :: Maybe [Text]
stepIds = Maybe [Text]
a} :: AddJobFlowStepsResponse) 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
addJobFlowStepsResponse_httpStatus :: Lens.Lens' AddJobFlowStepsResponse Prelude.Int
addJobFlowStepsResponse_httpStatus :: Lens' AddJobFlowStepsResponse Int
addJobFlowStepsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddJobFlowStepsResponse' {Int
httpStatus :: Int
$sel:httpStatus:AddJobFlowStepsResponse' :: AddJobFlowStepsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AddJobFlowStepsResponse
s@AddJobFlowStepsResponse' {} Int
a -> AddJobFlowStepsResponse
s {$sel:httpStatus:AddJobFlowStepsResponse' :: Int
httpStatus = Int
a} :: AddJobFlowStepsResponse)
instance Prelude.NFData AddJobFlowStepsResponse where
rnf :: AddJobFlowStepsResponse -> ()
rnf AddJobFlowStepsResponse' {Int
Maybe [Text]
httpStatus :: Int
stepIds :: Maybe [Text]
$sel:httpStatus:AddJobFlowStepsResponse' :: AddJobFlowStepsResponse -> Int
$sel:stepIds:AddJobFlowStepsResponse' :: AddJobFlowStepsResponse -> Maybe [Text]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
stepIds
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus