{-# 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.KafkaConnect.CreateCustomPlugin
-- 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 custom plugin using the specified properties.
module Amazonka.KafkaConnect.CreateCustomPlugin
  ( -- * Creating a Request
    CreateCustomPlugin (..),
    newCreateCustomPlugin,

    -- * Request Lenses
    createCustomPlugin_description,
    createCustomPlugin_contentType,
    createCustomPlugin_location,
    createCustomPlugin_name,

    -- * Destructuring the Response
    CreateCustomPluginResponse (..),
    newCreateCustomPluginResponse,

    -- * Response Lenses
    createCustomPluginResponse_customPluginArn,
    createCustomPluginResponse_customPluginState,
    createCustomPluginResponse_name,
    createCustomPluginResponse_revision,
    createCustomPluginResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateCustomPlugin' smart constructor.
data CreateCustomPlugin = CreateCustomPlugin'
  { -- | A summary description of the custom plugin.
    CreateCustomPlugin -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The type of the plugin file.
    CreateCustomPlugin -> CustomPluginContentType
contentType :: CustomPluginContentType,
    -- | Information about the location of a custom plugin.
    CreateCustomPlugin -> CustomPluginLocation
location :: CustomPluginLocation,
    -- | The name of the custom plugin.
    CreateCustomPlugin -> Text
name :: Prelude.Text
  }
  deriving (CreateCustomPlugin -> CreateCustomPlugin -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCustomPlugin -> CreateCustomPlugin -> Bool
$c/= :: CreateCustomPlugin -> CreateCustomPlugin -> Bool
== :: CreateCustomPlugin -> CreateCustomPlugin -> Bool
$c== :: CreateCustomPlugin -> CreateCustomPlugin -> Bool
Prelude.Eq, ReadPrec [CreateCustomPlugin]
ReadPrec CreateCustomPlugin
Int -> ReadS CreateCustomPlugin
ReadS [CreateCustomPlugin]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCustomPlugin]
$creadListPrec :: ReadPrec [CreateCustomPlugin]
readPrec :: ReadPrec CreateCustomPlugin
$creadPrec :: ReadPrec CreateCustomPlugin
readList :: ReadS [CreateCustomPlugin]
$creadList :: ReadS [CreateCustomPlugin]
readsPrec :: Int -> ReadS CreateCustomPlugin
$creadsPrec :: Int -> ReadS CreateCustomPlugin
Prelude.Read, Int -> CreateCustomPlugin -> ShowS
[CreateCustomPlugin] -> ShowS
CreateCustomPlugin -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCustomPlugin] -> ShowS
$cshowList :: [CreateCustomPlugin] -> ShowS
show :: CreateCustomPlugin -> String
$cshow :: CreateCustomPlugin -> String
showsPrec :: Int -> CreateCustomPlugin -> ShowS
$cshowsPrec :: Int -> CreateCustomPlugin -> ShowS
Prelude.Show, forall x. Rep CreateCustomPlugin x -> CreateCustomPlugin
forall x. CreateCustomPlugin -> Rep CreateCustomPlugin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateCustomPlugin x -> CreateCustomPlugin
$cfrom :: forall x. CreateCustomPlugin -> Rep CreateCustomPlugin x
Prelude.Generic)

-- |
-- Create a value of 'CreateCustomPlugin' 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:
--
-- 'description', 'createCustomPlugin_description' - A summary description of the custom plugin.
--
-- 'contentType', 'createCustomPlugin_contentType' - The type of the plugin file.
--
-- 'location', 'createCustomPlugin_location' - Information about the location of a custom plugin.
--
-- 'name', 'createCustomPlugin_name' - The name of the custom plugin.
newCreateCustomPlugin ::
  -- | 'contentType'
  CustomPluginContentType ->
  -- | 'location'
  CustomPluginLocation ->
  -- | 'name'
  Prelude.Text ->
  CreateCustomPlugin
newCreateCustomPlugin :: CustomPluginContentType
-> CustomPluginLocation -> Text -> CreateCustomPlugin
newCreateCustomPlugin CustomPluginContentType
pContentType_ CustomPluginLocation
pLocation_ Text
pName_ =
  CreateCustomPlugin'
    { $sel:description:CreateCustomPlugin' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:contentType:CreateCustomPlugin' :: CustomPluginContentType
contentType = CustomPluginContentType
pContentType_,
      $sel:location:CreateCustomPlugin' :: CustomPluginLocation
location = CustomPluginLocation
pLocation_,
      $sel:name:CreateCustomPlugin' :: Text
name = Text
pName_
    }

-- | A summary description of the custom plugin.
createCustomPlugin_description :: Lens.Lens' CreateCustomPlugin (Prelude.Maybe Prelude.Text)
createCustomPlugin_description :: Lens' CreateCustomPlugin (Maybe Text)
createCustomPlugin_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomPlugin' {Maybe Text
description :: Maybe Text
$sel:description:CreateCustomPlugin' :: CreateCustomPlugin -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateCustomPlugin
s@CreateCustomPlugin' {} Maybe Text
a -> CreateCustomPlugin
s {$sel:description:CreateCustomPlugin' :: Maybe Text
description = Maybe Text
a} :: CreateCustomPlugin)

-- | The type of the plugin file.
createCustomPlugin_contentType :: Lens.Lens' CreateCustomPlugin CustomPluginContentType
createCustomPlugin_contentType :: Lens' CreateCustomPlugin CustomPluginContentType
createCustomPlugin_contentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomPlugin' {CustomPluginContentType
contentType :: CustomPluginContentType
$sel:contentType:CreateCustomPlugin' :: CreateCustomPlugin -> CustomPluginContentType
contentType} -> CustomPluginContentType
contentType) (\s :: CreateCustomPlugin
s@CreateCustomPlugin' {} CustomPluginContentType
a -> CreateCustomPlugin
s {$sel:contentType:CreateCustomPlugin' :: CustomPluginContentType
contentType = CustomPluginContentType
a} :: CreateCustomPlugin)

-- | Information about the location of a custom plugin.
createCustomPlugin_location :: Lens.Lens' CreateCustomPlugin CustomPluginLocation
createCustomPlugin_location :: Lens' CreateCustomPlugin CustomPluginLocation
createCustomPlugin_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomPlugin' {CustomPluginLocation
location :: CustomPluginLocation
$sel:location:CreateCustomPlugin' :: CreateCustomPlugin -> CustomPluginLocation
location} -> CustomPluginLocation
location) (\s :: CreateCustomPlugin
s@CreateCustomPlugin' {} CustomPluginLocation
a -> CreateCustomPlugin
s {$sel:location:CreateCustomPlugin' :: CustomPluginLocation
location = CustomPluginLocation
a} :: CreateCustomPlugin)

-- | The name of the custom plugin.
createCustomPlugin_name :: Lens.Lens' CreateCustomPlugin Prelude.Text
createCustomPlugin_name :: Lens' CreateCustomPlugin Text
createCustomPlugin_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomPlugin' {Text
name :: Text
$sel:name:CreateCustomPlugin' :: CreateCustomPlugin -> Text
name} -> Text
name) (\s :: CreateCustomPlugin
s@CreateCustomPlugin' {} Text
a -> CreateCustomPlugin
s {$sel:name:CreateCustomPlugin' :: Text
name = Text
a} :: CreateCustomPlugin)

instance Core.AWSRequest CreateCustomPlugin where
  type
    AWSResponse CreateCustomPlugin =
      CreateCustomPluginResponse
  request :: (Service -> Service)
-> CreateCustomPlugin -> Request CreateCustomPlugin
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 CreateCustomPlugin
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateCustomPlugin)))
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
-> Maybe CustomPluginState
-> Maybe Text
-> Maybe Integer
-> Int
-> CreateCustomPluginResponse
CreateCustomPluginResponse'
            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
"customPluginArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"customPluginState")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"revision")
            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 CreateCustomPlugin where
  hashWithSalt :: Int -> CreateCustomPlugin -> Int
hashWithSalt Int
_salt CreateCustomPlugin' {Maybe Text
Text
CustomPluginContentType
CustomPluginLocation
name :: Text
location :: CustomPluginLocation
contentType :: CustomPluginContentType
description :: Maybe Text
$sel:name:CreateCustomPlugin' :: CreateCustomPlugin -> Text
$sel:location:CreateCustomPlugin' :: CreateCustomPlugin -> CustomPluginLocation
$sel:contentType:CreateCustomPlugin' :: CreateCustomPlugin -> CustomPluginContentType
$sel:description:CreateCustomPlugin' :: CreateCustomPlugin -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CustomPluginContentType
contentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CustomPluginLocation
location
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateCustomPlugin where
  rnf :: CreateCustomPlugin -> ()
rnf CreateCustomPlugin' {Maybe Text
Text
CustomPluginContentType
CustomPluginLocation
name :: Text
location :: CustomPluginLocation
contentType :: CustomPluginContentType
description :: Maybe Text
$sel:name:CreateCustomPlugin' :: CreateCustomPlugin -> Text
$sel:location:CreateCustomPlugin' :: CreateCustomPlugin -> CustomPluginLocation
$sel:contentType:CreateCustomPlugin' :: CreateCustomPlugin -> CustomPluginContentType
$sel:description:CreateCustomPlugin' :: CreateCustomPlugin -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CustomPluginContentType
contentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CustomPluginLocation
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders CreateCustomPlugin where
  toHeaders :: CreateCustomPlugin -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateCustomPlugin where
  toJSON :: CreateCustomPlugin -> Value
toJSON CreateCustomPlugin' {Maybe Text
Text
CustomPluginContentType
CustomPluginLocation
name :: Text
location :: CustomPluginLocation
contentType :: CustomPluginContentType
description :: Maybe Text
$sel:name:CreateCustomPlugin' :: CreateCustomPlugin -> Text
$sel:location:CreateCustomPlugin' :: CreateCustomPlugin -> CustomPluginLocation
$sel:contentType:CreateCustomPlugin' :: CreateCustomPlugin -> CustomPluginContentType
$sel:description:CreateCustomPlugin' :: CreateCustomPlugin -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"description" 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
description,
            forall a. a -> Maybe a
Prelude.Just (Key
"contentType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= CustomPluginContentType
contentType),
            forall a. a -> Maybe a
Prelude.Just (Key
"location" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= CustomPluginLocation
location),
            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 CreateCustomPlugin where
  toPath :: CreateCustomPlugin -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/custom-plugins"

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

-- | /See:/ 'newCreateCustomPluginResponse' smart constructor.
data CreateCustomPluginResponse = CreateCustomPluginResponse'
  { -- | The Amazon Resource Name (ARN) that Amazon assigned to the custom
    -- plugin.
    CreateCustomPluginResponse -> Maybe Text
customPluginArn :: Prelude.Maybe Prelude.Text,
    -- | The state of the custom plugin.
    CreateCustomPluginResponse -> Maybe CustomPluginState
customPluginState :: Prelude.Maybe CustomPluginState,
    -- | The name of the custom plugin.
    CreateCustomPluginResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The revision of the custom plugin.
    CreateCustomPluginResponse -> Maybe Integer
revision :: Prelude.Maybe Prelude.Integer,
    -- | The response's http status code.
    CreateCustomPluginResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateCustomPluginResponse -> CreateCustomPluginResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCustomPluginResponse -> CreateCustomPluginResponse -> Bool
$c/= :: CreateCustomPluginResponse -> CreateCustomPluginResponse -> Bool
== :: CreateCustomPluginResponse -> CreateCustomPluginResponse -> Bool
$c== :: CreateCustomPluginResponse -> CreateCustomPluginResponse -> Bool
Prelude.Eq, ReadPrec [CreateCustomPluginResponse]
ReadPrec CreateCustomPluginResponse
Int -> ReadS CreateCustomPluginResponse
ReadS [CreateCustomPluginResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCustomPluginResponse]
$creadListPrec :: ReadPrec [CreateCustomPluginResponse]
readPrec :: ReadPrec CreateCustomPluginResponse
$creadPrec :: ReadPrec CreateCustomPluginResponse
readList :: ReadS [CreateCustomPluginResponse]
$creadList :: ReadS [CreateCustomPluginResponse]
readsPrec :: Int -> ReadS CreateCustomPluginResponse
$creadsPrec :: Int -> ReadS CreateCustomPluginResponse
Prelude.Read, Int -> CreateCustomPluginResponse -> ShowS
[CreateCustomPluginResponse] -> ShowS
CreateCustomPluginResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCustomPluginResponse] -> ShowS
$cshowList :: [CreateCustomPluginResponse] -> ShowS
show :: CreateCustomPluginResponse -> String
$cshow :: CreateCustomPluginResponse -> String
showsPrec :: Int -> CreateCustomPluginResponse -> ShowS
$cshowsPrec :: Int -> CreateCustomPluginResponse -> ShowS
Prelude.Show, forall x.
Rep CreateCustomPluginResponse x -> CreateCustomPluginResponse
forall x.
CreateCustomPluginResponse -> Rep CreateCustomPluginResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateCustomPluginResponse x -> CreateCustomPluginResponse
$cfrom :: forall x.
CreateCustomPluginResponse -> Rep CreateCustomPluginResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateCustomPluginResponse' 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:
--
-- 'customPluginArn', 'createCustomPluginResponse_customPluginArn' - The Amazon Resource Name (ARN) that Amazon assigned to the custom
-- plugin.
--
-- 'customPluginState', 'createCustomPluginResponse_customPluginState' - The state of the custom plugin.
--
-- 'name', 'createCustomPluginResponse_name' - The name of the custom plugin.
--
-- 'revision', 'createCustomPluginResponse_revision' - The revision of the custom plugin.
--
-- 'httpStatus', 'createCustomPluginResponse_httpStatus' - The response's http status code.
newCreateCustomPluginResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateCustomPluginResponse
newCreateCustomPluginResponse :: Int -> CreateCustomPluginResponse
newCreateCustomPluginResponse Int
pHttpStatus_ =
  CreateCustomPluginResponse'
    { $sel:customPluginArn:CreateCustomPluginResponse' :: Maybe Text
customPluginArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:customPluginState:CreateCustomPluginResponse' :: Maybe CustomPluginState
customPluginState = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateCustomPluginResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:revision:CreateCustomPluginResponse' :: Maybe Integer
revision = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateCustomPluginResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) that Amazon assigned to the custom
-- plugin.
createCustomPluginResponse_customPluginArn :: Lens.Lens' CreateCustomPluginResponse (Prelude.Maybe Prelude.Text)
createCustomPluginResponse_customPluginArn :: Lens' CreateCustomPluginResponse (Maybe Text)
createCustomPluginResponse_customPluginArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomPluginResponse' {Maybe Text
customPluginArn :: Maybe Text
$sel:customPluginArn:CreateCustomPluginResponse' :: CreateCustomPluginResponse -> Maybe Text
customPluginArn} -> Maybe Text
customPluginArn) (\s :: CreateCustomPluginResponse
s@CreateCustomPluginResponse' {} Maybe Text
a -> CreateCustomPluginResponse
s {$sel:customPluginArn:CreateCustomPluginResponse' :: Maybe Text
customPluginArn = Maybe Text
a} :: CreateCustomPluginResponse)

-- | The state of the custom plugin.
createCustomPluginResponse_customPluginState :: Lens.Lens' CreateCustomPluginResponse (Prelude.Maybe CustomPluginState)
createCustomPluginResponse_customPluginState :: Lens' CreateCustomPluginResponse (Maybe CustomPluginState)
createCustomPluginResponse_customPluginState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomPluginResponse' {Maybe CustomPluginState
customPluginState :: Maybe CustomPluginState
$sel:customPluginState:CreateCustomPluginResponse' :: CreateCustomPluginResponse -> Maybe CustomPluginState
customPluginState} -> Maybe CustomPluginState
customPluginState) (\s :: CreateCustomPluginResponse
s@CreateCustomPluginResponse' {} Maybe CustomPluginState
a -> CreateCustomPluginResponse
s {$sel:customPluginState:CreateCustomPluginResponse' :: Maybe CustomPluginState
customPluginState = Maybe CustomPluginState
a} :: CreateCustomPluginResponse)

-- | The name of the custom plugin.
createCustomPluginResponse_name :: Lens.Lens' CreateCustomPluginResponse (Prelude.Maybe Prelude.Text)
createCustomPluginResponse_name :: Lens' CreateCustomPluginResponse (Maybe Text)
createCustomPluginResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomPluginResponse' {Maybe Text
name :: Maybe Text
$sel:name:CreateCustomPluginResponse' :: CreateCustomPluginResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateCustomPluginResponse
s@CreateCustomPluginResponse' {} Maybe Text
a -> CreateCustomPluginResponse
s {$sel:name:CreateCustomPluginResponse' :: Maybe Text
name = Maybe Text
a} :: CreateCustomPluginResponse)

-- | The revision of the custom plugin.
createCustomPluginResponse_revision :: Lens.Lens' CreateCustomPluginResponse (Prelude.Maybe Prelude.Integer)
createCustomPluginResponse_revision :: Lens' CreateCustomPluginResponse (Maybe Integer)
createCustomPluginResponse_revision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomPluginResponse' {Maybe Integer
revision :: Maybe Integer
$sel:revision:CreateCustomPluginResponse' :: CreateCustomPluginResponse -> Maybe Integer
revision} -> Maybe Integer
revision) (\s :: CreateCustomPluginResponse
s@CreateCustomPluginResponse' {} Maybe Integer
a -> CreateCustomPluginResponse
s {$sel:revision:CreateCustomPluginResponse' :: Maybe Integer
revision = Maybe Integer
a} :: CreateCustomPluginResponse)

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

instance Prelude.NFData CreateCustomPluginResponse where
  rnf :: CreateCustomPluginResponse -> ()
rnf CreateCustomPluginResponse' {Int
Maybe Integer
Maybe Text
Maybe CustomPluginState
httpStatus :: Int
revision :: Maybe Integer
name :: Maybe Text
customPluginState :: Maybe CustomPluginState
customPluginArn :: Maybe Text
$sel:httpStatus:CreateCustomPluginResponse' :: CreateCustomPluginResponse -> Int
$sel:revision:CreateCustomPluginResponse' :: CreateCustomPluginResponse -> Maybe Integer
$sel:name:CreateCustomPluginResponse' :: CreateCustomPluginResponse -> Maybe Text
$sel:customPluginState:CreateCustomPluginResponse' :: CreateCustomPluginResponse -> Maybe CustomPluginState
$sel:customPluginArn:CreateCustomPluginResponse' :: CreateCustomPluginResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
customPluginArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomPluginState
customPluginState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
revision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus