module Stratosphere.PCAConnectorSCEP.Connector.MobileDeviceManagementProperty (
        module Exports, MobileDeviceManagementProperty(..),
        mkMobileDeviceManagementProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.PCAConnectorSCEP.Connector.IntuneConfigurationProperty as Exports
import Stratosphere.ResourceProperties
data MobileDeviceManagementProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-pcaconnectorscep-connector-mobiledevicemanagement.html>
    MobileDeviceManagementProperty {MobileDeviceManagementProperty -> ()
haddock_workaround_ :: (),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-pcaconnectorscep-connector-mobiledevicemanagement.html#cfn-pcaconnectorscep-connector-mobiledevicemanagement-intune>
                                    MobileDeviceManagementProperty -> IntuneConfigurationProperty
intune :: IntuneConfigurationProperty}
  deriving stock (MobileDeviceManagementProperty
-> MobileDeviceManagementProperty -> Bool
(MobileDeviceManagementProperty
 -> MobileDeviceManagementProperty -> Bool)
-> (MobileDeviceManagementProperty
    -> MobileDeviceManagementProperty -> Bool)
-> Eq MobileDeviceManagementProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MobileDeviceManagementProperty
-> MobileDeviceManagementProperty -> Bool
== :: MobileDeviceManagementProperty
-> MobileDeviceManagementProperty -> Bool
$c/= :: MobileDeviceManagementProperty
-> MobileDeviceManagementProperty -> Bool
/= :: MobileDeviceManagementProperty
-> MobileDeviceManagementProperty -> Bool
Prelude.Eq, Int -> MobileDeviceManagementProperty -> ShowS
[MobileDeviceManagementProperty] -> ShowS
MobileDeviceManagementProperty -> String
(Int -> MobileDeviceManagementProperty -> ShowS)
-> (MobileDeviceManagementProperty -> String)
-> ([MobileDeviceManagementProperty] -> ShowS)
-> Show MobileDeviceManagementProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MobileDeviceManagementProperty -> ShowS
showsPrec :: Int -> MobileDeviceManagementProperty -> ShowS
$cshow :: MobileDeviceManagementProperty -> String
show :: MobileDeviceManagementProperty -> String
$cshowList :: [MobileDeviceManagementProperty] -> ShowS
showList :: [MobileDeviceManagementProperty] -> ShowS
Prelude.Show)
mkMobileDeviceManagementProperty ::
  IntuneConfigurationProperty -> MobileDeviceManagementProperty
mkMobileDeviceManagementProperty :: IntuneConfigurationProperty -> MobileDeviceManagementProperty
mkMobileDeviceManagementProperty IntuneConfigurationProperty
intune
  = MobileDeviceManagementProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), intune :: IntuneConfigurationProperty
intune = IntuneConfigurationProperty
intune}
instance ToResourceProperties MobileDeviceManagementProperty where
  toResourceProperties :: MobileDeviceManagementProperty -> ResourceProperties
toResourceProperties MobileDeviceManagementProperty {()
IntuneConfigurationProperty
haddock_workaround_ :: MobileDeviceManagementProperty -> ()
intune :: MobileDeviceManagementProperty -> IntuneConfigurationProperty
haddock_workaround_ :: ()
intune :: IntuneConfigurationProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::PCAConnectorSCEP::Connector.MobileDeviceManagement",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Intune" Key -> IntuneConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= IntuneConfigurationProperty
intune]}
instance JSON.ToJSON MobileDeviceManagementProperty where
  toJSON :: MobileDeviceManagementProperty -> Value
toJSON MobileDeviceManagementProperty {()
IntuneConfigurationProperty
haddock_workaround_ :: MobileDeviceManagementProperty -> ()
intune :: MobileDeviceManagementProperty -> IntuneConfigurationProperty
haddock_workaround_ :: ()
intune :: IntuneConfigurationProperty
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"Intune" Key -> IntuneConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= IntuneConfigurationProperty
intune]
instance Property "Intune" MobileDeviceManagementProperty where
  type PropertyType "Intune" MobileDeviceManagementProperty = IntuneConfigurationProperty
  set :: PropertyType "Intune" MobileDeviceManagementProperty
-> MobileDeviceManagementProperty -> MobileDeviceManagementProperty
set PropertyType "Intune" MobileDeviceManagementProperty
newValue MobileDeviceManagementProperty {()
IntuneConfigurationProperty
haddock_workaround_ :: MobileDeviceManagementProperty -> ()
intune :: MobileDeviceManagementProperty -> IntuneConfigurationProperty
haddock_workaround_ :: ()
intune :: IntuneConfigurationProperty
..}
    = MobileDeviceManagementProperty {intune :: IntuneConfigurationProperty
intune = PropertyType "Intune" MobileDeviceManagementProperty
IntuneConfigurationProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}