{-# 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.GetLogGroupFields
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of the fields that are included in log events in the
-- specified log group. Includes the percentage of log events that contain
-- each field. The search is limited to a time period that you specify.
--
-- In the results, fields that start with @\@@ are fields generated by
-- CloudWatch Logs. For example, @\@timestamp@ is the timestamp of each log
-- event. For more information about the fields that are generated by
-- CloudWatch logs, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/logs/CWL_AnalyzeLogData-discoverable-fields.html Supported Logs and Discovered Fields>.
--
-- The response results are sorted by the frequency percentage, starting
-- with the highest percentage.
--
-- If you are using CloudWatch cross-account observability, you can use
-- this operation in a monitoring account and view data from the linked
-- source accounts. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/CloudWatch-Unified-Cross-Account.html CloudWatch cross-account observability>.
module Amazonka.CloudWatchLogs.GetLogGroupFields
  ( -- * Creating a Request
    GetLogGroupFields (..),
    newGetLogGroupFields,

    -- * Request Lenses
    getLogGroupFields_logGroupIdentifier,
    getLogGroupFields_time,
    getLogGroupFields_logGroupName,

    -- * Destructuring the Response
    GetLogGroupFieldsResponse (..),
    newGetLogGroupFieldsResponse,

    -- * Response Lenses
    getLogGroupFieldsResponse_logGroupFields,
    getLogGroupFieldsResponse_httpStatus,
  )
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:/ 'newGetLogGroupFields' smart constructor.
data GetLogGroupFields = GetLogGroupFields'
  { -- | Specify either the name or ARN of the log group to view. If the log
    -- group is in a source account and you are using a monitoring account, you
    -- must specify the ARN.
    --
    -- If you specify values for both @logGroupName@ and @logGroupIdentifier@,
    -- the action returns an @InvalidParameterException@ error.
    GetLogGroupFields -> Maybe Text
logGroupIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The time to set as the center of the query. If you specify @time@, the
    -- 15 minutes before this time are queries. If you omit @time@, the 8
    -- minutes before and 8 minutes after this time are searched.
    --
    -- The @time@ value is specified as epoch time, which is the number of
    -- seconds since @January 1, 1970, 00:00:00 UTC@.
    GetLogGroupFields -> Maybe Natural
time :: Prelude.Maybe Prelude.Natural,
    -- | The name of the log group to search.
    --
    -- If you specify values for both @logGroupName@ and @logGroupIdentifier@,
    -- the action returns an @InvalidParameterException@ error.
    GetLogGroupFields -> Text
logGroupName :: Prelude.Text
  }
  deriving (GetLogGroupFields -> GetLogGroupFields -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLogGroupFields -> GetLogGroupFields -> Bool
$c/= :: GetLogGroupFields -> GetLogGroupFields -> Bool
== :: GetLogGroupFields -> GetLogGroupFields -> Bool
$c== :: GetLogGroupFields -> GetLogGroupFields -> Bool
Prelude.Eq, ReadPrec [GetLogGroupFields]
ReadPrec GetLogGroupFields
Int -> ReadS GetLogGroupFields
ReadS [GetLogGroupFields]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLogGroupFields]
$creadListPrec :: ReadPrec [GetLogGroupFields]
readPrec :: ReadPrec GetLogGroupFields
$creadPrec :: ReadPrec GetLogGroupFields
readList :: ReadS [GetLogGroupFields]
$creadList :: ReadS [GetLogGroupFields]
readsPrec :: Int -> ReadS GetLogGroupFields
$creadsPrec :: Int -> ReadS GetLogGroupFields
Prelude.Read, Int -> GetLogGroupFields -> ShowS
[GetLogGroupFields] -> ShowS
GetLogGroupFields -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLogGroupFields] -> ShowS
$cshowList :: [GetLogGroupFields] -> ShowS
show :: GetLogGroupFields -> String
$cshow :: GetLogGroupFields -> String
showsPrec :: Int -> GetLogGroupFields -> ShowS
$cshowsPrec :: Int -> GetLogGroupFields -> ShowS
Prelude.Show, forall x. Rep GetLogGroupFields x -> GetLogGroupFields
forall x. GetLogGroupFields -> Rep GetLogGroupFields x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLogGroupFields x -> GetLogGroupFields
$cfrom :: forall x. GetLogGroupFields -> Rep GetLogGroupFields x
Prelude.Generic)

-- |
-- Create a value of 'GetLogGroupFields' 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:
--
-- 'logGroupIdentifier', 'getLogGroupFields_logGroupIdentifier' - Specify either the name or ARN of the log group to view. If the log
-- group is in a source account and you are using a monitoring account, you
-- must specify the ARN.
--
-- If you specify values for both @logGroupName@ and @logGroupIdentifier@,
-- the action returns an @InvalidParameterException@ error.
--
-- 'time', 'getLogGroupFields_time' - The time to set as the center of the query. If you specify @time@, the
-- 15 minutes before this time are queries. If you omit @time@, the 8
-- minutes before and 8 minutes after this time are searched.
--
-- The @time@ value is specified as epoch time, which is the number of
-- seconds since @January 1, 1970, 00:00:00 UTC@.
--
-- 'logGroupName', 'getLogGroupFields_logGroupName' - The name of the log group to search.
--
-- If you specify values for both @logGroupName@ and @logGroupIdentifier@,
-- the action returns an @InvalidParameterException@ error.
newGetLogGroupFields ::
  -- | 'logGroupName'
  Prelude.Text ->
  GetLogGroupFields
newGetLogGroupFields :: Text -> GetLogGroupFields
newGetLogGroupFields Text
pLogGroupName_ =
  GetLogGroupFields'
    { $sel:logGroupIdentifier:GetLogGroupFields' :: Maybe Text
logGroupIdentifier =
        forall a. Maybe a
Prelude.Nothing,
      $sel:time:GetLogGroupFields' :: Maybe Natural
time = forall a. Maybe a
Prelude.Nothing,
      $sel:logGroupName:GetLogGroupFields' :: Text
logGroupName = Text
pLogGroupName_
    }

-- | Specify either the name or ARN of the log group to view. If the log
-- group is in a source account and you are using a monitoring account, you
-- must specify the ARN.
--
-- If you specify values for both @logGroupName@ and @logGroupIdentifier@,
-- the action returns an @InvalidParameterException@ error.
getLogGroupFields_logGroupIdentifier :: Lens.Lens' GetLogGroupFields (Prelude.Maybe Prelude.Text)
getLogGroupFields_logGroupIdentifier :: Lens' GetLogGroupFields (Maybe Text)
getLogGroupFields_logGroupIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLogGroupFields' {Maybe Text
logGroupIdentifier :: Maybe Text
$sel:logGroupIdentifier:GetLogGroupFields' :: GetLogGroupFields -> Maybe Text
logGroupIdentifier} -> Maybe Text
logGroupIdentifier) (\s :: GetLogGroupFields
s@GetLogGroupFields' {} Maybe Text
a -> GetLogGroupFields
s {$sel:logGroupIdentifier:GetLogGroupFields' :: Maybe Text
logGroupIdentifier = Maybe Text
a} :: GetLogGroupFields)

-- | The time to set as the center of the query. If you specify @time@, the
-- 15 minutes before this time are queries. If you omit @time@, the 8
-- minutes before and 8 minutes after this time are searched.
--
-- The @time@ value is specified as epoch time, which is the number of
-- seconds since @January 1, 1970, 00:00:00 UTC@.
getLogGroupFields_time :: Lens.Lens' GetLogGroupFields (Prelude.Maybe Prelude.Natural)
getLogGroupFields_time :: Lens' GetLogGroupFields (Maybe Natural)
getLogGroupFields_time = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLogGroupFields' {Maybe Natural
time :: Maybe Natural
$sel:time:GetLogGroupFields' :: GetLogGroupFields -> Maybe Natural
time} -> Maybe Natural
time) (\s :: GetLogGroupFields
s@GetLogGroupFields' {} Maybe Natural
a -> GetLogGroupFields
s {$sel:time:GetLogGroupFields' :: Maybe Natural
time = Maybe Natural
a} :: GetLogGroupFields)

-- | The name of the log group to search.
--
-- If you specify values for both @logGroupName@ and @logGroupIdentifier@,
-- the action returns an @InvalidParameterException@ error.
getLogGroupFields_logGroupName :: Lens.Lens' GetLogGroupFields Prelude.Text
getLogGroupFields_logGroupName :: Lens' GetLogGroupFields Text
getLogGroupFields_logGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLogGroupFields' {Text
logGroupName :: Text
$sel:logGroupName:GetLogGroupFields' :: GetLogGroupFields -> Text
logGroupName} -> Text
logGroupName) (\s :: GetLogGroupFields
s@GetLogGroupFields' {} Text
a -> GetLogGroupFields
s {$sel:logGroupName:GetLogGroupFields' :: Text
logGroupName = Text
a} :: GetLogGroupFields)

instance Core.AWSRequest GetLogGroupFields where
  type
    AWSResponse GetLogGroupFields =
      GetLogGroupFieldsResponse
  request :: (Service -> Service)
-> GetLogGroupFields -> Request GetLogGroupFields
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 GetLogGroupFields
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetLogGroupFields)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [LogGroupField] -> Int -> GetLogGroupFieldsResponse
GetLogGroupFieldsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"logGroupFields" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetLogGroupFields where
  hashWithSalt :: Int -> GetLogGroupFields -> Int
hashWithSalt Int
_salt GetLogGroupFields' {Maybe Natural
Maybe Text
Text
logGroupName :: Text
time :: Maybe Natural
logGroupIdentifier :: Maybe Text
$sel:logGroupName:GetLogGroupFields' :: GetLogGroupFields -> Text
$sel:time:GetLogGroupFields' :: GetLogGroupFields -> Maybe Natural
$sel:logGroupIdentifier:GetLogGroupFields' :: GetLogGroupFields -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
logGroupIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
time
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
logGroupName

instance Prelude.NFData GetLogGroupFields where
  rnf :: GetLogGroupFields -> ()
rnf GetLogGroupFields' {Maybe Natural
Maybe Text
Text
logGroupName :: Text
time :: Maybe Natural
logGroupIdentifier :: Maybe Text
$sel:logGroupName:GetLogGroupFields' :: GetLogGroupFields -> Text
$sel:time:GetLogGroupFields' :: GetLogGroupFields -> Maybe Natural
$sel:logGroupIdentifier:GetLogGroupFields' :: GetLogGroupFields -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logGroupIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
time
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
logGroupName

instance Data.ToHeaders GetLogGroupFields where
  toHeaders :: GetLogGroupFields -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"Logs_20140328.GetLogGroupFields" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

-- | /See:/ 'newGetLogGroupFieldsResponse' smart constructor.
data GetLogGroupFieldsResponse = GetLogGroupFieldsResponse'
  { -- | The array of fields found in the query. Each object in the array
    -- contains the name of the field, along with the percentage of time it
    -- appeared in the log events that were queried.
    GetLogGroupFieldsResponse -> Maybe [LogGroupField]
logGroupFields :: Prelude.Maybe [LogGroupField],
    -- | The response's http status code.
    GetLogGroupFieldsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetLogGroupFieldsResponse -> GetLogGroupFieldsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLogGroupFieldsResponse -> GetLogGroupFieldsResponse -> Bool
$c/= :: GetLogGroupFieldsResponse -> GetLogGroupFieldsResponse -> Bool
== :: GetLogGroupFieldsResponse -> GetLogGroupFieldsResponse -> Bool
$c== :: GetLogGroupFieldsResponse -> GetLogGroupFieldsResponse -> Bool
Prelude.Eq, ReadPrec [GetLogGroupFieldsResponse]
ReadPrec GetLogGroupFieldsResponse
Int -> ReadS GetLogGroupFieldsResponse
ReadS [GetLogGroupFieldsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLogGroupFieldsResponse]
$creadListPrec :: ReadPrec [GetLogGroupFieldsResponse]
readPrec :: ReadPrec GetLogGroupFieldsResponse
$creadPrec :: ReadPrec GetLogGroupFieldsResponse
readList :: ReadS [GetLogGroupFieldsResponse]
$creadList :: ReadS [GetLogGroupFieldsResponse]
readsPrec :: Int -> ReadS GetLogGroupFieldsResponse
$creadsPrec :: Int -> ReadS GetLogGroupFieldsResponse
Prelude.Read, Int -> GetLogGroupFieldsResponse -> ShowS
[GetLogGroupFieldsResponse] -> ShowS
GetLogGroupFieldsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLogGroupFieldsResponse] -> ShowS
$cshowList :: [GetLogGroupFieldsResponse] -> ShowS
show :: GetLogGroupFieldsResponse -> String
$cshow :: GetLogGroupFieldsResponse -> String
showsPrec :: Int -> GetLogGroupFieldsResponse -> ShowS
$cshowsPrec :: Int -> GetLogGroupFieldsResponse -> ShowS
Prelude.Show, forall x.
Rep GetLogGroupFieldsResponse x -> GetLogGroupFieldsResponse
forall x.
GetLogGroupFieldsResponse -> Rep GetLogGroupFieldsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetLogGroupFieldsResponse x -> GetLogGroupFieldsResponse
$cfrom :: forall x.
GetLogGroupFieldsResponse -> Rep GetLogGroupFieldsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetLogGroupFieldsResponse' 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:
--
-- 'logGroupFields', 'getLogGroupFieldsResponse_logGroupFields' - The array of fields found in the query. Each object in the array
-- contains the name of the field, along with the percentage of time it
-- appeared in the log events that were queried.
--
-- 'httpStatus', 'getLogGroupFieldsResponse_httpStatus' - The response's http status code.
newGetLogGroupFieldsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetLogGroupFieldsResponse
newGetLogGroupFieldsResponse :: Int -> GetLogGroupFieldsResponse
newGetLogGroupFieldsResponse Int
pHttpStatus_ =
  GetLogGroupFieldsResponse'
    { $sel:logGroupFields:GetLogGroupFieldsResponse' :: Maybe [LogGroupField]
logGroupFields =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetLogGroupFieldsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The array of fields found in the query. Each object in the array
-- contains the name of the field, along with the percentage of time it
-- appeared in the log events that were queried.
getLogGroupFieldsResponse_logGroupFields :: Lens.Lens' GetLogGroupFieldsResponse (Prelude.Maybe [LogGroupField])
getLogGroupFieldsResponse_logGroupFields :: Lens' GetLogGroupFieldsResponse (Maybe [LogGroupField])
getLogGroupFieldsResponse_logGroupFields = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLogGroupFieldsResponse' {Maybe [LogGroupField]
logGroupFields :: Maybe [LogGroupField]
$sel:logGroupFields:GetLogGroupFieldsResponse' :: GetLogGroupFieldsResponse -> Maybe [LogGroupField]
logGroupFields} -> Maybe [LogGroupField]
logGroupFields) (\s :: GetLogGroupFieldsResponse
s@GetLogGroupFieldsResponse' {} Maybe [LogGroupField]
a -> GetLogGroupFieldsResponse
s {$sel:logGroupFields:GetLogGroupFieldsResponse' :: Maybe [LogGroupField]
logGroupFields = Maybe [LogGroupField]
a} :: GetLogGroupFieldsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The response's http status code.
getLogGroupFieldsResponse_httpStatus :: Lens.Lens' GetLogGroupFieldsResponse Prelude.Int
getLogGroupFieldsResponse_httpStatus :: Lens' GetLogGroupFieldsResponse Int
getLogGroupFieldsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLogGroupFieldsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetLogGroupFieldsResponse' :: GetLogGroupFieldsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetLogGroupFieldsResponse
s@GetLogGroupFieldsResponse' {} Int
a -> GetLogGroupFieldsResponse
s {$sel:httpStatus:GetLogGroupFieldsResponse' :: Int
httpStatus = Int
a} :: GetLogGroupFieldsResponse)

instance Prelude.NFData GetLogGroupFieldsResponse where
  rnf :: GetLogGroupFieldsResponse -> ()
rnf GetLogGroupFieldsResponse' {Int
Maybe [LogGroupField]
httpStatus :: Int
logGroupFields :: Maybe [LogGroupField]
$sel:httpStatus:GetLogGroupFieldsResponse' :: GetLogGroupFieldsResponse -> Int
$sel:logGroupFields:GetLogGroupFieldsResponse' :: GetLogGroupFieldsResponse -> Maybe [LogGroupField]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [LogGroupField]
logGroupFields
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus