{-# 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.IoTWireless.ListEventConfigurations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- List event configurations where at least one event topic has been
-- enabled.
module Amazonka.IoTWireless.ListEventConfigurations
  ( -- * Creating a Request
    ListEventConfigurations (..),
    newListEventConfigurations,

    -- * Request Lenses
    listEventConfigurations_maxResults,
    listEventConfigurations_nextToken,
    listEventConfigurations_resourceType,

    -- * Destructuring the Response
    ListEventConfigurationsResponse (..),
    newListEventConfigurationsResponse,

    -- * Response Lenses
    listEventConfigurationsResponse_eventConfigurationsList,
    listEventConfigurationsResponse_nextToken,
    listEventConfigurationsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListEventConfigurations' smart constructor.
data ListEventConfigurations = ListEventConfigurations'
  { ListEventConfigurations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | To retrieve the next set of results, the @nextToken@ value from a
    -- previous response; otherwise __null__ to receive the first set of
    -- results.
    ListEventConfigurations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Resource type to filter event configurations.
    ListEventConfigurations -> EventNotificationResourceType
resourceType :: EventNotificationResourceType
  }
  deriving (ListEventConfigurations -> ListEventConfigurations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListEventConfigurations -> ListEventConfigurations -> Bool
$c/= :: ListEventConfigurations -> ListEventConfigurations -> Bool
== :: ListEventConfigurations -> ListEventConfigurations -> Bool
$c== :: ListEventConfigurations -> ListEventConfigurations -> Bool
Prelude.Eq, ReadPrec [ListEventConfigurations]
ReadPrec ListEventConfigurations
Int -> ReadS ListEventConfigurations
ReadS [ListEventConfigurations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListEventConfigurations]
$creadListPrec :: ReadPrec [ListEventConfigurations]
readPrec :: ReadPrec ListEventConfigurations
$creadPrec :: ReadPrec ListEventConfigurations
readList :: ReadS [ListEventConfigurations]
$creadList :: ReadS [ListEventConfigurations]
readsPrec :: Int -> ReadS ListEventConfigurations
$creadsPrec :: Int -> ReadS ListEventConfigurations
Prelude.Read, Int -> ListEventConfigurations -> ShowS
[ListEventConfigurations] -> ShowS
ListEventConfigurations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListEventConfigurations] -> ShowS
$cshowList :: [ListEventConfigurations] -> ShowS
show :: ListEventConfigurations -> String
$cshow :: ListEventConfigurations -> String
showsPrec :: Int -> ListEventConfigurations -> ShowS
$cshowsPrec :: Int -> ListEventConfigurations -> ShowS
Prelude.Show, forall x. Rep ListEventConfigurations x -> ListEventConfigurations
forall x. ListEventConfigurations -> Rep ListEventConfigurations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListEventConfigurations x -> ListEventConfigurations
$cfrom :: forall x. ListEventConfigurations -> Rep ListEventConfigurations x
Prelude.Generic)

-- |
-- Create a value of 'ListEventConfigurations' 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', 'listEventConfigurations_maxResults' - Undocumented member.
--
-- 'nextToken', 'listEventConfigurations_nextToken' - To retrieve the next set of results, the @nextToken@ value from a
-- previous response; otherwise __null__ to receive the first set of
-- results.
--
-- 'resourceType', 'listEventConfigurations_resourceType' - Resource type to filter event configurations.
newListEventConfigurations ::
  -- | 'resourceType'
  EventNotificationResourceType ->
  ListEventConfigurations
newListEventConfigurations :: EventNotificationResourceType -> ListEventConfigurations
newListEventConfigurations EventNotificationResourceType
pResourceType_ =
  ListEventConfigurations'
    { $sel:maxResults:ListEventConfigurations' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListEventConfigurations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:ListEventConfigurations' :: EventNotificationResourceType
resourceType = EventNotificationResourceType
pResourceType_
    }

-- | Undocumented member.
listEventConfigurations_maxResults :: Lens.Lens' ListEventConfigurations (Prelude.Maybe Prelude.Natural)
listEventConfigurations_maxResults :: Lens' ListEventConfigurations (Maybe Natural)
listEventConfigurations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEventConfigurations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListEventConfigurations' :: ListEventConfigurations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListEventConfigurations
s@ListEventConfigurations' {} Maybe Natural
a -> ListEventConfigurations
s {$sel:maxResults:ListEventConfigurations' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListEventConfigurations)

-- | To retrieve the next set of results, the @nextToken@ value from a
-- previous response; otherwise __null__ to receive the first set of
-- results.
listEventConfigurations_nextToken :: Lens.Lens' ListEventConfigurations (Prelude.Maybe Prelude.Text)
listEventConfigurations_nextToken :: Lens' ListEventConfigurations (Maybe Text)
listEventConfigurations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEventConfigurations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListEventConfigurations' :: ListEventConfigurations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListEventConfigurations
s@ListEventConfigurations' {} Maybe Text
a -> ListEventConfigurations
s {$sel:nextToken:ListEventConfigurations' :: Maybe Text
nextToken = Maybe Text
a} :: ListEventConfigurations)

-- | Resource type to filter event configurations.
listEventConfigurations_resourceType :: Lens.Lens' ListEventConfigurations EventNotificationResourceType
listEventConfigurations_resourceType :: Lens' ListEventConfigurations EventNotificationResourceType
listEventConfigurations_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEventConfigurations' {EventNotificationResourceType
resourceType :: EventNotificationResourceType
$sel:resourceType:ListEventConfigurations' :: ListEventConfigurations -> EventNotificationResourceType
resourceType} -> EventNotificationResourceType
resourceType) (\s :: ListEventConfigurations
s@ListEventConfigurations' {} EventNotificationResourceType
a -> ListEventConfigurations
s {$sel:resourceType:ListEventConfigurations' :: EventNotificationResourceType
resourceType = EventNotificationResourceType
a} :: ListEventConfigurations)

instance Core.AWSRequest ListEventConfigurations where
  type
    AWSResponse ListEventConfigurations =
      ListEventConfigurationsResponse
  request :: (Service -> Service)
-> ListEventConfigurations -> Request ListEventConfigurations
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 ListEventConfigurations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListEventConfigurations)))
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 [EventConfigurationItem]
-> Maybe Text -> Int -> ListEventConfigurationsResponse
ListEventConfigurationsResponse'
            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
"EventConfigurationsList"
                            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 ListEventConfigurations where
  hashWithSalt :: Int -> ListEventConfigurations -> Int
hashWithSalt Int
_salt ListEventConfigurations' {Maybe Natural
Maybe Text
EventNotificationResourceType
resourceType :: EventNotificationResourceType
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceType:ListEventConfigurations' :: ListEventConfigurations -> EventNotificationResourceType
$sel:nextToken:ListEventConfigurations' :: ListEventConfigurations -> Maybe Text
$sel:maxResults:ListEventConfigurations' :: ListEventConfigurations -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` EventNotificationResourceType
resourceType

instance Prelude.NFData ListEventConfigurations where
  rnf :: ListEventConfigurations -> ()
rnf ListEventConfigurations' {Maybe Natural
Maybe Text
EventNotificationResourceType
resourceType :: EventNotificationResourceType
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceType:ListEventConfigurations' :: ListEventConfigurations -> EventNotificationResourceType
$sel:nextToken:ListEventConfigurations' :: ListEventConfigurations -> Maybe Text
$sel:maxResults:ListEventConfigurations' :: ListEventConfigurations -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf EventNotificationResourceType
resourceType

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

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

instance Data.ToQuery ListEventConfigurations where
  toQuery :: ListEventConfigurations -> QueryString
toQuery ListEventConfigurations' {Maybe Natural
Maybe Text
EventNotificationResourceType
resourceType :: EventNotificationResourceType
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceType:ListEventConfigurations' :: ListEventConfigurations -> EventNotificationResourceType
$sel:nextToken:ListEventConfigurations' :: ListEventConfigurations -> Maybe Text
$sel:maxResults:ListEventConfigurations' :: ListEventConfigurations -> 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,
        ByteString
"resourceType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: EventNotificationResourceType
resourceType
      ]

-- | /See:/ 'newListEventConfigurationsResponse' smart constructor.
data ListEventConfigurationsResponse = ListEventConfigurationsResponse'
  { -- | Event configurations of all events for a single resource.
    ListEventConfigurationsResponse -> Maybe [EventConfigurationItem]
eventConfigurationsList :: Prelude.Maybe [EventConfigurationItem],
    -- | To retrieve the next set of results, the @nextToken@ value from a
    -- previous response; otherwise __null__ to receive the first set of
    -- results.
    ListEventConfigurationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListEventConfigurationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListEventConfigurationsResponse
-> ListEventConfigurationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListEventConfigurationsResponse
-> ListEventConfigurationsResponse -> Bool
$c/= :: ListEventConfigurationsResponse
-> ListEventConfigurationsResponse -> Bool
== :: ListEventConfigurationsResponse
-> ListEventConfigurationsResponse -> Bool
$c== :: ListEventConfigurationsResponse
-> ListEventConfigurationsResponse -> Bool
Prelude.Eq, ReadPrec [ListEventConfigurationsResponse]
ReadPrec ListEventConfigurationsResponse
Int -> ReadS ListEventConfigurationsResponse
ReadS [ListEventConfigurationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListEventConfigurationsResponse]
$creadListPrec :: ReadPrec [ListEventConfigurationsResponse]
readPrec :: ReadPrec ListEventConfigurationsResponse
$creadPrec :: ReadPrec ListEventConfigurationsResponse
readList :: ReadS [ListEventConfigurationsResponse]
$creadList :: ReadS [ListEventConfigurationsResponse]
readsPrec :: Int -> ReadS ListEventConfigurationsResponse
$creadsPrec :: Int -> ReadS ListEventConfigurationsResponse
Prelude.Read, Int -> ListEventConfigurationsResponse -> ShowS
[ListEventConfigurationsResponse] -> ShowS
ListEventConfigurationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListEventConfigurationsResponse] -> ShowS
$cshowList :: [ListEventConfigurationsResponse] -> ShowS
show :: ListEventConfigurationsResponse -> String
$cshow :: ListEventConfigurationsResponse -> String
showsPrec :: Int -> ListEventConfigurationsResponse -> ShowS
$cshowsPrec :: Int -> ListEventConfigurationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListEventConfigurationsResponse x
-> ListEventConfigurationsResponse
forall x.
ListEventConfigurationsResponse
-> Rep ListEventConfigurationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListEventConfigurationsResponse x
-> ListEventConfigurationsResponse
$cfrom :: forall x.
ListEventConfigurationsResponse
-> Rep ListEventConfigurationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListEventConfigurationsResponse' 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:
--
-- 'eventConfigurationsList', 'listEventConfigurationsResponse_eventConfigurationsList' - Event configurations of all events for a single resource.
--
-- 'nextToken', 'listEventConfigurationsResponse_nextToken' - To retrieve the next set of results, the @nextToken@ value from a
-- previous response; otherwise __null__ to receive the first set of
-- results.
--
-- 'httpStatus', 'listEventConfigurationsResponse_httpStatus' - The response's http status code.
newListEventConfigurationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListEventConfigurationsResponse
newListEventConfigurationsResponse :: Int -> ListEventConfigurationsResponse
newListEventConfigurationsResponse Int
pHttpStatus_ =
  ListEventConfigurationsResponse'
    { $sel:eventConfigurationsList:ListEventConfigurationsResponse' :: Maybe [EventConfigurationItem]
eventConfigurationsList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListEventConfigurationsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListEventConfigurationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Event configurations of all events for a single resource.
listEventConfigurationsResponse_eventConfigurationsList :: Lens.Lens' ListEventConfigurationsResponse (Prelude.Maybe [EventConfigurationItem])
listEventConfigurationsResponse_eventConfigurationsList :: Lens'
  ListEventConfigurationsResponse (Maybe [EventConfigurationItem])
listEventConfigurationsResponse_eventConfigurationsList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEventConfigurationsResponse' {Maybe [EventConfigurationItem]
eventConfigurationsList :: Maybe [EventConfigurationItem]
$sel:eventConfigurationsList:ListEventConfigurationsResponse' :: ListEventConfigurationsResponse -> Maybe [EventConfigurationItem]
eventConfigurationsList} -> Maybe [EventConfigurationItem]
eventConfigurationsList) (\s :: ListEventConfigurationsResponse
s@ListEventConfigurationsResponse' {} Maybe [EventConfigurationItem]
a -> ListEventConfigurationsResponse
s {$sel:eventConfigurationsList:ListEventConfigurationsResponse' :: Maybe [EventConfigurationItem]
eventConfigurationsList = Maybe [EventConfigurationItem]
a} :: ListEventConfigurationsResponse) 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

-- | To retrieve the next set of results, the @nextToken@ value from a
-- previous response; otherwise __null__ to receive the first set of
-- results.
listEventConfigurationsResponse_nextToken :: Lens.Lens' ListEventConfigurationsResponse (Prelude.Maybe Prelude.Text)
listEventConfigurationsResponse_nextToken :: Lens' ListEventConfigurationsResponse (Maybe Text)
listEventConfigurationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEventConfigurationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListEventConfigurationsResponse' :: ListEventConfigurationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListEventConfigurationsResponse
s@ListEventConfigurationsResponse' {} Maybe Text
a -> ListEventConfigurationsResponse
s {$sel:nextToken:ListEventConfigurationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListEventConfigurationsResponse)

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

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