module Stratosphere.Lambda.Alias.VersionWeightProperty (
VersionWeightProperty(..), mkVersionWeightProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data VersionWeightProperty
=
VersionWeightProperty {VersionWeightProperty -> ()
haddock_workaround_ :: (),
VersionWeightProperty -> Value Text
functionVersion :: (Value Prelude.Text),
VersionWeightProperty -> Value Double
functionWeight :: (Value Prelude.Double)}
deriving stock (VersionWeightProperty -> VersionWeightProperty -> Bool
(VersionWeightProperty -> VersionWeightProperty -> Bool)
-> (VersionWeightProperty -> VersionWeightProperty -> Bool)
-> Eq VersionWeightProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VersionWeightProperty -> VersionWeightProperty -> Bool
== :: VersionWeightProperty -> VersionWeightProperty -> Bool
$c/= :: VersionWeightProperty -> VersionWeightProperty -> Bool
/= :: VersionWeightProperty -> VersionWeightProperty -> Bool
Prelude.Eq, Int -> VersionWeightProperty -> ShowS
[VersionWeightProperty] -> ShowS
VersionWeightProperty -> String
(Int -> VersionWeightProperty -> ShowS)
-> (VersionWeightProperty -> String)
-> ([VersionWeightProperty] -> ShowS)
-> Show VersionWeightProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VersionWeightProperty -> ShowS
showsPrec :: Int -> VersionWeightProperty -> ShowS
$cshow :: VersionWeightProperty -> String
show :: VersionWeightProperty -> String
$cshowList :: [VersionWeightProperty] -> ShowS
showList :: [VersionWeightProperty] -> ShowS
Prelude.Show)
mkVersionWeightProperty ::
Value Prelude.Text -> Value Prelude.Double -> VersionWeightProperty
mkVersionWeightProperty :: Value Text -> Value Double -> VersionWeightProperty
mkVersionWeightProperty Value Text
functionVersion Value Double
functionWeight
= VersionWeightProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), functionVersion :: Value Text
functionVersion = Value Text
functionVersion,
functionWeight :: Value Double
functionWeight = Value Double
functionWeight}
instance ToResourceProperties VersionWeightProperty where
toResourceProperties :: VersionWeightProperty -> ResourceProperties
toResourceProperties VersionWeightProperty {()
Value Double
Value Text
haddock_workaround_ :: VersionWeightProperty -> ()
functionVersion :: VersionWeightProperty -> Value Text
functionWeight :: VersionWeightProperty -> Value Double
haddock_workaround_ :: ()
functionVersion :: Value Text
functionWeight :: Value Double
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Lambda::Alias.VersionWeight",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"FunctionVersion" 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
functionVersion,
Key
"FunctionWeight" Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Double
functionWeight]}
instance JSON.ToJSON VersionWeightProperty where
toJSON :: VersionWeightProperty -> Value
toJSON VersionWeightProperty {()
Value Double
Value Text
haddock_workaround_ :: VersionWeightProperty -> ()
functionVersion :: VersionWeightProperty -> Value Text
functionWeight :: VersionWeightProperty -> Value Double
haddock_workaround_ :: ()
functionVersion :: Value Text
functionWeight :: Value Double
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"FunctionVersion" 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
functionVersion,
Key
"FunctionWeight" Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Double
functionWeight]
instance Property "FunctionVersion" VersionWeightProperty where
type PropertyType "FunctionVersion" VersionWeightProperty = Value Prelude.Text
set :: PropertyType "FunctionVersion" VersionWeightProperty
-> VersionWeightProperty -> VersionWeightProperty
set PropertyType "FunctionVersion" VersionWeightProperty
newValue VersionWeightProperty {()
Value Double
Value Text
haddock_workaround_ :: VersionWeightProperty -> ()
functionVersion :: VersionWeightProperty -> Value Text
functionWeight :: VersionWeightProperty -> Value Double
haddock_workaround_ :: ()
functionVersion :: Value Text
functionWeight :: Value Double
..}
= VersionWeightProperty {functionVersion :: Value Text
functionVersion = PropertyType "FunctionVersion" VersionWeightProperty
Value Text
newValue, ()
Value Double
haddock_workaround_ :: ()
functionWeight :: Value Double
haddock_workaround_ :: ()
functionWeight :: Value Double
..}
instance Property "FunctionWeight" VersionWeightProperty where
type PropertyType "FunctionWeight" VersionWeightProperty = Value Prelude.Double
set :: PropertyType "FunctionWeight" VersionWeightProperty
-> VersionWeightProperty -> VersionWeightProperty
set PropertyType "FunctionWeight" VersionWeightProperty
newValue VersionWeightProperty {()
Value Double
Value Text
haddock_workaround_ :: VersionWeightProperty -> ()
functionVersion :: VersionWeightProperty -> Value Text
functionWeight :: VersionWeightProperty -> Value Double
haddock_workaround_ :: ()
functionVersion :: Value Text
functionWeight :: Value Double
..}
= VersionWeightProperty {functionWeight :: Value Double
functionWeight = PropertyType "FunctionWeight" VersionWeightProperty
Value Double
newValue, ()
Value Text
haddock_workaround_ :: ()
functionVersion :: Value Text
haddock_workaround_ :: ()
functionVersion :: Value Text
..}