{-# 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.WellArchitected.ListNotifications
-- 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 lens notifications.
module Amazonka.WellArchitected.ListNotifications
  ( -- * Creating a Request
    ListNotifications (..),
    newListNotifications,

    -- * Request Lenses
    listNotifications_maxResults,
    listNotifications_nextToken,
    listNotifications_workloadId,

    -- * Destructuring the Response
    ListNotificationsResponse (..),
    newListNotificationsResponse,

    -- * Response Lenses
    listNotificationsResponse_nextToken,
    listNotificationsResponse_notificationSummaries,
    listNotificationsResponse_httpStatus,
  )
where

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
import Amazonka.WellArchitected.Types

-- | /See:/ 'newListNotifications' smart constructor.
data ListNotifications = ListNotifications'
  { -- | The maximum number of results to return for this request.
    ListNotifications -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    ListNotifications -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    ListNotifications -> Maybe Text
workloadId :: Prelude.Maybe Prelude.Text
  }
  deriving (ListNotifications -> ListNotifications -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListNotifications -> ListNotifications -> Bool
$c/= :: ListNotifications -> ListNotifications -> Bool
== :: ListNotifications -> ListNotifications -> Bool
$c== :: ListNotifications -> ListNotifications -> Bool
Prelude.Eq, ReadPrec [ListNotifications]
ReadPrec ListNotifications
Int -> ReadS ListNotifications
ReadS [ListNotifications]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListNotifications]
$creadListPrec :: ReadPrec [ListNotifications]
readPrec :: ReadPrec ListNotifications
$creadPrec :: ReadPrec ListNotifications
readList :: ReadS [ListNotifications]
$creadList :: ReadS [ListNotifications]
readsPrec :: Int -> ReadS ListNotifications
$creadsPrec :: Int -> ReadS ListNotifications
Prelude.Read, Int -> ListNotifications -> ShowS
[ListNotifications] -> ShowS
ListNotifications -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListNotifications] -> ShowS
$cshowList :: [ListNotifications] -> ShowS
show :: ListNotifications -> String
$cshow :: ListNotifications -> String
showsPrec :: Int -> ListNotifications -> ShowS
$cshowsPrec :: Int -> ListNotifications -> ShowS
Prelude.Show, forall x. Rep ListNotifications x -> ListNotifications
forall x. ListNotifications -> Rep ListNotifications x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListNotifications x -> ListNotifications
$cfrom :: forall x. ListNotifications -> Rep ListNotifications x
Prelude.Generic)

-- |
-- Create a value of 'ListNotifications' 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', 'listNotifications_maxResults' - The maximum number of results to return for this request.
--
-- 'nextToken', 'listNotifications_nextToken' - Undocumented member.
--
-- 'workloadId', 'listNotifications_workloadId' - Undocumented member.
newListNotifications ::
  ListNotifications
newListNotifications :: ListNotifications
newListNotifications =
  ListNotifications'
    { $sel:maxResults:ListNotifications' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListNotifications' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:workloadId:ListNotifications' :: Maybe Text
workloadId = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of results to return for this request.
listNotifications_maxResults :: Lens.Lens' ListNotifications (Prelude.Maybe Prelude.Natural)
listNotifications_maxResults :: Lens' ListNotifications (Maybe Natural)
listNotifications_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNotifications' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListNotifications' :: ListNotifications -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListNotifications
s@ListNotifications' {} Maybe Natural
a -> ListNotifications
s {$sel:maxResults:ListNotifications' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListNotifications)

-- | Undocumented member.
listNotifications_nextToken :: Lens.Lens' ListNotifications (Prelude.Maybe Prelude.Text)
listNotifications_nextToken :: Lens' ListNotifications (Maybe Text)
listNotifications_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNotifications' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListNotifications' :: ListNotifications -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListNotifications
s@ListNotifications' {} Maybe Text
a -> ListNotifications
s {$sel:nextToken:ListNotifications' :: Maybe Text
nextToken = Maybe Text
a} :: ListNotifications)

-- | Undocumented member.
listNotifications_workloadId :: Lens.Lens' ListNotifications (Prelude.Maybe Prelude.Text)
listNotifications_workloadId :: Lens' ListNotifications (Maybe Text)
listNotifications_workloadId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNotifications' {Maybe Text
workloadId :: Maybe Text
$sel:workloadId:ListNotifications' :: ListNotifications -> Maybe Text
workloadId} -> Maybe Text
workloadId) (\s :: ListNotifications
s@ListNotifications' {} Maybe Text
a -> ListNotifications
s {$sel:workloadId:ListNotifications' :: Maybe Text
workloadId = Maybe Text
a} :: ListNotifications)

instance Core.AWSRequest ListNotifications where
  type
    AWSResponse ListNotifications =
      ListNotificationsResponse
  request :: (Service -> Service)
-> ListNotifications -> Request ListNotifications
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 ListNotifications
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListNotifications)))
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 [NotificationSummary] -> Int -> ListNotificationsResponse
ListNotificationsResponse'
            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
"NotificationSummaries"
                            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 ListNotifications where
  hashWithSalt :: Int -> ListNotifications -> Int
hashWithSalt Int
_salt ListNotifications' {Maybe Natural
Maybe Text
workloadId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:workloadId:ListNotifications' :: ListNotifications -> Maybe Text
$sel:nextToken:ListNotifications' :: ListNotifications -> Maybe Text
$sel:maxResults:ListNotifications' :: ListNotifications -> 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` Maybe Text
workloadId

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

instance Data.ToHeaders ListNotifications where
  toHeaders :: ListNotifications -> 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 ListNotifications where
  toJSON :: ListNotifications -> Value
toJSON ListNotifications' {Maybe Natural
Maybe Text
workloadId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:workloadId:ListNotifications' :: ListNotifications -> Maybe Text
$sel:nextToken:ListNotifications' :: ListNotifications -> Maybe Text
$sel:maxResults:ListNotifications' :: ListNotifications -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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,
            (Key
"WorkloadId" 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
workloadId
          ]
      )

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

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

-- | /See:/ 'newListNotificationsResponse' smart constructor.
data ListNotificationsResponse = ListNotificationsResponse'
  { ListNotificationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | List of lens notification summaries in a workload.
    ListNotificationsResponse -> Maybe [NotificationSummary]
notificationSummaries :: Prelude.Maybe [NotificationSummary],
    -- | The response's http status code.
    ListNotificationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListNotificationsResponse -> ListNotificationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListNotificationsResponse -> ListNotificationsResponse -> Bool
$c/= :: ListNotificationsResponse -> ListNotificationsResponse -> Bool
== :: ListNotificationsResponse -> ListNotificationsResponse -> Bool
$c== :: ListNotificationsResponse -> ListNotificationsResponse -> Bool
Prelude.Eq, ReadPrec [ListNotificationsResponse]
ReadPrec ListNotificationsResponse
Int -> ReadS ListNotificationsResponse
ReadS [ListNotificationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListNotificationsResponse]
$creadListPrec :: ReadPrec [ListNotificationsResponse]
readPrec :: ReadPrec ListNotificationsResponse
$creadPrec :: ReadPrec ListNotificationsResponse
readList :: ReadS [ListNotificationsResponse]
$creadList :: ReadS [ListNotificationsResponse]
readsPrec :: Int -> ReadS ListNotificationsResponse
$creadsPrec :: Int -> ReadS ListNotificationsResponse
Prelude.Read, Int -> ListNotificationsResponse -> ShowS
[ListNotificationsResponse] -> ShowS
ListNotificationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListNotificationsResponse] -> ShowS
$cshowList :: [ListNotificationsResponse] -> ShowS
show :: ListNotificationsResponse -> String
$cshow :: ListNotificationsResponse -> String
showsPrec :: Int -> ListNotificationsResponse -> ShowS
$cshowsPrec :: Int -> ListNotificationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListNotificationsResponse x -> ListNotificationsResponse
forall x.
ListNotificationsResponse -> Rep ListNotificationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListNotificationsResponse x -> ListNotificationsResponse
$cfrom :: forall x.
ListNotificationsResponse -> Rep ListNotificationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListNotificationsResponse' 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', 'listNotificationsResponse_nextToken' - Undocumented member.
--
-- 'notificationSummaries', 'listNotificationsResponse_notificationSummaries' - List of lens notification summaries in a workload.
--
-- 'httpStatus', 'listNotificationsResponse_httpStatus' - The response's http status code.
newListNotificationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListNotificationsResponse
newListNotificationsResponse :: Int -> ListNotificationsResponse
newListNotificationsResponse Int
pHttpStatus_ =
  ListNotificationsResponse'
    { $sel:nextToken:ListNotificationsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:notificationSummaries:ListNotificationsResponse' :: Maybe [NotificationSummary]
notificationSummaries = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListNotificationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
listNotificationsResponse_nextToken :: Lens.Lens' ListNotificationsResponse (Prelude.Maybe Prelude.Text)
listNotificationsResponse_nextToken :: Lens' ListNotificationsResponse (Maybe Text)
listNotificationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNotificationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListNotificationsResponse' :: ListNotificationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListNotificationsResponse
s@ListNotificationsResponse' {} Maybe Text
a -> ListNotificationsResponse
s {$sel:nextToken:ListNotificationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListNotificationsResponse)

-- | List of lens notification summaries in a workload.
listNotificationsResponse_notificationSummaries :: Lens.Lens' ListNotificationsResponse (Prelude.Maybe [NotificationSummary])
listNotificationsResponse_notificationSummaries :: Lens' ListNotificationsResponse (Maybe [NotificationSummary])
listNotificationsResponse_notificationSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNotificationsResponse' {Maybe [NotificationSummary]
notificationSummaries :: Maybe [NotificationSummary]
$sel:notificationSummaries:ListNotificationsResponse' :: ListNotificationsResponse -> Maybe [NotificationSummary]
notificationSummaries} -> Maybe [NotificationSummary]
notificationSummaries) (\s :: ListNotificationsResponse
s@ListNotificationsResponse' {} Maybe [NotificationSummary]
a -> ListNotificationsResponse
s {$sel:notificationSummaries:ListNotificationsResponse' :: Maybe [NotificationSummary]
notificationSummaries = Maybe [NotificationSummary]
a} :: ListNotificationsResponse) 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.
listNotificationsResponse_httpStatus :: Lens.Lens' ListNotificationsResponse Prelude.Int
listNotificationsResponse_httpStatus :: Lens' ListNotificationsResponse Int
listNotificationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNotificationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListNotificationsResponse' :: ListNotificationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListNotificationsResponse
s@ListNotificationsResponse' {} Int
a -> ListNotificationsResponse
s {$sel:httpStatus:ListNotificationsResponse' :: Int
httpStatus = Int
a} :: ListNotificationsResponse)

instance Prelude.NFData ListNotificationsResponse where
  rnf :: ListNotificationsResponse -> ()
rnf ListNotificationsResponse' {Int
Maybe [NotificationSummary]
Maybe Text
httpStatus :: Int
notificationSummaries :: Maybe [NotificationSummary]
nextToken :: Maybe Text
$sel:httpStatus:ListNotificationsResponse' :: ListNotificationsResponse -> Int
$sel:notificationSummaries:ListNotificationsResponse' :: ListNotificationsResponse -> Maybe [NotificationSummary]
$sel:nextToken:ListNotificationsResponse' :: ListNotificationsResponse -> 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 [NotificationSummary]
notificationSummaries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus