module Stratosphere.Deadline.Queue.WindowsUserProperty (
WindowsUserProperty(..), mkWindowsUserProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data WindowsUserProperty
=
WindowsUserProperty {WindowsUserProperty -> ()
haddock_workaround_ :: (),
WindowsUserProperty -> Value Text
passwordArn :: (Value Prelude.Text),
WindowsUserProperty -> Value Text
user :: (Value Prelude.Text)}
deriving stock (WindowsUserProperty -> WindowsUserProperty -> Bool
(WindowsUserProperty -> WindowsUserProperty -> Bool)
-> (WindowsUserProperty -> WindowsUserProperty -> Bool)
-> Eq WindowsUserProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WindowsUserProperty -> WindowsUserProperty -> Bool
== :: WindowsUserProperty -> WindowsUserProperty -> Bool
$c/= :: WindowsUserProperty -> WindowsUserProperty -> Bool
/= :: WindowsUserProperty -> WindowsUserProperty -> Bool
Prelude.Eq, Int -> WindowsUserProperty -> ShowS
[WindowsUserProperty] -> ShowS
WindowsUserProperty -> String
(Int -> WindowsUserProperty -> ShowS)
-> (WindowsUserProperty -> String)
-> ([WindowsUserProperty] -> ShowS)
-> Show WindowsUserProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WindowsUserProperty -> ShowS
showsPrec :: Int -> WindowsUserProperty -> ShowS
$cshow :: WindowsUserProperty -> String
show :: WindowsUserProperty -> String
$cshowList :: [WindowsUserProperty] -> ShowS
showList :: [WindowsUserProperty] -> ShowS
Prelude.Show)
mkWindowsUserProperty ::
Value Prelude.Text -> Value Prelude.Text -> WindowsUserProperty
mkWindowsUserProperty :: Value Text -> Value Text -> WindowsUserProperty
mkWindowsUserProperty Value Text
passwordArn Value Text
user
= WindowsUserProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), passwordArn :: Value Text
passwordArn = Value Text
passwordArn, user :: Value Text
user = Value Text
user}
instance ToResourceProperties WindowsUserProperty where
toResourceProperties :: WindowsUserProperty -> ResourceProperties
toResourceProperties WindowsUserProperty {()
Value Text
haddock_workaround_ :: WindowsUserProperty -> ()
passwordArn :: WindowsUserProperty -> Value Text
user :: WindowsUserProperty -> Value Text
haddock_workaround_ :: ()
passwordArn :: Value Text
user :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Deadline::Queue.WindowsUser",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"PasswordArn" 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
passwordArn,
Key
"User" 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
user]}
instance JSON.ToJSON WindowsUserProperty where
toJSON :: WindowsUserProperty -> Value
toJSON WindowsUserProperty {()
Value Text
haddock_workaround_ :: WindowsUserProperty -> ()
passwordArn :: WindowsUserProperty -> Value Text
user :: WindowsUserProperty -> Value Text
haddock_workaround_ :: ()
passwordArn :: Value Text
user :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"PasswordArn" 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
passwordArn, Key
"User" 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
user]
instance Property "PasswordArn" WindowsUserProperty where
type PropertyType "PasswordArn" WindowsUserProperty = Value Prelude.Text
set :: PropertyType "PasswordArn" WindowsUserProperty
-> WindowsUserProperty -> WindowsUserProperty
set PropertyType "PasswordArn" WindowsUserProperty
newValue WindowsUserProperty {()
Value Text
haddock_workaround_ :: WindowsUserProperty -> ()
passwordArn :: WindowsUserProperty -> Value Text
user :: WindowsUserProperty -> Value Text
haddock_workaround_ :: ()
passwordArn :: Value Text
user :: Value Text
..}
= WindowsUserProperty {passwordArn :: Value Text
passwordArn = PropertyType "PasswordArn" WindowsUserProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
user :: Value Text
haddock_workaround_ :: ()
user :: Value Text
..}
instance Property "User" WindowsUserProperty where
type PropertyType "User" WindowsUserProperty = Value Prelude.Text
set :: PropertyType "User" WindowsUserProperty
-> WindowsUserProperty -> WindowsUserProperty
set PropertyType "User" WindowsUserProperty
newValue WindowsUserProperty {()
Value Text
haddock_workaround_ :: WindowsUserProperty -> ()
passwordArn :: WindowsUserProperty -> Value Text
user :: WindowsUserProperty -> Value Text
haddock_workaround_ :: ()
passwordArn :: Value Text
user :: Value Text
..}
= WindowsUserProperty {user :: Value Text
user = PropertyType "User" WindowsUserProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
passwordArn :: Value Text
haddock_workaround_ :: ()
passwordArn :: Value Text
..}