{-# 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.CloudWatchLogs.PutRetentionPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Sets the retention of the specified log group. With a retention policy,
-- you can configure the number of days for which to retain log events in
-- the specified log group.
--
-- CloudWatch Logs doesn’t immediately delete log events when they reach
-- their retention setting. It typically takes up to 72 hours after that
-- before log events are deleted, but in rare situations might take longer.
--
-- To illustrate, imagine that you change a log group to have a longer
-- retention setting when it contains log events that are past the
-- expiration date, but haven’t been deleted. Those log events will take up
-- to 72 hours to be deleted after the new retention date is reached. To
-- make sure that log data is deleted permanently, keep a log group at its
-- lower retention setting until 72 hours after the previous retention
-- period ends. Alternatively, wait to change the retention setting until
-- you confirm that the earlier log events are deleted.
module Amazonka.CloudWatchLogs.PutRetentionPolicy
  ( -- * Creating a Request
    PutRetentionPolicy (..),
    newPutRetentionPolicy,

    -- * Request Lenses
    putRetentionPolicy_logGroupName,
    putRetentionPolicy_retentionInDays,

    -- * Destructuring the Response
    PutRetentionPolicyResponse (..),
    newPutRetentionPolicyResponse,
  )
where

import Amazonka.CloudWatchLogs.Types
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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

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

-- |
-- Create a value of 'PutRetentionPolicy' 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:
--
-- 'logGroupName', 'putRetentionPolicy_logGroupName' - The name of the log group.
--
-- 'retentionInDays', 'putRetentionPolicy_retentionInDays' - Undocumented member.
newPutRetentionPolicy ::
  -- | 'logGroupName'
  Prelude.Text ->
  -- | 'retentionInDays'
  Prelude.Int ->
  PutRetentionPolicy
newPutRetentionPolicy :: Text -> Int -> PutRetentionPolicy
newPutRetentionPolicy
  Text
pLogGroupName_
  Int
pRetentionInDays_ =
    PutRetentionPolicy'
      { $sel:logGroupName:PutRetentionPolicy' :: Text
logGroupName = Text
pLogGroupName_,
        $sel:retentionInDays:PutRetentionPolicy' :: Int
retentionInDays = Int
pRetentionInDays_
      }

-- | The name of the log group.
putRetentionPolicy_logGroupName :: Lens.Lens' PutRetentionPolicy Prelude.Text
putRetentionPolicy_logGroupName :: Lens' PutRetentionPolicy Text
putRetentionPolicy_logGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutRetentionPolicy' {Text
logGroupName :: Text
$sel:logGroupName:PutRetentionPolicy' :: PutRetentionPolicy -> Text
logGroupName} -> Text
logGroupName) (\s :: PutRetentionPolicy
s@PutRetentionPolicy' {} Text
a -> PutRetentionPolicy
s {$sel:logGroupName:PutRetentionPolicy' :: Text
logGroupName = Text
a} :: PutRetentionPolicy)

-- | Undocumented member.
putRetentionPolicy_retentionInDays :: Lens.Lens' PutRetentionPolicy Prelude.Int
putRetentionPolicy_retentionInDays :: Lens' PutRetentionPolicy Int
putRetentionPolicy_retentionInDays = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutRetentionPolicy' {Int
retentionInDays :: Int
$sel:retentionInDays:PutRetentionPolicy' :: PutRetentionPolicy -> Int
retentionInDays} -> Int
retentionInDays) (\s :: PutRetentionPolicy
s@PutRetentionPolicy' {} Int
a -> PutRetentionPolicy
s {$sel:retentionInDays:PutRetentionPolicy' :: Int
retentionInDays = Int
a} :: PutRetentionPolicy)

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

instance Prelude.Hashable PutRetentionPolicy where
  hashWithSalt :: Int -> PutRetentionPolicy -> Int
hashWithSalt Int
_salt PutRetentionPolicy' {Int
Text
retentionInDays :: Int
logGroupName :: Text
$sel:retentionInDays:PutRetentionPolicy' :: PutRetentionPolicy -> Int
$sel:logGroupName:PutRetentionPolicy' :: PutRetentionPolicy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
logGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
retentionInDays

instance Prelude.NFData PutRetentionPolicy where
  rnf :: PutRetentionPolicy -> ()
rnf PutRetentionPolicy' {Int
Text
retentionInDays :: Int
logGroupName :: Text
$sel:retentionInDays:PutRetentionPolicy' :: PutRetentionPolicy -> Int
$sel:logGroupName:PutRetentionPolicy' :: PutRetentionPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
logGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
retentionInDays

instance Data.ToHeaders PutRetentionPolicy where
  toHeaders :: PutRetentionPolicy -> [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
"Logs_20140328.PutRetentionPolicy" ::
                          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 PutRetentionPolicy where
  toJSON :: PutRetentionPolicy -> Value
toJSON PutRetentionPolicy' {Int
Text
retentionInDays :: Int
logGroupName :: Text
$sel:retentionInDays:PutRetentionPolicy' :: PutRetentionPolicy -> Int
$sel:logGroupName:PutRetentionPolicy' :: PutRetentionPolicy -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"logGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
logGroupName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"retentionInDays" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Int
retentionInDays)
          ]
      )

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

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

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

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

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