module Stratosphere.Bedrock.DataSource.IntermediateStorageProperty (
module Exports, IntermediateStorageProperty(..),
mkIntermediateStorageProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Bedrock.DataSource.S3LocationProperty as Exports
import Stratosphere.ResourceProperties
data IntermediateStorageProperty
=
IntermediateStorageProperty {IntermediateStorageProperty -> ()
haddock_workaround_ :: (),
IntermediateStorageProperty -> S3LocationProperty
s3Location :: S3LocationProperty}
deriving stock (IntermediateStorageProperty -> IntermediateStorageProperty -> Bool
(IntermediateStorageProperty
-> IntermediateStorageProperty -> Bool)
-> (IntermediateStorageProperty
-> IntermediateStorageProperty -> Bool)
-> Eq IntermediateStorageProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntermediateStorageProperty -> IntermediateStorageProperty -> Bool
== :: IntermediateStorageProperty -> IntermediateStorageProperty -> Bool
$c/= :: IntermediateStorageProperty -> IntermediateStorageProperty -> Bool
/= :: IntermediateStorageProperty -> IntermediateStorageProperty -> Bool
Prelude.Eq, Int -> IntermediateStorageProperty -> ShowS
[IntermediateStorageProperty] -> ShowS
IntermediateStorageProperty -> String
(Int -> IntermediateStorageProperty -> ShowS)
-> (IntermediateStorageProperty -> String)
-> ([IntermediateStorageProperty] -> ShowS)
-> Show IntermediateStorageProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IntermediateStorageProperty -> ShowS
showsPrec :: Int -> IntermediateStorageProperty -> ShowS
$cshow :: IntermediateStorageProperty -> String
show :: IntermediateStorageProperty -> String
$cshowList :: [IntermediateStorageProperty] -> ShowS
showList :: [IntermediateStorageProperty] -> ShowS
Prelude.Show)
mkIntermediateStorageProperty ::
S3LocationProperty -> IntermediateStorageProperty
mkIntermediateStorageProperty :: S3LocationProperty -> IntermediateStorageProperty
mkIntermediateStorageProperty S3LocationProperty
s3Location
= IntermediateStorageProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), s3Location :: S3LocationProperty
s3Location = S3LocationProperty
s3Location}
instance ToResourceProperties IntermediateStorageProperty where
toResourceProperties :: IntermediateStorageProperty -> ResourceProperties
toResourceProperties IntermediateStorageProperty {()
S3LocationProperty
haddock_workaround_ :: IntermediateStorageProperty -> ()
s3Location :: IntermediateStorageProperty -> S3LocationProperty
haddock_workaround_ :: ()
s3Location :: S3LocationProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Bedrock::DataSource.IntermediateStorage",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"S3Location" Key -> S3LocationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= S3LocationProperty
s3Location]}
instance JSON.ToJSON IntermediateStorageProperty where
toJSON :: IntermediateStorageProperty -> Value
toJSON IntermediateStorageProperty {()
S3LocationProperty
haddock_workaround_ :: IntermediateStorageProperty -> ()
s3Location :: IntermediateStorageProperty -> S3LocationProperty
haddock_workaround_ :: ()
s3Location :: S3LocationProperty
..}
= [(Key, Value)] -> Value
JSON.object [Key
"S3Location" Key -> S3LocationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= S3LocationProperty
s3Location]
instance Property "S3Location" IntermediateStorageProperty where
type PropertyType "S3Location" IntermediateStorageProperty = S3LocationProperty
set :: PropertyType "S3Location" IntermediateStorageProperty
-> IntermediateStorageProperty -> IntermediateStorageProperty
set PropertyType "S3Location" IntermediateStorageProperty
newValue IntermediateStorageProperty {()
S3LocationProperty
haddock_workaround_ :: IntermediateStorageProperty -> ()
s3Location :: IntermediateStorageProperty -> S3LocationProperty
haddock_workaround_ :: ()
s3Location :: S3LocationProperty
..}
= IntermediateStorageProperty {s3Location :: S3LocationProperty
s3Location = PropertyType "S3Location" IntermediateStorageProperty
S3LocationProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}