module Stratosphere.IoTSiteWise.ComputationModel.AnomalyDetectionComputationModelConfigurationProperty (
        AnomalyDetectionComputationModelConfigurationProperty(..),
        mkAnomalyDetectionComputationModelConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data AnomalyDetectionComputationModelConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-iotsitewise-computationmodel-anomalydetectioncomputationmodelconfiguration.html>
    AnomalyDetectionComputationModelConfigurationProperty {AnomalyDetectionComputationModelConfigurationProperty -> ()
haddock_workaround_ :: (),
                                                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-iotsitewise-computationmodel-anomalydetectioncomputationmodelconfiguration.html#cfn-iotsitewise-computationmodel-anomalydetectioncomputationmodelconfiguration-inputproperties>
                                                           AnomalyDetectionComputationModelConfigurationProperty -> Value Text
inputProperties :: (Value Prelude.Text),
                                                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-iotsitewise-computationmodel-anomalydetectioncomputationmodelconfiguration.html#cfn-iotsitewise-computationmodel-anomalydetectioncomputationmodelconfiguration-resultproperty>
                                                           AnomalyDetectionComputationModelConfigurationProperty -> Value Text
resultProperty :: (Value Prelude.Text)}
  deriving stock (AnomalyDetectionComputationModelConfigurationProperty
-> AnomalyDetectionComputationModelConfigurationProperty -> Bool
(AnomalyDetectionComputationModelConfigurationProperty
 -> AnomalyDetectionComputationModelConfigurationProperty -> Bool)
-> (AnomalyDetectionComputationModelConfigurationProperty
    -> AnomalyDetectionComputationModelConfigurationProperty -> Bool)
-> Eq AnomalyDetectionComputationModelConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnomalyDetectionComputationModelConfigurationProperty
-> AnomalyDetectionComputationModelConfigurationProperty -> Bool
== :: AnomalyDetectionComputationModelConfigurationProperty
-> AnomalyDetectionComputationModelConfigurationProperty -> Bool
$c/= :: AnomalyDetectionComputationModelConfigurationProperty
-> AnomalyDetectionComputationModelConfigurationProperty -> Bool
/= :: AnomalyDetectionComputationModelConfigurationProperty
-> AnomalyDetectionComputationModelConfigurationProperty -> Bool
Prelude.Eq, Int
-> AnomalyDetectionComputationModelConfigurationProperty -> ShowS
[AnomalyDetectionComputationModelConfigurationProperty] -> ShowS
AnomalyDetectionComputationModelConfigurationProperty -> String
(Int
 -> AnomalyDetectionComputationModelConfigurationProperty -> ShowS)
-> (AnomalyDetectionComputationModelConfigurationProperty
    -> String)
-> ([AnomalyDetectionComputationModelConfigurationProperty]
    -> ShowS)
-> Show AnomalyDetectionComputationModelConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int
-> AnomalyDetectionComputationModelConfigurationProperty -> ShowS
showsPrec :: Int
-> AnomalyDetectionComputationModelConfigurationProperty -> ShowS
$cshow :: AnomalyDetectionComputationModelConfigurationProperty -> String
show :: AnomalyDetectionComputationModelConfigurationProperty -> String
$cshowList :: [AnomalyDetectionComputationModelConfigurationProperty] -> ShowS
showList :: [AnomalyDetectionComputationModelConfigurationProperty] -> ShowS
Prelude.Show)
mkAnomalyDetectionComputationModelConfigurationProperty ::
  Value Prelude.Text
  -> Value Prelude.Text
     -> AnomalyDetectionComputationModelConfigurationProperty
mkAnomalyDetectionComputationModelConfigurationProperty :: Value Text
-> Value Text
-> AnomalyDetectionComputationModelConfigurationProperty
mkAnomalyDetectionComputationModelConfigurationProperty
  Value Text
inputProperties
  Value Text
resultProperty
  = AnomalyDetectionComputationModelConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), inputProperties :: Value Text
inputProperties = Value Text
inputProperties,
       resultProperty :: Value Text
resultProperty = Value Text
resultProperty}
instance ToResourceProperties AnomalyDetectionComputationModelConfigurationProperty where
  toResourceProperties :: AnomalyDetectionComputationModelConfigurationProperty
-> ResourceProperties
toResourceProperties
    AnomalyDetectionComputationModelConfigurationProperty {()
Value Text
haddock_workaround_ :: AnomalyDetectionComputationModelConfigurationProperty -> ()
inputProperties :: AnomalyDetectionComputationModelConfigurationProperty -> Value Text
resultProperty :: AnomalyDetectionComputationModelConfigurationProperty -> Value Text
haddock_workaround_ :: ()
inputProperties :: Value Text
resultProperty :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::IoTSiteWise::ComputationModel.AnomalyDetectionComputationModelConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"InputProperties" 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
inputProperties,
                       Key
"ResultProperty" 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
resultProperty]}
instance JSON.ToJSON AnomalyDetectionComputationModelConfigurationProperty where
  toJSON :: AnomalyDetectionComputationModelConfigurationProperty -> Value
toJSON AnomalyDetectionComputationModelConfigurationProperty {()
Value Text
haddock_workaround_ :: AnomalyDetectionComputationModelConfigurationProperty -> ()
inputProperties :: AnomalyDetectionComputationModelConfigurationProperty -> Value Text
resultProperty :: AnomalyDetectionComputationModelConfigurationProperty -> Value Text
haddock_workaround_ :: ()
inputProperties :: Value Text
resultProperty :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"InputProperties" 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
inputProperties,
         Key
"ResultProperty" 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
resultProperty]
instance Property "InputProperties" AnomalyDetectionComputationModelConfigurationProperty where
  type PropertyType "InputProperties" AnomalyDetectionComputationModelConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "InputProperties"
  AnomalyDetectionComputationModelConfigurationProperty
-> AnomalyDetectionComputationModelConfigurationProperty
-> AnomalyDetectionComputationModelConfigurationProperty
set
    PropertyType
  "InputProperties"
  AnomalyDetectionComputationModelConfigurationProperty
newValue
    AnomalyDetectionComputationModelConfigurationProperty {()
Value Text
haddock_workaround_ :: AnomalyDetectionComputationModelConfigurationProperty -> ()
inputProperties :: AnomalyDetectionComputationModelConfigurationProperty -> Value Text
resultProperty :: AnomalyDetectionComputationModelConfigurationProperty -> Value Text
haddock_workaround_ :: ()
inputProperties :: Value Text
resultProperty :: Value Text
..}
    = AnomalyDetectionComputationModelConfigurationProperty
        {inputProperties :: Value Text
inputProperties = PropertyType
  "InputProperties"
  AnomalyDetectionComputationModelConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
resultProperty :: Value Text
haddock_workaround_ :: ()
resultProperty :: Value Text
..}
instance Property "ResultProperty" AnomalyDetectionComputationModelConfigurationProperty where
  type PropertyType "ResultProperty" AnomalyDetectionComputationModelConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "ResultProperty"
  AnomalyDetectionComputationModelConfigurationProperty
-> AnomalyDetectionComputationModelConfigurationProperty
-> AnomalyDetectionComputationModelConfigurationProperty
set
    PropertyType
  "ResultProperty"
  AnomalyDetectionComputationModelConfigurationProperty
newValue
    AnomalyDetectionComputationModelConfigurationProperty {()
Value Text
haddock_workaround_ :: AnomalyDetectionComputationModelConfigurationProperty -> ()
inputProperties :: AnomalyDetectionComputationModelConfigurationProperty -> Value Text
resultProperty :: AnomalyDetectionComputationModelConfigurationProperty -> Value Text
haddock_workaround_ :: ()
inputProperties :: Value Text
resultProperty :: Value Text
..}
    = AnomalyDetectionComputationModelConfigurationProperty
        {resultProperty :: Value Text
resultProperty = PropertyType
  "ResultProperty"
  AnomalyDetectionComputationModelConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
inputProperties :: Value Text
haddock_workaround_ :: ()
inputProperties :: Value Text
..}