module Stratosphere.Athena.WorkGroup.ResultConfigurationProperty (
module Exports, ResultConfigurationProperty(..),
mkResultConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Athena.WorkGroup.AclConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Athena.WorkGroup.EncryptionConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ResultConfigurationProperty
=
ResultConfigurationProperty {ResultConfigurationProperty -> ()
haddock_workaround_ :: (),
ResultConfigurationProperty -> Maybe AclConfigurationProperty
aclConfiguration :: (Prelude.Maybe AclConfigurationProperty),
ResultConfigurationProperty
-> Maybe EncryptionConfigurationProperty
encryptionConfiguration :: (Prelude.Maybe EncryptionConfigurationProperty),
ResultConfigurationProperty -> Maybe (Value Text)
expectedBucketOwner :: (Prelude.Maybe (Value Prelude.Text)),
ResultConfigurationProperty -> Maybe (Value Text)
outputLocation :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (ResultConfigurationProperty -> ResultConfigurationProperty -> Bool
(ResultConfigurationProperty
-> ResultConfigurationProperty -> Bool)
-> (ResultConfigurationProperty
-> ResultConfigurationProperty -> Bool)
-> Eq ResultConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResultConfigurationProperty -> ResultConfigurationProperty -> Bool
== :: ResultConfigurationProperty -> ResultConfigurationProperty -> Bool
$c/= :: ResultConfigurationProperty -> ResultConfigurationProperty -> Bool
/= :: ResultConfigurationProperty -> ResultConfigurationProperty -> Bool
Prelude.Eq, Int -> ResultConfigurationProperty -> ShowS
[ResultConfigurationProperty] -> ShowS
ResultConfigurationProperty -> String
(Int -> ResultConfigurationProperty -> ShowS)
-> (ResultConfigurationProperty -> String)
-> ([ResultConfigurationProperty] -> ShowS)
-> Show ResultConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResultConfigurationProperty -> ShowS
showsPrec :: Int -> ResultConfigurationProperty -> ShowS
$cshow :: ResultConfigurationProperty -> String
show :: ResultConfigurationProperty -> String
$cshowList :: [ResultConfigurationProperty] -> ShowS
showList :: [ResultConfigurationProperty] -> ShowS
Prelude.Show)
mkResultConfigurationProperty :: ResultConfigurationProperty
mkResultConfigurationProperty :: ResultConfigurationProperty
mkResultConfigurationProperty
= ResultConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), aclConfiguration :: Maybe AclConfigurationProperty
aclConfiguration = Maybe AclConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
encryptionConfiguration = Maybe EncryptionConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
expectedBucketOwner :: Maybe (Value Text)
expectedBucketOwner = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
outputLocation :: Maybe (Value Text)
outputLocation = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ResultConfigurationProperty where
toResourceProperties :: ResultConfigurationProperty -> ResourceProperties
toResourceProperties ResultConfigurationProperty {Maybe (Value Text)
Maybe AclConfigurationProperty
Maybe EncryptionConfigurationProperty
()
haddock_workaround_ :: ResultConfigurationProperty -> ()
aclConfiguration :: ResultConfigurationProperty -> Maybe AclConfigurationProperty
encryptionConfiguration :: ResultConfigurationProperty
-> Maybe EncryptionConfigurationProperty
expectedBucketOwner :: ResultConfigurationProperty -> Maybe (Value Text)
outputLocation :: ResultConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Athena::WorkGroup.ResultConfiguration",
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 -> AclConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AclConfiguration" (AclConfigurationProperty -> (Key, Value))
-> Maybe AclConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AclConfigurationProperty
aclConfiguration,
Key -> EncryptionConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EncryptionConfiguration"
(EncryptionConfigurationProperty -> (Key, Value))
-> Maybe EncryptionConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EncryptionConfigurationProperty
encryptionConfiguration,
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
"ExpectedBucketOwner" (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)
expectedBucketOwner,
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
"OutputLocation" (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)
outputLocation])}
instance JSON.ToJSON ResultConfigurationProperty where
toJSON :: ResultConfigurationProperty -> Value
toJSON ResultConfigurationProperty {Maybe (Value Text)
Maybe AclConfigurationProperty
Maybe EncryptionConfigurationProperty
()
haddock_workaround_ :: ResultConfigurationProperty -> ()
aclConfiguration :: ResultConfigurationProperty -> Maybe AclConfigurationProperty
encryptionConfiguration :: ResultConfigurationProperty
-> Maybe EncryptionConfigurationProperty
expectedBucketOwner :: ResultConfigurationProperty -> Maybe (Value Text)
outputLocation :: ResultConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: 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 -> AclConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AclConfiguration" (AclConfigurationProperty -> (Key, Value))
-> Maybe AclConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AclConfigurationProperty
aclConfiguration,
Key -> EncryptionConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EncryptionConfiguration"
(EncryptionConfigurationProperty -> (Key, Value))
-> Maybe EncryptionConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EncryptionConfigurationProperty
encryptionConfiguration,
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
"ExpectedBucketOwner" (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)
expectedBucketOwner,
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
"OutputLocation" (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)
outputLocation]))
instance Property "AclConfiguration" ResultConfigurationProperty where
type PropertyType "AclConfiguration" ResultConfigurationProperty = AclConfigurationProperty
set :: PropertyType "AclConfiguration" ResultConfigurationProperty
-> ResultConfigurationProperty -> ResultConfigurationProperty
set PropertyType "AclConfiguration" ResultConfigurationProperty
newValue ResultConfigurationProperty {Maybe (Value Text)
Maybe AclConfigurationProperty
Maybe EncryptionConfigurationProperty
()
haddock_workaround_ :: ResultConfigurationProperty -> ()
aclConfiguration :: ResultConfigurationProperty -> Maybe AclConfigurationProperty
encryptionConfiguration :: ResultConfigurationProperty
-> Maybe EncryptionConfigurationProperty
expectedBucketOwner :: ResultConfigurationProperty -> Maybe (Value Text)
outputLocation :: ResultConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: Maybe (Value Text)
..}
= ResultConfigurationProperty
{aclConfiguration :: Maybe AclConfigurationProperty
aclConfiguration = AclConfigurationProperty -> Maybe AclConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AclConfiguration" ResultConfigurationProperty
AclConfigurationProperty
newValue, Maybe (Value Text)
Maybe EncryptionConfigurationProperty
()
haddock_workaround_ :: ()
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: Maybe (Value Text)
haddock_workaround_ :: ()
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: Maybe (Value Text)
..}
instance Property "EncryptionConfiguration" ResultConfigurationProperty where
type PropertyType "EncryptionConfiguration" ResultConfigurationProperty = EncryptionConfigurationProperty
set :: PropertyType "EncryptionConfiguration" ResultConfigurationProperty
-> ResultConfigurationProperty -> ResultConfigurationProperty
set PropertyType "EncryptionConfiguration" ResultConfigurationProperty
newValue ResultConfigurationProperty {Maybe (Value Text)
Maybe AclConfigurationProperty
Maybe EncryptionConfigurationProperty
()
haddock_workaround_ :: ResultConfigurationProperty -> ()
aclConfiguration :: ResultConfigurationProperty -> Maybe AclConfigurationProperty
encryptionConfiguration :: ResultConfigurationProperty
-> Maybe EncryptionConfigurationProperty
expectedBucketOwner :: ResultConfigurationProperty -> Maybe (Value Text)
outputLocation :: ResultConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: Maybe (Value Text)
..}
= ResultConfigurationProperty
{encryptionConfiguration :: Maybe EncryptionConfigurationProperty
encryptionConfiguration = EncryptionConfigurationProperty
-> Maybe EncryptionConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EncryptionConfiguration" ResultConfigurationProperty
EncryptionConfigurationProperty
newValue, Maybe (Value Text)
Maybe AclConfigurationProperty
()
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: Maybe (Value Text)
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: Maybe (Value Text)
..}
instance Property "ExpectedBucketOwner" ResultConfigurationProperty where
type PropertyType "ExpectedBucketOwner" ResultConfigurationProperty = Value Prelude.Text
set :: PropertyType "ExpectedBucketOwner" ResultConfigurationProperty
-> ResultConfigurationProperty -> ResultConfigurationProperty
set PropertyType "ExpectedBucketOwner" ResultConfigurationProperty
newValue ResultConfigurationProperty {Maybe (Value Text)
Maybe AclConfigurationProperty
Maybe EncryptionConfigurationProperty
()
haddock_workaround_ :: ResultConfigurationProperty -> ()
aclConfiguration :: ResultConfigurationProperty -> Maybe AclConfigurationProperty
encryptionConfiguration :: ResultConfigurationProperty
-> Maybe EncryptionConfigurationProperty
expectedBucketOwner :: ResultConfigurationProperty -> Maybe (Value Text)
outputLocation :: ResultConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: Maybe (Value Text)
..}
= ResultConfigurationProperty
{expectedBucketOwner :: Maybe (Value Text)
expectedBucketOwner = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ExpectedBucketOwner" ResultConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe AclConfigurationProperty
Maybe EncryptionConfigurationProperty
()
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
outputLocation :: Maybe (Value Text)
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
outputLocation :: Maybe (Value Text)
..}
instance Property "OutputLocation" ResultConfigurationProperty where
type PropertyType "OutputLocation" ResultConfigurationProperty = Value Prelude.Text
set :: PropertyType "OutputLocation" ResultConfigurationProperty
-> ResultConfigurationProperty -> ResultConfigurationProperty
set PropertyType "OutputLocation" ResultConfigurationProperty
newValue ResultConfigurationProperty {Maybe (Value Text)
Maybe AclConfigurationProperty
Maybe EncryptionConfigurationProperty
()
haddock_workaround_ :: ResultConfigurationProperty -> ()
aclConfiguration :: ResultConfigurationProperty -> Maybe AclConfigurationProperty
encryptionConfiguration :: ResultConfigurationProperty
-> Maybe EncryptionConfigurationProperty
expectedBucketOwner :: ResultConfigurationProperty -> Maybe (Value Text)
outputLocation :: ResultConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
outputLocation :: Maybe (Value Text)
..}
= ResultConfigurationProperty
{outputLocation :: Maybe (Value Text)
outputLocation = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "OutputLocation" ResultConfigurationProperty
Value Text
newValue, Maybe (Value Text)
Maybe AclConfigurationProperty
Maybe EncryptionConfigurationProperty
()
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
haddock_workaround_ :: ()
aclConfiguration :: Maybe AclConfigurationProperty
encryptionConfiguration :: Maybe EncryptionConfigurationProperty
expectedBucketOwner :: Maybe (Value Text)
..}