{-# 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.DevOpsGuru.SearchOrganizationInsights
-- 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 insights in your organization. You can specify which
-- insights are returned by their start time, one or more statuses
-- (@ONGOING@, @CLOSED@, and @CLOSED@), one or more severities (@LOW@,
-- @MEDIUM@, and @HIGH@), and type (@REACTIVE@ or @PROACTIVE@).
--
-- Use the @Filters@ parameter to specify status and severity search
-- parameters. Use the @Type@ parameter to specify @REACTIVE@ or
-- @PROACTIVE@ in your search.
--
-- This operation returns paginated results.
module Amazonka.DevOpsGuru.SearchOrganizationInsights
  ( -- * Creating a Request
    SearchOrganizationInsights (..),
    newSearchOrganizationInsights,

    -- * Request Lenses
    searchOrganizationInsights_filters,
    searchOrganizationInsights_maxResults,
    searchOrganizationInsights_nextToken,
    searchOrganizationInsights_accountIds,
    searchOrganizationInsights_startTimeRange,
    searchOrganizationInsights_type,

    -- * Destructuring the Response
    SearchOrganizationInsightsResponse (..),
    newSearchOrganizationInsightsResponse,

    -- * Response Lenses
    searchOrganizationInsightsResponse_nextToken,
    searchOrganizationInsightsResponse_proactiveInsights,
    searchOrganizationInsightsResponse_reactiveInsights,
    searchOrganizationInsightsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newSearchOrganizationInsights' smart constructor.
data SearchOrganizationInsights = SearchOrganizationInsights'
  { -- | A @SearchOrganizationInsightsFilters@ object that is used to set the
    -- severity and status filters on your insight search.
    SearchOrganizationInsights
-> Maybe SearchOrganizationInsightsFilters
filters :: Prelude.Maybe SearchOrganizationInsightsFilters,
    -- | The maximum number of results to return with a single call. To retrieve
    -- the remaining results, make another call with the returned @nextToken@
    -- value.
    SearchOrganizationInsights -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The pagination token to use to retrieve the next page of results for
    -- this operation. If this value is null, it retrieves the first page.
    SearchOrganizationInsights -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon Web Services account.
    SearchOrganizationInsights -> NonEmpty Text
accountIds :: Prelude.NonEmpty Prelude.Text,
    SearchOrganizationInsights -> StartTimeRange
startTimeRange :: StartTimeRange,
    -- | The type of insights you are searching for (@REACTIVE@ or @PROACTIVE@).
    SearchOrganizationInsights -> InsightType
type' :: InsightType
  }
  deriving (SearchOrganizationInsights -> SearchOrganizationInsights -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchOrganizationInsights -> SearchOrganizationInsights -> Bool
$c/= :: SearchOrganizationInsights -> SearchOrganizationInsights -> Bool
== :: SearchOrganizationInsights -> SearchOrganizationInsights -> Bool
$c== :: SearchOrganizationInsights -> SearchOrganizationInsights -> Bool
Prelude.Eq, ReadPrec [SearchOrganizationInsights]
ReadPrec SearchOrganizationInsights
Int -> ReadS SearchOrganizationInsights
ReadS [SearchOrganizationInsights]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchOrganizationInsights]
$creadListPrec :: ReadPrec [SearchOrganizationInsights]
readPrec :: ReadPrec SearchOrganizationInsights
$creadPrec :: ReadPrec SearchOrganizationInsights
readList :: ReadS [SearchOrganizationInsights]
$creadList :: ReadS [SearchOrganizationInsights]
readsPrec :: Int -> ReadS SearchOrganizationInsights
$creadsPrec :: Int -> ReadS SearchOrganizationInsights
Prelude.Read, Int -> SearchOrganizationInsights -> ShowS
[SearchOrganizationInsights] -> ShowS
SearchOrganizationInsights -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchOrganizationInsights] -> ShowS
$cshowList :: [SearchOrganizationInsights] -> ShowS
show :: SearchOrganizationInsights -> String
$cshow :: SearchOrganizationInsights -> String
showsPrec :: Int -> SearchOrganizationInsights -> ShowS
$cshowsPrec :: Int -> SearchOrganizationInsights -> ShowS
Prelude.Show, forall x.
Rep SearchOrganizationInsights x -> SearchOrganizationInsights
forall x.
SearchOrganizationInsights -> Rep SearchOrganizationInsights x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SearchOrganizationInsights x -> SearchOrganizationInsights
$cfrom :: forall x.
SearchOrganizationInsights -> Rep SearchOrganizationInsights x
Prelude.Generic)

-- |
-- Create a value of 'SearchOrganizationInsights' 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:
--
-- 'filters', 'searchOrganizationInsights_filters' - A @SearchOrganizationInsightsFilters@ object that is used to set the
-- severity and status filters on your insight search.
--
-- 'maxResults', 'searchOrganizationInsights_maxResults' - The maximum number of results to return with a single call. To retrieve
-- the remaining results, make another call with the returned @nextToken@
-- value.
--
-- 'nextToken', 'searchOrganizationInsights_nextToken' - The pagination token to use to retrieve the next page of results for
-- this operation. If this value is null, it retrieves the first page.
--
-- 'accountIds', 'searchOrganizationInsights_accountIds' - The ID of the Amazon Web Services account.
--
-- 'startTimeRange', 'searchOrganizationInsights_startTimeRange' - Undocumented member.
--
-- 'type'', 'searchOrganizationInsights_type' - The type of insights you are searching for (@REACTIVE@ or @PROACTIVE@).
newSearchOrganizationInsights ::
  -- | 'accountIds'
  Prelude.NonEmpty Prelude.Text ->
  -- | 'startTimeRange'
  StartTimeRange ->
  -- | 'type''
  InsightType ->
  SearchOrganizationInsights
newSearchOrganizationInsights :: NonEmpty Text
-> StartTimeRange -> InsightType -> SearchOrganizationInsights
newSearchOrganizationInsights
  NonEmpty Text
pAccountIds_
  StartTimeRange
pStartTimeRange_
  InsightType
pType_ =
    SearchOrganizationInsights'
      { $sel:filters:SearchOrganizationInsights' :: Maybe SearchOrganizationInsightsFilters
filters =
          forall a. Maybe a
Prelude.Nothing,
        $sel:maxResults:SearchOrganizationInsights' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:SearchOrganizationInsights' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:accountIds:SearchOrganizationInsights' :: NonEmpty Text
accountIds = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pAccountIds_,
        $sel:startTimeRange:SearchOrganizationInsights' :: StartTimeRange
startTimeRange = StartTimeRange
pStartTimeRange_,
        $sel:type':SearchOrganizationInsights' :: InsightType
type' = InsightType
pType_
      }

-- | A @SearchOrganizationInsightsFilters@ object that is used to set the
-- severity and status filters on your insight search.
searchOrganizationInsights_filters :: Lens.Lens' SearchOrganizationInsights (Prelude.Maybe SearchOrganizationInsightsFilters)
searchOrganizationInsights_filters :: Lens'
  SearchOrganizationInsights
  (Maybe SearchOrganizationInsightsFilters)
searchOrganizationInsights_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsights' {Maybe SearchOrganizationInsightsFilters
filters :: Maybe SearchOrganizationInsightsFilters
$sel:filters:SearchOrganizationInsights' :: SearchOrganizationInsights
-> Maybe SearchOrganizationInsightsFilters
filters} -> Maybe SearchOrganizationInsightsFilters
filters) (\s :: SearchOrganizationInsights
s@SearchOrganizationInsights' {} Maybe SearchOrganizationInsightsFilters
a -> SearchOrganizationInsights
s {$sel:filters:SearchOrganizationInsights' :: Maybe SearchOrganizationInsightsFilters
filters = Maybe SearchOrganizationInsightsFilters
a} :: SearchOrganizationInsights)

-- | The maximum number of results to return with a single call. To retrieve
-- the remaining results, make another call with the returned @nextToken@
-- value.
searchOrganizationInsights_maxResults :: Lens.Lens' SearchOrganizationInsights (Prelude.Maybe Prelude.Natural)
searchOrganizationInsights_maxResults :: Lens' SearchOrganizationInsights (Maybe Natural)
searchOrganizationInsights_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsights' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:SearchOrganizationInsights' :: SearchOrganizationInsights -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: SearchOrganizationInsights
s@SearchOrganizationInsights' {} Maybe Natural
a -> SearchOrganizationInsights
s {$sel:maxResults:SearchOrganizationInsights' :: Maybe Natural
maxResults = Maybe Natural
a} :: SearchOrganizationInsights)

-- | The pagination token to use to retrieve the next page of results for
-- this operation. If this value is null, it retrieves the first page.
searchOrganizationInsights_nextToken :: Lens.Lens' SearchOrganizationInsights (Prelude.Maybe Prelude.Text)
searchOrganizationInsights_nextToken :: Lens' SearchOrganizationInsights (Maybe Text)
searchOrganizationInsights_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsights' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchOrganizationInsights' :: SearchOrganizationInsights -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchOrganizationInsights
s@SearchOrganizationInsights' {} Maybe Text
a -> SearchOrganizationInsights
s {$sel:nextToken:SearchOrganizationInsights' :: Maybe Text
nextToken = Maybe Text
a} :: SearchOrganizationInsights)

-- | The ID of the Amazon Web Services account.
searchOrganizationInsights_accountIds :: Lens.Lens' SearchOrganizationInsights (Prelude.NonEmpty Prelude.Text)
searchOrganizationInsights_accountIds :: Lens' SearchOrganizationInsights (NonEmpty Text)
searchOrganizationInsights_accountIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsights' {NonEmpty Text
accountIds :: NonEmpty Text
$sel:accountIds:SearchOrganizationInsights' :: SearchOrganizationInsights -> NonEmpty Text
accountIds} -> NonEmpty Text
accountIds) (\s :: SearchOrganizationInsights
s@SearchOrganizationInsights' {} NonEmpty Text
a -> SearchOrganizationInsights
s {$sel:accountIds:SearchOrganizationInsights' :: NonEmpty Text
accountIds = NonEmpty Text
a} :: SearchOrganizationInsights) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Undocumented member.
searchOrganizationInsights_startTimeRange :: Lens.Lens' SearchOrganizationInsights StartTimeRange
searchOrganizationInsights_startTimeRange :: Lens' SearchOrganizationInsights StartTimeRange
searchOrganizationInsights_startTimeRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsights' {StartTimeRange
startTimeRange :: StartTimeRange
$sel:startTimeRange:SearchOrganizationInsights' :: SearchOrganizationInsights -> StartTimeRange
startTimeRange} -> StartTimeRange
startTimeRange) (\s :: SearchOrganizationInsights
s@SearchOrganizationInsights' {} StartTimeRange
a -> SearchOrganizationInsights
s {$sel:startTimeRange:SearchOrganizationInsights' :: StartTimeRange
startTimeRange = StartTimeRange
a} :: SearchOrganizationInsights)

-- | The type of insights you are searching for (@REACTIVE@ or @PROACTIVE@).
searchOrganizationInsights_type :: Lens.Lens' SearchOrganizationInsights InsightType
searchOrganizationInsights_type :: Lens' SearchOrganizationInsights InsightType
searchOrganizationInsights_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsights' {InsightType
type' :: InsightType
$sel:type':SearchOrganizationInsights' :: SearchOrganizationInsights -> InsightType
type'} -> InsightType
type') (\s :: SearchOrganizationInsights
s@SearchOrganizationInsights' {} InsightType
a -> SearchOrganizationInsights
s {$sel:type':SearchOrganizationInsights' :: InsightType
type' = InsightType
a} :: SearchOrganizationInsights)

instance Core.AWSPager SearchOrganizationInsights where
  page :: SearchOrganizationInsights
-> AWSResponse SearchOrganizationInsights
-> Maybe SearchOrganizationInsights
page SearchOrganizationInsights
rq AWSResponse SearchOrganizationInsights
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse SearchOrganizationInsights
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchOrganizationInsightsResponse (Maybe Text)
searchOrganizationInsightsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse SearchOrganizationInsights
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  SearchOrganizationInsightsResponse
  (Maybe [ProactiveInsightSummary])
searchOrganizationInsightsResponse_proactiveInsights
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse SearchOrganizationInsights
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  SearchOrganizationInsightsResponse (Maybe [ReactiveInsightSummary])
searchOrganizationInsightsResponse_reactiveInsights
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ SearchOrganizationInsights
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' SearchOrganizationInsights (Maybe Text)
searchOrganizationInsights_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse SearchOrganizationInsights
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchOrganizationInsightsResponse (Maybe Text)
searchOrganizationInsightsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest SearchOrganizationInsights where
  type
    AWSResponse SearchOrganizationInsights =
      SearchOrganizationInsightsResponse
  request :: (Service -> Service)
-> SearchOrganizationInsights -> Request SearchOrganizationInsights
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 SearchOrganizationInsights
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SearchOrganizationInsights)))
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 [ProactiveInsightSummary]
-> Maybe [ReactiveInsightSummary]
-> Int
-> SearchOrganizationInsightsResponse
SearchOrganizationInsightsResponse'
            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
"NextToken")
            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
"ProactiveInsights"
                            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
"ReactiveInsights"
                            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 SearchOrganizationInsights where
  hashWithSalt :: Int -> SearchOrganizationInsights -> Int
hashWithSalt Int
_salt SearchOrganizationInsights' {Maybe Natural
Maybe Text
Maybe SearchOrganizationInsightsFilters
NonEmpty Text
InsightType
StartTimeRange
type' :: InsightType
startTimeRange :: StartTimeRange
accountIds :: NonEmpty Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe SearchOrganizationInsightsFilters
$sel:type':SearchOrganizationInsights' :: SearchOrganizationInsights -> InsightType
$sel:startTimeRange:SearchOrganizationInsights' :: SearchOrganizationInsights -> StartTimeRange
$sel:accountIds:SearchOrganizationInsights' :: SearchOrganizationInsights -> NonEmpty Text
$sel:nextToken:SearchOrganizationInsights' :: SearchOrganizationInsights -> Maybe Text
$sel:maxResults:SearchOrganizationInsights' :: SearchOrganizationInsights -> Maybe Natural
$sel:filters:SearchOrganizationInsights' :: SearchOrganizationInsights
-> Maybe SearchOrganizationInsightsFilters
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SearchOrganizationInsightsFilters
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
accountIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` StartTimeRange
startTimeRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` InsightType
type'

instance Prelude.NFData SearchOrganizationInsights where
  rnf :: SearchOrganizationInsights -> ()
rnf SearchOrganizationInsights' {Maybe Natural
Maybe Text
Maybe SearchOrganizationInsightsFilters
NonEmpty Text
InsightType
StartTimeRange
type' :: InsightType
startTimeRange :: StartTimeRange
accountIds :: NonEmpty Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe SearchOrganizationInsightsFilters
$sel:type':SearchOrganizationInsights' :: SearchOrganizationInsights -> InsightType
$sel:startTimeRange:SearchOrganizationInsights' :: SearchOrganizationInsights -> StartTimeRange
$sel:accountIds:SearchOrganizationInsights' :: SearchOrganizationInsights -> NonEmpty Text
$sel:nextToken:SearchOrganizationInsights' :: SearchOrganizationInsights -> Maybe Text
$sel:maxResults:SearchOrganizationInsights' :: SearchOrganizationInsights -> Maybe Natural
$sel:filters:SearchOrganizationInsights' :: SearchOrganizationInsights
-> Maybe SearchOrganizationInsightsFilters
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SearchOrganizationInsightsFilters
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
accountIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf StartTimeRange
startTimeRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf InsightType
type'

instance Data.ToHeaders SearchOrganizationInsights where
  toHeaders :: SearchOrganizationInsights -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON SearchOrganizationInsights where
  toJSON :: SearchOrganizationInsights -> Value
toJSON SearchOrganizationInsights' {Maybe Natural
Maybe Text
Maybe SearchOrganizationInsightsFilters
NonEmpty Text
InsightType
StartTimeRange
type' :: InsightType
startTimeRange :: StartTimeRange
accountIds :: NonEmpty Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe SearchOrganizationInsightsFilters
$sel:type':SearchOrganizationInsights' :: SearchOrganizationInsights -> InsightType
$sel:startTimeRange:SearchOrganizationInsights' :: SearchOrganizationInsights -> StartTimeRange
$sel:accountIds:SearchOrganizationInsights' :: SearchOrganizationInsights -> NonEmpty Text
$sel:nextToken:SearchOrganizationInsights' :: SearchOrganizationInsights -> Maybe Text
$sel:maxResults:SearchOrganizationInsights' :: SearchOrganizationInsights -> Maybe Natural
$sel:filters:SearchOrganizationInsights' :: SearchOrganizationInsights
-> Maybe SearchOrganizationInsightsFilters
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" 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 SearchOrganizationInsightsFilters
filters,
            (Key
"MaxResults" 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
maxResults,
            (Key
"NextToken" 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
nextToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"AccountIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
accountIds),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"StartTimeRange" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= StartTimeRange
startTimeRange),
            forall a. a -> Maybe a
Prelude.Just (Key
"Type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= InsightType
type')
          ]
      )

instance Data.ToPath SearchOrganizationInsights where
  toPath :: SearchOrganizationInsights -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/organization/insights/search"

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

-- | /See:/ 'newSearchOrganizationInsightsResponse' smart constructor.
data SearchOrganizationInsightsResponse = SearchOrganizationInsightsResponse'
  { -- | The pagination token to use to retrieve the next page of results for
    -- this operation. If there are no more pages, this value is null.
    SearchOrganizationInsightsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An integer that specifies the number of open proactive insights in your
    -- Amazon Web Services account.
    SearchOrganizationInsightsResponse
-> Maybe [ProactiveInsightSummary]
proactiveInsights :: Prelude.Maybe [ProactiveInsightSummary],
    -- | An integer that specifies the number of open reactive insights in your
    -- Amazon Web Services account.
    SearchOrganizationInsightsResponse
-> Maybe [ReactiveInsightSummary]
reactiveInsights :: Prelude.Maybe [ReactiveInsightSummary],
    -- | The response's http status code.
    SearchOrganizationInsightsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SearchOrganizationInsightsResponse
-> SearchOrganizationInsightsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchOrganizationInsightsResponse
-> SearchOrganizationInsightsResponse -> Bool
$c/= :: SearchOrganizationInsightsResponse
-> SearchOrganizationInsightsResponse -> Bool
== :: SearchOrganizationInsightsResponse
-> SearchOrganizationInsightsResponse -> Bool
$c== :: SearchOrganizationInsightsResponse
-> SearchOrganizationInsightsResponse -> Bool
Prelude.Eq, ReadPrec [SearchOrganizationInsightsResponse]
ReadPrec SearchOrganizationInsightsResponse
Int -> ReadS SearchOrganizationInsightsResponse
ReadS [SearchOrganizationInsightsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchOrganizationInsightsResponse]
$creadListPrec :: ReadPrec [SearchOrganizationInsightsResponse]
readPrec :: ReadPrec SearchOrganizationInsightsResponse
$creadPrec :: ReadPrec SearchOrganizationInsightsResponse
readList :: ReadS [SearchOrganizationInsightsResponse]
$creadList :: ReadS [SearchOrganizationInsightsResponse]
readsPrec :: Int -> ReadS SearchOrganizationInsightsResponse
$creadsPrec :: Int -> ReadS SearchOrganizationInsightsResponse
Prelude.Read, Int -> SearchOrganizationInsightsResponse -> ShowS
[SearchOrganizationInsightsResponse] -> ShowS
SearchOrganizationInsightsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchOrganizationInsightsResponse] -> ShowS
$cshowList :: [SearchOrganizationInsightsResponse] -> ShowS
show :: SearchOrganizationInsightsResponse -> String
$cshow :: SearchOrganizationInsightsResponse -> String
showsPrec :: Int -> SearchOrganizationInsightsResponse -> ShowS
$cshowsPrec :: Int -> SearchOrganizationInsightsResponse -> ShowS
Prelude.Show, forall x.
Rep SearchOrganizationInsightsResponse x
-> SearchOrganizationInsightsResponse
forall x.
SearchOrganizationInsightsResponse
-> Rep SearchOrganizationInsightsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SearchOrganizationInsightsResponse x
-> SearchOrganizationInsightsResponse
$cfrom :: forall x.
SearchOrganizationInsightsResponse
-> Rep SearchOrganizationInsightsResponse x
Prelude.Generic)

-- |
-- Create a value of 'SearchOrganizationInsightsResponse' 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:
--
-- 'nextToken', 'searchOrganizationInsightsResponse_nextToken' - The pagination token to use to retrieve the next page of results for
-- this operation. If there are no more pages, this value is null.
--
-- 'proactiveInsights', 'searchOrganizationInsightsResponse_proactiveInsights' - An integer that specifies the number of open proactive insights in your
-- Amazon Web Services account.
--
-- 'reactiveInsights', 'searchOrganizationInsightsResponse_reactiveInsights' - An integer that specifies the number of open reactive insights in your
-- Amazon Web Services account.
--
-- 'httpStatus', 'searchOrganizationInsightsResponse_httpStatus' - The response's http status code.
newSearchOrganizationInsightsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SearchOrganizationInsightsResponse
newSearchOrganizationInsightsResponse :: Int -> SearchOrganizationInsightsResponse
newSearchOrganizationInsightsResponse Int
pHttpStatus_ =
  SearchOrganizationInsightsResponse'
    { $sel:nextToken:SearchOrganizationInsightsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:proactiveInsights:SearchOrganizationInsightsResponse' :: Maybe [ProactiveInsightSummary]
proactiveInsights = forall a. Maybe a
Prelude.Nothing,
      $sel:reactiveInsights:SearchOrganizationInsightsResponse' :: Maybe [ReactiveInsightSummary]
reactiveInsights = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SearchOrganizationInsightsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The pagination token to use to retrieve the next page of results for
-- this operation. If there are no more pages, this value is null.
searchOrganizationInsightsResponse_nextToken :: Lens.Lens' SearchOrganizationInsightsResponse (Prelude.Maybe Prelude.Text)
searchOrganizationInsightsResponse_nextToken :: Lens' SearchOrganizationInsightsResponse (Maybe Text)
searchOrganizationInsightsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsightsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchOrganizationInsightsResponse' :: SearchOrganizationInsightsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchOrganizationInsightsResponse
s@SearchOrganizationInsightsResponse' {} Maybe Text
a -> SearchOrganizationInsightsResponse
s {$sel:nextToken:SearchOrganizationInsightsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: SearchOrganizationInsightsResponse)

-- | An integer that specifies the number of open proactive insights in your
-- Amazon Web Services account.
searchOrganizationInsightsResponse_proactiveInsights :: Lens.Lens' SearchOrganizationInsightsResponse (Prelude.Maybe [ProactiveInsightSummary])
searchOrganizationInsightsResponse_proactiveInsights :: Lens'
  SearchOrganizationInsightsResponse
  (Maybe [ProactiveInsightSummary])
searchOrganizationInsightsResponse_proactiveInsights = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsightsResponse' {Maybe [ProactiveInsightSummary]
proactiveInsights :: Maybe [ProactiveInsightSummary]
$sel:proactiveInsights:SearchOrganizationInsightsResponse' :: SearchOrganizationInsightsResponse
-> Maybe [ProactiveInsightSummary]
proactiveInsights} -> Maybe [ProactiveInsightSummary]
proactiveInsights) (\s :: SearchOrganizationInsightsResponse
s@SearchOrganizationInsightsResponse' {} Maybe [ProactiveInsightSummary]
a -> SearchOrganizationInsightsResponse
s {$sel:proactiveInsights:SearchOrganizationInsightsResponse' :: Maybe [ProactiveInsightSummary]
proactiveInsights = Maybe [ProactiveInsightSummary]
a} :: SearchOrganizationInsightsResponse) 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

-- | An integer that specifies the number of open reactive insights in your
-- Amazon Web Services account.
searchOrganizationInsightsResponse_reactiveInsights :: Lens.Lens' SearchOrganizationInsightsResponse (Prelude.Maybe [ReactiveInsightSummary])
searchOrganizationInsightsResponse_reactiveInsights :: Lens'
  SearchOrganizationInsightsResponse (Maybe [ReactiveInsightSummary])
searchOrganizationInsightsResponse_reactiveInsights = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsightsResponse' {Maybe [ReactiveInsightSummary]
reactiveInsights :: Maybe [ReactiveInsightSummary]
$sel:reactiveInsights:SearchOrganizationInsightsResponse' :: SearchOrganizationInsightsResponse
-> Maybe [ReactiveInsightSummary]
reactiveInsights} -> Maybe [ReactiveInsightSummary]
reactiveInsights) (\s :: SearchOrganizationInsightsResponse
s@SearchOrganizationInsightsResponse' {} Maybe [ReactiveInsightSummary]
a -> SearchOrganizationInsightsResponse
s {$sel:reactiveInsights:SearchOrganizationInsightsResponse' :: Maybe [ReactiveInsightSummary]
reactiveInsights = Maybe [ReactiveInsightSummary]
a} :: SearchOrganizationInsightsResponse) 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.
searchOrganizationInsightsResponse_httpStatus :: Lens.Lens' SearchOrganizationInsightsResponse Prelude.Int
searchOrganizationInsightsResponse_httpStatus :: Lens' SearchOrganizationInsightsResponse Int
searchOrganizationInsightsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchOrganizationInsightsResponse' {Int
httpStatus :: Int
$sel:httpStatus:SearchOrganizationInsightsResponse' :: SearchOrganizationInsightsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SearchOrganizationInsightsResponse
s@SearchOrganizationInsightsResponse' {} Int
a -> SearchOrganizationInsightsResponse
s {$sel:httpStatus:SearchOrganizationInsightsResponse' :: Int
httpStatus = Int
a} :: SearchOrganizationInsightsResponse)

instance
  Prelude.NFData
    SearchOrganizationInsightsResponse
  where
  rnf :: SearchOrganizationInsightsResponse -> ()
rnf SearchOrganizationInsightsResponse' {Int
Maybe [ReactiveInsightSummary]
Maybe [ProactiveInsightSummary]
Maybe Text
httpStatus :: Int
reactiveInsights :: Maybe [ReactiveInsightSummary]
proactiveInsights :: Maybe [ProactiveInsightSummary]
nextToken :: Maybe Text
$sel:httpStatus:SearchOrganizationInsightsResponse' :: SearchOrganizationInsightsResponse -> Int
$sel:reactiveInsights:SearchOrganizationInsightsResponse' :: SearchOrganizationInsightsResponse
-> Maybe [ReactiveInsightSummary]
$sel:proactiveInsights:SearchOrganizationInsightsResponse' :: SearchOrganizationInsightsResponse
-> Maybe [ProactiveInsightSummary]
$sel:nextToken:SearchOrganizationInsightsResponse' :: SearchOrganizationInsightsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ProactiveInsightSummary]
proactiveInsights
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ReactiveInsightSummary]
reactiveInsights
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus