module Stratosphere.LakeFormation.TagAssociation (
module Exports, TagAssociation(..), mkTagAssociation
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.LakeFormation.TagAssociation.LFTagPairProperty as Exports
import {-# SOURCE #-} Stratosphere.LakeFormation.TagAssociation.ResourceProperty as Exports
import Stratosphere.ResourceProperties
data TagAssociation
=
TagAssociation {TagAssociation -> ()
haddock_workaround_ :: (),
TagAssociation -> [LFTagPairProperty]
lFTags :: [LFTagPairProperty],
TagAssociation -> ResourceProperty
resource :: ResourceProperty}
deriving stock (TagAssociation -> TagAssociation -> Bool
(TagAssociation -> TagAssociation -> Bool)
-> (TagAssociation -> TagAssociation -> Bool) -> Eq TagAssociation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TagAssociation -> TagAssociation -> Bool
== :: TagAssociation -> TagAssociation -> Bool
$c/= :: TagAssociation -> TagAssociation -> Bool
/= :: TagAssociation -> TagAssociation -> Bool
Prelude.Eq, Int -> TagAssociation -> ShowS
[TagAssociation] -> ShowS
TagAssociation -> String
(Int -> TagAssociation -> ShowS)
-> (TagAssociation -> String)
-> ([TagAssociation] -> ShowS)
-> Show TagAssociation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TagAssociation -> ShowS
showsPrec :: Int -> TagAssociation -> ShowS
$cshow :: TagAssociation -> String
show :: TagAssociation -> String
$cshowList :: [TagAssociation] -> ShowS
showList :: [TagAssociation] -> ShowS
Prelude.Show)
mkTagAssociation ::
[LFTagPairProperty] -> ResourceProperty -> TagAssociation
mkTagAssociation :: [LFTagPairProperty] -> ResourceProperty -> TagAssociation
mkTagAssociation [LFTagPairProperty]
lFTags ResourceProperty
resource
= TagAssociation
{haddock_workaround_ :: ()
haddock_workaround_ = (), lFTags :: [LFTagPairProperty]
lFTags = [LFTagPairProperty]
lFTags, resource :: ResourceProperty
resource = ResourceProperty
resource}
instance ToResourceProperties TagAssociation where
toResourceProperties :: TagAssociation -> ResourceProperties
toResourceProperties TagAssociation {[LFTagPairProperty]
()
ResourceProperty
haddock_workaround_ :: TagAssociation -> ()
lFTags :: TagAssociation -> [LFTagPairProperty]
resource :: TagAssociation -> ResourceProperty
haddock_workaround_ :: ()
lFTags :: [LFTagPairProperty]
resource :: ResourceProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::LakeFormation::TagAssociation",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"LFTags" Key -> [LFTagPairProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [LFTagPairProperty]
lFTags,
Key
"Resource" Key -> ResourceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ResourceProperty
resource]}
instance JSON.ToJSON TagAssociation where
toJSON :: TagAssociation -> Value
toJSON TagAssociation {[LFTagPairProperty]
()
ResourceProperty
haddock_workaround_ :: TagAssociation -> ()
lFTags :: TagAssociation -> [LFTagPairProperty]
resource :: TagAssociation -> ResourceProperty
haddock_workaround_ :: ()
lFTags :: [LFTagPairProperty]
resource :: ResourceProperty
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"LFTags" Key -> [LFTagPairProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [LFTagPairProperty]
lFTags, Key
"Resource" Key -> ResourceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ResourceProperty
resource]
instance Property "LFTags" TagAssociation where
type PropertyType "LFTags" TagAssociation = [LFTagPairProperty]
set :: PropertyType "LFTags" TagAssociation
-> TagAssociation -> TagAssociation
set PropertyType "LFTags" TagAssociation
newValue TagAssociation {[LFTagPairProperty]
()
ResourceProperty
haddock_workaround_ :: TagAssociation -> ()
lFTags :: TagAssociation -> [LFTagPairProperty]
resource :: TagAssociation -> ResourceProperty
haddock_workaround_ :: ()
lFTags :: [LFTagPairProperty]
resource :: ResourceProperty
..}
= TagAssociation {lFTags :: [LFTagPairProperty]
lFTags = [LFTagPairProperty]
PropertyType "LFTags" TagAssociation
newValue, ()
ResourceProperty
haddock_workaround_ :: ()
resource :: ResourceProperty
haddock_workaround_ :: ()
resource :: ResourceProperty
..}
instance Property "Resource" TagAssociation where
type PropertyType "Resource" TagAssociation = ResourceProperty
set :: PropertyType "Resource" TagAssociation
-> TagAssociation -> TagAssociation
set PropertyType "Resource" TagAssociation
newValue TagAssociation {[LFTagPairProperty]
()
ResourceProperty
haddock_workaround_ :: TagAssociation -> ()
lFTags :: TagAssociation -> [LFTagPairProperty]
resource :: TagAssociation -> ResourceProperty
haddock_workaround_ :: ()
lFTags :: [LFTagPairProperty]
resource :: ResourceProperty
..}
= TagAssociation {resource :: ResourceProperty
resource = PropertyType "Resource" TagAssociation
ResourceProperty
newValue, [LFTagPairProperty]
()
haddock_workaround_ :: ()
lFTags :: [LFTagPairProperty]
haddock_workaround_ :: ()
lFTags :: [LFTagPairProperty]
..}