{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.Endpoint
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.SageMaker.Types.Endpoint 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 Amazonka.SageMaker.Types.DataCaptureConfigSummary
import Amazonka.SageMaker.Types.EndpointStatus
import Amazonka.SageMaker.Types.MonitoringSchedule
import Amazonka.SageMaker.Types.ProductionVariantSummary
import Amazonka.SageMaker.Types.Tag

-- | A hosted endpoint for real-time inference.
--
-- /See:/ 'newEndpoint' smart constructor.
data Endpoint = Endpoint'
  { Endpoint -> Maybe DataCaptureConfigSummary
dataCaptureConfig :: Prelude.Maybe DataCaptureConfigSummary,
    -- | If the endpoint failed, the reason it failed.
    Endpoint -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | A list of monitoring schedules for the endpoint. For information about
    -- model monitoring, see
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/model-monitor.html Amazon SageMaker Model Monitor>.
    Endpoint -> Maybe [MonitoringSchedule]
monitoringSchedules :: Prelude.Maybe [MonitoringSchedule],
    -- | A list of the production variants hosted on the endpoint. Each
    -- production variant is a model.
    Endpoint -> Maybe (NonEmpty ProductionVariantSummary)
productionVariants :: Prelude.Maybe (Prelude.NonEmpty ProductionVariantSummary),
    -- | A list of the shadow variants hosted on the endpoint. Each shadow
    -- variant is a model in shadow mode with production traffic replicated
    -- from the proudction variant.
    Endpoint -> Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants :: Prelude.Maybe (Prelude.NonEmpty ProductionVariantSummary),
    -- | A list of the tags associated with the endpoint. For more information,
    -- see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>
    -- in the /Amazon Web Services General Reference Guide/.
    Endpoint -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the endpoint.
    Endpoint -> Text
endpointName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the endpoint.
    Endpoint -> Text
endpointArn :: Prelude.Text,
    -- | The endpoint configuration associated with the endpoint.
    Endpoint -> Text
endpointConfigName :: Prelude.Text,
    -- | The status of the endpoint.
    Endpoint -> EndpointStatus
endpointStatus :: EndpointStatus,
    -- | The time that the endpoint was created.
    Endpoint -> POSIX
creationTime :: Data.POSIX,
    -- | The last time the endpoint was modified.
    Endpoint -> POSIX
lastModifiedTime :: Data.POSIX
  }
  deriving (Endpoint -> Endpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Endpoint -> Endpoint -> Bool
$c/= :: Endpoint -> Endpoint -> Bool
== :: Endpoint -> Endpoint -> Bool
$c== :: Endpoint -> Endpoint -> Bool
Prelude.Eq, ReadPrec [Endpoint]
ReadPrec Endpoint
Int -> ReadS Endpoint
ReadS [Endpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Endpoint]
$creadListPrec :: ReadPrec [Endpoint]
readPrec :: ReadPrec Endpoint
$creadPrec :: ReadPrec Endpoint
readList :: ReadS [Endpoint]
$creadList :: ReadS [Endpoint]
readsPrec :: Int -> ReadS Endpoint
$creadsPrec :: Int -> ReadS Endpoint
Prelude.Read, Int -> Endpoint -> ShowS
[Endpoint] -> ShowS
Endpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Endpoint] -> ShowS
$cshowList :: [Endpoint] -> ShowS
show :: Endpoint -> String
$cshow :: Endpoint -> String
showsPrec :: Int -> Endpoint -> ShowS
$cshowsPrec :: Int -> Endpoint -> ShowS
Prelude.Show, forall x. Rep Endpoint x -> Endpoint
forall x. Endpoint -> Rep Endpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Endpoint x -> Endpoint
$cfrom :: forall x. Endpoint -> Rep Endpoint x
Prelude.Generic)

-- |
-- Create a value of 'Endpoint' 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:
--
-- 'dataCaptureConfig', 'endpoint_dataCaptureConfig' - Undocumented member.
--
-- 'failureReason', 'endpoint_failureReason' - If the endpoint failed, the reason it failed.
--
-- 'monitoringSchedules', 'endpoint_monitoringSchedules' - A list of monitoring schedules for the endpoint. For information about
-- model monitoring, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/model-monitor.html Amazon SageMaker Model Monitor>.
--
-- 'productionVariants', 'endpoint_productionVariants' - A list of the production variants hosted on the endpoint. Each
-- production variant is a model.
--
-- 'shadowProductionVariants', 'endpoint_shadowProductionVariants' - A list of the shadow variants hosted on the endpoint. Each shadow
-- variant is a model in shadow mode with production traffic replicated
-- from the proudction variant.
--
-- 'tags', 'endpoint_tags' - A list of the tags associated with the endpoint. For more information,
-- see
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>
-- in the /Amazon Web Services General Reference Guide/.
--
-- 'endpointName', 'endpoint_endpointName' - The name of the endpoint.
--
-- 'endpointArn', 'endpoint_endpointArn' - The Amazon Resource Name (ARN) of the endpoint.
--
-- 'endpointConfigName', 'endpoint_endpointConfigName' - The endpoint configuration associated with the endpoint.
--
-- 'endpointStatus', 'endpoint_endpointStatus' - The status of the endpoint.
--
-- 'creationTime', 'endpoint_creationTime' - The time that the endpoint was created.
--
-- 'lastModifiedTime', 'endpoint_lastModifiedTime' - The last time the endpoint was modified.
newEndpoint ::
  -- | 'endpointName'
  Prelude.Text ->
  -- | 'endpointArn'
  Prelude.Text ->
  -- | 'endpointConfigName'
  Prelude.Text ->
  -- | 'endpointStatus'
  EndpointStatus ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModifiedTime'
  Prelude.UTCTime ->
  Endpoint
newEndpoint :: Text
-> Text -> Text -> EndpointStatus -> UTCTime -> UTCTime -> Endpoint
newEndpoint
  Text
pEndpointName_
  Text
pEndpointArn_
  Text
pEndpointConfigName_
  EndpointStatus
pEndpointStatus_
  UTCTime
pCreationTime_
  UTCTime
pLastModifiedTime_ =
    Endpoint'
      { $sel:dataCaptureConfig:Endpoint' :: Maybe DataCaptureConfigSummary
dataCaptureConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:failureReason:Endpoint' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
        $sel:monitoringSchedules:Endpoint' :: Maybe [MonitoringSchedule]
monitoringSchedules = forall a. Maybe a
Prelude.Nothing,
        $sel:productionVariants:Endpoint' :: Maybe (NonEmpty ProductionVariantSummary)
productionVariants = forall a. Maybe a
Prelude.Nothing,
        $sel:shadowProductionVariants:Endpoint' :: Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:Endpoint' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:endpointName:Endpoint' :: Text
endpointName = Text
pEndpointName_,
        $sel:endpointArn:Endpoint' :: Text
endpointArn = Text
pEndpointArn_,
        $sel:endpointConfigName:Endpoint' :: Text
endpointConfigName = Text
pEndpointConfigName_,
        $sel:endpointStatus:Endpoint' :: EndpointStatus
endpointStatus = EndpointStatus
pEndpointStatus_,
        $sel:creationTime:Endpoint' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModifiedTime:Endpoint' :: POSIX
lastModifiedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedTime_
      }

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

-- | If the endpoint failed, the reason it failed.
endpoint_failureReason :: Lens.Lens' Endpoint (Prelude.Maybe Prelude.Text)
endpoint_failureReason :: Lens' Endpoint (Maybe Text)
endpoint_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:Endpoint' :: Endpoint -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: Endpoint
s@Endpoint' {} Maybe Text
a -> Endpoint
s {$sel:failureReason:Endpoint' :: Maybe Text
failureReason = Maybe Text
a} :: Endpoint)

-- | A list of monitoring schedules for the endpoint. For information about
-- model monitoring, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/model-monitor.html Amazon SageMaker Model Monitor>.
endpoint_monitoringSchedules :: Lens.Lens' Endpoint (Prelude.Maybe [MonitoringSchedule])
endpoint_monitoringSchedules :: Lens' Endpoint (Maybe [MonitoringSchedule])
endpoint_monitoringSchedules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe [MonitoringSchedule]
monitoringSchedules :: Maybe [MonitoringSchedule]
$sel:monitoringSchedules:Endpoint' :: Endpoint -> Maybe [MonitoringSchedule]
monitoringSchedules} -> Maybe [MonitoringSchedule]
monitoringSchedules) (\s :: Endpoint
s@Endpoint' {} Maybe [MonitoringSchedule]
a -> Endpoint
s {$sel:monitoringSchedules:Endpoint' :: Maybe [MonitoringSchedule]
monitoringSchedules = Maybe [MonitoringSchedule]
a} :: Endpoint) 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

-- | A list of the production variants hosted on the endpoint. Each
-- production variant is a model.
endpoint_productionVariants :: Lens.Lens' Endpoint (Prelude.Maybe (Prelude.NonEmpty ProductionVariantSummary))
endpoint_productionVariants :: Lens' Endpoint (Maybe (NonEmpty ProductionVariantSummary))
endpoint_productionVariants = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe (NonEmpty ProductionVariantSummary)
productionVariants :: Maybe (NonEmpty ProductionVariantSummary)
$sel:productionVariants:Endpoint' :: Endpoint -> Maybe (NonEmpty ProductionVariantSummary)
productionVariants} -> Maybe (NonEmpty ProductionVariantSummary)
productionVariants) (\s :: Endpoint
s@Endpoint' {} Maybe (NonEmpty ProductionVariantSummary)
a -> Endpoint
s {$sel:productionVariants:Endpoint' :: Maybe (NonEmpty ProductionVariantSummary)
productionVariants = Maybe (NonEmpty ProductionVariantSummary)
a} :: Endpoint) 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

-- | A list of the shadow variants hosted on the endpoint. Each shadow
-- variant is a model in shadow mode with production traffic replicated
-- from the proudction variant.
endpoint_shadowProductionVariants :: Lens.Lens' Endpoint (Prelude.Maybe (Prelude.NonEmpty ProductionVariantSummary))
endpoint_shadowProductionVariants :: Lens' Endpoint (Maybe (NonEmpty ProductionVariantSummary))
endpoint_shadowProductionVariants = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants :: Maybe (NonEmpty ProductionVariantSummary)
$sel:shadowProductionVariants:Endpoint' :: Endpoint -> Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants} -> Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants) (\s :: Endpoint
s@Endpoint' {} Maybe (NonEmpty ProductionVariantSummary)
a -> Endpoint
s {$sel:shadowProductionVariants:Endpoint' :: Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants = Maybe (NonEmpty ProductionVariantSummary)
a} :: Endpoint) 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

-- | A list of the tags associated with the endpoint. For more information,
-- see
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>
-- in the /Amazon Web Services General Reference Guide/.
endpoint_tags :: Lens.Lens' Endpoint (Prelude.Maybe [Tag])
endpoint_tags :: Lens' Endpoint (Maybe [Tag])
endpoint_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:Endpoint' :: Endpoint -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: Endpoint
s@Endpoint' {} Maybe [Tag]
a -> Endpoint
s {$sel:tags:Endpoint' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: Endpoint) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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

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

-- | The status of the endpoint.
endpoint_endpointStatus :: Lens.Lens' Endpoint EndpointStatus
endpoint_endpointStatus :: Lens' Endpoint EndpointStatus
endpoint_endpointStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {EndpointStatus
endpointStatus :: EndpointStatus
$sel:endpointStatus:Endpoint' :: Endpoint -> EndpointStatus
endpointStatus} -> EndpointStatus
endpointStatus) (\s :: Endpoint
s@Endpoint' {} EndpointStatus
a -> Endpoint
s {$sel:endpointStatus:Endpoint' :: EndpointStatus
endpointStatus = EndpointStatus
a} :: Endpoint)

-- | The time that the endpoint was created.
endpoint_creationTime :: Lens.Lens' Endpoint Prelude.UTCTime
endpoint_creationTime :: Lens' Endpoint UTCTime
endpoint_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {POSIX
creationTime :: POSIX
$sel:creationTime:Endpoint' :: Endpoint -> POSIX
creationTime} -> POSIX
creationTime) (\s :: Endpoint
s@Endpoint' {} POSIX
a -> Endpoint
s {$sel:creationTime:Endpoint' :: POSIX
creationTime = POSIX
a} :: Endpoint) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The last time the endpoint was modified.
endpoint_lastModifiedTime :: Lens.Lens' Endpoint Prelude.UTCTime
endpoint_lastModifiedTime :: Lens' Endpoint UTCTime
endpoint_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {POSIX
lastModifiedTime :: POSIX
$sel:lastModifiedTime:Endpoint' :: Endpoint -> POSIX
lastModifiedTime} -> POSIX
lastModifiedTime) (\s :: Endpoint
s@Endpoint' {} POSIX
a -> Endpoint
s {$sel:lastModifiedTime:Endpoint' :: POSIX
lastModifiedTime = POSIX
a} :: Endpoint) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromJSON Endpoint where
  parseJSON :: Value -> Parser Endpoint
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Endpoint"
      ( \Object
x ->
          Maybe DataCaptureConfigSummary
-> Maybe Text
-> Maybe [MonitoringSchedule]
-> Maybe (NonEmpty ProductionVariantSummary)
-> Maybe (NonEmpty ProductionVariantSummary)
-> Maybe [Tag]
-> Text
-> Text
-> Text
-> EndpointStatus
-> POSIX
-> POSIX
-> Endpoint
Endpoint'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"MonitoringSchedules"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"ShadowProductionVariants")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser 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 -> Parser 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 -> Parser 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 -> Parser 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 -> Parser 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 -> Parser a
Data..: Key
"LastModifiedTime")
      )

instance Prelude.Hashable Endpoint where
  hashWithSalt :: Int -> Endpoint -> Int
hashWithSalt Int
_salt Endpoint' {Maybe [Tag]
Maybe [MonitoringSchedule]
Maybe (NonEmpty ProductionVariantSummary)
Maybe Text
Maybe DataCaptureConfigSummary
Text
POSIX
EndpointStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
endpointStatus :: EndpointStatus
endpointConfigName :: Text
endpointArn :: Text
endpointName :: Text
tags :: Maybe [Tag]
shadowProductionVariants :: Maybe (NonEmpty ProductionVariantSummary)
productionVariants :: Maybe (NonEmpty ProductionVariantSummary)
monitoringSchedules :: Maybe [MonitoringSchedule]
failureReason :: Maybe Text
dataCaptureConfig :: Maybe DataCaptureConfigSummary
$sel:lastModifiedTime:Endpoint' :: Endpoint -> POSIX
$sel:creationTime:Endpoint' :: Endpoint -> POSIX
$sel:endpointStatus:Endpoint' :: Endpoint -> EndpointStatus
$sel:endpointConfigName:Endpoint' :: Endpoint -> Text
$sel:endpointArn:Endpoint' :: Endpoint -> Text
$sel:endpointName:Endpoint' :: Endpoint -> Text
$sel:tags:Endpoint' :: Endpoint -> Maybe [Tag]
$sel:shadowProductionVariants:Endpoint' :: Endpoint -> Maybe (NonEmpty ProductionVariantSummary)
$sel:productionVariants:Endpoint' :: Endpoint -> Maybe (NonEmpty ProductionVariantSummary)
$sel:monitoringSchedules:Endpoint' :: Endpoint -> Maybe [MonitoringSchedule]
$sel:failureReason:Endpoint' :: Endpoint -> Maybe Text
$sel:dataCaptureConfig:Endpoint' :: Endpoint -> Maybe DataCaptureConfigSummary
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataCaptureConfigSummary
dataCaptureConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [MonitoringSchedule]
monitoringSchedules
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty ProductionVariantSummary)
productionVariants
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty ProductionVariantSummary)
shadowProductionVariants
      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
endpointArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointConfigName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` EndpointStatus
endpointStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
lastModifiedTime

instance Prelude.NFData Endpoint where
  rnf :: Endpoint -> ()
rnf Endpoint' {Maybe [Tag]
Maybe [MonitoringSchedule]
Maybe (NonEmpty ProductionVariantSummary)
Maybe Text
Maybe DataCaptureConfigSummary
Text
POSIX
EndpointStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
endpointStatus :: EndpointStatus
endpointConfigName :: Text
endpointArn :: Text
endpointName :: Text
tags :: Maybe [Tag]
shadowProductionVariants :: Maybe (NonEmpty ProductionVariantSummary)
productionVariants :: Maybe (NonEmpty ProductionVariantSummary)
monitoringSchedules :: Maybe [MonitoringSchedule]
failureReason :: Maybe Text
dataCaptureConfig :: Maybe DataCaptureConfigSummary
$sel:lastModifiedTime:Endpoint' :: Endpoint -> POSIX
$sel:creationTime:Endpoint' :: Endpoint -> POSIX
$sel:endpointStatus:Endpoint' :: Endpoint -> EndpointStatus
$sel:endpointConfigName:Endpoint' :: Endpoint -> Text
$sel:endpointArn:Endpoint' :: Endpoint -> Text
$sel:endpointName:Endpoint' :: Endpoint -> Text
$sel:tags:Endpoint' :: Endpoint -> Maybe [Tag]
$sel:shadowProductionVariants:Endpoint' :: Endpoint -> Maybe (NonEmpty ProductionVariantSummary)
$sel:productionVariants:Endpoint' :: Endpoint -> Maybe (NonEmpty ProductionVariantSummary)
$sel:monitoringSchedules:Endpoint' :: Endpoint -> Maybe [MonitoringSchedule]
$sel:failureReason:Endpoint' :: Endpoint -> Maybe Text
$sel:dataCaptureConfig:Endpoint' :: Endpoint -> Maybe DataCaptureConfigSummary
..} =
    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 Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [MonitoringSchedule]
monitoringSchedules
      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 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
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