{-# 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.IncreaseStreamRetentionPeriod
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Increases the Kinesis data stream\'s retention period, which is the
-- length of time data records are accessible after they are added to the
-- stream. The maximum value of a stream\'s retention period is 8760 hours
-- (365 days).
--
-- When invoking this API, it is recommended you use the @StreamARN@ input
-- parameter rather than the @StreamName@ input parameter.
--
-- If you choose a longer stream retention period, this operation increases
-- the time period during which records that have not yet expired are
-- accessible. However, it does not make previous, expired data (older than
-- the stream\'s previous retention period) accessible after the operation
-- has been called. For example, if a stream\'s retention period is set to
-- 24 hours and is increased to 168 hours, any data that is older than 24
-- hours remains inaccessible to consumer applications.
module Amazonka.Kinesis.IncreaseStreamRetentionPeriod
  ( -- * Creating a Request
    IncreaseStreamRetentionPeriod (..),
    newIncreaseStreamRetentionPeriod,

    -- * Request Lenses
    increaseStreamRetentionPeriod_streamARN,
    increaseStreamRetentionPeriod_streamName,
    increaseStreamRetentionPeriod_retentionPeriodHours,

    -- * Destructuring the Response
    IncreaseStreamRetentionPeriodResponse (..),
    newIncreaseStreamRetentionPeriodResponse,
  )
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 IncreaseStreamRetentionPeriod.
--
-- /See:/ 'newIncreaseStreamRetentionPeriod' smart constructor.
data IncreaseStreamRetentionPeriod = IncreaseStreamRetentionPeriod'
  { -- | The ARN of the stream.
    IncreaseStreamRetentionPeriod -> Maybe Text
streamARN :: Prelude.Maybe Prelude.Text,
    -- | The name of the stream to modify.
    IncreaseStreamRetentionPeriod -> Maybe Text
streamName :: Prelude.Maybe Prelude.Text,
    -- | The new retention period of the stream, in hours. Must be more than the
    -- current retention period.
    IncreaseStreamRetentionPeriod -> Int
retentionPeriodHours :: Prelude.Int
  }
  deriving (IncreaseStreamRetentionPeriod
-> IncreaseStreamRetentionPeriod -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IncreaseStreamRetentionPeriod
-> IncreaseStreamRetentionPeriod -> Bool
$c/= :: IncreaseStreamRetentionPeriod
-> IncreaseStreamRetentionPeriod -> Bool
== :: IncreaseStreamRetentionPeriod
-> IncreaseStreamRetentionPeriod -> Bool
$c== :: IncreaseStreamRetentionPeriod
-> IncreaseStreamRetentionPeriod -> Bool
Prelude.Eq, ReadPrec [IncreaseStreamRetentionPeriod]
ReadPrec IncreaseStreamRetentionPeriod
Int -> ReadS IncreaseStreamRetentionPeriod
ReadS [IncreaseStreamRetentionPeriod]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IncreaseStreamRetentionPeriod]
$creadListPrec :: ReadPrec [IncreaseStreamRetentionPeriod]
readPrec :: ReadPrec IncreaseStreamRetentionPeriod
$creadPrec :: ReadPrec IncreaseStreamRetentionPeriod
readList :: ReadS [IncreaseStreamRetentionPeriod]
$creadList :: ReadS [IncreaseStreamRetentionPeriod]
readsPrec :: Int -> ReadS IncreaseStreamRetentionPeriod
$creadsPrec :: Int -> ReadS IncreaseStreamRetentionPeriod
Prelude.Read, Int -> IncreaseStreamRetentionPeriod -> ShowS
[IncreaseStreamRetentionPeriod] -> ShowS
IncreaseStreamRetentionPeriod -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IncreaseStreamRetentionPeriod] -> ShowS
$cshowList :: [IncreaseStreamRetentionPeriod] -> ShowS
show :: IncreaseStreamRetentionPeriod -> String
$cshow :: IncreaseStreamRetentionPeriod -> String
showsPrec :: Int -> IncreaseStreamRetentionPeriod -> ShowS
$cshowsPrec :: Int -> IncreaseStreamRetentionPeriod -> ShowS
Prelude.Show, forall x.
Rep IncreaseStreamRetentionPeriod x
-> IncreaseStreamRetentionPeriod
forall x.
IncreaseStreamRetentionPeriod
-> Rep IncreaseStreamRetentionPeriod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep IncreaseStreamRetentionPeriod x
-> IncreaseStreamRetentionPeriod
$cfrom :: forall x.
IncreaseStreamRetentionPeriod
-> Rep IncreaseStreamRetentionPeriod x
Prelude.Generic)

-- |
-- Create a value of 'IncreaseStreamRetentionPeriod' 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', 'increaseStreamRetentionPeriod_streamARN' - The ARN of the stream.
--
-- 'streamName', 'increaseStreamRetentionPeriod_streamName' - The name of the stream to modify.
--
-- 'retentionPeriodHours', 'increaseStreamRetentionPeriod_retentionPeriodHours' - The new retention period of the stream, in hours. Must be more than the
-- current retention period.
newIncreaseStreamRetentionPeriod ::
  -- | 'retentionPeriodHours'
  Prelude.Int ->
  IncreaseStreamRetentionPeriod
newIncreaseStreamRetentionPeriod :: Int -> IncreaseStreamRetentionPeriod
newIncreaseStreamRetentionPeriod
  Int
pRetentionPeriodHours_ =
    IncreaseStreamRetentionPeriod'
      { $sel:streamARN:IncreaseStreamRetentionPeriod' :: Maybe Text
streamARN =
          forall a. Maybe a
Prelude.Nothing,
        $sel:streamName:IncreaseStreamRetentionPeriod' :: Maybe Text
streamName = forall a. Maybe a
Prelude.Nothing,
        $sel:retentionPeriodHours:IncreaseStreamRetentionPeriod' :: Int
retentionPeriodHours =
          Int
pRetentionPeriodHours_
      }

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

-- | The name of the stream to modify.
increaseStreamRetentionPeriod_streamName :: Lens.Lens' IncreaseStreamRetentionPeriod (Prelude.Maybe Prelude.Text)
increaseStreamRetentionPeriod_streamName :: Lens' IncreaseStreamRetentionPeriod (Maybe Text)
increaseStreamRetentionPeriod_streamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IncreaseStreamRetentionPeriod' {Maybe Text
streamName :: Maybe Text
$sel:streamName:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> Maybe Text
streamName} -> Maybe Text
streamName) (\s :: IncreaseStreamRetentionPeriod
s@IncreaseStreamRetentionPeriod' {} Maybe Text
a -> IncreaseStreamRetentionPeriod
s {$sel:streamName:IncreaseStreamRetentionPeriod' :: Maybe Text
streamName = Maybe Text
a} :: IncreaseStreamRetentionPeriod)

-- | The new retention period of the stream, in hours. Must be more than the
-- current retention period.
increaseStreamRetentionPeriod_retentionPeriodHours :: Lens.Lens' IncreaseStreamRetentionPeriod Prelude.Int
increaseStreamRetentionPeriod_retentionPeriodHours :: Lens' IncreaseStreamRetentionPeriod Int
increaseStreamRetentionPeriod_retentionPeriodHours = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IncreaseStreamRetentionPeriod' {Int
retentionPeriodHours :: Int
$sel:retentionPeriodHours:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> Int
retentionPeriodHours} -> Int
retentionPeriodHours) (\s :: IncreaseStreamRetentionPeriod
s@IncreaseStreamRetentionPeriod' {} Int
a -> IncreaseStreamRetentionPeriod
s {$sel:retentionPeriodHours:IncreaseStreamRetentionPeriod' :: Int
retentionPeriodHours = Int
a} :: IncreaseStreamRetentionPeriod)

instance
  Core.AWSRequest
    IncreaseStreamRetentionPeriod
  where
  type
    AWSResponse IncreaseStreamRetentionPeriod =
      IncreaseStreamRetentionPeriodResponse
  request :: (Service -> Service)
-> IncreaseStreamRetentionPeriod
-> Request IncreaseStreamRetentionPeriod
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 IncreaseStreamRetentionPeriod
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse IncreaseStreamRetentionPeriod)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      IncreaseStreamRetentionPeriodResponse
IncreaseStreamRetentionPeriodResponse'

instance
  Prelude.Hashable
    IncreaseStreamRetentionPeriod
  where
  hashWithSalt :: Int -> IncreaseStreamRetentionPeriod -> Int
hashWithSalt Int
_salt IncreaseStreamRetentionPeriod' {Int
Maybe Text
retentionPeriodHours :: Int
streamName :: Maybe Text
streamARN :: Maybe Text
$sel:retentionPeriodHours:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> Int
$sel:streamName:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> Maybe Text
$sel:streamARN:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> 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` Int
retentionPeriodHours

instance Prelude.NFData IncreaseStreamRetentionPeriod where
  rnf :: IncreaseStreamRetentionPeriod -> ()
rnf IncreaseStreamRetentionPeriod' {Int
Maybe Text
retentionPeriodHours :: Int
streamName :: Maybe Text
streamARN :: Maybe Text
$sel:retentionPeriodHours:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> Int
$sel:streamName:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> Maybe Text
$sel:streamARN:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> 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 Int
retentionPeriodHours

instance Data.ToHeaders IncreaseStreamRetentionPeriod where
  toHeaders :: IncreaseStreamRetentionPeriod -> [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.IncreaseStreamRetentionPeriod" ::
                          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 IncreaseStreamRetentionPeriod where
  toJSON :: IncreaseStreamRetentionPeriod -> Value
toJSON IncreaseStreamRetentionPeriod' {Int
Maybe Text
retentionPeriodHours :: Int
streamName :: Maybe Text
streamARN :: Maybe Text
$sel:retentionPeriodHours:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> Int
$sel:streamName:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> Maybe Text
$sel:streamARN:IncreaseStreamRetentionPeriod' :: IncreaseStreamRetentionPeriod -> 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
"RetentionPeriodHours"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Int
retentionPeriodHours
              )
          ]
      )

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

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

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

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

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