{-# 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.CloudWatchLogs.Types.LogStream
-- 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.CloudWatchLogs.Types.LogStream where

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

-- | Represents a log stream, which is a sequence of log events from a single
-- emitter of logs.
--
-- /See:/ 'newLogStream' smart constructor.
data LogStream = LogStream'
  { -- | The Amazon Resource Name (ARN) of the log stream.
    LogStream -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The creation time of the stream, expressed as the number of milliseconds
    -- after @Jan 1, 1970 00:00:00 UTC@.
    LogStream -> Maybe Natural
creationTime :: Prelude.Maybe Prelude.Natural,
    -- | The time of the first event, expressed as the number of milliseconds
    -- after @Jan 1, 1970 00:00:00 UTC@.
    LogStream -> Maybe Natural
firstEventTimestamp :: Prelude.Maybe Prelude.Natural,
    -- | The time of the most recent log event in the log stream in CloudWatch
    -- Logs. This number is expressed as the number of milliseconds after
    -- @Jan 1, 1970 00:00:00 UTC@. The @lastEventTime@ value updates on an
    -- eventual consistency basis. It typically updates in less than an hour
    -- from ingestion, but in rare situations might take longer.
    LogStream -> Maybe Natural
lastEventTimestamp :: Prelude.Maybe Prelude.Natural,
    -- | The ingestion time, expressed as the number of milliseconds after
    -- @Jan 1, 1970 00:00:00 UTC@ The @lastIngestionTime@ value updates on an
    -- eventual consistency basis. It typically updates in less than an hour
    -- after ingestion, but in rare situations might take longer.
    LogStream -> Maybe Natural
lastIngestionTime :: Prelude.Maybe Prelude.Natural,
    -- | The name of the log stream.
    LogStream -> Maybe Text
logStreamName :: Prelude.Maybe Prelude.Text,
    -- | The number of bytes stored.
    --
    -- __Important:__ As of June 17, 2019, this parameter is no longer
    -- supported for log streams, and is always reported as zero. This change
    -- applies only to log streams. The @storedBytes@ parameter for log groups
    -- is not affected.
    LogStream -> Maybe Natural
storedBytes :: Prelude.Maybe Prelude.Natural,
    -- | The sequence token.
    --
    -- The sequence token is now ignored in @PutLogEvents@ actions.
    -- @PutLogEvents@ actions are always accepted regardless of receiving an
    -- invalid sequence token. You don\'t need to obtain @uploadSequenceToken@
    -- to use a @PutLogEvents@ action.
    LogStream -> Maybe Text
uploadSequenceToken :: Prelude.Maybe Prelude.Text
  }
  deriving (LogStream -> LogStream -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogStream -> LogStream -> Bool
$c/= :: LogStream -> LogStream -> Bool
== :: LogStream -> LogStream -> Bool
$c== :: LogStream -> LogStream -> Bool
Prelude.Eq, ReadPrec [LogStream]
ReadPrec LogStream
Int -> ReadS LogStream
ReadS [LogStream]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LogStream]
$creadListPrec :: ReadPrec [LogStream]
readPrec :: ReadPrec LogStream
$creadPrec :: ReadPrec LogStream
readList :: ReadS [LogStream]
$creadList :: ReadS [LogStream]
readsPrec :: Int -> ReadS LogStream
$creadsPrec :: Int -> ReadS LogStream
Prelude.Read, Int -> LogStream -> ShowS
[LogStream] -> ShowS
LogStream -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogStream] -> ShowS
$cshowList :: [LogStream] -> ShowS
show :: LogStream -> String
$cshow :: LogStream -> String
showsPrec :: Int -> LogStream -> ShowS
$cshowsPrec :: Int -> LogStream -> ShowS
Prelude.Show, forall x. Rep LogStream x -> LogStream
forall x. LogStream -> Rep LogStream x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LogStream x -> LogStream
$cfrom :: forall x. LogStream -> Rep LogStream x
Prelude.Generic)

-- |
-- Create a value of 'LogStream' 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:
--
-- 'arn', 'logStream_arn' - The Amazon Resource Name (ARN) of the log stream.
--
-- 'creationTime', 'logStream_creationTime' - The creation time of the stream, expressed as the number of milliseconds
-- after @Jan 1, 1970 00:00:00 UTC@.
--
-- 'firstEventTimestamp', 'logStream_firstEventTimestamp' - The time of the first event, expressed as the number of milliseconds
-- after @Jan 1, 1970 00:00:00 UTC@.
--
-- 'lastEventTimestamp', 'logStream_lastEventTimestamp' - The time of the most recent log event in the log stream in CloudWatch
-- Logs. This number is expressed as the number of milliseconds after
-- @Jan 1, 1970 00:00:00 UTC@. The @lastEventTime@ value updates on an
-- eventual consistency basis. It typically updates in less than an hour
-- from ingestion, but in rare situations might take longer.
--
-- 'lastIngestionTime', 'logStream_lastIngestionTime' - The ingestion time, expressed as the number of milliseconds after
-- @Jan 1, 1970 00:00:00 UTC@ The @lastIngestionTime@ value updates on an
-- eventual consistency basis. It typically updates in less than an hour
-- after ingestion, but in rare situations might take longer.
--
-- 'logStreamName', 'logStream_logStreamName' - The name of the log stream.
--
-- 'storedBytes', 'logStream_storedBytes' - The number of bytes stored.
--
-- __Important:__ As of June 17, 2019, this parameter is no longer
-- supported for log streams, and is always reported as zero. This change
-- applies only to log streams. The @storedBytes@ parameter for log groups
-- is not affected.
--
-- 'uploadSequenceToken', 'logStream_uploadSequenceToken' - The sequence token.
--
-- The sequence token is now ignored in @PutLogEvents@ actions.
-- @PutLogEvents@ actions are always accepted regardless of receiving an
-- invalid sequence token. You don\'t need to obtain @uploadSequenceToken@
-- to use a @PutLogEvents@ action.
newLogStream ::
  LogStream
newLogStream :: LogStream
newLogStream =
  LogStream'
    { $sel:arn:LogStream' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:LogStream' :: Maybe Natural
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:firstEventTimestamp:LogStream' :: Maybe Natural
firstEventTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:lastEventTimestamp:LogStream' :: Maybe Natural
lastEventTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:lastIngestionTime:LogStream' :: Maybe Natural
lastIngestionTime = forall a. Maybe a
Prelude.Nothing,
      $sel:logStreamName:LogStream' :: Maybe Text
logStreamName = forall a. Maybe a
Prelude.Nothing,
      $sel:storedBytes:LogStream' :: Maybe Natural
storedBytes = forall a. Maybe a
Prelude.Nothing,
      $sel:uploadSequenceToken:LogStream' :: Maybe Text
uploadSequenceToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the log stream.
logStream_arn :: Lens.Lens' LogStream (Prelude.Maybe Prelude.Text)
logStream_arn :: Lens' LogStream (Maybe Text)
logStream_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogStream' {Maybe Text
arn :: Maybe Text
$sel:arn:LogStream' :: LogStream -> Maybe Text
arn} -> Maybe Text
arn) (\s :: LogStream
s@LogStream' {} Maybe Text
a -> LogStream
s {$sel:arn:LogStream' :: Maybe Text
arn = Maybe Text
a} :: LogStream)

-- | The creation time of the stream, expressed as the number of milliseconds
-- after @Jan 1, 1970 00:00:00 UTC@.
logStream_creationTime :: Lens.Lens' LogStream (Prelude.Maybe Prelude.Natural)
logStream_creationTime :: Lens' LogStream (Maybe Natural)
logStream_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogStream' {Maybe Natural
creationTime :: Maybe Natural
$sel:creationTime:LogStream' :: LogStream -> Maybe Natural
creationTime} -> Maybe Natural
creationTime) (\s :: LogStream
s@LogStream' {} Maybe Natural
a -> LogStream
s {$sel:creationTime:LogStream' :: Maybe Natural
creationTime = Maybe Natural
a} :: LogStream)

-- | The time of the first event, expressed as the number of milliseconds
-- after @Jan 1, 1970 00:00:00 UTC@.
logStream_firstEventTimestamp :: Lens.Lens' LogStream (Prelude.Maybe Prelude.Natural)
logStream_firstEventTimestamp :: Lens' LogStream (Maybe Natural)
logStream_firstEventTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogStream' {Maybe Natural
firstEventTimestamp :: Maybe Natural
$sel:firstEventTimestamp:LogStream' :: LogStream -> Maybe Natural
firstEventTimestamp} -> Maybe Natural
firstEventTimestamp) (\s :: LogStream
s@LogStream' {} Maybe Natural
a -> LogStream
s {$sel:firstEventTimestamp:LogStream' :: Maybe Natural
firstEventTimestamp = Maybe Natural
a} :: LogStream)

-- | The time of the most recent log event in the log stream in CloudWatch
-- Logs. This number is expressed as the number of milliseconds after
-- @Jan 1, 1970 00:00:00 UTC@. The @lastEventTime@ value updates on an
-- eventual consistency basis. It typically updates in less than an hour
-- from ingestion, but in rare situations might take longer.
logStream_lastEventTimestamp :: Lens.Lens' LogStream (Prelude.Maybe Prelude.Natural)
logStream_lastEventTimestamp :: Lens' LogStream (Maybe Natural)
logStream_lastEventTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogStream' {Maybe Natural
lastEventTimestamp :: Maybe Natural
$sel:lastEventTimestamp:LogStream' :: LogStream -> Maybe Natural
lastEventTimestamp} -> Maybe Natural
lastEventTimestamp) (\s :: LogStream
s@LogStream' {} Maybe Natural
a -> LogStream
s {$sel:lastEventTimestamp:LogStream' :: Maybe Natural
lastEventTimestamp = Maybe Natural
a} :: LogStream)

-- | The ingestion time, expressed as the number of milliseconds after
-- @Jan 1, 1970 00:00:00 UTC@ The @lastIngestionTime@ value updates on an
-- eventual consistency basis. It typically updates in less than an hour
-- after ingestion, but in rare situations might take longer.
logStream_lastIngestionTime :: Lens.Lens' LogStream (Prelude.Maybe Prelude.Natural)
logStream_lastIngestionTime :: Lens' LogStream (Maybe Natural)
logStream_lastIngestionTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogStream' {Maybe Natural
lastIngestionTime :: Maybe Natural
$sel:lastIngestionTime:LogStream' :: LogStream -> Maybe Natural
lastIngestionTime} -> Maybe Natural
lastIngestionTime) (\s :: LogStream
s@LogStream' {} Maybe Natural
a -> LogStream
s {$sel:lastIngestionTime:LogStream' :: Maybe Natural
lastIngestionTime = Maybe Natural
a} :: LogStream)

-- | The name of the log stream.
logStream_logStreamName :: Lens.Lens' LogStream (Prelude.Maybe Prelude.Text)
logStream_logStreamName :: Lens' LogStream (Maybe Text)
logStream_logStreamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogStream' {Maybe Text
logStreamName :: Maybe Text
$sel:logStreamName:LogStream' :: LogStream -> Maybe Text
logStreamName} -> Maybe Text
logStreamName) (\s :: LogStream
s@LogStream' {} Maybe Text
a -> LogStream
s {$sel:logStreamName:LogStream' :: Maybe Text
logStreamName = Maybe Text
a} :: LogStream)

-- | The number of bytes stored.
--
-- __Important:__ As of June 17, 2019, this parameter is no longer
-- supported for log streams, and is always reported as zero. This change
-- applies only to log streams. The @storedBytes@ parameter for log groups
-- is not affected.
logStream_storedBytes :: Lens.Lens' LogStream (Prelude.Maybe Prelude.Natural)
logStream_storedBytes :: Lens' LogStream (Maybe Natural)
logStream_storedBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogStream' {Maybe Natural
storedBytes :: Maybe Natural
$sel:storedBytes:LogStream' :: LogStream -> Maybe Natural
storedBytes} -> Maybe Natural
storedBytes) (\s :: LogStream
s@LogStream' {} Maybe Natural
a -> LogStream
s {$sel:storedBytes:LogStream' :: Maybe Natural
storedBytes = Maybe Natural
a} :: LogStream)

-- | The sequence token.
--
-- The sequence token is now ignored in @PutLogEvents@ actions.
-- @PutLogEvents@ actions are always accepted regardless of receiving an
-- invalid sequence token. You don\'t need to obtain @uploadSequenceToken@
-- to use a @PutLogEvents@ action.
logStream_uploadSequenceToken :: Lens.Lens' LogStream (Prelude.Maybe Prelude.Text)
logStream_uploadSequenceToken :: Lens' LogStream (Maybe Text)
logStream_uploadSequenceToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogStream' {Maybe Text
uploadSequenceToken :: Maybe Text
$sel:uploadSequenceToken:LogStream' :: LogStream -> Maybe Text
uploadSequenceToken} -> Maybe Text
uploadSequenceToken) (\s :: LogStream
s@LogStream' {} Maybe Text
a -> LogStream
s {$sel:uploadSequenceToken:LogStream' :: Maybe Text
uploadSequenceToken = Maybe Text
a} :: LogStream)

instance Data.FromJSON LogStream where
  parseJSON :: Value -> Parser LogStream
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"LogStream"
      ( \Object
x ->
          Maybe Text
-> Maybe Natural
-> Maybe Natural
-> Maybe Natural
-> Maybe Natural
-> Maybe Text
-> Maybe Natural
-> Maybe Text
-> LogStream
LogStream'
            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
"arn")
            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
"creationTime")
            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
"firstEventTimestamp")
            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
"lastEventTimestamp")
            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
"lastIngestionTime")
            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
"logStreamName")
            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
"storedBytes")
            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
"uploadSequenceToken")
      )

instance Prelude.Hashable LogStream where
  hashWithSalt :: Int -> LogStream -> Int
hashWithSalt Int
_salt LogStream' {Maybe Natural
Maybe Text
uploadSequenceToken :: Maybe Text
storedBytes :: Maybe Natural
logStreamName :: Maybe Text
lastIngestionTime :: Maybe Natural
lastEventTimestamp :: Maybe Natural
firstEventTimestamp :: Maybe Natural
creationTime :: Maybe Natural
arn :: Maybe Text
$sel:uploadSequenceToken:LogStream' :: LogStream -> Maybe Text
$sel:storedBytes:LogStream' :: LogStream -> Maybe Natural
$sel:logStreamName:LogStream' :: LogStream -> Maybe Text
$sel:lastIngestionTime:LogStream' :: LogStream -> Maybe Natural
$sel:lastEventTimestamp:LogStream' :: LogStream -> Maybe Natural
$sel:firstEventTimestamp:LogStream' :: LogStream -> Maybe Natural
$sel:creationTime:LogStream' :: LogStream -> Maybe Natural
$sel:arn:LogStream' :: LogStream -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
firstEventTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
lastEventTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
lastIngestionTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
logStreamName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
storedBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
uploadSequenceToken

instance Prelude.NFData LogStream where
  rnf :: LogStream -> ()
rnf LogStream' {Maybe Natural
Maybe Text
uploadSequenceToken :: Maybe Text
storedBytes :: Maybe Natural
logStreamName :: Maybe Text
lastIngestionTime :: Maybe Natural
lastEventTimestamp :: Maybe Natural
firstEventTimestamp :: Maybe Natural
creationTime :: Maybe Natural
arn :: Maybe Text
$sel:uploadSequenceToken:LogStream' :: LogStream -> Maybe Text
$sel:storedBytes:LogStream' :: LogStream -> Maybe Natural
$sel:logStreamName:LogStream' :: LogStream -> Maybe Text
$sel:lastIngestionTime:LogStream' :: LogStream -> Maybe Natural
$sel:lastEventTimestamp:LogStream' :: LogStream -> Maybe Natural
$sel:firstEventTimestamp:LogStream' :: LogStream -> Maybe Natural
$sel:creationTime:LogStream' :: LogStream -> Maybe Natural
$sel:arn:LogStream' :: LogStream -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
firstEventTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
lastEventTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
lastIngestionTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logStreamName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
storedBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
uploadSequenceToken