{-# 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.LookoutMetrics.Types.JsonFormatDescriptor
-- 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.LookoutMetrics.Types.JsonFormatDescriptor where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.LookoutMetrics.Types.JsonFileCompression
import qualified Amazonka.Prelude as Prelude

-- | Contains information about how a source JSON data file should be
-- analyzed.
--
-- /See:/ 'newJsonFormatDescriptor' smart constructor.
data JsonFormatDescriptor = JsonFormatDescriptor'
  { -- | The character set in which the source JSON file is written.
    JsonFormatDescriptor -> Maybe Text
charset :: Prelude.Maybe Prelude.Text,
    -- | The level of compression of the source CSV file.
    JsonFormatDescriptor -> Maybe JsonFileCompression
fileCompression :: Prelude.Maybe JsonFileCompression
  }
  deriving (JsonFormatDescriptor -> JsonFormatDescriptor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JsonFormatDescriptor -> JsonFormatDescriptor -> Bool
$c/= :: JsonFormatDescriptor -> JsonFormatDescriptor -> Bool
== :: JsonFormatDescriptor -> JsonFormatDescriptor -> Bool
$c== :: JsonFormatDescriptor -> JsonFormatDescriptor -> Bool
Prelude.Eq, ReadPrec [JsonFormatDescriptor]
ReadPrec JsonFormatDescriptor
Int -> ReadS JsonFormatDescriptor
ReadS [JsonFormatDescriptor]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JsonFormatDescriptor]
$creadListPrec :: ReadPrec [JsonFormatDescriptor]
readPrec :: ReadPrec JsonFormatDescriptor
$creadPrec :: ReadPrec JsonFormatDescriptor
readList :: ReadS [JsonFormatDescriptor]
$creadList :: ReadS [JsonFormatDescriptor]
readsPrec :: Int -> ReadS JsonFormatDescriptor
$creadsPrec :: Int -> ReadS JsonFormatDescriptor
Prelude.Read, Int -> JsonFormatDescriptor -> ShowS
[JsonFormatDescriptor] -> ShowS
JsonFormatDescriptor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JsonFormatDescriptor] -> ShowS
$cshowList :: [JsonFormatDescriptor] -> ShowS
show :: JsonFormatDescriptor -> String
$cshow :: JsonFormatDescriptor -> String
showsPrec :: Int -> JsonFormatDescriptor -> ShowS
$cshowsPrec :: Int -> JsonFormatDescriptor -> ShowS
Prelude.Show, forall x. Rep JsonFormatDescriptor x -> JsonFormatDescriptor
forall x. JsonFormatDescriptor -> Rep JsonFormatDescriptor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JsonFormatDescriptor x -> JsonFormatDescriptor
$cfrom :: forall x. JsonFormatDescriptor -> Rep JsonFormatDescriptor x
Prelude.Generic)

-- |
-- Create a value of 'JsonFormatDescriptor' 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:
--
-- 'charset', 'jsonFormatDescriptor_charset' - The character set in which the source JSON file is written.
--
-- 'fileCompression', 'jsonFormatDescriptor_fileCompression' - The level of compression of the source CSV file.
newJsonFormatDescriptor ::
  JsonFormatDescriptor
newJsonFormatDescriptor :: JsonFormatDescriptor
newJsonFormatDescriptor =
  JsonFormatDescriptor'
    { $sel:charset:JsonFormatDescriptor' :: Maybe Text
charset = forall a. Maybe a
Prelude.Nothing,
      $sel:fileCompression:JsonFormatDescriptor' :: Maybe JsonFileCompression
fileCompression = forall a. Maybe a
Prelude.Nothing
    }

-- | The character set in which the source JSON file is written.
jsonFormatDescriptor_charset :: Lens.Lens' JsonFormatDescriptor (Prelude.Maybe Prelude.Text)
jsonFormatDescriptor_charset :: Lens' JsonFormatDescriptor (Maybe Text)
jsonFormatDescriptor_charset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JsonFormatDescriptor' {Maybe Text
charset :: Maybe Text
$sel:charset:JsonFormatDescriptor' :: JsonFormatDescriptor -> Maybe Text
charset} -> Maybe Text
charset) (\s :: JsonFormatDescriptor
s@JsonFormatDescriptor' {} Maybe Text
a -> JsonFormatDescriptor
s {$sel:charset:JsonFormatDescriptor' :: Maybe Text
charset = Maybe Text
a} :: JsonFormatDescriptor)

-- | The level of compression of the source CSV file.
jsonFormatDescriptor_fileCompression :: Lens.Lens' JsonFormatDescriptor (Prelude.Maybe JsonFileCompression)
jsonFormatDescriptor_fileCompression :: Lens' JsonFormatDescriptor (Maybe JsonFileCompression)
jsonFormatDescriptor_fileCompression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JsonFormatDescriptor' {Maybe JsonFileCompression
fileCompression :: Maybe JsonFileCompression
$sel:fileCompression:JsonFormatDescriptor' :: JsonFormatDescriptor -> Maybe JsonFileCompression
fileCompression} -> Maybe JsonFileCompression
fileCompression) (\s :: JsonFormatDescriptor
s@JsonFormatDescriptor' {} Maybe JsonFileCompression
a -> JsonFormatDescriptor
s {$sel:fileCompression:JsonFormatDescriptor' :: Maybe JsonFileCompression
fileCompression = Maybe JsonFileCompression
a} :: JsonFormatDescriptor)

instance Data.FromJSON JsonFormatDescriptor where
  parseJSON :: Value -> Parser JsonFormatDescriptor
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JsonFormatDescriptor"
      ( \Object
x ->
          Maybe Text -> Maybe JsonFileCompression -> JsonFormatDescriptor
JsonFormatDescriptor'
            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
"Charset")
            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
"FileCompression")
      )

instance Prelude.Hashable JsonFormatDescriptor where
  hashWithSalt :: Int -> JsonFormatDescriptor -> Int
hashWithSalt Int
_salt JsonFormatDescriptor' {Maybe Text
Maybe JsonFileCompression
fileCompression :: Maybe JsonFileCompression
charset :: Maybe Text
$sel:fileCompression:JsonFormatDescriptor' :: JsonFormatDescriptor -> Maybe JsonFileCompression
$sel:charset:JsonFormatDescriptor' :: JsonFormatDescriptor -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
charset
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JsonFileCompression
fileCompression

instance Prelude.NFData JsonFormatDescriptor where
  rnf :: JsonFormatDescriptor -> ()
rnf JsonFormatDescriptor' {Maybe Text
Maybe JsonFileCompression
fileCompression :: Maybe JsonFileCompression
charset :: Maybe Text
$sel:fileCompression:JsonFormatDescriptor' :: JsonFormatDescriptor -> Maybe JsonFileCompression
$sel:charset:JsonFormatDescriptor' :: JsonFormatDescriptor -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
charset
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JsonFileCompression
fileCompression

instance Data.ToJSON JsonFormatDescriptor where
  toJSON :: JsonFormatDescriptor -> Value
toJSON JsonFormatDescriptor' {Maybe Text
Maybe JsonFileCompression
fileCompression :: Maybe JsonFileCompression
charset :: Maybe Text
$sel:fileCompression:JsonFormatDescriptor' :: JsonFormatDescriptor -> Maybe JsonFileCompression
$sel:charset:JsonFormatDescriptor' :: JsonFormatDescriptor -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Charset" 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
charset,
            (Key
"FileCompression" 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 JsonFileCompression
fileCompression
          ]
      )