module Stratosphere.QuickSight.Template.FilterScopeConfigurationProperty (
        module Exports, FilterScopeConfigurationProperty(..),
        mkFilterScopeConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Template.SelectedSheetsFilterScopeConfigurationProperty as Exports
import Stratosphere.ResourceProperties
data FilterScopeConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-filterscopeconfiguration.html>
    FilterScopeConfigurationProperty {FilterScopeConfigurationProperty -> ()
haddock_workaround_ :: (),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-filterscopeconfiguration.html#cfn-quicksight-template-filterscopeconfiguration-allsheets>
                                      FilterScopeConfigurationProperty -> Maybe Object
allSheets :: (Prelude.Maybe JSON.Object),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-filterscopeconfiguration.html#cfn-quicksight-template-filterscopeconfiguration-selectedsheets>
                                      FilterScopeConfigurationProperty
-> Maybe SelectedSheetsFilterScopeConfigurationProperty
selectedSheets :: (Prelude.Maybe SelectedSheetsFilterScopeConfigurationProperty)}
  deriving stock (FilterScopeConfigurationProperty
-> FilterScopeConfigurationProperty -> Bool
(FilterScopeConfigurationProperty
 -> FilterScopeConfigurationProperty -> Bool)
-> (FilterScopeConfigurationProperty
    -> FilterScopeConfigurationProperty -> Bool)
-> Eq FilterScopeConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FilterScopeConfigurationProperty
-> FilterScopeConfigurationProperty -> Bool
== :: FilterScopeConfigurationProperty
-> FilterScopeConfigurationProperty -> Bool
$c/= :: FilterScopeConfigurationProperty
-> FilterScopeConfigurationProperty -> Bool
/= :: FilterScopeConfigurationProperty
-> FilterScopeConfigurationProperty -> Bool
Prelude.Eq, Int -> FilterScopeConfigurationProperty -> ShowS
[FilterScopeConfigurationProperty] -> ShowS
FilterScopeConfigurationProperty -> String
(Int -> FilterScopeConfigurationProperty -> ShowS)
-> (FilterScopeConfigurationProperty -> String)
-> ([FilterScopeConfigurationProperty] -> ShowS)
-> Show FilterScopeConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FilterScopeConfigurationProperty -> ShowS
showsPrec :: Int -> FilterScopeConfigurationProperty -> ShowS
$cshow :: FilterScopeConfigurationProperty -> String
show :: FilterScopeConfigurationProperty -> String
$cshowList :: [FilterScopeConfigurationProperty] -> ShowS
showList :: [FilterScopeConfigurationProperty] -> ShowS
Prelude.Show)
mkFilterScopeConfigurationProperty ::
  FilterScopeConfigurationProperty
mkFilterScopeConfigurationProperty :: FilterScopeConfigurationProperty
mkFilterScopeConfigurationProperty
  = FilterScopeConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), allSheets :: Maybe Object
allSheets = Maybe Object
forall a. Maybe a
Prelude.Nothing,
       selectedSheets :: Maybe SelectedSheetsFilterScopeConfigurationProperty
selectedSheets = Maybe SelectedSheetsFilterScopeConfigurationProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties FilterScopeConfigurationProperty where
  toResourceProperties :: FilterScopeConfigurationProperty -> ResourceProperties
toResourceProperties FilterScopeConfigurationProperty {Maybe Object
Maybe SelectedSheetsFilterScopeConfigurationProperty
()
haddock_workaround_ :: FilterScopeConfigurationProperty -> ()
allSheets :: FilterScopeConfigurationProperty -> Maybe Object
selectedSheets :: FilterScopeConfigurationProperty
-> Maybe SelectedSheetsFilterScopeConfigurationProperty
haddock_workaround_ :: ()
allSheets :: Maybe Object
selectedSheets :: Maybe SelectedSheetsFilterScopeConfigurationProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::QuickSight::Template.FilterScopeConfiguration",
         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 -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AllSheets" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
allSheets,
                            Key
-> SelectedSheetsFilterScopeConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SelectedSheets" (SelectedSheetsFilterScopeConfigurationProperty -> (Key, Value))
-> Maybe SelectedSheetsFilterScopeConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SelectedSheetsFilterScopeConfigurationProperty
selectedSheets])}
instance JSON.ToJSON FilterScopeConfigurationProperty where
  toJSON :: FilterScopeConfigurationProperty -> Value
toJSON FilterScopeConfigurationProperty {Maybe Object
Maybe SelectedSheetsFilterScopeConfigurationProperty
()
haddock_workaround_ :: FilterScopeConfigurationProperty -> ()
allSheets :: FilterScopeConfigurationProperty -> Maybe Object
selectedSheets :: FilterScopeConfigurationProperty
-> Maybe SelectedSheetsFilterScopeConfigurationProperty
haddock_workaround_ :: ()
allSheets :: Maybe Object
selectedSheets :: Maybe SelectedSheetsFilterScopeConfigurationProperty
..}
    = [(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 -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AllSheets" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
allSheets,
               Key
-> SelectedSheetsFilterScopeConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SelectedSheets" (SelectedSheetsFilterScopeConfigurationProperty -> (Key, Value))
-> Maybe SelectedSheetsFilterScopeConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SelectedSheetsFilterScopeConfigurationProperty
selectedSheets]))
instance Property "AllSheets" FilterScopeConfigurationProperty where
  type PropertyType "AllSheets" FilterScopeConfigurationProperty = JSON.Object
  set :: PropertyType "AllSheets" FilterScopeConfigurationProperty
-> FilterScopeConfigurationProperty
-> FilterScopeConfigurationProperty
set PropertyType "AllSheets" FilterScopeConfigurationProperty
newValue FilterScopeConfigurationProperty {Maybe Object
Maybe SelectedSheetsFilterScopeConfigurationProperty
()
haddock_workaround_ :: FilterScopeConfigurationProperty -> ()
allSheets :: FilterScopeConfigurationProperty -> Maybe Object
selectedSheets :: FilterScopeConfigurationProperty
-> Maybe SelectedSheetsFilterScopeConfigurationProperty
haddock_workaround_ :: ()
allSheets :: Maybe Object
selectedSheets :: Maybe SelectedSheetsFilterScopeConfigurationProperty
..}
    = FilterScopeConfigurationProperty
        {allSheets :: Maybe Object
allSheets = Object -> Maybe Object
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Object
PropertyType "AllSheets" FilterScopeConfigurationProperty
newValue, Maybe SelectedSheetsFilterScopeConfigurationProperty
()
haddock_workaround_ :: ()
selectedSheets :: Maybe SelectedSheetsFilterScopeConfigurationProperty
haddock_workaround_ :: ()
selectedSheets :: Maybe SelectedSheetsFilterScopeConfigurationProperty
..}
instance Property "SelectedSheets" FilterScopeConfigurationProperty where
  type PropertyType "SelectedSheets" FilterScopeConfigurationProperty = SelectedSheetsFilterScopeConfigurationProperty
  set :: PropertyType "SelectedSheets" FilterScopeConfigurationProperty
-> FilterScopeConfigurationProperty
-> FilterScopeConfigurationProperty
set PropertyType "SelectedSheets" FilterScopeConfigurationProperty
newValue FilterScopeConfigurationProperty {Maybe Object
Maybe SelectedSheetsFilterScopeConfigurationProperty
()
haddock_workaround_ :: FilterScopeConfigurationProperty -> ()
allSheets :: FilterScopeConfigurationProperty -> Maybe Object
selectedSheets :: FilterScopeConfigurationProperty
-> Maybe SelectedSheetsFilterScopeConfigurationProperty
haddock_workaround_ :: ()
allSheets :: Maybe Object
selectedSheets :: Maybe SelectedSheetsFilterScopeConfigurationProperty
..}
    = FilterScopeConfigurationProperty
        {selectedSheets :: Maybe SelectedSheetsFilterScopeConfigurationProperty
selectedSheets = SelectedSheetsFilterScopeConfigurationProperty
-> Maybe SelectedSheetsFilterScopeConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SelectedSheets" FilterScopeConfigurationProperty
SelectedSheetsFilterScopeConfigurationProperty
newValue, Maybe Object
()
haddock_workaround_ :: ()
allSheets :: Maybe Object
haddock_workaround_ :: ()
allSheets :: Maybe Object
..}