module Stratosphere.Lambda.Function.FileSystemConfigProperty (
FileSystemConfigProperty(..), mkFileSystemConfigProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data FileSystemConfigProperty
=
FileSystemConfigProperty {FileSystemConfigProperty -> ()
haddock_workaround_ :: (),
FileSystemConfigProperty -> Value Text
arn :: (Value Prelude.Text),
FileSystemConfigProperty -> Value Text
localMountPath :: (Value Prelude.Text)}
deriving stock (FileSystemConfigProperty -> FileSystemConfigProperty -> Bool
(FileSystemConfigProperty -> FileSystemConfigProperty -> Bool)
-> (FileSystemConfigProperty -> FileSystemConfigProperty -> Bool)
-> Eq FileSystemConfigProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileSystemConfigProperty -> FileSystemConfigProperty -> Bool
== :: FileSystemConfigProperty -> FileSystemConfigProperty -> Bool
$c/= :: FileSystemConfigProperty -> FileSystemConfigProperty -> Bool
/= :: FileSystemConfigProperty -> FileSystemConfigProperty -> Bool
Prelude.Eq, Int -> FileSystemConfigProperty -> ShowS
[FileSystemConfigProperty] -> ShowS
FileSystemConfigProperty -> String
(Int -> FileSystemConfigProperty -> ShowS)
-> (FileSystemConfigProperty -> String)
-> ([FileSystemConfigProperty] -> ShowS)
-> Show FileSystemConfigProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileSystemConfigProperty -> ShowS
showsPrec :: Int -> FileSystemConfigProperty -> ShowS
$cshow :: FileSystemConfigProperty -> String
show :: FileSystemConfigProperty -> String
$cshowList :: [FileSystemConfigProperty] -> ShowS
showList :: [FileSystemConfigProperty] -> ShowS
Prelude.Show)
mkFileSystemConfigProperty ::
Value Prelude.Text
-> Value Prelude.Text -> FileSystemConfigProperty
mkFileSystemConfigProperty :: Value Text -> Value Text -> FileSystemConfigProperty
mkFileSystemConfigProperty Value Text
arn Value Text
localMountPath
= FileSystemConfigProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), arn :: Value Text
arn = Value Text
arn,
localMountPath :: Value Text
localMountPath = Value Text
localMountPath}
instance ToResourceProperties FileSystemConfigProperty where
toResourceProperties :: FileSystemConfigProperty -> ResourceProperties
toResourceProperties FileSystemConfigProperty {()
Value Text
haddock_workaround_ :: FileSystemConfigProperty -> ()
arn :: FileSystemConfigProperty -> Value Text
localMountPath :: FileSystemConfigProperty -> Value Text
haddock_workaround_ :: ()
arn :: Value Text
localMountPath :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Lambda::Function.FileSystemConfig",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Arn" 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
arn,
Key
"LocalMountPath" 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
localMountPath]}
instance JSON.ToJSON FileSystemConfigProperty where
toJSON :: FileSystemConfigProperty -> Value
toJSON FileSystemConfigProperty {()
Value Text
haddock_workaround_ :: FileSystemConfigProperty -> ()
arn :: FileSystemConfigProperty -> Value Text
localMountPath :: FileSystemConfigProperty -> Value Text
haddock_workaround_ :: ()
arn :: Value Text
localMountPath :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"Arn" 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
arn, Key
"LocalMountPath" 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
localMountPath]
instance Property "Arn" FileSystemConfigProperty where
type PropertyType "Arn" FileSystemConfigProperty = Value Prelude.Text
set :: PropertyType "Arn" FileSystemConfigProperty
-> FileSystemConfigProperty -> FileSystemConfigProperty
set PropertyType "Arn" FileSystemConfigProperty
newValue FileSystemConfigProperty {()
Value Text
haddock_workaround_ :: FileSystemConfigProperty -> ()
arn :: FileSystemConfigProperty -> Value Text
localMountPath :: FileSystemConfigProperty -> Value Text
haddock_workaround_ :: ()
arn :: Value Text
localMountPath :: Value Text
..}
= FileSystemConfigProperty {arn :: Value Text
arn = PropertyType "Arn" FileSystemConfigProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
localMountPath :: Value Text
haddock_workaround_ :: ()
localMountPath :: Value Text
..}
instance Property "LocalMountPath" FileSystemConfigProperty where
type PropertyType "LocalMountPath" FileSystemConfigProperty = Value Prelude.Text
set :: PropertyType "LocalMountPath" FileSystemConfigProperty
-> FileSystemConfigProperty -> FileSystemConfigProperty
set PropertyType "LocalMountPath" FileSystemConfigProperty
newValue FileSystemConfigProperty {()
Value Text
haddock_workaround_ :: FileSystemConfigProperty -> ()
arn :: FileSystemConfigProperty -> Value Text
localMountPath :: FileSystemConfigProperty -> Value Text
haddock_workaround_ :: ()
arn :: Value Text
localMountPath :: Value Text
..}
= FileSystemConfigProperty {localMountPath :: Value Text
localMountPath = PropertyType "LocalMountPath" FileSystemConfigProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
arn :: Value Text
haddock_workaround_ :: ()
arn :: Value Text
..}