module Stratosphere.AppMesh.VirtualNode.VirtualServiceBackendProperty (
module Exports, VirtualServiceBackendProperty(..),
mkVirtualServiceBackendProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AppMesh.VirtualNode.ClientPolicyProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data VirtualServiceBackendProperty
=
VirtualServiceBackendProperty {VirtualServiceBackendProperty -> ()
haddock_workaround_ :: (),
VirtualServiceBackendProperty -> Maybe ClientPolicyProperty
clientPolicy :: (Prelude.Maybe ClientPolicyProperty),
VirtualServiceBackendProperty -> Value Text
virtualServiceName :: (Value Prelude.Text)}
deriving stock (VirtualServiceBackendProperty
-> VirtualServiceBackendProperty -> Bool
(VirtualServiceBackendProperty
-> VirtualServiceBackendProperty -> Bool)
-> (VirtualServiceBackendProperty
-> VirtualServiceBackendProperty -> Bool)
-> Eq VirtualServiceBackendProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VirtualServiceBackendProperty
-> VirtualServiceBackendProperty -> Bool
== :: VirtualServiceBackendProperty
-> VirtualServiceBackendProperty -> Bool
$c/= :: VirtualServiceBackendProperty
-> VirtualServiceBackendProperty -> Bool
/= :: VirtualServiceBackendProperty
-> VirtualServiceBackendProperty -> Bool
Prelude.Eq, Int -> VirtualServiceBackendProperty -> ShowS
[VirtualServiceBackendProperty] -> ShowS
VirtualServiceBackendProperty -> String
(Int -> VirtualServiceBackendProperty -> ShowS)
-> (VirtualServiceBackendProperty -> String)
-> ([VirtualServiceBackendProperty] -> ShowS)
-> Show VirtualServiceBackendProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VirtualServiceBackendProperty -> ShowS
showsPrec :: Int -> VirtualServiceBackendProperty -> ShowS
$cshow :: VirtualServiceBackendProperty -> String
show :: VirtualServiceBackendProperty -> String
$cshowList :: [VirtualServiceBackendProperty] -> ShowS
showList :: [VirtualServiceBackendProperty] -> ShowS
Prelude.Show)
mkVirtualServiceBackendProperty ::
Value Prelude.Text -> VirtualServiceBackendProperty
mkVirtualServiceBackendProperty :: Value Text -> VirtualServiceBackendProperty
mkVirtualServiceBackendProperty Value Text
virtualServiceName
= VirtualServiceBackendProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), virtualServiceName :: Value Text
virtualServiceName = Value Text
virtualServiceName,
clientPolicy :: Maybe ClientPolicyProperty
clientPolicy = Maybe ClientPolicyProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties VirtualServiceBackendProperty where
toResourceProperties :: VirtualServiceBackendProperty -> ResourceProperties
toResourceProperties VirtualServiceBackendProperty {Maybe ClientPolicyProperty
()
Value Text
haddock_workaround_ :: VirtualServiceBackendProperty -> ()
clientPolicy :: VirtualServiceBackendProperty -> Maybe ClientPolicyProperty
virtualServiceName :: VirtualServiceBackendProperty -> Value Text
haddock_workaround_ :: ()
clientPolicy :: Maybe ClientPolicyProperty
virtualServiceName :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::AppMesh::VirtualNode.VirtualServiceBackend",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"VirtualServiceName" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
virtualServiceName]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> ClientPolicyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClientPolicy" (ClientPolicyProperty -> (Key, Value))
-> Maybe ClientPolicyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ClientPolicyProperty
clientPolicy]))}
instance JSON.ToJSON VirtualServiceBackendProperty where
toJSON :: VirtualServiceBackendProperty -> Value
toJSON VirtualServiceBackendProperty {Maybe ClientPolicyProperty
()
Value Text
haddock_workaround_ :: VirtualServiceBackendProperty -> ()
clientPolicy :: VirtualServiceBackendProperty -> Maybe ClientPolicyProperty
virtualServiceName :: VirtualServiceBackendProperty -> Value Text
haddock_workaround_ :: ()
clientPolicy :: Maybe ClientPolicyProperty
virtualServiceName :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"VirtualServiceName" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
virtualServiceName]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> ClientPolicyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClientPolicy" (ClientPolicyProperty -> (Key, Value))
-> Maybe ClientPolicyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ClientPolicyProperty
clientPolicy])))
instance Property "ClientPolicy" VirtualServiceBackendProperty where
type PropertyType "ClientPolicy" VirtualServiceBackendProperty = ClientPolicyProperty
set :: PropertyType "ClientPolicy" VirtualServiceBackendProperty
-> VirtualServiceBackendProperty -> VirtualServiceBackendProperty
set PropertyType "ClientPolicy" VirtualServiceBackendProperty
newValue VirtualServiceBackendProperty {Maybe ClientPolicyProperty
()
Value Text
haddock_workaround_ :: VirtualServiceBackendProperty -> ()
clientPolicy :: VirtualServiceBackendProperty -> Maybe ClientPolicyProperty
virtualServiceName :: VirtualServiceBackendProperty -> Value Text
haddock_workaround_ :: ()
clientPolicy :: Maybe ClientPolicyProperty
virtualServiceName :: Value Text
..}
= VirtualServiceBackendProperty
{clientPolicy :: Maybe ClientPolicyProperty
clientPolicy = ClientPolicyProperty -> Maybe ClientPolicyProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ClientPolicy" VirtualServiceBackendProperty
ClientPolicyProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
virtualServiceName :: Value Text
haddock_workaround_ :: ()
virtualServiceName :: Value Text
..}
instance Property "VirtualServiceName" VirtualServiceBackendProperty where
type PropertyType "VirtualServiceName" VirtualServiceBackendProperty = Value Prelude.Text
set :: PropertyType "VirtualServiceName" VirtualServiceBackendProperty
-> VirtualServiceBackendProperty -> VirtualServiceBackendProperty
set PropertyType "VirtualServiceName" VirtualServiceBackendProperty
newValue VirtualServiceBackendProperty {Maybe ClientPolicyProperty
()
Value Text
haddock_workaround_ :: VirtualServiceBackendProperty -> ()
clientPolicy :: VirtualServiceBackendProperty -> Maybe ClientPolicyProperty
virtualServiceName :: VirtualServiceBackendProperty -> Value Text
haddock_workaround_ :: ()
clientPolicy :: Maybe ClientPolicyProperty
virtualServiceName :: Value Text
..}
= VirtualServiceBackendProperty {virtualServiceName :: Value Text
virtualServiceName = PropertyType "VirtualServiceName" VirtualServiceBackendProperty
Value Text
newValue, Maybe ClientPolicyProperty
()
haddock_workaround_ :: ()
clientPolicy :: Maybe ClientPolicyProperty
haddock_workaround_ :: ()
clientPolicy :: Maybe ClientPolicyProperty
..}