module Stratosphere.Cognito.UserPoolResourceServer.ResourceServerScopeTypeProperty (
        ResourceServerScopeTypeProperty(..),
        mkResourceServerScopeTypeProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ResourceServerScopeTypeProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-cognito-userpoolresourceserver-resourceserverscopetype.html>
    ResourceServerScopeTypeProperty {ResourceServerScopeTypeProperty -> ()
haddock_workaround_ :: (),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-cognito-userpoolresourceserver-resourceserverscopetype.html#cfn-cognito-userpoolresourceserver-resourceserverscopetype-scopedescription>
                                     ResourceServerScopeTypeProperty -> Value Text
scopeDescription :: (Value Prelude.Text),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-cognito-userpoolresourceserver-resourceserverscopetype.html#cfn-cognito-userpoolresourceserver-resourceserverscopetype-scopename>
                                     ResourceServerScopeTypeProperty -> Value Text
scopeName :: (Value Prelude.Text)}
  deriving stock (ResourceServerScopeTypeProperty
-> ResourceServerScopeTypeProperty -> Bool
(ResourceServerScopeTypeProperty
 -> ResourceServerScopeTypeProperty -> Bool)
-> (ResourceServerScopeTypeProperty
    -> ResourceServerScopeTypeProperty -> Bool)
-> Eq ResourceServerScopeTypeProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResourceServerScopeTypeProperty
-> ResourceServerScopeTypeProperty -> Bool
== :: ResourceServerScopeTypeProperty
-> ResourceServerScopeTypeProperty -> Bool
$c/= :: ResourceServerScopeTypeProperty
-> ResourceServerScopeTypeProperty -> Bool
/= :: ResourceServerScopeTypeProperty
-> ResourceServerScopeTypeProperty -> Bool
Prelude.Eq, Int -> ResourceServerScopeTypeProperty -> ShowS
[ResourceServerScopeTypeProperty] -> ShowS
ResourceServerScopeTypeProperty -> String
(Int -> ResourceServerScopeTypeProperty -> ShowS)
-> (ResourceServerScopeTypeProperty -> String)
-> ([ResourceServerScopeTypeProperty] -> ShowS)
-> Show ResourceServerScopeTypeProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResourceServerScopeTypeProperty -> ShowS
showsPrec :: Int -> ResourceServerScopeTypeProperty -> ShowS
$cshow :: ResourceServerScopeTypeProperty -> String
show :: ResourceServerScopeTypeProperty -> String
$cshowList :: [ResourceServerScopeTypeProperty] -> ShowS
showList :: [ResourceServerScopeTypeProperty] -> ShowS
Prelude.Show)
mkResourceServerScopeTypeProperty ::
  Value Prelude.Text
  -> Value Prelude.Text -> ResourceServerScopeTypeProperty
mkResourceServerScopeTypeProperty :: Value Text -> Value Text -> ResourceServerScopeTypeProperty
mkResourceServerScopeTypeProperty Value Text
scopeDescription Value Text
scopeName
  = ResourceServerScopeTypeProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), scopeDescription :: Value Text
scopeDescription = Value Text
scopeDescription,
       scopeName :: Value Text
scopeName = Value Text
scopeName}
instance ToResourceProperties ResourceServerScopeTypeProperty where
  toResourceProperties :: ResourceServerScopeTypeProperty -> ResourceProperties
toResourceProperties ResourceServerScopeTypeProperty {()
Value Text
haddock_workaround_ :: ResourceServerScopeTypeProperty -> ()
scopeDescription :: ResourceServerScopeTypeProperty -> Value Text
scopeName :: ResourceServerScopeTypeProperty -> Value Text
haddock_workaround_ :: ()
scopeDescription :: Value Text
scopeName :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Cognito::UserPoolResourceServer.ResourceServerScopeType",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"ScopeDescription" 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
scopeDescription,
                       Key
"ScopeName" 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
scopeName]}
instance JSON.ToJSON ResourceServerScopeTypeProperty where
  toJSON :: ResourceServerScopeTypeProperty -> Value
toJSON ResourceServerScopeTypeProperty {()
Value Text
haddock_workaround_ :: ResourceServerScopeTypeProperty -> ()
scopeDescription :: ResourceServerScopeTypeProperty -> Value Text
scopeName :: ResourceServerScopeTypeProperty -> Value Text
haddock_workaround_ :: ()
scopeDescription :: Value Text
scopeName :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"ScopeDescription" 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
scopeDescription,
         Key
"ScopeName" 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
scopeName]
instance Property "ScopeDescription" ResourceServerScopeTypeProperty where
  type PropertyType "ScopeDescription" ResourceServerScopeTypeProperty = Value Prelude.Text
  set :: PropertyType "ScopeDescription" ResourceServerScopeTypeProperty
-> ResourceServerScopeTypeProperty
-> ResourceServerScopeTypeProperty
set PropertyType "ScopeDescription" ResourceServerScopeTypeProperty
newValue ResourceServerScopeTypeProperty {()
Value Text
haddock_workaround_ :: ResourceServerScopeTypeProperty -> ()
scopeDescription :: ResourceServerScopeTypeProperty -> Value Text
scopeName :: ResourceServerScopeTypeProperty -> Value Text
haddock_workaround_ :: ()
scopeDescription :: Value Text
scopeName :: Value Text
..}
    = ResourceServerScopeTypeProperty {scopeDescription :: Value Text
scopeDescription = PropertyType "ScopeDescription" ResourceServerScopeTypeProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
scopeName :: Value Text
haddock_workaround_ :: ()
scopeName :: Value Text
..}
instance Property "ScopeName" ResourceServerScopeTypeProperty where
  type PropertyType "ScopeName" ResourceServerScopeTypeProperty = Value Prelude.Text
  set :: PropertyType "ScopeName" ResourceServerScopeTypeProperty
-> ResourceServerScopeTypeProperty
-> ResourceServerScopeTypeProperty
set PropertyType "ScopeName" ResourceServerScopeTypeProperty
newValue ResourceServerScopeTypeProperty {()
Value Text
haddock_workaround_ :: ResourceServerScopeTypeProperty -> ()
scopeDescription :: ResourceServerScopeTypeProperty -> Value Text
scopeName :: ResourceServerScopeTypeProperty -> Value Text
haddock_workaround_ :: ()
scopeDescription :: Value Text
scopeName :: Value Text
..}
    = ResourceServerScopeTypeProperty {scopeName :: Value Text
scopeName = PropertyType "ScopeName" ResourceServerScopeTypeProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
scopeDescription :: Value Text
haddock_workaround_ :: ()
scopeDescription :: Value Text
..}