module Stratosphere.AppMesh.Route.MatchRangeProperty (
MatchRangeProperty(..), mkMatchRangeProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data MatchRangeProperty
=
MatchRangeProperty {MatchRangeProperty -> ()
haddock_workaround_ :: (),
MatchRangeProperty -> Value Integer
end :: (Value Prelude.Integer),
MatchRangeProperty -> Value Integer
start :: (Value Prelude.Integer)}
deriving stock (MatchRangeProperty -> MatchRangeProperty -> Bool
(MatchRangeProperty -> MatchRangeProperty -> Bool)
-> (MatchRangeProperty -> MatchRangeProperty -> Bool)
-> Eq MatchRangeProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MatchRangeProperty -> MatchRangeProperty -> Bool
== :: MatchRangeProperty -> MatchRangeProperty -> Bool
$c/= :: MatchRangeProperty -> MatchRangeProperty -> Bool
/= :: MatchRangeProperty -> MatchRangeProperty -> Bool
Prelude.Eq, Int -> MatchRangeProperty -> ShowS
[MatchRangeProperty] -> ShowS
MatchRangeProperty -> String
(Int -> MatchRangeProperty -> ShowS)
-> (MatchRangeProperty -> String)
-> ([MatchRangeProperty] -> ShowS)
-> Show MatchRangeProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MatchRangeProperty -> ShowS
showsPrec :: Int -> MatchRangeProperty -> ShowS
$cshow :: MatchRangeProperty -> String
show :: MatchRangeProperty -> String
$cshowList :: [MatchRangeProperty] -> ShowS
showList :: [MatchRangeProperty] -> ShowS
Prelude.Show)
mkMatchRangeProperty ::
Value Prelude.Integer
-> Value Prelude.Integer -> MatchRangeProperty
mkMatchRangeProperty :: Value Integer -> Value Integer -> MatchRangeProperty
mkMatchRangeProperty Value Integer
end Value Integer
start
= MatchRangeProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), end :: Value Integer
end = Value Integer
end, start :: Value Integer
start = Value Integer
start}
instance ToResourceProperties MatchRangeProperty where
toResourceProperties :: MatchRangeProperty -> ResourceProperties
toResourceProperties MatchRangeProperty {()
Value Integer
haddock_workaround_ :: MatchRangeProperty -> ()
end :: MatchRangeProperty -> Value Integer
start :: MatchRangeProperty -> Value Integer
haddock_workaround_ :: ()
end :: Value Integer
start :: Value Integer
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::AppMesh::Route.MatchRange",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"End" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
end, Key
"Start" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
start]}
instance JSON.ToJSON MatchRangeProperty where
toJSON :: MatchRangeProperty -> Value
toJSON MatchRangeProperty {()
Value Integer
haddock_workaround_ :: MatchRangeProperty -> ()
end :: MatchRangeProperty -> Value Integer
start :: MatchRangeProperty -> Value Integer
haddock_workaround_ :: ()
end :: Value Integer
start :: Value Integer
..}
= [(Key, Value)] -> Value
JSON.object [Key
"End" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
end, Key
"Start" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
start]
instance Property "End" MatchRangeProperty where
type PropertyType "End" MatchRangeProperty = Value Prelude.Integer
set :: PropertyType "End" MatchRangeProperty
-> MatchRangeProperty -> MatchRangeProperty
set PropertyType "End" MatchRangeProperty
newValue MatchRangeProperty {()
Value Integer
haddock_workaround_ :: MatchRangeProperty -> ()
end :: MatchRangeProperty -> Value Integer
start :: MatchRangeProperty -> Value Integer
haddock_workaround_ :: ()
end :: Value Integer
start :: Value Integer
..}
= MatchRangeProperty {end :: Value Integer
end = PropertyType "End" MatchRangeProperty
Value Integer
newValue, ()
Value Integer
haddock_workaround_ :: ()
start :: Value Integer
haddock_workaround_ :: ()
start :: Value Integer
..}
instance Property "Start" MatchRangeProperty where
type PropertyType "Start" MatchRangeProperty = Value Prelude.Integer
set :: PropertyType "Start" MatchRangeProperty
-> MatchRangeProperty -> MatchRangeProperty
set PropertyType "Start" MatchRangeProperty
newValue MatchRangeProperty {()
Value Integer
haddock_workaround_ :: MatchRangeProperty -> ()
end :: MatchRangeProperty -> Value Integer
start :: MatchRangeProperty -> Value Integer
haddock_workaround_ :: ()
end :: Value Integer
start :: Value Integer
..}
= MatchRangeProperty {start :: Value Integer
start = PropertyType "Start" MatchRangeProperty
Value Integer
newValue, ()
Value Integer
haddock_workaround_ :: ()
end :: Value Integer
haddock_workaround_ :: ()
end :: Value Integer
..}