{-# 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.Inspector.GetTelemetryMetadata
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Information about the data that is collected for the specified
-- assessment run.
module Amazonka.Inspector.GetTelemetryMetadata
  ( -- * Creating a Request
    GetTelemetryMetadata (..),
    newGetTelemetryMetadata,

    -- * Request Lenses
    getTelemetryMetadata_assessmentRunArn,

    -- * Destructuring the Response
    GetTelemetryMetadataResponse (..),
    newGetTelemetryMetadataResponse,

    -- * Response Lenses
    getTelemetryMetadataResponse_httpStatus,
    getTelemetryMetadataResponse_telemetryMetadata,
  )
where

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

-- | /See:/ 'newGetTelemetryMetadata' smart constructor.
data GetTelemetryMetadata = GetTelemetryMetadata'
  { -- | The ARN that specifies the assessment run that has the telemetry data
    -- that you want to obtain.
    GetTelemetryMetadata -> Text
assessmentRunArn :: Prelude.Text
  }
  deriving (GetTelemetryMetadata -> GetTelemetryMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTelemetryMetadata -> GetTelemetryMetadata -> Bool
$c/= :: GetTelemetryMetadata -> GetTelemetryMetadata -> Bool
== :: GetTelemetryMetadata -> GetTelemetryMetadata -> Bool
$c== :: GetTelemetryMetadata -> GetTelemetryMetadata -> Bool
Prelude.Eq, ReadPrec [GetTelemetryMetadata]
ReadPrec GetTelemetryMetadata
Int -> ReadS GetTelemetryMetadata
ReadS [GetTelemetryMetadata]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTelemetryMetadata]
$creadListPrec :: ReadPrec [GetTelemetryMetadata]
readPrec :: ReadPrec GetTelemetryMetadata
$creadPrec :: ReadPrec GetTelemetryMetadata
readList :: ReadS [GetTelemetryMetadata]
$creadList :: ReadS [GetTelemetryMetadata]
readsPrec :: Int -> ReadS GetTelemetryMetadata
$creadsPrec :: Int -> ReadS GetTelemetryMetadata
Prelude.Read, Int -> GetTelemetryMetadata -> ShowS
[GetTelemetryMetadata] -> ShowS
GetTelemetryMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTelemetryMetadata] -> ShowS
$cshowList :: [GetTelemetryMetadata] -> ShowS
show :: GetTelemetryMetadata -> String
$cshow :: GetTelemetryMetadata -> String
showsPrec :: Int -> GetTelemetryMetadata -> ShowS
$cshowsPrec :: Int -> GetTelemetryMetadata -> ShowS
Prelude.Show, forall x. Rep GetTelemetryMetadata x -> GetTelemetryMetadata
forall x. GetTelemetryMetadata -> Rep GetTelemetryMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTelemetryMetadata x -> GetTelemetryMetadata
$cfrom :: forall x. GetTelemetryMetadata -> Rep GetTelemetryMetadata x
Prelude.Generic)

-- |
-- Create a value of 'GetTelemetryMetadata' 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:
--
-- 'assessmentRunArn', 'getTelemetryMetadata_assessmentRunArn' - The ARN that specifies the assessment run that has the telemetry data
-- that you want to obtain.
newGetTelemetryMetadata ::
  -- | 'assessmentRunArn'
  Prelude.Text ->
  GetTelemetryMetadata
newGetTelemetryMetadata :: Text -> GetTelemetryMetadata
newGetTelemetryMetadata Text
pAssessmentRunArn_ =
  GetTelemetryMetadata'
    { $sel:assessmentRunArn:GetTelemetryMetadata' :: Text
assessmentRunArn =
        Text
pAssessmentRunArn_
    }

-- | The ARN that specifies the assessment run that has the telemetry data
-- that you want to obtain.
getTelemetryMetadata_assessmentRunArn :: Lens.Lens' GetTelemetryMetadata Prelude.Text
getTelemetryMetadata_assessmentRunArn :: Lens' GetTelemetryMetadata Text
getTelemetryMetadata_assessmentRunArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTelemetryMetadata' {Text
assessmentRunArn :: Text
$sel:assessmentRunArn:GetTelemetryMetadata' :: GetTelemetryMetadata -> Text
assessmentRunArn} -> Text
assessmentRunArn) (\s :: GetTelemetryMetadata
s@GetTelemetryMetadata' {} Text
a -> GetTelemetryMetadata
s {$sel:assessmentRunArn:GetTelemetryMetadata' :: Text
assessmentRunArn = Text
a} :: GetTelemetryMetadata)

instance Core.AWSRequest GetTelemetryMetadata where
  type
    AWSResponse GetTelemetryMetadata =
      GetTelemetryMetadataResponse
  request :: (Service -> Service)
-> GetTelemetryMetadata -> Request GetTelemetryMetadata
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 GetTelemetryMetadata
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetTelemetryMetadata)))
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 ->
          Int -> [TelemetryMetadata] -> GetTelemetryMetadataResponse
GetTelemetryMetadataResponse'
            forall (f :: * -> *) a b. Functor 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))
            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
"telemetryMetadata"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable GetTelemetryMetadata where
  hashWithSalt :: Int -> GetTelemetryMetadata -> Int
hashWithSalt Int
_salt GetTelemetryMetadata' {Text
assessmentRunArn :: Text
$sel:assessmentRunArn:GetTelemetryMetadata' :: GetTelemetryMetadata -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
assessmentRunArn

instance Prelude.NFData GetTelemetryMetadata where
  rnf :: GetTelemetryMetadata -> ()
rnf GetTelemetryMetadata' {Text
assessmentRunArn :: Text
$sel:assessmentRunArn:GetTelemetryMetadata' :: GetTelemetryMetadata -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
assessmentRunArn

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

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

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

-- | /See:/ 'newGetTelemetryMetadataResponse' smart constructor.
data GetTelemetryMetadataResponse = GetTelemetryMetadataResponse'
  { -- | The response's http status code.
    GetTelemetryMetadataResponse -> Int
httpStatus :: Prelude.Int,
    -- | Telemetry details.
    GetTelemetryMetadataResponse -> [TelemetryMetadata]
telemetryMetadata :: [TelemetryMetadata]
  }
  deriving (GetTelemetryMetadataResponse
-> GetTelemetryMetadataResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTelemetryMetadataResponse
-> GetTelemetryMetadataResponse -> Bool
$c/= :: GetTelemetryMetadataResponse
-> GetTelemetryMetadataResponse -> Bool
== :: GetTelemetryMetadataResponse
-> GetTelemetryMetadataResponse -> Bool
$c== :: GetTelemetryMetadataResponse
-> GetTelemetryMetadataResponse -> Bool
Prelude.Eq, ReadPrec [GetTelemetryMetadataResponse]
ReadPrec GetTelemetryMetadataResponse
Int -> ReadS GetTelemetryMetadataResponse
ReadS [GetTelemetryMetadataResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTelemetryMetadataResponse]
$creadListPrec :: ReadPrec [GetTelemetryMetadataResponse]
readPrec :: ReadPrec GetTelemetryMetadataResponse
$creadPrec :: ReadPrec GetTelemetryMetadataResponse
readList :: ReadS [GetTelemetryMetadataResponse]
$creadList :: ReadS [GetTelemetryMetadataResponse]
readsPrec :: Int -> ReadS GetTelemetryMetadataResponse
$creadsPrec :: Int -> ReadS GetTelemetryMetadataResponse
Prelude.Read, Int -> GetTelemetryMetadataResponse -> ShowS
[GetTelemetryMetadataResponse] -> ShowS
GetTelemetryMetadataResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTelemetryMetadataResponse] -> ShowS
$cshowList :: [GetTelemetryMetadataResponse] -> ShowS
show :: GetTelemetryMetadataResponse -> String
$cshow :: GetTelemetryMetadataResponse -> String
showsPrec :: Int -> GetTelemetryMetadataResponse -> ShowS
$cshowsPrec :: Int -> GetTelemetryMetadataResponse -> ShowS
Prelude.Show, forall x.
Rep GetTelemetryMetadataResponse x -> GetTelemetryMetadataResponse
forall x.
GetTelemetryMetadataResponse -> Rep GetTelemetryMetadataResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetTelemetryMetadataResponse x -> GetTelemetryMetadataResponse
$cfrom :: forall x.
GetTelemetryMetadataResponse -> Rep GetTelemetryMetadataResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetTelemetryMetadataResponse' 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:
--
-- 'httpStatus', 'getTelemetryMetadataResponse_httpStatus' - The response's http status code.
--
-- 'telemetryMetadata', 'getTelemetryMetadataResponse_telemetryMetadata' - Telemetry details.
newGetTelemetryMetadataResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetTelemetryMetadataResponse
newGetTelemetryMetadataResponse :: Int -> GetTelemetryMetadataResponse
newGetTelemetryMetadataResponse Int
pHttpStatus_ =
  GetTelemetryMetadataResponse'
    { $sel:httpStatus:GetTelemetryMetadataResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:telemetryMetadata:GetTelemetryMetadataResponse' :: [TelemetryMetadata]
telemetryMetadata = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | Telemetry details.
getTelemetryMetadataResponse_telemetryMetadata :: Lens.Lens' GetTelemetryMetadataResponse [TelemetryMetadata]
getTelemetryMetadataResponse_telemetryMetadata :: Lens' GetTelemetryMetadataResponse [TelemetryMetadata]
getTelemetryMetadataResponse_telemetryMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTelemetryMetadataResponse' {[TelemetryMetadata]
telemetryMetadata :: [TelemetryMetadata]
$sel:telemetryMetadata:GetTelemetryMetadataResponse' :: GetTelemetryMetadataResponse -> [TelemetryMetadata]
telemetryMetadata} -> [TelemetryMetadata]
telemetryMetadata) (\s :: GetTelemetryMetadataResponse
s@GetTelemetryMetadataResponse' {} [TelemetryMetadata]
a -> GetTelemetryMetadataResponse
s {$sel:telemetryMetadata:GetTelemetryMetadataResponse' :: [TelemetryMetadata]
telemetryMetadata = [TelemetryMetadata]
a} :: GetTelemetryMetadataResponse) 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

instance Prelude.NFData GetTelemetryMetadataResponse where
  rnf :: GetTelemetryMetadataResponse -> ()
rnf GetTelemetryMetadataResponse' {Int
[TelemetryMetadata]
telemetryMetadata :: [TelemetryMetadata]
httpStatus :: Int
$sel:telemetryMetadata:GetTelemetryMetadataResponse' :: GetTelemetryMetadataResponse -> [TelemetryMetadata]
$sel:httpStatus:GetTelemetryMetadataResponse' :: GetTelemetryMetadataResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [TelemetryMetadata]
telemetryMetadata