module Stratosphere.VerifiedPermissions.IdentitySource.IdentitySourceConfigurationProperty (
module Exports, IdentitySourceConfigurationProperty(..),
mkIdentitySourceConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.VerifiedPermissions.IdentitySource.CognitoUserPoolConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.VerifiedPermissions.IdentitySource.OpenIdConnectConfigurationProperty as Exports
import Stratosphere.ResourceProperties
data IdentitySourceConfigurationProperty
=
IdentitySourceConfigurationProperty {IdentitySourceConfigurationProperty -> ()
haddock_workaround_ :: (),
IdentitySourceConfigurationProperty
-> Maybe CognitoUserPoolConfigurationProperty
cognitoUserPoolConfiguration :: (Prelude.Maybe CognitoUserPoolConfigurationProperty),
IdentitySourceConfigurationProperty
-> Maybe OpenIdConnectConfigurationProperty
openIdConnectConfiguration :: (Prelude.Maybe OpenIdConnectConfigurationProperty)}
deriving stock (IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty -> Bool
(IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty -> Bool)
-> (IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty -> Bool)
-> Eq IdentitySourceConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty -> Bool
== :: IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty -> Bool
$c/= :: IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty -> Bool
/= :: IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty -> Bool
Prelude.Eq, Int -> IdentitySourceConfigurationProperty -> ShowS
[IdentitySourceConfigurationProperty] -> ShowS
IdentitySourceConfigurationProperty -> String
(Int -> IdentitySourceConfigurationProperty -> ShowS)
-> (IdentitySourceConfigurationProperty -> String)
-> ([IdentitySourceConfigurationProperty] -> ShowS)
-> Show IdentitySourceConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IdentitySourceConfigurationProperty -> ShowS
showsPrec :: Int -> IdentitySourceConfigurationProperty -> ShowS
$cshow :: IdentitySourceConfigurationProperty -> String
show :: IdentitySourceConfigurationProperty -> String
$cshowList :: [IdentitySourceConfigurationProperty] -> ShowS
showList :: [IdentitySourceConfigurationProperty] -> ShowS
Prelude.Show)
mkIdentitySourceConfigurationProperty ::
IdentitySourceConfigurationProperty
mkIdentitySourceConfigurationProperty :: IdentitySourceConfigurationProperty
mkIdentitySourceConfigurationProperty
= IdentitySourceConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (),
cognitoUserPoolConfiguration :: Maybe CognitoUserPoolConfigurationProperty
cognitoUserPoolConfiguration = Maybe CognitoUserPoolConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
openIdConnectConfiguration :: Maybe OpenIdConnectConfigurationProperty
openIdConnectConfiguration = Maybe OpenIdConnectConfigurationProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties IdentitySourceConfigurationProperty where
toResourceProperties :: IdentitySourceConfigurationProperty -> ResourceProperties
toResourceProperties IdentitySourceConfigurationProperty {Maybe CognitoUserPoolConfigurationProperty
Maybe OpenIdConnectConfigurationProperty
()
haddock_workaround_ :: IdentitySourceConfigurationProperty -> ()
cognitoUserPoolConfiguration :: IdentitySourceConfigurationProperty
-> Maybe CognitoUserPoolConfigurationProperty
openIdConnectConfiguration :: IdentitySourceConfigurationProperty
-> Maybe OpenIdConnectConfigurationProperty
haddock_workaround_ :: ()
cognitoUserPoolConfiguration :: Maybe CognitoUserPoolConfigurationProperty
openIdConnectConfiguration :: Maybe OpenIdConnectConfigurationProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::VerifiedPermissions::IdentitySource.IdentitySourceConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CognitoUserPoolConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CognitoUserPoolConfiguration"
(CognitoUserPoolConfigurationProperty -> (Key, Value))
-> Maybe CognitoUserPoolConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CognitoUserPoolConfigurationProperty
cognitoUserPoolConfiguration,
Key -> OpenIdConnectConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OpenIdConnectConfiguration"
(OpenIdConnectConfigurationProperty -> (Key, Value))
-> Maybe OpenIdConnectConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe OpenIdConnectConfigurationProperty
openIdConnectConfiguration])}
instance JSON.ToJSON IdentitySourceConfigurationProperty where
toJSON :: IdentitySourceConfigurationProperty -> Value
toJSON IdentitySourceConfigurationProperty {Maybe CognitoUserPoolConfigurationProperty
Maybe OpenIdConnectConfigurationProperty
()
haddock_workaround_ :: IdentitySourceConfigurationProperty -> ()
cognitoUserPoolConfiguration :: IdentitySourceConfigurationProperty
-> Maybe CognitoUserPoolConfigurationProperty
openIdConnectConfiguration :: IdentitySourceConfigurationProperty
-> Maybe OpenIdConnectConfigurationProperty
haddock_workaround_ :: ()
cognitoUserPoolConfiguration :: Maybe CognitoUserPoolConfigurationProperty
openIdConnectConfiguration :: Maybe OpenIdConnectConfigurationProperty
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CognitoUserPoolConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CognitoUserPoolConfiguration"
(CognitoUserPoolConfigurationProperty -> (Key, Value))
-> Maybe CognitoUserPoolConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CognitoUserPoolConfigurationProperty
cognitoUserPoolConfiguration,
Key -> OpenIdConnectConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OpenIdConnectConfiguration"
(OpenIdConnectConfigurationProperty -> (Key, Value))
-> Maybe OpenIdConnectConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe OpenIdConnectConfigurationProperty
openIdConnectConfiguration]))
instance Property "CognitoUserPoolConfiguration" IdentitySourceConfigurationProperty where
type PropertyType "CognitoUserPoolConfiguration" IdentitySourceConfigurationProperty = CognitoUserPoolConfigurationProperty
set :: PropertyType
"CognitoUserPoolConfiguration" IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty
set PropertyType
"CognitoUserPoolConfiguration" IdentitySourceConfigurationProperty
newValue IdentitySourceConfigurationProperty {Maybe CognitoUserPoolConfigurationProperty
Maybe OpenIdConnectConfigurationProperty
()
haddock_workaround_ :: IdentitySourceConfigurationProperty -> ()
cognitoUserPoolConfiguration :: IdentitySourceConfigurationProperty
-> Maybe CognitoUserPoolConfigurationProperty
openIdConnectConfiguration :: IdentitySourceConfigurationProperty
-> Maybe OpenIdConnectConfigurationProperty
haddock_workaround_ :: ()
cognitoUserPoolConfiguration :: Maybe CognitoUserPoolConfigurationProperty
openIdConnectConfiguration :: Maybe OpenIdConnectConfigurationProperty
..}
= IdentitySourceConfigurationProperty
{cognitoUserPoolConfiguration :: Maybe CognitoUserPoolConfigurationProperty
cognitoUserPoolConfiguration = CognitoUserPoolConfigurationProperty
-> Maybe CognitoUserPoolConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"CognitoUserPoolConfiguration" IdentitySourceConfigurationProperty
CognitoUserPoolConfigurationProperty
newValue, Maybe OpenIdConnectConfigurationProperty
()
haddock_workaround_ :: ()
openIdConnectConfiguration :: Maybe OpenIdConnectConfigurationProperty
haddock_workaround_ :: ()
openIdConnectConfiguration :: Maybe OpenIdConnectConfigurationProperty
..}
instance Property "OpenIdConnectConfiguration" IdentitySourceConfigurationProperty where
type PropertyType "OpenIdConnectConfiguration" IdentitySourceConfigurationProperty = OpenIdConnectConfigurationProperty
set :: PropertyType
"OpenIdConnectConfiguration" IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty
-> IdentitySourceConfigurationProperty
set PropertyType
"OpenIdConnectConfiguration" IdentitySourceConfigurationProperty
newValue IdentitySourceConfigurationProperty {Maybe CognitoUserPoolConfigurationProperty
Maybe OpenIdConnectConfigurationProperty
()
haddock_workaround_ :: IdentitySourceConfigurationProperty -> ()
cognitoUserPoolConfiguration :: IdentitySourceConfigurationProperty
-> Maybe CognitoUserPoolConfigurationProperty
openIdConnectConfiguration :: IdentitySourceConfigurationProperty
-> Maybe OpenIdConnectConfigurationProperty
haddock_workaround_ :: ()
cognitoUserPoolConfiguration :: Maybe CognitoUserPoolConfigurationProperty
openIdConnectConfiguration :: Maybe OpenIdConnectConfigurationProperty
..}
= IdentitySourceConfigurationProperty
{openIdConnectConfiguration :: Maybe OpenIdConnectConfigurationProperty
openIdConnectConfiguration = OpenIdConnectConfigurationProperty
-> Maybe OpenIdConnectConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"OpenIdConnectConfiguration" IdentitySourceConfigurationProperty
OpenIdConnectConfigurationProperty
newValue, Maybe CognitoUserPoolConfigurationProperty
()
haddock_workaround_ :: ()
cognitoUserPoolConfiguration :: Maybe CognitoUserPoolConfigurationProperty
haddock_workaround_ :: ()
cognitoUserPoolConfiguration :: Maybe CognitoUserPoolConfigurationProperty
..}