{-# 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.ELBV2.Types.Action
-- 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.ELBV2.Types.Action where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ELBV2.Types.ActionTypeEnum
import Amazonka.ELBV2.Types.AuthenticateCognitoActionConfig
import Amazonka.ELBV2.Types.AuthenticateOidcActionConfig
import Amazonka.ELBV2.Types.FixedResponseActionConfig
import Amazonka.ELBV2.Types.ForwardActionConfig
import Amazonka.ELBV2.Types.RedirectActionConfig
import qualified Amazonka.Prelude as Prelude

-- | Information about an action.
--
-- Each rule must include exactly one of the following types of actions:
-- @forward@, @fixed-response@, or @redirect@, and it must be the last
-- action to be performed.
--
-- /See:/ 'newAction' smart constructor.
data Action = Action'
  { -- | [HTTPS listeners] Information for using Amazon Cognito to authenticate
    -- users. Specify only when @Type@ is @authenticate-cognito@.
    Action -> Maybe AuthenticateCognitoActionConfig
authenticateCognitoConfig :: Prelude.Maybe AuthenticateCognitoActionConfig,
    -- | [HTTPS listeners] Information about an identity provider that is
    -- compliant with OpenID Connect (OIDC). Specify only when @Type@ is
    -- @authenticate-oidc@.
    Action -> Maybe AuthenticateOidcActionConfig
authenticateOidcConfig :: Prelude.Maybe AuthenticateOidcActionConfig,
    -- | [Application Load Balancer] Information for creating an action that
    -- returns a custom HTTP response. Specify only when @Type@ is
    -- @fixed-response@.
    Action -> Maybe FixedResponseActionConfig
fixedResponseConfig :: Prelude.Maybe FixedResponseActionConfig,
    -- | Information for creating an action that distributes requests among one
    -- or more target groups. For Network Load Balancers, you can specify a
    -- single target group. Specify only when @Type@ is @forward@. If you
    -- specify both @ForwardConfig@ and @TargetGroupArn@, you can specify only
    -- one target group using @ForwardConfig@ and it must be the same target
    -- group specified in @TargetGroupArn@.
    Action -> Maybe ForwardActionConfig
forwardConfig :: Prelude.Maybe ForwardActionConfig,
    -- | The order for the action. This value is required for rules with multiple
    -- actions. The action with the lowest value for order is performed first.
    Action -> Maybe Natural
order :: Prelude.Maybe Prelude.Natural,
    -- | [Application Load Balancer] Information for creating a redirect action.
    -- Specify only when @Type@ is @redirect@.
    Action -> Maybe RedirectActionConfig
redirectConfig :: Prelude.Maybe RedirectActionConfig,
    -- | The Amazon Resource Name (ARN) of the target group. Specify only when
    -- @Type@ is @forward@ and you want to route to a single target group. To
    -- route to one or more target groups, use @ForwardConfig@ instead.
    Action -> Maybe Text
targetGroupArn :: Prelude.Maybe Prelude.Text,
    -- | The type of action.
    Action -> ActionTypeEnum
type' :: ActionTypeEnum
  }
  deriving (Action -> Action -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Action -> Action -> Bool
$c/= :: Action -> Action -> Bool
== :: Action -> Action -> Bool
$c== :: Action -> Action -> Bool
Prelude.Eq, ReadPrec [Action]
ReadPrec Action
Int -> ReadS Action
ReadS [Action]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Action]
$creadListPrec :: ReadPrec [Action]
readPrec :: ReadPrec Action
$creadPrec :: ReadPrec Action
readList :: ReadS [Action]
$creadList :: ReadS [Action]
readsPrec :: Int -> ReadS Action
$creadsPrec :: Int -> ReadS Action
Prelude.Read, Int -> Action -> ShowS
[Action] -> ShowS
Action -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Action] -> ShowS
$cshowList :: [Action] -> ShowS
show :: Action -> String
$cshow :: Action -> String
showsPrec :: Int -> Action -> ShowS
$cshowsPrec :: Int -> Action -> ShowS
Prelude.Show, forall x. Rep Action x -> Action
forall x. Action -> Rep Action x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Action x -> Action
$cfrom :: forall x. Action -> Rep Action x
Prelude.Generic)

-- |
-- Create a value of 'Action' 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:
--
-- 'authenticateCognitoConfig', 'action_authenticateCognitoConfig' - [HTTPS listeners] Information for using Amazon Cognito to authenticate
-- users. Specify only when @Type@ is @authenticate-cognito@.
--
-- 'authenticateOidcConfig', 'action_authenticateOidcConfig' - [HTTPS listeners] Information about an identity provider that is
-- compliant with OpenID Connect (OIDC). Specify only when @Type@ is
-- @authenticate-oidc@.
--
-- 'fixedResponseConfig', 'action_fixedResponseConfig' - [Application Load Balancer] Information for creating an action that
-- returns a custom HTTP response. Specify only when @Type@ is
-- @fixed-response@.
--
-- 'forwardConfig', 'action_forwardConfig' - Information for creating an action that distributes requests among one
-- or more target groups. For Network Load Balancers, you can specify a
-- single target group. Specify only when @Type@ is @forward@. If you
-- specify both @ForwardConfig@ and @TargetGroupArn@, you can specify only
-- one target group using @ForwardConfig@ and it must be the same target
-- group specified in @TargetGroupArn@.
--
-- 'order', 'action_order' - The order for the action. This value is required for rules with multiple
-- actions. The action with the lowest value for order is performed first.
--
-- 'redirectConfig', 'action_redirectConfig' - [Application Load Balancer] Information for creating a redirect action.
-- Specify only when @Type@ is @redirect@.
--
-- 'targetGroupArn', 'action_targetGroupArn' - The Amazon Resource Name (ARN) of the target group. Specify only when
-- @Type@ is @forward@ and you want to route to a single target group. To
-- route to one or more target groups, use @ForwardConfig@ instead.
--
-- 'type'', 'action_type' - The type of action.
newAction ::
  -- | 'type''
  ActionTypeEnum ->
  Action
newAction :: ActionTypeEnum -> Action
newAction ActionTypeEnum
pType_ =
  Action'
    { $sel:authenticateCognitoConfig:Action' :: Maybe AuthenticateCognitoActionConfig
authenticateCognitoConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:authenticateOidcConfig:Action' :: Maybe AuthenticateOidcActionConfig
authenticateOidcConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:fixedResponseConfig:Action' :: Maybe FixedResponseActionConfig
fixedResponseConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:forwardConfig:Action' :: Maybe ForwardActionConfig
forwardConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:order:Action' :: Maybe Natural
order = forall a. Maybe a
Prelude.Nothing,
      $sel:redirectConfig:Action' :: Maybe RedirectActionConfig
redirectConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:targetGroupArn:Action' :: Maybe Text
targetGroupArn = forall a. Maybe a
Prelude.Nothing,
      $sel:type':Action' :: ActionTypeEnum
type' = ActionTypeEnum
pType_
    }

-- | [HTTPS listeners] Information for using Amazon Cognito to authenticate
-- users. Specify only when @Type@ is @authenticate-cognito@.
action_authenticateCognitoConfig :: Lens.Lens' Action (Prelude.Maybe AuthenticateCognitoActionConfig)
action_authenticateCognitoConfig :: Lens' Action (Maybe AuthenticateCognitoActionConfig)
action_authenticateCognitoConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Action' {Maybe AuthenticateCognitoActionConfig
authenticateCognitoConfig :: Maybe AuthenticateCognitoActionConfig
$sel:authenticateCognitoConfig:Action' :: Action -> Maybe AuthenticateCognitoActionConfig
authenticateCognitoConfig} -> Maybe AuthenticateCognitoActionConfig
authenticateCognitoConfig) (\s :: Action
s@Action' {} Maybe AuthenticateCognitoActionConfig
a -> Action
s {$sel:authenticateCognitoConfig:Action' :: Maybe AuthenticateCognitoActionConfig
authenticateCognitoConfig = Maybe AuthenticateCognitoActionConfig
a} :: Action)

-- | [HTTPS listeners] Information about an identity provider that is
-- compliant with OpenID Connect (OIDC). Specify only when @Type@ is
-- @authenticate-oidc@.
action_authenticateOidcConfig :: Lens.Lens' Action (Prelude.Maybe AuthenticateOidcActionConfig)
action_authenticateOidcConfig :: Lens' Action (Maybe AuthenticateOidcActionConfig)
action_authenticateOidcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Action' {Maybe AuthenticateOidcActionConfig
authenticateOidcConfig :: Maybe AuthenticateOidcActionConfig
$sel:authenticateOidcConfig:Action' :: Action -> Maybe AuthenticateOidcActionConfig
authenticateOidcConfig} -> Maybe AuthenticateOidcActionConfig
authenticateOidcConfig) (\s :: Action
s@Action' {} Maybe AuthenticateOidcActionConfig
a -> Action
s {$sel:authenticateOidcConfig:Action' :: Maybe AuthenticateOidcActionConfig
authenticateOidcConfig = Maybe AuthenticateOidcActionConfig
a} :: Action)

-- | [Application Load Balancer] Information for creating an action that
-- returns a custom HTTP response. Specify only when @Type@ is
-- @fixed-response@.
action_fixedResponseConfig :: Lens.Lens' Action (Prelude.Maybe FixedResponseActionConfig)
action_fixedResponseConfig :: Lens' Action (Maybe FixedResponseActionConfig)
action_fixedResponseConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Action' {Maybe FixedResponseActionConfig
fixedResponseConfig :: Maybe FixedResponseActionConfig
$sel:fixedResponseConfig:Action' :: Action -> Maybe FixedResponseActionConfig
fixedResponseConfig} -> Maybe FixedResponseActionConfig
fixedResponseConfig) (\s :: Action
s@Action' {} Maybe FixedResponseActionConfig
a -> Action
s {$sel:fixedResponseConfig:Action' :: Maybe FixedResponseActionConfig
fixedResponseConfig = Maybe FixedResponseActionConfig
a} :: Action)

-- | Information for creating an action that distributes requests among one
-- or more target groups. For Network Load Balancers, you can specify a
-- single target group. Specify only when @Type@ is @forward@. If you
-- specify both @ForwardConfig@ and @TargetGroupArn@, you can specify only
-- one target group using @ForwardConfig@ and it must be the same target
-- group specified in @TargetGroupArn@.
action_forwardConfig :: Lens.Lens' Action (Prelude.Maybe ForwardActionConfig)
action_forwardConfig :: Lens' Action (Maybe ForwardActionConfig)
action_forwardConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Action' {Maybe ForwardActionConfig
forwardConfig :: Maybe ForwardActionConfig
$sel:forwardConfig:Action' :: Action -> Maybe ForwardActionConfig
forwardConfig} -> Maybe ForwardActionConfig
forwardConfig) (\s :: Action
s@Action' {} Maybe ForwardActionConfig
a -> Action
s {$sel:forwardConfig:Action' :: Maybe ForwardActionConfig
forwardConfig = Maybe ForwardActionConfig
a} :: Action)

-- | The order for the action. This value is required for rules with multiple
-- actions. The action with the lowest value for order is performed first.
action_order :: Lens.Lens' Action (Prelude.Maybe Prelude.Natural)
action_order :: Lens' Action (Maybe Natural)
action_order = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Action' {Maybe Natural
order :: Maybe Natural
$sel:order:Action' :: Action -> Maybe Natural
order} -> Maybe Natural
order) (\s :: Action
s@Action' {} Maybe Natural
a -> Action
s {$sel:order:Action' :: Maybe Natural
order = Maybe Natural
a} :: Action)

-- | [Application Load Balancer] Information for creating a redirect action.
-- Specify only when @Type@ is @redirect@.
action_redirectConfig :: Lens.Lens' Action (Prelude.Maybe RedirectActionConfig)
action_redirectConfig :: Lens' Action (Maybe RedirectActionConfig)
action_redirectConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Action' {Maybe RedirectActionConfig
redirectConfig :: Maybe RedirectActionConfig
$sel:redirectConfig:Action' :: Action -> Maybe RedirectActionConfig
redirectConfig} -> Maybe RedirectActionConfig
redirectConfig) (\s :: Action
s@Action' {} Maybe RedirectActionConfig
a -> Action
s {$sel:redirectConfig:Action' :: Maybe RedirectActionConfig
redirectConfig = Maybe RedirectActionConfig
a} :: Action)

-- | The Amazon Resource Name (ARN) of the target group. Specify only when
-- @Type@ is @forward@ and you want to route to a single target group. To
-- route to one or more target groups, use @ForwardConfig@ instead.
action_targetGroupArn :: Lens.Lens' Action (Prelude.Maybe Prelude.Text)
action_targetGroupArn :: Lens' Action (Maybe Text)
action_targetGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Action' {Maybe Text
targetGroupArn :: Maybe Text
$sel:targetGroupArn:Action' :: Action -> Maybe Text
targetGroupArn} -> Maybe Text
targetGroupArn) (\s :: Action
s@Action' {} Maybe Text
a -> Action
s {$sel:targetGroupArn:Action' :: Maybe Text
targetGroupArn = Maybe Text
a} :: Action)

-- | The type of action.
action_type :: Lens.Lens' Action ActionTypeEnum
action_type :: Lens' Action ActionTypeEnum
action_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Action' {ActionTypeEnum
type' :: ActionTypeEnum
$sel:type':Action' :: Action -> ActionTypeEnum
type'} -> ActionTypeEnum
type') (\s :: Action
s@Action' {} ActionTypeEnum
a -> Action
s {$sel:type':Action' :: ActionTypeEnum
type' = ActionTypeEnum
a} :: Action)

instance Data.FromXML Action where
  parseXML :: [Node] -> Either String Action
parseXML [Node]
x =
    Maybe AuthenticateCognitoActionConfig
-> Maybe AuthenticateOidcActionConfig
-> Maybe FixedResponseActionConfig
-> Maybe ForwardActionConfig
-> Maybe Natural
-> Maybe RedirectActionConfig
-> Maybe Text
-> ActionTypeEnum
-> Action
Action'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AuthenticateCognitoConfig")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AuthenticateOidcConfig")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"FixedResponseConfig")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ForwardConfig")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Order")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"RedirectConfig")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TargetGroupArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"Type")

instance Prelude.Hashable Action where
  hashWithSalt :: Int -> Action -> Int
hashWithSalt Int
_salt Action' {Maybe Natural
Maybe Text
Maybe AuthenticateCognitoActionConfig
Maybe AuthenticateOidcActionConfig
Maybe FixedResponseActionConfig
Maybe RedirectActionConfig
Maybe ForwardActionConfig
ActionTypeEnum
type' :: ActionTypeEnum
targetGroupArn :: Maybe Text
redirectConfig :: Maybe RedirectActionConfig
order :: Maybe Natural
forwardConfig :: Maybe ForwardActionConfig
fixedResponseConfig :: Maybe FixedResponseActionConfig
authenticateOidcConfig :: Maybe AuthenticateOidcActionConfig
authenticateCognitoConfig :: Maybe AuthenticateCognitoActionConfig
$sel:type':Action' :: Action -> ActionTypeEnum
$sel:targetGroupArn:Action' :: Action -> Maybe Text
$sel:redirectConfig:Action' :: Action -> Maybe RedirectActionConfig
$sel:order:Action' :: Action -> Maybe Natural
$sel:forwardConfig:Action' :: Action -> Maybe ForwardActionConfig
$sel:fixedResponseConfig:Action' :: Action -> Maybe FixedResponseActionConfig
$sel:authenticateOidcConfig:Action' :: Action -> Maybe AuthenticateOidcActionConfig
$sel:authenticateCognitoConfig:Action' :: Action -> Maybe AuthenticateCognitoActionConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthenticateCognitoActionConfig
authenticateCognitoConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthenticateOidcActionConfig
authenticateOidcConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FixedResponseActionConfig
fixedResponseConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ForwardActionConfig
forwardConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
order
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RedirectActionConfig
redirectConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
targetGroupArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ActionTypeEnum
type'

instance Prelude.NFData Action where
  rnf :: Action -> ()
rnf Action' {Maybe Natural
Maybe Text
Maybe AuthenticateCognitoActionConfig
Maybe AuthenticateOidcActionConfig
Maybe FixedResponseActionConfig
Maybe RedirectActionConfig
Maybe ForwardActionConfig
ActionTypeEnum
type' :: ActionTypeEnum
targetGroupArn :: Maybe Text
redirectConfig :: Maybe RedirectActionConfig
order :: Maybe Natural
forwardConfig :: Maybe ForwardActionConfig
fixedResponseConfig :: Maybe FixedResponseActionConfig
authenticateOidcConfig :: Maybe AuthenticateOidcActionConfig
authenticateCognitoConfig :: Maybe AuthenticateCognitoActionConfig
$sel:type':Action' :: Action -> ActionTypeEnum
$sel:targetGroupArn:Action' :: Action -> Maybe Text
$sel:redirectConfig:Action' :: Action -> Maybe RedirectActionConfig
$sel:order:Action' :: Action -> Maybe Natural
$sel:forwardConfig:Action' :: Action -> Maybe ForwardActionConfig
$sel:fixedResponseConfig:Action' :: Action -> Maybe FixedResponseActionConfig
$sel:authenticateOidcConfig:Action' :: Action -> Maybe AuthenticateOidcActionConfig
$sel:authenticateCognitoConfig:Action' :: Action -> Maybe AuthenticateCognitoActionConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AuthenticateCognitoActionConfig
authenticateCognitoConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AuthenticateOidcActionConfig
authenticateOidcConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FixedResponseActionConfig
fixedResponseConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ForwardActionConfig
forwardConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
order
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RedirectActionConfig
redirectConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
targetGroupArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ActionTypeEnum
type'

instance Data.ToQuery Action where
  toQuery :: Action -> QueryString
toQuery Action' {Maybe Natural
Maybe Text
Maybe AuthenticateCognitoActionConfig
Maybe AuthenticateOidcActionConfig
Maybe FixedResponseActionConfig
Maybe RedirectActionConfig
Maybe ForwardActionConfig
ActionTypeEnum
type' :: ActionTypeEnum
targetGroupArn :: Maybe Text
redirectConfig :: Maybe RedirectActionConfig
order :: Maybe Natural
forwardConfig :: Maybe ForwardActionConfig
fixedResponseConfig :: Maybe FixedResponseActionConfig
authenticateOidcConfig :: Maybe AuthenticateOidcActionConfig
authenticateCognitoConfig :: Maybe AuthenticateCognitoActionConfig
$sel:type':Action' :: Action -> ActionTypeEnum
$sel:targetGroupArn:Action' :: Action -> Maybe Text
$sel:redirectConfig:Action' :: Action -> Maybe RedirectActionConfig
$sel:order:Action' :: Action -> Maybe Natural
$sel:forwardConfig:Action' :: Action -> Maybe ForwardActionConfig
$sel:fixedResponseConfig:Action' :: Action -> Maybe FixedResponseActionConfig
$sel:authenticateOidcConfig:Action' :: Action -> Maybe AuthenticateOidcActionConfig
$sel:authenticateCognitoConfig:Action' :: Action -> Maybe AuthenticateCognitoActionConfig
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"AuthenticateCognitoConfig"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AuthenticateCognitoActionConfig
authenticateCognitoConfig,
        ByteString
"AuthenticateOidcConfig"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AuthenticateOidcActionConfig
authenticateOidcConfig,
        ByteString
"FixedResponseConfig" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe FixedResponseActionConfig
fixedResponseConfig,
        ByteString
"ForwardConfig" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ForwardActionConfig
forwardConfig,
        ByteString
"Order" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
order,
        ByteString
"RedirectConfig" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe RedirectActionConfig
redirectConfig,
        ByteString
"TargetGroupArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
targetGroupArn,
        ByteString
"Type" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ActionTypeEnum
type'
      ]