{-# 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.AppFlow.Types.AggregationConfig
-- 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.AppFlow.Types.AggregationConfig where

import Amazonka.AppFlow.Types.AggregationType
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

-- | The aggregation settings that you can use to customize the output format
-- of your flow data.
--
-- /See:/ 'newAggregationConfig' smart constructor.
data AggregationConfig = AggregationConfig'
  { -- | Specifies whether Amazon AppFlow aggregates the flow records into a
    -- single file, or leave them unaggregated.
    AggregationConfig -> Maybe AggregationType
aggregationType :: Prelude.Maybe AggregationType,
    -- | The desired file size, in MB, for each output file that Amazon AppFlow
    -- writes to the flow destination. For each file, Amazon AppFlow attempts
    -- to achieve the size that you specify. The actual file sizes might differ
    -- from this target based on the number and size of the records that each
    -- file contains.
    AggregationConfig -> Maybe Integer
targetFileSize :: Prelude.Maybe Prelude.Integer
  }
  deriving (AggregationConfig -> AggregationConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AggregationConfig -> AggregationConfig -> Bool
$c/= :: AggregationConfig -> AggregationConfig -> Bool
== :: AggregationConfig -> AggregationConfig -> Bool
$c== :: AggregationConfig -> AggregationConfig -> Bool
Prelude.Eq, ReadPrec [AggregationConfig]
ReadPrec AggregationConfig
Int -> ReadS AggregationConfig
ReadS [AggregationConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AggregationConfig]
$creadListPrec :: ReadPrec [AggregationConfig]
readPrec :: ReadPrec AggregationConfig
$creadPrec :: ReadPrec AggregationConfig
readList :: ReadS [AggregationConfig]
$creadList :: ReadS [AggregationConfig]
readsPrec :: Int -> ReadS AggregationConfig
$creadsPrec :: Int -> ReadS AggregationConfig
Prelude.Read, Int -> AggregationConfig -> ShowS
[AggregationConfig] -> ShowS
AggregationConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AggregationConfig] -> ShowS
$cshowList :: [AggregationConfig] -> ShowS
show :: AggregationConfig -> String
$cshow :: AggregationConfig -> String
showsPrec :: Int -> AggregationConfig -> ShowS
$cshowsPrec :: Int -> AggregationConfig -> ShowS
Prelude.Show, forall x. Rep AggregationConfig x -> AggregationConfig
forall x. AggregationConfig -> Rep AggregationConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AggregationConfig x -> AggregationConfig
$cfrom :: forall x. AggregationConfig -> Rep AggregationConfig x
Prelude.Generic)

-- |
-- Create a value of 'AggregationConfig' 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:
--
-- 'aggregationType', 'aggregationConfig_aggregationType' - Specifies whether Amazon AppFlow aggregates the flow records into a
-- single file, or leave them unaggregated.
--
-- 'targetFileSize', 'aggregationConfig_targetFileSize' - The desired file size, in MB, for each output file that Amazon AppFlow
-- writes to the flow destination. For each file, Amazon AppFlow attempts
-- to achieve the size that you specify. The actual file sizes might differ
-- from this target based on the number and size of the records that each
-- file contains.
newAggregationConfig ::
  AggregationConfig
newAggregationConfig :: AggregationConfig
newAggregationConfig =
  AggregationConfig'
    { $sel:aggregationType:AggregationConfig' :: Maybe AggregationType
aggregationType =
        forall a. Maybe a
Prelude.Nothing,
      $sel:targetFileSize:AggregationConfig' :: Maybe Integer
targetFileSize = forall a. Maybe a
Prelude.Nothing
    }

-- | Specifies whether Amazon AppFlow aggregates the flow records into a
-- single file, or leave them unaggregated.
aggregationConfig_aggregationType :: Lens.Lens' AggregationConfig (Prelude.Maybe AggregationType)
aggregationConfig_aggregationType :: Lens' AggregationConfig (Maybe AggregationType)
aggregationConfig_aggregationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregationConfig' {Maybe AggregationType
aggregationType :: Maybe AggregationType
$sel:aggregationType:AggregationConfig' :: AggregationConfig -> Maybe AggregationType
aggregationType} -> Maybe AggregationType
aggregationType) (\s :: AggregationConfig
s@AggregationConfig' {} Maybe AggregationType
a -> AggregationConfig
s {$sel:aggregationType:AggregationConfig' :: Maybe AggregationType
aggregationType = Maybe AggregationType
a} :: AggregationConfig)

-- | The desired file size, in MB, for each output file that Amazon AppFlow
-- writes to the flow destination. For each file, Amazon AppFlow attempts
-- to achieve the size that you specify. The actual file sizes might differ
-- from this target based on the number and size of the records that each
-- file contains.
aggregationConfig_targetFileSize :: Lens.Lens' AggregationConfig (Prelude.Maybe Prelude.Integer)
aggregationConfig_targetFileSize :: Lens' AggregationConfig (Maybe Integer)
aggregationConfig_targetFileSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregationConfig' {Maybe Integer
targetFileSize :: Maybe Integer
$sel:targetFileSize:AggregationConfig' :: AggregationConfig -> Maybe Integer
targetFileSize} -> Maybe Integer
targetFileSize) (\s :: AggregationConfig
s@AggregationConfig' {} Maybe Integer
a -> AggregationConfig
s {$sel:targetFileSize:AggregationConfig' :: Maybe Integer
targetFileSize = Maybe Integer
a} :: AggregationConfig)

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

instance Prelude.Hashable AggregationConfig where
  hashWithSalt :: Int -> AggregationConfig -> Int
hashWithSalt Int
_salt AggregationConfig' {Maybe Integer
Maybe AggregationType
targetFileSize :: Maybe Integer
aggregationType :: Maybe AggregationType
$sel:targetFileSize:AggregationConfig' :: AggregationConfig -> Maybe Integer
$sel:aggregationType:AggregationConfig' :: AggregationConfig -> Maybe AggregationType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AggregationType
aggregationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
targetFileSize

instance Prelude.NFData AggregationConfig where
  rnf :: AggregationConfig -> ()
rnf AggregationConfig' {Maybe Integer
Maybe AggregationType
targetFileSize :: Maybe Integer
aggregationType :: Maybe AggregationType
$sel:targetFileSize:AggregationConfig' :: AggregationConfig -> Maybe Integer
$sel:aggregationType:AggregationConfig' :: AggregationConfig -> Maybe AggregationType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AggregationType
aggregationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
targetFileSize

instance Data.ToJSON AggregationConfig where
  toJSON :: AggregationConfig -> Value
toJSON AggregationConfig' {Maybe Integer
Maybe AggregationType
targetFileSize :: Maybe Integer
aggregationType :: Maybe AggregationType
$sel:targetFileSize:AggregationConfig' :: AggregationConfig -> Maybe Integer
$sel:aggregationType:AggregationConfig' :: AggregationConfig -> Maybe AggregationType
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"aggregationType" 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 AggregationType
aggregationType,
            (Key
"targetFileSize" 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 Integer
targetFileSize
          ]
      )