module Stratosphere.CloudFront.Distribution.GrpcConfigProperty (
        GrpcConfigProperty(..), mkGrpcConfigProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data GrpcConfigProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-cloudfront-distribution-grpcconfig.html>
    GrpcConfigProperty {GrpcConfigProperty -> ()
haddock_workaround_ :: (),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-cloudfront-distribution-grpcconfig.html#cfn-cloudfront-distribution-grpcconfig-enabled>
                        GrpcConfigProperty -> Value Bool
enabled :: (Value Prelude.Bool)}
  deriving stock (GrpcConfigProperty -> GrpcConfigProperty -> Bool
(GrpcConfigProperty -> GrpcConfigProperty -> Bool)
-> (GrpcConfigProperty -> GrpcConfigProperty -> Bool)
-> Eq GrpcConfigProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GrpcConfigProperty -> GrpcConfigProperty -> Bool
== :: GrpcConfigProperty -> GrpcConfigProperty -> Bool
$c/= :: GrpcConfigProperty -> GrpcConfigProperty -> Bool
/= :: GrpcConfigProperty -> GrpcConfigProperty -> Bool
Prelude.Eq, Int -> GrpcConfigProperty -> ShowS
[GrpcConfigProperty] -> ShowS
GrpcConfigProperty -> String
(Int -> GrpcConfigProperty -> ShowS)
-> (GrpcConfigProperty -> String)
-> ([GrpcConfigProperty] -> ShowS)
-> Show GrpcConfigProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GrpcConfigProperty -> ShowS
showsPrec :: Int -> GrpcConfigProperty -> ShowS
$cshow :: GrpcConfigProperty -> String
show :: GrpcConfigProperty -> String
$cshowList :: [GrpcConfigProperty] -> ShowS
showList :: [GrpcConfigProperty] -> ShowS
Prelude.Show)
mkGrpcConfigProperty :: Value Prelude.Bool -> GrpcConfigProperty
mkGrpcConfigProperty :: Value Bool -> GrpcConfigProperty
mkGrpcConfigProperty Value Bool
enabled
  = GrpcConfigProperty {haddock_workaround_ :: ()
haddock_workaround_ = (), enabled :: Value Bool
enabled = Value Bool
enabled}
instance ToResourceProperties GrpcConfigProperty where
  toResourceProperties :: GrpcConfigProperty -> ResourceProperties
toResourceProperties GrpcConfigProperty {()
Value Bool
haddock_workaround_ :: GrpcConfigProperty -> ()
enabled :: GrpcConfigProperty -> Value Bool
haddock_workaround_ :: ()
enabled :: Value Bool
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::CloudFront::Distribution.GrpcConfig",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Enabled" Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Bool
enabled]}
instance JSON.ToJSON GrpcConfigProperty where
  toJSON :: GrpcConfigProperty -> Value
toJSON GrpcConfigProperty {()
Value Bool
haddock_workaround_ :: GrpcConfigProperty -> ()
enabled :: GrpcConfigProperty -> Value Bool
haddock_workaround_ :: ()
enabled :: Value Bool
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"Enabled" Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Bool
enabled]
instance Property "Enabled" GrpcConfigProperty where
  type PropertyType "Enabled" GrpcConfigProperty = Value Prelude.Bool
  set :: PropertyType "Enabled" GrpcConfigProperty
-> GrpcConfigProperty -> GrpcConfigProperty
set PropertyType "Enabled" GrpcConfigProperty
newValue GrpcConfigProperty {()
Value Bool
haddock_workaround_ :: GrpcConfigProperty -> ()
enabled :: GrpcConfigProperty -> Value Bool
haddock_workaround_ :: ()
enabled :: Value Bool
..}
    = GrpcConfigProperty {enabled :: Value Bool
enabled = PropertyType "Enabled" GrpcConfigProperty
Value Bool
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}