module Stratosphere.SMSVOICE.PhoneNumber.MandatoryKeywordsProperty (
        module Exports, MandatoryKeywordsProperty(..),
        mkMandatoryKeywordsProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SMSVOICE.PhoneNumber.MandatoryKeywordProperty as Exports
import Stratosphere.ResourceProperties
data MandatoryKeywordsProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-smsvoice-phonenumber-mandatorykeywords.html>
    MandatoryKeywordsProperty {MandatoryKeywordsProperty -> ()
haddock_workaround_ :: (),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-smsvoice-phonenumber-mandatorykeywords.html#cfn-smsvoice-phonenumber-mandatorykeywords-help>
                               MandatoryKeywordsProperty -> MandatoryKeywordProperty
hELP :: MandatoryKeywordProperty,
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-smsvoice-phonenumber-mandatorykeywords.html#cfn-smsvoice-phonenumber-mandatorykeywords-stop>
                               MandatoryKeywordsProperty -> MandatoryKeywordProperty
sTOP :: MandatoryKeywordProperty}
  deriving stock (MandatoryKeywordsProperty -> MandatoryKeywordsProperty -> Bool
(MandatoryKeywordsProperty -> MandatoryKeywordsProperty -> Bool)
-> (MandatoryKeywordsProperty -> MandatoryKeywordsProperty -> Bool)
-> Eq MandatoryKeywordsProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MandatoryKeywordsProperty -> MandatoryKeywordsProperty -> Bool
== :: MandatoryKeywordsProperty -> MandatoryKeywordsProperty -> Bool
$c/= :: MandatoryKeywordsProperty -> MandatoryKeywordsProperty -> Bool
/= :: MandatoryKeywordsProperty -> MandatoryKeywordsProperty -> Bool
Prelude.Eq, Int -> MandatoryKeywordsProperty -> ShowS
[MandatoryKeywordsProperty] -> ShowS
MandatoryKeywordsProperty -> String
(Int -> MandatoryKeywordsProperty -> ShowS)
-> (MandatoryKeywordsProperty -> String)
-> ([MandatoryKeywordsProperty] -> ShowS)
-> Show MandatoryKeywordsProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MandatoryKeywordsProperty -> ShowS
showsPrec :: Int -> MandatoryKeywordsProperty -> ShowS
$cshow :: MandatoryKeywordsProperty -> String
show :: MandatoryKeywordsProperty -> String
$cshowList :: [MandatoryKeywordsProperty] -> ShowS
showList :: [MandatoryKeywordsProperty] -> ShowS
Prelude.Show)
mkMandatoryKeywordsProperty ::
  MandatoryKeywordProperty
  -> MandatoryKeywordProperty -> MandatoryKeywordsProperty
mkMandatoryKeywordsProperty :: MandatoryKeywordProperty
-> MandatoryKeywordProperty -> MandatoryKeywordsProperty
mkMandatoryKeywordsProperty MandatoryKeywordProperty
hELP MandatoryKeywordProperty
sTOP
  = MandatoryKeywordsProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), hELP :: MandatoryKeywordProperty
hELP = MandatoryKeywordProperty
hELP, sTOP :: MandatoryKeywordProperty
sTOP = MandatoryKeywordProperty
sTOP}
instance ToResourceProperties MandatoryKeywordsProperty where
  toResourceProperties :: MandatoryKeywordsProperty -> ResourceProperties
toResourceProperties MandatoryKeywordsProperty {()
MandatoryKeywordProperty
haddock_workaround_ :: MandatoryKeywordsProperty -> ()
hELP :: MandatoryKeywordsProperty -> MandatoryKeywordProperty
sTOP :: MandatoryKeywordsProperty -> MandatoryKeywordProperty
haddock_workaround_ :: ()
hELP :: MandatoryKeywordProperty
sTOP :: MandatoryKeywordProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::SMSVOICE::PhoneNumber.MandatoryKeywords",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"HELP" Key -> MandatoryKeywordProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MandatoryKeywordProperty
hELP, Key
"STOP" Key -> MandatoryKeywordProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MandatoryKeywordProperty
sTOP]}
instance JSON.ToJSON MandatoryKeywordsProperty where
  toJSON :: MandatoryKeywordsProperty -> Value
toJSON MandatoryKeywordsProperty {()
MandatoryKeywordProperty
haddock_workaround_ :: MandatoryKeywordsProperty -> ()
hELP :: MandatoryKeywordsProperty -> MandatoryKeywordProperty
sTOP :: MandatoryKeywordsProperty -> MandatoryKeywordProperty
haddock_workaround_ :: ()
hELP :: MandatoryKeywordProperty
sTOP :: MandatoryKeywordProperty
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"HELP" Key -> MandatoryKeywordProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MandatoryKeywordProperty
hELP, Key
"STOP" Key -> MandatoryKeywordProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MandatoryKeywordProperty
sTOP]
instance Property "HELP" MandatoryKeywordsProperty where
  type PropertyType "HELP" MandatoryKeywordsProperty = MandatoryKeywordProperty
  set :: PropertyType "HELP" MandatoryKeywordsProperty
-> MandatoryKeywordsProperty -> MandatoryKeywordsProperty
set PropertyType "HELP" MandatoryKeywordsProperty
newValue MandatoryKeywordsProperty {()
MandatoryKeywordProperty
haddock_workaround_ :: MandatoryKeywordsProperty -> ()
hELP :: MandatoryKeywordsProperty -> MandatoryKeywordProperty
sTOP :: MandatoryKeywordsProperty -> MandatoryKeywordProperty
haddock_workaround_ :: ()
hELP :: MandatoryKeywordProperty
sTOP :: MandatoryKeywordProperty
..}
    = MandatoryKeywordsProperty {hELP :: MandatoryKeywordProperty
hELP = PropertyType "HELP" MandatoryKeywordsProperty
MandatoryKeywordProperty
newValue, ()
MandatoryKeywordProperty
haddock_workaround_ :: ()
sTOP :: MandatoryKeywordProperty
haddock_workaround_ :: ()
sTOP :: MandatoryKeywordProperty
..}
instance Property "STOP" MandatoryKeywordsProperty where
  type PropertyType "STOP" MandatoryKeywordsProperty = MandatoryKeywordProperty
  set :: PropertyType "STOP" MandatoryKeywordsProperty
-> MandatoryKeywordsProperty -> MandatoryKeywordsProperty
set PropertyType "STOP" MandatoryKeywordsProperty
newValue MandatoryKeywordsProperty {()
MandatoryKeywordProperty
haddock_workaround_ :: MandatoryKeywordsProperty -> ()
hELP :: MandatoryKeywordsProperty -> MandatoryKeywordProperty
sTOP :: MandatoryKeywordsProperty -> MandatoryKeywordProperty
haddock_workaround_ :: ()
hELP :: MandatoryKeywordProperty
sTOP :: MandatoryKeywordProperty
..}
    = MandatoryKeywordsProperty {sTOP :: MandatoryKeywordProperty
sTOP = PropertyType "STOP" MandatoryKeywordsProperty
MandatoryKeywordProperty
newValue, ()
MandatoryKeywordProperty
haddock_workaround_ :: ()
hELP :: MandatoryKeywordProperty
haddock_workaround_ :: ()
hELP :: MandatoryKeywordProperty
..}