module Stratosphere.AppMesh.VirtualService (
        module Exports, VirtualService(..), mkVirtualService
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AppMesh.VirtualService.VirtualServiceSpecProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data VirtualService
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-appmesh-virtualservice.html>
    VirtualService {VirtualService -> ()
haddock_workaround_ :: (),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-appmesh-virtualservice.html#cfn-appmesh-virtualservice-meshname>
                    VirtualService -> Value Text
meshName :: (Value Prelude.Text),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-appmesh-virtualservice.html#cfn-appmesh-virtualservice-meshowner>
                    VirtualService -> Maybe (Value Text)
meshOwner :: (Prelude.Maybe (Value Prelude.Text)),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-appmesh-virtualservice.html#cfn-appmesh-virtualservice-spec>
                    VirtualService -> VirtualServiceSpecProperty
spec :: VirtualServiceSpecProperty,
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-appmesh-virtualservice.html#cfn-appmesh-virtualservice-tags>
                    VirtualService -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag]),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-appmesh-virtualservice.html#cfn-appmesh-virtualservice-virtualservicename>
                    VirtualService -> Value Text
virtualServiceName :: (Value Prelude.Text)}
  deriving stock (VirtualService -> VirtualService -> Bool
(VirtualService -> VirtualService -> Bool)
-> (VirtualService -> VirtualService -> Bool) -> Eq VirtualService
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VirtualService -> VirtualService -> Bool
== :: VirtualService -> VirtualService -> Bool
$c/= :: VirtualService -> VirtualService -> Bool
/= :: VirtualService -> VirtualService -> Bool
Prelude.Eq, Int -> VirtualService -> ShowS
[VirtualService] -> ShowS
VirtualService -> String
(Int -> VirtualService -> ShowS)
-> (VirtualService -> String)
-> ([VirtualService] -> ShowS)
-> Show VirtualService
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VirtualService -> ShowS
showsPrec :: Int -> VirtualService -> ShowS
$cshow :: VirtualService -> String
show :: VirtualService -> String
$cshowList :: [VirtualService] -> ShowS
showList :: [VirtualService] -> ShowS
Prelude.Show)
mkVirtualService ::
  Value Prelude.Text
  -> VirtualServiceSpecProperty
     -> Value Prelude.Text -> VirtualService
mkVirtualService :: Value Text
-> VirtualServiceSpecProperty -> Value Text -> VirtualService
mkVirtualService Value Text
meshName VirtualServiceSpecProperty
spec Value Text
virtualServiceName
  = VirtualService
      {haddock_workaround_ :: ()
haddock_workaround_ = (), meshName :: Value Text
meshName = Value Text
meshName, spec :: VirtualServiceSpecProperty
spec = VirtualServiceSpecProperty
spec,
       virtualServiceName :: Value Text
virtualServiceName = Value Text
virtualServiceName,
       meshOwner :: Maybe (Value Text)
meshOwner = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties VirtualService where
  toResourceProperties :: VirtualService -> ResourceProperties
toResourceProperties VirtualService {Maybe [Tag]
Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: VirtualService -> ()
meshName :: VirtualService -> Value Text
meshOwner :: VirtualService -> Maybe (Value Text)
spec :: VirtualService -> VirtualServiceSpecProperty
tags :: VirtualService -> Maybe [Tag]
virtualServiceName :: VirtualService -> Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::AppMesh::VirtualService",
         supportsTags :: Bool
supportsTags = Bool
Prelude.True,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
                           [Key
"MeshName" 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
meshName, Key
"Spec" Key -> VirtualServiceSpecProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= VirtualServiceSpecProperty
spec,
                            Key
"VirtualServiceName" 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
virtualServiceName]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [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..=) Key
"MeshOwner" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
meshOwner,
                               Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags]))}
instance JSON.ToJSON VirtualService where
  toJSON :: VirtualService -> Value
toJSON VirtualService {Maybe [Tag]
Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: VirtualService -> ()
meshName :: VirtualService -> Value Text
meshOwner :: VirtualService -> Maybe (Value Text)
spec :: VirtualService -> VirtualServiceSpecProperty
tags :: VirtualService -> Maybe [Tag]
virtualServiceName :: VirtualService -> Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
              [Key
"MeshName" 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
meshName, Key
"Spec" Key -> VirtualServiceSpecProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= VirtualServiceSpecProperty
spec,
               Key
"VirtualServiceName" 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
virtualServiceName]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [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..=) Key
"MeshOwner" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
meshOwner,
                  Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags])))
instance Property "MeshName" VirtualService where
  type PropertyType "MeshName" VirtualService = Value Prelude.Text
  set :: PropertyType "MeshName" VirtualService
-> VirtualService -> VirtualService
set PropertyType "MeshName" VirtualService
newValue VirtualService {Maybe [Tag]
Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: VirtualService -> ()
meshName :: VirtualService -> Value Text
meshOwner :: VirtualService -> Maybe (Value Text)
spec :: VirtualService -> VirtualServiceSpecProperty
tags :: VirtualService -> Maybe [Tag]
virtualServiceName :: VirtualService -> Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
    = VirtualService {meshName :: Value Text
meshName = PropertyType "MeshName" VirtualService
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: ()
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
haddock_workaround_ :: ()
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
instance Property "MeshOwner" VirtualService where
  type PropertyType "MeshOwner" VirtualService = Value Prelude.Text
  set :: PropertyType "MeshOwner" VirtualService
-> VirtualService -> VirtualService
set PropertyType "MeshOwner" VirtualService
newValue VirtualService {Maybe [Tag]
Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: VirtualService -> ()
meshName :: VirtualService -> Value Text
meshOwner :: VirtualService -> Maybe (Value Text)
spec :: VirtualService -> VirtualServiceSpecProperty
tags :: VirtualService -> Maybe [Tag]
virtualServiceName :: VirtualService -> Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
    = VirtualService {meshOwner :: Maybe (Value Text)
meshOwner = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MeshOwner" VirtualService
Value Text
newValue, Maybe [Tag]
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: ()
meshName :: Value Text
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
haddock_workaround_ :: ()
meshName :: Value Text
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
instance Property "Spec" VirtualService where
  type PropertyType "Spec" VirtualService = VirtualServiceSpecProperty
  set :: PropertyType "Spec" VirtualService
-> VirtualService -> VirtualService
set PropertyType "Spec" VirtualService
newValue VirtualService {Maybe [Tag]
Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: VirtualService -> ()
meshName :: VirtualService -> Value Text
meshOwner :: VirtualService -> Maybe (Value Text)
spec :: VirtualService -> VirtualServiceSpecProperty
tags :: VirtualService -> Maybe [Tag]
virtualServiceName :: VirtualService -> Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
    = VirtualService {spec :: VirtualServiceSpecProperty
spec = PropertyType "Spec" VirtualService
VirtualServiceSpecProperty
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
tags :: Maybe [Tag]
virtualServiceName :: Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
instance Property "Tags" VirtualService where
  type PropertyType "Tags" VirtualService = [Tag]
  set :: PropertyType "Tags" VirtualService
-> VirtualService -> VirtualService
set PropertyType "Tags" VirtualService
newValue VirtualService {Maybe [Tag]
Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: VirtualService -> ()
meshName :: VirtualService -> Value Text
meshOwner :: VirtualService -> Maybe (Value Text)
spec :: VirtualService -> VirtualServiceSpecProperty
tags :: VirtualService -> Maybe [Tag]
virtualServiceName :: VirtualService -> Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
    = VirtualService {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" VirtualService
newValue, Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
virtualServiceName :: Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
virtualServiceName :: Value Text
..}
instance Property "VirtualServiceName" VirtualService where
  type PropertyType "VirtualServiceName" VirtualService = Value Prelude.Text
  set :: PropertyType "VirtualServiceName" VirtualService
-> VirtualService -> VirtualService
set PropertyType "VirtualServiceName" VirtualService
newValue VirtualService {Maybe [Tag]
Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: VirtualService -> ()
meshName :: VirtualService -> Value Text
meshOwner :: VirtualService -> Maybe (Value Text)
spec :: VirtualService -> VirtualServiceSpecProperty
tags :: VirtualService -> Maybe [Tag]
virtualServiceName :: VirtualService -> Value Text
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
virtualServiceName :: Value Text
..}
    = VirtualService {virtualServiceName :: Value Text
virtualServiceName = PropertyType "VirtualServiceName" VirtualService
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
VirtualServiceSpecProperty
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
meshName :: Value Text
meshOwner :: Maybe (Value Text)
spec :: VirtualServiceSpecProperty
tags :: Maybe [Tag]
..}