module Stratosphere.AppMesh.VirtualNode.ListenerTlsValidationContextTrustProperty (
        module Exports, ListenerTlsValidationContextTrustProperty(..),
        mkListenerTlsValidationContextTrustProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AppMesh.VirtualNode.TlsValidationContextFileTrustProperty as Exports
import {-# SOURCE #-} Stratosphere.AppMesh.VirtualNode.TlsValidationContextSdsTrustProperty as Exports
import Stratosphere.ResourceProperties
data ListenerTlsValidationContextTrustProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-appmesh-virtualnode-listenertlsvalidationcontexttrust.html>
    ListenerTlsValidationContextTrustProperty {ListenerTlsValidationContextTrustProperty -> ()
haddock_workaround_ :: (),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-appmesh-virtualnode-listenertlsvalidationcontexttrust.html#cfn-appmesh-virtualnode-listenertlsvalidationcontexttrust-file>
                                               ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextFileTrustProperty
file :: (Prelude.Maybe TlsValidationContextFileTrustProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-appmesh-virtualnode-listenertlsvalidationcontexttrust.html#cfn-appmesh-virtualnode-listenertlsvalidationcontexttrust-sds>
                                               ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextSdsTrustProperty
sDS :: (Prelude.Maybe TlsValidationContextSdsTrustProperty)}
  deriving stock (ListenerTlsValidationContextTrustProperty
-> ListenerTlsValidationContextTrustProperty -> Bool
(ListenerTlsValidationContextTrustProperty
 -> ListenerTlsValidationContextTrustProperty -> Bool)
-> (ListenerTlsValidationContextTrustProperty
    -> ListenerTlsValidationContextTrustProperty -> Bool)
-> Eq ListenerTlsValidationContextTrustProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListenerTlsValidationContextTrustProperty
-> ListenerTlsValidationContextTrustProperty -> Bool
== :: ListenerTlsValidationContextTrustProperty
-> ListenerTlsValidationContextTrustProperty -> Bool
$c/= :: ListenerTlsValidationContextTrustProperty
-> ListenerTlsValidationContextTrustProperty -> Bool
/= :: ListenerTlsValidationContextTrustProperty
-> ListenerTlsValidationContextTrustProperty -> Bool
Prelude.Eq, Int -> ListenerTlsValidationContextTrustProperty -> ShowS
[ListenerTlsValidationContextTrustProperty] -> ShowS
ListenerTlsValidationContextTrustProperty -> String
(Int -> ListenerTlsValidationContextTrustProperty -> ShowS)
-> (ListenerTlsValidationContextTrustProperty -> String)
-> ([ListenerTlsValidationContextTrustProperty] -> ShowS)
-> Show ListenerTlsValidationContextTrustProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListenerTlsValidationContextTrustProperty -> ShowS
showsPrec :: Int -> ListenerTlsValidationContextTrustProperty -> ShowS
$cshow :: ListenerTlsValidationContextTrustProperty -> String
show :: ListenerTlsValidationContextTrustProperty -> String
$cshowList :: [ListenerTlsValidationContextTrustProperty] -> ShowS
showList :: [ListenerTlsValidationContextTrustProperty] -> ShowS
Prelude.Show)
mkListenerTlsValidationContextTrustProperty ::
  ListenerTlsValidationContextTrustProperty
mkListenerTlsValidationContextTrustProperty :: ListenerTlsValidationContextTrustProperty
mkListenerTlsValidationContextTrustProperty
  = ListenerTlsValidationContextTrustProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), file :: Maybe TlsValidationContextFileTrustProperty
file = Maybe TlsValidationContextFileTrustProperty
forall a. Maybe a
Prelude.Nothing,
       sDS :: Maybe TlsValidationContextSdsTrustProperty
sDS = Maybe TlsValidationContextSdsTrustProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ListenerTlsValidationContextTrustProperty where
  toResourceProperties :: ListenerTlsValidationContextTrustProperty -> ResourceProperties
toResourceProperties ListenerTlsValidationContextTrustProperty {Maybe TlsValidationContextFileTrustProperty
Maybe TlsValidationContextSdsTrustProperty
()
haddock_workaround_ :: ListenerTlsValidationContextTrustProperty -> ()
file :: ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextFileTrustProperty
sDS :: ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextSdsTrustProperty
haddock_workaround_ :: ()
file :: Maybe TlsValidationContextFileTrustProperty
sDS :: Maybe TlsValidationContextSdsTrustProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::AppMesh::VirtualNode.ListenerTlsValidationContextTrust",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                           [Key -> TlsValidationContextFileTrustProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"File" (TlsValidationContextFileTrustProperty -> (Key, Value))
-> Maybe TlsValidationContextFileTrustProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TlsValidationContextFileTrustProperty
file,
                            Key -> TlsValidationContextSdsTrustProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SDS" (TlsValidationContextSdsTrustProperty -> (Key, Value))
-> Maybe TlsValidationContextSdsTrustProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TlsValidationContextSdsTrustProperty
sDS])}
instance JSON.ToJSON ListenerTlsValidationContextTrustProperty where
  toJSON :: ListenerTlsValidationContextTrustProperty -> Value
toJSON ListenerTlsValidationContextTrustProperty {Maybe TlsValidationContextFileTrustProperty
Maybe TlsValidationContextSdsTrustProperty
()
haddock_workaround_ :: ListenerTlsValidationContextTrustProperty -> ()
file :: ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextFileTrustProperty
sDS :: ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextSdsTrustProperty
haddock_workaround_ :: ()
file :: Maybe TlsValidationContextFileTrustProperty
sDS :: Maybe TlsValidationContextSdsTrustProperty
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
              [Key -> TlsValidationContextFileTrustProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"File" (TlsValidationContextFileTrustProperty -> (Key, Value))
-> Maybe TlsValidationContextFileTrustProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TlsValidationContextFileTrustProperty
file,
               Key -> TlsValidationContextSdsTrustProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SDS" (TlsValidationContextSdsTrustProperty -> (Key, Value))
-> Maybe TlsValidationContextSdsTrustProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TlsValidationContextSdsTrustProperty
sDS]))
instance Property "File" ListenerTlsValidationContextTrustProperty where
  type PropertyType "File" ListenerTlsValidationContextTrustProperty = TlsValidationContextFileTrustProperty
  set :: PropertyType "File" ListenerTlsValidationContextTrustProperty
-> ListenerTlsValidationContextTrustProperty
-> ListenerTlsValidationContextTrustProperty
set PropertyType "File" ListenerTlsValidationContextTrustProperty
newValue ListenerTlsValidationContextTrustProperty {Maybe TlsValidationContextFileTrustProperty
Maybe TlsValidationContextSdsTrustProperty
()
haddock_workaround_ :: ListenerTlsValidationContextTrustProperty -> ()
file :: ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextFileTrustProperty
sDS :: ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextSdsTrustProperty
haddock_workaround_ :: ()
file :: Maybe TlsValidationContextFileTrustProperty
sDS :: Maybe TlsValidationContextSdsTrustProperty
..}
    = ListenerTlsValidationContextTrustProperty
        {file :: Maybe TlsValidationContextFileTrustProperty
file = TlsValidationContextFileTrustProperty
-> Maybe TlsValidationContextFileTrustProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "File" ListenerTlsValidationContextTrustProperty
TlsValidationContextFileTrustProperty
newValue, Maybe TlsValidationContextSdsTrustProperty
()
haddock_workaround_ :: ()
sDS :: Maybe TlsValidationContextSdsTrustProperty
haddock_workaround_ :: ()
sDS :: Maybe TlsValidationContextSdsTrustProperty
..}
instance Property "SDS" ListenerTlsValidationContextTrustProperty where
  type PropertyType "SDS" ListenerTlsValidationContextTrustProperty = TlsValidationContextSdsTrustProperty
  set :: PropertyType "SDS" ListenerTlsValidationContextTrustProperty
-> ListenerTlsValidationContextTrustProperty
-> ListenerTlsValidationContextTrustProperty
set PropertyType "SDS" ListenerTlsValidationContextTrustProperty
newValue ListenerTlsValidationContextTrustProperty {Maybe TlsValidationContextFileTrustProperty
Maybe TlsValidationContextSdsTrustProperty
()
haddock_workaround_ :: ListenerTlsValidationContextTrustProperty -> ()
file :: ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextFileTrustProperty
sDS :: ListenerTlsValidationContextTrustProperty
-> Maybe TlsValidationContextSdsTrustProperty
haddock_workaround_ :: ()
file :: Maybe TlsValidationContextFileTrustProperty
sDS :: Maybe TlsValidationContextSdsTrustProperty
..}
    = ListenerTlsValidationContextTrustProperty
        {sDS :: Maybe TlsValidationContextSdsTrustProperty
sDS = TlsValidationContextSdsTrustProperty
-> Maybe TlsValidationContextSdsTrustProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SDS" ListenerTlsValidationContextTrustProperty
TlsValidationContextSdsTrustProperty
newValue, Maybe TlsValidationContextFileTrustProperty
()
haddock_workaround_ :: ()
file :: Maybe TlsValidationContextFileTrustProperty
haddock_workaround_ :: ()
file :: Maybe TlsValidationContextFileTrustProperty
..}