{-# 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.DynamoDB.DescribeContributorInsights
-- 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 information about contributor insights, for a given table or
-- global secondary index.
module Amazonka.DynamoDB.DescribeContributorInsights
  ( -- * Creating a Request
    DescribeContributorInsights (..),
    newDescribeContributorInsights,

    -- * Request Lenses
    describeContributorInsights_indexName,
    describeContributorInsights_tableName,

    -- * Destructuring the Response
    DescribeContributorInsightsResponse (..),
    newDescribeContributorInsightsResponse,

    -- * Response Lenses
    describeContributorInsightsResponse_contributorInsightsRuleList,
    describeContributorInsightsResponse_contributorInsightsStatus,
    describeContributorInsightsResponse_failureException,
    describeContributorInsightsResponse_indexName,
    describeContributorInsightsResponse_lastUpdateDateTime,
    describeContributorInsightsResponse_tableName,
    describeContributorInsightsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DynamoDB.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeContributorInsights' smart constructor.
data DescribeContributorInsights = DescribeContributorInsights'
  { -- | The name of the global secondary index to describe, if applicable.
    DescribeContributorInsights -> Maybe Text
indexName :: Prelude.Maybe Prelude.Text,
    -- | The name of the table to describe.
    DescribeContributorInsights -> Text
tableName :: Prelude.Text
  }
  deriving (DescribeContributorInsights -> DescribeContributorInsights -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeContributorInsights -> DescribeContributorInsights -> Bool
$c/= :: DescribeContributorInsights -> DescribeContributorInsights -> Bool
== :: DescribeContributorInsights -> DescribeContributorInsights -> Bool
$c== :: DescribeContributorInsights -> DescribeContributorInsights -> Bool
Prelude.Eq, ReadPrec [DescribeContributorInsights]
ReadPrec DescribeContributorInsights
Int -> ReadS DescribeContributorInsights
ReadS [DescribeContributorInsights]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeContributorInsights]
$creadListPrec :: ReadPrec [DescribeContributorInsights]
readPrec :: ReadPrec DescribeContributorInsights
$creadPrec :: ReadPrec DescribeContributorInsights
readList :: ReadS [DescribeContributorInsights]
$creadList :: ReadS [DescribeContributorInsights]
readsPrec :: Int -> ReadS DescribeContributorInsights
$creadsPrec :: Int -> ReadS DescribeContributorInsights
Prelude.Read, Int -> DescribeContributorInsights -> ShowS
[DescribeContributorInsights] -> ShowS
DescribeContributorInsights -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeContributorInsights] -> ShowS
$cshowList :: [DescribeContributorInsights] -> ShowS
show :: DescribeContributorInsights -> String
$cshow :: DescribeContributorInsights -> String
showsPrec :: Int -> DescribeContributorInsights -> ShowS
$cshowsPrec :: Int -> DescribeContributorInsights -> ShowS
Prelude.Show, forall x.
Rep DescribeContributorInsights x -> DescribeContributorInsights
forall x.
DescribeContributorInsights -> Rep DescribeContributorInsights x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeContributorInsights x -> DescribeContributorInsights
$cfrom :: forall x.
DescribeContributorInsights -> Rep DescribeContributorInsights x
Prelude.Generic)

-- |
-- Create a value of 'DescribeContributorInsights' 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:
--
-- 'indexName', 'describeContributorInsights_indexName' - The name of the global secondary index to describe, if applicable.
--
-- 'tableName', 'describeContributorInsights_tableName' - The name of the table to describe.
newDescribeContributorInsights ::
  -- | 'tableName'
  Prelude.Text ->
  DescribeContributorInsights
newDescribeContributorInsights :: Text -> DescribeContributorInsights
newDescribeContributorInsights Text
pTableName_ =
  DescribeContributorInsights'
    { $sel:indexName:DescribeContributorInsights' :: Maybe Text
indexName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tableName:DescribeContributorInsights' :: Text
tableName = Text
pTableName_
    }

-- | The name of the global secondary index to describe, if applicable.
describeContributorInsights_indexName :: Lens.Lens' DescribeContributorInsights (Prelude.Maybe Prelude.Text)
describeContributorInsights_indexName :: Lens' DescribeContributorInsights (Maybe Text)
describeContributorInsights_indexName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeContributorInsights' {Maybe Text
indexName :: Maybe Text
$sel:indexName:DescribeContributorInsights' :: DescribeContributorInsights -> Maybe Text
indexName} -> Maybe Text
indexName) (\s :: DescribeContributorInsights
s@DescribeContributorInsights' {} Maybe Text
a -> DescribeContributorInsights
s {$sel:indexName:DescribeContributorInsights' :: Maybe Text
indexName = Maybe Text
a} :: DescribeContributorInsights)

-- | The name of the table to describe.
describeContributorInsights_tableName :: Lens.Lens' DescribeContributorInsights Prelude.Text
describeContributorInsights_tableName :: Lens' DescribeContributorInsights Text
describeContributorInsights_tableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeContributorInsights' {Text
tableName :: Text
$sel:tableName:DescribeContributorInsights' :: DescribeContributorInsights -> Text
tableName} -> Text
tableName) (\s :: DescribeContributorInsights
s@DescribeContributorInsights' {} Text
a -> DescribeContributorInsights
s {$sel:tableName:DescribeContributorInsights' :: Text
tableName = Text
a} :: DescribeContributorInsights)

instance Core.AWSRequest DescribeContributorInsights where
  type
    AWSResponse DescribeContributorInsights =
      DescribeContributorInsightsResponse
  request :: (Service -> Service)
-> DescribeContributorInsights
-> Request DescribeContributorInsights
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 DescribeContributorInsights
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeContributorInsights)))
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 [Text]
-> Maybe ContributorInsightsStatus
-> Maybe FailureException
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Int
-> DescribeContributorInsightsResponse
DescribeContributorInsightsResponse'
            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
"ContributorInsightsRuleList"
                            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ContributorInsightsStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"FailureException")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"IndexName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LastUpdateDateTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"TableName")
            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 DescribeContributorInsights where
  hashWithSalt :: Int -> DescribeContributorInsights -> Int
hashWithSalt Int
_salt DescribeContributorInsights' {Maybe Text
Text
tableName :: Text
indexName :: Maybe Text
$sel:tableName:DescribeContributorInsights' :: DescribeContributorInsights -> Text
$sel:indexName:DescribeContributorInsights' :: DescribeContributorInsights -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
indexName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tableName

instance Prelude.NFData DescribeContributorInsights where
  rnf :: DescribeContributorInsights -> ()
rnf DescribeContributorInsights' {Maybe Text
Text
tableName :: Text
indexName :: Maybe Text
$sel:tableName:DescribeContributorInsights' :: DescribeContributorInsights -> Text
$sel:indexName:DescribeContributorInsights' :: DescribeContributorInsights -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
indexName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
tableName

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

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

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

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

-- | /See:/ 'newDescribeContributorInsightsResponse' smart constructor.
data DescribeContributorInsightsResponse = DescribeContributorInsightsResponse'
  { -- | List of names of the associated contributor insights rules.
    DescribeContributorInsightsResponse -> Maybe [Text]
contributorInsightsRuleList :: Prelude.Maybe [Prelude.Text],
    -- | Current status of contributor insights.
    DescribeContributorInsightsResponse
-> Maybe ContributorInsightsStatus
contributorInsightsStatus :: Prelude.Maybe ContributorInsightsStatus,
    -- | Returns information about the last failure that was encountered.
    --
    -- The most common exceptions for a FAILED status are:
    --
    -- -   LimitExceededException - Per-account Amazon CloudWatch Contributor
    --     Insights rule limit reached. Please disable Contributor Insights for
    --     other tables\/indexes OR disable Contributor Insights rules before
    --     retrying.
    --
    -- -   AccessDeniedException - Amazon CloudWatch Contributor Insights rules
    --     cannot be modified due to insufficient permissions.
    --
    -- -   AccessDeniedException - Failed to create service-linked role for
    --     Contributor Insights due to insufficient permissions.
    --
    -- -   InternalServerError - Failed to create Amazon CloudWatch Contributor
    --     Insights rules. Please retry request.
    DescribeContributorInsightsResponse -> Maybe FailureException
failureException :: Prelude.Maybe FailureException,
    -- | The name of the global secondary index being described.
    DescribeContributorInsightsResponse -> Maybe Text
indexName :: Prelude.Maybe Prelude.Text,
    -- | Timestamp of the last time the status was changed.
    DescribeContributorInsightsResponse -> Maybe POSIX
lastUpdateDateTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the table being described.
    DescribeContributorInsightsResponse -> Maybe Text
tableName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeContributorInsightsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeContributorInsightsResponse
-> DescribeContributorInsightsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeContributorInsightsResponse
-> DescribeContributorInsightsResponse -> Bool
$c/= :: DescribeContributorInsightsResponse
-> DescribeContributorInsightsResponse -> Bool
== :: DescribeContributorInsightsResponse
-> DescribeContributorInsightsResponse -> Bool
$c== :: DescribeContributorInsightsResponse
-> DescribeContributorInsightsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeContributorInsightsResponse]
ReadPrec DescribeContributorInsightsResponse
Int -> ReadS DescribeContributorInsightsResponse
ReadS [DescribeContributorInsightsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeContributorInsightsResponse]
$creadListPrec :: ReadPrec [DescribeContributorInsightsResponse]
readPrec :: ReadPrec DescribeContributorInsightsResponse
$creadPrec :: ReadPrec DescribeContributorInsightsResponse
readList :: ReadS [DescribeContributorInsightsResponse]
$creadList :: ReadS [DescribeContributorInsightsResponse]
readsPrec :: Int -> ReadS DescribeContributorInsightsResponse
$creadsPrec :: Int -> ReadS DescribeContributorInsightsResponse
Prelude.Read, Int -> DescribeContributorInsightsResponse -> ShowS
[DescribeContributorInsightsResponse] -> ShowS
DescribeContributorInsightsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeContributorInsightsResponse] -> ShowS
$cshowList :: [DescribeContributorInsightsResponse] -> ShowS
show :: DescribeContributorInsightsResponse -> String
$cshow :: DescribeContributorInsightsResponse -> String
showsPrec :: Int -> DescribeContributorInsightsResponse -> ShowS
$cshowsPrec :: Int -> DescribeContributorInsightsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeContributorInsightsResponse x
-> DescribeContributorInsightsResponse
forall x.
DescribeContributorInsightsResponse
-> Rep DescribeContributorInsightsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeContributorInsightsResponse x
-> DescribeContributorInsightsResponse
$cfrom :: forall x.
DescribeContributorInsightsResponse
-> Rep DescribeContributorInsightsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeContributorInsightsResponse' 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:
--
-- 'contributorInsightsRuleList', 'describeContributorInsightsResponse_contributorInsightsRuleList' - List of names of the associated contributor insights rules.
--
-- 'contributorInsightsStatus', 'describeContributorInsightsResponse_contributorInsightsStatus' - Current status of contributor insights.
--
-- 'failureException', 'describeContributorInsightsResponse_failureException' - Returns information about the last failure that was encountered.
--
-- The most common exceptions for a FAILED status are:
--
-- -   LimitExceededException - Per-account Amazon CloudWatch Contributor
--     Insights rule limit reached. Please disable Contributor Insights for
--     other tables\/indexes OR disable Contributor Insights rules before
--     retrying.
--
-- -   AccessDeniedException - Amazon CloudWatch Contributor Insights rules
--     cannot be modified due to insufficient permissions.
--
-- -   AccessDeniedException - Failed to create service-linked role for
--     Contributor Insights due to insufficient permissions.
--
-- -   InternalServerError - Failed to create Amazon CloudWatch Contributor
--     Insights rules. Please retry request.
--
-- 'indexName', 'describeContributorInsightsResponse_indexName' - The name of the global secondary index being described.
--
-- 'lastUpdateDateTime', 'describeContributorInsightsResponse_lastUpdateDateTime' - Timestamp of the last time the status was changed.
--
-- 'tableName', 'describeContributorInsightsResponse_tableName' - The name of the table being described.
--
-- 'httpStatus', 'describeContributorInsightsResponse_httpStatus' - The response's http status code.
newDescribeContributorInsightsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeContributorInsightsResponse
newDescribeContributorInsightsResponse :: Int -> DescribeContributorInsightsResponse
newDescribeContributorInsightsResponse Int
pHttpStatus_ =
  DescribeContributorInsightsResponse'
    { $sel:contributorInsightsRuleList:DescribeContributorInsightsResponse' :: Maybe [Text]
contributorInsightsRuleList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:contributorInsightsStatus:DescribeContributorInsightsResponse' :: Maybe ContributorInsightsStatus
contributorInsightsStatus =
        forall a. Maybe a
Prelude.Nothing,
      $sel:failureException:DescribeContributorInsightsResponse' :: Maybe FailureException
failureException = forall a. Maybe a
Prelude.Nothing,
      $sel:indexName:DescribeContributorInsightsResponse' :: Maybe Text
indexName = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdateDateTime:DescribeContributorInsightsResponse' :: Maybe POSIX
lastUpdateDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:tableName:DescribeContributorInsightsResponse' :: Maybe Text
tableName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeContributorInsightsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | List of names of the associated contributor insights rules.
describeContributorInsightsResponse_contributorInsightsRuleList :: Lens.Lens' DescribeContributorInsightsResponse (Prelude.Maybe [Prelude.Text])
describeContributorInsightsResponse_contributorInsightsRuleList :: Lens' DescribeContributorInsightsResponse (Maybe [Text])
describeContributorInsightsResponse_contributorInsightsRuleList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeContributorInsightsResponse' {Maybe [Text]
contributorInsightsRuleList :: Maybe [Text]
$sel:contributorInsightsRuleList:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe [Text]
contributorInsightsRuleList} -> Maybe [Text]
contributorInsightsRuleList) (\s :: DescribeContributorInsightsResponse
s@DescribeContributorInsightsResponse' {} Maybe [Text]
a -> DescribeContributorInsightsResponse
s {$sel:contributorInsightsRuleList:DescribeContributorInsightsResponse' :: Maybe [Text]
contributorInsightsRuleList = Maybe [Text]
a} :: DescribeContributorInsightsResponse) 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

-- | Current status of contributor insights.
describeContributorInsightsResponse_contributorInsightsStatus :: Lens.Lens' DescribeContributorInsightsResponse (Prelude.Maybe ContributorInsightsStatus)
describeContributorInsightsResponse_contributorInsightsStatus :: Lens'
  DescribeContributorInsightsResponse
  (Maybe ContributorInsightsStatus)
describeContributorInsightsResponse_contributorInsightsStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeContributorInsightsResponse' {Maybe ContributorInsightsStatus
contributorInsightsStatus :: Maybe ContributorInsightsStatus
$sel:contributorInsightsStatus:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse
-> Maybe ContributorInsightsStatus
contributorInsightsStatus} -> Maybe ContributorInsightsStatus
contributorInsightsStatus) (\s :: DescribeContributorInsightsResponse
s@DescribeContributorInsightsResponse' {} Maybe ContributorInsightsStatus
a -> DescribeContributorInsightsResponse
s {$sel:contributorInsightsStatus:DescribeContributorInsightsResponse' :: Maybe ContributorInsightsStatus
contributorInsightsStatus = Maybe ContributorInsightsStatus
a} :: DescribeContributorInsightsResponse)

-- | Returns information about the last failure that was encountered.
--
-- The most common exceptions for a FAILED status are:
--
-- -   LimitExceededException - Per-account Amazon CloudWatch Contributor
--     Insights rule limit reached. Please disable Contributor Insights for
--     other tables\/indexes OR disable Contributor Insights rules before
--     retrying.
--
-- -   AccessDeniedException - Amazon CloudWatch Contributor Insights rules
--     cannot be modified due to insufficient permissions.
--
-- -   AccessDeniedException - Failed to create service-linked role for
--     Contributor Insights due to insufficient permissions.
--
-- -   InternalServerError - Failed to create Amazon CloudWatch Contributor
--     Insights rules. Please retry request.
describeContributorInsightsResponse_failureException :: Lens.Lens' DescribeContributorInsightsResponse (Prelude.Maybe FailureException)
describeContributorInsightsResponse_failureException :: Lens' DescribeContributorInsightsResponse (Maybe FailureException)
describeContributorInsightsResponse_failureException = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeContributorInsightsResponse' {Maybe FailureException
failureException :: Maybe FailureException
$sel:failureException:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe FailureException
failureException} -> Maybe FailureException
failureException) (\s :: DescribeContributorInsightsResponse
s@DescribeContributorInsightsResponse' {} Maybe FailureException
a -> DescribeContributorInsightsResponse
s {$sel:failureException:DescribeContributorInsightsResponse' :: Maybe FailureException
failureException = Maybe FailureException
a} :: DescribeContributorInsightsResponse)

-- | The name of the global secondary index being described.
describeContributorInsightsResponse_indexName :: Lens.Lens' DescribeContributorInsightsResponse (Prelude.Maybe Prelude.Text)
describeContributorInsightsResponse_indexName :: Lens' DescribeContributorInsightsResponse (Maybe Text)
describeContributorInsightsResponse_indexName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeContributorInsightsResponse' {Maybe Text
indexName :: Maybe Text
$sel:indexName:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe Text
indexName} -> Maybe Text
indexName) (\s :: DescribeContributorInsightsResponse
s@DescribeContributorInsightsResponse' {} Maybe Text
a -> DescribeContributorInsightsResponse
s {$sel:indexName:DescribeContributorInsightsResponse' :: Maybe Text
indexName = Maybe Text
a} :: DescribeContributorInsightsResponse)

-- | Timestamp of the last time the status was changed.
describeContributorInsightsResponse_lastUpdateDateTime :: Lens.Lens' DescribeContributorInsightsResponse (Prelude.Maybe Prelude.UTCTime)
describeContributorInsightsResponse_lastUpdateDateTime :: Lens' DescribeContributorInsightsResponse (Maybe UTCTime)
describeContributorInsightsResponse_lastUpdateDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeContributorInsightsResponse' {Maybe POSIX
lastUpdateDateTime :: Maybe POSIX
$sel:lastUpdateDateTime:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe POSIX
lastUpdateDateTime} -> Maybe POSIX
lastUpdateDateTime) (\s :: DescribeContributorInsightsResponse
s@DescribeContributorInsightsResponse' {} Maybe POSIX
a -> DescribeContributorInsightsResponse
s {$sel:lastUpdateDateTime:DescribeContributorInsightsResponse' :: Maybe POSIX
lastUpdateDateTime = Maybe POSIX
a} :: DescribeContributorInsightsResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The name of the table being described.
describeContributorInsightsResponse_tableName :: Lens.Lens' DescribeContributorInsightsResponse (Prelude.Maybe Prelude.Text)
describeContributorInsightsResponse_tableName :: Lens' DescribeContributorInsightsResponse (Maybe Text)
describeContributorInsightsResponse_tableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeContributorInsightsResponse' {Maybe Text
tableName :: Maybe Text
$sel:tableName:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe Text
tableName} -> Maybe Text
tableName) (\s :: DescribeContributorInsightsResponse
s@DescribeContributorInsightsResponse' {} Maybe Text
a -> DescribeContributorInsightsResponse
s {$sel:tableName:DescribeContributorInsightsResponse' :: Maybe Text
tableName = Maybe Text
a} :: DescribeContributorInsightsResponse)

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

instance
  Prelude.NFData
    DescribeContributorInsightsResponse
  where
  rnf :: DescribeContributorInsightsResponse -> ()
rnf DescribeContributorInsightsResponse' {Int
Maybe [Text]
Maybe Text
Maybe POSIX
Maybe FailureException
Maybe ContributorInsightsStatus
httpStatus :: Int
tableName :: Maybe Text
lastUpdateDateTime :: Maybe POSIX
indexName :: Maybe Text
failureException :: Maybe FailureException
contributorInsightsStatus :: Maybe ContributorInsightsStatus
contributorInsightsRuleList :: Maybe [Text]
$sel:httpStatus:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Int
$sel:tableName:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe Text
$sel:lastUpdateDateTime:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe POSIX
$sel:indexName:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe Text
$sel:failureException:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe FailureException
$sel:contributorInsightsStatus:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse
-> Maybe ContributorInsightsStatus
$sel:contributorInsightsRuleList:DescribeContributorInsightsResponse' :: DescribeContributorInsightsResponse -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
contributorInsightsRuleList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ContributorInsightsStatus
contributorInsightsStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FailureException
failureException
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
indexName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdateDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tableName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus