module Stratosphere.ECR.RegistryScanningConfiguration (
        module Exports, RegistryScanningConfiguration(..),
        mkRegistryScanningConfiguration
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.ECR.RegistryScanningConfiguration.ScanningRuleProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RegistryScanningConfiguration
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecr-registryscanningconfiguration.html>
    RegistryScanningConfiguration {RegistryScanningConfiguration -> ()
haddock_workaround_ :: (),
                                   -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecr-registryscanningconfiguration.html#cfn-ecr-registryscanningconfiguration-rules>
                                   RegistryScanningConfiguration -> [ScanningRuleProperty]
rules :: [ScanningRuleProperty],
                                   -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecr-registryscanningconfiguration.html#cfn-ecr-registryscanningconfiguration-scantype>
                                   RegistryScanningConfiguration -> Value Text
scanType :: (Value Prelude.Text)}
  deriving stock (RegistryScanningConfiguration
-> RegistryScanningConfiguration -> Bool
(RegistryScanningConfiguration
 -> RegistryScanningConfiguration -> Bool)
-> (RegistryScanningConfiguration
    -> RegistryScanningConfiguration -> Bool)
-> Eq RegistryScanningConfiguration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RegistryScanningConfiguration
-> RegistryScanningConfiguration -> Bool
== :: RegistryScanningConfiguration
-> RegistryScanningConfiguration -> Bool
$c/= :: RegistryScanningConfiguration
-> RegistryScanningConfiguration -> Bool
/= :: RegistryScanningConfiguration
-> RegistryScanningConfiguration -> Bool
Prelude.Eq, Int -> RegistryScanningConfiguration -> ShowS
[RegistryScanningConfiguration] -> ShowS
RegistryScanningConfiguration -> String
(Int -> RegistryScanningConfiguration -> ShowS)
-> (RegistryScanningConfiguration -> String)
-> ([RegistryScanningConfiguration] -> ShowS)
-> Show RegistryScanningConfiguration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RegistryScanningConfiguration -> ShowS
showsPrec :: Int -> RegistryScanningConfiguration -> ShowS
$cshow :: RegistryScanningConfiguration -> String
show :: RegistryScanningConfiguration -> String
$cshowList :: [RegistryScanningConfiguration] -> ShowS
showList :: [RegistryScanningConfiguration] -> ShowS
Prelude.Show)
mkRegistryScanningConfiguration ::
  [ScanningRuleProperty]
  -> Value Prelude.Text -> RegistryScanningConfiguration
mkRegistryScanningConfiguration :: [ScanningRuleProperty]
-> Value Text -> RegistryScanningConfiguration
mkRegistryScanningConfiguration [ScanningRuleProperty]
rules Value Text
scanType
  = RegistryScanningConfiguration
      {haddock_workaround_ :: ()
haddock_workaround_ = (), rules :: [ScanningRuleProperty]
rules = [ScanningRuleProperty]
rules, scanType :: Value Text
scanType = Value Text
scanType}
instance ToResourceProperties RegistryScanningConfiguration where
  toResourceProperties :: RegistryScanningConfiguration -> ResourceProperties
toResourceProperties RegistryScanningConfiguration {[ScanningRuleProperty]
()
Value Text
haddock_workaround_ :: RegistryScanningConfiguration -> ()
rules :: RegistryScanningConfiguration -> [ScanningRuleProperty]
scanType :: RegistryScanningConfiguration -> Value Text
haddock_workaround_ :: ()
rules :: [ScanningRuleProperty]
scanType :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::ECR::RegistryScanningConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Rules" Key -> [ScanningRuleProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ScanningRuleProperty]
rules, Key
"ScanType" 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
scanType]}
instance JSON.ToJSON RegistryScanningConfiguration where
  toJSON :: RegistryScanningConfiguration -> Value
toJSON RegistryScanningConfiguration {[ScanningRuleProperty]
()
Value Text
haddock_workaround_ :: RegistryScanningConfiguration -> ()
rules :: RegistryScanningConfiguration -> [ScanningRuleProperty]
scanType :: RegistryScanningConfiguration -> Value Text
haddock_workaround_ :: ()
rules :: [ScanningRuleProperty]
scanType :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"Rules" Key -> [ScanningRuleProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ScanningRuleProperty]
rules, Key
"ScanType" 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
scanType]
instance Property "Rules" RegistryScanningConfiguration where
  type PropertyType "Rules" RegistryScanningConfiguration = [ScanningRuleProperty]
  set :: PropertyType "Rules" RegistryScanningConfiguration
-> RegistryScanningConfiguration -> RegistryScanningConfiguration
set PropertyType "Rules" RegistryScanningConfiguration
newValue RegistryScanningConfiguration {[ScanningRuleProperty]
()
Value Text
haddock_workaround_ :: RegistryScanningConfiguration -> ()
rules :: RegistryScanningConfiguration -> [ScanningRuleProperty]
scanType :: RegistryScanningConfiguration -> Value Text
haddock_workaround_ :: ()
rules :: [ScanningRuleProperty]
scanType :: Value Text
..}
    = RegistryScanningConfiguration {rules :: [ScanningRuleProperty]
rules = [ScanningRuleProperty]
PropertyType "Rules" RegistryScanningConfiguration
newValue, ()
Value Text
haddock_workaround_ :: ()
scanType :: Value Text
haddock_workaround_ :: ()
scanType :: Value Text
..}
instance Property "ScanType" RegistryScanningConfiguration where
  type PropertyType "ScanType" RegistryScanningConfiguration = Value Prelude.Text
  set :: PropertyType "ScanType" RegistryScanningConfiguration
-> RegistryScanningConfiguration -> RegistryScanningConfiguration
set PropertyType "ScanType" RegistryScanningConfiguration
newValue RegistryScanningConfiguration {[ScanningRuleProperty]
()
Value Text
haddock_workaround_ :: RegistryScanningConfiguration -> ()
rules :: RegistryScanningConfiguration -> [ScanningRuleProperty]
scanType :: RegistryScanningConfiguration -> Value Text
haddock_workaround_ :: ()
rules :: [ScanningRuleProperty]
scanType :: Value Text
..}
    = RegistryScanningConfiguration {scanType :: Value Text
scanType = PropertyType "ScanType" RegistryScanningConfiguration
Value Text
newValue, [ScanningRuleProperty]
()
haddock_workaround_ :: ()
rules :: [ScanningRuleProperty]
haddock_workaround_ :: ()
rules :: [ScanningRuleProperty]
..}