{-# 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.TimeStreamQuery.Types.MixedMeasureMapping
-- 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.TimeStreamQuery.Types.MixedMeasureMapping 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.TimeStreamQuery.Types.MeasureValueType
import Amazonka.TimeStreamQuery.Types.MultiMeasureAttributeMapping

-- | MixedMeasureMappings are mappings that can be used to ingest data into a
-- mixture of narrow and multi measures in the derived table.
--
-- /See:/ 'newMixedMeasureMapping' smart constructor.
data MixedMeasureMapping = MixedMeasureMapping'
  { -- | Refers to the value of measure_name in a result row. This field is
    -- required if MeasureNameColumn is provided.
    MixedMeasureMapping -> Maybe Text
measureName :: Prelude.Maybe Prelude.Text,
    -- | Required when measureValueType is MULTI. Attribute mappings for MULTI
    -- value measures.
    MixedMeasureMapping
-> Maybe (NonEmpty MultiMeasureAttributeMapping)
multiMeasureAttributeMappings :: Prelude.Maybe (Prelude.NonEmpty MultiMeasureAttributeMapping),
    -- | This field refers to the source column from which measure-value is to be
    -- read for result materialization.
    MixedMeasureMapping -> Maybe Text
sourceColumn :: Prelude.Maybe Prelude.Text,
    -- | Target measure name to be used. If not provided, the target measure name
    -- by default would be measure-name if provided, or sourceColumn otherwise.
    MixedMeasureMapping -> Maybe Text
targetMeasureName :: Prelude.Maybe Prelude.Text,
    -- | Type of the value that is to be read from sourceColumn. If the mapping
    -- is for MULTI, use MeasureValueType.MULTI.
    MixedMeasureMapping -> MeasureValueType
measureValueType :: MeasureValueType
  }
  deriving (MixedMeasureMapping -> MixedMeasureMapping -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MixedMeasureMapping -> MixedMeasureMapping -> Bool
$c/= :: MixedMeasureMapping -> MixedMeasureMapping -> Bool
== :: MixedMeasureMapping -> MixedMeasureMapping -> Bool
$c== :: MixedMeasureMapping -> MixedMeasureMapping -> Bool
Prelude.Eq, ReadPrec [MixedMeasureMapping]
ReadPrec MixedMeasureMapping
Int -> ReadS MixedMeasureMapping
ReadS [MixedMeasureMapping]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MixedMeasureMapping]
$creadListPrec :: ReadPrec [MixedMeasureMapping]
readPrec :: ReadPrec MixedMeasureMapping
$creadPrec :: ReadPrec MixedMeasureMapping
readList :: ReadS [MixedMeasureMapping]
$creadList :: ReadS [MixedMeasureMapping]
readsPrec :: Int -> ReadS MixedMeasureMapping
$creadsPrec :: Int -> ReadS MixedMeasureMapping
Prelude.Read, Int -> MixedMeasureMapping -> ShowS
[MixedMeasureMapping] -> ShowS
MixedMeasureMapping -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MixedMeasureMapping] -> ShowS
$cshowList :: [MixedMeasureMapping] -> ShowS
show :: MixedMeasureMapping -> String
$cshow :: MixedMeasureMapping -> String
showsPrec :: Int -> MixedMeasureMapping -> ShowS
$cshowsPrec :: Int -> MixedMeasureMapping -> ShowS
Prelude.Show, forall x. Rep MixedMeasureMapping x -> MixedMeasureMapping
forall x. MixedMeasureMapping -> Rep MixedMeasureMapping x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MixedMeasureMapping x -> MixedMeasureMapping
$cfrom :: forall x. MixedMeasureMapping -> Rep MixedMeasureMapping x
Prelude.Generic)

-- |
-- Create a value of 'MixedMeasureMapping' 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:
--
-- 'measureName', 'mixedMeasureMapping_measureName' - Refers to the value of measure_name in a result row. This field is
-- required if MeasureNameColumn is provided.
--
-- 'multiMeasureAttributeMappings', 'mixedMeasureMapping_multiMeasureAttributeMappings' - Required when measureValueType is MULTI. Attribute mappings for MULTI
-- value measures.
--
-- 'sourceColumn', 'mixedMeasureMapping_sourceColumn' - This field refers to the source column from which measure-value is to be
-- read for result materialization.
--
-- 'targetMeasureName', 'mixedMeasureMapping_targetMeasureName' - Target measure name to be used. If not provided, the target measure name
-- by default would be measure-name if provided, or sourceColumn otherwise.
--
-- 'measureValueType', 'mixedMeasureMapping_measureValueType' - Type of the value that is to be read from sourceColumn. If the mapping
-- is for MULTI, use MeasureValueType.MULTI.
newMixedMeasureMapping ::
  -- | 'measureValueType'
  MeasureValueType ->
  MixedMeasureMapping
newMixedMeasureMapping :: MeasureValueType -> MixedMeasureMapping
newMixedMeasureMapping MeasureValueType
pMeasureValueType_ =
  MixedMeasureMapping'
    { $sel:measureName:MixedMeasureMapping' :: Maybe Text
measureName = forall a. Maybe a
Prelude.Nothing,
      $sel:multiMeasureAttributeMappings:MixedMeasureMapping' :: Maybe (NonEmpty MultiMeasureAttributeMapping)
multiMeasureAttributeMappings = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceColumn:MixedMeasureMapping' :: Maybe Text
sourceColumn = forall a. Maybe a
Prelude.Nothing,
      $sel:targetMeasureName:MixedMeasureMapping' :: Maybe Text
targetMeasureName = forall a. Maybe a
Prelude.Nothing,
      $sel:measureValueType:MixedMeasureMapping' :: MeasureValueType
measureValueType = MeasureValueType
pMeasureValueType_
    }

-- | Refers to the value of measure_name in a result row. This field is
-- required if MeasureNameColumn is provided.
mixedMeasureMapping_measureName :: Lens.Lens' MixedMeasureMapping (Prelude.Maybe Prelude.Text)
mixedMeasureMapping_measureName :: Lens' MixedMeasureMapping (Maybe Text)
mixedMeasureMapping_measureName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MixedMeasureMapping' {Maybe Text
measureName :: Maybe Text
$sel:measureName:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
measureName} -> Maybe Text
measureName) (\s :: MixedMeasureMapping
s@MixedMeasureMapping' {} Maybe Text
a -> MixedMeasureMapping
s {$sel:measureName:MixedMeasureMapping' :: Maybe Text
measureName = Maybe Text
a} :: MixedMeasureMapping)

-- | Required when measureValueType is MULTI. Attribute mappings for MULTI
-- value measures.
mixedMeasureMapping_multiMeasureAttributeMappings :: Lens.Lens' MixedMeasureMapping (Prelude.Maybe (Prelude.NonEmpty MultiMeasureAttributeMapping))
mixedMeasureMapping_multiMeasureAttributeMappings :: Lens'
  MixedMeasureMapping (Maybe (NonEmpty MultiMeasureAttributeMapping))
mixedMeasureMapping_multiMeasureAttributeMappings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MixedMeasureMapping' {Maybe (NonEmpty MultiMeasureAttributeMapping)
multiMeasureAttributeMappings :: Maybe (NonEmpty MultiMeasureAttributeMapping)
$sel:multiMeasureAttributeMappings:MixedMeasureMapping' :: MixedMeasureMapping
-> Maybe (NonEmpty MultiMeasureAttributeMapping)
multiMeasureAttributeMappings} -> Maybe (NonEmpty MultiMeasureAttributeMapping)
multiMeasureAttributeMappings) (\s :: MixedMeasureMapping
s@MixedMeasureMapping' {} Maybe (NonEmpty MultiMeasureAttributeMapping)
a -> MixedMeasureMapping
s {$sel:multiMeasureAttributeMappings:MixedMeasureMapping' :: Maybe (NonEmpty MultiMeasureAttributeMapping)
multiMeasureAttributeMappings = Maybe (NonEmpty MultiMeasureAttributeMapping)
a} :: MixedMeasureMapping) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | This field refers to the source column from which measure-value is to be
-- read for result materialization.
mixedMeasureMapping_sourceColumn :: Lens.Lens' MixedMeasureMapping (Prelude.Maybe Prelude.Text)
mixedMeasureMapping_sourceColumn :: Lens' MixedMeasureMapping (Maybe Text)
mixedMeasureMapping_sourceColumn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MixedMeasureMapping' {Maybe Text
sourceColumn :: Maybe Text
$sel:sourceColumn:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
sourceColumn} -> Maybe Text
sourceColumn) (\s :: MixedMeasureMapping
s@MixedMeasureMapping' {} Maybe Text
a -> MixedMeasureMapping
s {$sel:sourceColumn:MixedMeasureMapping' :: Maybe Text
sourceColumn = Maybe Text
a} :: MixedMeasureMapping)

-- | Target measure name to be used. If not provided, the target measure name
-- by default would be measure-name if provided, or sourceColumn otherwise.
mixedMeasureMapping_targetMeasureName :: Lens.Lens' MixedMeasureMapping (Prelude.Maybe Prelude.Text)
mixedMeasureMapping_targetMeasureName :: Lens' MixedMeasureMapping (Maybe Text)
mixedMeasureMapping_targetMeasureName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MixedMeasureMapping' {Maybe Text
targetMeasureName :: Maybe Text
$sel:targetMeasureName:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
targetMeasureName} -> Maybe Text
targetMeasureName) (\s :: MixedMeasureMapping
s@MixedMeasureMapping' {} Maybe Text
a -> MixedMeasureMapping
s {$sel:targetMeasureName:MixedMeasureMapping' :: Maybe Text
targetMeasureName = Maybe Text
a} :: MixedMeasureMapping)

-- | Type of the value that is to be read from sourceColumn. If the mapping
-- is for MULTI, use MeasureValueType.MULTI.
mixedMeasureMapping_measureValueType :: Lens.Lens' MixedMeasureMapping MeasureValueType
mixedMeasureMapping_measureValueType :: Lens' MixedMeasureMapping MeasureValueType
mixedMeasureMapping_measureValueType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MixedMeasureMapping' {MeasureValueType
measureValueType :: MeasureValueType
$sel:measureValueType:MixedMeasureMapping' :: MixedMeasureMapping -> MeasureValueType
measureValueType} -> MeasureValueType
measureValueType) (\s :: MixedMeasureMapping
s@MixedMeasureMapping' {} MeasureValueType
a -> MixedMeasureMapping
s {$sel:measureValueType:MixedMeasureMapping' :: MeasureValueType
measureValueType = MeasureValueType
a} :: MixedMeasureMapping)

instance Data.FromJSON MixedMeasureMapping where
  parseJSON :: Value -> Parser MixedMeasureMapping
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MixedMeasureMapping"
      ( \Object
x ->
          Maybe Text
-> Maybe (NonEmpty MultiMeasureAttributeMapping)
-> Maybe Text
-> Maybe Text
-> MeasureValueType
-> MixedMeasureMapping
MixedMeasureMapping'
            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
"MeasureName")
            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
"MultiMeasureAttributeMappings")
            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
"SourceColumn")
            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
"TargetMeasureName")
            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
"MeasureValueType")
      )

instance Prelude.Hashable MixedMeasureMapping where
  hashWithSalt :: Int -> MixedMeasureMapping -> Int
hashWithSalt Int
_salt MixedMeasureMapping' {Maybe (NonEmpty MultiMeasureAttributeMapping)
Maybe Text
MeasureValueType
measureValueType :: MeasureValueType
targetMeasureName :: Maybe Text
sourceColumn :: Maybe Text
multiMeasureAttributeMappings :: Maybe (NonEmpty MultiMeasureAttributeMapping)
measureName :: Maybe Text
$sel:measureValueType:MixedMeasureMapping' :: MixedMeasureMapping -> MeasureValueType
$sel:targetMeasureName:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
$sel:sourceColumn:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
$sel:multiMeasureAttributeMappings:MixedMeasureMapping' :: MixedMeasureMapping
-> Maybe (NonEmpty MultiMeasureAttributeMapping)
$sel:measureName:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
measureName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty MultiMeasureAttributeMapping)
multiMeasureAttributeMappings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceColumn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
targetMeasureName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` MeasureValueType
measureValueType

instance Prelude.NFData MixedMeasureMapping where
  rnf :: MixedMeasureMapping -> ()
rnf MixedMeasureMapping' {Maybe (NonEmpty MultiMeasureAttributeMapping)
Maybe Text
MeasureValueType
measureValueType :: MeasureValueType
targetMeasureName :: Maybe Text
sourceColumn :: Maybe Text
multiMeasureAttributeMappings :: Maybe (NonEmpty MultiMeasureAttributeMapping)
measureName :: Maybe Text
$sel:measureValueType:MixedMeasureMapping' :: MixedMeasureMapping -> MeasureValueType
$sel:targetMeasureName:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
$sel:sourceColumn:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
$sel:multiMeasureAttributeMappings:MixedMeasureMapping' :: MixedMeasureMapping
-> Maybe (NonEmpty MultiMeasureAttributeMapping)
$sel:measureName:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
measureName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty MultiMeasureAttributeMapping)
multiMeasureAttributeMappings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceColumn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
targetMeasureName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf MeasureValueType
measureValueType

instance Data.ToJSON MixedMeasureMapping where
  toJSON :: MixedMeasureMapping -> Value
toJSON MixedMeasureMapping' {Maybe (NonEmpty MultiMeasureAttributeMapping)
Maybe Text
MeasureValueType
measureValueType :: MeasureValueType
targetMeasureName :: Maybe Text
sourceColumn :: Maybe Text
multiMeasureAttributeMappings :: Maybe (NonEmpty MultiMeasureAttributeMapping)
measureName :: Maybe Text
$sel:measureValueType:MixedMeasureMapping' :: MixedMeasureMapping -> MeasureValueType
$sel:targetMeasureName:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
$sel:sourceColumn:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
$sel:multiMeasureAttributeMappings:MixedMeasureMapping' :: MixedMeasureMapping
-> Maybe (NonEmpty MultiMeasureAttributeMapping)
$sel:measureName:MixedMeasureMapping' :: MixedMeasureMapping -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MeasureName" 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 Text
measureName,
            (Key
"MultiMeasureAttributeMappings" 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 (NonEmpty MultiMeasureAttributeMapping)
multiMeasureAttributeMappings,
            (Key
"SourceColumn" 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 Text
sourceColumn,
            (Key
"TargetMeasureName" 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 Text
targetMeasureName,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"MeasureValueType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= MeasureValueType
measureValueType)
          ]
      )