{-# 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.Glue.Types.JDBCConnectorOptions
-- 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.Glue.Types.JDBCConnectorOptions where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types.GlueRecordType
import Amazonka.Glue.Types.JDBCDataType
import qualified Amazonka.Prelude as Prelude

-- | Additional connection options for the connector.
--
-- /See:/ 'newJDBCConnectorOptions' smart constructor.
data JDBCConnectorOptions = JDBCConnectorOptions'
  { -- | Custom data type mapping that builds a mapping from a JDBC data type to
    -- an Glue data type. For example, the option
    -- @\"dataTypeMapping\":{\"FLOAT\":\"STRING\"}@ maps data fields of JDBC
    -- type @FLOAT@ into the Java @String@ type by calling the
    -- @ResultSet.getString()@ method of the driver, and uses it to build the
    -- Glue record. The @ResultSet@ object is implemented by each driver, so
    -- the behavior is specific to the driver you use. Refer to the
    -- documentation for your JDBC driver to understand how the driver performs
    -- the conversions.
    JDBCConnectorOptions -> Maybe (HashMap JDBCDataType GlueRecordType)
dataTypeMapping :: Prelude.Maybe (Prelude.HashMap JDBCDataType GlueRecordType),
    -- | Extra condition clause to filter data from source. For example:
    --
    -- @BillingCity=\'Mountain View\'@
    --
    -- When using a query instead of a table name, you should validate that the
    -- query works with the specified @filterPredicate@.
    JDBCConnectorOptions -> Maybe Text
filterPredicate :: Prelude.Maybe Prelude.Text,
    -- | The name of the job bookmark keys on which to sort.
    JDBCConnectorOptions -> Maybe [Text]
jobBookmarkKeys :: Prelude.Maybe [Prelude.Text],
    -- | Specifies an ascending or descending sort order.
    JDBCConnectorOptions -> Maybe Text
jobBookmarkKeysSortOrder :: Prelude.Maybe Prelude.Text,
    -- | The minimum value of @partitionColumn@ that is used to decide partition
    -- stride.
    JDBCConnectorOptions -> Maybe Natural
lowerBound :: Prelude.Maybe Prelude.Natural,
    -- | The number of partitions. This value, along with @lowerBound@
    -- (inclusive) and @upperBound@ (exclusive), form partition strides for
    -- generated @WHERE@ clause expressions that are used to split the
    -- @partitionColumn@.
    JDBCConnectorOptions -> Maybe Natural
numPartitions :: Prelude.Maybe Prelude.Natural,
    -- | The name of an integer column that is used for partitioning. This option
    -- works only when it\'s included with @lowerBound@, @upperBound@, and
    -- @numPartitions@. This option works the same way as in the Spark SQL JDBC
    -- reader.
    JDBCConnectorOptions -> Maybe Text
partitionColumn :: Prelude.Maybe Prelude.Text,
    -- | The maximum value of @partitionColumn@ that is used to decide partition
    -- stride.
    JDBCConnectorOptions -> Maybe Natural
upperBound :: Prelude.Maybe Prelude.Natural
  }
  deriving (JDBCConnectorOptions -> JDBCConnectorOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JDBCConnectorOptions -> JDBCConnectorOptions -> Bool
$c/= :: JDBCConnectorOptions -> JDBCConnectorOptions -> Bool
== :: JDBCConnectorOptions -> JDBCConnectorOptions -> Bool
$c== :: JDBCConnectorOptions -> JDBCConnectorOptions -> Bool
Prelude.Eq, ReadPrec [JDBCConnectorOptions]
ReadPrec JDBCConnectorOptions
Int -> ReadS JDBCConnectorOptions
ReadS [JDBCConnectorOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JDBCConnectorOptions]
$creadListPrec :: ReadPrec [JDBCConnectorOptions]
readPrec :: ReadPrec JDBCConnectorOptions
$creadPrec :: ReadPrec JDBCConnectorOptions
readList :: ReadS [JDBCConnectorOptions]
$creadList :: ReadS [JDBCConnectorOptions]
readsPrec :: Int -> ReadS JDBCConnectorOptions
$creadsPrec :: Int -> ReadS JDBCConnectorOptions
Prelude.Read, Int -> JDBCConnectorOptions -> ShowS
[JDBCConnectorOptions] -> ShowS
JDBCConnectorOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JDBCConnectorOptions] -> ShowS
$cshowList :: [JDBCConnectorOptions] -> ShowS
show :: JDBCConnectorOptions -> String
$cshow :: JDBCConnectorOptions -> String
showsPrec :: Int -> JDBCConnectorOptions -> ShowS
$cshowsPrec :: Int -> JDBCConnectorOptions -> ShowS
Prelude.Show, forall x. Rep JDBCConnectorOptions x -> JDBCConnectorOptions
forall x. JDBCConnectorOptions -> Rep JDBCConnectorOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JDBCConnectorOptions x -> JDBCConnectorOptions
$cfrom :: forall x. JDBCConnectorOptions -> Rep JDBCConnectorOptions x
Prelude.Generic)

-- |
-- Create a value of 'JDBCConnectorOptions' 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:
--
-- 'dataTypeMapping', 'jDBCConnectorOptions_dataTypeMapping' - Custom data type mapping that builds a mapping from a JDBC data type to
-- an Glue data type. For example, the option
-- @\"dataTypeMapping\":{\"FLOAT\":\"STRING\"}@ maps data fields of JDBC
-- type @FLOAT@ into the Java @String@ type by calling the
-- @ResultSet.getString()@ method of the driver, and uses it to build the
-- Glue record. The @ResultSet@ object is implemented by each driver, so
-- the behavior is specific to the driver you use. Refer to the
-- documentation for your JDBC driver to understand how the driver performs
-- the conversions.
--
-- 'filterPredicate', 'jDBCConnectorOptions_filterPredicate' - Extra condition clause to filter data from source. For example:
--
-- @BillingCity=\'Mountain View\'@
--
-- When using a query instead of a table name, you should validate that the
-- query works with the specified @filterPredicate@.
--
-- 'jobBookmarkKeys', 'jDBCConnectorOptions_jobBookmarkKeys' - The name of the job bookmark keys on which to sort.
--
-- 'jobBookmarkKeysSortOrder', 'jDBCConnectorOptions_jobBookmarkKeysSortOrder' - Specifies an ascending or descending sort order.
--
-- 'lowerBound', 'jDBCConnectorOptions_lowerBound' - The minimum value of @partitionColumn@ that is used to decide partition
-- stride.
--
-- 'numPartitions', 'jDBCConnectorOptions_numPartitions' - The number of partitions. This value, along with @lowerBound@
-- (inclusive) and @upperBound@ (exclusive), form partition strides for
-- generated @WHERE@ clause expressions that are used to split the
-- @partitionColumn@.
--
-- 'partitionColumn', 'jDBCConnectorOptions_partitionColumn' - The name of an integer column that is used for partitioning. This option
-- works only when it\'s included with @lowerBound@, @upperBound@, and
-- @numPartitions@. This option works the same way as in the Spark SQL JDBC
-- reader.
--
-- 'upperBound', 'jDBCConnectorOptions_upperBound' - The maximum value of @partitionColumn@ that is used to decide partition
-- stride.
newJDBCConnectorOptions ::
  JDBCConnectorOptions
newJDBCConnectorOptions :: JDBCConnectorOptions
newJDBCConnectorOptions =
  JDBCConnectorOptions'
    { $sel:dataTypeMapping:JDBCConnectorOptions' :: Maybe (HashMap JDBCDataType GlueRecordType)
dataTypeMapping =
        forall a. Maybe a
Prelude.Nothing,
      $sel:filterPredicate:JDBCConnectorOptions' :: Maybe Text
filterPredicate = forall a. Maybe a
Prelude.Nothing,
      $sel:jobBookmarkKeys:JDBCConnectorOptions' :: Maybe [Text]
jobBookmarkKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:jobBookmarkKeysSortOrder:JDBCConnectorOptions' :: Maybe Text
jobBookmarkKeysSortOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:lowerBound:JDBCConnectorOptions' :: Maybe Natural
lowerBound = forall a. Maybe a
Prelude.Nothing,
      $sel:numPartitions:JDBCConnectorOptions' :: Maybe Natural
numPartitions = forall a. Maybe a
Prelude.Nothing,
      $sel:partitionColumn:JDBCConnectorOptions' :: Maybe Text
partitionColumn = forall a. Maybe a
Prelude.Nothing,
      $sel:upperBound:JDBCConnectorOptions' :: Maybe Natural
upperBound = forall a. Maybe a
Prelude.Nothing
    }

-- | Custom data type mapping that builds a mapping from a JDBC data type to
-- an Glue data type. For example, the option
-- @\"dataTypeMapping\":{\"FLOAT\":\"STRING\"}@ maps data fields of JDBC
-- type @FLOAT@ into the Java @String@ type by calling the
-- @ResultSet.getString()@ method of the driver, and uses it to build the
-- Glue record. The @ResultSet@ object is implemented by each driver, so
-- the behavior is specific to the driver you use. Refer to the
-- documentation for your JDBC driver to understand how the driver performs
-- the conversions.
jDBCConnectorOptions_dataTypeMapping :: Lens.Lens' JDBCConnectorOptions (Prelude.Maybe (Prelude.HashMap JDBCDataType GlueRecordType))
jDBCConnectorOptions_dataTypeMapping :: Lens'
  JDBCConnectorOptions (Maybe (HashMap JDBCDataType GlueRecordType))
jDBCConnectorOptions_dataTypeMapping = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JDBCConnectorOptions' {Maybe (HashMap JDBCDataType GlueRecordType)
dataTypeMapping :: Maybe (HashMap JDBCDataType GlueRecordType)
$sel:dataTypeMapping:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe (HashMap JDBCDataType GlueRecordType)
dataTypeMapping} -> Maybe (HashMap JDBCDataType GlueRecordType)
dataTypeMapping) (\s :: JDBCConnectorOptions
s@JDBCConnectorOptions' {} Maybe (HashMap JDBCDataType GlueRecordType)
a -> JDBCConnectorOptions
s {$sel:dataTypeMapping:JDBCConnectorOptions' :: Maybe (HashMap JDBCDataType GlueRecordType)
dataTypeMapping = Maybe (HashMap JDBCDataType GlueRecordType)
a} :: JDBCConnectorOptions) 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

-- | Extra condition clause to filter data from source. For example:
--
-- @BillingCity=\'Mountain View\'@
--
-- When using a query instead of a table name, you should validate that the
-- query works with the specified @filterPredicate@.
jDBCConnectorOptions_filterPredicate :: Lens.Lens' JDBCConnectorOptions (Prelude.Maybe Prelude.Text)
jDBCConnectorOptions_filterPredicate :: Lens' JDBCConnectorOptions (Maybe Text)
jDBCConnectorOptions_filterPredicate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JDBCConnectorOptions' {Maybe Text
filterPredicate :: Maybe Text
$sel:filterPredicate:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
filterPredicate} -> Maybe Text
filterPredicate) (\s :: JDBCConnectorOptions
s@JDBCConnectorOptions' {} Maybe Text
a -> JDBCConnectorOptions
s {$sel:filterPredicate:JDBCConnectorOptions' :: Maybe Text
filterPredicate = Maybe Text
a} :: JDBCConnectorOptions)

-- | The name of the job bookmark keys on which to sort.
jDBCConnectorOptions_jobBookmarkKeys :: Lens.Lens' JDBCConnectorOptions (Prelude.Maybe [Prelude.Text])
jDBCConnectorOptions_jobBookmarkKeys :: Lens' JDBCConnectorOptions (Maybe [Text])
jDBCConnectorOptions_jobBookmarkKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JDBCConnectorOptions' {Maybe [Text]
jobBookmarkKeys :: Maybe [Text]
$sel:jobBookmarkKeys:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe [Text]
jobBookmarkKeys} -> Maybe [Text]
jobBookmarkKeys) (\s :: JDBCConnectorOptions
s@JDBCConnectorOptions' {} Maybe [Text]
a -> JDBCConnectorOptions
s {$sel:jobBookmarkKeys:JDBCConnectorOptions' :: Maybe [Text]
jobBookmarkKeys = Maybe [Text]
a} :: JDBCConnectorOptions) 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

-- | Specifies an ascending or descending sort order.
jDBCConnectorOptions_jobBookmarkKeysSortOrder :: Lens.Lens' JDBCConnectorOptions (Prelude.Maybe Prelude.Text)
jDBCConnectorOptions_jobBookmarkKeysSortOrder :: Lens' JDBCConnectorOptions (Maybe Text)
jDBCConnectorOptions_jobBookmarkKeysSortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JDBCConnectorOptions' {Maybe Text
jobBookmarkKeysSortOrder :: Maybe Text
$sel:jobBookmarkKeysSortOrder:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
jobBookmarkKeysSortOrder} -> Maybe Text
jobBookmarkKeysSortOrder) (\s :: JDBCConnectorOptions
s@JDBCConnectorOptions' {} Maybe Text
a -> JDBCConnectorOptions
s {$sel:jobBookmarkKeysSortOrder:JDBCConnectorOptions' :: Maybe Text
jobBookmarkKeysSortOrder = Maybe Text
a} :: JDBCConnectorOptions)

-- | The minimum value of @partitionColumn@ that is used to decide partition
-- stride.
jDBCConnectorOptions_lowerBound :: Lens.Lens' JDBCConnectorOptions (Prelude.Maybe Prelude.Natural)
jDBCConnectorOptions_lowerBound :: Lens' JDBCConnectorOptions (Maybe Natural)
jDBCConnectorOptions_lowerBound = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JDBCConnectorOptions' {Maybe Natural
lowerBound :: Maybe Natural
$sel:lowerBound:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
lowerBound} -> Maybe Natural
lowerBound) (\s :: JDBCConnectorOptions
s@JDBCConnectorOptions' {} Maybe Natural
a -> JDBCConnectorOptions
s {$sel:lowerBound:JDBCConnectorOptions' :: Maybe Natural
lowerBound = Maybe Natural
a} :: JDBCConnectorOptions)

-- | The number of partitions. This value, along with @lowerBound@
-- (inclusive) and @upperBound@ (exclusive), form partition strides for
-- generated @WHERE@ clause expressions that are used to split the
-- @partitionColumn@.
jDBCConnectorOptions_numPartitions :: Lens.Lens' JDBCConnectorOptions (Prelude.Maybe Prelude.Natural)
jDBCConnectorOptions_numPartitions :: Lens' JDBCConnectorOptions (Maybe Natural)
jDBCConnectorOptions_numPartitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JDBCConnectorOptions' {Maybe Natural
numPartitions :: Maybe Natural
$sel:numPartitions:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
numPartitions} -> Maybe Natural
numPartitions) (\s :: JDBCConnectorOptions
s@JDBCConnectorOptions' {} Maybe Natural
a -> JDBCConnectorOptions
s {$sel:numPartitions:JDBCConnectorOptions' :: Maybe Natural
numPartitions = Maybe Natural
a} :: JDBCConnectorOptions)

-- | The name of an integer column that is used for partitioning. This option
-- works only when it\'s included with @lowerBound@, @upperBound@, and
-- @numPartitions@. This option works the same way as in the Spark SQL JDBC
-- reader.
jDBCConnectorOptions_partitionColumn :: Lens.Lens' JDBCConnectorOptions (Prelude.Maybe Prelude.Text)
jDBCConnectorOptions_partitionColumn :: Lens' JDBCConnectorOptions (Maybe Text)
jDBCConnectorOptions_partitionColumn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JDBCConnectorOptions' {Maybe Text
partitionColumn :: Maybe Text
$sel:partitionColumn:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
partitionColumn} -> Maybe Text
partitionColumn) (\s :: JDBCConnectorOptions
s@JDBCConnectorOptions' {} Maybe Text
a -> JDBCConnectorOptions
s {$sel:partitionColumn:JDBCConnectorOptions' :: Maybe Text
partitionColumn = Maybe Text
a} :: JDBCConnectorOptions)

-- | The maximum value of @partitionColumn@ that is used to decide partition
-- stride.
jDBCConnectorOptions_upperBound :: Lens.Lens' JDBCConnectorOptions (Prelude.Maybe Prelude.Natural)
jDBCConnectorOptions_upperBound :: Lens' JDBCConnectorOptions (Maybe Natural)
jDBCConnectorOptions_upperBound = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JDBCConnectorOptions' {Maybe Natural
upperBound :: Maybe Natural
$sel:upperBound:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
upperBound} -> Maybe Natural
upperBound) (\s :: JDBCConnectorOptions
s@JDBCConnectorOptions' {} Maybe Natural
a -> JDBCConnectorOptions
s {$sel:upperBound:JDBCConnectorOptions' :: Maybe Natural
upperBound = Maybe Natural
a} :: JDBCConnectorOptions)

instance Data.FromJSON JDBCConnectorOptions where
  parseJSON :: Value -> Parser JDBCConnectorOptions
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JDBCConnectorOptions"
      ( \Object
x ->
          Maybe (HashMap JDBCDataType GlueRecordType)
-> Maybe Text
-> Maybe [Text]
-> Maybe Text
-> Maybe Natural
-> Maybe Natural
-> Maybe Text
-> Maybe Natural
-> JDBCConnectorOptions
JDBCConnectorOptions'
            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
"DataTypeMapping"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"FilterPredicate")
            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
"JobBookmarkKeys"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"JobBookmarkKeysSortOrder")
            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
"LowerBound")
            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
"NumPartitions")
            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
"PartitionColumn")
            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
"UpperBound")
      )

instance Prelude.Hashable JDBCConnectorOptions where
  hashWithSalt :: Int -> JDBCConnectorOptions -> Int
hashWithSalt Int
_salt JDBCConnectorOptions' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe (HashMap JDBCDataType GlueRecordType)
upperBound :: Maybe Natural
partitionColumn :: Maybe Text
numPartitions :: Maybe Natural
lowerBound :: Maybe Natural
jobBookmarkKeysSortOrder :: Maybe Text
jobBookmarkKeys :: Maybe [Text]
filterPredicate :: Maybe Text
dataTypeMapping :: Maybe (HashMap JDBCDataType GlueRecordType)
$sel:upperBound:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
$sel:partitionColumn:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
$sel:numPartitions:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
$sel:lowerBound:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
$sel:jobBookmarkKeysSortOrder:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
$sel:jobBookmarkKeys:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe [Text]
$sel:filterPredicate:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
$sel:dataTypeMapping:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe (HashMap JDBCDataType GlueRecordType)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap JDBCDataType GlueRecordType)
dataTypeMapping
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
filterPredicate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
jobBookmarkKeys
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobBookmarkKeysSortOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
lowerBound
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
numPartitions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
partitionColumn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
upperBound

instance Prelude.NFData JDBCConnectorOptions where
  rnf :: JDBCConnectorOptions -> ()
rnf JDBCConnectorOptions' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe (HashMap JDBCDataType GlueRecordType)
upperBound :: Maybe Natural
partitionColumn :: Maybe Text
numPartitions :: Maybe Natural
lowerBound :: Maybe Natural
jobBookmarkKeysSortOrder :: Maybe Text
jobBookmarkKeys :: Maybe [Text]
filterPredicate :: Maybe Text
dataTypeMapping :: Maybe (HashMap JDBCDataType GlueRecordType)
$sel:upperBound:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
$sel:partitionColumn:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
$sel:numPartitions:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
$sel:lowerBound:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
$sel:jobBookmarkKeysSortOrder:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
$sel:jobBookmarkKeys:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe [Text]
$sel:filterPredicate:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
$sel:dataTypeMapping:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe (HashMap JDBCDataType GlueRecordType)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap JDBCDataType GlueRecordType)
dataTypeMapping
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
filterPredicate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
jobBookmarkKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobBookmarkKeysSortOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
lowerBound
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
numPartitions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
partitionColumn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
upperBound

instance Data.ToJSON JDBCConnectorOptions where
  toJSON :: JDBCConnectorOptions -> Value
toJSON JDBCConnectorOptions' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe (HashMap JDBCDataType GlueRecordType)
upperBound :: Maybe Natural
partitionColumn :: Maybe Text
numPartitions :: Maybe Natural
lowerBound :: Maybe Natural
jobBookmarkKeysSortOrder :: Maybe Text
jobBookmarkKeys :: Maybe [Text]
filterPredicate :: Maybe Text
dataTypeMapping :: Maybe (HashMap JDBCDataType GlueRecordType)
$sel:upperBound:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
$sel:partitionColumn:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
$sel:numPartitions:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
$sel:lowerBound:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Natural
$sel:jobBookmarkKeysSortOrder:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
$sel:jobBookmarkKeys:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe [Text]
$sel:filterPredicate:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe Text
$sel:dataTypeMapping:JDBCConnectorOptions' :: JDBCConnectorOptions -> Maybe (HashMap JDBCDataType GlueRecordType)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DataTypeMapping" 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 (HashMap JDBCDataType GlueRecordType)
dataTypeMapping,
            (Key
"FilterPredicate" 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
filterPredicate,
            (Key
"JobBookmarkKeys" 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]
jobBookmarkKeys,
            (Key
"JobBookmarkKeysSortOrder" 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
jobBookmarkKeysSortOrder,
            (Key
"LowerBound" 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 Natural
lowerBound,
            (Key
"NumPartitions" 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 Natural
numPartitions,
            (Key
"PartitionColumn" 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
partitionColumn,
            (Key
"UpperBound" 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 Natural
upperBound
          ]
      )