{-# 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.SageMaker.RetryPipelineExecution
  ( 
    RetryPipelineExecution (..),
    newRetryPipelineExecution,
    
    retryPipelineExecution_parallelismConfiguration,
    retryPipelineExecution_pipelineExecutionArn,
    retryPipelineExecution_clientRequestToken,
    
    RetryPipelineExecutionResponse (..),
    newRetryPipelineExecutionResponse,
    
    retryPipelineExecutionResponse_pipelineExecutionArn,
    retryPipelineExecutionResponse_httpStatus,
  )
where
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
import Amazonka.SageMaker.Types
data RetryPipelineExecution = RetryPipelineExecution'
  { 
    
    RetryPipelineExecution -> Maybe ParallelismConfiguration
parallelismConfiguration :: Prelude.Maybe ParallelismConfiguration,
    
    RetryPipelineExecution -> Text
pipelineExecutionArn :: Prelude.Text,
    
    
    
    RetryPipelineExecution -> Text
clientRequestToken :: Prelude.Text
  }
  deriving (RetryPipelineExecution -> RetryPipelineExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RetryPipelineExecution -> RetryPipelineExecution -> Bool
$c/= :: RetryPipelineExecution -> RetryPipelineExecution -> Bool
== :: RetryPipelineExecution -> RetryPipelineExecution -> Bool
$c== :: RetryPipelineExecution -> RetryPipelineExecution -> Bool
Prelude.Eq, ReadPrec [RetryPipelineExecution]
ReadPrec RetryPipelineExecution
Int -> ReadS RetryPipelineExecution
ReadS [RetryPipelineExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RetryPipelineExecution]
$creadListPrec :: ReadPrec [RetryPipelineExecution]
readPrec :: ReadPrec RetryPipelineExecution
$creadPrec :: ReadPrec RetryPipelineExecution
readList :: ReadS [RetryPipelineExecution]
$creadList :: ReadS [RetryPipelineExecution]
readsPrec :: Int -> ReadS RetryPipelineExecution
$creadsPrec :: Int -> ReadS RetryPipelineExecution
Prelude.Read, Int -> RetryPipelineExecution -> ShowS
[RetryPipelineExecution] -> ShowS
RetryPipelineExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetryPipelineExecution] -> ShowS
$cshowList :: [RetryPipelineExecution] -> ShowS
show :: RetryPipelineExecution -> String
$cshow :: RetryPipelineExecution -> String
showsPrec :: Int -> RetryPipelineExecution -> ShowS
$cshowsPrec :: Int -> RetryPipelineExecution -> ShowS
Prelude.Show, forall x. Rep RetryPipelineExecution x -> RetryPipelineExecution
forall x. RetryPipelineExecution -> Rep RetryPipelineExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RetryPipelineExecution x -> RetryPipelineExecution
$cfrom :: forall x. RetryPipelineExecution -> Rep RetryPipelineExecution x
Prelude.Generic)
newRetryPipelineExecution ::
  
  Prelude.Text ->
  
  Prelude.Text ->
  RetryPipelineExecution
newRetryPipelineExecution :: Text -> Text -> RetryPipelineExecution
newRetryPipelineExecution
  Text
pPipelineExecutionArn_
  Text
pClientRequestToken_ =
    RetryPipelineExecution'
      { $sel:parallelismConfiguration:RetryPipelineExecution' :: Maybe ParallelismConfiguration
parallelismConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:pipelineExecutionArn:RetryPipelineExecution' :: Text
pipelineExecutionArn = Text
pPipelineExecutionArn_,
        $sel:clientRequestToken:RetryPipelineExecution' :: Text
clientRequestToken = Text
pClientRequestToken_
      }
retryPipelineExecution_parallelismConfiguration :: Lens.Lens' RetryPipelineExecution (Prelude.Maybe ParallelismConfiguration)
retryPipelineExecution_parallelismConfiguration :: Lens' RetryPipelineExecution (Maybe ParallelismConfiguration)
retryPipelineExecution_parallelismConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryPipelineExecution' {Maybe ParallelismConfiguration
parallelismConfiguration :: Maybe ParallelismConfiguration
$sel:parallelismConfiguration:RetryPipelineExecution' :: RetryPipelineExecution -> Maybe ParallelismConfiguration
parallelismConfiguration} -> Maybe ParallelismConfiguration
parallelismConfiguration) (\s :: RetryPipelineExecution
s@RetryPipelineExecution' {} Maybe ParallelismConfiguration
a -> RetryPipelineExecution
s {$sel:parallelismConfiguration:RetryPipelineExecution' :: Maybe ParallelismConfiguration
parallelismConfiguration = Maybe ParallelismConfiguration
a} :: RetryPipelineExecution)
retryPipelineExecution_pipelineExecutionArn :: Lens.Lens' RetryPipelineExecution Prelude.Text
retryPipelineExecution_pipelineExecutionArn :: Lens' RetryPipelineExecution Text
retryPipelineExecution_pipelineExecutionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryPipelineExecution' {Text
pipelineExecutionArn :: Text
$sel:pipelineExecutionArn:RetryPipelineExecution' :: RetryPipelineExecution -> Text
pipelineExecutionArn} -> Text
pipelineExecutionArn) (\s :: RetryPipelineExecution
s@RetryPipelineExecution' {} Text
a -> RetryPipelineExecution
s {$sel:pipelineExecutionArn:RetryPipelineExecution' :: Text
pipelineExecutionArn = Text
a} :: RetryPipelineExecution)
retryPipelineExecution_clientRequestToken :: Lens.Lens' RetryPipelineExecution Prelude.Text
retryPipelineExecution_clientRequestToken :: Lens' RetryPipelineExecution Text
retryPipelineExecution_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryPipelineExecution' {Text
clientRequestToken :: Text
$sel:clientRequestToken:RetryPipelineExecution' :: RetryPipelineExecution -> Text
clientRequestToken} -> Text
clientRequestToken) (\s :: RetryPipelineExecution
s@RetryPipelineExecution' {} Text
a -> RetryPipelineExecution
s {$sel:clientRequestToken:RetryPipelineExecution' :: Text
clientRequestToken = Text
a} :: RetryPipelineExecution)
instance Core.AWSRequest RetryPipelineExecution where
  type
    AWSResponse RetryPipelineExecution =
      RetryPipelineExecutionResponse
  request :: (Service -> Service)
-> RetryPipelineExecution -> Request RetryPipelineExecution
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 RetryPipelineExecution
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RetryPipelineExecution)))
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 -> RetryPipelineExecutionResponse
RetryPipelineExecutionResponse'
            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
"PipelineExecutionArn")
            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 RetryPipelineExecution where
  hashWithSalt :: Int -> RetryPipelineExecution -> Int
hashWithSalt Int
_salt RetryPipelineExecution' {Maybe ParallelismConfiguration
Text
clientRequestToken :: Text
pipelineExecutionArn :: Text
parallelismConfiguration :: Maybe ParallelismConfiguration
$sel:clientRequestToken:RetryPipelineExecution' :: RetryPipelineExecution -> Text
$sel:pipelineExecutionArn:RetryPipelineExecution' :: RetryPipelineExecution -> Text
$sel:parallelismConfiguration:RetryPipelineExecution' :: RetryPipelineExecution -> Maybe ParallelismConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ParallelismConfiguration
parallelismConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pipelineExecutionArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientRequestToken
instance Prelude.NFData RetryPipelineExecution where
  rnf :: RetryPipelineExecution -> ()
rnf RetryPipelineExecution' {Maybe ParallelismConfiguration
Text
clientRequestToken :: Text
pipelineExecutionArn :: Text
parallelismConfiguration :: Maybe ParallelismConfiguration
$sel:clientRequestToken:RetryPipelineExecution' :: RetryPipelineExecution -> Text
$sel:pipelineExecutionArn:RetryPipelineExecution' :: RetryPipelineExecution -> Text
$sel:parallelismConfiguration:RetryPipelineExecution' :: RetryPipelineExecution -> Maybe ParallelismConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ParallelismConfiguration
parallelismConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
pipelineExecutionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientRequestToken
instance Data.ToHeaders RetryPipelineExecution where
  toHeaders :: RetryPipelineExecution -> 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
"SageMaker.RetryPipelineExecution" ::
                          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 RetryPipelineExecution where
  toJSON :: RetryPipelineExecution -> Value
toJSON RetryPipelineExecution' {Maybe ParallelismConfiguration
Text
clientRequestToken :: Text
pipelineExecutionArn :: Text
parallelismConfiguration :: Maybe ParallelismConfiguration
$sel:clientRequestToken:RetryPipelineExecution' :: RetryPipelineExecution -> Text
$sel:pipelineExecutionArn:RetryPipelineExecution' :: RetryPipelineExecution -> Text
$sel:parallelismConfiguration:RetryPipelineExecution' :: RetryPipelineExecution -> Maybe ParallelismConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ParallelismConfiguration" 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 ParallelismConfiguration
parallelismConfiguration,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"PipelineExecutionArn"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
pipelineExecutionArn
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ClientRequestToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clientRequestToken)
          ]
      )
instance Data.ToPath RetryPipelineExecution where
  toPath :: RetryPipelineExecution -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery RetryPipelineExecution where
  toQuery :: RetryPipelineExecution -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data RetryPipelineExecutionResponse = RetryPipelineExecutionResponse'
  { 
    RetryPipelineExecutionResponse -> Maybe Text
pipelineExecutionArn :: Prelude.Maybe Prelude.Text,
    
    RetryPipelineExecutionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RetryPipelineExecutionResponse
-> RetryPipelineExecutionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RetryPipelineExecutionResponse
-> RetryPipelineExecutionResponse -> Bool
$c/= :: RetryPipelineExecutionResponse
-> RetryPipelineExecutionResponse -> Bool
== :: RetryPipelineExecutionResponse
-> RetryPipelineExecutionResponse -> Bool
$c== :: RetryPipelineExecutionResponse
-> RetryPipelineExecutionResponse -> Bool
Prelude.Eq, ReadPrec [RetryPipelineExecutionResponse]
ReadPrec RetryPipelineExecutionResponse
Int -> ReadS RetryPipelineExecutionResponse
ReadS [RetryPipelineExecutionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RetryPipelineExecutionResponse]
$creadListPrec :: ReadPrec [RetryPipelineExecutionResponse]
readPrec :: ReadPrec RetryPipelineExecutionResponse
$creadPrec :: ReadPrec RetryPipelineExecutionResponse
readList :: ReadS [RetryPipelineExecutionResponse]
$creadList :: ReadS [RetryPipelineExecutionResponse]
readsPrec :: Int -> ReadS RetryPipelineExecutionResponse
$creadsPrec :: Int -> ReadS RetryPipelineExecutionResponse
Prelude.Read, Int -> RetryPipelineExecutionResponse -> ShowS
[RetryPipelineExecutionResponse] -> ShowS
RetryPipelineExecutionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetryPipelineExecutionResponse] -> ShowS
$cshowList :: [RetryPipelineExecutionResponse] -> ShowS
show :: RetryPipelineExecutionResponse -> String
$cshow :: RetryPipelineExecutionResponse -> String
showsPrec :: Int -> RetryPipelineExecutionResponse -> ShowS
$cshowsPrec :: Int -> RetryPipelineExecutionResponse -> ShowS
Prelude.Show, forall x.
Rep RetryPipelineExecutionResponse x
-> RetryPipelineExecutionResponse
forall x.
RetryPipelineExecutionResponse
-> Rep RetryPipelineExecutionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RetryPipelineExecutionResponse x
-> RetryPipelineExecutionResponse
$cfrom :: forall x.
RetryPipelineExecutionResponse
-> Rep RetryPipelineExecutionResponse x
Prelude.Generic)
newRetryPipelineExecutionResponse ::
  
  Prelude.Int ->
  RetryPipelineExecutionResponse
newRetryPipelineExecutionResponse :: Int -> RetryPipelineExecutionResponse
newRetryPipelineExecutionResponse Int
pHttpStatus_ =
  RetryPipelineExecutionResponse'
    { $sel:pipelineExecutionArn:RetryPipelineExecutionResponse' :: Maybe Text
pipelineExecutionArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RetryPipelineExecutionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }
retryPipelineExecutionResponse_pipelineExecutionArn :: Lens.Lens' RetryPipelineExecutionResponse (Prelude.Maybe Prelude.Text)
retryPipelineExecutionResponse_pipelineExecutionArn :: Lens' RetryPipelineExecutionResponse (Maybe Text)
retryPipelineExecutionResponse_pipelineExecutionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryPipelineExecutionResponse' {Maybe Text
pipelineExecutionArn :: Maybe Text
$sel:pipelineExecutionArn:RetryPipelineExecutionResponse' :: RetryPipelineExecutionResponse -> Maybe Text
pipelineExecutionArn} -> Maybe Text
pipelineExecutionArn) (\s :: RetryPipelineExecutionResponse
s@RetryPipelineExecutionResponse' {} Maybe Text
a -> RetryPipelineExecutionResponse
s {$sel:pipelineExecutionArn:RetryPipelineExecutionResponse' :: Maybe Text
pipelineExecutionArn = Maybe Text
a} :: RetryPipelineExecutionResponse)
retryPipelineExecutionResponse_httpStatus :: Lens.Lens' RetryPipelineExecutionResponse Prelude.Int
retryPipelineExecutionResponse_httpStatus :: Lens' RetryPipelineExecutionResponse Int
retryPipelineExecutionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryPipelineExecutionResponse' {Int
httpStatus :: Int
$sel:httpStatus:RetryPipelineExecutionResponse' :: RetryPipelineExecutionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: RetryPipelineExecutionResponse
s@RetryPipelineExecutionResponse' {} Int
a -> RetryPipelineExecutionResponse
s {$sel:httpStatus:RetryPipelineExecutionResponse' :: Int
httpStatus = Int
a} :: RetryPipelineExecutionResponse)
instance
  Prelude.NFData
    RetryPipelineExecutionResponse
  where
  rnf :: RetryPipelineExecutionResponse -> ()
rnf RetryPipelineExecutionResponse' {Int
Maybe Text
httpStatus :: Int
pipelineExecutionArn :: Maybe Text
$sel:httpStatus:RetryPipelineExecutionResponse' :: RetryPipelineExecutionResponse -> Int
$sel:pipelineExecutionArn:RetryPipelineExecutionResponse' :: RetryPipelineExecutionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pipelineExecutionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus