{-# 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.Comprehend.CreateEndpoint
-- 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 model-specific endpoint for synchronous inference for a
-- previously trained custom model For information about endpoints, see
-- <https://docs.aws.amazon.com/comprehend/latest/dg/manage-endpoints.html Managing endpoints>.
module Amazonka.Comprehend.CreateEndpoint
  ( -- * Creating a Request
    CreateEndpoint (..),
    newCreateEndpoint,

    -- * Request Lenses
    createEndpoint_clientRequestToken,
    createEndpoint_dataAccessRoleArn,
    createEndpoint_tags,
    createEndpoint_endpointName,
    createEndpoint_modelArn,
    createEndpoint_desiredInferenceUnits,

    -- * Destructuring the Response
    CreateEndpointResponse (..),
    newCreateEndpointResponse,

    -- * Response Lenses
    createEndpointResponse_endpointArn,
    createEndpointResponse_httpStatus,
  )
where

import Amazonka.Comprehend.Types
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

-- | /See:/ 'newCreateEndpoint' smart constructor.
data CreateEndpoint = CreateEndpoint'
  { -- | An idempotency token provided by the customer. If this token matches a
    -- previous endpoint creation request, Amazon Comprehend will not return a
    -- @ResourceInUseException@.
    CreateEndpoint -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the AWS identity and Access Management
    -- (IAM) role that grants Amazon Comprehend read access to trained custom
    -- models encrypted with a customer managed key (ModelKmsKeyId).
    CreateEndpoint -> Maybe Text
dataAccessRoleArn :: Prelude.Maybe Prelude.Text,
    -- | Tags associated with the endpoint being created. A tag is a key-value
    -- pair that adds metadata to the endpoint. For example, a tag with
    -- \"Sales\" as the key might be added to an endpoint to indicate its use
    -- by the sales department.
    CreateEndpoint -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | This is the descriptive suffix that becomes part of the @EndpointArn@
    -- used for all subsequent requests to this resource.
    CreateEndpoint -> Text
endpointName :: Prelude.Text,
    -- | The Amazon Resource Number (ARN) of the model to which the endpoint will
    -- be attached.
    CreateEndpoint -> Text
modelArn :: Prelude.Text,
    -- | The desired number of inference units to be used by the model using this
    -- endpoint. Each inference unit represents of a throughput of 100
    -- characters per second.
    CreateEndpoint -> Natural
desiredInferenceUnits :: Prelude.Natural
  }
  deriving (CreateEndpoint -> CreateEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateEndpoint -> CreateEndpoint -> Bool
$c/= :: CreateEndpoint -> CreateEndpoint -> Bool
== :: CreateEndpoint -> CreateEndpoint -> Bool
$c== :: CreateEndpoint -> CreateEndpoint -> Bool
Prelude.Eq, ReadPrec [CreateEndpoint]
ReadPrec CreateEndpoint
Int -> ReadS CreateEndpoint
ReadS [CreateEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateEndpoint]
$creadListPrec :: ReadPrec [CreateEndpoint]
readPrec :: ReadPrec CreateEndpoint
$creadPrec :: ReadPrec CreateEndpoint
readList :: ReadS [CreateEndpoint]
$creadList :: ReadS [CreateEndpoint]
readsPrec :: Int -> ReadS CreateEndpoint
$creadsPrec :: Int -> ReadS CreateEndpoint
Prelude.Read, Int -> CreateEndpoint -> ShowS
[CreateEndpoint] -> ShowS
CreateEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateEndpoint] -> ShowS
$cshowList :: [CreateEndpoint] -> ShowS
show :: CreateEndpoint -> String
$cshow :: CreateEndpoint -> String
showsPrec :: Int -> CreateEndpoint -> ShowS
$cshowsPrec :: Int -> CreateEndpoint -> ShowS
Prelude.Show, forall x. Rep CreateEndpoint x -> CreateEndpoint
forall x. CreateEndpoint -> Rep CreateEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateEndpoint x -> CreateEndpoint
$cfrom :: forall x. CreateEndpoint -> Rep CreateEndpoint x
Prelude.Generic)

-- |
-- Create a value of 'CreateEndpoint' 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:
--
-- 'clientRequestToken', 'createEndpoint_clientRequestToken' - An idempotency token provided by the customer. If this token matches a
-- previous endpoint creation request, Amazon Comprehend will not return a
-- @ResourceInUseException@.
--
-- 'dataAccessRoleArn', 'createEndpoint_dataAccessRoleArn' - The Amazon Resource Name (ARN) of the AWS identity and Access Management
-- (IAM) role that grants Amazon Comprehend read access to trained custom
-- models encrypted with a customer managed key (ModelKmsKeyId).
--
-- 'tags', 'createEndpoint_tags' - Tags associated with the endpoint being created. A tag is a key-value
-- pair that adds metadata to the endpoint. For example, a tag with
-- \"Sales\" as the key might be added to an endpoint to indicate its use
-- by the sales department.
--
-- 'endpointName', 'createEndpoint_endpointName' - This is the descriptive suffix that becomes part of the @EndpointArn@
-- used for all subsequent requests to this resource.
--
-- 'modelArn', 'createEndpoint_modelArn' - The Amazon Resource Number (ARN) of the model to which the endpoint will
-- be attached.
--
-- 'desiredInferenceUnits', 'createEndpoint_desiredInferenceUnits' - The desired number of inference units to be used by the model using this
-- endpoint. Each inference unit represents of a throughput of 100
-- characters per second.
newCreateEndpoint ::
  -- | 'endpointName'
  Prelude.Text ->
  -- | 'modelArn'
  Prelude.Text ->
  -- | 'desiredInferenceUnits'
  Prelude.Natural ->
  CreateEndpoint
newCreateEndpoint :: Text -> Text -> Natural -> CreateEndpoint
newCreateEndpoint
  Text
pEndpointName_
  Text
pModelArn_
  Natural
pDesiredInferenceUnits_ =
    CreateEndpoint'
      { $sel:clientRequestToken:CreateEndpoint' :: Maybe Text
clientRequestToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:dataAccessRoleArn:CreateEndpoint' :: Maybe Text
dataAccessRoleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateEndpoint' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:endpointName:CreateEndpoint' :: Text
endpointName = Text
pEndpointName_,
        $sel:modelArn:CreateEndpoint' :: Text
modelArn = Text
pModelArn_,
        $sel:desiredInferenceUnits:CreateEndpoint' :: Natural
desiredInferenceUnits = Natural
pDesiredInferenceUnits_
      }

-- | An idempotency token provided by the customer. If this token matches a
-- previous endpoint creation request, Amazon Comprehend will not return a
-- @ResourceInUseException@.
createEndpoint_clientRequestToken :: Lens.Lens' CreateEndpoint (Prelude.Maybe Prelude.Text)
createEndpoint_clientRequestToken :: Lens' CreateEndpoint (Maybe Text)
createEndpoint_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:CreateEndpoint' :: CreateEndpoint -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: CreateEndpoint
s@CreateEndpoint' {} Maybe Text
a -> CreateEndpoint
s {$sel:clientRequestToken:CreateEndpoint' :: Maybe Text
clientRequestToken = Maybe Text
a} :: CreateEndpoint)

-- | The Amazon Resource Name (ARN) of the AWS identity and Access Management
-- (IAM) role that grants Amazon Comprehend read access to trained custom
-- models encrypted with a customer managed key (ModelKmsKeyId).
createEndpoint_dataAccessRoleArn :: Lens.Lens' CreateEndpoint (Prelude.Maybe Prelude.Text)
createEndpoint_dataAccessRoleArn :: Lens' CreateEndpoint (Maybe Text)
createEndpoint_dataAccessRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Maybe Text
dataAccessRoleArn :: Maybe Text
$sel:dataAccessRoleArn:CreateEndpoint' :: CreateEndpoint -> Maybe Text
dataAccessRoleArn} -> Maybe Text
dataAccessRoleArn) (\s :: CreateEndpoint
s@CreateEndpoint' {} Maybe Text
a -> CreateEndpoint
s {$sel:dataAccessRoleArn:CreateEndpoint' :: Maybe Text
dataAccessRoleArn = Maybe Text
a} :: CreateEndpoint)

-- | Tags associated with the endpoint being created. A tag is a key-value
-- pair that adds metadata to the endpoint. For example, a tag with
-- \"Sales\" as the key might be added to an endpoint to indicate its use
-- by the sales department.
createEndpoint_tags :: Lens.Lens' CreateEndpoint (Prelude.Maybe [Tag])
createEndpoint_tags :: Lens' CreateEndpoint (Maybe [Tag])
createEndpoint_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateEndpoint' :: CreateEndpoint -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateEndpoint
s@CreateEndpoint' {} Maybe [Tag]
a -> CreateEndpoint
s {$sel:tags:CreateEndpoint' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateEndpoint) 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

-- | This is the descriptive suffix that becomes part of the @EndpointArn@
-- used for all subsequent requests to this resource.
createEndpoint_endpointName :: Lens.Lens' CreateEndpoint Prelude.Text
createEndpoint_endpointName :: Lens' CreateEndpoint Text
createEndpoint_endpointName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Text
endpointName :: Text
$sel:endpointName:CreateEndpoint' :: CreateEndpoint -> Text
endpointName} -> Text
endpointName) (\s :: CreateEndpoint
s@CreateEndpoint' {} Text
a -> CreateEndpoint
s {$sel:endpointName:CreateEndpoint' :: Text
endpointName = Text
a} :: CreateEndpoint)

-- | The Amazon Resource Number (ARN) of the model to which the endpoint will
-- be attached.
createEndpoint_modelArn :: Lens.Lens' CreateEndpoint Prelude.Text
createEndpoint_modelArn :: Lens' CreateEndpoint Text
createEndpoint_modelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Text
modelArn :: Text
$sel:modelArn:CreateEndpoint' :: CreateEndpoint -> Text
modelArn} -> Text
modelArn) (\s :: CreateEndpoint
s@CreateEndpoint' {} Text
a -> CreateEndpoint
s {$sel:modelArn:CreateEndpoint' :: Text
modelArn = Text
a} :: CreateEndpoint)

-- | The desired number of inference units to be used by the model using this
-- endpoint. Each inference unit represents of a throughput of 100
-- characters per second.
createEndpoint_desiredInferenceUnits :: Lens.Lens' CreateEndpoint Prelude.Natural
createEndpoint_desiredInferenceUnits :: Lens' CreateEndpoint Natural
createEndpoint_desiredInferenceUnits = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Natural
desiredInferenceUnits :: Natural
$sel:desiredInferenceUnits:CreateEndpoint' :: CreateEndpoint -> Natural
desiredInferenceUnits} -> Natural
desiredInferenceUnits) (\s :: CreateEndpoint
s@CreateEndpoint' {} Natural
a -> CreateEndpoint
s {$sel:desiredInferenceUnits:CreateEndpoint' :: Natural
desiredInferenceUnits = Natural
a} :: CreateEndpoint)

instance Core.AWSRequest CreateEndpoint where
  type
    AWSResponse CreateEndpoint =
      CreateEndpointResponse
  request :: (Service -> Service) -> CreateEndpoint -> Request CreateEndpoint
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 CreateEndpoint
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateEndpoint)))
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 -> CreateEndpointResponse
CreateEndpointResponse'
            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
"EndpointArn")
            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 CreateEndpoint where
  hashWithSalt :: Int -> CreateEndpoint -> Int
hashWithSalt Int
_salt CreateEndpoint' {Natural
Maybe [Tag]
Maybe Text
Text
desiredInferenceUnits :: Natural
modelArn :: Text
endpointName :: Text
tags :: Maybe [Tag]
dataAccessRoleArn :: Maybe Text
clientRequestToken :: Maybe Text
$sel:desiredInferenceUnits:CreateEndpoint' :: CreateEndpoint -> Natural
$sel:modelArn:CreateEndpoint' :: CreateEndpoint -> Text
$sel:endpointName:CreateEndpoint' :: CreateEndpoint -> Text
$sel:tags:CreateEndpoint' :: CreateEndpoint -> Maybe [Tag]
$sel:dataAccessRoleArn:CreateEndpoint' :: CreateEndpoint -> Maybe Text
$sel:clientRequestToken:CreateEndpoint' :: CreateEndpoint -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dataAccessRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
modelArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
desiredInferenceUnits

instance Prelude.NFData CreateEndpoint where
  rnf :: CreateEndpoint -> ()
rnf CreateEndpoint' {Natural
Maybe [Tag]
Maybe Text
Text
desiredInferenceUnits :: Natural
modelArn :: Text
endpointName :: Text
tags :: Maybe [Tag]
dataAccessRoleArn :: Maybe Text
clientRequestToken :: Maybe Text
$sel:desiredInferenceUnits:CreateEndpoint' :: CreateEndpoint -> Natural
$sel:modelArn:CreateEndpoint' :: CreateEndpoint -> Text
$sel:endpointName:CreateEndpoint' :: CreateEndpoint -> Text
$sel:tags:CreateEndpoint' :: CreateEndpoint -> Maybe [Tag]
$sel:dataAccessRoleArn:CreateEndpoint' :: CreateEndpoint -> Maybe Text
$sel:clientRequestToken:CreateEndpoint' :: CreateEndpoint -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dataAccessRoleArn
      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
endpointName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
modelArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
desiredInferenceUnits

instance Data.ToHeaders CreateEndpoint where
  toHeaders :: CreateEndpoint -> 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
"Comprehend_20171127.CreateEndpoint" ::
                          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 CreateEndpoint where
  toJSON :: CreateEndpoint -> Value
toJSON CreateEndpoint' {Natural
Maybe [Tag]
Maybe Text
Text
desiredInferenceUnits :: Natural
modelArn :: Text
endpointName :: Text
tags :: Maybe [Tag]
dataAccessRoleArn :: Maybe Text
clientRequestToken :: Maybe Text
$sel:desiredInferenceUnits:CreateEndpoint' :: CreateEndpoint -> Natural
$sel:modelArn:CreateEndpoint' :: CreateEndpoint -> Text
$sel:endpointName:CreateEndpoint' :: CreateEndpoint -> Text
$sel:tags:CreateEndpoint' :: CreateEndpoint -> Maybe [Tag]
$sel:dataAccessRoleArn:CreateEndpoint' :: CreateEndpoint -> Maybe Text
$sel:clientRequestToken:CreateEndpoint' :: CreateEndpoint -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientRequestToken" 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
clientRequestToken,
            (Key
"DataAccessRoleArn" 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
dataAccessRoleArn,
            (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
"EndpointName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
endpointName),
            forall a. a -> Maybe a
Prelude.Just (Key
"ModelArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
modelArn),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"DesiredInferenceUnits"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
desiredInferenceUnits
              )
          ]
      )

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

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

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

-- |
-- Create a value of 'CreateEndpointResponse' 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:
--
-- 'endpointArn', 'createEndpointResponse_endpointArn' - The Amazon Resource Number (ARN) of the endpoint being created.
--
-- 'httpStatus', 'createEndpointResponse_httpStatus' - The response's http status code.
newCreateEndpointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateEndpointResponse
newCreateEndpointResponse :: Int -> CreateEndpointResponse
newCreateEndpointResponse Int
pHttpStatus_ =
  CreateEndpointResponse'
    { $sel:endpointArn:CreateEndpointResponse' :: Maybe Text
endpointArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateEndpointResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Number (ARN) of the endpoint being created.
createEndpointResponse_endpointArn :: Lens.Lens' CreateEndpointResponse (Prelude.Maybe Prelude.Text)
createEndpointResponse_endpointArn :: Lens' CreateEndpointResponse (Maybe Text)
createEndpointResponse_endpointArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointResponse' {Maybe Text
endpointArn :: Maybe Text
$sel:endpointArn:CreateEndpointResponse' :: CreateEndpointResponse -> Maybe Text
endpointArn} -> Maybe Text
endpointArn) (\s :: CreateEndpointResponse
s@CreateEndpointResponse' {} Maybe Text
a -> CreateEndpointResponse
s {$sel:endpointArn:CreateEndpointResponse' :: Maybe Text
endpointArn = Maybe Text
a} :: CreateEndpointResponse)

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

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