{-# 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.AuditManager.GetInsights
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the latest analytics data for all your current active assessments.
module Amazonka.AuditManager.GetInsights
  ( -- * Creating a Request
    GetInsights (..),
    newGetInsights,

    -- * Destructuring the Response
    GetInsightsResponse (..),
    newGetInsightsResponse,

    -- * Response Lenses
    getInsightsResponse_insights,
    getInsightsResponse_httpStatus,
  )
where

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

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

instance Core.AWSRequest GetInsights where
  type AWSResponse GetInsights = GetInsightsResponse
  request :: (Service -> Service) -> GetInsights -> Request GetInsights
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetInsights
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetInsights)))
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 Insights -> Int -> GetInsightsResponse
GetInsightsResponse'
            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
"insights")
            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 GetInsights where
  hashWithSalt :: Int -> GetInsights -> Int
hashWithSalt Int
_salt GetInsights
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance Data.ToHeaders GetInsights where
  toHeaders :: GetInsights -> 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.ToPath GetInsights where
  toPath :: GetInsights -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/insights"

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

-- | /See:/ 'newGetInsightsResponse' smart constructor.
data GetInsightsResponse = GetInsightsResponse'
  { -- | The analytics data that the @GetInsights@ API returned.
    GetInsightsResponse -> Maybe Insights
insights :: Prelude.Maybe Insights,
    -- | The response's http status code.
    GetInsightsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetInsightsResponse -> GetInsightsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInsightsResponse -> GetInsightsResponse -> Bool
$c/= :: GetInsightsResponse -> GetInsightsResponse -> Bool
== :: GetInsightsResponse -> GetInsightsResponse -> Bool
$c== :: GetInsightsResponse -> GetInsightsResponse -> Bool
Prelude.Eq, ReadPrec [GetInsightsResponse]
ReadPrec GetInsightsResponse
Int -> ReadS GetInsightsResponse
ReadS [GetInsightsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetInsightsResponse]
$creadListPrec :: ReadPrec [GetInsightsResponse]
readPrec :: ReadPrec GetInsightsResponse
$creadPrec :: ReadPrec GetInsightsResponse
readList :: ReadS [GetInsightsResponse]
$creadList :: ReadS [GetInsightsResponse]
readsPrec :: Int -> ReadS GetInsightsResponse
$creadsPrec :: Int -> ReadS GetInsightsResponse
Prelude.Read, Int -> GetInsightsResponse -> ShowS
[GetInsightsResponse] -> ShowS
GetInsightsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInsightsResponse] -> ShowS
$cshowList :: [GetInsightsResponse] -> ShowS
show :: GetInsightsResponse -> String
$cshow :: GetInsightsResponse -> String
showsPrec :: Int -> GetInsightsResponse -> ShowS
$cshowsPrec :: Int -> GetInsightsResponse -> ShowS
Prelude.Show, forall x. Rep GetInsightsResponse x -> GetInsightsResponse
forall x. GetInsightsResponse -> Rep GetInsightsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetInsightsResponse x -> GetInsightsResponse
$cfrom :: forall x. GetInsightsResponse -> Rep GetInsightsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetInsightsResponse' 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:
--
-- 'insights', 'getInsightsResponse_insights' - The analytics data that the @GetInsights@ API returned.
--
-- 'httpStatus', 'getInsightsResponse_httpStatus' - The response's http status code.
newGetInsightsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetInsightsResponse
newGetInsightsResponse :: Int -> GetInsightsResponse
newGetInsightsResponse Int
pHttpStatus_ =
  GetInsightsResponse'
    { $sel:insights:GetInsightsResponse' :: Maybe Insights
insights = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetInsightsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The analytics data that the @GetInsights@ API returned.
getInsightsResponse_insights :: Lens.Lens' GetInsightsResponse (Prelude.Maybe Insights)
getInsightsResponse_insights :: Lens' GetInsightsResponse (Maybe Insights)
getInsightsResponse_insights = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightsResponse' {Maybe Insights
insights :: Maybe Insights
$sel:insights:GetInsightsResponse' :: GetInsightsResponse -> Maybe Insights
insights} -> Maybe Insights
insights) (\s :: GetInsightsResponse
s@GetInsightsResponse' {} Maybe Insights
a -> GetInsightsResponse
s {$sel:insights:GetInsightsResponse' :: Maybe Insights
insights = Maybe Insights
a} :: GetInsightsResponse)

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

instance Prelude.NFData GetInsightsResponse where
  rnf :: GetInsightsResponse -> ()
rnf GetInsightsResponse' {Int
Maybe Insights
httpStatus :: Int
insights :: Maybe Insights
$sel:httpStatus:GetInsightsResponse' :: GetInsightsResponse -> Int
$sel:insights:GetInsightsResponse' :: GetInsightsResponse -> Maybe Insights
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Insights
insights
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus