{-# 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.GlobalAccelerator.CreateEndpointGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Create an endpoint group for the specified listener. An endpoint group
-- is a collection of endpoints in one Amazon Web Services Region. A
-- resource must be valid and active when you add it as an endpoint.
module Amazonka.GlobalAccelerator.CreateEndpointGroup
  ( -- * Creating a Request
    CreateEndpointGroup (..),
    newCreateEndpointGroup,

    -- * Request Lenses
    createEndpointGroup_endpointConfigurations,
    createEndpointGroup_healthCheckIntervalSeconds,
    createEndpointGroup_healthCheckPath,
    createEndpointGroup_healthCheckPort,
    createEndpointGroup_healthCheckProtocol,
    createEndpointGroup_portOverrides,
    createEndpointGroup_thresholdCount,
    createEndpointGroup_trafficDialPercentage,
    createEndpointGroup_listenerArn,
    createEndpointGroup_endpointGroupRegion,
    createEndpointGroup_idempotencyToken,

    -- * Destructuring the Response
    CreateEndpointGroupResponse (..),
    newCreateEndpointGroupResponse,

    -- * Response Lenses
    createEndpointGroupResponse_endpointGroup,
    createEndpointGroupResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateEndpointGroup' smart constructor.
data CreateEndpointGroup = CreateEndpointGroup'
  { -- | The list of endpoint objects.
    CreateEndpointGroup -> Maybe [EndpointConfiguration]
endpointConfigurations :: Prelude.Maybe [EndpointConfiguration],
    -- | The time—10 seconds or 30 seconds—between each health check for an
    -- endpoint. The default value is 30.
    CreateEndpointGroup -> Maybe Natural
healthCheckIntervalSeconds :: Prelude.Maybe Prelude.Natural,
    -- | If the protocol is HTTP\/S, then this specifies the path that is the
    -- destination for health check targets. The default value is slash (\/).
    CreateEndpointGroup -> Maybe Text
healthCheckPath :: Prelude.Maybe Prelude.Text,
    -- | The port that Global Accelerator uses to check the health of endpoints
    -- that are part of this endpoint group. The default port is the listener
    -- port that this endpoint group is associated with. If listener port is a
    -- list of ports, Global Accelerator uses the first port in the list.
    CreateEndpointGroup -> Maybe Natural
healthCheckPort :: Prelude.Maybe Prelude.Natural,
    -- | The protocol that Global Accelerator uses to check the health of
    -- endpoints that are part of this endpoint group. The default value is
    -- TCP.
    CreateEndpointGroup -> Maybe HealthCheckProtocol
healthCheckProtocol :: Prelude.Maybe HealthCheckProtocol,
    -- | Override specific listener ports used to route traffic to endpoints that
    -- are part of this endpoint group. For example, you can create a port
    -- override in which the listener receives user traffic on ports 80 and
    -- 443, but your accelerator routes that traffic to ports 1080 and 1443,
    -- respectively, on the endpoints.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/global-accelerator/latest/dg/about-endpoint-groups-port-override.html Overriding listener ports>
    -- in the /Global Accelerator Developer Guide/.
    CreateEndpointGroup -> Maybe [PortOverride]
portOverrides :: Prelude.Maybe [PortOverride],
    -- | The number of consecutive health checks required to set the state of a
    -- healthy endpoint to unhealthy, or to set an unhealthy endpoint to
    -- healthy. The default value is 3.
    CreateEndpointGroup -> Maybe Natural
thresholdCount :: Prelude.Maybe Prelude.Natural,
    -- | The percentage of traffic to send to an Amazon Web Services Region.
    -- Additional traffic is distributed to other endpoint groups for this
    -- listener.
    --
    -- Use this action to increase (dial up) or decrease (dial down) traffic to
    -- a specific Region. The percentage is applied to the traffic that would
    -- otherwise have been routed to the Region based on optimal routing.
    --
    -- The default value is 100.
    CreateEndpointGroup -> Maybe Double
trafficDialPercentage :: Prelude.Maybe Prelude.Double,
    -- | The Amazon Resource Name (ARN) of the listener.
    CreateEndpointGroup -> Text
listenerArn :: Prelude.Text,
    -- | The Amazon Web Services Region where the endpoint group is located. A
    -- listener can have only one endpoint group in a specific Region.
    CreateEndpointGroup -> Text
endpointGroupRegion :: Prelude.Text,
    -- | A unique, case-sensitive identifier that you provide to ensure the
    -- idempotency—that is, the uniqueness—of the request.
    CreateEndpointGroup -> Text
idempotencyToken :: Prelude.Text
  }
  deriving (CreateEndpointGroup -> CreateEndpointGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateEndpointGroup -> CreateEndpointGroup -> Bool
$c/= :: CreateEndpointGroup -> CreateEndpointGroup -> Bool
== :: CreateEndpointGroup -> CreateEndpointGroup -> Bool
$c== :: CreateEndpointGroup -> CreateEndpointGroup -> Bool
Prelude.Eq, ReadPrec [CreateEndpointGroup]
ReadPrec CreateEndpointGroup
Int -> ReadS CreateEndpointGroup
ReadS [CreateEndpointGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateEndpointGroup]
$creadListPrec :: ReadPrec [CreateEndpointGroup]
readPrec :: ReadPrec CreateEndpointGroup
$creadPrec :: ReadPrec CreateEndpointGroup
readList :: ReadS [CreateEndpointGroup]
$creadList :: ReadS [CreateEndpointGroup]
readsPrec :: Int -> ReadS CreateEndpointGroup
$creadsPrec :: Int -> ReadS CreateEndpointGroup
Prelude.Read, Int -> CreateEndpointGroup -> ShowS
[CreateEndpointGroup] -> ShowS
CreateEndpointGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateEndpointGroup] -> ShowS
$cshowList :: [CreateEndpointGroup] -> ShowS
show :: CreateEndpointGroup -> String
$cshow :: CreateEndpointGroup -> String
showsPrec :: Int -> CreateEndpointGroup -> ShowS
$cshowsPrec :: Int -> CreateEndpointGroup -> ShowS
Prelude.Show, forall x. Rep CreateEndpointGroup x -> CreateEndpointGroup
forall x. CreateEndpointGroup -> Rep CreateEndpointGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateEndpointGroup x -> CreateEndpointGroup
$cfrom :: forall x. CreateEndpointGroup -> Rep CreateEndpointGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateEndpointGroup' 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:
--
-- 'endpointConfigurations', 'createEndpointGroup_endpointConfigurations' - The list of endpoint objects.
--
-- 'healthCheckIntervalSeconds', 'createEndpointGroup_healthCheckIntervalSeconds' - The time—10 seconds or 30 seconds—between each health check for an
-- endpoint. The default value is 30.
--
-- 'healthCheckPath', 'createEndpointGroup_healthCheckPath' - If the protocol is HTTP\/S, then this specifies the path that is the
-- destination for health check targets. The default value is slash (\/).
--
-- 'healthCheckPort', 'createEndpointGroup_healthCheckPort' - The port that Global Accelerator uses to check the health of endpoints
-- that are part of this endpoint group. The default port is the listener
-- port that this endpoint group is associated with. If listener port is a
-- list of ports, Global Accelerator uses the first port in the list.
--
-- 'healthCheckProtocol', 'createEndpointGroup_healthCheckProtocol' - The protocol that Global Accelerator uses to check the health of
-- endpoints that are part of this endpoint group. The default value is
-- TCP.
--
-- 'portOverrides', 'createEndpointGroup_portOverrides' - Override specific listener ports used to route traffic to endpoints that
-- are part of this endpoint group. For example, you can create a port
-- override in which the listener receives user traffic on ports 80 and
-- 443, but your accelerator routes that traffic to ports 1080 and 1443,
-- respectively, on the endpoints.
--
-- For more information, see
-- <https://docs.aws.amazon.com/global-accelerator/latest/dg/about-endpoint-groups-port-override.html Overriding listener ports>
-- in the /Global Accelerator Developer Guide/.
--
-- 'thresholdCount', 'createEndpointGroup_thresholdCount' - The number of consecutive health checks required to set the state of a
-- healthy endpoint to unhealthy, or to set an unhealthy endpoint to
-- healthy. The default value is 3.
--
-- 'trafficDialPercentage', 'createEndpointGroup_trafficDialPercentage' - The percentage of traffic to send to an Amazon Web Services Region.
-- Additional traffic is distributed to other endpoint groups for this
-- listener.
--
-- Use this action to increase (dial up) or decrease (dial down) traffic to
-- a specific Region. The percentage is applied to the traffic that would
-- otherwise have been routed to the Region based on optimal routing.
--
-- The default value is 100.
--
-- 'listenerArn', 'createEndpointGroup_listenerArn' - The Amazon Resource Name (ARN) of the listener.
--
-- 'endpointGroupRegion', 'createEndpointGroup_endpointGroupRegion' - The Amazon Web Services Region where the endpoint group is located. A
-- listener can have only one endpoint group in a specific Region.
--
-- 'idempotencyToken', 'createEndpointGroup_idempotencyToken' - A unique, case-sensitive identifier that you provide to ensure the
-- idempotency—that is, the uniqueness—of the request.
newCreateEndpointGroup ::
  -- | 'listenerArn'
  Prelude.Text ->
  -- | 'endpointGroupRegion'
  Prelude.Text ->
  -- | 'idempotencyToken'
  Prelude.Text ->
  CreateEndpointGroup
newCreateEndpointGroup :: Text -> Text -> Text -> CreateEndpointGroup
newCreateEndpointGroup
  Text
pListenerArn_
  Text
pEndpointGroupRegion_
  Text
pIdempotencyToken_ =
    CreateEndpointGroup'
      { $sel:endpointConfigurations:CreateEndpointGroup' :: Maybe [EndpointConfiguration]
endpointConfigurations =
          forall a. Maybe a
Prelude.Nothing,
        $sel:healthCheckIntervalSeconds:CreateEndpointGroup' :: Maybe Natural
healthCheckIntervalSeconds = forall a. Maybe a
Prelude.Nothing,
        $sel:healthCheckPath:CreateEndpointGroup' :: Maybe Text
healthCheckPath = forall a. Maybe a
Prelude.Nothing,
        $sel:healthCheckPort:CreateEndpointGroup' :: Maybe Natural
healthCheckPort = forall a. Maybe a
Prelude.Nothing,
        $sel:healthCheckProtocol:CreateEndpointGroup' :: Maybe HealthCheckProtocol
healthCheckProtocol = forall a. Maybe a
Prelude.Nothing,
        $sel:portOverrides:CreateEndpointGroup' :: Maybe [PortOverride]
portOverrides = forall a. Maybe a
Prelude.Nothing,
        $sel:thresholdCount:CreateEndpointGroup' :: Maybe Natural
thresholdCount = forall a. Maybe a
Prelude.Nothing,
        $sel:trafficDialPercentage:CreateEndpointGroup' :: Maybe Double
trafficDialPercentage = forall a. Maybe a
Prelude.Nothing,
        $sel:listenerArn:CreateEndpointGroup' :: Text
listenerArn = Text
pListenerArn_,
        $sel:endpointGroupRegion:CreateEndpointGroup' :: Text
endpointGroupRegion = Text
pEndpointGroupRegion_,
        $sel:idempotencyToken:CreateEndpointGroup' :: Text
idempotencyToken = Text
pIdempotencyToken_
      }

-- | The list of endpoint objects.
createEndpointGroup_endpointConfigurations :: Lens.Lens' CreateEndpointGroup (Prelude.Maybe [EndpointConfiguration])
createEndpointGroup_endpointConfigurations :: Lens' CreateEndpointGroup (Maybe [EndpointConfiguration])
createEndpointGroup_endpointConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Maybe [EndpointConfiguration]
endpointConfigurations :: Maybe [EndpointConfiguration]
$sel:endpointConfigurations:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe [EndpointConfiguration]
endpointConfigurations} -> Maybe [EndpointConfiguration]
endpointConfigurations) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Maybe [EndpointConfiguration]
a -> CreateEndpointGroup
s {$sel:endpointConfigurations:CreateEndpointGroup' :: Maybe [EndpointConfiguration]
endpointConfigurations = Maybe [EndpointConfiguration]
a} :: CreateEndpointGroup) 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 time—10 seconds or 30 seconds—between each health check for an
-- endpoint. The default value is 30.
createEndpointGroup_healthCheckIntervalSeconds :: Lens.Lens' CreateEndpointGroup (Prelude.Maybe Prelude.Natural)
createEndpointGroup_healthCheckIntervalSeconds :: Lens' CreateEndpointGroup (Maybe Natural)
createEndpointGroup_healthCheckIntervalSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Maybe Natural
healthCheckIntervalSeconds :: Maybe Natural
$sel:healthCheckIntervalSeconds:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
healthCheckIntervalSeconds} -> Maybe Natural
healthCheckIntervalSeconds) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Maybe Natural
a -> CreateEndpointGroup
s {$sel:healthCheckIntervalSeconds:CreateEndpointGroup' :: Maybe Natural
healthCheckIntervalSeconds = Maybe Natural
a} :: CreateEndpointGroup)

-- | If the protocol is HTTP\/S, then this specifies the path that is the
-- destination for health check targets. The default value is slash (\/).
createEndpointGroup_healthCheckPath :: Lens.Lens' CreateEndpointGroup (Prelude.Maybe Prelude.Text)
createEndpointGroup_healthCheckPath :: Lens' CreateEndpointGroup (Maybe Text)
createEndpointGroup_healthCheckPath = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Maybe Text
healthCheckPath :: Maybe Text
$sel:healthCheckPath:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Text
healthCheckPath} -> Maybe Text
healthCheckPath) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Maybe Text
a -> CreateEndpointGroup
s {$sel:healthCheckPath:CreateEndpointGroup' :: Maybe Text
healthCheckPath = Maybe Text
a} :: CreateEndpointGroup)

-- | The port that Global Accelerator uses to check the health of endpoints
-- that are part of this endpoint group. The default port is the listener
-- port that this endpoint group is associated with. If listener port is a
-- list of ports, Global Accelerator uses the first port in the list.
createEndpointGroup_healthCheckPort :: Lens.Lens' CreateEndpointGroup (Prelude.Maybe Prelude.Natural)
createEndpointGroup_healthCheckPort :: Lens' CreateEndpointGroup (Maybe Natural)
createEndpointGroup_healthCheckPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Maybe Natural
healthCheckPort :: Maybe Natural
$sel:healthCheckPort:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
healthCheckPort} -> Maybe Natural
healthCheckPort) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Maybe Natural
a -> CreateEndpointGroup
s {$sel:healthCheckPort:CreateEndpointGroup' :: Maybe Natural
healthCheckPort = Maybe Natural
a} :: CreateEndpointGroup)

-- | The protocol that Global Accelerator uses to check the health of
-- endpoints that are part of this endpoint group. The default value is
-- TCP.
createEndpointGroup_healthCheckProtocol :: Lens.Lens' CreateEndpointGroup (Prelude.Maybe HealthCheckProtocol)
createEndpointGroup_healthCheckProtocol :: Lens' CreateEndpointGroup (Maybe HealthCheckProtocol)
createEndpointGroup_healthCheckProtocol = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Maybe HealthCheckProtocol
healthCheckProtocol :: Maybe HealthCheckProtocol
$sel:healthCheckProtocol:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe HealthCheckProtocol
healthCheckProtocol} -> Maybe HealthCheckProtocol
healthCheckProtocol) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Maybe HealthCheckProtocol
a -> CreateEndpointGroup
s {$sel:healthCheckProtocol:CreateEndpointGroup' :: Maybe HealthCheckProtocol
healthCheckProtocol = Maybe HealthCheckProtocol
a} :: CreateEndpointGroup)

-- | Override specific listener ports used to route traffic to endpoints that
-- are part of this endpoint group. For example, you can create a port
-- override in which the listener receives user traffic on ports 80 and
-- 443, but your accelerator routes that traffic to ports 1080 and 1443,
-- respectively, on the endpoints.
--
-- For more information, see
-- <https://docs.aws.amazon.com/global-accelerator/latest/dg/about-endpoint-groups-port-override.html Overriding listener ports>
-- in the /Global Accelerator Developer Guide/.
createEndpointGroup_portOverrides :: Lens.Lens' CreateEndpointGroup (Prelude.Maybe [PortOverride])
createEndpointGroup_portOverrides :: Lens' CreateEndpointGroup (Maybe [PortOverride])
createEndpointGroup_portOverrides = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Maybe [PortOverride]
portOverrides :: Maybe [PortOverride]
$sel:portOverrides:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe [PortOverride]
portOverrides} -> Maybe [PortOverride]
portOverrides) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Maybe [PortOverride]
a -> CreateEndpointGroup
s {$sel:portOverrides:CreateEndpointGroup' :: Maybe [PortOverride]
portOverrides = Maybe [PortOverride]
a} :: CreateEndpointGroup) 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 number of consecutive health checks required to set the state of a
-- healthy endpoint to unhealthy, or to set an unhealthy endpoint to
-- healthy. The default value is 3.
createEndpointGroup_thresholdCount :: Lens.Lens' CreateEndpointGroup (Prelude.Maybe Prelude.Natural)
createEndpointGroup_thresholdCount :: Lens' CreateEndpointGroup (Maybe Natural)
createEndpointGroup_thresholdCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Maybe Natural
thresholdCount :: Maybe Natural
$sel:thresholdCount:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
thresholdCount} -> Maybe Natural
thresholdCount) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Maybe Natural
a -> CreateEndpointGroup
s {$sel:thresholdCount:CreateEndpointGroup' :: Maybe Natural
thresholdCount = Maybe Natural
a} :: CreateEndpointGroup)

-- | The percentage of traffic to send to an Amazon Web Services Region.
-- Additional traffic is distributed to other endpoint groups for this
-- listener.
--
-- Use this action to increase (dial up) or decrease (dial down) traffic to
-- a specific Region. The percentage is applied to the traffic that would
-- otherwise have been routed to the Region based on optimal routing.
--
-- The default value is 100.
createEndpointGroup_trafficDialPercentage :: Lens.Lens' CreateEndpointGroup (Prelude.Maybe Prelude.Double)
createEndpointGroup_trafficDialPercentage :: Lens' CreateEndpointGroup (Maybe Double)
createEndpointGroup_trafficDialPercentage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Maybe Double
trafficDialPercentage :: Maybe Double
$sel:trafficDialPercentage:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Double
trafficDialPercentage} -> Maybe Double
trafficDialPercentage) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Maybe Double
a -> CreateEndpointGroup
s {$sel:trafficDialPercentage:CreateEndpointGroup' :: Maybe Double
trafficDialPercentage = Maybe Double
a} :: CreateEndpointGroup)

-- | The Amazon Resource Name (ARN) of the listener.
createEndpointGroup_listenerArn :: Lens.Lens' CreateEndpointGroup Prelude.Text
createEndpointGroup_listenerArn :: Lens' CreateEndpointGroup Text
createEndpointGroup_listenerArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Text
listenerArn :: Text
$sel:listenerArn:CreateEndpointGroup' :: CreateEndpointGroup -> Text
listenerArn} -> Text
listenerArn) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Text
a -> CreateEndpointGroup
s {$sel:listenerArn:CreateEndpointGroup' :: Text
listenerArn = Text
a} :: CreateEndpointGroup)

-- | The Amazon Web Services Region where the endpoint group is located. A
-- listener can have only one endpoint group in a specific Region.
createEndpointGroup_endpointGroupRegion :: Lens.Lens' CreateEndpointGroup Prelude.Text
createEndpointGroup_endpointGroupRegion :: Lens' CreateEndpointGroup Text
createEndpointGroup_endpointGroupRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Text
endpointGroupRegion :: Text
$sel:endpointGroupRegion:CreateEndpointGroup' :: CreateEndpointGroup -> Text
endpointGroupRegion} -> Text
endpointGroupRegion) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Text
a -> CreateEndpointGroup
s {$sel:endpointGroupRegion:CreateEndpointGroup' :: Text
endpointGroupRegion = Text
a} :: CreateEndpointGroup)

-- | A unique, case-sensitive identifier that you provide to ensure the
-- idempotency—that is, the uniqueness—of the request.
createEndpointGroup_idempotencyToken :: Lens.Lens' CreateEndpointGroup Prelude.Text
createEndpointGroup_idempotencyToken :: Lens' CreateEndpointGroup Text
createEndpointGroup_idempotencyToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroup' {Text
idempotencyToken :: Text
$sel:idempotencyToken:CreateEndpointGroup' :: CreateEndpointGroup -> Text
idempotencyToken} -> Text
idempotencyToken) (\s :: CreateEndpointGroup
s@CreateEndpointGroup' {} Text
a -> CreateEndpointGroup
s {$sel:idempotencyToken:CreateEndpointGroup' :: Text
idempotencyToken = Text
a} :: CreateEndpointGroup)

instance Core.AWSRequest CreateEndpointGroup where
  type
    AWSResponse CreateEndpointGroup =
      CreateEndpointGroupResponse
  request :: (Service -> Service)
-> CreateEndpointGroup -> Request CreateEndpointGroup
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 CreateEndpointGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateEndpointGroup)))
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 EndpointGroup -> Int -> CreateEndpointGroupResponse
CreateEndpointGroupResponse'
            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
"EndpointGroup")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateEndpointGroup where
  hashWithSalt :: Int -> CreateEndpointGroup -> Int
hashWithSalt Int
_salt CreateEndpointGroup' {Maybe Double
Maybe Natural
Maybe [EndpointConfiguration]
Maybe [PortOverride]
Maybe Text
Maybe HealthCheckProtocol
Text
idempotencyToken :: Text
endpointGroupRegion :: Text
listenerArn :: Text
trafficDialPercentage :: Maybe Double
thresholdCount :: Maybe Natural
portOverrides :: Maybe [PortOverride]
healthCheckProtocol :: Maybe HealthCheckProtocol
healthCheckPort :: Maybe Natural
healthCheckPath :: Maybe Text
healthCheckIntervalSeconds :: Maybe Natural
endpointConfigurations :: Maybe [EndpointConfiguration]
$sel:idempotencyToken:CreateEndpointGroup' :: CreateEndpointGroup -> Text
$sel:endpointGroupRegion:CreateEndpointGroup' :: CreateEndpointGroup -> Text
$sel:listenerArn:CreateEndpointGroup' :: CreateEndpointGroup -> Text
$sel:trafficDialPercentage:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Double
$sel:thresholdCount:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
$sel:portOverrides:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe [PortOverride]
$sel:healthCheckProtocol:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe HealthCheckProtocol
$sel:healthCheckPort:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
$sel:healthCheckPath:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Text
$sel:healthCheckIntervalSeconds:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
$sel:endpointConfigurations:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe [EndpointConfiguration]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [EndpointConfiguration]
endpointConfigurations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
healthCheckIntervalSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
healthCheckPath
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
healthCheckPort
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HealthCheckProtocol
healthCheckProtocol
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PortOverride]
portOverrides
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
thresholdCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
trafficDialPercentage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
listenerArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointGroupRegion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
idempotencyToken

instance Prelude.NFData CreateEndpointGroup where
  rnf :: CreateEndpointGroup -> ()
rnf CreateEndpointGroup' {Maybe Double
Maybe Natural
Maybe [EndpointConfiguration]
Maybe [PortOverride]
Maybe Text
Maybe HealthCheckProtocol
Text
idempotencyToken :: Text
endpointGroupRegion :: Text
listenerArn :: Text
trafficDialPercentage :: Maybe Double
thresholdCount :: Maybe Natural
portOverrides :: Maybe [PortOverride]
healthCheckProtocol :: Maybe HealthCheckProtocol
healthCheckPort :: Maybe Natural
healthCheckPath :: Maybe Text
healthCheckIntervalSeconds :: Maybe Natural
endpointConfigurations :: Maybe [EndpointConfiguration]
$sel:idempotencyToken:CreateEndpointGroup' :: CreateEndpointGroup -> Text
$sel:endpointGroupRegion:CreateEndpointGroup' :: CreateEndpointGroup -> Text
$sel:listenerArn:CreateEndpointGroup' :: CreateEndpointGroup -> Text
$sel:trafficDialPercentage:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Double
$sel:thresholdCount:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
$sel:portOverrides:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe [PortOverride]
$sel:healthCheckProtocol:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe HealthCheckProtocol
$sel:healthCheckPort:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
$sel:healthCheckPath:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Text
$sel:healthCheckIntervalSeconds:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
$sel:endpointConfigurations:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe [EndpointConfiguration]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [EndpointConfiguration]
endpointConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
healthCheckIntervalSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
healthCheckPath
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
healthCheckPort
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HealthCheckProtocol
healthCheckProtocol
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PortOverride]
portOverrides
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
thresholdCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
trafficDialPercentage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
listenerArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointGroupRegion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
idempotencyToken

instance Data.ToHeaders CreateEndpointGroup where
  toHeaders :: CreateEndpointGroup -> 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
"GlobalAccelerator_V20180706.CreateEndpointGroup" ::
                          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 CreateEndpointGroup where
  toJSON :: CreateEndpointGroup -> Value
toJSON CreateEndpointGroup' {Maybe Double
Maybe Natural
Maybe [EndpointConfiguration]
Maybe [PortOverride]
Maybe Text
Maybe HealthCheckProtocol
Text
idempotencyToken :: Text
endpointGroupRegion :: Text
listenerArn :: Text
trafficDialPercentage :: Maybe Double
thresholdCount :: Maybe Natural
portOverrides :: Maybe [PortOverride]
healthCheckProtocol :: Maybe HealthCheckProtocol
healthCheckPort :: Maybe Natural
healthCheckPath :: Maybe Text
healthCheckIntervalSeconds :: Maybe Natural
endpointConfigurations :: Maybe [EndpointConfiguration]
$sel:idempotencyToken:CreateEndpointGroup' :: CreateEndpointGroup -> Text
$sel:endpointGroupRegion:CreateEndpointGroup' :: CreateEndpointGroup -> Text
$sel:listenerArn:CreateEndpointGroup' :: CreateEndpointGroup -> Text
$sel:trafficDialPercentage:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Double
$sel:thresholdCount:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
$sel:portOverrides:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe [PortOverride]
$sel:healthCheckProtocol:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe HealthCheckProtocol
$sel:healthCheckPort:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
$sel:healthCheckPath:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Text
$sel:healthCheckIntervalSeconds:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe Natural
$sel:endpointConfigurations:CreateEndpointGroup' :: CreateEndpointGroup -> Maybe [EndpointConfiguration]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"EndpointConfigurations" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [EndpointConfiguration]
endpointConfigurations,
            (Key
"HealthCheckIntervalSeconds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
healthCheckIntervalSeconds,
            (Key
"HealthCheckPath" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
healthCheckPath,
            (Key
"HealthCheckPort" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
healthCheckPort,
            (Key
"HealthCheckProtocol" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HealthCheckProtocol
healthCheckProtocol,
            (Key
"PortOverrides" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [PortOverride]
portOverrides,
            (Key
"ThresholdCount" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
thresholdCount,
            (Key
"TrafficDialPercentage" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Double
trafficDialPercentage,
            forall a. a -> Maybe a
Prelude.Just (Key
"ListenerArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
listenerArn),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"EndpointGroupRegion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
endpointGroupRegion),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"IdempotencyToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
idempotencyToken)
          ]
      )

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

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

-- | /See:/ 'newCreateEndpointGroupResponse' smart constructor.
data CreateEndpointGroupResponse = CreateEndpointGroupResponse'
  { -- | The information about the endpoint group that was created.
    CreateEndpointGroupResponse -> Maybe EndpointGroup
endpointGroup :: Prelude.Maybe EndpointGroup,
    -- | The response's http status code.
    CreateEndpointGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateEndpointGroupResponse -> CreateEndpointGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateEndpointGroupResponse -> CreateEndpointGroupResponse -> Bool
$c/= :: CreateEndpointGroupResponse -> CreateEndpointGroupResponse -> Bool
== :: CreateEndpointGroupResponse -> CreateEndpointGroupResponse -> Bool
$c== :: CreateEndpointGroupResponse -> CreateEndpointGroupResponse -> Bool
Prelude.Eq, ReadPrec [CreateEndpointGroupResponse]
ReadPrec CreateEndpointGroupResponse
Int -> ReadS CreateEndpointGroupResponse
ReadS [CreateEndpointGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateEndpointGroupResponse]
$creadListPrec :: ReadPrec [CreateEndpointGroupResponse]
readPrec :: ReadPrec CreateEndpointGroupResponse
$creadPrec :: ReadPrec CreateEndpointGroupResponse
readList :: ReadS [CreateEndpointGroupResponse]
$creadList :: ReadS [CreateEndpointGroupResponse]
readsPrec :: Int -> ReadS CreateEndpointGroupResponse
$creadsPrec :: Int -> ReadS CreateEndpointGroupResponse
Prelude.Read, Int -> CreateEndpointGroupResponse -> ShowS
[CreateEndpointGroupResponse] -> ShowS
CreateEndpointGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateEndpointGroupResponse] -> ShowS
$cshowList :: [CreateEndpointGroupResponse] -> ShowS
show :: CreateEndpointGroupResponse -> String
$cshow :: CreateEndpointGroupResponse -> String
showsPrec :: Int -> CreateEndpointGroupResponse -> ShowS
$cshowsPrec :: Int -> CreateEndpointGroupResponse -> ShowS
Prelude.Show, forall x.
Rep CreateEndpointGroupResponse x -> CreateEndpointGroupResponse
forall x.
CreateEndpointGroupResponse -> Rep CreateEndpointGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateEndpointGroupResponse x -> CreateEndpointGroupResponse
$cfrom :: forall x.
CreateEndpointGroupResponse -> Rep CreateEndpointGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateEndpointGroupResponse' 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:
--
-- 'endpointGroup', 'createEndpointGroupResponse_endpointGroup' - The information about the endpoint group that was created.
--
-- 'httpStatus', 'createEndpointGroupResponse_httpStatus' - The response's http status code.
newCreateEndpointGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateEndpointGroupResponse
newCreateEndpointGroupResponse :: Int -> CreateEndpointGroupResponse
newCreateEndpointGroupResponse Int
pHttpStatus_ =
  CreateEndpointGroupResponse'
    { $sel:endpointGroup:CreateEndpointGroupResponse' :: Maybe EndpointGroup
endpointGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateEndpointGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The information about the endpoint group that was created.
createEndpointGroupResponse_endpointGroup :: Lens.Lens' CreateEndpointGroupResponse (Prelude.Maybe EndpointGroup)
createEndpointGroupResponse_endpointGroup :: Lens' CreateEndpointGroupResponse (Maybe EndpointGroup)
createEndpointGroupResponse_endpointGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointGroupResponse' {Maybe EndpointGroup
endpointGroup :: Maybe EndpointGroup
$sel:endpointGroup:CreateEndpointGroupResponse' :: CreateEndpointGroupResponse -> Maybe EndpointGroup
endpointGroup} -> Maybe EndpointGroup
endpointGroup) (\s :: CreateEndpointGroupResponse
s@CreateEndpointGroupResponse' {} Maybe EndpointGroup
a -> CreateEndpointGroupResponse
s {$sel:endpointGroup:CreateEndpointGroupResponse' :: Maybe EndpointGroup
endpointGroup = Maybe EndpointGroup
a} :: CreateEndpointGroupResponse)

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

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