{-# 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.AppRunner.Types.Service
-- 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.AppRunner.Types.Service where

import Amazonka.AppRunner.Types.AutoScalingConfigurationSummary
import Amazonka.AppRunner.Types.EncryptionConfiguration
import Amazonka.AppRunner.Types.HealthCheckConfiguration
import Amazonka.AppRunner.Types.InstanceConfiguration
import Amazonka.AppRunner.Types.NetworkConfiguration
import Amazonka.AppRunner.Types.ServiceObservabilityConfiguration
import Amazonka.AppRunner.Types.ServiceStatus
import Amazonka.AppRunner.Types.SourceConfiguration
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

-- | Describes an App Runner service. It can describe a service in any state,
-- including deleted services.
--
-- This type contains the full information about a service, including
-- configuration details. It\'s returned by the
-- <https://docs.aws.amazon.com/apprunner/latest/api/API_CreateService.html CreateService>,
-- <https://docs.aws.amazon.com/apprunner/latest/api/API_DescribeService.html DescribeService>,
-- and
-- <https://docs.aws.amazon.com/apprunner/latest/api/API_DeleteService.html DeleteService>
-- actions. A subset of this information is returned by the
-- <https://docs.aws.amazon.com/apprunner/latest/api/API_ListServices.html ListServices>
-- action using the
-- <https://docs.aws.amazon.com/apprunner/latest/api/API_ServiceSummary.html ServiceSummary>
-- type.
--
-- /See:/ 'newService' smart constructor.
data Service = Service'
  { -- | The time when the App Runner service was deleted. It\'s in the Unix time
    -- stamp format.
    Service -> Maybe POSIX
deletedAt :: Prelude.Maybe Data.POSIX,
    -- | The encryption key that App Runner uses to encrypt the service logs and
    -- the copy of the source repository that App Runner maintains for the
    -- service. It can be either a customer-provided encryption key or an
    -- Amazon Web Services managed key.
    Service -> Maybe EncryptionConfiguration
encryptionConfiguration :: Prelude.Maybe EncryptionConfiguration,
    -- | The settings for the health check that App Runner performs to monitor
    -- the health of this service.
    Service -> Maybe HealthCheckConfiguration
healthCheckConfiguration :: Prelude.Maybe HealthCheckConfiguration,
    -- | The observability configuration of this service.
    Service -> Maybe ServiceObservabilityConfiguration
observabilityConfiguration :: Prelude.Maybe ServiceObservabilityConfiguration,
    -- | A subdomain URL that App Runner generated for this service. You can use
    -- this URL to access your service web application.
    Service -> Maybe Text
serviceUrl :: Prelude.Maybe Prelude.Text,
    -- | The customer-provided service name.
    Service -> Text
serviceName :: Prelude.Text,
    -- | An ID that App Runner generated for this service. It\'s unique within
    -- the Amazon Web Services Region.
    Service -> Text
serviceId :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of this service.
    Service -> Text
serviceArn :: Prelude.Text,
    -- | The time when the App Runner service was created. It\'s in the Unix time
    -- stamp format.
    Service -> POSIX
createdAt :: Data.POSIX,
    -- | The time when the App Runner service was last updated at. It\'s in the
    -- Unix time stamp format.
    Service -> POSIX
updatedAt :: Data.POSIX,
    -- | The current state of the App Runner service. These particular values
    -- mean the following.
    --
    -- -   @CREATE_FAILED@ – The service failed to create. To troubleshoot this
    --     failure, read the failure events and logs, change any parameters
    --     that need to be fixed, and retry the call to create the service.
    --
    --     The failed service isn\'t usable, and still counts towards your
    --     service quota. When you\'re done analyzing the failure, delete the
    --     service.
    --
    -- -   @DELETE_FAILED@ – The service failed to delete and can\'t be
    --     successfully recovered. Retry the service deletion call to ensure
    --     that all related resources are removed.
    Service -> ServiceStatus
status :: ServiceStatus,
    -- | The source deployed to the App Runner service. It can be a code or an
    -- image repository.
    Service -> SourceConfiguration
sourceConfiguration :: SourceConfiguration,
    -- | The runtime configuration of instances (scaling units) of this service.
    Service -> InstanceConfiguration
instanceConfiguration :: InstanceConfiguration,
    -- | Summary information for the App Runner automatic scaling configuration
    -- resource that\'s associated with this service.
    Service -> AutoScalingConfigurationSummary
autoScalingConfigurationSummary :: AutoScalingConfigurationSummary,
    -- | Configuration settings related to network traffic of the web application
    -- that this service runs.
    Service -> NetworkConfiguration
networkConfiguration :: NetworkConfiguration
  }
  deriving (Service -> Service -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Service -> Service -> Bool
$c/= :: Service -> Service -> Bool
== :: Service -> Service -> Bool
$c== :: Service -> Service -> Bool
Prelude.Eq, Int -> Service -> ShowS
[Service] -> ShowS
Service -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Service] -> ShowS
$cshowList :: [Service] -> ShowS
show :: Service -> String
$cshow :: Service -> String
showsPrec :: Int -> Service -> ShowS
$cshowsPrec :: Int -> Service -> ShowS
Prelude.Show, forall x. Rep Service x -> Service
forall x. Service -> Rep Service x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Service x -> Service
$cfrom :: forall x. Service -> Rep Service x
Prelude.Generic)

-- |
-- Create a value of 'Service' 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:
--
-- 'deletedAt', 'service_deletedAt' - The time when the App Runner service was deleted. It\'s in the Unix time
-- stamp format.
--
-- 'encryptionConfiguration', 'service_encryptionConfiguration' - The encryption key that App Runner uses to encrypt the service logs and
-- the copy of the source repository that App Runner maintains for the
-- service. It can be either a customer-provided encryption key or an
-- Amazon Web Services managed key.
--
-- 'healthCheckConfiguration', 'service_healthCheckConfiguration' - The settings for the health check that App Runner performs to monitor
-- the health of this service.
--
-- 'observabilityConfiguration', 'service_observabilityConfiguration' - The observability configuration of this service.
--
-- 'serviceUrl', 'service_serviceUrl' - A subdomain URL that App Runner generated for this service. You can use
-- this URL to access your service web application.
--
-- 'serviceName', 'service_serviceName' - The customer-provided service name.
--
-- 'serviceId', 'service_serviceId' - An ID that App Runner generated for this service. It\'s unique within
-- the Amazon Web Services Region.
--
-- 'serviceArn', 'service_serviceArn' - The Amazon Resource Name (ARN) of this service.
--
-- 'createdAt', 'service_createdAt' - The time when the App Runner service was created. It\'s in the Unix time
-- stamp format.
--
-- 'updatedAt', 'service_updatedAt' - The time when the App Runner service was last updated at. It\'s in the
-- Unix time stamp format.
--
-- 'status', 'service_status' - The current state of the App Runner service. These particular values
-- mean the following.
--
-- -   @CREATE_FAILED@ – The service failed to create. To troubleshoot this
--     failure, read the failure events and logs, change any parameters
--     that need to be fixed, and retry the call to create the service.
--
--     The failed service isn\'t usable, and still counts towards your
--     service quota. When you\'re done analyzing the failure, delete the
--     service.
--
-- -   @DELETE_FAILED@ – The service failed to delete and can\'t be
--     successfully recovered. Retry the service deletion call to ensure
--     that all related resources are removed.
--
-- 'sourceConfiguration', 'service_sourceConfiguration' - The source deployed to the App Runner service. It can be a code or an
-- image repository.
--
-- 'instanceConfiguration', 'service_instanceConfiguration' - The runtime configuration of instances (scaling units) of this service.
--
-- 'autoScalingConfigurationSummary', 'service_autoScalingConfigurationSummary' - Summary information for the App Runner automatic scaling configuration
-- resource that\'s associated with this service.
--
-- 'networkConfiguration', 'service_networkConfiguration' - Configuration settings related to network traffic of the web application
-- that this service runs.
newService ::
  -- | 'serviceName'
  Prelude.Text ->
  -- | 'serviceId'
  Prelude.Text ->
  -- | 'serviceArn'
  Prelude.Text ->
  -- | 'createdAt'
  Prelude.UTCTime ->
  -- | 'updatedAt'
  Prelude.UTCTime ->
  -- | 'status'
  ServiceStatus ->
  -- | 'sourceConfiguration'
  SourceConfiguration ->
  -- | 'instanceConfiguration'
  InstanceConfiguration ->
  -- | 'autoScalingConfigurationSummary'
  AutoScalingConfigurationSummary ->
  -- | 'networkConfiguration'
  NetworkConfiguration ->
  Service
newService :: Text
-> Text
-> Text
-> UTCTime
-> UTCTime
-> ServiceStatus
-> SourceConfiguration
-> InstanceConfiguration
-> AutoScalingConfigurationSummary
-> NetworkConfiguration
-> Service
newService
  Text
pServiceName_
  Text
pServiceId_
  Text
pServiceArn_
  UTCTime
pCreatedAt_
  UTCTime
pUpdatedAt_
  ServiceStatus
pStatus_
  SourceConfiguration
pSourceConfiguration_
  InstanceConfiguration
pInstanceConfiguration_
  AutoScalingConfigurationSummary
pAutoScalingConfigurationSummary_
  NetworkConfiguration
pNetworkConfiguration_ =
    Service'
      { $sel:deletedAt:Service' :: Maybe POSIX
deletedAt = forall a. Maybe a
Prelude.Nothing,
        $sel:encryptionConfiguration:Service' :: Maybe EncryptionConfiguration
encryptionConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:healthCheckConfiguration:Service' :: Maybe HealthCheckConfiguration
healthCheckConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:observabilityConfiguration:Service' :: Maybe ServiceObservabilityConfiguration
observabilityConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:serviceUrl:Service' :: Maybe Text
serviceUrl = forall a. Maybe a
Prelude.Nothing,
        $sel:serviceName:Service' :: Text
serviceName = Text
pServiceName_,
        $sel:serviceId:Service' :: Text
serviceId = Text
pServiceId_,
        $sel:serviceArn:Service' :: Text
serviceArn = Text
pServiceArn_,
        $sel:createdAt:Service' :: POSIX
createdAt = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreatedAt_,
        $sel:updatedAt:Service' :: POSIX
updatedAt = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pUpdatedAt_,
        $sel:status:Service' :: ServiceStatus
status = ServiceStatus
pStatus_,
        $sel:sourceConfiguration:Service' :: SourceConfiguration
sourceConfiguration = SourceConfiguration
pSourceConfiguration_,
        $sel:instanceConfiguration:Service' :: InstanceConfiguration
instanceConfiguration = InstanceConfiguration
pInstanceConfiguration_,
        $sel:autoScalingConfigurationSummary:Service' :: AutoScalingConfigurationSummary
autoScalingConfigurationSummary =
          AutoScalingConfigurationSummary
pAutoScalingConfigurationSummary_,
        $sel:networkConfiguration:Service' :: NetworkConfiguration
networkConfiguration = NetworkConfiguration
pNetworkConfiguration_
      }

-- | The time when the App Runner service was deleted. It\'s in the Unix time
-- stamp format.
service_deletedAt :: Lens.Lens' Service (Prelude.Maybe Prelude.UTCTime)
service_deletedAt :: Lens' Service (Maybe UTCTime)
service_deletedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {Maybe POSIX
deletedAt :: Maybe POSIX
$sel:deletedAt:Service' :: Service -> Maybe POSIX
deletedAt} -> Maybe POSIX
deletedAt) (\s :: Service
s@Service' {} Maybe POSIX
a -> Service
s {$sel:deletedAt:Service' :: Maybe POSIX
deletedAt = Maybe POSIX
a} :: Service) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The encryption key that App Runner uses to encrypt the service logs and
-- the copy of the source repository that App Runner maintains for the
-- service. It can be either a customer-provided encryption key or an
-- Amazon Web Services managed key.
service_encryptionConfiguration :: Lens.Lens' Service (Prelude.Maybe EncryptionConfiguration)
service_encryptionConfiguration :: Lens' Service (Maybe EncryptionConfiguration)
service_encryptionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {Maybe EncryptionConfiguration
encryptionConfiguration :: Maybe EncryptionConfiguration
$sel:encryptionConfiguration:Service' :: Service -> Maybe EncryptionConfiguration
encryptionConfiguration} -> Maybe EncryptionConfiguration
encryptionConfiguration) (\s :: Service
s@Service' {} Maybe EncryptionConfiguration
a -> Service
s {$sel:encryptionConfiguration:Service' :: Maybe EncryptionConfiguration
encryptionConfiguration = Maybe EncryptionConfiguration
a} :: Service)

-- | The settings for the health check that App Runner performs to monitor
-- the health of this service.
service_healthCheckConfiguration :: Lens.Lens' Service (Prelude.Maybe HealthCheckConfiguration)
service_healthCheckConfiguration :: Lens' Service (Maybe HealthCheckConfiguration)
service_healthCheckConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {Maybe HealthCheckConfiguration
healthCheckConfiguration :: Maybe HealthCheckConfiguration
$sel:healthCheckConfiguration:Service' :: Service -> Maybe HealthCheckConfiguration
healthCheckConfiguration} -> Maybe HealthCheckConfiguration
healthCheckConfiguration) (\s :: Service
s@Service' {} Maybe HealthCheckConfiguration
a -> Service
s {$sel:healthCheckConfiguration:Service' :: Maybe HealthCheckConfiguration
healthCheckConfiguration = Maybe HealthCheckConfiguration
a} :: Service)

-- | The observability configuration of this service.
service_observabilityConfiguration :: Lens.Lens' Service (Prelude.Maybe ServiceObservabilityConfiguration)
service_observabilityConfiguration :: Lens' Service (Maybe ServiceObservabilityConfiguration)
service_observabilityConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {Maybe ServiceObservabilityConfiguration
observabilityConfiguration :: Maybe ServiceObservabilityConfiguration
$sel:observabilityConfiguration:Service' :: Service -> Maybe ServiceObservabilityConfiguration
observabilityConfiguration} -> Maybe ServiceObservabilityConfiguration
observabilityConfiguration) (\s :: Service
s@Service' {} Maybe ServiceObservabilityConfiguration
a -> Service
s {$sel:observabilityConfiguration:Service' :: Maybe ServiceObservabilityConfiguration
observabilityConfiguration = Maybe ServiceObservabilityConfiguration
a} :: Service)

-- | A subdomain URL that App Runner generated for this service. You can use
-- this URL to access your service web application.
service_serviceUrl :: Lens.Lens' Service (Prelude.Maybe Prelude.Text)
service_serviceUrl :: Lens' Service (Maybe Text)
service_serviceUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {Maybe Text
serviceUrl :: Maybe Text
$sel:serviceUrl:Service' :: Service -> Maybe Text
serviceUrl} -> Maybe Text
serviceUrl) (\s :: Service
s@Service' {} Maybe Text
a -> Service
s {$sel:serviceUrl:Service' :: Maybe Text
serviceUrl = Maybe Text
a} :: Service)

-- | The customer-provided service name.
service_serviceName :: Lens.Lens' Service Prelude.Text
service_serviceName :: Lens' Service Text
service_serviceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {Text
serviceName :: Text
$sel:serviceName:Service' :: Service -> Text
serviceName} -> Text
serviceName) (\s :: Service
s@Service' {} Text
a -> Service
s {$sel:serviceName:Service' :: Text
serviceName = Text
a} :: Service)

-- | An ID that App Runner generated for this service. It\'s unique within
-- the Amazon Web Services Region.
service_serviceId :: Lens.Lens' Service Prelude.Text
service_serviceId :: Lens' Service Text
service_serviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {Text
serviceId :: Text
$sel:serviceId:Service' :: Service -> Text
serviceId} -> Text
serviceId) (\s :: Service
s@Service' {} Text
a -> Service
s {$sel:serviceId:Service' :: Text
serviceId = Text
a} :: Service)

-- | The Amazon Resource Name (ARN) of this service.
service_serviceArn :: Lens.Lens' Service Prelude.Text
service_serviceArn :: Lens' Service Text
service_serviceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {Text
serviceArn :: Text
$sel:serviceArn:Service' :: Service -> Text
serviceArn} -> Text
serviceArn) (\s :: Service
s@Service' {} Text
a -> Service
s {$sel:serviceArn:Service' :: Text
serviceArn = Text
a} :: Service)

-- | The time when the App Runner service was created. It\'s in the Unix time
-- stamp format.
service_createdAt :: Lens.Lens' Service Prelude.UTCTime
service_createdAt :: Lens' Service UTCTime
service_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {POSIX
createdAt :: POSIX
$sel:createdAt:Service' :: Service -> POSIX
createdAt} -> POSIX
createdAt) (\s :: Service
s@Service' {} POSIX
a -> Service
s {$sel:createdAt:Service' :: POSIX
createdAt = POSIX
a} :: Service) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The time when the App Runner service was last updated at. It\'s in the
-- Unix time stamp format.
service_updatedAt :: Lens.Lens' Service Prelude.UTCTime
service_updatedAt :: Lens' Service UTCTime
service_updatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {POSIX
updatedAt :: POSIX
$sel:updatedAt:Service' :: Service -> POSIX
updatedAt} -> POSIX
updatedAt) (\s :: Service
s@Service' {} POSIX
a -> Service
s {$sel:updatedAt:Service' :: POSIX
updatedAt = POSIX
a} :: Service) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The current state of the App Runner service. These particular values
-- mean the following.
--
-- -   @CREATE_FAILED@ – The service failed to create. To troubleshoot this
--     failure, read the failure events and logs, change any parameters
--     that need to be fixed, and retry the call to create the service.
--
--     The failed service isn\'t usable, and still counts towards your
--     service quota. When you\'re done analyzing the failure, delete the
--     service.
--
-- -   @DELETE_FAILED@ – The service failed to delete and can\'t be
--     successfully recovered. Retry the service deletion call to ensure
--     that all related resources are removed.
service_status :: Lens.Lens' Service ServiceStatus
service_status :: Lens' Service ServiceStatus
service_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {ServiceStatus
status :: ServiceStatus
$sel:status:Service' :: Service -> ServiceStatus
status} -> ServiceStatus
status) (\s :: Service
s@Service' {} ServiceStatus
a -> Service
s {$sel:status:Service' :: ServiceStatus
status = ServiceStatus
a} :: Service)

-- | The source deployed to the App Runner service. It can be a code or an
-- image repository.
service_sourceConfiguration :: Lens.Lens' Service SourceConfiguration
service_sourceConfiguration :: Lens' Service SourceConfiguration
service_sourceConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {SourceConfiguration
sourceConfiguration :: SourceConfiguration
$sel:sourceConfiguration:Service' :: Service -> SourceConfiguration
sourceConfiguration} -> SourceConfiguration
sourceConfiguration) (\s :: Service
s@Service' {} SourceConfiguration
a -> Service
s {$sel:sourceConfiguration:Service' :: SourceConfiguration
sourceConfiguration = SourceConfiguration
a} :: Service)

-- | The runtime configuration of instances (scaling units) of this service.
service_instanceConfiguration :: Lens.Lens' Service InstanceConfiguration
service_instanceConfiguration :: Lens' Service InstanceConfiguration
service_instanceConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {InstanceConfiguration
instanceConfiguration :: InstanceConfiguration
$sel:instanceConfiguration:Service' :: Service -> InstanceConfiguration
instanceConfiguration} -> InstanceConfiguration
instanceConfiguration) (\s :: Service
s@Service' {} InstanceConfiguration
a -> Service
s {$sel:instanceConfiguration:Service' :: InstanceConfiguration
instanceConfiguration = InstanceConfiguration
a} :: Service)

-- | Summary information for the App Runner automatic scaling configuration
-- resource that\'s associated with this service.
service_autoScalingConfigurationSummary :: Lens.Lens' Service AutoScalingConfigurationSummary
service_autoScalingConfigurationSummary :: Lens' Service AutoScalingConfigurationSummary
service_autoScalingConfigurationSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {AutoScalingConfigurationSummary
autoScalingConfigurationSummary :: AutoScalingConfigurationSummary
$sel:autoScalingConfigurationSummary:Service' :: Service -> AutoScalingConfigurationSummary
autoScalingConfigurationSummary} -> AutoScalingConfigurationSummary
autoScalingConfigurationSummary) (\s :: Service
s@Service' {} AutoScalingConfigurationSummary
a -> Service
s {$sel:autoScalingConfigurationSummary:Service' :: AutoScalingConfigurationSummary
autoScalingConfigurationSummary = AutoScalingConfigurationSummary
a} :: Service)

-- | Configuration settings related to network traffic of the web application
-- that this service runs.
service_networkConfiguration :: Lens.Lens' Service NetworkConfiguration
service_networkConfiguration :: Lens' Service NetworkConfiguration
service_networkConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Service' {NetworkConfiguration
networkConfiguration :: NetworkConfiguration
$sel:networkConfiguration:Service' :: Service -> NetworkConfiguration
networkConfiguration} -> NetworkConfiguration
networkConfiguration) (\s :: Service
s@Service' {} NetworkConfiguration
a -> Service
s {$sel:networkConfiguration:Service' :: NetworkConfiguration
networkConfiguration = NetworkConfiguration
a} :: Service)

instance Data.FromJSON Service where
  parseJSON :: Value -> Parser Service
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Service"
      ( \Object
x ->
          Maybe POSIX
-> Maybe EncryptionConfiguration
-> Maybe HealthCheckConfiguration
-> Maybe ServiceObservabilityConfiguration
-> Maybe Text
-> Text
-> Text
-> Text
-> POSIX
-> POSIX
-> ServiceStatus
-> SourceConfiguration
-> InstanceConfiguration
-> AutoScalingConfigurationSummary
-> NetworkConfiguration
-> Service
Service'
            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
"DeletedAt")
            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
"EncryptionConfiguration")
            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
"HealthCheckConfiguration")
            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
"ObservabilityConfiguration")
            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
"ServiceUrl")
            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
"ServiceName")
            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
"ServiceId")
            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
"ServiceArn")
            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
"CreatedAt")
            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
"UpdatedAt")
            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
"Status")
            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
"SourceConfiguration")
            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
"InstanceConfiguration")
            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
"AutoScalingConfigurationSummary")
            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
"NetworkConfiguration")
      )

instance Prelude.Hashable Service where
  hashWithSalt :: Int -> Service -> Int
hashWithSalt Int
_salt Service' {Maybe Text
Maybe POSIX
Maybe EncryptionConfiguration
Maybe HealthCheckConfiguration
Maybe ServiceObservabilityConfiguration
Text
POSIX
AutoScalingConfigurationSummary
InstanceConfiguration
NetworkConfiguration
ServiceStatus
SourceConfiguration
networkConfiguration :: NetworkConfiguration
autoScalingConfigurationSummary :: AutoScalingConfigurationSummary
instanceConfiguration :: InstanceConfiguration
sourceConfiguration :: SourceConfiguration
status :: ServiceStatus
updatedAt :: POSIX
createdAt :: POSIX
serviceArn :: Text
serviceId :: Text
serviceName :: Text
serviceUrl :: Maybe Text
observabilityConfiguration :: Maybe ServiceObservabilityConfiguration
healthCheckConfiguration :: Maybe HealthCheckConfiguration
encryptionConfiguration :: Maybe EncryptionConfiguration
deletedAt :: Maybe POSIX
$sel:networkConfiguration:Service' :: Service -> NetworkConfiguration
$sel:autoScalingConfigurationSummary:Service' :: Service -> AutoScalingConfigurationSummary
$sel:instanceConfiguration:Service' :: Service -> InstanceConfiguration
$sel:sourceConfiguration:Service' :: Service -> SourceConfiguration
$sel:status:Service' :: Service -> ServiceStatus
$sel:updatedAt:Service' :: Service -> POSIX
$sel:createdAt:Service' :: Service -> POSIX
$sel:serviceArn:Service' :: Service -> Text
$sel:serviceId:Service' :: Service -> Text
$sel:serviceName:Service' :: Service -> Text
$sel:serviceUrl:Service' :: Service -> Maybe Text
$sel:observabilityConfiguration:Service' :: Service -> Maybe ServiceObservabilityConfiguration
$sel:healthCheckConfiguration:Service' :: Service -> Maybe HealthCheckConfiguration
$sel:encryptionConfiguration:Service' :: Service -> Maybe EncryptionConfiguration
$sel:deletedAt:Service' :: Service -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
deletedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EncryptionConfiguration
encryptionConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HealthCheckConfiguration
healthCheckConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ServiceObservabilityConfiguration
observabilityConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serviceUrl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
updatedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ServiceStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SourceConfiguration
sourceConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` InstanceConfiguration
instanceConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AutoScalingConfigurationSummary
autoScalingConfigurationSummary
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NetworkConfiguration
networkConfiguration

instance Prelude.NFData Service where
  rnf :: Service -> ()
rnf Service' {Maybe Text
Maybe POSIX
Maybe EncryptionConfiguration
Maybe HealthCheckConfiguration
Maybe ServiceObservabilityConfiguration
Text
POSIX
AutoScalingConfigurationSummary
InstanceConfiguration
NetworkConfiguration
ServiceStatus
SourceConfiguration
networkConfiguration :: NetworkConfiguration
autoScalingConfigurationSummary :: AutoScalingConfigurationSummary
instanceConfiguration :: InstanceConfiguration
sourceConfiguration :: SourceConfiguration
status :: ServiceStatus
updatedAt :: POSIX
createdAt :: POSIX
serviceArn :: Text
serviceId :: Text
serviceName :: Text
serviceUrl :: Maybe Text
observabilityConfiguration :: Maybe ServiceObservabilityConfiguration
healthCheckConfiguration :: Maybe HealthCheckConfiguration
encryptionConfiguration :: Maybe EncryptionConfiguration
deletedAt :: Maybe POSIX
$sel:networkConfiguration:Service' :: Service -> NetworkConfiguration
$sel:autoScalingConfigurationSummary:Service' :: Service -> AutoScalingConfigurationSummary
$sel:instanceConfiguration:Service' :: Service -> InstanceConfiguration
$sel:sourceConfiguration:Service' :: Service -> SourceConfiguration
$sel:status:Service' :: Service -> ServiceStatus
$sel:updatedAt:Service' :: Service -> POSIX
$sel:createdAt:Service' :: Service -> POSIX
$sel:serviceArn:Service' :: Service -> Text
$sel:serviceId:Service' :: Service -> Text
$sel:serviceName:Service' :: Service -> Text
$sel:serviceUrl:Service' :: Service -> Maybe Text
$sel:observabilityConfiguration:Service' :: Service -> Maybe ServiceObservabilityConfiguration
$sel:healthCheckConfiguration:Service' :: Service -> Maybe HealthCheckConfiguration
$sel:encryptionConfiguration:Service' :: Service -> Maybe EncryptionConfiguration
$sel:deletedAt:Service' :: Service -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
deletedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionConfiguration
encryptionConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HealthCheckConfiguration
healthCheckConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ServiceObservabilityConfiguration
observabilityConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serviceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serviceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serviceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
updatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ServiceStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SourceConfiguration
sourceConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf InstanceConfiguration
instanceConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        AutoScalingConfigurationSummary
autoScalingConfigurationSummary
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NetworkConfiguration
networkConfiguration