module Stratosphere.DirectoryService.MicrosoftAD (
module Exports, MicrosoftAD(..), mkMicrosoftAD
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.DirectoryService.MicrosoftAD.VpcSettingsProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data MicrosoftAD
=
MicrosoftAD {MicrosoftAD -> ()
haddock_workaround_ :: (),
MicrosoftAD -> Maybe (Value Bool)
createAlias :: (Prelude.Maybe (Value Prelude.Bool)),
MicrosoftAD -> Maybe (Value Text)
edition :: (Prelude.Maybe (Value Prelude.Text)),
MicrosoftAD -> Maybe (Value Bool)
enableSso :: (Prelude.Maybe (Value Prelude.Bool)),
MicrosoftAD -> Value Text
name :: (Value Prelude.Text),
MicrosoftAD -> Value Text
password :: (Value Prelude.Text),
MicrosoftAD -> Maybe (Value Text)
shortName :: (Prelude.Maybe (Value Prelude.Text)),
MicrosoftAD -> VpcSettingsProperty
vpcSettings :: VpcSettingsProperty}
deriving stock (MicrosoftAD -> MicrosoftAD -> Bool
(MicrosoftAD -> MicrosoftAD -> Bool)
-> (MicrosoftAD -> MicrosoftAD -> Bool) -> Eq MicrosoftAD
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MicrosoftAD -> MicrosoftAD -> Bool
== :: MicrosoftAD -> MicrosoftAD -> Bool
$c/= :: MicrosoftAD -> MicrosoftAD -> Bool
/= :: MicrosoftAD -> MicrosoftAD -> Bool
Prelude.Eq, Int -> MicrosoftAD -> ShowS
[MicrosoftAD] -> ShowS
MicrosoftAD -> String
(Int -> MicrosoftAD -> ShowS)
-> (MicrosoftAD -> String)
-> ([MicrosoftAD] -> ShowS)
-> Show MicrosoftAD
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MicrosoftAD -> ShowS
showsPrec :: Int -> MicrosoftAD -> ShowS
$cshow :: MicrosoftAD -> String
show :: MicrosoftAD -> String
$cshowList :: [MicrosoftAD] -> ShowS
showList :: [MicrosoftAD] -> ShowS
Prelude.Show)
mkMicrosoftAD ::
Value Prelude.Text
-> Value Prelude.Text -> VpcSettingsProperty -> MicrosoftAD
mkMicrosoftAD :: Value Text -> Value Text -> VpcSettingsProperty -> MicrosoftAD
mkMicrosoftAD Value Text
name Value Text
password VpcSettingsProperty
vpcSettings
= MicrosoftAD
{haddock_workaround_ :: ()
haddock_workaround_ = (), name :: Value Text
name = Value Text
name, password :: Value Text
password = Value Text
password,
vpcSettings :: VpcSettingsProperty
vpcSettings = VpcSettingsProperty
vpcSettings, createAlias :: Maybe (Value Bool)
createAlias = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
edition :: Maybe (Value Text)
edition = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, enableSso :: Maybe (Value Bool)
enableSso = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
shortName :: Maybe (Value Text)
shortName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties MicrosoftAD where
toResourceProperties :: MicrosoftAD -> ResourceProperties
toResourceProperties MicrosoftAD {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: MicrosoftAD -> ()
createAlias :: MicrosoftAD -> Maybe (Value Bool)
edition :: MicrosoftAD -> Maybe (Value Text)
enableSso :: MicrosoftAD -> Maybe (Value Bool)
name :: MicrosoftAD -> Value Text
password :: MicrosoftAD -> Value Text
shortName :: MicrosoftAD -> Maybe (Value Text)
vpcSettings :: MicrosoftAD -> VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::DirectoryService::MicrosoftAD",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
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
"Name" 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
name, Key
"Password" 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
password,
Key
"VpcSettings" Key -> VpcSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= VpcSettingsProperty
vpcSettings]
([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
"CreateAlias" (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)
createAlias,
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
"Edition" (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)
edition,
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
"EnableSso" (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)
enableSso,
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
"ShortName" (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)
shortName]))}
instance JSON.ToJSON MicrosoftAD where
toJSON :: MicrosoftAD -> Value
toJSON MicrosoftAD {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: MicrosoftAD -> ()
createAlias :: MicrosoftAD -> Maybe (Value Bool)
edition :: MicrosoftAD -> Maybe (Value Text)
enableSso :: MicrosoftAD -> Maybe (Value Bool)
name :: MicrosoftAD -> Value Text
password :: MicrosoftAD -> Value Text
shortName :: MicrosoftAD -> Maybe (Value Text)
vpcSettings :: MicrosoftAD -> VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
= [(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
"Name" 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
name, Key
"Password" 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
password,
Key
"VpcSettings" Key -> VpcSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= VpcSettingsProperty
vpcSettings]
([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
"CreateAlias" (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)
createAlias,
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
"Edition" (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)
edition,
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
"EnableSso" (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)
enableSso,
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
"ShortName" (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)
shortName])))
instance Property "CreateAlias" MicrosoftAD where
type PropertyType "CreateAlias" MicrosoftAD = Value Prelude.Bool
set :: PropertyType "CreateAlias" MicrosoftAD
-> MicrosoftAD -> MicrosoftAD
set PropertyType "CreateAlias" MicrosoftAD
newValue MicrosoftAD {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: MicrosoftAD -> ()
createAlias :: MicrosoftAD -> Maybe (Value Bool)
edition :: MicrosoftAD -> Maybe (Value Text)
enableSso :: MicrosoftAD -> Maybe (Value Bool)
name :: MicrosoftAD -> Value Text
password :: MicrosoftAD -> Value Text
shortName :: MicrosoftAD -> Maybe (Value Text)
vpcSettings :: MicrosoftAD -> VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
= MicrosoftAD {createAlias :: Maybe (Value Bool)
createAlias = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CreateAlias" MicrosoftAD
Value Bool
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: ()
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
haddock_workaround_ :: ()
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
instance Property "Edition" MicrosoftAD where
type PropertyType "Edition" MicrosoftAD = Value Prelude.Text
set :: PropertyType "Edition" MicrosoftAD -> MicrosoftAD -> MicrosoftAD
set PropertyType "Edition" MicrosoftAD
newValue MicrosoftAD {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: MicrosoftAD -> ()
createAlias :: MicrosoftAD -> Maybe (Value Bool)
edition :: MicrosoftAD -> Maybe (Value Text)
enableSso :: MicrosoftAD -> Maybe (Value Bool)
name :: MicrosoftAD -> Value Text
password :: MicrosoftAD -> Value Text
shortName :: MicrosoftAD -> Maybe (Value Text)
vpcSettings :: MicrosoftAD -> VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
= MicrosoftAD {edition :: Maybe (Value Text)
edition = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Edition" MicrosoftAD
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
instance Property "EnableSso" MicrosoftAD where
type PropertyType "EnableSso" MicrosoftAD = Value Prelude.Bool
set :: PropertyType "EnableSso" MicrosoftAD -> MicrosoftAD -> MicrosoftAD
set PropertyType "EnableSso" MicrosoftAD
newValue MicrosoftAD {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: MicrosoftAD -> ()
createAlias :: MicrosoftAD -> Maybe (Value Bool)
edition :: MicrosoftAD -> Maybe (Value Text)
enableSso :: MicrosoftAD -> Maybe (Value Bool)
name :: MicrosoftAD -> Value Text
password :: MicrosoftAD -> Value Text
shortName :: MicrosoftAD -> Maybe (Value Text)
vpcSettings :: MicrosoftAD -> VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
= MicrosoftAD {enableSso :: Maybe (Value Bool)
enableSso = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EnableSso" MicrosoftAD
Value Bool
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
instance Property "Name" MicrosoftAD where
type PropertyType "Name" MicrosoftAD = Value Prelude.Text
set :: PropertyType "Name" MicrosoftAD -> MicrosoftAD -> MicrosoftAD
set PropertyType "Name" MicrosoftAD
newValue MicrosoftAD {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: MicrosoftAD -> ()
createAlias :: MicrosoftAD -> Maybe (Value Bool)
edition :: MicrosoftAD -> Maybe (Value Text)
enableSso :: MicrosoftAD -> Maybe (Value Bool)
name :: MicrosoftAD -> Value Text
password :: MicrosoftAD -> Value Text
shortName :: MicrosoftAD -> Maybe (Value Text)
vpcSettings :: MicrosoftAD -> VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..} = MicrosoftAD {name :: Value Text
name = PropertyType "Name" MicrosoftAD
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
instance Property "Password" MicrosoftAD where
type PropertyType "Password" MicrosoftAD = Value Prelude.Text
set :: PropertyType "Password" MicrosoftAD -> MicrosoftAD -> MicrosoftAD
set PropertyType "Password" MicrosoftAD
newValue MicrosoftAD {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: MicrosoftAD -> ()
createAlias :: MicrosoftAD -> Maybe (Value Bool)
edition :: MicrosoftAD -> Maybe (Value Text)
enableSso :: MicrosoftAD -> Maybe (Value Bool)
name :: MicrosoftAD -> Value Text
password :: MicrosoftAD -> Value Text
shortName :: MicrosoftAD -> Maybe (Value Text)
vpcSettings :: MicrosoftAD -> VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
= MicrosoftAD {password :: Value Text
password = PropertyType "Password" MicrosoftAD
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
instance Property "ShortName" MicrosoftAD where
type PropertyType "ShortName" MicrosoftAD = Value Prelude.Text
set :: PropertyType "ShortName" MicrosoftAD -> MicrosoftAD -> MicrosoftAD
set PropertyType "ShortName" MicrosoftAD
newValue MicrosoftAD {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: MicrosoftAD -> ()
createAlias :: MicrosoftAD -> Maybe (Value Bool)
edition :: MicrosoftAD -> Maybe (Value Text)
enableSso :: MicrosoftAD -> Maybe (Value Bool)
name :: MicrosoftAD -> Value Text
password :: MicrosoftAD -> Value Text
shortName :: MicrosoftAD -> Maybe (Value Text)
vpcSettings :: MicrosoftAD -> VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
= MicrosoftAD {shortName :: Maybe (Value Text)
shortName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ShortName" MicrosoftAD
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
vpcSettings :: VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
vpcSettings :: VpcSettingsProperty
..}
instance Property "VpcSettings" MicrosoftAD where
type PropertyType "VpcSettings" MicrosoftAD = VpcSettingsProperty
set :: PropertyType "VpcSettings" MicrosoftAD
-> MicrosoftAD -> MicrosoftAD
set PropertyType "VpcSettings" MicrosoftAD
newValue MicrosoftAD {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
VpcSettingsProperty
haddock_workaround_ :: MicrosoftAD -> ()
createAlias :: MicrosoftAD -> Maybe (Value Bool)
edition :: MicrosoftAD -> Maybe (Value Text)
enableSso :: MicrosoftAD -> Maybe (Value Bool)
name :: MicrosoftAD -> Value Text
password :: MicrosoftAD -> Value Text
shortName :: MicrosoftAD -> Maybe (Value Text)
vpcSettings :: MicrosoftAD -> VpcSettingsProperty
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
vpcSettings :: VpcSettingsProperty
..}
= MicrosoftAD {vpcSettings :: VpcSettingsProperty
vpcSettings = PropertyType "VpcSettings" MicrosoftAD
VpcSettingsProperty
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
haddock_workaround_ :: ()
createAlias :: Maybe (Value Bool)
edition :: Maybe (Value Text)
enableSso :: Maybe (Value Bool)
name :: Value Text
password :: Value Text
shortName :: Maybe (Value Text)
..}