module Stratosphere.AppMesh.VirtualGateway.VirtualGatewayListenerTlsAcmCertificateProperty (
        VirtualGatewayListenerTlsAcmCertificateProperty(..),
        mkVirtualGatewayListenerTlsAcmCertificateProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data VirtualGatewayListenerTlsAcmCertificateProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-appmesh-virtualgateway-virtualgatewaylistenertlsacmcertificate.html>
    VirtualGatewayListenerTlsAcmCertificateProperty {VirtualGatewayListenerTlsAcmCertificateProperty -> ()
haddock_workaround_ :: (),
                                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-appmesh-virtualgateway-virtualgatewaylistenertlsacmcertificate.html#cfn-appmesh-virtualgateway-virtualgatewaylistenertlsacmcertificate-certificatearn>
                                                     VirtualGatewayListenerTlsAcmCertificateProperty -> Value Text
certificateArn :: (Value Prelude.Text)}
  deriving stock (VirtualGatewayListenerTlsAcmCertificateProperty
-> VirtualGatewayListenerTlsAcmCertificateProperty -> Bool
(VirtualGatewayListenerTlsAcmCertificateProperty
 -> VirtualGatewayListenerTlsAcmCertificateProperty -> Bool)
-> (VirtualGatewayListenerTlsAcmCertificateProperty
    -> VirtualGatewayListenerTlsAcmCertificateProperty -> Bool)
-> Eq VirtualGatewayListenerTlsAcmCertificateProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VirtualGatewayListenerTlsAcmCertificateProperty
-> VirtualGatewayListenerTlsAcmCertificateProperty -> Bool
== :: VirtualGatewayListenerTlsAcmCertificateProperty
-> VirtualGatewayListenerTlsAcmCertificateProperty -> Bool
$c/= :: VirtualGatewayListenerTlsAcmCertificateProperty
-> VirtualGatewayListenerTlsAcmCertificateProperty -> Bool
/= :: VirtualGatewayListenerTlsAcmCertificateProperty
-> VirtualGatewayListenerTlsAcmCertificateProperty -> Bool
Prelude.Eq, Int -> VirtualGatewayListenerTlsAcmCertificateProperty -> ShowS
[VirtualGatewayListenerTlsAcmCertificateProperty] -> ShowS
VirtualGatewayListenerTlsAcmCertificateProperty -> String
(Int -> VirtualGatewayListenerTlsAcmCertificateProperty -> ShowS)
-> (VirtualGatewayListenerTlsAcmCertificateProperty -> String)
-> ([VirtualGatewayListenerTlsAcmCertificateProperty] -> ShowS)
-> Show VirtualGatewayListenerTlsAcmCertificateProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VirtualGatewayListenerTlsAcmCertificateProperty -> ShowS
showsPrec :: Int -> VirtualGatewayListenerTlsAcmCertificateProperty -> ShowS
$cshow :: VirtualGatewayListenerTlsAcmCertificateProperty -> String
show :: VirtualGatewayListenerTlsAcmCertificateProperty -> String
$cshowList :: [VirtualGatewayListenerTlsAcmCertificateProperty] -> ShowS
showList :: [VirtualGatewayListenerTlsAcmCertificateProperty] -> ShowS
Prelude.Show)
mkVirtualGatewayListenerTlsAcmCertificateProperty ::
  Value Prelude.Text
  -> VirtualGatewayListenerTlsAcmCertificateProperty
mkVirtualGatewayListenerTlsAcmCertificateProperty :: Value Text -> VirtualGatewayListenerTlsAcmCertificateProperty
mkVirtualGatewayListenerTlsAcmCertificateProperty Value Text
certificateArn
  = VirtualGatewayListenerTlsAcmCertificateProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), certificateArn :: Value Text
certificateArn = Value Text
certificateArn}
instance ToResourceProperties VirtualGatewayListenerTlsAcmCertificateProperty where
  toResourceProperties :: VirtualGatewayListenerTlsAcmCertificateProperty
-> ResourceProperties
toResourceProperties
    VirtualGatewayListenerTlsAcmCertificateProperty {()
Value Text
haddock_workaround_ :: VirtualGatewayListenerTlsAcmCertificateProperty -> ()
certificateArn :: VirtualGatewayListenerTlsAcmCertificateProperty -> Value Text
haddock_workaround_ :: ()
certificateArn :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::AppMesh::VirtualGateway.VirtualGatewayListenerTlsAcmCertificate",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"CertificateArn" 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
certificateArn]}
instance JSON.ToJSON VirtualGatewayListenerTlsAcmCertificateProperty where
  toJSON :: VirtualGatewayListenerTlsAcmCertificateProperty -> Value
toJSON VirtualGatewayListenerTlsAcmCertificateProperty {()
Value Text
haddock_workaround_ :: VirtualGatewayListenerTlsAcmCertificateProperty -> ()
certificateArn :: VirtualGatewayListenerTlsAcmCertificateProperty -> Value Text
haddock_workaround_ :: ()
certificateArn :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"CertificateArn" 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
certificateArn]
instance Property "CertificateArn" VirtualGatewayListenerTlsAcmCertificateProperty where
  type PropertyType "CertificateArn" VirtualGatewayListenerTlsAcmCertificateProperty = Value Prelude.Text
  set :: PropertyType
  "CertificateArn" VirtualGatewayListenerTlsAcmCertificateProperty
-> VirtualGatewayListenerTlsAcmCertificateProperty
-> VirtualGatewayListenerTlsAcmCertificateProperty
set PropertyType
  "CertificateArn" VirtualGatewayListenerTlsAcmCertificateProperty
newValue VirtualGatewayListenerTlsAcmCertificateProperty {()
Value Text
haddock_workaround_ :: VirtualGatewayListenerTlsAcmCertificateProperty -> ()
certificateArn :: VirtualGatewayListenerTlsAcmCertificateProperty -> Value Text
haddock_workaround_ :: ()
certificateArn :: Value Text
..}
    = VirtualGatewayListenerTlsAcmCertificateProperty
        {certificateArn :: Value Text
certificateArn = PropertyType
  "CertificateArn" VirtualGatewayListenerTlsAcmCertificateProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}