module Stratosphere.QuickSight.Dashboard.NumericRangeFilterProperty (
module Exports, NumericRangeFilterProperty(..),
mkNumericRangeFilterProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.AggregationFunctionProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.ColumnIdentifierProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.DefaultFilterControlConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.NumericRangeFilterValueProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data NumericRangeFilterProperty
=
NumericRangeFilterProperty {NumericRangeFilterProperty -> ()
haddock_workaround_ :: (),
NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
aggregationFunction :: (Prelude.Maybe AggregationFunctionProperty),
NumericRangeFilterProperty -> ColumnIdentifierProperty
column :: ColumnIdentifierProperty,
NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
defaultFilterControlConfiguration :: (Prelude.Maybe DefaultFilterControlConfigurationProperty),
NumericRangeFilterProperty -> Value Text
filterId :: (Value Prelude.Text),
NumericRangeFilterProperty -> Maybe (Value Bool)
includeMaximum :: (Prelude.Maybe (Value Prelude.Bool)),
NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: (Prelude.Maybe (Value Prelude.Bool)),
NumericRangeFilterProperty -> Value Text
nullOption :: (Value Prelude.Text),
NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMaximum :: (Prelude.Maybe NumericRangeFilterValueProperty),
NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: (Prelude.Maybe NumericRangeFilterValueProperty),
NumericRangeFilterProperty -> Maybe (Value Text)
selectAllOptions :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (NumericRangeFilterProperty -> NumericRangeFilterProperty -> Bool
(NumericRangeFilterProperty -> NumericRangeFilterProperty -> Bool)
-> (NumericRangeFilterProperty
-> NumericRangeFilterProperty -> Bool)
-> Eq NumericRangeFilterProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NumericRangeFilterProperty -> NumericRangeFilterProperty -> Bool
== :: NumericRangeFilterProperty -> NumericRangeFilterProperty -> Bool
$c/= :: NumericRangeFilterProperty -> NumericRangeFilterProperty -> Bool
/= :: NumericRangeFilterProperty -> NumericRangeFilterProperty -> Bool
Prelude.Eq, Int -> NumericRangeFilterProperty -> ShowS
[NumericRangeFilterProperty] -> ShowS
NumericRangeFilterProperty -> String
(Int -> NumericRangeFilterProperty -> ShowS)
-> (NumericRangeFilterProperty -> String)
-> ([NumericRangeFilterProperty] -> ShowS)
-> Show NumericRangeFilterProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NumericRangeFilterProperty -> ShowS
showsPrec :: Int -> NumericRangeFilterProperty -> ShowS
$cshow :: NumericRangeFilterProperty -> String
show :: NumericRangeFilterProperty -> String
$cshowList :: [NumericRangeFilterProperty] -> ShowS
showList :: [NumericRangeFilterProperty] -> ShowS
Prelude.Show)
mkNumericRangeFilterProperty ::
ColumnIdentifierProperty
-> Value Prelude.Text
-> Value Prelude.Text -> NumericRangeFilterProperty
mkNumericRangeFilterProperty :: ColumnIdentifierProperty
-> Value Text -> Value Text -> NumericRangeFilterProperty
mkNumericRangeFilterProperty ColumnIdentifierProperty
column Value Text
filterId Value Text
nullOption
= NumericRangeFilterProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), column :: ColumnIdentifierProperty
column = ColumnIdentifierProperty
column, filterId :: Value Text
filterId = Value Text
filterId,
nullOption :: Value Text
nullOption = Value Text
nullOption, aggregationFunction :: Maybe AggregationFunctionProperty
aggregationFunction = Maybe AggregationFunctionProperty
forall a. Maybe a
Prelude.Nothing,
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
defaultFilterControlConfiguration = Maybe DefaultFilterControlConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
includeMaximum :: Maybe (Value Bool)
includeMaximum = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing, includeMinimum :: Maybe (Value Bool)
includeMinimum = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMaximum = Maybe NumericRangeFilterValueProperty
forall a. Maybe a
Prelude.Nothing, rangeMinimum :: Maybe NumericRangeFilterValueProperty
rangeMinimum = Maybe NumericRangeFilterValueProperty
forall a. Maybe a
Prelude.Nothing,
selectAllOptions :: Maybe (Value Text)
selectAllOptions = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties NumericRangeFilterProperty where
toResourceProperties :: NumericRangeFilterProperty -> ResourceProperties
toResourceProperties NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::QuickSight::Dashboard.NumericRangeFilter",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Column" Key -> ColumnIdentifierProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ColumnIdentifierProperty
column, Key
"FilterId" 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
filterId,
Key
"NullOption" 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
nullOption]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> AggregationFunctionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AggregationFunction" (AggregationFunctionProperty -> (Key, Value))
-> Maybe AggregationFunctionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AggregationFunctionProperty
aggregationFunction,
Key -> DefaultFilterControlConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DefaultFilterControlConfiguration"
(DefaultFilterControlConfigurationProperty -> (Key, Value))
-> Maybe DefaultFilterControlConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DefaultFilterControlConfigurationProperty
defaultFilterControlConfiguration,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IncludeMaximum" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
includeMaximum,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IncludeMinimum" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
includeMinimum,
Key -> NumericRangeFilterValueProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RangeMaximum" (NumericRangeFilterValueProperty -> (Key, Value))
-> Maybe NumericRangeFilterValueProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NumericRangeFilterValueProperty
rangeMaximum,
Key -> NumericRangeFilterValueProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RangeMinimum" (NumericRangeFilterValueProperty -> (Key, Value))
-> Maybe NumericRangeFilterValueProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NumericRangeFilterValueProperty
rangeMinimum,
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
"SelectAllOptions" (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)
selectAllOptions]))}
instance JSON.ToJSON NumericRangeFilterProperty where
toJSON :: NumericRangeFilterProperty -> Value
toJSON NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Column" Key -> ColumnIdentifierProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ColumnIdentifierProperty
column, Key
"FilterId" 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
filterId,
Key
"NullOption" 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
nullOption]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> AggregationFunctionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AggregationFunction" (AggregationFunctionProperty -> (Key, Value))
-> Maybe AggregationFunctionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AggregationFunctionProperty
aggregationFunction,
Key -> DefaultFilterControlConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DefaultFilterControlConfiguration"
(DefaultFilterControlConfigurationProperty -> (Key, Value))
-> Maybe DefaultFilterControlConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DefaultFilterControlConfigurationProperty
defaultFilterControlConfiguration,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IncludeMaximum" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
includeMaximum,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IncludeMinimum" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
includeMinimum,
Key -> NumericRangeFilterValueProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RangeMaximum" (NumericRangeFilterValueProperty -> (Key, Value))
-> Maybe NumericRangeFilterValueProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NumericRangeFilterValueProperty
rangeMaximum,
Key -> NumericRangeFilterValueProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RangeMinimum" (NumericRangeFilterValueProperty -> (Key, Value))
-> Maybe NumericRangeFilterValueProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NumericRangeFilterValueProperty
rangeMinimum,
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
"SelectAllOptions" (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)
selectAllOptions])))
instance Property "AggregationFunction" NumericRangeFilterProperty where
type PropertyType "AggregationFunction" NumericRangeFilterProperty = AggregationFunctionProperty
set :: PropertyType "AggregationFunction" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType "AggregationFunction" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty
{aggregationFunction :: Maybe AggregationFunctionProperty
aggregationFunction = AggregationFunctionProperty -> Maybe AggregationFunctionProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AggregationFunction" NumericRangeFilterProperty
AggregationFunctionProperty
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: ()
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
haddock_workaround_ :: ()
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
instance Property "Column" NumericRangeFilterProperty where
type PropertyType "Column" NumericRangeFilterProperty = ColumnIdentifierProperty
set :: PropertyType "Column" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType "Column" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty {column :: ColumnIdentifierProperty
column = PropertyType "Column" NumericRangeFilterProperty
ColumnIdentifierProperty
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
instance Property "DefaultFilterControlConfiguration" NumericRangeFilterProperty where
type PropertyType "DefaultFilterControlConfiguration" NumericRangeFilterProperty = DefaultFilterControlConfigurationProperty
set :: PropertyType
"DefaultFilterControlConfiguration" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType
"DefaultFilterControlConfiguration" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty
{defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
defaultFilterControlConfiguration = DefaultFilterControlConfigurationProperty
-> Maybe DefaultFilterControlConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"DefaultFilterControlConfiguration" NumericRangeFilterProperty
DefaultFilterControlConfigurationProperty
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
instance Property "FilterId" NumericRangeFilterProperty where
type PropertyType "FilterId" NumericRangeFilterProperty = Value Prelude.Text
set :: PropertyType "FilterId" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType "FilterId" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty {filterId :: Value Text
filterId = PropertyType "FilterId" NumericRangeFilterProperty
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
instance Property "IncludeMaximum" NumericRangeFilterProperty where
type PropertyType "IncludeMaximum" NumericRangeFilterProperty = Value Prelude.Bool
set :: PropertyType "IncludeMaximum" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType "IncludeMaximum" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty
{includeMaximum :: Maybe (Value Bool)
includeMaximum = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IncludeMaximum" NumericRangeFilterProperty
Value Bool
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
instance Property "IncludeMinimum" NumericRangeFilterProperty where
type PropertyType "IncludeMinimum" NumericRangeFilterProperty = Value Prelude.Bool
set :: PropertyType "IncludeMinimum" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType "IncludeMinimum" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty
{includeMinimum :: Maybe (Value Bool)
includeMinimum = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IncludeMinimum" NumericRangeFilterProperty
Value Bool
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
instance Property "NullOption" NumericRangeFilterProperty where
type PropertyType "NullOption" NumericRangeFilterProperty = Value Prelude.Text
set :: PropertyType "NullOption" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType "NullOption" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty {nullOption :: Value Text
nullOption = PropertyType "NullOption" NumericRangeFilterProperty
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
instance Property "RangeMaximum" NumericRangeFilterProperty where
type PropertyType "RangeMaximum" NumericRangeFilterProperty = NumericRangeFilterValueProperty
set :: PropertyType "RangeMaximum" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType "RangeMaximum" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty
{rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMaximum = NumericRangeFilterValueProperty
-> Maybe NumericRangeFilterValueProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RangeMaximum" NumericRangeFilterProperty
NumericRangeFilterValueProperty
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
instance Property "RangeMinimum" NumericRangeFilterProperty where
type PropertyType "RangeMinimum" NumericRangeFilterProperty = NumericRangeFilterValueProperty
set :: PropertyType "RangeMinimum" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType "RangeMinimum" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty
{rangeMinimum :: Maybe NumericRangeFilterValueProperty
rangeMinimum = NumericRangeFilterValueProperty
-> Maybe NumericRangeFilterValueProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RangeMinimum" NumericRangeFilterProperty
NumericRangeFilterValueProperty
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
instance Property "SelectAllOptions" NumericRangeFilterProperty where
type PropertyType "SelectAllOptions" NumericRangeFilterProperty = Value Prelude.Text
set :: PropertyType "SelectAllOptions" NumericRangeFilterProperty
-> NumericRangeFilterProperty -> NumericRangeFilterProperty
set PropertyType "SelectAllOptions" NumericRangeFilterProperty
newValue NumericRangeFilterProperty {Maybe (Value Bool)
Maybe (Value Text)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: NumericRangeFilterProperty -> ()
aggregationFunction :: NumericRangeFilterProperty -> Maybe AggregationFunctionProperty
column :: NumericRangeFilterProperty -> ColumnIdentifierProperty
defaultFilterControlConfiguration :: NumericRangeFilterProperty
-> Maybe DefaultFilterControlConfigurationProperty
filterId :: NumericRangeFilterProperty -> Value Text
includeMaximum :: NumericRangeFilterProperty -> Maybe (Value Bool)
includeMinimum :: NumericRangeFilterProperty -> Maybe (Value Bool)
nullOption :: NumericRangeFilterProperty -> Value Text
rangeMaximum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
rangeMinimum :: NumericRangeFilterProperty -> Maybe NumericRangeFilterValueProperty
selectAllOptions :: NumericRangeFilterProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
selectAllOptions :: Maybe (Value Text)
..}
= NumericRangeFilterProperty
{selectAllOptions :: Maybe (Value Text)
selectAllOptions = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SelectAllOptions" NumericRangeFilterProperty
Value Text
newValue, Maybe (Value Bool)
Maybe NumericRangeFilterValueProperty
Maybe AggregationFunctionProperty
Maybe DefaultFilterControlConfigurationProperty
()
Value Text
ColumnIdentifierProperty
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
haddock_workaround_ :: ()
aggregationFunction :: Maybe AggregationFunctionProperty
column :: ColumnIdentifierProperty
defaultFilterControlConfiguration :: Maybe DefaultFilterControlConfigurationProperty
filterId :: Value Text
includeMaximum :: Maybe (Value Bool)
includeMinimum :: Maybe (Value Bool)
nullOption :: Value Text
rangeMaximum :: Maybe NumericRangeFilterValueProperty
rangeMinimum :: Maybe NumericRangeFilterValueProperty
..}