{-# 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.Athena.Types.ColumnInfo
-- 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.Athena.Types.ColumnInfo where

import Amazonka.Athena.Types.ColumnNullable
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

-- | Information about the columns in a query execution result.
--
-- /See:/ 'newColumnInfo' smart constructor.
data ColumnInfo = ColumnInfo'
  { -- | Indicates whether values in the column are case-sensitive.
    ColumnInfo -> Maybe Bool
caseSensitive :: Prelude.Maybe Prelude.Bool,
    -- | The catalog to which the query results belong.
    ColumnInfo -> Maybe Text
catalogName :: Prelude.Maybe Prelude.Text,
    -- | A column label.
    ColumnInfo -> Maybe Text
label :: Prelude.Maybe Prelude.Text,
    -- | Indicates the column\'s nullable status.
    ColumnInfo -> Maybe ColumnNullable
nullable :: Prelude.Maybe ColumnNullable,
    -- | For @DECIMAL@ data types, specifies the total number of digits, up to
    -- 38. For performance reasons, we recommend up to 18 digits.
    ColumnInfo -> Maybe Int
precision :: Prelude.Maybe Prelude.Int,
    -- | For @DECIMAL@ data types, specifies the total number of digits in the
    -- fractional part of the value. Defaults to 0.
    ColumnInfo -> Maybe Int
scale :: Prelude.Maybe Prelude.Int,
    -- | The schema name (database name) to which the query results belong.
    ColumnInfo -> Maybe Text
schemaName :: Prelude.Maybe Prelude.Text,
    -- | The table name for the query results.
    ColumnInfo -> Maybe Text
tableName :: Prelude.Maybe Prelude.Text,
    -- | The name of the column.
    ColumnInfo -> Text
name :: Prelude.Text,
    -- | The data type of the column.
    ColumnInfo -> Text
type' :: Prelude.Text
  }
  deriving (ColumnInfo -> ColumnInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColumnInfo -> ColumnInfo -> Bool
$c/= :: ColumnInfo -> ColumnInfo -> Bool
== :: ColumnInfo -> ColumnInfo -> Bool
$c== :: ColumnInfo -> ColumnInfo -> Bool
Prelude.Eq, ReadPrec [ColumnInfo]
ReadPrec ColumnInfo
Int -> ReadS ColumnInfo
ReadS [ColumnInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ColumnInfo]
$creadListPrec :: ReadPrec [ColumnInfo]
readPrec :: ReadPrec ColumnInfo
$creadPrec :: ReadPrec ColumnInfo
readList :: ReadS [ColumnInfo]
$creadList :: ReadS [ColumnInfo]
readsPrec :: Int -> ReadS ColumnInfo
$creadsPrec :: Int -> ReadS ColumnInfo
Prelude.Read, Int -> ColumnInfo -> ShowS
[ColumnInfo] -> ShowS
ColumnInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColumnInfo] -> ShowS
$cshowList :: [ColumnInfo] -> ShowS
show :: ColumnInfo -> String
$cshow :: ColumnInfo -> String
showsPrec :: Int -> ColumnInfo -> ShowS
$cshowsPrec :: Int -> ColumnInfo -> ShowS
Prelude.Show, forall x. Rep ColumnInfo x -> ColumnInfo
forall x. ColumnInfo -> Rep ColumnInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColumnInfo x -> ColumnInfo
$cfrom :: forall x. ColumnInfo -> Rep ColumnInfo x
Prelude.Generic)

-- |
-- Create a value of 'ColumnInfo' 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:
--
-- 'caseSensitive', 'columnInfo_caseSensitive' - Indicates whether values in the column are case-sensitive.
--
-- 'catalogName', 'columnInfo_catalogName' - The catalog to which the query results belong.
--
-- 'label', 'columnInfo_label' - A column label.
--
-- 'nullable', 'columnInfo_nullable' - Indicates the column\'s nullable status.
--
-- 'precision', 'columnInfo_precision' - For @DECIMAL@ data types, specifies the total number of digits, up to
-- 38. For performance reasons, we recommend up to 18 digits.
--
-- 'scale', 'columnInfo_scale' - For @DECIMAL@ data types, specifies the total number of digits in the
-- fractional part of the value. Defaults to 0.
--
-- 'schemaName', 'columnInfo_schemaName' - The schema name (database name) to which the query results belong.
--
-- 'tableName', 'columnInfo_tableName' - The table name for the query results.
--
-- 'name', 'columnInfo_name' - The name of the column.
--
-- 'type'', 'columnInfo_type' - The data type of the column.
newColumnInfo ::
  -- | 'name'
  Prelude.Text ->
  -- | 'type''
  Prelude.Text ->
  ColumnInfo
newColumnInfo :: Text -> Text -> ColumnInfo
newColumnInfo Text
pName_ Text
pType_ =
  ColumnInfo'
    { $sel:caseSensitive:ColumnInfo' :: Maybe Bool
caseSensitive = forall a. Maybe a
Prelude.Nothing,
      $sel:catalogName:ColumnInfo' :: Maybe Text
catalogName = forall a. Maybe a
Prelude.Nothing,
      $sel:label:ColumnInfo' :: Maybe Text
label = forall a. Maybe a
Prelude.Nothing,
      $sel:nullable:ColumnInfo' :: Maybe ColumnNullable
nullable = forall a. Maybe a
Prelude.Nothing,
      $sel:precision:ColumnInfo' :: Maybe Int
precision = forall a. Maybe a
Prelude.Nothing,
      $sel:scale:ColumnInfo' :: Maybe Int
scale = forall a. Maybe a
Prelude.Nothing,
      $sel:schemaName:ColumnInfo' :: Maybe Text
schemaName = forall a. Maybe a
Prelude.Nothing,
      $sel:tableName:ColumnInfo' :: Maybe Text
tableName = forall a. Maybe a
Prelude.Nothing,
      $sel:name:ColumnInfo' :: Text
name = Text
pName_,
      $sel:type':ColumnInfo' :: Text
type' = Text
pType_
    }

-- | Indicates whether values in the column are case-sensitive.
columnInfo_caseSensitive :: Lens.Lens' ColumnInfo (Prelude.Maybe Prelude.Bool)
columnInfo_caseSensitive :: Lens' ColumnInfo (Maybe Bool)
columnInfo_caseSensitive = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Maybe Bool
caseSensitive :: Maybe Bool
$sel:caseSensitive:ColumnInfo' :: ColumnInfo -> Maybe Bool
caseSensitive} -> Maybe Bool
caseSensitive) (\s :: ColumnInfo
s@ColumnInfo' {} Maybe Bool
a -> ColumnInfo
s {$sel:caseSensitive:ColumnInfo' :: Maybe Bool
caseSensitive = Maybe Bool
a} :: ColumnInfo)

-- | The catalog to which the query results belong.
columnInfo_catalogName :: Lens.Lens' ColumnInfo (Prelude.Maybe Prelude.Text)
columnInfo_catalogName :: Lens' ColumnInfo (Maybe Text)
columnInfo_catalogName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Maybe Text
catalogName :: Maybe Text
$sel:catalogName:ColumnInfo' :: ColumnInfo -> Maybe Text
catalogName} -> Maybe Text
catalogName) (\s :: ColumnInfo
s@ColumnInfo' {} Maybe Text
a -> ColumnInfo
s {$sel:catalogName:ColumnInfo' :: Maybe Text
catalogName = Maybe Text
a} :: ColumnInfo)

-- | A column label.
columnInfo_label :: Lens.Lens' ColumnInfo (Prelude.Maybe Prelude.Text)
columnInfo_label :: Lens' ColumnInfo (Maybe Text)
columnInfo_label = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Maybe Text
label :: Maybe Text
$sel:label:ColumnInfo' :: ColumnInfo -> Maybe Text
label} -> Maybe Text
label) (\s :: ColumnInfo
s@ColumnInfo' {} Maybe Text
a -> ColumnInfo
s {$sel:label:ColumnInfo' :: Maybe Text
label = Maybe Text
a} :: ColumnInfo)

-- | Indicates the column\'s nullable status.
columnInfo_nullable :: Lens.Lens' ColumnInfo (Prelude.Maybe ColumnNullable)
columnInfo_nullable :: Lens' ColumnInfo (Maybe ColumnNullable)
columnInfo_nullable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Maybe ColumnNullable
nullable :: Maybe ColumnNullable
$sel:nullable:ColumnInfo' :: ColumnInfo -> Maybe ColumnNullable
nullable} -> Maybe ColumnNullable
nullable) (\s :: ColumnInfo
s@ColumnInfo' {} Maybe ColumnNullable
a -> ColumnInfo
s {$sel:nullable:ColumnInfo' :: Maybe ColumnNullable
nullable = Maybe ColumnNullable
a} :: ColumnInfo)

-- | For @DECIMAL@ data types, specifies the total number of digits, up to
-- 38. For performance reasons, we recommend up to 18 digits.
columnInfo_precision :: Lens.Lens' ColumnInfo (Prelude.Maybe Prelude.Int)
columnInfo_precision :: Lens' ColumnInfo (Maybe Int)
columnInfo_precision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Maybe Int
precision :: Maybe Int
$sel:precision:ColumnInfo' :: ColumnInfo -> Maybe Int
precision} -> Maybe Int
precision) (\s :: ColumnInfo
s@ColumnInfo' {} Maybe Int
a -> ColumnInfo
s {$sel:precision:ColumnInfo' :: Maybe Int
precision = Maybe Int
a} :: ColumnInfo)

-- | For @DECIMAL@ data types, specifies the total number of digits in the
-- fractional part of the value. Defaults to 0.
columnInfo_scale :: Lens.Lens' ColumnInfo (Prelude.Maybe Prelude.Int)
columnInfo_scale :: Lens' ColumnInfo (Maybe Int)
columnInfo_scale = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Maybe Int
scale :: Maybe Int
$sel:scale:ColumnInfo' :: ColumnInfo -> Maybe Int
scale} -> Maybe Int
scale) (\s :: ColumnInfo
s@ColumnInfo' {} Maybe Int
a -> ColumnInfo
s {$sel:scale:ColumnInfo' :: Maybe Int
scale = Maybe Int
a} :: ColumnInfo)

-- | The schema name (database name) to which the query results belong.
columnInfo_schemaName :: Lens.Lens' ColumnInfo (Prelude.Maybe Prelude.Text)
columnInfo_schemaName :: Lens' ColumnInfo (Maybe Text)
columnInfo_schemaName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Maybe Text
schemaName :: Maybe Text
$sel:schemaName:ColumnInfo' :: ColumnInfo -> Maybe Text
schemaName} -> Maybe Text
schemaName) (\s :: ColumnInfo
s@ColumnInfo' {} Maybe Text
a -> ColumnInfo
s {$sel:schemaName:ColumnInfo' :: Maybe Text
schemaName = Maybe Text
a} :: ColumnInfo)

-- | The table name for the query results.
columnInfo_tableName :: Lens.Lens' ColumnInfo (Prelude.Maybe Prelude.Text)
columnInfo_tableName :: Lens' ColumnInfo (Maybe Text)
columnInfo_tableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Maybe Text
tableName :: Maybe Text
$sel:tableName:ColumnInfo' :: ColumnInfo -> Maybe Text
tableName} -> Maybe Text
tableName) (\s :: ColumnInfo
s@ColumnInfo' {} Maybe Text
a -> ColumnInfo
s {$sel:tableName:ColumnInfo' :: Maybe Text
tableName = Maybe Text
a} :: ColumnInfo)

-- | The name of the column.
columnInfo_name :: Lens.Lens' ColumnInfo Prelude.Text
columnInfo_name :: Lens' ColumnInfo Text
columnInfo_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Text
name :: Text
$sel:name:ColumnInfo' :: ColumnInfo -> Text
name} -> Text
name) (\s :: ColumnInfo
s@ColumnInfo' {} Text
a -> ColumnInfo
s {$sel:name:ColumnInfo' :: Text
name = Text
a} :: ColumnInfo)

-- | The data type of the column.
columnInfo_type :: Lens.Lens' ColumnInfo Prelude.Text
columnInfo_type :: Lens' ColumnInfo Text
columnInfo_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ColumnInfo' {Text
type' :: Text
$sel:type':ColumnInfo' :: ColumnInfo -> Text
type'} -> Text
type') (\s :: ColumnInfo
s@ColumnInfo' {} Text
a -> ColumnInfo
s {$sel:type':ColumnInfo' :: Text
type' = Text
a} :: ColumnInfo)

instance Data.FromJSON ColumnInfo where
  parseJSON :: Value -> Parser ColumnInfo
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ColumnInfo"
      ( \Object
x ->
          Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe ColumnNullable
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> ColumnInfo
ColumnInfo'
            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
"CaseSensitive")
            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
"CatalogName")
            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
"Label")
            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
"Nullable")
            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
"Precision")
            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
"Scale")
            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
"SchemaName")
            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
"TableName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Type")
      )

instance Prelude.Hashable ColumnInfo where
  hashWithSalt :: Int -> ColumnInfo -> Int
hashWithSalt Int
_salt ColumnInfo' {Maybe Bool
Maybe Int
Maybe Text
Maybe ColumnNullable
Text
type' :: Text
name :: Text
tableName :: Maybe Text
schemaName :: Maybe Text
scale :: Maybe Int
precision :: Maybe Int
nullable :: Maybe ColumnNullable
label :: Maybe Text
catalogName :: Maybe Text
caseSensitive :: Maybe Bool
$sel:type':ColumnInfo' :: ColumnInfo -> Text
$sel:name:ColumnInfo' :: ColumnInfo -> Text
$sel:tableName:ColumnInfo' :: ColumnInfo -> Maybe Text
$sel:schemaName:ColumnInfo' :: ColumnInfo -> Maybe Text
$sel:scale:ColumnInfo' :: ColumnInfo -> Maybe Int
$sel:precision:ColumnInfo' :: ColumnInfo -> Maybe Int
$sel:nullable:ColumnInfo' :: ColumnInfo -> Maybe ColumnNullable
$sel:label:ColumnInfo' :: ColumnInfo -> Maybe Text
$sel:catalogName:ColumnInfo' :: ColumnInfo -> Maybe Text
$sel:caseSensitive:ColumnInfo' :: ColumnInfo -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
caseSensitive
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
catalogName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
label
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ColumnNullable
nullable
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
precision
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
scale
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
schemaName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tableName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
type'

instance Prelude.NFData ColumnInfo where
  rnf :: ColumnInfo -> ()
rnf ColumnInfo' {Maybe Bool
Maybe Int
Maybe Text
Maybe ColumnNullable
Text
type' :: Text
name :: Text
tableName :: Maybe Text
schemaName :: Maybe Text
scale :: Maybe Int
precision :: Maybe Int
nullable :: Maybe ColumnNullable
label :: Maybe Text
catalogName :: Maybe Text
caseSensitive :: Maybe Bool
$sel:type':ColumnInfo' :: ColumnInfo -> Text
$sel:name:ColumnInfo' :: ColumnInfo -> Text
$sel:tableName:ColumnInfo' :: ColumnInfo -> Maybe Text
$sel:schemaName:ColumnInfo' :: ColumnInfo -> Maybe Text
$sel:scale:ColumnInfo' :: ColumnInfo -> Maybe Int
$sel:precision:ColumnInfo' :: ColumnInfo -> Maybe Int
$sel:nullable:ColumnInfo' :: ColumnInfo -> Maybe ColumnNullable
$sel:label:ColumnInfo' :: ColumnInfo -> Maybe Text
$sel:catalogName:ColumnInfo' :: ColumnInfo -> Maybe Text
$sel:caseSensitive:ColumnInfo' :: ColumnInfo -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
caseSensitive
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
catalogName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
label
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ColumnNullable
nullable
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
precision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
scale
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
schemaName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tableName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
type'