{-# 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.DynamoDB.Types.InputFormatOptions
-- 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.DynamoDB.Types.InputFormatOptions where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DynamoDB.Types.AttributeValue
import Amazonka.DynamoDB.Types.CsvOptions
import Amazonka.DynamoDB.Types.WriteRequest
import qualified Amazonka.Prelude as Prelude

-- | The format options for the data that was imported into the target table.
-- There is one value, CsvOption.
--
-- /See:/ 'newInputFormatOptions' smart constructor.
data InputFormatOptions = InputFormatOptions'
  { -- | The options for imported source files in CSV format. The values are
    -- Delimiter and HeaderList.
    InputFormatOptions -> Maybe CsvOptions
csv :: Prelude.Maybe CsvOptions
  }
  deriving (InputFormatOptions -> InputFormatOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputFormatOptions -> InputFormatOptions -> Bool
$c/= :: InputFormatOptions -> InputFormatOptions -> Bool
== :: InputFormatOptions -> InputFormatOptions -> Bool
$c== :: InputFormatOptions -> InputFormatOptions -> Bool
Prelude.Eq, ReadPrec [InputFormatOptions]
ReadPrec InputFormatOptions
Int -> ReadS InputFormatOptions
ReadS [InputFormatOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputFormatOptions]
$creadListPrec :: ReadPrec [InputFormatOptions]
readPrec :: ReadPrec InputFormatOptions
$creadPrec :: ReadPrec InputFormatOptions
readList :: ReadS [InputFormatOptions]
$creadList :: ReadS [InputFormatOptions]
readsPrec :: Int -> ReadS InputFormatOptions
$creadsPrec :: Int -> ReadS InputFormatOptions
Prelude.Read, Int -> InputFormatOptions -> ShowS
[InputFormatOptions] -> ShowS
InputFormatOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputFormatOptions] -> ShowS
$cshowList :: [InputFormatOptions] -> ShowS
show :: InputFormatOptions -> String
$cshow :: InputFormatOptions -> String
showsPrec :: Int -> InputFormatOptions -> ShowS
$cshowsPrec :: Int -> InputFormatOptions -> ShowS
Prelude.Show, forall x. Rep InputFormatOptions x -> InputFormatOptions
forall x. InputFormatOptions -> Rep InputFormatOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputFormatOptions x -> InputFormatOptions
$cfrom :: forall x. InputFormatOptions -> Rep InputFormatOptions x
Prelude.Generic)

-- |
-- Create a value of 'InputFormatOptions' 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', 'inputFormatOptions_csv' - The options for imported source files in CSV format. The values are
-- Delimiter and HeaderList.
newInputFormatOptions ::
  InputFormatOptions
newInputFormatOptions :: InputFormatOptions
newInputFormatOptions =
  InputFormatOptions' {$sel:csv:InputFormatOptions' :: Maybe CsvOptions
csv = forall a. Maybe a
Prelude.Nothing}

-- | The options for imported source files in CSV format. The values are
-- Delimiter and HeaderList.
inputFormatOptions_csv :: Lens.Lens' InputFormatOptions (Prelude.Maybe CsvOptions)
inputFormatOptions_csv :: Lens' InputFormatOptions (Maybe CsvOptions)
inputFormatOptions_csv = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InputFormatOptions' {Maybe CsvOptions
csv :: Maybe CsvOptions
$sel:csv:InputFormatOptions' :: InputFormatOptions -> Maybe CsvOptions
csv} -> Maybe CsvOptions
csv) (\s :: InputFormatOptions
s@InputFormatOptions' {} Maybe CsvOptions
a -> InputFormatOptions
s {$sel:csv:InputFormatOptions' :: Maybe CsvOptions
csv = Maybe CsvOptions
a} :: InputFormatOptions)

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

instance Prelude.Hashable InputFormatOptions where
  hashWithSalt :: Int -> InputFormatOptions -> Int
hashWithSalt Int
_salt InputFormatOptions' {Maybe CsvOptions
csv :: Maybe CsvOptions
$sel:csv:InputFormatOptions' :: InputFormatOptions -> Maybe CsvOptions
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CsvOptions
csv

instance Prelude.NFData InputFormatOptions where
  rnf :: InputFormatOptions -> ()
rnf InputFormatOptions' {Maybe CsvOptions
csv :: Maybe CsvOptions
$sel:csv:InputFormatOptions' :: InputFormatOptions -> Maybe CsvOptions
..} = forall a. NFData a => a -> ()
Prelude.rnf Maybe CsvOptions
csv

instance Data.ToJSON InputFormatOptions where
  toJSON :: InputFormatOptions -> Value
toJSON InputFormatOptions' {Maybe CsvOptions
csv :: Maybe CsvOptions
$sel:csv:InputFormatOptions' :: InputFormatOptions -> 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])