{-# 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.Projection
-- 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.Projection 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.ProjectionType
import Amazonka.DynamoDB.Types.WriteRequest
import qualified Amazonka.Prelude as Prelude

-- | Represents attributes that are copied (projected) from the table into an
-- index. These are in addition to the primary key attributes and index key
-- attributes, which are automatically projected.
--
-- /See:/ 'newProjection' smart constructor.
data Projection = Projection'
  { -- | Represents the non-key attribute names which will be projected into the
    -- index.
    --
    -- For local secondary indexes, the total count of @NonKeyAttributes@
    -- summed across all of the local secondary indexes, must not exceed 100.
    -- If you project the same attribute into two different indexes, this
    -- counts as two distinct attributes when determining the total.
    Projection -> Maybe (NonEmpty Text)
nonKeyAttributes :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The set of attributes that are projected into the index:
    --
    -- -   @KEYS_ONLY@ - Only the index and primary keys are projected into the
    --     index.
    --
    -- -   @INCLUDE@ - In addition to the attributes described in @KEYS_ONLY@,
    --     the secondary index will include other non-key attributes that you
    --     specify.
    --
    -- -   @ALL@ - All of the table attributes are projected into the index.
    Projection -> Maybe ProjectionType
projectionType :: Prelude.Maybe ProjectionType
  }
  deriving (Projection -> Projection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Projection -> Projection -> Bool
$c/= :: Projection -> Projection -> Bool
== :: Projection -> Projection -> Bool
$c== :: Projection -> Projection -> Bool
Prelude.Eq, ReadPrec [Projection]
ReadPrec Projection
Int -> ReadS Projection
ReadS [Projection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Projection]
$creadListPrec :: ReadPrec [Projection]
readPrec :: ReadPrec Projection
$creadPrec :: ReadPrec Projection
readList :: ReadS [Projection]
$creadList :: ReadS [Projection]
readsPrec :: Int -> ReadS Projection
$creadsPrec :: Int -> ReadS Projection
Prelude.Read, Int -> Projection -> ShowS
[Projection] -> ShowS
Projection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Projection] -> ShowS
$cshowList :: [Projection] -> ShowS
show :: Projection -> String
$cshow :: Projection -> String
showsPrec :: Int -> Projection -> ShowS
$cshowsPrec :: Int -> Projection -> ShowS
Prelude.Show, forall x. Rep Projection x -> Projection
forall x. Projection -> Rep Projection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Projection x -> Projection
$cfrom :: forall x. Projection -> Rep Projection x
Prelude.Generic)

-- |
-- Create a value of 'Projection' 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:
--
-- 'nonKeyAttributes', 'projection_nonKeyAttributes' - Represents the non-key attribute names which will be projected into the
-- index.
--
-- For local secondary indexes, the total count of @NonKeyAttributes@
-- summed across all of the local secondary indexes, must not exceed 100.
-- If you project the same attribute into two different indexes, this
-- counts as two distinct attributes when determining the total.
--
-- 'projectionType', 'projection_projectionType' - The set of attributes that are projected into the index:
--
-- -   @KEYS_ONLY@ - Only the index and primary keys are projected into the
--     index.
--
-- -   @INCLUDE@ - In addition to the attributes described in @KEYS_ONLY@,
--     the secondary index will include other non-key attributes that you
--     specify.
--
-- -   @ALL@ - All of the table attributes are projected into the index.
newProjection ::
  Projection
newProjection :: Projection
newProjection =
  Projection'
    { $sel:nonKeyAttributes:Projection' :: Maybe (NonEmpty Text)
nonKeyAttributes = forall a. Maybe a
Prelude.Nothing,
      $sel:projectionType:Projection' :: Maybe ProjectionType
projectionType = forall a. Maybe a
Prelude.Nothing
    }

-- | Represents the non-key attribute names which will be projected into the
-- index.
--
-- For local secondary indexes, the total count of @NonKeyAttributes@
-- summed across all of the local secondary indexes, must not exceed 100.
-- If you project the same attribute into two different indexes, this
-- counts as two distinct attributes when determining the total.
projection_nonKeyAttributes :: Lens.Lens' Projection (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
projection_nonKeyAttributes :: Lens' Projection (Maybe (NonEmpty Text))
projection_nonKeyAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Projection' {Maybe (NonEmpty Text)
nonKeyAttributes :: Maybe (NonEmpty Text)
$sel:nonKeyAttributes:Projection' :: Projection -> Maybe (NonEmpty Text)
nonKeyAttributes} -> Maybe (NonEmpty Text)
nonKeyAttributes) (\s :: Projection
s@Projection' {} Maybe (NonEmpty Text)
a -> Projection
s {$sel:nonKeyAttributes:Projection' :: Maybe (NonEmpty Text)
nonKeyAttributes = Maybe (NonEmpty Text)
a} :: Projection) 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

-- | The set of attributes that are projected into the index:
--
-- -   @KEYS_ONLY@ - Only the index and primary keys are projected into the
--     index.
--
-- -   @INCLUDE@ - In addition to the attributes described in @KEYS_ONLY@,
--     the secondary index will include other non-key attributes that you
--     specify.
--
-- -   @ALL@ - All of the table attributes are projected into the index.
projection_projectionType :: Lens.Lens' Projection (Prelude.Maybe ProjectionType)
projection_projectionType :: Lens' Projection (Maybe ProjectionType)
projection_projectionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Projection' {Maybe ProjectionType
projectionType :: Maybe ProjectionType
$sel:projectionType:Projection' :: Projection -> Maybe ProjectionType
projectionType} -> Maybe ProjectionType
projectionType) (\s :: Projection
s@Projection' {} Maybe ProjectionType
a -> Projection
s {$sel:projectionType:Projection' :: Maybe ProjectionType
projectionType = Maybe ProjectionType
a} :: Projection)

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

instance Prelude.Hashable Projection where
  hashWithSalt :: Int -> Projection -> Int
hashWithSalt Int
_salt Projection' {Maybe (NonEmpty Text)
Maybe ProjectionType
projectionType :: Maybe ProjectionType
nonKeyAttributes :: Maybe (NonEmpty Text)
$sel:projectionType:Projection' :: Projection -> Maybe ProjectionType
$sel:nonKeyAttributes:Projection' :: Projection -> Maybe (NonEmpty Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
nonKeyAttributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProjectionType
projectionType

instance Prelude.NFData Projection where
  rnf :: Projection -> ()
rnf Projection' {Maybe (NonEmpty Text)
Maybe ProjectionType
projectionType :: Maybe ProjectionType
nonKeyAttributes :: Maybe (NonEmpty Text)
$sel:projectionType:Projection' :: Projection -> Maybe ProjectionType
$sel:nonKeyAttributes:Projection' :: Projection -> Maybe (NonEmpty Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
nonKeyAttributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProjectionType
projectionType

instance Data.ToJSON Projection where
  toJSON :: Projection -> Value
toJSON Projection' {Maybe (NonEmpty Text)
Maybe ProjectionType
projectionType :: Maybe ProjectionType
nonKeyAttributes :: Maybe (NonEmpty Text)
$sel:projectionType:Projection' :: Projection -> Maybe ProjectionType
$sel:nonKeyAttributes:Projection' :: Projection -> Maybe (NonEmpty Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"NonKeyAttributes" 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 (NonEmpty Text)
nonKeyAttributes,
            (Key
"ProjectionType" 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 ProjectionType
projectionType
          ]
      )