{-# 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.SSM.ListResourceDataSync
-- 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 resource data sync configurations. Includes information about
-- the last time a sync attempted to start, the last sync status, and the
-- last time a sync successfully completed.
--
-- The number of sync configurations might be too large to return using a
-- single call to @ListResourceDataSync@. You can limit the number of sync
-- configurations returned by using the @MaxResults@ parameter. To
-- determine whether there are more sync configurations to list, check the
-- value of @NextToken@ in the output. If there are more sync
-- configurations to list, you can request them by specifying the
-- @NextToken@ returned in the call to the parameter of a subsequent call.
--
-- This operation returns paginated results.
module Amazonka.SSM.ListResourceDataSync
  ( -- * Creating a Request
    ListResourceDataSync (..),
    newListResourceDataSync,

    -- * Request Lenses
    listResourceDataSync_maxResults,
    listResourceDataSync_nextToken,
    listResourceDataSync_syncType,

    -- * Destructuring the Response
    ListResourceDataSyncResponse (..),
    newListResourceDataSyncResponse,

    -- * Response Lenses
    listResourceDataSyncResponse_nextToken,
    listResourceDataSyncResponse_resourceDataSyncItems,
    listResourceDataSyncResponse_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.SSM.Types

-- | /See:/ 'newListResourceDataSync' smart constructor.
data ListResourceDataSync = ListResourceDataSync'
  { -- | The maximum number of items to return for this call. The call also
    -- returns a token that you can specify in a subsequent call to get the
    -- next set of results.
    ListResourceDataSync -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token to start the list. Use this token to get the next set of
    -- results.
    ListResourceDataSync -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | View a list of resource data syncs according to the sync type. Specify
    -- @SyncToDestination@ to view resource data syncs that synchronize data to
    -- an Amazon S3 bucket. Specify @SyncFromSource@ to view resource data
    -- syncs from Organizations or from multiple Amazon Web Services Regions.
    ListResourceDataSync -> Maybe Text
syncType :: Prelude.Maybe Prelude.Text
  }
  deriving (ListResourceDataSync -> ListResourceDataSync -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourceDataSync -> ListResourceDataSync -> Bool
$c/= :: ListResourceDataSync -> ListResourceDataSync -> Bool
== :: ListResourceDataSync -> ListResourceDataSync -> Bool
$c== :: ListResourceDataSync -> ListResourceDataSync -> Bool
Prelude.Eq, ReadPrec [ListResourceDataSync]
ReadPrec ListResourceDataSync
Int -> ReadS ListResourceDataSync
ReadS [ListResourceDataSync]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourceDataSync]
$creadListPrec :: ReadPrec [ListResourceDataSync]
readPrec :: ReadPrec ListResourceDataSync
$creadPrec :: ReadPrec ListResourceDataSync
readList :: ReadS [ListResourceDataSync]
$creadList :: ReadS [ListResourceDataSync]
readsPrec :: Int -> ReadS ListResourceDataSync
$creadsPrec :: Int -> ReadS ListResourceDataSync
Prelude.Read, Int -> ListResourceDataSync -> ShowS
[ListResourceDataSync] -> ShowS
ListResourceDataSync -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourceDataSync] -> ShowS
$cshowList :: [ListResourceDataSync] -> ShowS
show :: ListResourceDataSync -> String
$cshow :: ListResourceDataSync -> String
showsPrec :: Int -> ListResourceDataSync -> ShowS
$cshowsPrec :: Int -> ListResourceDataSync -> ShowS
Prelude.Show, forall x. Rep ListResourceDataSync x -> ListResourceDataSync
forall x. ListResourceDataSync -> Rep ListResourceDataSync x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListResourceDataSync x -> ListResourceDataSync
$cfrom :: forall x. ListResourceDataSync -> Rep ListResourceDataSync x
Prelude.Generic)

-- |
-- Create a value of 'ListResourceDataSync' 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', 'listResourceDataSync_maxResults' - The maximum number of items to return for this call. The call also
-- returns a token that you can specify in a subsequent call to get the
-- next set of results.
--
-- 'nextToken', 'listResourceDataSync_nextToken' - A token to start the list. Use this token to get the next set of
-- results.
--
-- 'syncType', 'listResourceDataSync_syncType' - View a list of resource data syncs according to the sync type. Specify
-- @SyncToDestination@ to view resource data syncs that synchronize data to
-- an Amazon S3 bucket. Specify @SyncFromSource@ to view resource data
-- syncs from Organizations or from multiple Amazon Web Services Regions.
newListResourceDataSync ::
  ListResourceDataSync
newListResourceDataSync :: ListResourceDataSync
newListResourceDataSync =
  ListResourceDataSync'
    { $sel:maxResults:ListResourceDataSync' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListResourceDataSync' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:syncType:ListResourceDataSync' :: Maybe Text
syncType = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of items to return for this call. The call also
-- returns a token that you can specify in a subsequent call to get the
-- next set of results.
listResourceDataSync_maxResults :: Lens.Lens' ListResourceDataSync (Prelude.Maybe Prelude.Natural)
listResourceDataSync_maxResults :: Lens' ListResourceDataSync (Maybe Natural)
listResourceDataSync_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceDataSync' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListResourceDataSync' :: ListResourceDataSync -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListResourceDataSync
s@ListResourceDataSync' {} Maybe Natural
a -> ListResourceDataSync
s {$sel:maxResults:ListResourceDataSync' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListResourceDataSync)

-- | A token to start the list. Use this token to get the next set of
-- results.
listResourceDataSync_nextToken :: Lens.Lens' ListResourceDataSync (Prelude.Maybe Prelude.Text)
listResourceDataSync_nextToken :: Lens' ListResourceDataSync (Maybe Text)
listResourceDataSync_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceDataSync' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListResourceDataSync' :: ListResourceDataSync -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListResourceDataSync
s@ListResourceDataSync' {} Maybe Text
a -> ListResourceDataSync
s {$sel:nextToken:ListResourceDataSync' :: Maybe Text
nextToken = Maybe Text
a} :: ListResourceDataSync)

-- | View a list of resource data syncs according to the sync type. Specify
-- @SyncToDestination@ to view resource data syncs that synchronize data to
-- an Amazon S3 bucket. Specify @SyncFromSource@ to view resource data
-- syncs from Organizations or from multiple Amazon Web Services Regions.
listResourceDataSync_syncType :: Lens.Lens' ListResourceDataSync (Prelude.Maybe Prelude.Text)
listResourceDataSync_syncType :: Lens' ListResourceDataSync (Maybe Text)
listResourceDataSync_syncType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceDataSync' {Maybe Text
syncType :: Maybe Text
$sel:syncType:ListResourceDataSync' :: ListResourceDataSync -> Maybe Text
syncType} -> Maybe Text
syncType) (\s :: ListResourceDataSync
s@ListResourceDataSync' {} Maybe Text
a -> ListResourceDataSync
s {$sel:syncType:ListResourceDataSync' :: Maybe Text
syncType = Maybe Text
a} :: ListResourceDataSync)

instance Core.AWSPager ListResourceDataSync where
  page :: ListResourceDataSync
-> AWSResponse ListResourceDataSync -> Maybe ListResourceDataSync
page ListResourceDataSync
rq AWSResponse ListResourceDataSync
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListResourceDataSync
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourceDataSyncResponse (Maybe Text)
listResourceDataSyncResponse_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 ListResourceDataSync
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourceDataSyncResponse (Maybe [ResourceDataSyncItem])
listResourceDataSyncResponse_resourceDataSyncItems
            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.$ ListResourceDataSync
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListResourceDataSync (Maybe Text)
listResourceDataSync_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListResourceDataSync
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourceDataSyncResponse (Maybe Text)
listResourceDataSyncResponse_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 ListResourceDataSync where
  type
    AWSResponse ListResourceDataSync =
      ListResourceDataSyncResponse
  request :: (Service -> Service)
-> ListResourceDataSync -> Request ListResourceDataSync
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 ListResourceDataSync
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListResourceDataSync)))
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 [ResourceDataSyncItem]
-> Int
-> ListResourceDataSyncResponse
ListResourceDataSyncResponse'
            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
"ResourceDataSyncItems"
                            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 ListResourceDataSync where
  hashWithSalt :: Int -> ListResourceDataSync -> Int
hashWithSalt Int
_salt ListResourceDataSync' {Maybe Natural
Maybe Text
syncType :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:syncType:ListResourceDataSync' :: ListResourceDataSync -> Maybe Text
$sel:nextToken:ListResourceDataSync' :: ListResourceDataSync -> Maybe Text
$sel:maxResults:ListResourceDataSync' :: ListResourceDataSync -> 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
syncType

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

instance Data.ToHeaders ListResourceDataSync where
  toHeaders :: ListResourceDataSync -> 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
"AmazonSSM.ListResourceDataSync" ::
                          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 ListResourceDataSync where
  toJSON :: ListResourceDataSync -> Value
toJSON ListResourceDataSync' {Maybe Natural
Maybe Text
syncType :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:syncType:ListResourceDataSync' :: ListResourceDataSync -> Maybe Text
$sel:nextToken:ListResourceDataSync' :: ListResourceDataSync -> Maybe Text
$sel:maxResults:ListResourceDataSync' :: ListResourceDataSync -> 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
"SyncType" 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
syncType
          ]
      )

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

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

-- | /See:/ 'newListResourceDataSyncResponse' smart constructor.
data ListResourceDataSyncResponse = ListResourceDataSyncResponse'
  { -- | The token for the next set of items to return. Use this token to get the
    -- next set of results.
    ListResourceDataSyncResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of your current resource data sync configurations and their
    -- statuses.
    ListResourceDataSyncResponse -> Maybe [ResourceDataSyncItem]
resourceDataSyncItems :: Prelude.Maybe [ResourceDataSyncItem],
    -- | The response's http status code.
    ListResourceDataSyncResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListResourceDataSyncResponse
-> ListResourceDataSyncResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourceDataSyncResponse
-> ListResourceDataSyncResponse -> Bool
$c/= :: ListResourceDataSyncResponse
-> ListResourceDataSyncResponse -> Bool
== :: ListResourceDataSyncResponse
-> ListResourceDataSyncResponse -> Bool
$c== :: ListResourceDataSyncResponse
-> ListResourceDataSyncResponse -> Bool
Prelude.Eq, ReadPrec [ListResourceDataSyncResponse]
ReadPrec ListResourceDataSyncResponse
Int -> ReadS ListResourceDataSyncResponse
ReadS [ListResourceDataSyncResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourceDataSyncResponse]
$creadListPrec :: ReadPrec [ListResourceDataSyncResponse]
readPrec :: ReadPrec ListResourceDataSyncResponse
$creadPrec :: ReadPrec ListResourceDataSyncResponse
readList :: ReadS [ListResourceDataSyncResponse]
$creadList :: ReadS [ListResourceDataSyncResponse]
readsPrec :: Int -> ReadS ListResourceDataSyncResponse
$creadsPrec :: Int -> ReadS ListResourceDataSyncResponse
Prelude.Read, Int -> ListResourceDataSyncResponse -> ShowS
[ListResourceDataSyncResponse] -> ShowS
ListResourceDataSyncResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourceDataSyncResponse] -> ShowS
$cshowList :: [ListResourceDataSyncResponse] -> ShowS
show :: ListResourceDataSyncResponse -> String
$cshow :: ListResourceDataSyncResponse -> String
showsPrec :: Int -> ListResourceDataSyncResponse -> ShowS
$cshowsPrec :: Int -> ListResourceDataSyncResponse -> ShowS
Prelude.Show, forall x.
Rep ListResourceDataSyncResponse x -> ListResourceDataSyncResponse
forall x.
ListResourceDataSyncResponse -> Rep ListResourceDataSyncResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListResourceDataSyncResponse x -> ListResourceDataSyncResponse
$cfrom :: forall x.
ListResourceDataSyncResponse -> Rep ListResourceDataSyncResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListResourceDataSyncResponse' 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', 'listResourceDataSyncResponse_nextToken' - The token for the next set of items to return. Use this token to get the
-- next set of results.
--
-- 'resourceDataSyncItems', 'listResourceDataSyncResponse_resourceDataSyncItems' - A list of your current resource data sync configurations and their
-- statuses.
--
-- 'httpStatus', 'listResourceDataSyncResponse_httpStatus' - The response's http status code.
newListResourceDataSyncResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListResourceDataSyncResponse
newListResourceDataSyncResponse :: Int -> ListResourceDataSyncResponse
newListResourceDataSyncResponse Int
pHttpStatus_ =
  ListResourceDataSyncResponse'
    { $sel:nextToken:ListResourceDataSyncResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceDataSyncItems:ListResourceDataSyncResponse' :: Maybe [ResourceDataSyncItem]
resourceDataSyncItems = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListResourceDataSyncResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | A list of your current resource data sync configurations and their
-- statuses.
listResourceDataSyncResponse_resourceDataSyncItems :: Lens.Lens' ListResourceDataSyncResponse (Prelude.Maybe [ResourceDataSyncItem])
listResourceDataSyncResponse_resourceDataSyncItems :: Lens' ListResourceDataSyncResponse (Maybe [ResourceDataSyncItem])
listResourceDataSyncResponse_resourceDataSyncItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceDataSyncResponse' {Maybe [ResourceDataSyncItem]
resourceDataSyncItems :: Maybe [ResourceDataSyncItem]
$sel:resourceDataSyncItems:ListResourceDataSyncResponse' :: ListResourceDataSyncResponse -> Maybe [ResourceDataSyncItem]
resourceDataSyncItems} -> Maybe [ResourceDataSyncItem]
resourceDataSyncItems) (\s :: ListResourceDataSyncResponse
s@ListResourceDataSyncResponse' {} Maybe [ResourceDataSyncItem]
a -> ListResourceDataSyncResponse
s {$sel:resourceDataSyncItems:ListResourceDataSyncResponse' :: Maybe [ResourceDataSyncItem]
resourceDataSyncItems = Maybe [ResourceDataSyncItem]
a} :: ListResourceDataSyncResponse) 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.
listResourceDataSyncResponse_httpStatus :: Lens.Lens' ListResourceDataSyncResponse Prelude.Int
listResourceDataSyncResponse_httpStatus :: Lens' ListResourceDataSyncResponse Int
listResourceDataSyncResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceDataSyncResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListResourceDataSyncResponse' :: ListResourceDataSyncResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListResourceDataSyncResponse
s@ListResourceDataSyncResponse' {} Int
a -> ListResourceDataSyncResponse
s {$sel:httpStatus:ListResourceDataSyncResponse' :: Int
httpStatus = Int
a} :: ListResourceDataSyncResponse)

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