{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.SplitShard
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Splits a shard into two new shards in the Kinesis data stream, to
-- increase the stream\'s capacity to ingest and transport data.
-- @SplitShard@ is called when there is a need to increase the overall
-- capacity of a stream because of an expected increase in the volume of
-- data records being ingested. This API is only supported for the data
-- streams with the provisioned capacity mode.
--
-- When invoking this API, it is recommended you use the @StreamARN@ input
-- parameter rather than the @StreamName@ input parameter.
--
-- You can also use @SplitShard@ when a shard appears to be approaching its
-- maximum utilization; for example, the producers sending data into the
-- specific shard are suddenly sending more than previously anticipated.
-- You can also call @SplitShard@ to increase stream capacity, so that more
-- Kinesis Data Streams applications can simultaneously read data from the
-- stream for real-time processing.
--
-- You must specify the shard to be split and the new hash key, which is
-- the position in the shard where the shard gets split in two. In many
-- cases, the new hash key might be the average of the beginning and ending
-- hash key, but it can be any hash key value in the range being mapped
-- into the shard. For more information, see
-- <https://docs.aws.amazon.com/kinesis/latest/dev/kinesis-using-sdk-java-resharding-split.html Split a Shard>
-- in the /Amazon Kinesis Data Streams Developer Guide/.
--
-- You can use DescribeStreamSummary and the ListShards APIs to determine
-- the shard ID and hash key values for the @ShardToSplit@ and
-- @NewStartingHashKey@ parameters that are specified in the @SplitShard@
-- request.
--
-- @SplitShard@ is an asynchronous operation. Upon receiving a @SplitShard@
-- request, Kinesis Data Streams immediately returns a response and sets
-- the stream status to @UPDATING@. After the operation is completed,
-- Kinesis Data Streams sets the stream status to @ACTIVE@. Read and write
-- operations continue to work while the stream is in the @UPDATING@ state.
--
-- You can use DescribeStreamSummary to check the status of the stream,
-- which is returned in @StreamStatus@. If the stream is in the @ACTIVE@
-- state, you can call @SplitShard@.
--
-- If the specified stream does not exist, DescribeStreamSummary returns a
-- @ResourceNotFoundException@. If you try to create more shards than are
-- authorized for your account, you receive a @LimitExceededException@.
--
-- For the default shard limit for an Amazon Web Services account, see
-- <https://docs.aws.amazon.com/kinesis/latest/dev/service-sizes-and-limits.html Kinesis Data Streams Limits>
-- in the /Amazon Kinesis Data Streams Developer Guide/. To increase this
-- limit,
-- <https://docs.aws.amazon.com/general/latest/gr/aws_service_limits.html contact Amazon Web Services Support>.
--
-- If you try to operate on too many streams simultaneously using
-- CreateStream, DeleteStream, MergeShards, and\/or SplitShard, you receive
-- a @LimitExceededException@.
--
-- @SplitShard@ has a limit of five transactions per second per account.
module Amazonka.Kinesis.SplitShard
  ( -- * Creating a Request
    SplitShard (..),
    newSplitShard,

    -- * Request Lenses
    splitShard_streamARN,
    splitShard_streamName,
    splitShard_shardToSplit,
    splitShard_newStartingHashKey,

    -- * Destructuring the Response
    SplitShardResponse (..),
    newSplitShardResponse,
  )
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
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Represents the input for @SplitShard@.
--
-- /See:/ 'newSplitShard' smart constructor.
data SplitShard = SplitShard'
  { -- | The ARN of the stream.
    SplitShard -> Maybe Text
streamARN :: Prelude.Maybe Prelude.Text,
    -- | The name of the stream for the shard split.
    SplitShard -> Maybe Text
streamName :: Prelude.Maybe Prelude.Text,
    -- | The shard ID of the shard to split.
    SplitShard -> Text
shardToSplit :: Prelude.Text,
    -- | A hash key value for the starting hash key of one of the child shards
    -- created by the split. The hash key range for a given shard constitutes a
    -- set of ordered contiguous positive integers. The value for
    -- @NewStartingHashKey@ must be in the range of hash keys being mapped into
    -- the shard. The @NewStartingHashKey@ hash key value and all higher hash
    -- key values in hash key range are distributed to one of the child shards.
    -- All the lower hash key values in the range are distributed to the other
    -- child shard.
    SplitShard -> Text
newStartingHashKey' :: Prelude.Text
  }
  deriving (SplitShard -> SplitShard -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SplitShard -> SplitShard -> Bool
$c/= :: SplitShard -> SplitShard -> Bool
== :: SplitShard -> SplitShard -> Bool
$c== :: SplitShard -> SplitShard -> Bool
Prelude.Eq, ReadPrec [SplitShard]
ReadPrec SplitShard
Int -> ReadS SplitShard
ReadS [SplitShard]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SplitShard]
$creadListPrec :: ReadPrec [SplitShard]
readPrec :: ReadPrec SplitShard
$creadPrec :: ReadPrec SplitShard
readList :: ReadS [SplitShard]
$creadList :: ReadS [SplitShard]
readsPrec :: Int -> ReadS SplitShard
$creadsPrec :: Int -> ReadS SplitShard
Prelude.Read, Int -> SplitShard -> ShowS
[SplitShard] -> ShowS
SplitShard -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SplitShard] -> ShowS
$cshowList :: [SplitShard] -> ShowS
show :: SplitShard -> String
$cshow :: SplitShard -> String
showsPrec :: Int -> SplitShard -> ShowS
$cshowsPrec :: Int -> SplitShard -> ShowS
Prelude.Show, forall x. Rep SplitShard x -> SplitShard
forall x. SplitShard -> Rep SplitShard x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SplitShard x -> SplitShard
$cfrom :: forall x. SplitShard -> Rep SplitShard x
Prelude.Generic)

-- |
-- Create a value of 'SplitShard' 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:
--
-- 'streamARN', 'splitShard_streamARN' - The ARN of the stream.
--
-- 'streamName', 'splitShard_streamName' - The name of the stream for the shard split.
--
-- 'shardToSplit', 'splitShard_shardToSplit' - The shard ID of the shard to split.
--
-- 'newStartingHashKey'', 'splitShard_newStartingHashKey' - A hash key value for the starting hash key of one of the child shards
-- created by the split. The hash key range for a given shard constitutes a
-- set of ordered contiguous positive integers. The value for
-- @NewStartingHashKey@ must be in the range of hash keys being mapped into
-- the shard. The @NewStartingHashKey@ hash key value and all higher hash
-- key values in hash key range are distributed to one of the child shards.
-- All the lower hash key values in the range are distributed to the other
-- child shard.
newSplitShard ::
  -- | 'shardToSplit'
  Prelude.Text ->
  -- | 'newStartingHashKey''
  Prelude.Text ->
  SplitShard
newSplitShard :: Text -> Text -> SplitShard
newSplitShard Text
pShardToSplit_ Text
pNewStartingHashKey_ =
  SplitShard'
    { $sel:streamARN:SplitShard' :: Maybe Text
streamARN = forall a. Maybe a
Prelude.Nothing,
      $sel:streamName:SplitShard' :: Maybe Text
streamName = forall a. Maybe a
Prelude.Nothing,
      $sel:shardToSplit:SplitShard' :: Text
shardToSplit = Text
pShardToSplit_,
      $sel:newStartingHashKey':SplitShard' :: Text
newStartingHashKey' = Text
pNewStartingHashKey_
    }

-- | The ARN of the stream.
splitShard_streamARN :: Lens.Lens' SplitShard (Prelude.Maybe Prelude.Text)
splitShard_streamARN :: Lens' SplitShard (Maybe Text)
splitShard_streamARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplitShard' {Maybe Text
streamARN :: Maybe Text
$sel:streamARN:SplitShard' :: SplitShard -> Maybe Text
streamARN} -> Maybe Text
streamARN) (\s :: SplitShard
s@SplitShard' {} Maybe Text
a -> SplitShard
s {$sel:streamARN:SplitShard' :: Maybe Text
streamARN = Maybe Text
a} :: SplitShard)

-- | The name of the stream for the shard split.
splitShard_streamName :: Lens.Lens' SplitShard (Prelude.Maybe Prelude.Text)
splitShard_streamName :: Lens' SplitShard (Maybe Text)
splitShard_streamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplitShard' {Maybe Text
streamName :: Maybe Text
$sel:streamName:SplitShard' :: SplitShard -> Maybe Text
streamName} -> Maybe Text
streamName) (\s :: SplitShard
s@SplitShard' {} Maybe Text
a -> SplitShard
s {$sel:streamName:SplitShard' :: Maybe Text
streamName = Maybe Text
a} :: SplitShard)

-- | The shard ID of the shard to split.
splitShard_shardToSplit :: Lens.Lens' SplitShard Prelude.Text
splitShard_shardToSplit :: Lens' SplitShard Text
splitShard_shardToSplit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplitShard' {Text
shardToSplit :: Text
$sel:shardToSplit:SplitShard' :: SplitShard -> Text
shardToSplit} -> Text
shardToSplit) (\s :: SplitShard
s@SplitShard' {} Text
a -> SplitShard
s {$sel:shardToSplit:SplitShard' :: Text
shardToSplit = Text
a} :: SplitShard)

-- | A hash key value for the starting hash key of one of the child shards
-- created by the split. The hash key range for a given shard constitutes a
-- set of ordered contiguous positive integers. The value for
-- @NewStartingHashKey@ must be in the range of hash keys being mapped into
-- the shard. The @NewStartingHashKey@ hash key value and all higher hash
-- key values in hash key range are distributed to one of the child shards.
-- All the lower hash key values in the range are distributed to the other
-- child shard.
splitShard_newStartingHashKey :: Lens.Lens' SplitShard Prelude.Text
splitShard_newStartingHashKey :: Lens' SplitShard Text
splitShard_newStartingHashKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SplitShard' {Text
newStartingHashKey' :: Text
$sel:newStartingHashKey':SplitShard' :: SplitShard -> Text
newStartingHashKey'} -> Text
newStartingHashKey') (\s :: SplitShard
s@SplitShard' {} Text
a -> SplitShard
s {$sel:newStartingHashKey':SplitShard' :: Text
newStartingHashKey' = Text
a} :: SplitShard)

instance Core.AWSRequest SplitShard where
  type AWSResponse SplitShard = SplitShardResponse
  request :: (Service -> Service) -> SplitShard -> Request SplitShard
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy SplitShard
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse SplitShard)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull SplitShardResponse
SplitShardResponse'

instance Prelude.Hashable SplitShard where
  hashWithSalt :: Int -> SplitShard -> Int
hashWithSalt Int
_salt SplitShard' {Maybe Text
Text
newStartingHashKey' :: Text
shardToSplit :: Text
streamName :: Maybe Text
streamARN :: Maybe Text
$sel:newStartingHashKey':SplitShard' :: SplitShard -> Text
$sel:shardToSplit:SplitShard' :: SplitShard -> Text
$sel:streamName:SplitShard' :: SplitShard -> Maybe Text
$sel:streamARN:SplitShard' :: SplitShard -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
shardToSplit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
newStartingHashKey'

instance Prelude.NFData SplitShard where
  rnf :: SplitShard -> ()
rnf SplitShard' {Maybe Text
Text
newStartingHashKey' :: Text
shardToSplit :: Text
streamName :: Maybe Text
streamARN :: Maybe Text
$sel:newStartingHashKey':SplitShard' :: SplitShard -> Text
$sel:shardToSplit:SplitShard' :: SplitShard -> Text
$sel:streamName:SplitShard' :: SplitShard -> Maybe Text
$sel:streamARN:SplitShard' :: SplitShard -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
shardToSplit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
newStartingHashKey'

instance Data.ToHeaders SplitShard where
  toHeaders :: SplitShard -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"Kinesis_20131202.SplitShard" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON SplitShard where
  toJSON :: SplitShard -> Value
toJSON SplitShard' {Maybe Text
Text
newStartingHashKey' :: Text
shardToSplit :: Text
streamName :: Maybe Text
streamARN :: Maybe Text
$sel:newStartingHashKey':SplitShard' :: SplitShard -> Text
$sel:shardToSplit:SplitShard' :: SplitShard -> Text
$sel:streamName:SplitShard' :: SplitShard -> Maybe Text
$sel:streamARN:SplitShard' :: SplitShard -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"StreamARN" 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
streamARN,
            (Key
"StreamName" 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
streamName,
            forall a. a -> Maybe a
Prelude.Just (Key
"ShardToSplit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
shardToSplit),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"NewStartingHashKey" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
newStartingHashKey')
          ]
      )

instance Data.ToPath SplitShard where
  toPath :: SplitShard -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery SplitShard where
  toQuery :: SplitShard -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newSplitShardResponse' smart constructor.
data SplitShardResponse = SplitShardResponse'
  {
  }
  deriving (SplitShardResponse -> SplitShardResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SplitShardResponse -> SplitShardResponse -> Bool
$c/= :: SplitShardResponse -> SplitShardResponse -> Bool
== :: SplitShardResponse -> SplitShardResponse -> Bool
$c== :: SplitShardResponse -> SplitShardResponse -> Bool
Prelude.Eq, ReadPrec [SplitShardResponse]
ReadPrec SplitShardResponse
Int -> ReadS SplitShardResponse
ReadS [SplitShardResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SplitShardResponse]
$creadListPrec :: ReadPrec [SplitShardResponse]
readPrec :: ReadPrec SplitShardResponse
$creadPrec :: ReadPrec SplitShardResponse
readList :: ReadS [SplitShardResponse]
$creadList :: ReadS [SplitShardResponse]
readsPrec :: Int -> ReadS SplitShardResponse
$creadsPrec :: Int -> ReadS SplitShardResponse
Prelude.Read, Int -> SplitShardResponse -> ShowS
[SplitShardResponse] -> ShowS
SplitShardResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SplitShardResponse] -> ShowS
$cshowList :: [SplitShardResponse] -> ShowS
show :: SplitShardResponse -> String
$cshow :: SplitShardResponse -> String
showsPrec :: Int -> SplitShardResponse -> ShowS
$cshowsPrec :: Int -> SplitShardResponse -> ShowS
Prelude.Show, forall x. Rep SplitShardResponse x -> SplitShardResponse
forall x. SplitShardResponse -> Rep SplitShardResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SplitShardResponse x -> SplitShardResponse
$cfrom :: forall x. SplitShardResponse -> Rep SplitShardResponse x
Prelude.Generic)

-- |
-- Create a value of 'SplitShardResponse' 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.
newSplitShardResponse ::
  SplitShardResponse
newSplitShardResponse :: SplitShardResponse
newSplitShardResponse = SplitShardResponse
SplitShardResponse'

instance Prelude.NFData SplitShardResponse where
  rnf :: SplitShardResponse -> ()
rnf SplitShardResponse
_ = ()