module Stratosphere.AppMesh.Route.GrpcRouteProperty (
module Exports, GrpcRouteProperty(..), mkGrpcRouteProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AppMesh.Route.GrpcRetryPolicyProperty as Exports
import {-# SOURCE #-} Stratosphere.AppMesh.Route.GrpcRouteActionProperty as Exports
import {-# SOURCE #-} Stratosphere.AppMesh.Route.GrpcRouteMatchProperty as Exports
import {-# SOURCE #-} Stratosphere.AppMesh.Route.GrpcTimeoutProperty as Exports
import Stratosphere.ResourceProperties
data GrpcRouteProperty
=
GrpcRouteProperty {GrpcRouteProperty -> ()
haddock_workaround_ :: (),
GrpcRouteProperty -> GrpcRouteActionProperty
action :: GrpcRouteActionProperty,
GrpcRouteProperty -> GrpcRouteMatchProperty
match :: GrpcRouteMatchProperty,
GrpcRouteProperty -> Maybe GrpcRetryPolicyProperty
retryPolicy :: (Prelude.Maybe GrpcRetryPolicyProperty),
GrpcRouteProperty -> Maybe GrpcTimeoutProperty
timeout :: (Prelude.Maybe GrpcTimeoutProperty)}
deriving stock (GrpcRouteProperty -> GrpcRouteProperty -> Bool
(GrpcRouteProperty -> GrpcRouteProperty -> Bool)
-> (GrpcRouteProperty -> GrpcRouteProperty -> Bool)
-> Eq GrpcRouteProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GrpcRouteProperty -> GrpcRouteProperty -> Bool
== :: GrpcRouteProperty -> GrpcRouteProperty -> Bool
$c/= :: GrpcRouteProperty -> GrpcRouteProperty -> Bool
/= :: GrpcRouteProperty -> GrpcRouteProperty -> Bool
Prelude.Eq, Int -> GrpcRouteProperty -> ShowS
[GrpcRouteProperty] -> ShowS
GrpcRouteProperty -> String
(Int -> GrpcRouteProperty -> ShowS)
-> (GrpcRouteProperty -> String)
-> ([GrpcRouteProperty] -> ShowS)
-> Show GrpcRouteProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GrpcRouteProperty -> ShowS
showsPrec :: Int -> GrpcRouteProperty -> ShowS
$cshow :: GrpcRouteProperty -> String
show :: GrpcRouteProperty -> String
$cshowList :: [GrpcRouteProperty] -> ShowS
showList :: [GrpcRouteProperty] -> ShowS
Prelude.Show)
mkGrpcRouteProperty ::
GrpcRouteActionProperty
-> GrpcRouteMatchProperty -> GrpcRouteProperty
mkGrpcRouteProperty :: GrpcRouteActionProperty
-> GrpcRouteMatchProperty -> GrpcRouteProperty
mkGrpcRouteProperty GrpcRouteActionProperty
action GrpcRouteMatchProperty
match
= GrpcRouteProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), action :: GrpcRouteActionProperty
action = GrpcRouteActionProperty
action, match :: GrpcRouteMatchProperty
match = GrpcRouteMatchProperty
match,
retryPolicy :: Maybe GrpcRetryPolicyProperty
retryPolicy = Maybe GrpcRetryPolicyProperty
forall a. Maybe a
Prelude.Nothing, timeout :: Maybe GrpcTimeoutProperty
timeout = Maybe GrpcTimeoutProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties GrpcRouteProperty where
toResourceProperties :: GrpcRouteProperty -> ResourceProperties
toResourceProperties GrpcRouteProperty {Maybe GrpcRetryPolicyProperty
Maybe GrpcTimeoutProperty
()
GrpcRouteMatchProperty
GrpcRouteActionProperty
haddock_workaround_ :: GrpcRouteProperty -> ()
action :: GrpcRouteProperty -> GrpcRouteActionProperty
match :: GrpcRouteProperty -> GrpcRouteMatchProperty
retryPolicy :: GrpcRouteProperty -> Maybe GrpcRetryPolicyProperty
timeout :: GrpcRouteProperty -> Maybe GrpcTimeoutProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::AppMesh::Route.GrpcRoute",
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
"Action" Key -> GrpcRouteActionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= GrpcRouteActionProperty
action, Key
"Match" Key -> GrpcRouteMatchProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= GrpcRouteMatchProperty
match]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> GrpcRetryPolicyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RetryPolicy" (GrpcRetryPolicyProperty -> (Key, Value))
-> Maybe GrpcRetryPolicyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GrpcRetryPolicyProperty
retryPolicy,
Key -> GrpcTimeoutProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Timeout" (GrpcTimeoutProperty -> (Key, Value))
-> Maybe GrpcTimeoutProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GrpcTimeoutProperty
timeout]))}
instance JSON.ToJSON GrpcRouteProperty where
toJSON :: GrpcRouteProperty -> Value
toJSON GrpcRouteProperty {Maybe GrpcRetryPolicyProperty
Maybe GrpcTimeoutProperty
()
GrpcRouteMatchProperty
GrpcRouteActionProperty
haddock_workaround_ :: GrpcRouteProperty -> ()
action :: GrpcRouteProperty -> GrpcRouteActionProperty
match :: GrpcRouteProperty -> GrpcRouteMatchProperty
retryPolicy :: GrpcRouteProperty -> Maybe GrpcRetryPolicyProperty
timeout :: GrpcRouteProperty -> Maybe GrpcTimeoutProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
..}
= [(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
"Action" Key -> GrpcRouteActionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= GrpcRouteActionProperty
action, Key
"Match" Key -> GrpcRouteMatchProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= GrpcRouteMatchProperty
match]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> GrpcRetryPolicyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RetryPolicy" (GrpcRetryPolicyProperty -> (Key, Value))
-> Maybe GrpcRetryPolicyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GrpcRetryPolicyProperty
retryPolicy,
Key -> GrpcTimeoutProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Timeout" (GrpcTimeoutProperty -> (Key, Value))
-> Maybe GrpcTimeoutProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GrpcTimeoutProperty
timeout])))
instance Property "Action" GrpcRouteProperty where
type PropertyType "Action" GrpcRouteProperty = GrpcRouteActionProperty
set :: PropertyType "Action" GrpcRouteProperty
-> GrpcRouteProperty -> GrpcRouteProperty
set PropertyType "Action" GrpcRouteProperty
newValue GrpcRouteProperty {Maybe GrpcRetryPolicyProperty
Maybe GrpcTimeoutProperty
()
GrpcRouteMatchProperty
GrpcRouteActionProperty
haddock_workaround_ :: GrpcRouteProperty -> ()
action :: GrpcRouteProperty -> GrpcRouteActionProperty
match :: GrpcRouteProperty -> GrpcRouteMatchProperty
retryPolicy :: GrpcRouteProperty -> Maybe GrpcRetryPolicyProperty
timeout :: GrpcRouteProperty -> Maybe GrpcTimeoutProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
..}
= GrpcRouteProperty {action :: GrpcRouteActionProperty
action = PropertyType "Action" GrpcRouteProperty
GrpcRouteActionProperty
newValue, Maybe GrpcRetryPolicyProperty
Maybe GrpcTimeoutProperty
()
GrpcRouteMatchProperty
haddock_workaround_ :: ()
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
haddock_workaround_ :: ()
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
..}
instance Property "Match" GrpcRouteProperty where
type PropertyType "Match" GrpcRouteProperty = GrpcRouteMatchProperty
set :: PropertyType "Match" GrpcRouteProperty
-> GrpcRouteProperty -> GrpcRouteProperty
set PropertyType "Match" GrpcRouteProperty
newValue GrpcRouteProperty {Maybe GrpcRetryPolicyProperty
Maybe GrpcTimeoutProperty
()
GrpcRouteMatchProperty
GrpcRouteActionProperty
haddock_workaround_ :: GrpcRouteProperty -> ()
action :: GrpcRouteProperty -> GrpcRouteActionProperty
match :: GrpcRouteProperty -> GrpcRouteMatchProperty
retryPolicy :: GrpcRouteProperty -> Maybe GrpcRetryPolicyProperty
timeout :: GrpcRouteProperty -> Maybe GrpcTimeoutProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
..}
= GrpcRouteProperty {match :: GrpcRouteMatchProperty
match = PropertyType "Match" GrpcRouteProperty
GrpcRouteMatchProperty
newValue, Maybe GrpcRetryPolicyProperty
Maybe GrpcTimeoutProperty
()
GrpcRouteActionProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
..}
instance Property "RetryPolicy" GrpcRouteProperty where
type PropertyType "RetryPolicy" GrpcRouteProperty = GrpcRetryPolicyProperty
set :: PropertyType "RetryPolicy" GrpcRouteProperty
-> GrpcRouteProperty -> GrpcRouteProperty
set PropertyType "RetryPolicy" GrpcRouteProperty
newValue GrpcRouteProperty {Maybe GrpcRetryPolicyProperty
Maybe GrpcTimeoutProperty
()
GrpcRouteMatchProperty
GrpcRouteActionProperty
haddock_workaround_ :: GrpcRouteProperty -> ()
action :: GrpcRouteProperty -> GrpcRouteActionProperty
match :: GrpcRouteProperty -> GrpcRouteMatchProperty
retryPolicy :: GrpcRouteProperty -> Maybe GrpcRetryPolicyProperty
timeout :: GrpcRouteProperty -> Maybe GrpcTimeoutProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
..}
= GrpcRouteProperty {retryPolicy :: Maybe GrpcRetryPolicyProperty
retryPolicy = GrpcRetryPolicyProperty -> Maybe GrpcRetryPolicyProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RetryPolicy" GrpcRouteProperty
GrpcRetryPolicyProperty
newValue, Maybe GrpcTimeoutProperty
()
GrpcRouteMatchProperty
GrpcRouteActionProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
timeout :: Maybe GrpcTimeoutProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
timeout :: Maybe GrpcTimeoutProperty
..}
instance Property "Timeout" GrpcRouteProperty where
type PropertyType "Timeout" GrpcRouteProperty = GrpcTimeoutProperty
set :: PropertyType "Timeout" GrpcRouteProperty
-> GrpcRouteProperty -> GrpcRouteProperty
set PropertyType "Timeout" GrpcRouteProperty
newValue GrpcRouteProperty {Maybe GrpcRetryPolicyProperty
Maybe GrpcTimeoutProperty
()
GrpcRouteMatchProperty
GrpcRouteActionProperty
haddock_workaround_ :: GrpcRouteProperty -> ()
action :: GrpcRouteProperty -> GrpcRouteActionProperty
match :: GrpcRouteProperty -> GrpcRouteMatchProperty
retryPolicy :: GrpcRouteProperty -> Maybe GrpcRetryPolicyProperty
timeout :: GrpcRouteProperty -> Maybe GrpcTimeoutProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
timeout :: Maybe GrpcTimeoutProperty
..}
= GrpcRouteProperty {timeout :: Maybe GrpcTimeoutProperty
timeout = GrpcTimeoutProperty -> Maybe GrpcTimeoutProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Timeout" GrpcRouteProperty
GrpcTimeoutProperty
newValue, Maybe GrpcRetryPolicyProperty
()
GrpcRouteMatchProperty
GrpcRouteActionProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
haddock_workaround_ :: ()
action :: GrpcRouteActionProperty
match :: GrpcRouteMatchProperty
retryPolicy :: Maybe GrpcRetryPolicyProperty
..}