module Stratosphere.EFS.AccessPoint.RootDirectoryProperty (
module Exports, RootDirectoryProperty(..), mkRootDirectoryProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.EFS.AccessPoint.CreationInfoProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RootDirectoryProperty
=
RootDirectoryProperty {RootDirectoryProperty -> ()
haddock_workaround_ :: (),
RootDirectoryProperty -> Maybe CreationInfoProperty
creationInfo :: (Prelude.Maybe CreationInfoProperty),
RootDirectoryProperty -> Maybe (Value Text)
path :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (RootDirectoryProperty -> RootDirectoryProperty -> Bool
(RootDirectoryProperty -> RootDirectoryProperty -> Bool)
-> (RootDirectoryProperty -> RootDirectoryProperty -> Bool)
-> Eq RootDirectoryProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RootDirectoryProperty -> RootDirectoryProperty -> Bool
== :: RootDirectoryProperty -> RootDirectoryProperty -> Bool
$c/= :: RootDirectoryProperty -> RootDirectoryProperty -> Bool
/= :: RootDirectoryProperty -> RootDirectoryProperty -> Bool
Prelude.Eq, Int -> RootDirectoryProperty -> ShowS
[RootDirectoryProperty] -> ShowS
RootDirectoryProperty -> String
(Int -> RootDirectoryProperty -> ShowS)
-> (RootDirectoryProperty -> String)
-> ([RootDirectoryProperty] -> ShowS)
-> Show RootDirectoryProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RootDirectoryProperty -> ShowS
showsPrec :: Int -> RootDirectoryProperty -> ShowS
$cshow :: RootDirectoryProperty -> String
show :: RootDirectoryProperty -> String
$cshowList :: [RootDirectoryProperty] -> ShowS
showList :: [RootDirectoryProperty] -> ShowS
Prelude.Show)
mkRootDirectoryProperty :: RootDirectoryProperty
mkRootDirectoryProperty :: RootDirectoryProperty
mkRootDirectoryProperty
= RootDirectoryProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), creationInfo :: Maybe CreationInfoProperty
creationInfo = Maybe CreationInfoProperty
forall a. Maybe a
Prelude.Nothing,
path :: Maybe (Value Text)
path = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties RootDirectoryProperty where
toResourceProperties :: RootDirectoryProperty -> ResourceProperties
toResourceProperties RootDirectoryProperty {Maybe (Value Text)
Maybe CreationInfoProperty
()
haddock_workaround_ :: RootDirectoryProperty -> ()
creationInfo :: RootDirectoryProperty -> Maybe CreationInfoProperty
path :: RootDirectoryProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
creationInfo :: Maybe CreationInfoProperty
path :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::EFS::AccessPoint.RootDirectory",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CreationInfoProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CreationInfo" (CreationInfoProperty -> (Key, Value))
-> Maybe CreationInfoProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CreationInfoProperty
creationInfo,
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..=) Key
"Path" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
path])}
instance JSON.ToJSON RootDirectoryProperty where
toJSON :: RootDirectoryProperty -> Value
toJSON RootDirectoryProperty {Maybe (Value Text)
Maybe CreationInfoProperty
()
haddock_workaround_ :: RootDirectoryProperty -> ()
creationInfo :: RootDirectoryProperty -> Maybe CreationInfoProperty
path :: RootDirectoryProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
creationInfo :: Maybe CreationInfoProperty
path :: Maybe (Value Text)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CreationInfoProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CreationInfo" (CreationInfoProperty -> (Key, Value))
-> Maybe CreationInfoProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CreationInfoProperty
creationInfo,
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..=) Key
"Path" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
path]))
instance Property "CreationInfo" RootDirectoryProperty where
type PropertyType "CreationInfo" RootDirectoryProperty = CreationInfoProperty
set :: PropertyType "CreationInfo" RootDirectoryProperty
-> RootDirectoryProperty -> RootDirectoryProperty
set PropertyType "CreationInfo" RootDirectoryProperty
newValue RootDirectoryProperty {Maybe (Value Text)
Maybe CreationInfoProperty
()
haddock_workaround_ :: RootDirectoryProperty -> ()
creationInfo :: RootDirectoryProperty -> Maybe CreationInfoProperty
path :: RootDirectoryProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
creationInfo :: Maybe CreationInfoProperty
path :: Maybe (Value Text)
..}
= RootDirectoryProperty {creationInfo :: Maybe CreationInfoProperty
creationInfo = CreationInfoProperty -> Maybe CreationInfoProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CreationInfo" RootDirectoryProperty
CreationInfoProperty
newValue, Maybe (Value Text)
()
haddock_workaround_ :: ()
path :: Maybe (Value Text)
haddock_workaround_ :: ()
path :: Maybe (Value Text)
..}
instance Property "Path" RootDirectoryProperty where
type PropertyType "Path" RootDirectoryProperty = Value Prelude.Text
set :: PropertyType "Path" RootDirectoryProperty
-> RootDirectoryProperty -> RootDirectoryProperty
set PropertyType "Path" RootDirectoryProperty
newValue RootDirectoryProperty {Maybe (Value Text)
Maybe CreationInfoProperty
()
haddock_workaround_ :: RootDirectoryProperty -> ()
creationInfo :: RootDirectoryProperty -> Maybe CreationInfoProperty
path :: RootDirectoryProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
creationInfo :: Maybe CreationInfoProperty
path :: Maybe (Value Text)
..}
= RootDirectoryProperty {path :: Maybe (Value Text)
path = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Path" RootDirectoryProperty
Value Text
newValue, Maybe CreationInfoProperty
()
haddock_workaround_ :: ()
creationInfo :: Maybe CreationInfoProperty
haddock_workaround_ :: ()
creationInfo :: Maybe CreationInfoProperty
..}