module Stratosphere.QuickSight.DataSet.TagColumnOperationProperty (
module Exports, TagColumnOperationProperty(..),
mkTagColumnOperationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.DataSet.ColumnTagProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data TagColumnOperationProperty
=
TagColumnOperationProperty {TagColumnOperationProperty -> ()
haddock_workaround_ :: (),
TagColumnOperationProperty -> Value Text
columnName :: (Value Prelude.Text),
TagColumnOperationProperty -> [ColumnTagProperty]
tags :: [ColumnTagProperty]}
deriving stock (TagColumnOperationProperty -> TagColumnOperationProperty -> Bool
(TagColumnOperationProperty -> TagColumnOperationProperty -> Bool)
-> (TagColumnOperationProperty
-> TagColumnOperationProperty -> Bool)
-> Eq TagColumnOperationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TagColumnOperationProperty -> TagColumnOperationProperty -> Bool
== :: TagColumnOperationProperty -> TagColumnOperationProperty -> Bool
$c/= :: TagColumnOperationProperty -> TagColumnOperationProperty -> Bool
/= :: TagColumnOperationProperty -> TagColumnOperationProperty -> Bool
Prelude.Eq, Int -> TagColumnOperationProperty -> ShowS
[TagColumnOperationProperty] -> ShowS
TagColumnOperationProperty -> String
(Int -> TagColumnOperationProperty -> ShowS)
-> (TagColumnOperationProperty -> String)
-> ([TagColumnOperationProperty] -> ShowS)
-> Show TagColumnOperationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TagColumnOperationProperty -> ShowS
showsPrec :: Int -> TagColumnOperationProperty -> ShowS
$cshow :: TagColumnOperationProperty -> String
show :: TagColumnOperationProperty -> String
$cshowList :: [TagColumnOperationProperty] -> ShowS
showList :: [TagColumnOperationProperty] -> ShowS
Prelude.Show)
mkTagColumnOperationProperty ::
Value Prelude.Text
-> [ColumnTagProperty] -> TagColumnOperationProperty
mkTagColumnOperationProperty :: Value Text -> [ColumnTagProperty] -> TagColumnOperationProperty
mkTagColumnOperationProperty Value Text
columnName [ColumnTagProperty]
tags
= TagColumnOperationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), columnName :: Value Text
columnName = Value Text
columnName, tags :: [ColumnTagProperty]
tags = [ColumnTagProperty]
tags}
instance ToResourceProperties TagColumnOperationProperty where
toResourceProperties :: TagColumnOperationProperty -> ResourceProperties
toResourceProperties TagColumnOperationProperty {[ColumnTagProperty]
()
Value Text
haddock_workaround_ :: TagColumnOperationProperty -> ()
columnName :: TagColumnOperationProperty -> Value Text
tags :: TagColumnOperationProperty -> [ColumnTagProperty]
haddock_workaround_ :: ()
columnName :: Value Text
tags :: [ColumnTagProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::QuickSight::DataSet.TagColumnOperation",
supportsTags :: Bool
supportsTags = Bool
Prelude.True,
properties :: Object
properties = [Key
"ColumnName" 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
columnName,
Key
"Tags" Key -> [ColumnTagProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ColumnTagProperty]
tags]}
instance JSON.ToJSON TagColumnOperationProperty where
toJSON :: TagColumnOperationProperty -> Value
toJSON TagColumnOperationProperty {[ColumnTagProperty]
()
Value Text
haddock_workaround_ :: TagColumnOperationProperty -> ()
columnName :: TagColumnOperationProperty -> Value Text
tags :: TagColumnOperationProperty -> [ColumnTagProperty]
haddock_workaround_ :: ()
columnName :: Value Text
tags :: [ColumnTagProperty]
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"ColumnName" 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
columnName, Key
"Tags" Key -> [ColumnTagProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ColumnTagProperty]
tags]
instance Property "ColumnName" TagColumnOperationProperty where
type PropertyType "ColumnName" TagColumnOperationProperty = Value Prelude.Text
set :: PropertyType "ColumnName" TagColumnOperationProperty
-> TagColumnOperationProperty -> TagColumnOperationProperty
set PropertyType "ColumnName" TagColumnOperationProperty
newValue TagColumnOperationProperty {[ColumnTagProperty]
()
Value Text
haddock_workaround_ :: TagColumnOperationProperty -> ()
columnName :: TagColumnOperationProperty -> Value Text
tags :: TagColumnOperationProperty -> [ColumnTagProperty]
haddock_workaround_ :: ()
columnName :: Value Text
tags :: [ColumnTagProperty]
..}
= TagColumnOperationProperty {columnName :: Value Text
columnName = PropertyType "ColumnName" TagColumnOperationProperty
Value Text
newValue, [ColumnTagProperty]
()
haddock_workaround_ :: ()
tags :: [ColumnTagProperty]
haddock_workaround_ :: ()
tags :: [ColumnTagProperty]
..}
instance Property "Tags" TagColumnOperationProperty where
type PropertyType "Tags" TagColumnOperationProperty = [ColumnTagProperty]
set :: PropertyType "Tags" TagColumnOperationProperty
-> TagColumnOperationProperty -> TagColumnOperationProperty
set PropertyType "Tags" TagColumnOperationProperty
newValue TagColumnOperationProperty {[ColumnTagProperty]
()
Value Text
haddock_workaround_ :: TagColumnOperationProperty -> ()
columnName :: TagColumnOperationProperty -> Value Text
tags :: TagColumnOperationProperty -> [ColumnTagProperty]
haddock_workaround_ :: ()
columnName :: Value Text
tags :: [ColumnTagProperty]
..}
= TagColumnOperationProperty {tags :: [ColumnTagProperty]
tags = [ColumnTagProperty]
PropertyType "Tags" TagColumnOperationProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
columnName :: Value Text
haddock_workaround_ :: ()
columnName :: Value Text
..}