module Stratosphere.QuickSight.Template.CustomActionURLOperationProperty (
        CustomActionURLOperationProperty(..),
        mkCustomActionURLOperationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data CustomActionURLOperationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-customactionurloperation.html>
    CustomActionURLOperationProperty {CustomActionURLOperationProperty -> ()
haddock_workaround_ :: (),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-customactionurloperation.html#cfn-quicksight-template-customactionurloperation-urltarget>
                                      CustomActionURLOperationProperty -> Value Text
uRLTarget :: (Value Prelude.Text),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-customactionurloperation.html#cfn-quicksight-template-customactionurloperation-urltemplate>
                                      CustomActionURLOperationProperty -> Value Text
uRLTemplate :: (Value Prelude.Text)}
  deriving stock (CustomActionURLOperationProperty
-> CustomActionURLOperationProperty -> Bool
(CustomActionURLOperationProperty
 -> CustomActionURLOperationProperty -> Bool)
-> (CustomActionURLOperationProperty
    -> CustomActionURLOperationProperty -> Bool)
-> Eq CustomActionURLOperationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CustomActionURLOperationProperty
-> CustomActionURLOperationProperty -> Bool
== :: CustomActionURLOperationProperty
-> CustomActionURLOperationProperty -> Bool
$c/= :: CustomActionURLOperationProperty
-> CustomActionURLOperationProperty -> Bool
/= :: CustomActionURLOperationProperty
-> CustomActionURLOperationProperty -> Bool
Prelude.Eq, Int -> CustomActionURLOperationProperty -> ShowS
[CustomActionURLOperationProperty] -> ShowS
CustomActionURLOperationProperty -> String
(Int -> CustomActionURLOperationProperty -> ShowS)
-> (CustomActionURLOperationProperty -> String)
-> ([CustomActionURLOperationProperty] -> ShowS)
-> Show CustomActionURLOperationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CustomActionURLOperationProperty -> ShowS
showsPrec :: Int -> CustomActionURLOperationProperty -> ShowS
$cshow :: CustomActionURLOperationProperty -> String
show :: CustomActionURLOperationProperty -> String
$cshowList :: [CustomActionURLOperationProperty] -> ShowS
showList :: [CustomActionURLOperationProperty] -> ShowS
Prelude.Show)
mkCustomActionURLOperationProperty ::
  Value Prelude.Text
  -> Value Prelude.Text -> CustomActionURLOperationProperty
mkCustomActionURLOperationProperty :: Value Text -> Value Text -> CustomActionURLOperationProperty
mkCustomActionURLOperationProperty Value Text
uRLTarget Value Text
uRLTemplate
  = CustomActionURLOperationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), uRLTarget :: Value Text
uRLTarget = Value Text
uRLTarget,
       uRLTemplate :: Value Text
uRLTemplate = Value Text
uRLTemplate}
instance ToResourceProperties CustomActionURLOperationProperty where
  toResourceProperties :: CustomActionURLOperationProperty -> ResourceProperties
toResourceProperties CustomActionURLOperationProperty {()
Value Text
haddock_workaround_ :: CustomActionURLOperationProperty -> ()
uRLTarget :: CustomActionURLOperationProperty -> Value Text
uRLTemplate :: CustomActionURLOperationProperty -> Value Text
haddock_workaround_ :: ()
uRLTarget :: Value Text
uRLTemplate :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::QuickSight::Template.CustomActionURLOperation",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"URLTarget" 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
uRLTarget,
                       Key
"URLTemplate" 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
uRLTemplate]}
instance JSON.ToJSON CustomActionURLOperationProperty where
  toJSON :: CustomActionURLOperationProperty -> Value
toJSON CustomActionURLOperationProperty {()
Value Text
haddock_workaround_ :: CustomActionURLOperationProperty -> ()
uRLTarget :: CustomActionURLOperationProperty -> Value Text
uRLTemplate :: CustomActionURLOperationProperty -> Value Text
haddock_workaround_ :: ()
uRLTarget :: Value Text
uRLTemplate :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"URLTarget" 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
uRLTarget, Key
"URLTemplate" 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
uRLTemplate]
instance Property "URLTarget" CustomActionURLOperationProperty where
  type PropertyType "URLTarget" CustomActionURLOperationProperty = Value Prelude.Text
  set :: PropertyType "URLTarget" CustomActionURLOperationProperty
-> CustomActionURLOperationProperty
-> CustomActionURLOperationProperty
set PropertyType "URLTarget" CustomActionURLOperationProperty
newValue CustomActionURLOperationProperty {()
Value Text
haddock_workaround_ :: CustomActionURLOperationProperty -> ()
uRLTarget :: CustomActionURLOperationProperty -> Value Text
uRLTemplate :: CustomActionURLOperationProperty -> Value Text
haddock_workaround_ :: ()
uRLTarget :: Value Text
uRLTemplate :: Value Text
..}
    = CustomActionURLOperationProperty {uRLTarget :: Value Text
uRLTarget = PropertyType "URLTarget" CustomActionURLOperationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
uRLTemplate :: Value Text
haddock_workaround_ :: ()
uRLTemplate :: Value Text
..}
instance Property "URLTemplate" CustomActionURLOperationProperty where
  type PropertyType "URLTemplate" CustomActionURLOperationProperty = Value Prelude.Text
  set :: PropertyType "URLTemplate" CustomActionURLOperationProperty
-> CustomActionURLOperationProperty
-> CustomActionURLOperationProperty
set PropertyType "URLTemplate" CustomActionURLOperationProperty
newValue CustomActionURLOperationProperty {()
Value Text
haddock_workaround_ :: CustomActionURLOperationProperty -> ()
uRLTarget :: CustomActionURLOperationProperty -> Value Text
uRLTemplate :: CustomActionURLOperationProperty -> Value Text
haddock_workaround_ :: ()
uRLTarget :: Value Text
uRLTemplate :: Value Text
..}
    = CustomActionURLOperationProperty {uRLTemplate :: Value Text
uRLTemplate = PropertyType "URLTemplate" CustomActionURLOperationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
uRLTarget :: Value Text
haddock_workaround_ :: ()
uRLTarget :: Value Text
..}