{-# 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.Kinesis.Types.Shard
-- 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.Kinesis.Types.Shard where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Kinesis.Types.HashKeyRange
import Amazonka.Kinesis.Types.SequenceNumberRange
import qualified Amazonka.Prelude as Prelude

-- | A uniquely identified group of data records in a Kinesis data stream.
--
-- /See:/ 'newShard' smart constructor.
data Shard = Shard'
  { -- | The shard ID of the shard adjacent to the shard\'s parent.
    Shard -> Maybe Text
adjacentParentShardId :: Prelude.Maybe Prelude.Text,
    -- | The shard ID of the shard\'s parent.
    Shard -> Maybe Text
parentShardId :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the shard within the stream.
    Shard -> Text
shardId :: Prelude.Text,
    -- | The range of possible hash key values for the shard, which is a set of
    -- ordered contiguous positive integers.
    Shard -> HashKeyRange
hashKeyRange :: HashKeyRange,
    -- | The range of possible sequence numbers for the shard.
    Shard -> SequenceNumberRange
sequenceNumberRange :: SequenceNumberRange
  }
  deriving (Shard -> Shard -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Shard -> Shard -> Bool
$c/= :: Shard -> Shard -> Bool
== :: Shard -> Shard -> Bool
$c== :: Shard -> Shard -> Bool
Prelude.Eq, ReadPrec [Shard]
ReadPrec Shard
Int -> ReadS Shard
ReadS [Shard]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Shard]
$creadListPrec :: ReadPrec [Shard]
readPrec :: ReadPrec Shard
$creadPrec :: ReadPrec Shard
readList :: ReadS [Shard]
$creadList :: ReadS [Shard]
readsPrec :: Int -> ReadS Shard
$creadsPrec :: Int -> ReadS Shard
Prelude.Read, Int -> Shard -> ShowS
[Shard] -> ShowS
Shard -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Shard] -> ShowS
$cshowList :: [Shard] -> ShowS
show :: Shard -> String
$cshow :: Shard -> String
showsPrec :: Int -> Shard -> ShowS
$cshowsPrec :: Int -> Shard -> ShowS
Prelude.Show, forall x. Rep Shard x -> Shard
forall x. Shard -> Rep Shard x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Shard x -> Shard
$cfrom :: forall x. Shard -> Rep Shard x
Prelude.Generic)

-- |
-- Create a value of 'Shard' 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:
--
-- 'adjacentParentShardId', 'shard_adjacentParentShardId' - The shard ID of the shard adjacent to the shard\'s parent.
--
-- 'parentShardId', 'shard_parentShardId' - The shard ID of the shard\'s parent.
--
-- 'shardId', 'shard_shardId' - The unique identifier of the shard within the stream.
--
-- 'hashKeyRange', 'shard_hashKeyRange' - The range of possible hash key values for the shard, which is a set of
-- ordered contiguous positive integers.
--
-- 'sequenceNumberRange', 'shard_sequenceNumberRange' - The range of possible sequence numbers for the shard.
newShard ::
  -- | 'shardId'
  Prelude.Text ->
  -- | 'hashKeyRange'
  HashKeyRange ->
  -- | 'sequenceNumberRange'
  SequenceNumberRange ->
  Shard
newShard :: Text -> HashKeyRange -> SequenceNumberRange -> Shard
newShard
  Text
pShardId_
  HashKeyRange
pHashKeyRange_
  SequenceNumberRange
pSequenceNumberRange_ =
    Shard'
      { $sel:adjacentParentShardId:Shard' :: Maybe Text
adjacentParentShardId = forall a. Maybe a
Prelude.Nothing,
        $sel:parentShardId:Shard' :: Maybe Text
parentShardId = forall a. Maybe a
Prelude.Nothing,
        $sel:shardId:Shard' :: Text
shardId = Text
pShardId_,
        $sel:hashKeyRange:Shard' :: HashKeyRange
hashKeyRange = HashKeyRange
pHashKeyRange_,
        $sel:sequenceNumberRange:Shard' :: SequenceNumberRange
sequenceNumberRange = SequenceNumberRange
pSequenceNumberRange_
      }

-- | The shard ID of the shard adjacent to the shard\'s parent.
shard_adjacentParentShardId :: Lens.Lens' Shard (Prelude.Maybe Prelude.Text)
shard_adjacentParentShardId :: Lens' Shard (Maybe Text)
shard_adjacentParentShardId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Shard' {Maybe Text
adjacentParentShardId :: Maybe Text
$sel:adjacentParentShardId:Shard' :: Shard -> Maybe Text
adjacentParentShardId} -> Maybe Text
adjacentParentShardId) (\s :: Shard
s@Shard' {} Maybe Text
a -> Shard
s {$sel:adjacentParentShardId:Shard' :: Maybe Text
adjacentParentShardId = Maybe Text
a} :: Shard)

-- | The shard ID of the shard\'s parent.
shard_parentShardId :: Lens.Lens' Shard (Prelude.Maybe Prelude.Text)
shard_parentShardId :: Lens' Shard (Maybe Text)
shard_parentShardId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Shard' {Maybe Text
parentShardId :: Maybe Text
$sel:parentShardId:Shard' :: Shard -> Maybe Text
parentShardId} -> Maybe Text
parentShardId) (\s :: Shard
s@Shard' {} Maybe Text
a -> Shard
s {$sel:parentShardId:Shard' :: Maybe Text
parentShardId = Maybe Text
a} :: Shard)

-- | The unique identifier of the shard within the stream.
shard_shardId :: Lens.Lens' Shard Prelude.Text
shard_shardId :: Lens' Shard Text
shard_shardId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Shard' {Text
shardId :: Text
$sel:shardId:Shard' :: Shard -> Text
shardId} -> Text
shardId) (\s :: Shard
s@Shard' {} Text
a -> Shard
s {$sel:shardId:Shard' :: Text
shardId = Text
a} :: Shard)

-- | The range of possible hash key values for the shard, which is a set of
-- ordered contiguous positive integers.
shard_hashKeyRange :: Lens.Lens' Shard HashKeyRange
shard_hashKeyRange :: Lens' Shard HashKeyRange
shard_hashKeyRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Shard' {HashKeyRange
hashKeyRange :: HashKeyRange
$sel:hashKeyRange:Shard' :: Shard -> HashKeyRange
hashKeyRange} -> HashKeyRange
hashKeyRange) (\s :: Shard
s@Shard' {} HashKeyRange
a -> Shard
s {$sel:hashKeyRange:Shard' :: HashKeyRange
hashKeyRange = HashKeyRange
a} :: Shard)

-- | The range of possible sequence numbers for the shard.
shard_sequenceNumberRange :: Lens.Lens' Shard SequenceNumberRange
shard_sequenceNumberRange :: Lens' Shard SequenceNumberRange
shard_sequenceNumberRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Shard' {SequenceNumberRange
sequenceNumberRange :: SequenceNumberRange
$sel:sequenceNumberRange:Shard' :: Shard -> SequenceNumberRange
sequenceNumberRange} -> SequenceNumberRange
sequenceNumberRange) (\s :: Shard
s@Shard' {} SequenceNumberRange
a -> Shard
s {$sel:sequenceNumberRange:Shard' :: SequenceNumberRange
sequenceNumberRange = SequenceNumberRange
a} :: Shard)

instance Data.FromJSON Shard where
  parseJSON :: Value -> Parser Shard
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Shard"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Text
-> HashKeyRange
-> SequenceNumberRange
-> Shard
Shard'
            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
"AdjacentParentShardId")
            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
"ParentShardId")
            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
"ShardId")
            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
"HashKeyRange")
            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
"SequenceNumberRange")
      )

instance Prelude.Hashable Shard where
  hashWithSalt :: Int -> Shard -> Int
hashWithSalt Int
_salt Shard' {Maybe Text
Text
HashKeyRange
SequenceNumberRange
sequenceNumberRange :: SequenceNumberRange
hashKeyRange :: HashKeyRange
shardId :: Text
parentShardId :: Maybe Text
adjacentParentShardId :: Maybe Text
$sel:sequenceNumberRange:Shard' :: Shard -> SequenceNumberRange
$sel:hashKeyRange:Shard' :: Shard -> HashKeyRange
$sel:shardId:Shard' :: Shard -> Text
$sel:parentShardId:Shard' :: Shard -> Maybe Text
$sel:adjacentParentShardId:Shard' :: Shard -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
adjacentParentShardId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parentShardId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
shardId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HashKeyRange
hashKeyRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SequenceNumberRange
sequenceNumberRange

instance Prelude.NFData Shard where
  rnf :: Shard -> ()
rnf Shard' {Maybe Text
Text
HashKeyRange
SequenceNumberRange
sequenceNumberRange :: SequenceNumberRange
hashKeyRange :: HashKeyRange
shardId :: Text
parentShardId :: Maybe Text
adjacentParentShardId :: Maybe Text
$sel:sequenceNumberRange:Shard' :: Shard -> SequenceNumberRange
$sel:hashKeyRange:Shard' :: Shard -> HashKeyRange
$sel:shardId:Shard' :: Shard -> Text
$sel:parentShardId:Shard' :: Shard -> Maybe Text
$sel:adjacentParentShardId:Shard' :: Shard -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
adjacentParentShardId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parentShardId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
shardId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HashKeyRange
hashKeyRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SequenceNumberRange
sequenceNumberRange