module Stratosphere.CodeArtifact.PackageGroup (
module Exports, PackageGroup(..), mkPackageGroup
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.CodeArtifact.PackageGroup.OriginConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data PackageGroup
=
PackageGroup {PackageGroup -> ()
haddock_workaround_ :: (),
PackageGroup -> Maybe (Value Text)
contactInfo :: (Prelude.Maybe (Value Prelude.Text)),
PackageGroup -> Maybe (Value Text)
description :: (Prelude.Maybe (Value Prelude.Text)),
PackageGroup -> Value Text
domainName :: (Value Prelude.Text),
PackageGroup -> Maybe (Value Text)
domainOwner :: (Prelude.Maybe (Value Prelude.Text)),
PackageGroup -> Maybe OriginConfigurationProperty
originConfiguration :: (Prelude.Maybe OriginConfigurationProperty),
PackageGroup -> Value Text
pattern :: (Value Prelude.Text),
PackageGroup -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag])}
deriving stock (PackageGroup -> PackageGroup -> Bool
(PackageGroup -> PackageGroup -> Bool)
-> (PackageGroup -> PackageGroup -> Bool) -> Eq PackageGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PackageGroup -> PackageGroup -> Bool
== :: PackageGroup -> PackageGroup -> Bool
$c/= :: PackageGroup -> PackageGroup -> Bool
/= :: PackageGroup -> PackageGroup -> Bool
Prelude.Eq, Int -> PackageGroup -> ShowS
[PackageGroup] -> ShowS
PackageGroup -> String
(Int -> PackageGroup -> ShowS)
-> (PackageGroup -> String)
-> ([PackageGroup] -> ShowS)
-> Show PackageGroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PackageGroup -> ShowS
showsPrec :: Int -> PackageGroup -> ShowS
$cshow :: PackageGroup -> String
show :: PackageGroup -> String
$cshowList :: [PackageGroup] -> ShowS
showList :: [PackageGroup] -> ShowS
Prelude.Show)
mkPackageGroup ::
Value Prelude.Text -> Value Prelude.Text -> PackageGroup
mkPackageGroup :: Value Text -> Value Text -> PackageGroup
mkPackageGroup Value Text
domainName Value Text
pattern
= PackageGroup
{haddock_workaround_ :: ()
haddock_workaround_ = (), domainName :: Value Text
domainName = Value Text
domainName,
pattern :: Value Text
pattern = Value Text
pattern, contactInfo :: Maybe (Value Text)
contactInfo = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
description :: Maybe (Value Text)
description = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, domainOwner :: Maybe (Value Text)
domainOwner = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
originConfiguration :: Maybe OriginConfigurationProperty
originConfiguration = Maybe OriginConfigurationProperty
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties PackageGroup where
toResourceProperties :: PackageGroup -> ResourceProperties
toResourceProperties PackageGroup {Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: PackageGroup -> ()
contactInfo :: PackageGroup -> Maybe (Value Text)
description :: PackageGroup -> Maybe (Value Text)
domainName :: PackageGroup -> Value Text
domainOwner :: PackageGroup -> Maybe (Value Text)
originConfiguration :: PackageGroup -> Maybe OriginConfigurationProperty
pattern :: PackageGroup -> Value Text
tags :: PackageGroup -> Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::CodeArtifact::PackageGroup",
supportsTags :: Bool
supportsTags = Bool
Prelude.True,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"DomainName" 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
domainName, Key
"Pattern" 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
pattern]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"ContactInfo" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
contactInfo,
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..=) Key
"Description" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
description,
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..=) Key
"DomainOwner" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
domainOwner,
Key -> OriginConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OriginConfiguration" (OriginConfigurationProperty -> (Key, Value))
-> Maybe OriginConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe OriginConfigurationProperty
originConfiguration,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags]))}
instance JSON.ToJSON PackageGroup where
toJSON :: PackageGroup -> Value
toJSON PackageGroup {Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: PackageGroup -> ()
contactInfo :: PackageGroup -> Maybe (Value Text)
description :: PackageGroup -> Maybe (Value Text)
domainName :: PackageGroup -> Value Text
domainOwner :: PackageGroup -> Maybe (Value Text)
originConfiguration :: PackageGroup -> Maybe OriginConfigurationProperty
pattern :: PackageGroup -> Value Text
tags :: PackageGroup -> Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"DomainName" 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
domainName, Key
"Pattern" 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
pattern]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"ContactInfo" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
contactInfo,
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..=) Key
"Description" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
description,
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..=) Key
"DomainOwner" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
domainOwner,
Key -> OriginConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OriginConfiguration" (OriginConfigurationProperty -> (Key, Value))
-> Maybe OriginConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe OriginConfigurationProperty
originConfiguration,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags])))
instance Property "ContactInfo" PackageGroup where
type PropertyType "ContactInfo" PackageGroup = Value Prelude.Text
set :: PropertyType "ContactInfo" PackageGroup
-> PackageGroup -> PackageGroup
set PropertyType "ContactInfo" PackageGroup
newValue PackageGroup {Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: PackageGroup -> ()
contactInfo :: PackageGroup -> Maybe (Value Text)
description :: PackageGroup -> Maybe (Value Text)
domainName :: PackageGroup -> Value Text
domainOwner :: PackageGroup -> Maybe (Value Text)
originConfiguration :: PackageGroup -> Maybe OriginConfigurationProperty
pattern :: PackageGroup -> Value Text
tags :: PackageGroup -> Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
= PackageGroup {contactInfo :: Maybe (Value Text)
contactInfo = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ContactInfo" PackageGroup
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
haddock_workaround_ :: ()
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
instance Property "Description" PackageGroup where
type PropertyType "Description" PackageGroup = Value Prelude.Text
set :: PropertyType "Description" PackageGroup
-> PackageGroup -> PackageGroup
set PropertyType "Description" PackageGroup
newValue PackageGroup {Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: PackageGroup -> ()
contactInfo :: PackageGroup -> Maybe (Value Text)
description :: PackageGroup -> Maybe (Value Text)
domainName :: PackageGroup -> Value Text
domainOwner :: PackageGroup -> Maybe (Value Text)
originConfiguration :: PackageGroup -> Maybe OriginConfigurationProperty
pattern :: PackageGroup -> Value Text
tags :: PackageGroup -> Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
= PackageGroup {description :: Maybe (Value Text)
description = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Description" PackageGroup
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
instance Property "DomainName" PackageGroup where
type PropertyType "DomainName" PackageGroup = Value Prelude.Text
set :: PropertyType "DomainName" PackageGroup
-> PackageGroup -> PackageGroup
set PropertyType "DomainName" PackageGroup
newValue PackageGroup {Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: PackageGroup -> ()
contactInfo :: PackageGroup -> Maybe (Value Text)
description :: PackageGroup -> Maybe (Value Text)
domainName :: PackageGroup -> Value Text
domainOwner :: PackageGroup -> Maybe (Value Text)
originConfiguration :: PackageGroup -> Maybe OriginConfigurationProperty
pattern :: PackageGroup -> Value Text
tags :: PackageGroup -> Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
= PackageGroup {domainName :: Value Text
domainName = PropertyType "DomainName" PackageGroup
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
instance Property "DomainOwner" PackageGroup where
type PropertyType "DomainOwner" PackageGroup = Value Prelude.Text
set :: PropertyType "DomainOwner" PackageGroup
-> PackageGroup -> PackageGroup
set PropertyType "DomainOwner" PackageGroup
newValue PackageGroup {Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: PackageGroup -> ()
contactInfo :: PackageGroup -> Maybe (Value Text)
description :: PackageGroup -> Maybe (Value Text)
domainName :: PackageGroup -> Value Text
domainOwner :: PackageGroup -> Maybe (Value Text)
originConfiguration :: PackageGroup -> Maybe OriginConfigurationProperty
pattern :: PackageGroup -> Value Text
tags :: PackageGroup -> Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
= PackageGroup {domainOwner :: Maybe (Value Text)
domainOwner = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DomainOwner" PackageGroup
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
instance Property "OriginConfiguration" PackageGroup where
type PropertyType "OriginConfiguration" PackageGroup = OriginConfigurationProperty
set :: PropertyType "OriginConfiguration" PackageGroup
-> PackageGroup -> PackageGroup
set PropertyType "OriginConfiguration" PackageGroup
newValue PackageGroup {Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: PackageGroup -> ()
contactInfo :: PackageGroup -> Maybe (Value Text)
description :: PackageGroup -> Maybe (Value Text)
domainName :: PackageGroup -> Value Text
domainOwner :: PackageGroup -> Maybe (Value Text)
originConfiguration :: PackageGroup -> Maybe OriginConfigurationProperty
pattern :: PackageGroup -> Value Text
tags :: PackageGroup -> Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
= PackageGroup {originConfiguration :: Maybe OriginConfigurationProperty
originConfiguration = OriginConfigurationProperty -> Maybe OriginConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "OriginConfiguration" PackageGroup
OriginConfigurationProperty
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
pattern :: Value Text
tags :: Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
pattern :: Value Text
tags :: Maybe [Tag]
..}
instance Property "Pattern" PackageGroup where
type PropertyType "Pattern" PackageGroup = Value Prelude.Text
set :: PropertyType "Pattern" PackageGroup -> PackageGroup -> PackageGroup
set PropertyType "Pattern" PackageGroup
newValue PackageGroup {Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: PackageGroup -> ()
contactInfo :: PackageGroup -> Maybe (Value Text)
description :: PackageGroup -> Maybe (Value Text)
domainName :: PackageGroup -> Value Text
domainOwner :: PackageGroup -> Maybe (Value Text)
originConfiguration :: PackageGroup -> Maybe OriginConfigurationProperty
pattern :: PackageGroup -> Value Text
tags :: PackageGroup -> Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
= PackageGroup {pattern :: Value Text
pattern = PropertyType "Pattern" PackageGroup
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
tags :: Maybe [Tag]
..}
instance Property "Tags" PackageGroup where
type PropertyType "Tags" PackageGroup = [Tag]
set :: PropertyType "Tags" PackageGroup -> PackageGroup -> PackageGroup
set PropertyType "Tags" PackageGroup
newValue PackageGroup {Maybe [Tag]
Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: PackageGroup -> ()
contactInfo :: PackageGroup -> Maybe (Value Text)
description :: PackageGroup -> Maybe (Value Text)
domainName :: PackageGroup -> Value Text
domainOwner :: PackageGroup -> Maybe (Value Text)
originConfiguration :: PackageGroup -> Maybe OriginConfigurationProperty
pattern :: PackageGroup -> Value Text
tags :: PackageGroup -> Maybe [Tag]
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
tags :: Maybe [Tag]
..}
= PackageGroup {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" PackageGroup
newValue, Maybe (Value Text)
Maybe OriginConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
haddock_workaround_ :: ()
contactInfo :: Maybe (Value Text)
description :: Maybe (Value Text)
domainName :: Value Text
domainOwner :: Maybe (Value Text)
originConfiguration :: Maybe OriginConfigurationProperty
pattern :: Value Text
..}