{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.QuickSight.Types.ColumnSort
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.QuickSight.Types.ColumnSort where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.QuickSight.Types.AggregationFunction
import Amazonka.QuickSight.Types.ColumnIdentifier
import Amazonka.QuickSight.Types.SortDirection

-- | The sort configuration for a column that is not used in a field well.
--
-- /See:/ 'newColumnSort' smart constructor.
data ColumnSort = ColumnSort'
  { -- | The aggregation function that is defined in the column sort.
    ColumnSort -> Maybe AggregationFunction
aggregationFunction :: Prelude.Maybe AggregationFunction,
    ColumnSort -> ColumnIdentifier
sortBy :: ColumnIdentifier,
    -- | The sort direction.
    ColumnSort -> SortDirection
direction :: SortDirection
  }
  deriving (ColumnSort -> ColumnSort -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColumnSort -> ColumnSort -> Bool
$c/= :: ColumnSort -> ColumnSort -> Bool
== :: ColumnSort -> ColumnSort -> Bool
$c== :: ColumnSort -> ColumnSort -> Bool
Prelude.Eq, ReadPrec [ColumnSort]
ReadPrec ColumnSort
Int -> ReadS ColumnSort
ReadS [ColumnSort]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ColumnSort]
$creadListPrec :: ReadPrec [ColumnSort]
readPrec :: ReadPrec ColumnSort
$creadPrec :: ReadPrec ColumnSort
readList :: ReadS [ColumnSort]
$creadList :: ReadS [ColumnSort]
readsPrec :: Int -> ReadS ColumnSort
$creadsPrec :: Int -> ReadS ColumnSort
Prelude.Read, Int -> ColumnSort -> ShowS
[ColumnSort] -> ShowS
ColumnSort -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColumnSort] -> ShowS
$cshowList :: [ColumnSort] -> ShowS
show :: ColumnSort -> String
$cshow :: ColumnSort -> String
showsPrec :: Int -> ColumnSort -> ShowS
$cshowsPrec :: Int -> ColumnSort -> ShowS
Prelude.Show, forall x. Rep ColumnSort x -> ColumnSort
forall x. ColumnSort -> Rep ColumnSort x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColumnSort x -> ColumnSort
$cfrom :: forall x. ColumnSort -> Rep ColumnSort x
Prelude.Generic)

-- |
-- Create a value of 'ColumnSort' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'aggregationFunction', 'columnSort_aggregationFunction' - The aggregation function that is defined in the column sort.
--
-- 'sortBy', 'columnSort_sortBy' - Undocumented member.
--
-- 'direction', 'columnSort_direction' - The sort direction.
newColumnSort ::
  -- | 'sortBy'
  ColumnIdentifier ->
  -- | 'direction'
  SortDirection ->
  ColumnSort
newColumnSort :: ColumnIdentifier -> SortDirection -> ColumnSort
newColumnSort ColumnIdentifier
pSortBy_ SortDirection
pDirection_ =
  ColumnSort'
    { $sel:aggregationFunction:ColumnSort' :: Maybe AggregationFunction
aggregationFunction = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ColumnSort' :: ColumnIdentifier
sortBy = ColumnIdentifier
pSortBy_,
      $sel:direction:ColumnSort' :: SortDirection
direction = SortDirection
pDirection_
    }

-- | The aggregation function that is defined in the column sort.
columnSort_aggregationFunction :: Lens.Lens' ColumnSort (Prelude.Maybe AggregationFunction)
columnSort_aggregationFunction :: Lens' ColumnSort (Maybe AggregationFunction)
columnSort_aggregationFunction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnSort' {Maybe AggregationFunction
aggregationFunction :: Maybe AggregationFunction
$sel:aggregationFunction:ColumnSort' :: ColumnSort -> Maybe AggregationFunction
aggregationFunction} -> Maybe AggregationFunction
aggregationFunction) (\s :: ColumnSort
s@ColumnSort' {} Maybe AggregationFunction
a -> ColumnSort
s {$sel:aggregationFunction:ColumnSort' :: Maybe AggregationFunction
aggregationFunction = Maybe AggregationFunction
a} :: ColumnSort)

-- | Undocumented member.
columnSort_sortBy :: Lens.Lens' ColumnSort ColumnIdentifier
columnSort_sortBy :: Lens' ColumnSort ColumnIdentifier
columnSort_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnSort' {ColumnIdentifier
sortBy :: ColumnIdentifier
$sel:sortBy:ColumnSort' :: ColumnSort -> ColumnIdentifier
sortBy} -> ColumnIdentifier
sortBy) (\s :: ColumnSort
s@ColumnSort' {} ColumnIdentifier
a -> ColumnSort
s {$sel:sortBy:ColumnSort' :: ColumnIdentifier
sortBy = ColumnIdentifier
a} :: ColumnSort)

-- | The sort direction.
columnSort_direction :: Lens.Lens' ColumnSort SortDirection
columnSort_direction :: Lens' ColumnSort SortDirection
columnSort_direction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnSort' {SortDirection
direction :: SortDirection
$sel:direction:ColumnSort' :: ColumnSort -> SortDirection
direction} -> SortDirection
direction) (\s :: ColumnSort
s@ColumnSort' {} SortDirection
a -> ColumnSort
s {$sel:direction:ColumnSort' :: SortDirection
direction = SortDirection
a} :: ColumnSort)

instance Data.FromJSON ColumnSort where
  parseJSON :: Value -> Parser ColumnSort
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ColumnSort"
      ( \Object
x ->
          Maybe AggregationFunction
-> ColumnIdentifier -> SortDirection -> ColumnSort
ColumnSort'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AggregationFunction")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"SortBy")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Direction")
      )

instance Prelude.Hashable ColumnSort where
  hashWithSalt :: Int -> ColumnSort -> Int
hashWithSalt Int
_salt ColumnSort' {Maybe AggregationFunction
ColumnIdentifier
SortDirection
direction :: SortDirection
sortBy :: ColumnIdentifier
aggregationFunction :: Maybe AggregationFunction
$sel:direction:ColumnSort' :: ColumnSort -> SortDirection
$sel:sortBy:ColumnSort' :: ColumnSort -> ColumnIdentifier
$sel:aggregationFunction:ColumnSort' :: ColumnSort -> Maybe AggregationFunction
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AggregationFunction
aggregationFunction
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ColumnIdentifier
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SortDirection
direction

instance Prelude.NFData ColumnSort where
  rnf :: ColumnSort -> ()
rnf ColumnSort' {Maybe AggregationFunction
ColumnIdentifier
SortDirection
direction :: SortDirection
sortBy :: ColumnIdentifier
aggregationFunction :: Maybe AggregationFunction
$sel:direction:ColumnSort' :: ColumnSort -> SortDirection
$sel:sortBy:ColumnSort' :: ColumnSort -> ColumnIdentifier
$sel:aggregationFunction:ColumnSort' :: ColumnSort -> Maybe AggregationFunction
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AggregationFunction
aggregationFunction
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ColumnIdentifier
sortBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SortDirection
direction

instance Data.ToJSON ColumnSort where
  toJSON :: ColumnSort -> Value
toJSON ColumnSort' {Maybe AggregationFunction
ColumnIdentifier
SortDirection
direction :: SortDirection
sortBy :: ColumnIdentifier
aggregationFunction :: Maybe AggregationFunction
$sel:direction:ColumnSort' :: ColumnSort -> SortDirection
$sel:sortBy:ColumnSort' :: ColumnSort -> ColumnIdentifier
$sel:aggregationFunction:ColumnSort' :: ColumnSort -> Maybe AggregationFunction
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AggregationFunction" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AggregationFunction
aggregationFunction,
            forall a. a -> Maybe a
Prelude.Just (Key
"SortBy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ColumnIdentifier
sortBy),
            forall a. a -> Maybe a
Prelude.Just (Key
"Direction" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= SortDirection
direction)
          ]
      )