module Stratosphere.SMSVOICE.Pool (
module Exports, Pool(..), mkPool
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SMSVOICE.Pool.MandatoryKeywordsProperty as Exports
import {-# SOURCE #-} Stratosphere.SMSVOICE.Pool.OptionalKeywordProperty as Exports
import {-# SOURCE #-} Stratosphere.SMSVOICE.Pool.TwoWayProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data Pool
=
Pool {Pool -> ()
haddock_workaround_ :: (),
Pool -> Maybe (Value Bool)
deletionProtectionEnabled :: (Prelude.Maybe (Value Prelude.Bool)),
Pool -> MandatoryKeywordsProperty
mandatoryKeywords :: MandatoryKeywordsProperty,
Pool -> Maybe (Value Text)
optOutListName :: (Prelude.Maybe (Value Prelude.Text)),
Pool -> Maybe [OptionalKeywordProperty]
optionalKeywords :: (Prelude.Maybe [OptionalKeywordProperty]),
Pool -> ValueList Text
originationIdentities :: (ValueList Prelude.Text),
Pool -> Maybe (Value Bool)
selfManagedOptOutsEnabled :: (Prelude.Maybe (Value Prelude.Bool)),
Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: (Prelude.Maybe (Value Prelude.Bool)),
Pool -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag]),
Pool -> Maybe TwoWayProperty
twoWay :: (Prelude.Maybe TwoWayProperty)}
deriving stock (Pool -> Pool -> Bool
(Pool -> Pool -> Bool) -> (Pool -> Pool -> Bool) -> Eq Pool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pool -> Pool -> Bool
== :: Pool -> Pool -> Bool
$c/= :: Pool -> Pool -> Bool
/= :: Pool -> Pool -> Bool
Prelude.Eq, Int -> Pool -> ShowS
[Pool] -> ShowS
Pool -> String
(Int -> Pool -> ShowS)
-> (Pool -> String) -> ([Pool] -> ShowS) -> Show Pool
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pool -> ShowS
showsPrec :: Int -> Pool -> ShowS
$cshow :: Pool -> String
show :: Pool -> String
$cshowList :: [Pool] -> ShowS
showList :: [Pool] -> ShowS
Prelude.Show)
mkPool ::
MandatoryKeywordsProperty -> ValueList Prelude.Text -> Pool
mkPool :: MandatoryKeywordsProperty -> ValueList Text -> Pool
mkPool MandatoryKeywordsProperty
mandatoryKeywords ValueList Text
originationIdentities
= Pool
{haddock_workaround_ :: ()
haddock_workaround_ = (), mandatoryKeywords :: MandatoryKeywordsProperty
mandatoryKeywords = MandatoryKeywordsProperty
mandatoryKeywords,
originationIdentities :: ValueList Text
originationIdentities = ValueList Text
originationIdentities,
deletionProtectionEnabled :: Maybe (Value Bool)
deletionProtectionEnabled = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
optOutListName :: Maybe (Value Text)
optOutListName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
optionalKeywords :: Maybe [OptionalKeywordProperty]
optionalKeywords = Maybe [OptionalKeywordProperty]
forall a. Maybe a
Prelude.Nothing,
selfManagedOptOutsEnabled :: Maybe (Value Bool)
selfManagedOptOutsEnabled = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
sharedRoutesEnabled :: Maybe (Value Bool)
sharedRoutesEnabled = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing,
twoWay :: Maybe TwoWayProperty
twoWay = Maybe TwoWayProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties Pool where
toResourceProperties :: Pool -> ResourceProperties
toResourceProperties Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SMSVOICE::Pool", 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
"MandatoryKeywords" Key -> MandatoryKeywordsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MandatoryKeywordsProperty
mandatoryKeywords,
Key
"OriginationIdentities" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
originationIdentities]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeletionProtectionEnabled"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
deletionProtectionEnabled,
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
"OptOutListName" (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)
optOutListName,
Key -> [OptionalKeywordProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OptionalKeywords" ([OptionalKeywordProperty] -> (Key, Value))
-> Maybe [OptionalKeywordProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [OptionalKeywordProperty]
optionalKeywords,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SelfManagedOptOutsEnabled"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
selfManagedOptOutsEnabled,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SharedRoutesEnabled" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
sharedRoutesEnabled,
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,
Key -> TwoWayProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TwoWay" (TwoWayProperty -> (Key, Value))
-> Maybe TwoWayProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TwoWayProperty
twoWay]))}
instance JSON.ToJSON Pool where
toJSON :: Pool -> Value
toJSON Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
= [(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
"MandatoryKeywords" Key -> MandatoryKeywordsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MandatoryKeywordsProperty
mandatoryKeywords,
Key
"OriginationIdentities" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
originationIdentities]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeletionProtectionEnabled"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
deletionProtectionEnabled,
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
"OptOutListName" (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)
optOutListName,
Key -> [OptionalKeywordProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OptionalKeywords" ([OptionalKeywordProperty] -> (Key, Value))
-> Maybe [OptionalKeywordProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [OptionalKeywordProperty]
optionalKeywords,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SelfManagedOptOutsEnabled"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
selfManagedOptOutsEnabled,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SharedRoutesEnabled" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
sharedRoutesEnabled,
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,
Key -> TwoWayProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TwoWay" (TwoWayProperty -> (Key, Value))
-> Maybe TwoWayProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TwoWayProperty
twoWay])))
instance Property "DeletionProtectionEnabled" Pool where
type PropertyType "DeletionProtectionEnabled" Pool = Value Prelude.Bool
set :: PropertyType "DeletionProtectionEnabled" Pool -> Pool -> Pool
set PropertyType "DeletionProtectionEnabled" Pool
newValue Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
= Pool {deletionProtectionEnabled :: Maybe (Value Bool)
deletionProtectionEnabled = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DeletionProtectionEnabled" Pool
Value Bool
newValue, Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: ()
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
haddock_workaround_ :: ()
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
instance Property "MandatoryKeywords" Pool where
type PropertyType "MandatoryKeywords" Pool = MandatoryKeywordsProperty
set :: PropertyType "MandatoryKeywords" Pool -> Pool -> Pool
set PropertyType "MandatoryKeywords" Pool
newValue Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..} = Pool {mandatoryKeywords :: MandatoryKeywordsProperty
mandatoryKeywords = PropertyType "MandatoryKeywords" Pool
MandatoryKeywordsProperty
newValue, Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
instance Property "OptOutListName" Pool where
type PropertyType "OptOutListName" Pool = Value Prelude.Text
set :: PropertyType "OptOutListName" Pool -> Pool -> Pool
set PropertyType "OptOutListName" Pool
newValue Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
= Pool {optOutListName :: Maybe (Value Text)
optOutListName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "OptOutListName" Pool
Value Text
newValue, Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
instance Property "OptionalKeywords" Pool where
type PropertyType "OptionalKeywords" Pool = [OptionalKeywordProperty]
set :: PropertyType "OptionalKeywords" Pool -> Pool -> Pool
set PropertyType "OptionalKeywords" Pool
newValue Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
= Pool {optionalKeywords :: Maybe [OptionalKeywordProperty]
optionalKeywords = [OptionalKeywordProperty] -> Maybe [OptionalKeywordProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [OptionalKeywordProperty]
PropertyType "OptionalKeywords" Pool
newValue, Maybe [Tag]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
instance Property "OriginationIdentities" Pool where
type PropertyType "OriginationIdentities" Pool = ValueList Prelude.Text
set :: PropertyType "OriginationIdentities" Pool -> Pool -> Pool
set PropertyType "OriginationIdentities" Pool
newValue Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
= Pool {originationIdentities :: ValueList Text
originationIdentities = PropertyType "OriginationIdentities" Pool
ValueList Text
newValue, Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
MandatoryKeywordsProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
instance Property "SelfManagedOptOutsEnabled" Pool where
type PropertyType "SelfManagedOptOutsEnabled" Pool = Value Prelude.Bool
set :: PropertyType "SelfManagedOptOutsEnabled" Pool -> Pool -> Pool
set PropertyType "SelfManagedOptOutsEnabled" Pool
newValue Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
= Pool {selfManagedOptOutsEnabled :: Maybe (Value Bool)
selfManagedOptOutsEnabled = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SelfManagedOptOutsEnabled" Pool
Value Bool
newValue, Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
instance Property "SharedRoutesEnabled" Pool where
type PropertyType "SharedRoutesEnabled" Pool = Value Prelude.Bool
set :: PropertyType "SharedRoutesEnabled" Pool -> Pool -> Pool
set PropertyType "SharedRoutesEnabled" Pool
newValue Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
= Pool {sharedRoutesEnabled :: Maybe (Value Bool)
sharedRoutesEnabled = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SharedRoutesEnabled" Pool
Value Bool
newValue, Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..}
instance Property "Tags" Pool where
type PropertyType "Tags" Pool = [Tag]
set :: PropertyType "Tags" Pool -> Pool -> Pool
set PropertyType "Tags" Pool
newValue Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..} = Pool {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" Pool
newValue, Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
twoWay :: Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
twoWay :: Maybe TwoWayProperty
..}
instance Property "TwoWay" Pool where
type PropertyType "TwoWay" Pool = TwoWayProperty
set :: PropertyType "TwoWay" Pool -> Pool -> Pool
set PropertyType "TwoWay" Pool
newValue Pool {Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe TwoWayProperty
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: Pool -> ()
deletionProtectionEnabled :: Pool -> Maybe (Value Bool)
mandatoryKeywords :: Pool -> MandatoryKeywordsProperty
optOutListName :: Pool -> Maybe (Value Text)
optionalKeywords :: Pool -> Maybe [OptionalKeywordProperty]
originationIdentities :: Pool -> ValueList Text
selfManagedOptOutsEnabled :: Pool -> Maybe (Value Bool)
sharedRoutesEnabled :: Pool -> Maybe (Value Bool)
tags :: Pool -> Maybe [Tag]
twoWay :: Pool -> Maybe TwoWayProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
twoWay :: Maybe TwoWayProperty
..} = Pool {twoWay :: Maybe TwoWayProperty
twoWay = TwoWayProperty -> Maybe TwoWayProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TwoWay" Pool
TwoWayProperty
newValue, Maybe [Tag]
Maybe [OptionalKeywordProperty]
Maybe (Value Bool)
Maybe (Value Text)
()
ValueList Text
MandatoryKeywordsProperty
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
deletionProtectionEnabled :: Maybe (Value Bool)
mandatoryKeywords :: MandatoryKeywordsProperty
optOutListName :: Maybe (Value Text)
optionalKeywords :: Maybe [OptionalKeywordProperty]
originationIdentities :: ValueList Text
selfManagedOptOutsEnabled :: Maybe (Value Bool)
sharedRoutesEnabled :: Maybe (Value Bool)
tags :: Maybe [Tag]
..}