module Stratosphere.AppTest.TestCase.OutputProperty (
        module Exports, OutputProperty(..), mkOutputProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AppTest.TestCase.OutputFileProperty as Exports
import Stratosphere.ResourceProperties
data OutputProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-apptest-testcase-output.html>
    OutputProperty {OutputProperty -> ()
haddock_workaround_ :: (),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-apptest-testcase-output.html#cfn-apptest-testcase-output-file>
                    OutputProperty -> OutputFileProperty
file :: OutputFileProperty}
  deriving stock (OutputProperty -> OutputProperty -> Bool
(OutputProperty -> OutputProperty -> Bool)
-> (OutputProperty -> OutputProperty -> Bool) -> Eq OutputProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputProperty -> OutputProperty -> Bool
== :: OutputProperty -> OutputProperty -> Bool
$c/= :: OutputProperty -> OutputProperty -> Bool
/= :: OutputProperty -> OutputProperty -> Bool
Prelude.Eq, Int -> OutputProperty -> ShowS
[OutputProperty] -> ShowS
OutputProperty -> String
(Int -> OutputProperty -> ShowS)
-> (OutputProperty -> String)
-> ([OutputProperty] -> ShowS)
-> Show OutputProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutputProperty -> ShowS
showsPrec :: Int -> OutputProperty -> ShowS
$cshow :: OutputProperty -> String
show :: OutputProperty -> String
$cshowList :: [OutputProperty] -> ShowS
showList :: [OutputProperty] -> ShowS
Prelude.Show)
mkOutputProperty :: OutputFileProperty -> OutputProperty
mkOutputProperty :: OutputFileProperty -> OutputProperty
mkOutputProperty OutputFileProperty
file
  = OutputProperty {haddock_workaround_ :: ()
haddock_workaround_ = (), file :: OutputFileProperty
file = OutputFileProperty
file}
instance ToResourceProperties OutputProperty where
  toResourceProperties :: OutputProperty -> ResourceProperties
toResourceProperties OutputProperty {()
OutputFileProperty
haddock_workaround_ :: OutputProperty -> ()
file :: OutputProperty -> OutputFileProperty
haddock_workaround_ :: ()
file :: OutputFileProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::AppTest::TestCase.Output",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False, properties :: Object
properties = [Key
"File" Key -> OutputFileProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= OutputFileProperty
file]}
instance JSON.ToJSON OutputProperty where
  toJSON :: OutputProperty -> Value
toJSON OutputProperty {()
OutputFileProperty
haddock_workaround_ :: OutputProperty -> ()
file :: OutputProperty -> OutputFileProperty
haddock_workaround_ :: ()
file :: OutputFileProperty
..} = [(Key, Value)] -> Value
JSON.object [Key
"File" Key -> OutputFileProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= OutputFileProperty
file]
instance Property "File" OutputProperty where
  type PropertyType "File" OutputProperty = OutputFileProperty
  set :: PropertyType "File" OutputProperty
-> OutputProperty -> OutputProperty
set PropertyType "File" OutputProperty
newValue OutputProperty {()
OutputFileProperty
haddock_workaround_ :: OutputProperty -> ()
file :: OutputProperty -> OutputFileProperty
haddock_workaround_ :: ()
file :: OutputFileProperty
..}
    = OutputProperty {file :: OutputFileProperty
file = PropertyType "File" OutputProperty
OutputFileProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}