{-# 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.IoT.ListCustomMetrics
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists your Device Defender detect custom metrics.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions ListCustomMetrics>
-- action.
--
-- This operation returns paginated results.
module Amazonka.IoT.ListCustomMetrics
  ( -- * Creating a Request
    ListCustomMetrics (..),
    newListCustomMetrics,

    -- * Request Lenses
    listCustomMetrics_maxResults,
    listCustomMetrics_nextToken,

    -- * Destructuring the Response
    ListCustomMetricsResponse (..),
    newListCustomMetricsResponse,

    -- * Response Lenses
    listCustomMetricsResponse_metricNames,
    listCustomMetricsResponse_nextToken,
    listCustomMetricsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListCustomMetrics' smart constructor.
data ListCustomMetrics = ListCustomMetrics'
  { -- | The maximum number of results to return at one time. The default is 25.
    ListCustomMetrics -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next set of results.
    ListCustomMetrics -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListCustomMetrics -> ListCustomMetrics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCustomMetrics -> ListCustomMetrics -> Bool
$c/= :: ListCustomMetrics -> ListCustomMetrics -> Bool
== :: ListCustomMetrics -> ListCustomMetrics -> Bool
$c== :: ListCustomMetrics -> ListCustomMetrics -> Bool
Prelude.Eq, ReadPrec [ListCustomMetrics]
ReadPrec ListCustomMetrics
Int -> ReadS ListCustomMetrics
ReadS [ListCustomMetrics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCustomMetrics]
$creadListPrec :: ReadPrec [ListCustomMetrics]
readPrec :: ReadPrec ListCustomMetrics
$creadPrec :: ReadPrec ListCustomMetrics
readList :: ReadS [ListCustomMetrics]
$creadList :: ReadS [ListCustomMetrics]
readsPrec :: Int -> ReadS ListCustomMetrics
$creadsPrec :: Int -> ReadS ListCustomMetrics
Prelude.Read, Int -> ListCustomMetrics -> ShowS
[ListCustomMetrics] -> ShowS
ListCustomMetrics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCustomMetrics] -> ShowS
$cshowList :: [ListCustomMetrics] -> ShowS
show :: ListCustomMetrics -> String
$cshow :: ListCustomMetrics -> String
showsPrec :: Int -> ListCustomMetrics -> ShowS
$cshowsPrec :: Int -> ListCustomMetrics -> ShowS
Prelude.Show, forall x. Rep ListCustomMetrics x -> ListCustomMetrics
forall x. ListCustomMetrics -> Rep ListCustomMetrics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCustomMetrics x -> ListCustomMetrics
$cfrom :: forall x. ListCustomMetrics -> Rep ListCustomMetrics x
Prelude.Generic)

-- |
-- Create a value of 'ListCustomMetrics' 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:
--
-- 'maxResults', 'listCustomMetrics_maxResults' - The maximum number of results to return at one time. The default is 25.
--
-- 'nextToken', 'listCustomMetrics_nextToken' - The token for the next set of results.
newListCustomMetrics ::
  ListCustomMetrics
newListCustomMetrics :: ListCustomMetrics
newListCustomMetrics =
  ListCustomMetrics'
    { $sel:maxResults:ListCustomMetrics' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCustomMetrics' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of results to return at one time. The default is 25.
listCustomMetrics_maxResults :: Lens.Lens' ListCustomMetrics (Prelude.Maybe Prelude.Natural)
listCustomMetrics_maxResults :: Lens' ListCustomMetrics (Maybe Natural)
listCustomMetrics_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCustomMetrics' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListCustomMetrics' :: ListCustomMetrics -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListCustomMetrics
s@ListCustomMetrics' {} Maybe Natural
a -> ListCustomMetrics
s {$sel:maxResults:ListCustomMetrics' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListCustomMetrics)

-- | The token for the next set of results.
listCustomMetrics_nextToken :: Lens.Lens' ListCustomMetrics (Prelude.Maybe Prelude.Text)
listCustomMetrics_nextToken :: Lens' ListCustomMetrics (Maybe Text)
listCustomMetrics_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCustomMetrics' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCustomMetrics' :: ListCustomMetrics -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCustomMetrics
s@ListCustomMetrics' {} Maybe Text
a -> ListCustomMetrics
s {$sel:nextToken:ListCustomMetrics' :: Maybe Text
nextToken = Maybe Text
a} :: ListCustomMetrics)

instance Core.AWSPager ListCustomMetrics where
  page :: ListCustomMetrics
-> AWSResponse ListCustomMetrics -> Maybe ListCustomMetrics
page ListCustomMetrics
rq AWSResponse ListCustomMetrics
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListCustomMetrics
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCustomMetricsResponse (Maybe Text)
listCustomMetricsResponse_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 ListCustomMetrics
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCustomMetricsResponse (Maybe [Text])
listCustomMetricsResponse_metricNames
            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.$ ListCustomMetrics
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListCustomMetrics (Maybe Text)
listCustomMetrics_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListCustomMetrics
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCustomMetricsResponse (Maybe Text)
listCustomMetricsResponse_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 ListCustomMetrics where
  type
    AWSResponse ListCustomMetrics =
      ListCustomMetricsResponse
  request :: (Service -> Service)
-> ListCustomMetrics -> Request ListCustomMetrics
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 ListCustomMetrics
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListCustomMetrics)))
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 Text -> Int -> ListCustomMetricsResponse
ListCustomMetricsResponse'
            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
"metricNames" 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
"nextToken")
            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 ListCustomMetrics where
  hashWithSalt :: Int -> ListCustomMetrics -> Int
hashWithSalt Int
_salt ListCustomMetrics' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListCustomMetrics' :: ListCustomMetrics -> Maybe Text
$sel:maxResults:ListCustomMetrics' :: ListCustomMetrics -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListCustomMetrics where
  rnf :: ListCustomMetrics -> ()
rnf ListCustomMetrics' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListCustomMetrics' :: ListCustomMetrics -> Maybe Text
$sel:maxResults:ListCustomMetrics' :: ListCustomMetrics -> Maybe Natural
..} =
    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

instance Data.ToHeaders ListCustomMetrics where
  toHeaders :: ListCustomMetrics -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ListCustomMetrics where
  toQuery :: ListCustomMetrics -> QueryString
toQuery ListCustomMetrics' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListCustomMetrics' :: ListCustomMetrics -> Maybe Text
$sel:maxResults:ListCustomMetrics' :: ListCustomMetrics -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListCustomMetricsResponse' smart constructor.
data ListCustomMetricsResponse = ListCustomMetricsResponse'
  { -- | The name of the custom metric.
    ListCustomMetricsResponse -> Maybe [Text]
metricNames :: Prelude.Maybe [Prelude.Text],
    -- | A token that can be used to retrieve the next set of results, or @null@
    -- if there are no additional results.
    ListCustomMetricsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListCustomMetricsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListCustomMetricsResponse -> ListCustomMetricsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCustomMetricsResponse -> ListCustomMetricsResponse -> Bool
$c/= :: ListCustomMetricsResponse -> ListCustomMetricsResponse -> Bool
== :: ListCustomMetricsResponse -> ListCustomMetricsResponse -> Bool
$c== :: ListCustomMetricsResponse -> ListCustomMetricsResponse -> Bool
Prelude.Eq, ReadPrec [ListCustomMetricsResponse]
ReadPrec ListCustomMetricsResponse
Int -> ReadS ListCustomMetricsResponse
ReadS [ListCustomMetricsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCustomMetricsResponse]
$creadListPrec :: ReadPrec [ListCustomMetricsResponse]
readPrec :: ReadPrec ListCustomMetricsResponse
$creadPrec :: ReadPrec ListCustomMetricsResponse
readList :: ReadS [ListCustomMetricsResponse]
$creadList :: ReadS [ListCustomMetricsResponse]
readsPrec :: Int -> ReadS ListCustomMetricsResponse
$creadsPrec :: Int -> ReadS ListCustomMetricsResponse
Prelude.Read, Int -> ListCustomMetricsResponse -> ShowS
[ListCustomMetricsResponse] -> ShowS
ListCustomMetricsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCustomMetricsResponse] -> ShowS
$cshowList :: [ListCustomMetricsResponse] -> ShowS
show :: ListCustomMetricsResponse -> String
$cshow :: ListCustomMetricsResponse -> String
showsPrec :: Int -> ListCustomMetricsResponse -> ShowS
$cshowsPrec :: Int -> ListCustomMetricsResponse -> ShowS
Prelude.Show, forall x.
Rep ListCustomMetricsResponse x -> ListCustomMetricsResponse
forall x.
ListCustomMetricsResponse -> Rep ListCustomMetricsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListCustomMetricsResponse x -> ListCustomMetricsResponse
$cfrom :: forall x.
ListCustomMetricsResponse -> Rep ListCustomMetricsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListCustomMetricsResponse' 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:
--
-- 'metricNames', 'listCustomMetricsResponse_metricNames' - The name of the custom metric.
--
-- 'nextToken', 'listCustomMetricsResponse_nextToken' - A token that can be used to retrieve the next set of results, or @null@
-- if there are no additional results.
--
-- 'httpStatus', 'listCustomMetricsResponse_httpStatus' - The response's http status code.
newListCustomMetricsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListCustomMetricsResponse
newListCustomMetricsResponse :: Int -> ListCustomMetricsResponse
newListCustomMetricsResponse Int
pHttpStatus_ =
  ListCustomMetricsResponse'
    { $sel:metricNames:ListCustomMetricsResponse' :: Maybe [Text]
metricNames =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCustomMetricsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListCustomMetricsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The name of the custom metric.
listCustomMetricsResponse_metricNames :: Lens.Lens' ListCustomMetricsResponse (Prelude.Maybe [Prelude.Text])
listCustomMetricsResponse_metricNames :: Lens' ListCustomMetricsResponse (Maybe [Text])
listCustomMetricsResponse_metricNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCustomMetricsResponse' {Maybe [Text]
metricNames :: Maybe [Text]
$sel:metricNames:ListCustomMetricsResponse' :: ListCustomMetricsResponse -> Maybe [Text]
metricNames} -> Maybe [Text]
metricNames) (\s :: ListCustomMetricsResponse
s@ListCustomMetricsResponse' {} Maybe [Text]
a -> ListCustomMetricsResponse
s {$sel:metricNames:ListCustomMetricsResponse' :: Maybe [Text]
metricNames = Maybe [Text]
a} :: ListCustomMetricsResponse) 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

-- | A token that can be used to retrieve the next set of results, or @null@
-- if there are no additional results.
listCustomMetricsResponse_nextToken :: Lens.Lens' ListCustomMetricsResponse (Prelude.Maybe Prelude.Text)
listCustomMetricsResponse_nextToken :: Lens' ListCustomMetricsResponse (Maybe Text)
listCustomMetricsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCustomMetricsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCustomMetricsResponse' :: ListCustomMetricsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCustomMetricsResponse
s@ListCustomMetricsResponse' {} Maybe Text
a -> ListCustomMetricsResponse
s {$sel:nextToken:ListCustomMetricsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListCustomMetricsResponse)

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

instance Prelude.NFData ListCustomMetricsResponse where
  rnf :: ListCustomMetricsResponse -> ()
rnf ListCustomMetricsResponse' {Int
Maybe [Text]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
metricNames :: Maybe [Text]
$sel:httpStatus:ListCustomMetricsResponse' :: ListCustomMetricsResponse -> Int
$sel:nextToken:ListCustomMetricsResponse' :: ListCustomMetricsResponse -> Maybe Text
$sel:metricNames:ListCustomMetricsResponse' :: ListCustomMetricsResponse -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
metricNames
      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 Int
httpStatus