{-# 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.SageMaker.CreatePipeline
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a pipeline using a JSON pipeline definition.
module Amazonka.SageMaker.CreatePipeline
  ( -- * Creating a Request
    CreatePipeline (..),
    newCreatePipeline,

    -- * Request Lenses
    createPipeline_parallelismConfiguration,
    createPipeline_pipelineDefinition,
    createPipeline_pipelineDefinitionS3Location,
    createPipeline_pipelineDescription,
    createPipeline_pipelineDisplayName,
    createPipeline_tags,
    createPipeline_pipelineName,
    createPipeline_clientRequestToken,
    createPipeline_roleArn,

    -- * Destructuring the Response
    CreatePipelineResponse (..),
    newCreatePipelineResponse,

    -- * Response Lenses
    createPipelineResponse_pipelineArn,
    createPipelineResponse_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

-- | /See:/ 'newCreatePipeline' smart constructor.
data CreatePipeline = CreatePipeline'
  { -- | This is the configuration that controls the parallelism of the pipeline.
    -- If specified, it applies to all runs of this pipeline by default.
    CreatePipeline -> Maybe ParallelismConfiguration
parallelismConfiguration :: Prelude.Maybe ParallelismConfiguration,
    -- | The JSON pipeline definition of the pipeline.
    CreatePipeline -> Maybe Text
pipelineDefinition :: Prelude.Maybe Prelude.Text,
    -- | The location of the pipeline definition stored in Amazon S3. If
    -- specified, SageMaker will retrieve the pipeline definition from this
    -- location.
    CreatePipeline -> Maybe PipelineDefinitionS3Location
pipelineDefinitionS3Location :: Prelude.Maybe PipelineDefinitionS3Location,
    -- | A description of the pipeline.
    CreatePipeline -> Maybe Text
pipelineDescription :: Prelude.Maybe Prelude.Text,
    -- | The display name of the pipeline.
    CreatePipeline -> Maybe Text
pipelineDisplayName :: Prelude.Maybe Prelude.Text,
    -- | A list of tags to apply to the created pipeline.
    CreatePipeline -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the pipeline.
    CreatePipeline -> Text
pipelineName :: Prelude.Text,
    -- | A unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the operation. An idempotent operation completes no more
    -- than one time.
    CreatePipeline -> Text
clientRequestToken :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the role used by the pipeline to
    -- access and create resources.
    CreatePipeline -> Text
roleArn :: Prelude.Text
  }
  deriving (CreatePipeline -> CreatePipeline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePipeline -> CreatePipeline -> Bool
$c/= :: CreatePipeline -> CreatePipeline -> Bool
== :: CreatePipeline -> CreatePipeline -> Bool
$c== :: CreatePipeline -> CreatePipeline -> Bool
Prelude.Eq, ReadPrec [CreatePipeline]
ReadPrec CreatePipeline
Int -> ReadS CreatePipeline
ReadS [CreatePipeline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePipeline]
$creadListPrec :: ReadPrec [CreatePipeline]
readPrec :: ReadPrec CreatePipeline
$creadPrec :: ReadPrec CreatePipeline
readList :: ReadS [CreatePipeline]
$creadList :: ReadS [CreatePipeline]
readsPrec :: Int -> ReadS CreatePipeline
$creadsPrec :: Int -> ReadS CreatePipeline
Prelude.Read, Int -> CreatePipeline -> ShowS
[CreatePipeline] -> ShowS
CreatePipeline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePipeline] -> ShowS
$cshowList :: [CreatePipeline] -> ShowS
show :: CreatePipeline -> String
$cshow :: CreatePipeline -> String
showsPrec :: Int -> CreatePipeline -> ShowS
$cshowsPrec :: Int -> CreatePipeline -> ShowS
Prelude.Show, forall x. Rep CreatePipeline x -> CreatePipeline
forall x. CreatePipeline -> Rep CreatePipeline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreatePipeline x -> CreatePipeline
$cfrom :: forall x. CreatePipeline -> Rep CreatePipeline x
Prelude.Generic)

-- |
-- Create a value of 'CreatePipeline' 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:
--
-- 'parallelismConfiguration', 'createPipeline_parallelismConfiguration' - This is the configuration that controls the parallelism of the pipeline.
-- If specified, it applies to all runs of this pipeline by default.
--
-- 'pipelineDefinition', 'createPipeline_pipelineDefinition' - The JSON pipeline definition of the pipeline.
--
-- 'pipelineDefinitionS3Location', 'createPipeline_pipelineDefinitionS3Location' - The location of the pipeline definition stored in Amazon S3. If
-- specified, SageMaker will retrieve the pipeline definition from this
-- location.
--
-- 'pipelineDescription', 'createPipeline_pipelineDescription' - A description of the pipeline.
--
-- 'pipelineDisplayName', 'createPipeline_pipelineDisplayName' - The display name of the pipeline.
--
-- 'tags', 'createPipeline_tags' - A list of tags to apply to the created pipeline.
--
-- 'pipelineName', 'createPipeline_pipelineName' - The name of the pipeline.
--
-- 'clientRequestToken', 'createPipeline_clientRequestToken' - A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the operation. An idempotent operation completes no more
-- than one time.
--
-- 'roleArn', 'createPipeline_roleArn' - The Amazon Resource Name (ARN) of the role used by the pipeline to
-- access and create resources.
newCreatePipeline ::
  -- | 'pipelineName'
  Prelude.Text ->
  -- | 'clientRequestToken'
  Prelude.Text ->
  -- | 'roleArn'
  Prelude.Text ->
  CreatePipeline
newCreatePipeline :: Text -> Text -> Text -> CreatePipeline
newCreatePipeline
  Text
pPipelineName_
  Text
pClientRequestToken_
  Text
pRoleArn_ =
    CreatePipeline'
      { $sel:parallelismConfiguration:CreatePipeline' :: Maybe ParallelismConfiguration
parallelismConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:pipelineDefinition:CreatePipeline' :: Maybe Text
pipelineDefinition = forall a. Maybe a
Prelude.Nothing,
        $sel:pipelineDefinitionS3Location:CreatePipeline' :: Maybe PipelineDefinitionS3Location
pipelineDefinitionS3Location = forall a. Maybe a
Prelude.Nothing,
        $sel:pipelineDescription:CreatePipeline' :: Maybe Text
pipelineDescription = forall a. Maybe a
Prelude.Nothing,
        $sel:pipelineDisplayName:CreatePipeline' :: Maybe Text
pipelineDisplayName = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreatePipeline' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:pipelineName:CreatePipeline' :: Text
pipelineName = Text
pPipelineName_,
        $sel:clientRequestToken:CreatePipeline' :: Text
clientRequestToken = Text
pClientRequestToken_,
        $sel:roleArn:CreatePipeline' :: Text
roleArn = Text
pRoleArn_
      }

-- | This is the configuration that controls the parallelism of the pipeline.
-- If specified, it applies to all runs of this pipeline by default.
createPipeline_parallelismConfiguration :: Lens.Lens' CreatePipeline (Prelude.Maybe ParallelismConfiguration)
createPipeline_parallelismConfiguration :: Lens' CreatePipeline (Maybe ParallelismConfiguration)
createPipeline_parallelismConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipeline' {Maybe ParallelismConfiguration
parallelismConfiguration :: Maybe ParallelismConfiguration
$sel:parallelismConfiguration:CreatePipeline' :: CreatePipeline -> Maybe ParallelismConfiguration
parallelismConfiguration} -> Maybe ParallelismConfiguration
parallelismConfiguration) (\s :: CreatePipeline
s@CreatePipeline' {} Maybe ParallelismConfiguration
a -> CreatePipeline
s {$sel:parallelismConfiguration:CreatePipeline' :: Maybe ParallelismConfiguration
parallelismConfiguration = Maybe ParallelismConfiguration
a} :: CreatePipeline)

-- | The JSON pipeline definition of the pipeline.
createPipeline_pipelineDefinition :: Lens.Lens' CreatePipeline (Prelude.Maybe Prelude.Text)
createPipeline_pipelineDefinition :: Lens' CreatePipeline (Maybe Text)
createPipeline_pipelineDefinition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipeline' {Maybe Text
pipelineDefinition :: Maybe Text
$sel:pipelineDefinition:CreatePipeline' :: CreatePipeline -> Maybe Text
pipelineDefinition} -> Maybe Text
pipelineDefinition) (\s :: CreatePipeline
s@CreatePipeline' {} Maybe Text
a -> CreatePipeline
s {$sel:pipelineDefinition:CreatePipeline' :: Maybe Text
pipelineDefinition = Maybe Text
a} :: CreatePipeline)

-- | The location of the pipeline definition stored in Amazon S3. If
-- specified, SageMaker will retrieve the pipeline definition from this
-- location.
createPipeline_pipelineDefinitionS3Location :: Lens.Lens' CreatePipeline (Prelude.Maybe PipelineDefinitionS3Location)
createPipeline_pipelineDefinitionS3Location :: Lens' CreatePipeline (Maybe PipelineDefinitionS3Location)
createPipeline_pipelineDefinitionS3Location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipeline' {Maybe PipelineDefinitionS3Location
pipelineDefinitionS3Location :: Maybe PipelineDefinitionS3Location
$sel:pipelineDefinitionS3Location:CreatePipeline' :: CreatePipeline -> Maybe PipelineDefinitionS3Location
pipelineDefinitionS3Location} -> Maybe PipelineDefinitionS3Location
pipelineDefinitionS3Location) (\s :: CreatePipeline
s@CreatePipeline' {} Maybe PipelineDefinitionS3Location
a -> CreatePipeline
s {$sel:pipelineDefinitionS3Location:CreatePipeline' :: Maybe PipelineDefinitionS3Location
pipelineDefinitionS3Location = Maybe PipelineDefinitionS3Location
a} :: CreatePipeline)

-- | A description of the pipeline.
createPipeline_pipelineDescription :: Lens.Lens' CreatePipeline (Prelude.Maybe Prelude.Text)
createPipeline_pipelineDescription :: Lens' CreatePipeline (Maybe Text)
createPipeline_pipelineDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipeline' {Maybe Text
pipelineDescription :: Maybe Text
$sel:pipelineDescription:CreatePipeline' :: CreatePipeline -> Maybe Text
pipelineDescription} -> Maybe Text
pipelineDescription) (\s :: CreatePipeline
s@CreatePipeline' {} Maybe Text
a -> CreatePipeline
s {$sel:pipelineDescription:CreatePipeline' :: Maybe Text
pipelineDescription = Maybe Text
a} :: CreatePipeline)

-- | The display name of the pipeline.
createPipeline_pipelineDisplayName :: Lens.Lens' CreatePipeline (Prelude.Maybe Prelude.Text)
createPipeline_pipelineDisplayName :: Lens' CreatePipeline (Maybe Text)
createPipeline_pipelineDisplayName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipeline' {Maybe Text
pipelineDisplayName :: Maybe Text
$sel:pipelineDisplayName:CreatePipeline' :: CreatePipeline -> Maybe Text
pipelineDisplayName} -> Maybe Text
pipelineDisplayName) (\s :: CreatePipeline
s@CreatePipeline' {} Maybe Text
a -> CreatePipeline
s {$sel:pipelineDisplayName:CreatePipeline' :: Maybe Text
pipelineDisplayName = Maybe Text
a} :: CreatePipeline)

-- | A list of tags to apply to the created pipeline.
createPipeline_tags :: Lens.Lens' CreatePipeline (Prelude.Maybe [Tag])
createPipeline_tags :: Lens' CreatePipeline (Maybe [Tag])
createPipeline_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipeline' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreatePipeline' :: CreatePipeline -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreatePipeline
s@CreatePipeline' {} Maybe [Tag]
a -> CreatePipeline
s {$sel:tags:CreatePipeline' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreatePipeline) 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 pipeline.
createPipeline_pipelineName :: Lens.Lens' CreatePipeline Prelude.Text
createPipeline_pipelineName :: Lens' CreatePipeline Text
createPipeline_pipelineName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipeline' {Text
pipelineName :: Text
$sel:pipelineName:CreatePipeline' :: CreatePipeline -> Text
pipelineName} -> Text
pipelineName) (\s :: CreatePipeline
s@CreatePipeline' {} Text
a -> CreatePipeline
s {$sel:pipelineName:CreatePipeline' :: Text
pipelineName = Text
a} :: CreatePipeline)

-- | A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the operation. An idempotent operation completes no more
-- than one time.
createPipeline_clientRequestToken :: Lens.Lens' CreatePipeline Prelude.Text
createPipeline_clientRequestToken :: Lens' CreatePipeline Text
createPipeline_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipeline' {Text
clientRequestToken :: Text
$sel:clientRequestToken:CreatePipeline' :: CreatePipeline -> Text
clientRequestToken} -> Text
clientRequestToken) (\s :: CreatePipeline
s@CreatePipeline' {} Text
a -> CreatePipeline
s {$sel:clientRequestToken:CreatePipeline' :: Text
clientRequestToken = Text
a} :: CreatePipeline)

-- | The Amazon Resource Name (ARN) of the role used by the pipeline to
-- access and create resources.
createPipeline_roleArn :: Lens.Lens' CreatePipeline Prelude.Text
createPipeline_roleArn :: Lens' CreatePipeline Text
createPipeline_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipeline' {Text
roleArn :: Text
$sel:roleArn:CreatePipeline' :: CreatePipeline -> Text
roleArn} -> Text
roleArn) (\s :: CreatePipeline
s@CreatePipeline' {} Text
a -> CreatePipeline
s {$sel:roleArn:CreatePipeline' :: Text
roleArn = Text
a} :: CreatePipeline)

instance Core.AWSRequest CreatePipeline where
  type
    AWSResponse CreatePipeline =
      CreatePipelineResponse
  request :: (Service -> Service) -> CreatePipeline -> Request CreatePipeline
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 CreatePipeline
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreatePipeline)))
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 -> CreatePipelineResponse
CreatePipelineResponse'
            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
"PipelineArn")
            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 CreatePipeline where
  hashWithSalt :: Int -> CreatePipeline -> Int
hashWithSalt Int
_salt CreatePipeline' {Maybe [Tag]
Maybe Text
Maybe ParallelismConfiguration
Maybe PipelineDefinitionS3Location
Text
roleArn :: Text
clientRequestToken :: Text
pipelineName :: Text
tags :: Maybe [Tag]
pipelineDisplayName :: Maybe Text
pipelineDescription :: Maybe Text
pipelineDefinitionS3Location :: Maybe PipelineDefinitionS3Location
pipelineDefinition :: Maybe Text
parallelismConfiguration :: Maybe ParallelismConfiguration
$sel:roleArn:CreatePipeline' :: CreatePipeline -> Text
$sel:clientRequestToken:CreatePipeline' :: CreatePipeline -> Text
$sel:pipelineName:CreatePipeline' :: CreatePipeline -> Text
$sel:tags:CreatePipeline' :: CreatePipeline -> Maybe [Tag]
$sel:pipelineDisplayName:CreatePipeline' :: CreatePipeline -> Maybe Text
$sel:pipelineDescription:CreatePipeline' :: CreatePipeline -> Maybe Text
$sel:pipelineDefinitionS3Location:CreatePipeline' :: CreatePipeline -> Maybe PipelineDefinitionS3Location
$sel:pipelineDefinition:CreatePipeline' :: CreatePipeline -> Maybe Text
$sel:parallelismConfiguration:CreatePipeline' :: CreatePipeline -> 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` Maybe Text
pipelineDefinition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PipelineDefinitionS3Location
pipelineDefinitionS3Location
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pipelineDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pipelineDisplayName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pipelineName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn

instance Prelude.NFData CreatePipeline where
  rnf :: CreatePipeline -> ()
rnf CreatePipeline' {Maybe [Tag]
Maybe Text
Maybe ParallelismConfiguration
Maybe PipelineDefinitionS3Location
Text
roleArn :: Text
clientRequestToken :: Text
pipelineName :: Text
tags :: Maybe [Tag]
pipelineDisplayName :: Maybe Text
pipelineDescription :: Maybe Text
pipelineDefinitionS3Location :: Maybe PipelineDefinitionS3Location
pipelineDefinition :: Maybe Text
parallelismConfiguration :: Maybe ParallelismConfiguration
$sel:roleArn:CreatePipeline' :: CreatePipeline -> Text
$sel:clientRequestToken:CreatePipeline' :: CreatePipeline -> Text
$sel:pipelineName:CreatePipeline' :: CreatePipeline -> Text
$sel:tags:CreatePipeline' :: CreatePipeline -> Maybe [Tag]
$sel:pipelineDisplayName:CreatePipeline' :: CreatePipeline -> Maybe Text
$sel:pipelineDescription:CreatePipeline' :: CreatePipeline -> Maybe Text
$sel:pipelineDefinitionS3Location:CreatePipeline' :: CreatePipeline -> Maybe PipelineDefinitionS3Location
$sel:pipelineDefinition:CreatePipeline' :: CreatePipeline -> Maybe Text
$sel:parallelismConfiguration:CreatePipeline' :: CreatePipeline -> 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 Maybe Text
pipelineDefinition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PipelineDefinitionS3Location
pipelineDefinitionS3Location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pipelineDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pipelineDisplayName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
pipelineName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn

instance Data.ToHeaders CreatePipeline where
  toHeaders :: CreatePipeline -> 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.CreatePipeline" :: 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 CreatePipeline where
  toJSON :: CreatePipeline -> Value
toJSON CreatePipeline' {Maybe [Tag]
Maybe Text
Maybe ParallelismConfiguration
Maybe PipelineDefinitionS3Location
Text
roleArn :: Text
clientRequestToken :: Text
pipelineName :: Text
tags :: Maybe [Tag]
pipelineDisplayName :: Maybe Text
pipelineDescription :: Maybe Text
pipelineDefinitionS3Location :: Maybe PipelineDefinitionS3Location
pipelineDefinition :: Maybe Text
parallelismConfiguration :: Maybe ParallelismConfiguration
$sel:roleArn:CreatePipeline' :: CreatePipeline -> Text
$sel:clientRequestToken:CreatePipeline' :: CreatePipeline -> Text
$sel:pipelineName:CreatePipeline' :: CreatePipeline -> Text
$sel:tags:CreatePipeline' :: CreatePipeline -> Maybe [Tag]
$sel:pipelineDisplayName:CreatePipeline' :: CreatePipeline -> Maybe Text
$sel:pipelineDescription:CreatePipeline' :: CreatePipeline -> Maybe Text
$sel:pipelineDefinitionS3Location:CreatePipeline' :: CreatePipeline -> Maybe PipelineDefinitionS3Location
$sel:pipelineDefinition:CreatePipeline' :: CreatePipeline -> Maybe Text
$sel:parallelismConfiguration:CreatePipeline' :: CreatePipeline -> 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,
            (Key
"PipelineDefinition" 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
pipelineDefinition,
            (Key
"PipelineDefinitionS3Location" 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 PipelineDefinitionS3Location
pipelineDefinitionS3Location,
            (Key
"PipelineDescription" 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
pipelineDescription,
            (Key
"PipelineDisplayName" 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
pipelineDisplayName,
            (Key
"Tags" 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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"PipelineName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
pipelineName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ClientRequestToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clientRequestToken),
            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 CreatePipeline where
  toPath :: CreatePipeline -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newCreatePipelineResponse' smart constructor.
data CreatePipelineResponse = CreatePipelineResponse'
  { -- | The Amazon Resource Name (ARN) of the created pipeline.
    CreatePipelineResponse -> Maybe Text
pipelineArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreatePipelineResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreatePipelineResponse -> CreatePipelineResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePipelineResponse -> CreatePipelineResponse -> Bool
$c/= :: CreatePipelineResponse -> CreatePipelineResponse -> Bool
== :: CreatePipelineResponse -> CreatePipelineResponse -> Bool
$c== :: CreatePipelineResponse -> CreatePipelineResponse -> Bool
Prelude.Eq, ReadPrec [CreatePipelineResponse]
ReadPrec CreatePipelineResponse
Int -> ReadS CreatePipelineResponse
ReadS [CreatePipelineResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePipelineResponse]
$creadListPrec :: ReadPrec [CreatePipelineResponse]
readPrec :: ReadPrec CreatePipelineResponse
$creadPrec :: ReadPrec CreatePipelineResponse
readList :: ReadS [CreatePipelineResponse]
$creadList :: ReadS [CreatePipelineResponse]
readsPrec :: Int -> ReadS CreatePipelineResponse
$creadsPrec :: Int -> ReadS CreatePipelineResponse
Prelude.Read, Int -> CreatePipelineResponse -> ShowS
[CreatePipelineResponse] -> ShowS
CreatePipelineResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePipelineResponse] -> ShowS
$cshowList :: [CreatePipelineResponse] -> ShowS
show :: CreatePipelineResponse -> String
$cshow :: CreatePipelineResponse -> String
showsPrec :: Int -> CreatePipelineResponse -> ShowS
$cshowsPrec :: Int -> CreatePipelineResponse -> ShowS
Prelude.Show, forall x. Rep CreatePipelineResponse x -> CreatePipelineResponse
forall x. CreatePipelineResponse -> Rep CreatePipelineResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreatePipelineResponse x -> CreatePipelineResponse
$cfrom :: forall x. CreatePipelineResponse -> Rep CreatePipelineResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreatePipelineResponse' 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:
--
-- 'pipelineArn', 'createPipelineResponse_pipelineArn' - The Amazon Resource Name (ARN) of the created pipeline.
--
-- 'httpStatus', 'createPipelineResponse_httpStatus' - The response's http status code.
newCreatePipelineResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreatePipelineResponse
newCreatePipelineResponse :: Int -> CreatePipelineResponse
newCreatePipelineResponse Int
pHttpStatus_ =
  CreatePipelineResponse'
    { $sel:pipelineArn:CreatePipelineResponse' :: Maybe Text
pipelineArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreatePipelineResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the created pipeline.
createPipelineResponse_pipelineArn :: Lens.Lens' CreatePipelineResponse (Prelude.Maybe Prelude.Text)
createPipelineResponse_pipelineArn :: Lens' CreatePipelineResponse (Maybe Text)
createPipelineResponse_pipelineArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePipelineResponse' {Maybe Text
pipelineArn :: Maybe Text
$sel:pipelineArn:CreatePipelineResponse' :: CreatePipelineResponse -> Maybe Text
pipelineArn} -> Maybe Text
pipelineArn) (\s :: CreatePipelineResponse
s@CreatePipelineResponse' {} Maybe Text
a -> CreatePipelineResponse
s {$sel:pipelineArn:CreatePipelineResponse' :: Maybe Text
pipelineArn = Maybe Text
a} :: CreatePipelineResponse)

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

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