module Stratosphere.Greengrass.ResourceDefinition.LocalVolumeResourceDataProperty (
        module Exports, LocalVolumeResourceDataProperty(..),
        mkLocalVolumeResourceDataProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Greengrass.ResourceDefinition.GroupOwnerSettingProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data LocalVolumeResourceDataProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-greengrass-resourcedefinition-localvolumeresourcedata.html>
    LocalVolumeResourceDataProperty {LocalVolumeResourceDataProperty -> ()
haddock_workaround_ :: (),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-greengrass-resourcedefinition-localvolumeresourcedata.html#cfn-greengrass-resourcedefinition-localvolumeresourcedata-destinationpath>
                                     LocalVolumeResourceDataProperty -> Value Text
destinationPath :: (Value Prelude.Text),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-greengrass-resourcedefinition-localvolumeresourcedata.html#cfn-greengrass-resourcedefinition-localvolumeresourcedata-groupownersetting>
                                     LocalVolumeResourceDataProperty -> Maybe GroupOwnerSettingProperty
groupOwnerSetting :: (Prelude.Maybe GroupOwnerSettingProperty),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-greengrass-resourcedefinition-localvolumeresourcedata.html#cfn-greengrass-resourcedefinition-localvolumeresourcedata-sourcepath>
                                     LocalVolumeResourceDataProperty -> Value Text
sourcePath :: (Value Prelude.Text)}
  deriving stock (LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty -> Bool
(LocalVolumeResourceDataProperty
 -> LocalVolumeResourceDataProperty -> Bool)
-> (LocalVolumeResourceDataProperty
    -> LocalVolumeResourceDataProperty -> Bool)
-> Eq LocalVolumeResourceDataProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty -> Bool
== :: LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty -> Bool
$c/= :: LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty -> Bool
/= :: LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty -> Bool
Prelude.Eq, Int -> LocalVolumeResourceDataProperty -> ShowS
[LocalVolumeResourceDataProperty] -> ShowS
LocalVolumeResourceDataProperty -> String
(Int -> LocalVolumeResourceDataProperty -> ShowS)
-> (LocalVolumeResourceDataProperty -> String)
-> ([LocalVolumeResourceDataProperty] -> ShowS)
-> Show LocalVolumeResourceDataProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LocalVolumeResourceDataProperty -> ShowS
showsPrec :: Int -> LocalVolumeResourceDataProperty -> ShowS
$cshow :: LocalVolumeResourceDataProperty -> String
show :: LocalVolumeResourceDataProperty -> String
$cshowList :: [LocalVolumeResourceDataProperty] -> ShowS
showList :: [LocalVolumeResourceDataProperty] -> ShowS
Prelude.Show)
mkLocalVolumeResourceDataProperty ::
  Value Prelude.Text
  -> Value Prelude.Text -> LocalVolumeResourceDataProperty
mkLocalVolumeResourceDataProperty :: Value Text -> Value Text -> LocalVolumeResourceDataProperty
mkLocalVolumeResourceDataProperty Value Text
destinationPath Value Text
sourcePath
  = LocalVolumeResourceDataProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), destinationPath :: Value Text
destinationPath = Value Text
destinationPath,
       sourcePath :: Value Text
sourcePath = Value Text
sourcePath, groupOwnerSetting :: Maybe GroupOwnerSettingProperty
groupOwnerSetting = Maybe GroupOwnerSettingProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties LocalVolumeResourceDataProperty where
  toResourceProperties :: LocalVolumeResourceDataProperty -> ResourceProperties
toResourceProperties LocalVolumeResourceDataProperty {Maybe GroupOwnerSettingProperty
()
Value Text
haddock_workaround_ :: LocalVolumeResourceDataProperty -> ()
destinationPath :: LocalVolumeResourceDataProperty -> Value Text
groupOwnerSetting :: LocalVolumeResourceDataProperty -> Maybe GroupOwnerSettingProperty
sourcePath :: LocalVolumeResourceDataProperty -> Value Text
haddock_workaround_ :: ()
destinationPath :: Value Text
groupOwnerSetting :: Maybe GroupOwnerSettingProperty
sourcePath :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Greengrass::ResourceDefinition.LocalVolumeResourceData",
         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
"DestinationPath" 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
destinationPath,
                            Key
"SourcePath" 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
sourcePath]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> GroupOwnerSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GroupOwnerSetting" (GroupOwnerSettingProperty -> (Key, Value))
-> Maybe GroupOwnerSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GroupOwnerSettingProperty
groupOwnerSetting]))}
instance JSON.ToJSON LocalVolumeResourceDataProperty where
  toJSON :: LocalVolumeResourceDataProperty -> Value
toJSON LocalVolumeResourceDataProperty {Maybe GroupOwnerSettingProperty
()
Value Text
haddock_workaround_ :: LocalVolumeResourceDataProperty -> ()
destinationPath :: LocalVolumeResourceDataProperty -> Value Text
groupOwnerSetting :: LocalVolumeResourceDataProperty -> Maybe GroupOwnerSettingProperty
sourcePath :: LocalVolumeResourceDataProperty -> Value Text
haddock_workaround_ :: ()
destinationPath :: Value Text
groupOwnerSetting :: Maybe GroupOwnerSettingProperty
sourcePath :: 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
"DestinationPath" 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
destinationPath,
               Key
"SourcePath" 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
sourcePath]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> GroupOwnerSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GroupOwnerSetting" (GroupOwnerSettingProperty -> (Key, Value))
-> Maybe GroupOwnerSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GroupOwnerSettingProperty
groupOwnerSetting])))
instance Property "DestinationPath" LocalVolumeResourceDataProperty where
  type PropertyType "DestinationPath" LocalVolumeResourceDataProperty = Value Prelude.Text
  set :: PropertyType "DestinationPath" LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty
set PropertyType "DestinationPath" LocalVolumeResourceDataProperty
newValue LocalVolumeResourceDataProperty {Maybe GroupOwnerSettingProperty
()
Value Text
haddock_workaround_ :: LocalVolumeResourceDataProperty -> ()
destinationPath :: LocalVolumeResourceDataProperty -> Value Text
groupOwnerSetting :: LocalVolumeResourceDataProperty -> Maybe GroupOwnerSettingProperty
sourcePath :: LocalVolumeResourceDataProperty -> Value Text
haddock_workaround_ :: ()
destinationPath :: Value Text
groupOwnerSetting :: Maybe GroupOwnerSettingProperty
sourcePath :: Value Text
..}
    = LocalVolumeResourceDataProperty {destinationPath :: Value Text
destinationPath = PropertyType "DestinationPath" LocalVolumeResourceDataProperty
Value Text
newValue, Maybe GroupOwnerSettingProperty
()
Value Text
haddock_workaround_ :: ()
groupOwnerSetting :: Maybe GroupOwnerSettingProperty
sourcePath :: Value Text
haddock_workaround_ :: ()
groupOwnerSetting :: Maybe GroupOwnerSettingProperty
sourcePath :: Value Text
..}
instance Property "GroupOwnerSetting" LocalVolumeResourceDataProperty where
  type PropertyType "GroupOwnerSetting" LocalVolumeResourceDataProperty = GroupOwnerSettingProperty
  set :: PropertyType "GroupOwnerSetting" LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty
set PropertyType "GroupOwnerSetting" LocalVolumeResourceDataProperty
newValue LocalVolumeResourceDataProperty {Maybe GroupOwnerSettingProperty
()
Value Text
haddock_workaround_ :: LocalVolumeResourceDataProperty -> ()
destinationPath :: LocalVolumeResourceDataProperty -> Value Text
groupOwnerSetting :: LocalVolumeResourceDataProperty -> Maybe GroupOwnerSettingProperty
sourcePath :: LocalVolumeResourceDataProperty -> Value Text
haddock_workaround_ :: ()
destinationPath :: Value Text
groupOwnerSetting :: Maybe GroupOwnerSettingProperty
sourcePath :: Value Text
..}
    = LocalVolumeResourceDataProperty
        {groupOwnerSetting :: Maybe GroupOwnerSettingProperty
groupOwnerSetting = GroupOwnerSettingProperty -> Maybe GroupOwnerSettingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "GroupOwnerSetting" LocalVolumeResourceDataProperty
GroupOwnerSettingProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
destinationPath :: Value Text
sourcePath :: Value Text
haddock_workaround_ :: ()
destinationPath :: Value Text
sourcePath :: Value Text
..}
instance Property "SourcePath" LocalVolumeResourceDataProperty where
  type PropertyType "SourcePath" LocalVolumeResourceDataProperty = Value Prelude.Text
  set :: PropertyType "SourcePath" LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty
-> LocalVolumeResourceDataProperty
set PropertyType "SourcePath" LocalVolumeResourceDataProperty
newValue LocalVolumeResourceDataProperty {Maybe GroupOwnerSettingProperty
()
Value Text
haddock_workaround_ :: LocalVolumeResourceDataProperty -> ()
destinationPath :: LocalVolumeResourceDataProperty -> Value Text
groupOwnerSetting :: LocalVolumeResourceDataProperty -> Maybe GroupOwnerSettingProperty
sourcePath :: LocalVolumeResourceDataProperty -> Value Text
haddock_workaround_ :: ()
destinationPath :: Value Text
groupOwnerSetting :: Maybe GroupOwnerSettingProperty
sourcePath :: Value Text
..}
    = LocalVolumeResourceDataProperty {sourcePath :: Value Text
sourcePath = PropertyType "SourcePath" LocalVolumeResourceDataProperty
Value Text
newValue, Maybe GroupOwnerSettingProperty
()
Value Text
haddock_workaround_ :: ()
destinationPath :: Value Text
groupOwnerSetting :: Maybe GroupOwnerSettingProperty
haddock_workaround_ :: ()
destinationPath :: Value Text
groupOwnerSetting :: Maybe GroupOwnerSettingProperty
..}