module Stratosphere.VpcLattice.Rule.ActionProperty (
module Exports, ActionProperty(..), mkActionProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.VpcLattice.Rule.FixedResponseProperty as Exports
import {-# SOURCE #-} Stratosphere.VpcLattice.Rule.ForwardProperty as Exports
import Stratosphere.ResourceProperties
data ActionProperty
=
ActionProperty {ActionProperty -> ()
haddock_workaround_ :: (),
ActionProperty -> Maybe FixedResponseProperty
fixedResponse :: (Prelude.Maybe FixedResponseProperty),
ActionProperty -> Maybe ForwardProperty
forward :: (Prelude.Maybe ForwardProperty)}
deriving stock (ActionProperty -> ActionProperty -> Bool
(ActionProperty -> ActionProperty -> Bool)
-> (ActionProperty -> ActionProperty -> Bool) -> Eq ActionProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ActionProperty -> ActionProperty -> Bool
== :: ActionProperty -> ActionProperty -> Bool
$c/= :: ActionProperty -> ActionProperty -> Bool
/= :: ActionProperty -> ActionProperty -> Bool
Prelude.Eq, Int -> ActionProperty -> ShowS
[ActionProperty] -> ShowS
ActionProperty -> String
(Int -> ActionProperty -> ShowS)
-> (ActionProperty -> String)
-> ([ActionProperty] -> ShowS)
-> Show ActionProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ActionProperty -> ShowS
showsPrec :: Int -> ActionProperty -> ShowS
$cshow :: ActionProperty -> String
show :: ActionProperty -> String
$cshowList :: [ActionProperty] -> ShowS
showList :: [ActionProperty] -> ShowS
Prelude.Show)
mkActionProperty :: ActionProperty
mkActionProperty :: ActionProperty
mkActionProperty
= ActionProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), fixedResponse :: Maybe FixedResponseProperty
fixedResponse = Maybe FixedResponseProperty
forall a. Maybe a
Prelude.Nothing,
forward :: Maybe ForwardProperty
forward = Maybe ForwardProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ActionProperty where
toResourceProperties :: ActionProperty -> ResourceProperties
toResourceProperties ActionProperty {Maybe FixedResponseProperty
Maybe ForwardProperty
()
haddock_workaround_ :: ActionProperty -> ()
fixedResponse :: ActionProperty -> Maybe FixedResponseProperty
forward :: ActionProperty -> Maybe ForwardProperty
haddock_workaround_ :: ()
fixedResponse :: Maybe FixedResponseProperty
forward :: Maybe ForwardProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::VpcLattice::Rule.Action",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> FixedResponseProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FixedResponse" (FixedResponseProperty -> (Key, Value))
-> Maybe FixedResponseProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FixedResponseProperty
fixedResponse,
Key -> ForwardProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Forward" (ForwardProperty -> (Key, Value))
-> Maybe ForwardProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ForwardProperty
forward])}
instance JSON.ToJSON ActionProperty where
toJSON :: ActionProperty -> Value
toJSON ActionProperty {Maybe FixedResponseProperty
Maybe ForwardProperty
()
haddock_workaround_ :: ActionProperty -> ()
fixedResponse :: ActionProperty -> Maybe FixedResponseProperty
forward :: ActionProperty -> Maybe ForwardProperty
haddock_workaround_ :: ()
fixedResponse :: Maybe FixedResponseProperty
forward :: Maybe ForwardProperty
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> FixedResponseProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FixedResponse" (FixedResponseProperty -> (Key, Value))
-> Maybe FixedResponseProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FixedResponseProperty
fixedResponse,
Key -> ForwardProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Forward" (ForwardProperty -> (Key, Value))
-> Maybe ForwardProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ForwardProperty
forward]))
instance Property "FixedResponse" ActionProperty where
type PropertyType "FixedResponse" ActionProperty = FixedResponseProperty
set :: PropertyType "FixedResponse" ActionProperty
-> ActionProperty -> ActionProperty
set PropertyType "FixedResponse" ActionProperty
newValue ActionProperty {Maybe FixedResponseProperty
Maybe ForwardProperty
()
haddock_workaround_ :: ActionProperty -> ()
fixedResponse :: ActionProperty -> Maybe FixedResponseProperty
forward :: ActionProperty -> Maybe ForwardProperty
haddock_workaround_ :: ()
fixedResponse :: Maybe FixedResponseProperty
forward :: Maybe ForwardProperty
..}
= ActionProperty {fixedResponse :: Maybe FixedResponseProperty
fixedResponse = FixedResponseProperty -> Maybe FixedResponseProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FixedResponse" ActionProperty
FixedResponseProperty
newValue, Maybe ForwardProperty
()
haddock_workaround_ :: ()
forward :: Maybe ForwardProperty
haddock_workaround_ :: ()
forward :: Maybe ForwardProperty
..}
instance Property "Forward" ActionProperty where
type PropertyType "Forward" ActionProperty = ForwardProperty
set :: PropertyType "Forward" ActionProperty
-> ActionProperty -> ActionProperty
set PropertyType "Forward" ActionProperty
newValue ActionProperty {Maybe FixedResponseProperty
Maybe ForwardProperty
()
haddock_workaround_ :: ActionProperty -> ()
fixedResponse :: ActionProperty -> Maybe FixedResponseProperty
forward :: ActionProperty -> Maybe ForwardProperty
haddock_workaround_ :: ()
fixedResponse :: Maybe FixedResponseProperty
forward :: Maybe ForwardProperty
..}
= ActionProperty {forward :: Maybe ForwardProperty
forward = ForwardProperty -> Maybe ForwardProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Forward" ActionProperty
ForwardProperty
newValue, Maybe FixedResponseProperty
()
haddock_workaround_ :: ()
fixedResponse :: Maybe FixedResponseProperty
haddock_workaround_ :: ()
fixedResponse :: Maybe FixedResponseProperty
..}