module Stratosphere.Glue.MLTransform.FindMatchesParametersProperty (
        FindMatchesParametersProperty(..), mkFindMatchesParametersProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data FindMatchesParametersProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-glue-mltransform-transformparameters-findmatchesparameters.html>
    FindMatchesParametersProperty {FindMatchesParametersProperty -> ()
haddock_workaround_ :: (),
                                   -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-glue-mltransform-transformparameters-findmatchesparameters.html#cfn-glue-mltransform-transformparameters-findmatchesparameters-accuracycosttradeoff>
                                   FindMatchesParametersProperty -> Maybe (Value Double)
accuracyCostTradeoff :: (Prelude.Maybe (Value Prelude.Double)),
                                   -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-glue-mltransform-transformparameters-findmatchesparameters.html#cfn-glue-mltransform-transformparameters-findmatchesparameters-enforceprovidedlabels>
                                   FindMatchesParametersProperty -> Maybe (Value Bool)
enforceProvidedLabels :: (Prelude.Maybe (Value Prelude.Bool)),
                                   -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-glue-mltransform-transformparameters-findmatchesparameters.html#cfn-glue-mltransform-transformparameters-findmatchesparameters-precisionrecalltradeoff>
                                   FindMatchesParametersProperty -> Maybe (Value Double)
precisionRecallTradeoff :: (Prelude.Maybe (Value Prelude.Double)),
                                   -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-glue-mltransform-transformparameters-findmatchesparameters.html#cfn-glue-mltransform-transformparameters-findmatchesparameters-primarykeycolumnname>
                                   FindMatchesParametersProperty -> Value Text
primaryKeyColumnName :: (Value Prelude.Text)}
  deriving stock (FindMatchesParametersProperty
-> FindMatchesParametersProperty -> Bool
(FindMatchesParametersProperty
 -> FindMatchesParametersProperty -> Bool)
-> (FindMatchesParametersProperty
    -> FindMatchesParametersProperty -> Bool)
-> Eq FindMatchesParametersProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FindMatchesParametersProperty
-> FindMatchesParametersProperty -> Bool
== :: FindMatchesParametersProperty
-> FindMatchesParametersProperty -> Bool
$c/= :: FindMatchesParametersProperty
-> FindMatchesParametersProperty -> Bool
/= :: FindMatchesParametersProperty
-> FindMatchesParametersProperty -> Bool
Prelude.Eq, Int -> FindMatchesParametersProperty -> ShowS
[FindMatchesParametersProperty] -> ShowS
FindMatchesParametersProperty -> String
(Int -> FindMatchesParametersProperty -> ShowS)
-> (FindMatchesParametersProperty -> String)
-> ([FindMatchesParametersProperty] -> ShowS)
-> Show FindMatchesParametersProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FindMatchesParametersProperty -> ShowS
showsPrec :: Int -> FindMatchesParametersProperty -> ShowS
$cshow :: FindMatchesParametersProperty -> String
show :: FindMatchesParametersProperty -> String
$cshowList :: [FindMatchesParametersProperty] -> ShowS
showList :: [FindMatchesParametersProperty] -> ShowS
Prelude.Show)
mkFindMatchesParametersProperty ::
  Value Prelude.Text -> FindMatchesParametersProperty
mkFindMatchesParametersProperty :: Value Text -> FindMatchesParametersProperty
mkFindMatchesParametersProperty Value Text
primaryKeyColumnName
  = FindMatchesParametersProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       primaryKeyColumnName :: Value Text
primaryKeyColumnName = Value Text
primaryKeyColumnName,
       accuracyCostTradeoff :: Maybe (Value Double)
accuracyCostTradeoff = Maybe (Value Double)
forall a. Maybe a
Prelude.Nothing,
       enforceProvidedLabels :: Maybe (Value Bool)
enforceProvidedLabels = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       precisionRecallTradeoff :: Maybe (Value Double)
precisionRecallTradeoff = Maybe (Value Double)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties FindMatchesParametersProperty where
  toResourceProperties :: FindMatchesParametersProperty -> ResourceProperties
toResourceProperties FindMatchesParametersProperty {Maybe (Value Bool)
Maybe (Value Double)
()
Value Text
haddock_workaround_ :: FindMatchesParametersProperty -> ()
accuracyCostTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
enforceProvidedLabels :: FindMatchesParametersProperty -> Maybe (Value Bool)
precisionRecallTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
primaryKeyColumnName :: FindMatchesParametersProperty -> Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Glue::MLTransform.FindMatchesParameters",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         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
"PrimaryKeyColumnName" 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
primaryKeyColumnName]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AccuracyCostTradeoff" (Value Double -> (Key, Value))
-> Maybe (Value Double) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Double)
accuracyCostTradeoff,
                               Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnforceProvidedLabels"
                                 (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
enforceProvidedLabels,
                               Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PrecisionRecallTradeoff"
                                 (Value Double -> (Key, Value))
-> Maybe (Value Double) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Double)
precisionRecallTradeoff]))}
instance JSON.ToJSON FindMatchesParametersProperty where
  toJSON :: FindMatchesParametersProperty -> Value
toJSON FindMatchesParametersProperty {Maybe (Value Bool)
Maybe (Value Double)
()
Value Text
haddock_workaround_ :: FindMatchesParametersProperty -> ()
accuracyCostTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
enforceProvidedLabels :: FindMatchesParametersProperty -> Maybe (Value Bool)
precisionRecallTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
primaryKeyColumnName :: FindMatchesParametersProperty -> Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: 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
"PrimaryKeyColumnName" 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
primaryKeyColumnName]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AccuracyCostTradeoff" (Value Double -> (Key, Value))
-> Maybe (Value Double) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Double)
accuracyCostTradeoff,
                  Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnforceProvidedLabels"
                    (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
enforceProvidedLabels,
                  Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PrecisionRecallTradeoff"
                    (Value Double -> (Key, Value))
-> Maybe (Value Double) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Double)
precisionRecallTradeoff])))
instance Property "AccuracyCostTradeoff" FindMatchesParametersProperty where
  type PropertyType "AccuracyCostTradeoff" FindMatchesParametersProperty = Value Prelude.Double
  set :: PropertyType "AccuracyCostTradeoff" FindMatchesParametersProperty
-> FindMatchesParametersProperty -> FindMatchesParametersProperty
set PropertyType "AccuracyCostTradeoff" FindMatchesParametersProperty
newValue FindMatchesParametersProperty {Maybe (Value Bool)
Maybe (Value Double)
()
Value Text
haddock_workaround_ :: FindMatchesParametersProperty -> ()
accuracyCostTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
enforceProvidedLabels :: FindMatchesParametersProperty -> Maybe (Value Bool)
precisionRecallTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
primaryKeyColumnName :: FindMatchesParametersProperty -> Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: Value Text
..}
    = FindMatchesParametersProperty
        {accuracyCostTradeoff :: Maybe (Value Double)
accuracyCostTradeoff = Value Double -> Maybe (Value Double)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AccuracyCostTradeoff" FindMatchesParametersProperty
Value Double
newValue, Maybe (Value Bool)
Maybe (Value Double)
()
Value Text
haddock_workaround_ :: ()
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: Value Text
haddock_workaround_ :: ()
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: Value Text
..}
instance Property "EnforceProvidedLabels" FindMatchesParametersProperty where
  type PropertyType "EnforceProvidedLabels" FindMatchesParametersProperty = Value Prelude.Bool
  set :: PropertyType "EnforceProvidedLabels" FindMatchesParametersProperty
-> FindMatchesParametersProperty -> FindMatchesParametersProperty
set PropertyType "EnforceProvidedLabels" FindMatchesParametersProperty
newValue FindMatchesParametersProperty {Maybe (Value Bool)
Maybe (Value Double)
()
Value Text
haddock_workaround_ :: FindMatchesParametersProperty -> ()
accuracyCostTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
enforceProvidedLabels :: FindMatchesParametersProperty -> Maybe (Value Bool)
precisionRecallTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
primaryKeyColumnName :: FindMatchesParametersProperty -> Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: Value Text
..}
    = FindMatchesParametersProperty
        {enforceProvidedLabels :: Maybe (Value Bool)
enforceProvidedLabels = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EnforceProvidedLabels" FindMatchesParametersProperty
Value Bool
newValue, Maybe (Value Double)
()
Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: Value Text
..}
instance Property "PrecisionRecallTradeoff" FindMatchesParametersProperty where
  type PropertyType "PrecisionRecallTradeoff" FindMatchesParametersProperty = Value Prelude.Double
  set :: PropertyType
  "PrecisionRecallTradeoff" FindMatchesParametersProperty
-> FindMatchesParametersProperty -> FindMatchesParametersProperty
set PropertyType
  "PrecisionRecallTradeoff" FindMatchesParametersProperty
newValue FindMatchesParametersProperty {Maybe (Value Bool)
Maybe (Value Double)
()
Value Text
haddock_workaround_ :: FindMatchesParametersProperty -> ()
accuracyCostTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
enforceProvidedLabels :: FindMatchesParametersProperty -> Maybe (Value Bool)
precisionRecallTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
primaryKeyColumnName :: FindMatchesParametersProperty -> Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: Value Text
..}
    = FindMatchesParametersProperty
        {precisionRecallTradeoff :: Maybe (Value Double)
precisionRecallTradeoff = Value Double -> Maybe (Value Double)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "PrecisionRecallTradeoff" FindMatchesParametersProperty
Value Double
newValue, Maybe (Value Bool)
Maybe (Value Double)
()
Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
primaryKeyColumnName :: Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
primaryKeyColumnName :: Value Text
..}
instance Property "PrimaryKeyColumnName" FindMatchesParametersProperty where
  type PropertyType "PrimaryKeyColumnName" FindMatchesParametersProperty = Value Prelude.Text
  set :: PropertyType "PrimaryKeyColumnName" FindMatchesParametersProperty
-> FindMatchesParametersProperty -> FindMatchesParametersProperty
set PropertyType "PrimaryKeyColumnName" FindMatchesParametersProperty
newValue FindMatchesParametersProperty {Maybe (Value Bool)
Maybe (Value Double)
()
Value Text
haddock_workaround_ :: FindMatchesParametersProperty -> ()
accuracyCostTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
enforceProvidedLabels :: FindMatchesParametersProperty -> Maybe (Value Bool)
precisionRecallTradeoff :: FindMatchesParametersProperty -> Maybe (Value Double)
primaryKeyColumnName :: FindMatchesParametersProperty -> Value Text
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
primaryKeyColumnName :: Value Text
..}
    = FindMatchesParametersProperty
        {primaryKeyColumnName :: Value Text
primaryKeyColumnName = PropertyType "PrimaryKeyColumnName" FindMatchesParametersProperty
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Double)
()
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
haddock_workaround_ :: ()
accuracyCostTradeoff :: Maybe (Value Double)
enforceProvidedLabels :: Maybe (Value Bool)
precisionRecallTradeoff :: Maybe (Value Double)
..}