{-# 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.AxisScale
-- 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.AxisScale 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.AxisLinearScale
import Amazonka.QuickSight.Types.AxisLogarithmicScale

-- | The scale setup options for a numeric axis display.
--
-- This is a union type structure. For this structure to be valid, only one
-- of the attributes can be defined.
--
-- /See:/ 'newAxisScale' smart constructor.
data AxisScale = AxisScale'
  { -- | The linear axis scale setup.
    AxisScale -> Maybe AxisLinearScale
linear :: Prelude.Maybe AxisLinearScale,
    -- | The logarithmic axis scale setup.
    AxisScale -> Maybe AxisLogarithmicScale
logarithmic :: Prelude.Maybe AxisLogarithmicScale
  }
  deriving (AxisScale -> AxisScale -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AxisScale -> AxisScale -> Bool
$c/= :: AxisScale -> AxisScale -> Bool
== :: AxisScale -> AxisScale -> Bool
$c== :: AxisScale -> AxisScale -> Bool
Prelude.Eq, ReadPrec [AxisScale]
ReadPrec AxisScale
Int -> ReadS AxisScale
ReadS [AxisScale]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AxisScale]
$creadListPrec :: ReadPrec [AxisScale]
readPrec :: ReadPrec AxisScale
$creadPrec :: ReadPrec AxisScale
readList :: ReadS [AxisScale]
$creadList :: ReadS [AxisScale]
readsPrec :: Int -> ReadS AxisScale
$creadsPrec :: Int -> ReadS AxisScale
Prelude.Read, Int -> AxisScale -> ShowS
[AxisScale] -> ShowS
AxisScale -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AxisScale] -> ShowS
$cshowList :: [AxisScale] -> ShowS
show :: AxisScale -> String
$cshow :: AxisScale -> String
showsPrec :: Int -> AxisScale -> ShowS
$cshowsPrec :: Int -> AxisScale -> ShowS
Prelude.Show, forall x. Rep AxisScale x -> AxisScale
forall x. AxisScale -> Rep AxisScale x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AxisScale x -> AxisScale
$cfrom :: forall x. AxisScale -> Rep AxisScale x
Prelude.Generic)

-- |
-- Create a value of 'AxisScale' 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:
--
-- 'linear', 'axisScale_linear' - The linear axis scale setup.
--
-- 'logarithmic', 'axisScale_logarithmic' - The logarithmic axis scale setup.
newAxisScale ::
  AxisScale
newAxisScale :: AxisScale
newAxisScale =
  AxisScale'
    { $sel:linear:AxisScale' :: Maybe AxisLinearScale
linear = forall a. Maybe a
Prelude.Nothing,
      $sel:logarithmic:AxisScale' :: Maybe AxisLogarithmicScale
logarithmic = forall a. Maybe a
Prelude.Nothing
    }

-- | The linear axis scale setup.
axisScale_linear :: Lens.Lens' AxisScale (Prelude.Maybe AxisLinearScale)
axisScale_linear :: Lens' AxisScale (Maybe AxisLinearScale)
axisScale_linear = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AxisScale' {Maybe AxisLinearScale
linear :: Maybe AxisLinearScale
$sel:linear:AxisScale' :: AxisScale -> Maybe AxisLinearScale
linear} -> Maybe AxisLinearScale
linear) (\s :: AxisScale
s@AxisScale' {} Maybe AxisLinearScale
a -> AxisScale
s {$sel:linear:AxisScale' :: Maybe AxisLinearScale
linear = Maybe AxisLinearScale
a} :: AxisScale)

-- | The logarithmic axis scale setup.
axisScale_logarithmic :: Lens.Lens' AxisScale (Prelude.Maybe AxisLogarithmicScale)
axisScale_logarithmic :: Lens' AxisScale (Maybe AxisLogarithmicScale)
axisScale_logarithmic = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AxisScale' {Maybe AxisLogarithmicScale
logarithmic :: Maybe AxisLogarithmicScale
$sel:logarithmic:AxisScale' :: AxisScale -> Maybe AxisLogarithmicScale
logarithmic} -> Maybe AxisLogarithmicScale
logarithmic) (\s :: AxisScale
s@AxisScale' {} Maybe AxisLogarithmicScale
a -> AxisScale
s {$sel:logarithmic:AxisScale' :: Maybe AxisLogarithmicScale
logarithmic = Maybe AxisLogarithmicScale
a} :: AxisScale)

instance Data.FromJSON AxisScale where
  parseJSON :: Value -> Parser AxisScale
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AxisScale"
      ( \Object
x ->
          Maybe AxisLinearScale -> Maybe AxisLogarithmicScale -> AxisScale
AxisScale'
            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
"Linear")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Logarithmic")
      )

instance Prelude.Hashable AxisScale where
  hashWithSalt :: Int -> AxisScale -> Int
hashWithSalt Int
_salt AxisScale' {Maybe AxisLinearScale
Maybe AxisLogarithmicScale
logarithmic :: Maybe AxisLogarithmicScale
linear :: Maybe AxisLinearScale
$sel:logarithmic:AxisScale' :: AxisScale -> Maybe AxisLogarithmicScale
$sel:linear:AxisScale' :: AxisScale -> Maybe AxisLinearScale
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AxisLinearScale
linear
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AxisLogarithmicScale
logarithmic

instance Prelude.NFData AxisScale where
  rnf :: AxisScale -> ()
rnf AxisScale' {Maybe AxisLinearScale
Maybe AxisLogarithmicScale
logarithmic :: Maybe AxisLogarithmicScale
linear :: Maybe AxisLinearScale
$sel:logarithmic:AxisScale' :: AxisScale -> Maybe AxisLogarithmicScale
$sel:linear:AxisScale' :: AxisScale -> Maybe AxisLinearScale
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AxisLinearScale
linear
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AxisLogarithmicScale
logarithmic

instance Data.ToJSON AxisScale where
  toJSON :: AxisScale -> Value
toJSON AxisScale' {Maybe AxisLinearScale
Maybe AxisLogarithmicScale
logarithmic :: Maybe AxisLogarithmicScale
linear :: Maybe AxisLinearScale
$sel:logarithmic:AxisScale' :: AxisScale -> Maybe AxisLogarithmicScale
$sel:linear:AxisScale' :: AxisScale -> Maybe AxisLinearScale
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Linear" 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 AxisLinearScale
linear,
            (Key
"Logarithmic" 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 AxisLogarithmicScale
logarithmic
          ]
      )