{-# 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.DataBrew.Types.FormatOptions
-- 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.DataBrew.Types.FormatOptions where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DataBrew.Types.CsvOptions
import Amazonka.DataBrew.Types.ExcelOptions
import Amazonka.DataBrew.Types.JsonOptions
import qualified Amazonka.Prelude as Prelude

-- | Represents a set of options that define the structure of either
-- comma-separated value (CSV), Excel, or JSON input.
--
-- /See:/ 'newFormatOptions' smart constructor.
data FormatOptions = FormatOptions'
  { -- | Options that define how CSV input is to be interpreted by DataBrew.
    FormatOptions -> Maybe CsvOptions
csv :: Prelude.Maybe CsvOptions,
    -- | Options that define how Excel input is to be interpreted by DataBrew.
    FormatOptions -> Maybe ExcelOptions
excel :: Prelude.Maybe ExcelOptions,
    -- | Options that define how JSON input is to be interpreted by DataBrew.
    FormatOptions -> Maybe JsonOptions
json :: Prelude.Maybe JsonOptions
  }
  deriving (FormatOptions -> FormatOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormatOptions -> FormatOptions -> Bool
$c/= :: FormatOptions -> FormatOptions -> Bool
== :: FormatOptions -> FormatOptions -> Bool
$c== :: FormatOptions -> FormatOptions -> Bool
Prelude.Eq, ReadPrec [FormatOptions]
ReadPrec FormatOptions
Int -> ReadS FormatOptions
ReadS [FormatOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FormatOptions]
$creadListPrec :: ReadPrec [FormatOptions]
readPrec :: ReadPrec FormatOptions
$creadPrec :: ReadPrec FormatOptions
readList :: ReadS [FormatOptions]
$creadList :: ReadS [FormatOptions]
readsPrec :: Int -> ReadS FormatOptions
$creadsPrec :: Int -> ReadS FormatOptions
Prelude.Read, Int -> FormatOptions -> ShowS
[FormatOptions] -> ShowS
FormatOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormatOptions] -> ShowS
$cshowList :: [FormatOptions] -> ShowS
show :: FormatOptions -> String
$cshow :: FormatOptions -> String
showsPrec :: Int -> FormatOptions -> ShowS
$cshowsPrec :: Int -> FormatOptions -> ShowS
Prelude.Show, forall x. Rep FormatOptions x -> FormatOptions
forall x. FormatOptions -> Rep FormatOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FormatOptions x -> FormatOptions
$cfrom :: forall x. FormatOptions -> Rep FormatOptions x
Prelude.Generic)

-- |
-- Create a value of 'FormatOptions' 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:
--
-- 'csv', 'formatOptions_csv' - Options that define how CSV input is to be interpreted by DataBrew.
--
-- 'excel', 'formatOptions_excel' - Options that define how Excel input is to be interpreted by DataBrew.
--
-- 'json', 'formatOptions_json' - Options that define how JSON input is to be interpreted by DataBrew.
newFormatOptions ::
  FormatOptions
newFormatOptions :: FormatOptions
newFormatOptions =
  FormatOptions'
    { $sel:csv:FormatOptions' :: Maybe CsvOptions
csv = forall a. Maybe a
Prelude.Nothing,
      $sel:excel:FormatOptions' :: Maybe ExcelOptions
excel = forall a. Maybe a
Prelude.Nothing,
      $sel:json:FormatOptions' :: Maybe JsonOptions
json = forall a. Maybe a
Prelude.Nothing
    }

-- | Options that define how CSV input is to be interpreted by DataBrew.
formatOptions_csv :: Lens.Lens' FormatOptions (Prelude.Maybe CsvOptions)
formatOptions_csv :: Lens' FormatOptions (Maybe CsvOptions)
formatOptions_csv = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FormatOptions' {Maybe CsvOptions
csv :: Maybe CsvOptions
$sel:csv:FormatOptions' :: FormatOptions -> Maybe CsvOptions
csv} -> Maybe CsvOptions
csv) (\s :: FormatOptions
s@FormatOptions' {} Maybe CsvOptions
a -> FormatOptions
s {$sel:csv:FormatOptions' :: Maybe CsvOptions
csv = Maybe CsvOptions
a} :: FormatOptions)

-- | Options that define how Excel input is to be interpreted by DataBrew.
formatOptions_excel :: Lens.Lens' FormatOptions (Prelude.Maybe ExcelOptions)
formatOptions_excel :: Lens' FormatOptions (Maybe ExcelOptions)
formatOptions_excel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FormatOptions' {Maybe ExcelOptions
excel :: Maybe ExcelOptions
$sel:excel:FormatOptions' :: FormatOptions -> Maybe ExcelOptions
excel} -> Maybe ExcelOptions
excel) (\s :: FormatOptions
s@FormatOptions' {} Maybe ExcelOptions
a -> FormatOptions
s {$sel:excel:FormatOptions' :: Maybe ExcelOptions
excel = Maybe ExcelOptions
a} :: FormatOptions)

-- | Options that define how JSON input is to be interpreted by DataBrew.
formatOptions_json :: Lens.Lens' FormatOptions (Prelude.Maybe JsonOptions)
formatOptions_json :: Lens' FormatOptions (Maybe JsonOptions)
formatOptions_json = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FormatOptions' {Maybe JsonOptions
json :: Maybe JsonOptions
$sel:json:FormatOptions' :: FormatOptions -> Maybe JsonOptions
json} -> Maybe JsonOptions
json) (\s :: FormatOptions
s@FormatOptions' {} Maybe JsonOptions
a -> FormatOptions
s {$sel:json:FormatOptions' :: Maybe JsonOptions
json = Maybe JsonOptions
a} :: FormatOptions)

instance Data.FromJSON FormatOptions where
  parseJSON :: Value -> Parser FormatOptions
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"FormatOptions"
      ( \Object
x ->
          Maybe CsvOptions
-> Maybe ExcelOptions -> Maybe JsonOptions -> FormatOptions
FormatOptions'
            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
"Csv")
            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
"Excel")
            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
"Json")
      )

instance Prelude.Hashable FormatOptions where
  hashWithSalt :: Int -> FormatOptions -> Int
hashWithSalt Int
_salt FormatOptions' {Maybe CsvOptions
Maybe ExcelOptions
Maybe JsonOptions
json :: Maybe JsonOptions
excel :: Maybe ExcelOptions
csv :: Maybe CsvOptions
$sel:json:FormatOptions' :: FormatOptions -> Maybe JsonOptions
$sel:excel:FormatOptions' :: FormatOptions -> Maybe ExcelOptions
$sel:csv:FormatOptions' :: FormatOptions -> Maybe CsvOptions
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CsvOptions
csv
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExcelOptions
excel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JsonOptions
json

instance Prelude.NFData FormatOptions where
  rnf :: FormatOptions -> ()
rnf FormatOptions' {Maybe CsvOptions
Maybe ExcelOptions
Maybe JsonOptions
json :: Maybe JsonOptions
excel :: Maybe ExcelOptions
csv :: Maybe CsvOptions
$sel:json:FormatOptions' :: FormatOptions -> Maybe JsonOptions
$sel:excel:FormatOptions' :: FormatOptions -> Maybe ExcelOptions
$sel:csv:FormatOptions' :: FormatOptions -> Maybe CsvOptions
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CsvOptions
csv
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExcelOptions
excel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JsonOptions
json

instance Data.ToJSON FormatOptions where
  toJSON :: FormatOptions -> Value
toJSON FormatOptions' {Maybe CsvOptions
Maybe ExcelOptions
Maybe JsonOptions
json :: Maybe JsonOptions
excel :: Maybe ExcelOptions
csv :: Maybe CsvOptions
$sel:json:FormatOptions' :: FormatOptions -> Maybe JsonOptions
$sel:excel:FormatOptions' :: FormatOptions -> Maybe ExcelOptions
$sel:csv:FormatOptions' :: FormatOptions -> Maybe CsvOptions
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Csv" 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 CsvOptions
csv,
            (Key
"Excel" 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 ExcelOptions
excel,
            (Key
"Json" 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 JsonOptions
json
          ]
      )