{-# 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.DescribeEndpoint
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the description of an endpoint.
module Amazonka.SageMaker.DescribeEndpoint
  ( -- * Creating a Request
    DescribeEndpoint (..),
    newDescribeEndpoint,

    -- * Request Lenses
    describeEndpoint_endpointName,

    -- * Destructuring the Response
    DescribeEndpointResponse (..),
    newDescribeEndpointResponse,

    -- * Response Lenses
    describeEndpointResponse_asyncInferenceConfig,
    describeEndpointResponse_dataCaptureConfig,
    describeEndpointResponse_explainerConfig,
    describeEndpointResponse_failureReason,
    describeEndpointResponse_lastDeploymentConfig,
    describeEndpointResponse_pendingDeploymentSummary,
    describeEndpointResponse_productionVariants,
    describeEndpointResponse_shadowProductionVariants,
    describeEndpointResponse_httpStatus,
    describeEndpointResponse_endpointName,
    describeEndpointResponse_endpointArn,
    describeEndpointResponse_endpointConfigName,
    describeEndpointResponse_endpointStatus,
    describeEndpointResponse_creationTime,
    describeEndpointResponse_lastModifiedTime,
  )
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:/ 'newDescribeEndpoint' smart constructor.
data DescribeEndpoint = DescribeEndpoint'
  { -- | The name of the endpoint.
    DescribeEndpoint -> Text
endpointName :: Prelude.Text
  }
  deriving (DescribeEndpoint -> DescribeEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeEndpoint -> DescribeEndpoint -> Bool
$c/= :: DescribeEndpoint -> DescribeEndpoint -> Bool
== :: DescribeEndpoint -> DescribeEndpoint -> Bool
$c== :: DescribeEndpoint -> DescribeEndpoint -> Bool
Prelude.Eq, ReadPrec [DescribeEndpoint]
ReadPrec DescribeEndpoint
Int -> ReadS DescribeEndpoint
ReadS [DescribeEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeEndpoint]
$creadListPrec :: ReadPrec [DescribeEndpoint]
readPrec :: ReadPrec DescribeEndpoint
$creadPrec :: ReadPrec DescribeEndpoint
readList :: ReadS [DescribeEndpoint]
$creadList :: ReadS [DescribeEndpoint]
readsPrec :: Int -> ReadS DescribeEndpoint
$creadsPrec :: Int -> ReadS DescribeEndpoint
Prelude.Read, Int -> DescribeEndpoint -> ShowS
[DescribeEndpoint] -> ShowS
DescribeEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeEndpoint] -> ShowS
$cshowList :: [DescribeEndpoint] -> ShowS
show :: DescribeEndpoint -> String
$cshow :: DescribeEndpoint -> String
showsPrec :: Int -> DescribeEndpoint -> ShowS
$cshowsPrec :: Int -> DescribeEndpoint -> ShowS
Prelude.Show, forall x. Rep DescribeEndpoint x -> DescribeEndpoint
forall x. DescribeEndpoint -> Rep DescribeEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeEndpoint x -> DescribeEndpoint
$cfrom :: forall x. DescribeEndpoint -> Rep DescribeEndpoint x
Prelude.Generic)

-- |
-- Create a value of 'DescribeEndpoint' 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:
--
-- 'endpointName', 'describeEndpoint_endpointName' - The name of the endpoint.
newDescribeEndpoint ::
  -- | 'endpointName'
  Prelude.Text ->
  DescribeEndpoint
newDescribeEndpoint :: Text -> DescribeEndpoint
newDescribeEndpoint Text
pEndpointName_ =
  DescribeEndpoint' {$sel:endpointName:DescribeEndpoint' :: Text
endpointName = Text
pEndpointName_}

-- | The name of the endpoint.
describeEndpoint_endpointName :: Lens.Lens' DescribeEndpoint Prelude.Text
describeEndpoint_endpointName :: Lens' DescribeEndpoint Text
describeEndpoint_endpointName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpoint' {Text
endpointName :: Text
$sel:endpointName:DescribeEndpoint' :: DescribeEndpoint -> Text
endpointName} -> Text
endpointName) (\s :: DescribeEndpoint
s@DescribeEndpoint' {} Text
a -> DescribeEndpoint
s {$sel:endpointName:DescribeEndpoint' :: Text
endpointName = Text
a} :: DescribeEndpoint)

instance Core.AWSRequest DescribeEndpoint where
  type
    AWSResponse DescribeEndpoint =
      DescribeEndpointResponse
  request :: (Service -> Service)
-> DescribeEndpoint -> Request DescribeEndpoint
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 DescribeEndpoint
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeEndpoint)))
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 AsyncInferenceConfig
-> Maybe DataCaptureConfigSummary
-> Maybe ExplainerConfig
-> Maybe Text
-> Maybe DeploymentConfig
-> Maybe PendingDeploymentSummary
-> Maybe (NonEmpty ProductionVariantSummary)
-> Maybe (NonEmpty ProductionVariantSummary)
-> Int
-> Text
-> Text
-> Text
-> EndpointStatus
-> POSIX
-> POSIX
-> DescribeEndpointResponse
DescribeEndpointResponse'
            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
"AsyncInferenceConfig")
            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
"DataCaptureConfig")
            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
"ExplainerConfig")
            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
"FailureReason")
            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
"LastDeploymentConfig")
            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
"PendingDeploymentSummary")
            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
"ProductionVariants")
            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
"ShadowProductionVariants")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"EndpointName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"EndpointArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"EndpointConfigName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"EndpointStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"LastModifiedTime")
      )

instance Prelude.Hashable DescribeEndpoint where
  hashWithSalt :: Int -> DescribeEndpoint -> Int
hashWithSalt Int
_salt DescribeEndpoint' {Text
endpointName :: Text
$sel:endpointName:DescribeEndpoint' :: DescribeEndpoint -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointName

instance Prelude.NFData DescribeEndpoint where
  rnf :: DescribeEndpoint -> ()
rnf DescribeEndpoint' {Text
endpointName :: Text
$sel:endpointName:DescribeEndpoint' :: DescribeEndpoint -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
endpointName

instance Data.ToHeaders DescribeEndpoint where
  toHeaders :: DescribeEndpoint -> 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.DescribeEndpoint" :: 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 DescribeEndpoint where
  toJSON :: DescribeEndpoint -> Value
toJSON DescribeEndpoint' {Text
endpointName :: Text
$sel:endpointName:DescribeEndpoint' :: DescribeEndpoint -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"EndpointName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
endpointName)]
      )

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

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

-- | /See:/ 'newDescribeEndpointResponse' smart constructor.
data DescribeEndpointResponse = DescribeEndpointResponse'
  { -- | Returns the description of an endpoint configuration created using the
    -- <https://docs.aws.amazon.com/sagemaker/latest/APIReference/API_CreateEndpointConfig.html CreateEndpointConfig>
    -- API.
    DescribeEndpointResponse -> Maybe AsyncInferenceConfig
asyncInferenceConfig :: Prelude.Maybe AsyncInferenceConfig,
    DescribeEndpointResponse -> Maybe DataCaptureConfigSummary
dataCaptureConfig :: Prelude.Maybe DataCaptureConfigSummary,
    -- | The configuration parameters for an explainer.
    DescribeEndpointResponse -> Maybe ExplainerConfig
explainerConfig :: Prelude.Maybe ExplainerConfig,
    -- | If the status of the endpoint is @Failed@, the reason why it failed.
    DescribeEndpointResponse -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The most recent deployment configuration for the endpoint.
    DescribeEndpointResponse -> Maybe DeploymentConfig
lastDeploymentConfig :: Prelude.Maybe DeploymentConfig,
    -- | Returns the summary of an in-progress deployment. This field is only
    -- returned when the endpoint is creating or updating with a new endpoint
    -- configuration.
    DescribeEndpointResponse -> Maybe PendingDeploymentSummary
pendingDeploymentSummary :: Prelude.Maybe PendingDeploymentSummary,
    -- | An array of ProductionVariantSummary objects, one for each model hosted
    -- behind this endpoint.
    DescribeEndpointResponse
-> Maybe (NonEmpty ProductionVariantSummary)
productionVariants :: Prelude.Maybe (Prelude.NonEmpty ProductionVariantSummary),
    -- | An array of ProductionVariantSummary objects, one for each model that
    -- you want to host at this endpoint in shadow mode with production traffic
    -- replicated from the model specified on @ProductionVariants@.
    DescribeEndpointResponse
-> Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants :: Prelude.Maybe (Prelude.NonEmpty ProductionVariantSummary),
    -- | The response's http status code.
    DescribeEndpointResponse -> Int
httpStatus :: Prelude.Int,
    -- | Name of the endpoint.
    DescribeEndpointResponse -> Text
endpointName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the endpoint.
    DescribeEndpointResponse -> Text
endpointArn :: Prelude.Text,
    -- | The name of the endpoint configuration associated with this endpoint.
    DescribeEndpointResponse -> Text
endpointConfigName :: Prelude.Text,
    -- | The status of the endpoint.
    --
    -- -   @OutOfService@: Endpoint is not available to take incoming requests.
    --
    -- -   @Creating@: CreateEndpoint is executing.
    --
    -- -   @Updating@: UpdateEndpoint or UpdateEndpointWeightsAndCapacities is
    --     executing.
    --
    -- -   @SystemUpdating@: Endpoint is undergoing maintenance and cannot be
    --     updated or deleted or re-scaled until it has completed. This
    --     maintenance operation does not change any customer-specified values
    --     such as VPC config, KMS encryption, model, instance type, or
    --     instance count.
    --
    -- -   @RollingBack@: Endpoint fails to scale up or down or change its
    --     variant weight and is in the process of rolling back to its previous
    --     configuration. Once the rollback completes, endpoint returns to an
    --     @InService@ status. This transitional status only applies to an
    --     endpoint that has autoscaling enabled and is undergoing variant
    --     weight or capacity changes as part of an
    --     UpdateEndpointWeightsAndCapacities call or when the
    --     UpdateEndpointWeightsAndCapacities operation is called explicitly.
    --
    -- -   @InService@: Endpoint is available to process incoming requests.
    --
    -- -   @Deleting@: DeleteEndpoint is executing.
    --
    -- -   @Failed@: Endpoint could not be created, updated, or re-scaled. Use
    --     DescribeEndpointOutput$FailureReason for information about the
    --     failure. DeleteEndpoint is the only operation that can be performed
    --     on a failed endpoint.
    DescribeEndpointResponse -> EndpointStatus
endpointStatus :: EndpointStatus,
    -- | A timestamp that shows when the endpoint was created.
    DescribeEndpointResponse -> POSIX
creationTime :: Data.POSIX,
    -- | A timestamp that shows when the endpoint was last modified.
    DescribeEndpointResponse -> POSIX
lastModifiedTime :: Data.POSIX
  }
  deriving (DescribeEndpointResponse -> DescribeEndpointResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeEndpointResponse -> DescribeEndpointResponse -> Bool
$c/= :: DescribeEndpointResponse -> DescribeEndpointResponse -> Bool
== :: DescribeEndpointResponse -> DescribeEndpointResponse -> Bool
$c== :: DescribeEndpointResponse -> DescribeEndpointResponse -> Bool
Prelude.Eq, ReadPrec [DescribeEndpointResponse]
ReadPrec DescribeEndpointResponse
Int -> ReadS DescribeEndpointResponse
ReadS [DescribeEndpointResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeEndpointResponse]
$creadListPrec :: ReadPrec [DescribeEndpointResponse]
readPrec :: ReadPrec DescribeEndpointResponse
$creadPrec :: ReadPrec DescribeEndpointResponse
readList :: ReadS [DescribeEndpointResponse]
$creadList :: ReadS [DescribeEndpointResponse]
readsPrec :: Int -> ReadS DescribeEndpointResponse
$creadsPrec :: Int -> ReadS DescribeEndpointResponse
Prelude.Read, Int -> DescribeEndpointResponse -> ShowS
[DescribeEndpointResponse] -> ShowS
DescribeEndpointResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeEndpointResponse] -> ShowS
$cshowList :: [DescribeEndpointResponse] -> ShowS
show :: DescribeEndpointResponse -> String
$cshow :: DescribeEndpointResponse -> String
showsPrec :: Int -> DescribeEndpointResponse -> ShowS
$cshowsPrec :: Int -> DescribeEndpointResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeEndpointResponse x -> DescribeEndpointResponse
forall x.
DescribeEndpointResponse -> Rep DescribeEndpointResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeEndpointResponse x -> DescribeEndpointResponse
$cfrom :: forall x.
DescribeEndpointResponse -> Rep DescribeEndpointResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeEndpointResponse' 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:
--
-- 'asyncInferenceConfig', 'describeEndpointResponse_asyncInferenceConfig' - Returns the description of an endpoint configuration created using the
-- <https://docs.aws.amazon.com/sagemaker/latest/APIReference/API_CreateEndpointConfig.html CreateEndpointConfig>
-- API.
--
-- 'dataCaptureConfig', 'describeEndpointResponse_dataCaptureConfig' - Undocumented member.
--
-- 'explainerConfig', 'describeEndpointResponse_explainerConfig' - The configuration parameters for an explainer.
--
-- 'failureReason', 'describeEndpointResponse_failureReason' - If the status of the endpoint is @Failed@, the reason why it failed.
--
-- 'lastDeploymentConfig', 'describeEndpointResponse_lastDeploymentConfig' - The most recent deployment configuration for the endpoint.
--
-- 'pendingDeploymentSummary', 'describeEndpointResponse_pendingDeploymentSummary' - Returns the summary of an in-progress deployment. This field is only
-- returned when the endpoint is creating or updating with a new endpoint
-- configuration.
--
-- 'productionVariants', 'describeEndpointResponse_productionVariants' - An array of ProductionVariantSummary objects, one for each model hosted
-- behind this endpoint.
--
-- 'shadowProductionVariants', 'describeEndpointResponse_shadowProductionVariants' - An array of ProductionVariantSummary objects, one for each model that
-- you want to host at this endpoint in shadow mode with production traffic
-- replicated from the model specified on @ProductionVariants@.
--
-- 'httpStatus', 'describeEndpointResponse_httpStatus' - The response's http status code.
--
-- 'endpointName', 'describeEndpointResponse_endpointName' - Name of the endpoint.
--
-- 'endpointArn', 'describeEndpointResponse_endpointArn' - The Amazon Resource Name (ARN) of the endpoint.
--
-- 'endpointConfigName', 'describeEndpointResponse_endpointConfigName' - The name of the endpoint configuration associated with this endpoint.
--
-- 'endpointStatus', 'describeEndpointResponse_endpointStatus' - The status of the endpoint.
--
-- -   @OutOfService@: Endpoint is not available to take incoming requests.
--
-- -   @Creating@: CreateEndpoint is executing.
--
-- -   @Updating@: UpdateEndpoint or UpdateEndpointWeightsAndCapacities is
--     executing.
--
-- -   @SystemUpdating@: Endpoint is undergoing maintenance and cannot be
--     updated or deleted or re-scaled until it has completed. This
--     maintenance operation does not change any customer-specified values
--     such as VPC config, KMS encryption, model, instance type, or
--     instance count.
--
-- -   @RollingBack@: Endpoint fails to scale up or down or change its
--     variant weight and is in the process of rolling back to its previous
--     configuration. Once the rollback completes, endpoint returns to an
--     @InService@ status. This transitional status only applies to an
--     endpoint that has autoscaling enabled and is undergoing variant
--     weight or capacity changes as part of an
--     UpdateEndpointWeightsAndCapacities call or when the
--     UpdateEndpointWeightsAndCapacities operation is called explicitly.
--
-- -   @InService@: Endpoint is available to process incoming requests.
--
-- -   @Deleting@: DeleteEndpoint is executing.
--
-- -   @Failed@: Endpoint could not be created, updated, or re-scaled. Use
--     DescribeEndpointOutput$FailureReason for information about the
--     failure. DeleteEndpoint is the only operation that can be performed
--     on a failed endpoint.
--
-- 'creationTime', 'describeEndpointResponse_creationTime' - A timestamp that shows when the endpoint was created.
--
-- 'lastModifiedTime', 'describeEndpointResponse_lastModifiedTime' - A timestamp that shows when the endpoint was last modified.
newDescribeEndpointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'endpointName'
  Prelude.Text ->
  -- | 'endpointArn'
  Prelude.Text ->
  -- | 'endpointConfigName'
  Prelude.Text ->
  -- | 'endpointStatus'
  EndpointStatus ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModifiedTime'
  Prelude.UTCTime ->
  DescribeEndpointResponse
newDescribeEndpointResponse :: Int
-> Text
-> Text
-> Text
-> EndpointStatus
-> UTCTime
-> UTCTime
-> DescribeEndpointResponse
newDescribeEndpointResponse
  Int
pHttpStatus_
  Text
pEndpointName_
  Text
pEndpointArn_
  Text
pEndpointConfigName_
  EndpointStatus
pEndpointStatus_
  UTCTime
pCreationTime_
  UTCTime
pLastModifiedTime_ =
    DescribeEndpointResponse'
      { $sel:asyncInferenceConfig:DescribeEndpointResponse' :: Maybe AsyncInferenceConfig
asyncInferenceConfig =
          forall a. Maybe a
Prelude.Nothing,
        $sel:dataCaptureConfig:DescribeEndpointResponse' :: Maybe DataCaptureConfigSummary
dataCaptureConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:explainerConfig:DescribeEndpointResponse' :: Maybe ExplainerConfig
explainerConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:failureReason:DescribeEndpointResponse' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
        $sel:lastDeploymentConfig:DescribeEndpointResponse' :: Maybe DeploymentConfig
lastDeploymentConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:pendingDeploymentSummary:DescribeEndpointResponse' :: Maybe PendingDeploymentSummary
pendingDeploymentSummary = forall a. Maybe a
Prelude.Nothing,
        $sel:productionVariants:DescribeEndpointResponse' :: Maybe (NonEmpty ProductionVariantSummary)
productionVariants = forall a. Maybe a
Prelude.Nothing,
        $sel:shadowProductionVariants:DescribeEndpointResponse' :: Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeEndpointResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:endpointName:DescribeEndpointResponse' :: Text
endpointName = Text
pEndpointName_,
        $sel:endpointArn:DescribeEndpointResponse' :: Text
endpointArn = Text
pEndpointArn_,
        $sel:endpointConfigName:DescribeEndpointResponse' :: Text
endpointConfigName = Text
pEndpointConfigName_,
        $sel:endpointStatus:DescribeEndpointResponse' :: EndpointStatus
endpointStatus = EndpointStatus
pEndpointStatus_,
        $sel:creationTime:DescribeEndpointResponse' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModifiedTime:DescribeEndpointResponse' :: POSIX
lastModifiedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedTime_
      }

-- | Returns the description of an endpoint configuration created using the
-- <https://docs.aws.amazon.com/sagemaker/latest/APIReference/API_CreateEndpointConfig.html CreateEndpointConfig>
-- API.
describeEndpointResponse_asyncInferenceConfig :: Lens.Lens' DescribeEndpointResponse (Prelude.Maybe AsyncInferenceConfig)
describeEndpointResponse_asyncInferenceConfig :: Lens' DescribeEndpointResponse (Maybe AsyncInferenceConfig)
describeEndpointResponse_asyncInferenceConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Maybe AsyncInferenceConfig
asyncInferenceConfig :: Maybe AsyncInferenceConfig
$sel:asyncInferenceConfig:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe AsyncInferenceConfig
asyncInferenceConfig} -> Maybe AsyncInferenceConfig
asyncInferenceConfig) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Maybe AsyncInferenceConfig
a -> DescribeEndpointResponse
s {$sel:asyncInferenceConfig:DescribeEndpointResponse' :: Maybe AsyncInferenceConfig
asyncInferenceConfig = Maybe AsyncInferenceConfig
a} :: DescribeEndpointResponse)

-- | Undocumented member.
describeEndpointResponse_dataCaptureConfig :: Lens.Lens' DescribeEndpointResponse (Prelude.Maybe DataCaptureConfigSummary)
describeEndpointResponse_dataCaptureConfig :: Lens' DescribeEndpointResponse (Maybe DataCaptureConfigSummary)
describeEndpointResponse_dataCaptureConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Maybe DataCaptureConfigSummary
dataCaptureConfig :: Maybe DataCaptureConfigSummary
$sel:dataCaptureConfig:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe DataCaptureConfigSummary
dataCaptureConfig} -> Maybe DataCaptureConfigSummary
dataCaptureConfig) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Maybe DataCaptureConfigSummary
a -> DescribeEndpointResponse
s {$sel:dataCaptureConfig:DescribeEndpointResponse' :: Maybe DataCaptureConfigSummary
dataCaptureConfig = Maybe DataCaptureConfigSummary
a} :: DescribeEndpointResponse)

-- | The configuration parameters for an explainer.
describeEndpointResponse_explainerConfig :: Lens.Lens' DescribeEndpointResponse (Prelude.Maybe ExplainerConfig)
describeEndpointResponse_explainerConfig :: Lens' DescribeEndpointResponse (Maybe ExplainerConfig)
describeEndpointResponse_explainerConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Maybe ExplainerConfig
explainerConfig :: Maybe ExplainerConfig
$sel:explainerConfig:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe ExplainerConfig
explainerConfig} -> Maybe ExplainerConfig
explainerConfig) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Maybe ExplainerConfig
a -> DescribeEndpointResponse
s {$sel:explainerConfig:DescribeEndpointResponse' :: Maybe ExplainerConfig
explainerConfig = Maybe ExplainerConfig
a} :: DescribeEndpointResponse)

-- | If the status of the endpoint is @Failed@, the reason why it failed.
describeEndpointResponse_failureReason :: Lens.Lens' DescribeEndpointResponse (Prelude.Maybe Prelude.Text)
describeEndpointResponse_failureReason :: Lens' DescribeEndpointResponse (Maybe Text)
describeEndpointResponse_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Maybe Text
a -> DescribeEndpointResponse
s {$sel:failureReason:DescribeEndpointResponse' :: Maybe Text
failureReason = Maybe Text
a} :: DescribeEndpointResponse)

-- | The most recent deployment configuration for the endpoint.
describeEndpointResponse_lastDeploymentConfig :: Lens.Lens' DescribeEndpointResponse (Prelude.Maybe DeploymentConfig)
describeEndpointResponse_lastDeploymentConfig :: Lens' DescribeEndpointResponse (Maybe DeploymentConfig)
describeEndpointResponse_lastDeploymentConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Maybe DeploymentConfig
lastDeploymentConfig :: Maybe DeploymentConfig
$sel:lastDeploymentConfig:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe DeploymentConfig
lastDeploymentConfig} -> Maybe DeploymentConfig
lastDeploymentConfig) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Maybe DeploymentConfig
a -> DescribeEndpointResponse
s {$sel:lastDeploymentConfig:DescribeEndpointResponse' :: Maybe DeploymentConfig
lastDeploymentConfig = Maybe DeploymentConfig
a} :: DescribeEndpointResponse)

-- | Returns the summary of an in-progress deployment. This field is only
-- returned when the endpoint is creating or updating with a new endpoint
-- configuration.
describeEndpointResponse_pendingDeploymentSummary :: Lens.Lens' DescribeEndpointResponse (Prelude.Maybe PendingDeploymentSummary)
describeEndpointResponse_pendingDeploymentSummary :: Lens' DescribeEndpointResponse (Maybe PendingDeploymentSummary)
describeEndpointResponse_pendingDeploymentSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Maybe PendingDeploymentSummary
pendingDeploymentSummary :: Maybe PendingDeploymentSummary
$sel:pendingDeploymentSummary:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe PendingDeploymentSummary
pendingDeploymentSummary} -> Maybe PendingDeploymentSummary
pendingDeploymentSummary) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Maybe PendingDeploymentSummary
a -> DescribeEndpointResponse
s {$sel:pendingDeploymentSummary:DescribeEndpointResponse' :: Maybe PendingDeploymentSummary
pendingDeploymentSummary = Maybe PendingDeploymentSummary
a} :: DescribeEndpointResponse)

-- | An array of ProductionVariantSummary objects, one for each model hosted
-- behind this endpoint.
describeEndpointResponse_productionVariants :: Lens.Lens' DescribeEndpointResponse (Prelude.Maybe (Prelude.NonEmpty ProductionVariantSummary))
describeEndpointResponse_productionVariants :: Lens'
  DescribeEndpointResponse
  (Maybe (NonEmpty ProductionVariantSummary))
describeEndpointResponse_productionVariants = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Maybe (NonEmpty ProductionVariantSummary)
productionVariants :: Maybe (NonEmpty ProductionVariantSummary)
$sel:productionVariants:DescribeEndpointResponse' :: DescribeEndpointResponse
-> Maybe (NonEmpty ProductionVariantSummary)
productionVariants} -> Maybe (NonEmpty ProductionVariantSummary)
productionVariants) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Maybe (NonEmpty ProductionVariantSummary)
a -> DescribeEndpointResponse
s {$sel:productionVariants:DescribeEndpointResponse' :: Maybe (NonEmpty ProductionVariantSummary)
productionVariants = Maybe (NonEmpty ProductionVariantSummary)
a} :: DescribeEndpointResponse) 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

-- | An array of ProductionVariantSummary objects, one for each model that
-- you want to host at this endpoint in shadow mode with production traffic
-- replicated from the model specified on @ProductionVariants@.
describeEndpointResponse_shadowProductionVariants :: Lens.Lens' DescribeEndpointResponse (Prelude.Maybe (Prelude.NonEmpty ProductionVariantSummary))
describeEndpointResponse_shadowProductionVariants :: Lens'
  DescribeEndpointResponse
  (Maybe (NonEmpty ProductionVariantSummary))
describeEndpointResponse_shadowProductionVariants = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants :: Maybe (NonEmpty ProductionVariantSummary)
$sel:shadowProductionVariants:DescribeEndpointResponse' :: DescribeEndpointResponse
-> Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants} -> Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Maybe (NonEmpty ProductionVariantSummary)
a -> DescribeEndpointResponse
s {$sel:shadowProductionVariants:DescribeEndpointResponse' :: Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants = Maybe (NonEmpty ProductionVariantSummary)
a} :: DescribeEndpointResponse) 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 response's http status code.
describeEndpointResponse_httpStatus :: Lens.Lens' DescribeEndpointResponse Prelude.Int
describeEndpointResponse_httpStatus :: Lens' DescribeEndpointResponse Int
describeEndpointResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeEndpointResponse' :: DescribeEndpointResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Int
a -> DescribeEndpointResponse
s {$sel:httpStatus:DescribeEndpointResponse' :: Int
httpStatus = Int
a} :: DescribeEndpointResponse)

-- | Name of the endpoint.
describeEndpointResponse_endpointName :: Lens.Lens' DescribeEndpointResponse Prelude.Text
describeEndpointResponse_endpointName :: Lens' DescribeEndpointResponse Text
describeEndpointResponse_endpointName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Text
endpointName :: Text
$sel:endpointName:DescribeEndpointResponse' :: DescribeEndpointResponse -> Text
endpointName} -> Text
endpointName) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Text
a -> DescribeEndpointResponse
s {$sel:endpointName:DescribeEndpointResponse' :: Text
endpointName = Text
a} :: DescribeEndpointResponse)

-- | The Amazon Resource Name (ARN) of the endpoint.
describeEndpointResponse_endpointArn :: Lens.Lens' DescribeEndpointResponse Prelude.Text
describeEndpointResponse_endpointArn :: Lens' DescribeEndpointResponse Text
describeEndpointResponse_endpointArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Text
endpointArn :: Text
$sel:endpointArn:DescribeEndpointResponse' :: DescribeEndpointResponse -> Text
endpointArn} -> Text
endpointArn) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Text
a -> DescribeEndpointResponse
s {$sel:endpointArn:DescribeEndpointResponse' :: Text
endpointArn = Text
a} :: DescribeEndpointResponse)

-- | The name of the endpoint configuration associated with this endpoint.
describeEndpointResponse_endpointConfigName :: Lens.Lens' DescribeEndpointResponse Prelude.Text
describeEndpointResponse_endpointConfigName :: Lens' DescribeEndpointResponse Text
describeEndpointResponse_endpointConfigName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {Text
endpointConfigName :: Text
$sel:endpointConfigName:DescribeEndpointResponse' :: DescribeEndpointResponse -> Text
endpointConfigName} -> Text
endpointConfigName) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} Text
a -> DescribeEndpointResponse
s {$sel:endpointConfigName:DescribeEndpointResponse' :: Text
endpointConfigName = Text
a} :: DescribeEndpointResponse)

-- | The status of the endpoint.
--
-- -   @OutOfService@: Endpoint is not available to take incoming requests.
--
-- -   @Creating@: CreateEndpoint is executing.
--
-- -   @Updating@: UpdateEndpoint or UpdateEndpointWeightsAndCapacities is
--     executing.
--
-- -   @SystemUpdating@: Endpoint is undergoing maintenance and cannot be
--     updated or deleted or re-scaled until it has completed. This
--     maintenance operation does not change any customer-specified values
--     such as VPC config, KMS encryption, model, instance type, or
--     instance count.
--
-- -   @RollingBack@: Endpoint fails to scale up or down or change its
--     variant weight and is in the process of rolling back to its previous
--     configuration. Once the rollback completes, endpoint returns to an
--     @InService@ status. This transitional status only applies to an
--     endpoint that has autoscaling enabled and is undergoing variant
--     weight or capacity changes as part of an
--     UpdateEndpointWeightsAndCapacities call or when the
--     UpdateEndpointWeightsAndCapacities operation is called explicitly.
--
-- -   @InService@: Endpoint is available to process incoming requests.
--
-- -   @Deleting@: DeleteEndpoint is executing.
--
-- -   @Failed@: Endpoint could not be created, updated, or re-scaled. Use
--     DescribeEndpointOutput$FailureReason for information about the
--     failure. DeleteEndpoint is the only operation that can be performed
--     on a failed endpoint.
describeEndpointResponse_endpointStatus :: Lens.Lens' DescribeEndpointResponse EndpointStatus
describeEndpointResponse_endpointStatus :: Lens' DescribeEndpointResponse EndpointStatus
describeEndpointResponse_endpointStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {EndpointStatus
endpointStatus :: EndpointStatus
$sel:endpointStatus:DescribeEndpointResponse' :: DescribeEndpointResponse -> EndpointStatus
endpointStatus} -> EndpointStatus
endpointStatus) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} EndpointStatus
a -> DescribeEndpointResponse
s {$sel:endpointStatus:DescribeEndpointResponse' :: EndpointStatus
endpointStatus = EndpointStatus
a} :: DescribeEndpointResponse)

-- | A timestamp that shows when the endpoint was created.
describeEndpointResponse_creationTime :: Lens.Lens' DescribeEndpointResponse Prelude.UTCTime
describeEndpointResponse_creationTime :: Lens' DescribeEndpointResponse UTCTime
describeEndpointResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:DescribeEndpointResponse' :: DescribeEndpointResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} POSIX
a -> DescribeEndpointResponse
s {$sel:creationTime:DescribeEndpointResponse' :: POSIX
creationTime = POSIX
a} :: DescribeEndpointResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A timestamp that shows when the endpoint was last modified.
describeEndpointResponse_lastModifiedTime :: Lens.Lens' DescribeEndpointResponse Prelude.UTCTime
describeEndpointResponse_lastModifiedTime :: Lens' DescribeEndpointResponse UTCTime
describeEndpointResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEndpointResponse' {POSIX
lastModifiedTime :: POSIX
$sel:lastModifiedTime:DescribeEndpointResponse' :: DescribeEndpointResponse -> POSIX
lastModifiedTime} -> POSIX
lastModifiedTime) (\s :: DescribeEndpointResponse
s@DescribeEndpointResponse' {} POSIX
a -> DescribeEndpointResponse
s {$sel:lastModifiedTime:DescribeEndpointResponse' :: POSIX
lastModifiedTime = POSIX
a} :: DescribeEndpointResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData DescribeEndpointResponse where
  rnf :: DescribeEndpointResponse -> ()
rnf DescribeEndpointResponse' {Int
Maybe (NonEmpty ProductionVariantSummary)
Maybe Text
Maybe AsyncInferenceConfig
Maybe DataCaptureConfigSummary
Maybe ExplainerConfig
Maybe DeploymentConfig
Maybe PendingDeploymentSummary
Text
POSIX
EndpointStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
endpointStatus :: EndpointStatus
endpointConfigName :: Text
endpointArn :: Text
endpointName :: Text
httpStatus :: Int
shadowProductionVariants :: Maybe (NonEmpty ProductionVariantSummary)
productionVariants :: Maybe (NonEmpty ProductionVariantSummary)
pendingDeploymentSummary :: Maybe PendingDeploymentSummary
lastDeploymentConfig :: Maybe DeploymentConfig
failureReason :: Maybe Text
explainerConfig :: Maybe ExplainerConfig
dataCaptureConfig :: Maybe DataCaptureConfigSummary
asyncInferenceConfig :: Maybe AsyncInferenceConfig
$sel:lastModifiedTime:DescribeEndpointResponse' :: DescribeEndpointResponse -> POSIX
$sel:creationTime:DescribeEndpointResponse' :: DescribeEndpointResponse -> POSIX
$sel:endpointStatus:DescribeEndpointResponse' :: DescribeEndpointResponse -> EndpointStatus
$sel:endpointConfigName:DescribeEndpointResponse' :: DescribeEndpointResponse -> Text
$sel:endpointArn:DescribeEndpointResponse' :: DescribeEndpointResponse -> Text
$sel:endpointName:DescribeEndpointResponse' :: DescribeEndpointResponse -> Text
$sel:httpStatus:DescribeEndpointResponse' :: DescribeEndpointResponse -> Int
$sel:shadowProductionVariants:DescribeEndpointResponse' :: DescribeEndpointResponse
-> Maybe (NonEmpty ProductionVariantSummary)
$sel:productionVariants:DescribeEndpointResponse' :: DescribeEndpointResponse
-> Maybe (NonEmpty ProductionVariantSummary)
$sel:pendingDeploymentSummary:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe PendingDeploymentSummary
$sel:lastDeploymentConfig:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe DeploymentConfig
$sel:failureReason:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe Text
$sel:explainerConfig:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe ExplainerConfig
$sel:dataCaptureConfig:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe DataCaptureConfigSummary
$sel:asyncInferenceConfig:DescribeEndpointResponse' :: DescribeEndpointResponse -> Maybe AsyncInferenceConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AsyncInferenceConfig
asyncInferenceConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataCaptureConfigSummary
dataCaptureConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExplainerConfig
explainerConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeploymentConfig
lastDeploymentConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PendingDeploymentSummary
pendingDeploymentSummary
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty ProductionVariantSummary)
productionVariants
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      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
endpointArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointConfigName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf EndpointStatus
endpointStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastModifiedTime