module Stratosphere.IAM.SAMLProvider.SAMLPrivateKeyProperty (
        SAMLPrivateKeyProperty(..), mkSAMLPrivateKeyProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SAMLPrivateKeyProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-iam-samlprovider-samlprivatekey.html>
    SAMLPrivateKeyProperty {SAMLPrivateKeyProperty -> ()
haddock_workaround_ :: (),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-iam-samlprovider-samlprivatekey.html#cfn-iam-samlprovider-samlprivatekey-keyid>
                            SAMLPrivateKeyProperty -> Value Text
keyId :: (Value Prelude.Text),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-iam-samlprovider-samlprivatekey.html#cfn-iam-samlprovider-samlprivatekey-timestamp>
                            SAMLPrivateKeyProperty -> Value Text
timestamp :: (Value Prelude.Text)}
  deriving stock (SAMLPrivateKeyProperty -> SAMLPrivateKeyProperty -> Bool
(SAMLPrivateKeyProperty -> SAMLPrivateKeyProperty -> Bool)
-> (SAMLPrivateKeyProperty -> SAMLPrivateKeyProperty -> Bool)
-> Eq SAMLPrivateKeyProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SAMLPrivateKeyProperty -> SAMLPrivateKeyProperty -> Bool
== :: SAMLPrivateKeyProperty -> SAMLPrivateKeyProperty -> Bool
$c/= :: SAMLPrivateKeyProperty -> SAMLPrivateKeyProperty -> Bool
/= :: SAMLPrivateKeyProperty -> SAMLPrivateKeyProperty -> Bool
Prelude.Eq, Int -> SAMLPrivateKeyProperty -> ShowS
[SAMLPrivateKeyProperty] -> ShowS
SAMLPrivateKeyProperty -> String
(Int -> SAMLPrivateKeyProperty -> ShowS)
-> (SAMLPrivateKeyProperty -> String)
-> ([SAMLPrivateKeyProperty] -> ShowS)
-> Show SAMLPrivateKeyProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SAMLPrivateKeyProperty -> ShowS
showsPrec :: Int -> SAMLPrivateKeyProperty -> ShowS
$cshow :: SAMLPrivateKeyProperty -> String
show :: SAMLPrivateKeyProperty -> String
$cshowList :: [SAMLPrivateKeyProperty] -> ShowS
showList :: [SAMLPrivateKeyProperty] -> ShowS
Prelude.Show)
mkSAMLPrivateKeyProperty ::
  Value Prelude.Text -> Value Prelude.Text -> SAMLPrivateKeyProperty
mkSAMLPrivateKeyProperty :: Value Text -> Value Text -> SAMLPrivateKeyProperty
mkSAMLPrivateKeyProperty Value Text
keyId Value Text
timestamp
  = SAMLPrivateKeyProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), keyId :: Value Text
keyId = Value Text
keyId, timestamp :: Value Text
timestamp = Value Text
timestamp}
instance ToResourceProperties SAMLPrivateKeyProperty where
  toResourceProperties :: SAMLPrivateKeyProperty -> ResourceProperties
toResourceProperties SAMLPrivateKeyProperty {()
Value Text
haddock_workaround_ :: SAMLPrivateKeyProperty -> ()
keyId :: SAMLPrivateKeyProperty -> Value Text
timestamp :: SAMLPrivateKeyProperty -> Value Text
haddock_workaround_ :: ()
keyId :: Value Text
timestamp :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::IAM::SAMLProvider.SAMLPrivateKey",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"KeyId" 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
keyId,
                       Key
"Timestamp" 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
timestamp]}
instance JSON.ToJSON SAMLPrivateKeyProperty where
  toJSON :: SAMLPrivateKeyProperty -> Value
toJSON SAMLPrivateKeyProperty {()
Value Text
haddock_workaround_ :: SAMLPrivateKeyProperty -> ()
keyId :: SAMLPrivateKeyProperty -> Value Text
timestamp :: SAMLPrivateKeyProperty -> Value Text
haddock_workaround_ :: ()
keyId :: Value Text
timestamp :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"KeyId" 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
keyId, Key
"Timestamp" 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
timestamp]
instance Property "KeyId" SAMLPrivateKeyProperty where
  type PropertyType "KeyId" SAMLPrivateKeyProperty = Value Prelude.Text
  set :: PropertyType "KeyId" SAMLPrivateKeyProperty
-> SAMLPrivateKeyProperty -> SAMLPrivateKeyProperty
set PropertyType "KeyId" SAMLPrivateKeyProperty
newValue SAMLPrivateKeyProperty {()
Value Text
haddock_workaround_ :: SAMLPrivateKeyProperty -> ()
keyId :: SAMLPrivateKeyProperty -> Value Text
timestamp :: SAMLPrivateKeyProperty -> Value Text
haddock_workaround_ :: ()
keyId :: Value Text
timestamp :: Value Text
..}
    = SAMLPrivateKeyProperty {keyId :: Value Text
keyId = PropertyType "KeyId" SAMLPrivateKeyProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
timestamp :: Value Text
haddock_workaround_ :: ()
timestamp :: Value Text
..}
instance Property "Timestamp" SAMLPrivateKeyProperty where
  type PropertyType "Timestamp" SAMLPrivateKeyProperty = Value Prelude.Text
  set :: PropertyType "Timestamp" SAMLPrivateKeyProperty
-> SAMLPrivateKeyProperty -> SAMLPrivateKeyProperty
set PropertyType "Timestamp" SAMLPrivateKeyProperty
newValue SAMLPrivateKeyProperty {()
Value Text
haddock_workaround_ :: SAMLPrivateKeyProperty -> ()
keyId :: SAMLPrivateKeyProperty -> Value Text
timestamp :: SAMLPrivateKeyProperty -> Value Text
haddock_workaround_ :: ()
keyId :: Value Text
timestamp :: Value Text
..}
    = SAMLPrivateKeyProperty {timestamp :: Value Text
timestamp = PropertyType "Timestamp" SAMLPrivateKeyProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
keyId :: Value Text
haddock_workaround_ :: ()
keyId :: Value Text
..}