{-# 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.DirectoryService.ListLogSubscriptions
-- 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 the active log subscriptions for the Amazon Web Services account.
--
-- This operation returns paginated results.
module Amazonka.DirectoryService.ListLogSubscriptions
  ( -- * Creating a Request
    ListLogSubscriptions (..),
    newListLogSubscriptions,

    -- * Request Lenses
    listLogSubscriptions_directoryId,
    listLogSubscriptions_limit,
    listLogSubscriptions_nextToken,

    -- * Destructuring the Response
    ListLogSubscriptionsResponse (..),
    newListLogSubscriptionsResponse,

    -- * Response Lenses
    listLogSubscriptionsResponse_logSubscriptions,
    listLogSubscriptionsResponse_nextToken,
    listLogSubscriptionsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListLogSubscriptions' smart constructor.
data ListLogSubscriptions = ListLogSubscriptions'
  { -- | If a /DirectoryID/ is provided, lists only the log subscription
    -- associated with that directory. If no /DirectoryId/ is provided, lists
    -- all log subscriptions associated with your Amazon Web Services account.
    -- If there are no log subscriptions for the Amazon Web Services account or
    -- the directory, an empty list will be returned.
    ListLogSubscriptions -> Maybe Text
directoryId :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of items returned.
    ListLogSubscriptions -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next set of items to return.
    ListLogSubscriptions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListLogSubscriptions -> ListLogSubscriptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLogSubscriptions -> ListLogSubscriptions -> Bool
$c/= :: ListLogSubscriptions -> ListLogSubscriptions -> Bool
== :: ListLogSubscriptions -> ListLogSubscriptions -> Bool
$c== :: ListLogSubscriptions -> ListLogSubscriptions -> Bool
Prelude.Eq, ReadPrec [ListLogSubscriptions]
ReadPrec ListLogSubscriptions
Int -> ReadS ListLogSubscriptions
ReadS [ListLogSubscriptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLogSubscriptions]
$creadListPrec :: ReadPrec [ListLogSubscriptions]
readPrec :: ReadPrec ListLogSubscriptions
$creadPrec :: ReadPrec ListLogSubscriptions
readList :: ReadS [ListLogSubscriptions]
$creadList :: ReadS [ListLogSubscriptions]
readsPrec :: Int -> ReadS ListLogSubscriptions
$creadsPrec :: Int -> ReadS ListLogSubscriptions
Prelude.Read, Int -> ListLogSubscriptions -> ShowS
[ListLogSubscriptions] -> ShowS
ListLogSubscriptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLogSubscriptions] -> ShowS
$cshowList :: [ListLogSubscriptions] -> ShowS
show :: ListLogSubscriptions -> String
$cshow :: ListLogSubscriptions -> String
showsPrec :: Int -> ListLogSubscriptions -> ShowS
$cshowsPrec :: Int -> ListLogSubscriptions -> ShowS
Prelude.Show, forall x. Rep ListLogSubscriptions x -> ListLogSubscriptions
forall x. ListLogSubscriptions -> Rep ListLogSubscriptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLogSubscriptions x -> ListLogSubscriptions
$cfrom :: forall x. ListLogSubscriptions -> Rep ListLogSubscriptions x
Prelude.Generic)

-- |
-- Create a value of 'ListLogSubscriptions' 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:
--
-- 'directoryId', 'listLogSubscriptions_directoryId' - If a /DirectoryID/ is provided, lists only the log subscription
-- associated with that directory. If no /DirectoryId/ is provided, lists
-- all log subscriptions associated with your Amazon Web Services account.
-- If there are no log subscriptions for the Amazon Web Services account or
-- the directory, an empty list will be returned.
--
-- 'limit', 'listLogSubscriptions_limit' - The maximum number of items returned.
--
-- 'nextToken', 'listLogSubscriptions_nextToken' - The token for the next set of items to return.
newListLogSubscriptions ::
  ListLogSubscriptions
newListLogSubscriptions :: ListLogSubscriptions
newListLogSubscriptions =
  ListLogSubscriptions'
    { $sel:directoryId:ListLogSubscriptions' :: Maybe Text
directoryId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ListLogSubscriptions' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListLogSubscriptions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | If a /DirectoryID/ is provided, lists only the log subscription
-- associated with that directory. If no /DirectoryId/ is provided, lists
-- all log subscriptions associated with your Amazon Web Services account.
-- If there are no log subscriptions for the Amazon Web Services account or
-- the directory, an empty list will be returned.
listLogSubscriptions_directoryId :: Lens.Lens' ListLogSubscriptions (Prelude.Maybe Prelude.Text)
listLogSubscriptions_directoryId :: Lens' ListLogSubscriptions (Maybe Text)
listLogSubscriptions_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLogSubscriptions' {Maybe Text
directoryId :: Maybe Text
$sel:directoryId:ListLogSubscriptions' :: ListLogSubscriptions -> Maybe Text
directoryId} -> Maybe Text
directoryId) (\s :: ListLogSubscriptions
s@ListLogSubscriptions' {} Maybe Text
a -> ListLogSubscriptions
s {$sel:directoryId:ListLogSubscriptions' :: Maybe Text
directoryId = Maybe Text
a} :: ListLogSubscriptions)

-- | The maximum number of items returned.
listLogSubscriptions_limit :: Lens.Lens' ListLogSubscriptions (Prelude.Maybe Prelude.Natural)
listLogSubscriptions_limit :: Lens' ListLogSubscriptions (Maybe Natural)
listLogSubscriptions_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLogSubscriptions' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListLogSubscriptions' :: ListLogSubscriptions -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListLogSubscriptions
s@ListLogSubscriptions' {} Maybe Natural
a -> ListLogSubscriptions
s {$sel:limit:ListLogSubscriptions' :: Maybe Natural
limit = Maybe Natural
a} :: ListLogSubscriptions)

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

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

instance Prelude.NFData ListLogSubscriptions where
  rnf :: ListLogSubscriptions -> ()
rnf ListLogSubscriptions' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
limit :: Maybe Natural
directoryId :: Maybe Text
$sel:nextToken:ListLogSubscriptions' :: ListLogSubscriptions -> Maybe Text
$sel:limit:ListLogSubscriptions' :: ListLogSubscriptions -> Maybe Natural
$sel:directoryId:ListLogSubscriptions' :: ListLogSubscriptions -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
directoryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

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

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

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

-- | /See:/ 'newListLogSubscriptionsResponse' smart constructor.
data ListLogSubscriptionsResponse = ListLogSubscriptionsResponse'
  { -- | A list of active LogSubscription objects for calling the Amazon Web
    -- Services account.
    ListLogSubscriptionsResponse -> Maybe [LogSubscription]
logSubscriptions :: Prelude.Maybe [LogSubscription],
    -- | The token for the next set of items to return.
    ListLogSubscriptionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListLogSubscriptionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListLogSubscriptionsResponse
-> ListLogSubscriptionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLogSubscriptionsResponse
-> ListLogSubscriptionsResponse -> Bool
$c/= :: ListLogSubscriptionsResponse
-> ListLogSubscriptionsResponse -> Bool
== :: ListLogSubscriptionsResponse
-> ListLogSubscriptionsResponse -> Bool
$c== :: ListLogSubscriptionsResponse
-> ListLogSubscriptionsResponse -> Bool
Prelude.Eq, ReadPrec [ListLogSubscriptionsResponse]
ReadPrec ListLogSubscriptionsResponse
Int -> ReadS ListLogSubscriptionsResponse
ReadS [ListLogSubscriptionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLogSubscriptionsResponse]
$creadListPrec :: ReadPrec [ListLogSubscriptionsResponse]
readPrec :: ReadPrec ListLogSubscriptionsResponse
$creadPrec :: ReadPrec ListLogSubscriptionsResponse
readList :: ReadS [ListLogSubscriptionsResponse]
$creadList :: ReadS [ListLogSubscriptionsResponse]
readsPrec :: Int -> ReadS ListLogSubscriptionsResponse
$creadsPrec :: Int -> ReadS ListLogSubscriptionsResponse
Prelude.Read, Int -> ListLogSubscriptionsResponse -> ShowS
[ListLogSubscriptionsResponse] -> ShowS
ListLogSubscriptionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLogSubscriptionsResponse] -> ShowS
$cshowList :: [ListLogSubscriptionsResponse] -> ShowS
show :: ListLogSubscriptionsResponse -> String
$cshow :: ListLogSubscriptionsResponse -> String
showsPrec :: Int -> ListLogSubscriptionsResponse -> ShowS
$cshowsPrec :: Int -> ListLogSubscriptionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListLogSubscriptionsResponse x -> ListLogSubscriptionsResponse
forall x.
ListLogSubscriptionsResponse -> Rep ListLogSubscriptionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListLogSubscriptionsResponse x -> ListLogSubscriptionsResponse
$cfrom :: forall x.
ListLogSubscriptionsResponse -> Rep ListLogSubscriptionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListLogSubscriptionsResponse' 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:
--
-- 'logSubscriptions', 'listLogSubscriptionsResponse_logSubscriptions' - A list of active LogSubscription objects for calling the Amazon Web
-- Services account.
--
-- 'nextToken', 'listLogSubscriptionsResponse_nextToken' - The token for the next set of items to return.
--
-- 'httpStatus', 'listLogSubscriptionsResponse_httpStatus' - The response's http status code.
newListLogSubscriptionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListLogSubscriptionsResponse
newListLogSubscriptionsResponse :: Int -> ListLogSubscriptionsResponse
newListLogSubscriptionsResponse Int
pHttpStatus_ =
  ListLogSubscriptionsResponse'
    { $sel:logSubscriptions:ListLogSubscriptionsResponse' :: Maybe [LogSubscription]
logSubscriptions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListLogSubscriptionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListLogSubscriptionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of active LogSubscription objects for calling the Amazon Web
-- Services account.
listLogSubscriptionsResponse_logSubscriptions :: Lens.Lens' ListLogSubscriptionsResponse (Prelude.Maybe [LogSubscription])
listLogSubscriptionsResponse_logSubscriptions :: Lens' ListLogSubscriptionsResponse (Maybe [LogSubscription])
listLogSubscriptionsResponse_logSubscriptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLogSubscriptionsResponse' {Maybe [LogSubscription]
logSubscriptions :: Maybe [LogSubscription]
$sel:logSubscriptions:ListLogSubscriptionsResponse' :: ListLogSubscriptionsResponse -> Maybe [LogSubscription]
logSubscriptions} -> Maybe [LogSubscription]
logSubscriptions) (\s :: ListLogSubscriptionsResponse
s@ListLogSubscriptionsResponse' {} Maybe [LogSubscription]
a -> ListLogSubscriptionsResponse
s {$sel:logSubscriptions:ListLogSubscriptionsResponse' :: Maybe [LogSubscription]
logSubscriptions = Maybe [LogSubscription]
a} :: ListLogSubscriptionsResponse) 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 token for the next set of items to return.
listLogSubscriptionsResponse_nextToken :: Lens.Lens' ListLogSubscriptionsResponse (Prelude.Maybe Prelude.Text)
listLogSubscriptionsResponse_nextToken :: Lens' ListLogSubscriptionsResponse (Maybe Text)
listLogSubscriptionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLogSubscriptionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListLogSubscriptionsResponse' :: ListLogSubscriptionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListLogSubscriptionsResponse
s@ListLogSubscriptionsResponse' {} Maybe Text
a -> ListLogSubscriptionsResponse
s {$sel:nextToken:ListLogSubscriptionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListLogSubscriptionsResponse)

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

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