module Stratosphere.KinesisAnalyticsV2.Application.ApplicationCodeConfigurationProperty (
        module Exports, ApplicationCodeConfigurationProperty(..),
        mkApplicationCodeConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.KinesisAnalyticsV2.Application.CodeContentProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ApplicationCodeConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisanalyticsv2-application-applicationcodeconfiguration.html>
    ApplicationCodeConfigurationProperty {ApplicationCodeConfigurationProperty -> ()
haddock_workaround_ :: (),
                                          -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisanalyticsv2-application-applicationcodeconfiguration.html#cfn-kinesisanalyticsv2-application-applicationcodeconfiguration-codecontent>
                                          ApplicationCodeConfigurationProperty -> CodeContentProperty
codeContent :: CodeContentProperty,
                                          -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kinesisanalyticsv2-application-applicationcodeconfiguration.html#cfn-kinesisanalyticsv2-application-applicationcodeconfiguration-codecontenttype>
                                          ApplicationCodeConfigurationProperty -> Value Text
codeContentType :: (Value Prelude.Text)}
  deriving stock (ApplicationCodeConfigurationProperty
-> ApplicationCodeConfigurationProperty -> Bool
(ApplicationCodeConfigurationProperty
 -> ApplicationCodeConfigurationProperty -> Bool)
-> (ApplicationCodeConfigurationProperty
    -> ApplicationCodeConfigurationProperty -> Bool)
-> Eq ApplicationCodeConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApplicationCodeConfigurationProperty
-> ApplicationCodeConfigurationProperty -> Bool
== :: ApplicationCodeConfigurationProperty
-> ApplicationCodeConfigurationProperty -> Bool
$c/= :: ApplicationCodeConfigurationProperty
-> ApplicationCodeConfigurationProperty -> Bool
/= :: ApplicationCodeConfigurationProperty
-> ApplicationCodeConfigurationProperty -> Bool
Prelude.Eq, Int -> ApplicationCodeConfigurationProperty -> ShowS
[ApplicationCodeConfigurationProperty] -> ShowS
ApplicationCodeConfigurationProperty -> String
(Int -> ApplicationCodeConfigurationProperty -> ShowS)
-> (ApplicationCodeConfigurationProperty -> String)
-> ([ApplicationCodeConfigurationProperty] -> ShowS)
-> Show ApplicationCodeConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApplicationCodeConfigurationProperty -> ShowS
showsPrec :: Int -> ApplicationCodeConfigurationProperty -> ShowS
$cshow :: ApplicationCodeConfigurationProperty -> String
show :: ApplicationCodeConfigurationProperty -> String
$cshowList :: [ApplicationCodeConfigurationProperty] -> ShowS
showList :: [ApplicationCodeConfigurationProperty] -> ShowS
Prelude.Show)
mkApplicationCodeConfigurationProperty ::
  CodeContentProperty
  -> Value Prelude.Text -> ApplicationCodeConfigurationProperty
mkApplicationCodeConfigurationProperty :: CodeContentProperty
-> Value Text -> ApplicationCodeConfigurationProperty
mkApplicationCodeConfigurationProperty CodeContentProperty
codeContent Value Text
codeContentType
  = ApplicationCodeConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), codeContent :: CodeContentProperty
codeContent = CodeContentProperty
codeContent,
       codeContentType :: Value Text
codeContentType = Value Text
codeContentType}
instance ToResourceProperties ApplicationCodeConfigurationProperty where
  toResourceProperties :: ApplicationCodeConfigurationProperty -> ResourceProperties
toResourceProperties ApplicationCodeConfigurationProperty {()
Value Text
CodeContentProperty
haddock_workaround_ :: ApplicationCodeConfigurationProperty -> ()
codeContent :: ApplicationCodeConfigurationProperty -> CodeContentProperty
codeContentType :: ApplicationCodeConfigurationProperty -> Value Text
haddock_workaround_ :: ()
codeContent :: CodeContentProperty
codeContentType :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::KinesisAnalyticsV2::Application.ApplicationCodeConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"CodeContent" Key -> CodeContentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= CodeContentProperty
codeContent,
                       Key
"CodeContentType" 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
codeContentType]}
instance JSON.ToJSON ApplicationCodeConfigurationProperty where
  toJSON :: ApplicationCodeConfigurationProperty -> Value
toJSON ApplicationCodeConfigurationProperty {()
Value Text
CodeContentProperty
haddock_workaround_ :: ApplicationCodeConfigurationProperty -> ()
codeContent :: ApplicationCodeConfigurationProperty -> CodeContentProperty
codeContentType :: ApplicationCodeConfigurationProperty -> Value Text
haddock_workaround_ :: ()
codeContent :: CodeContentProperty
codeContentType :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"CodeContent" Key -> CodeContentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= CodeContentProperty
codeContent,
         Key
"CodeContentType" 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
codeContentType]
instance Property "CodeContent" ApplicationCodeConfigurationProperty where
  type PropertyType "CodeContent" ApplicationCodeConfigurationProperty = CodeContentProperty
  set :: PropertyType "CodeContent" ApplicationCodeConfigurationProperty
-> ApplicationCodeConfigurationProperty
-> ApplicationCodeConfigurationProperty
set PropertyType "CodeContent" ApplicationCodeConfigurationProperty
newValue ApplicationCodeConfigurationProperty {()
Value Text
CodeContentProperty
haddock_workaround_ :: ApplicationCodeConfigurationProperty -> ()
codeContent :: ApplicationCodeConfigurationProperty -> CodeContentProperty
codeContentType :: ApplicationCodeConfigurationProperty -> Value Text
haddock_workaround_ :: ()
codeContent :: CodeContentProperty
codeContentType :: Value Text
..}
    = ApplicationCodeConfigurationProperty {codeContent :: CodeContentProperty
codeContent = PropertyType "CodeContent" ApplicationCodeConfigurationProperty
CodeContentProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
codeContentType :: Value Text
haddock_workaround_ :: ()
codeContentType :: Value Text
..}
instance Property "CodeContentType" ApplicationCodeConfigurationProperty where
  type PropertyType "CodeContentType" ApplicationCodeConfigurationProperty = Value Prelude.Text
  set :: PropertyType "CodeContentType" ApplicationCodeConfigurationProperty
-> ApplicationCodeConfigurationProperty
-> ApplicationCodeConfigurationProperty
set PropertyType "CodeContentType" ApplicationCodeConfigurationProperty
newValue ApplicationCodeConfigurationProperty {()
Value Text
CodeContentProperty
haddock_workaround_ :: ApplicationCodeConfigurationProperty -> ()
codeContent :: ApplicationCodeConfigurationProperty -> CodeContentProperty
codeContentType :: ApplicationCodeConfigurationProperty -> Value Text
haddock_workaround_ :: ()
codeContent :: CodeContentProperty
codeContentType :: Value Text
..}
    = ApplicationCodeConfigurationProperty
        {codeContentType :: Value Text
codeContentType = PropertyType "CodeContentType" ApplicationCodeConfigurationProperty
Value Text
newValue, ()
CodeContentProperty
haddock_workaround_ :: ()
codeContent :: CodeContentProperty
haddock_workaround_ :: ()
codeContent :: CodeContentProperty
..}