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