{-# 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.IotTwinMaker.ListSyncResources
-- 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 sync resources.
module Amazonka.IotTwinMaker.ListSyncResources
  ( -- * Creating a Request
    ListSyncResources (..),
    newListSyncResources,

    -- * Request Lenses
    listSyncResources_filters,
    listSyncResources_maxResults,
    listSyncResources_nextToken,
    listSyncResources_workspaceId,
    listSyncResources_syncSource,

    -- * Destructuring the Response
    ListSyncResourcesResponse (..),
    newListSyncResourcesResponse,

    -- * Response Lenses
    listSyncResourcesResponse_nextToken,
    listSyncResourcesResponse_syncResources,
    listSyncResourcesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListSyncResources' smart constructor.
data ListSyncResources = ListSyncResources'
  { -- | A list of objects that filter the request.
    ListSyncResources -> Maybe [SyncResourceFilter]
filters :: Prelude.Maybe [SyncResourceFilter],
    -- | The maximum number of results to return at one time. The default is 50.
    --
    -- Valid Range: Minimum value of 0. Maximum value of 200.
    ListSyncResources -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The string that specifies the next page of results.
    ListSyncResources -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the workspace that contains the sync job.
    ListSyncResources -> Text
workspaceId :: Prelude.Text,
    -- | The sync soucre.
    --
    -- Currently the only supported syncSoucre is @SITEWISE @.
    ListSyncResources -> Text
syncSource :: Prelude.Text
  }
  deriving (ListSyncResources -> ListSyncResources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSyncResources -> ListSyncResources -> Bool
$c/= :: ListSyncResources -> ListSyncResources -> Bool
== :: ListSyncResources -> ListSyncResources -> Bool
$c== :: ListSyncResources -> ListSyncResources -> Bool
Prelude.Eq, ReadPrec [ListSyncResources]
ReadPrec ListSyncResources
Int -> ReadS ListSyncResources
ReadS [ListSyncResources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSyncResources]
$creadListPrec :: ReadPrec [ListSyncResources]
readPrec :: ReadPrec ListSyncResources
$creadPrec :: ReadPrec ListSyncResources
readList :: ReadS [ListSyncResources]
$creadList :: ReadS [ListSyncResources]
readsPrec :: Int -> ReadS ListSyncResources
$creadsPrec :: Int -> ReadS ListSyncResources
Prelude.Read, Int -> ListSyncResources -> ShowS
[ListSyncResources] -> ShowS
ListSyncResources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSyncResources] -> ShowS
$cshowList :: [ListSyncResources] -> ShowS
show :: ListSyncResources -> String
$cshow :: ListSyncResources -> String
showsPrec :: Int -> ListSyncResources -> ShowS
$cshowsPrec :: Int -> ListSyncResources -> ShowS
Prelude.Show, forall x. Rep ListSyncResources x -> ListSyncResources
forall x. ListSyncResources -> Rep ListSyncResources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListSyncResources x -> ListSyncResources
$cfrom :: forall x. ListSyncResources -> Rep ListSyncResources x
Prelude.Generic)

-- |
-- Create a value of 'ListSyncResources' 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:
--
-- 'filters', 'listSyncResources_filters' - A list of objects that filter the request.
--
-- 'maxResults', 'listSyncResources_maxResults' - The maximum number of results to return at one time. The default is 50.
--
-- Valid Range: Minimum value of 0. Maximum value of 200.
--
-- 'nextToken', 'listSyncResources_nextToken' - The string that specifies the next page of results.
--
-- 'workspaceId', 'listSyncResources_workspaceId' - The ID of the workspace that contains the sync job.
--
-- 'syncSource', 'listSyncResources_syncSource' - The sync soucre.
--
-- Currently the only supported syncSoucre is @SITEWISE @.
newListSyncResources ::
  -- | 'workspaceId'
  Prelude.Text ->
  -- | 'syncSource'
  Prelude.Text ->
  ListSyncResources
newListSyncResources :: Text -> Text -> ListSyncResources
newListSyncResources Text
pWorkspaceId_ Text
pSyncSource_ =
  ListSyncResources'
    { $sel:filters:ListSyncResources' :: Maybe [SyncResourceFilter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListSyncResources' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListSyncResources' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceId:ListSyncResources' :: Text
workspaceId = Text
pWorkspaceId_,
      $sel:syncSource:ListSyncResources' :: Text
syncSource = Text
pSyncSource_
    }

-- | A list of objects that filter the request.
listSyncResources_filters :: Lens.Lens' ListSyncResources (Prelude.Maybe [SyncResourceFilter])
listSyncResources_filters :: Lens' ListSyncResources (Maybe [SyncResourceFilter])
listSyncResources_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSyncResources' {Maybe [SyncResourceFilter]
filters :: Maybe [SyncResourceFilter]
$sel:filters:ListSyncResources' :: ListSyncResources -> Maybe [SyncResourceFilter]
filters} -> Maybe [SyncResourceFilter]
filters) (\s :: ListSyncResources
s@ListSyncResources' {} Maybe [SyncResourceFilter]
a -> ListSyncResources
s {$sel:filters:ListSyncResources' :: Maybe [SyncResourceFilter]
filters = Maybe [SyncResourceFilter]
a} :: ListSyncResources) 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 maximum number of results to return at one time. The default is 50.
--
-- Valid Range: Minimum value of 0. Maximum value of 200.
listSyncResources_maxResults :: Lens.Lens' ListSyncResources (Prelude.Maybe Prelude.Natural)
listSyncResources_maxResults :: Lens' ListSyncResources (Maybe Natural)
listSyncResources_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSyncResources' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListSyncResources' :: ListSyncResources -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListSyncResources
s@ListSyncResources' {} Maybe Natural
a -> ListSyncResources
s {$sel:maxResults:ListSyncResources' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListSyncResources)

-- | The string that specifies the next page of results.
listSyncResources_nextToken :: Lens.Lens' ListSyncResources (Prelude.Maybe Prelude.Text)
listSyncResources_nextToken :: Lens' ListSyncResources (Maybe Text)
listSyncResources_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSyncResources' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSyncResources' :: ListSyncResources -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSyncResources
s@ListSyncResources' {} Maybe Text
a -> ListSyncResources
s {$sel:nextToken:ListSyncResources' :: Maybe Text
nextToken = Maybe Text
a} :: ListSyncResources)

-- | The ID of the workspace that contains the sync job.
listSyncResources_workspaceId :: Lens.Lens' ListSyncResources Prelude.Text
listSyncResources_workspaceId :: Lens' ListSyncResources Text
listSyncResources_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSyncResources' {Text
workspaceId :: Text
$sel:workspaceId:ListSyncResources' :: ListSyncResources -> Text
workspaceId} -> Text
workspaceId) (\s :: ListSyncResources
s@ListSyncResources' {} Text
a -> ListSyncResources
s {$sel:workspaceId:ListSyncResources' :: Text
workspaceId = Text
a} :: ListSyncResources)

-- | The sync soucre.
--
-- Currently the only supported syncSoucre is @SITEWISE @.
listSyncResources_syncSource :: Lens.Lens' ListSyncResources Prelude.Text
listSyncResources_syncSource :: Lens' ListSyncResources Text
listSyncResources_syncSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSyncResources' {Text
syncSource :: Text
$sel:syncSource:ListSyncResources' :: ListSyncResources -> Text
syncSource} -> Text
syncSource) (\s :: ListSyncResources
s@ListSyncResources' {} Text
a -> ListSyncResources
s {$sel:syncSource:ListSyncResources' :: Text
syncSource = Text
a} :: ListSyncResources)

instance Core.AWSRequest ListSyncResources where
  type
    AWSResponse ListSyncResources =
      ListSyncResourcesResponse
  request :: (Service -> Service)
-> ListSyncResources -> Request ListSyncResources
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 ListSyncResources
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListSyncResources)))
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 [SyncResourceSummary] -> Int -> ListSyncResourcesResponse
ListSyncResourcesResponse'
            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
"syncResources" 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 ListSyncResources where
  hashWithSalt :: Int -> ListSyncResources -> Int
hashWithSalt Int
_salt ListSyncResources' {Maybe Natural
Maybe [SyncResourceFilter]
Maybe Text
Text
syncSource :: Text
workspaceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [SyncResourceFilter]
$sel:syncSource:ListSyncResources' :: ListSyncResources -> Text
$sel:workspaceId:ListSyncResources' :: ListSyncResources -> Text
$sel:nextToken:ListSyncResources' :: ListSyncResources -> Maybe Text
$sel:maxResults:ListSyncResources' :: ListSyncResources -> Maybe Natural
$sel:filters:ListSyncResources' :: ListSyncResources -> Maybe [SyncResourceFilter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SyncResourceFilter]
filters
      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` Text
workspaceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
syncSource

instance Prelude.NFData ListSyncResources where
  rnf :: ListSyncResources -> ()
rnf ListSyncResources' {Maybe Natural
Maybe [SyncResourceFilter]
Maybe Text
Text
syncSource :: Text
workspaceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [SyncResourceFilter]
$sel:syncSource:ListSyncResources' :: ListSyncResources -> Text
$sel:workspaceId:ListSyncResources' :: ListSyncResources -> Text
$sel:nextToken:ListSyncResources' :: ListSyncResources -> Maybe Text
$sel:maxResults:ListSyncResources' :: ListSyncResources -> Maybe Natural
$sel:filters:ListSyncResources' :: ListSyncResources -> Maybe [SyncResourceFilter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [SyncResourceFilter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
workspaceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
syncSource

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

instance Data.ToPath ListSyncResources where
  toPath :: ListSyncResources -> ByteString
toPath ListSyncResources' {Maybe Natural
Maybe [SyncResourceFilter]
Maybe Text
Text
syncSource :: Text
workspaceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [SyncResourceFilter]
$sel:syncSource:ListSyncResources' :: ListSyncResources -> Text
$sel:workspaceId:ListSyncResources' :: ListSyncResources -> Text
$sel:nextToken:ListSyncResources' :: ListSyncResources -> Maybe Text
$sel:maxResults:ListSyncResources' :: ListSyncResources -> Maybe Natural
$sel:filters:ListSyncResources' :: ListSyncResources -> Maybe [SyncResourceFilter]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/workspaces/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
workspaceId,
        ByteString
"/sync-jobs/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
syncSource,
        ByteString
"/resources-list"
      ]

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

-- | /See:/ 'newListSyncResourcesResponse' smart constructor.
data ListSyncResourcesResponse = ListSyncResourcesResponse'
  { -- | The string that specifies the next page of results.
    ListSyncResourcesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The sync resources.
    ListSyncResourcesResponse -> Maybe [SyncResourceSummary]
syncResources :: Prelude.Maybe [SyncResourceSummary],
    -- | The response's http status code.
    ListSyncResourcesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListSyncResourcesResponse -> ListSyncResourcesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSyncResourcesResponse -> ListSyncResourcesResponse -> Bool
$c/= :: ListSyncResourcesResponse -> ListSyncResourcesResponse -> Bool
== :: ListSyncResourcesResponse -> ListSyncResourcesResponse -> Bool
$c== :: ListSyncResourcesResponse -> ListSyncResourcesResponse -> Bool
Prelude.Eq, ReadPrec [ListSyncResourcesResponse]
ReadPrec ListSyncResourcesResponse
Int -> ReadS ListSyncResourcesResponse
ReadS [ListSyncResourcesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSyncResourcesResponse]
$creadListPrec :: ReadPrec [ListSyncResourcesResponse]
readPrec :: ReadPrec ListSyncResourcesResponse
$creadPrec :: ReadPrec ListSyncResourcesResponse
readList :: ReadS [ListSyncResourcesResponse]
$creadList :: ReadS [ListSyncResourcesResponse]
readsPrec :: Int -> ReadS ListSyncResourcesResponse
$creadsPrec :: Int -> ReadS ListSyncResourcesResponse
Prelude.Read, Int -> ListSyncResourcesResponse -> ShowS
[ListSyncResourcesResponse] -> ShowS
ListSyncResourcesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSyncResourcesResponse] -> ShowS
$cshowList :: [ListSyncResourcesResponse] -> ShowS
show :: ListSyncResourcesResponse -> String
$cshow :: ListSyncResourcesResponse -> String
showsPrec :: Int -> ListSyncResourcesResponse -> ShowS
$cshowsPrec :: Int -> ListSyncResourcesResponse -> ShowS
Prelude.Show, forall x.
Rep ListSyncResourcesResponse x -> ListSyncResourcesResponse
forall x.
ListSyncResourcesResponse -> Rep ListSyncResourcesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListSyncResourcesResponse x -> ListSyncResourcesResponse
$cfrom :: forall x.
ListSyncResourcesResponse -> Rep ListSyncResourcesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListSyncResourcesResponse' 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', 'listSyncResourcesResponse_nextToken' - The string that specifies the next page of results.
--
-- 'syncResources', 'listSyncResourcesResponse_syncResources' - The sync resources.
--
-- 'httpStatus', 'listSyncResourcesResponse_httpStatus' - The response's http status code.
newListSyncResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListSyncResourcesResponse
newListSyncResourcesResponse :: Int -> ListSyncResourcesResponse
newListSyncResourcesResponse Int
pHttpStatus_ =
  ListSyncResourcesResponse'
    { $sel:nextToken:ListSyncResourcesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:syncResources:ListSyncResourcesResponse' :: Maybe [SyncResourceSummary]
syncResources = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListSyncResourcesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The string that specifies the next page of results.
listSyncResourcesResponse_nextToken :: Lens.Lens' ListSyncResourcesResponse (Prelude.Maybe Prelude.Text)
listSyncResourcesResponse_nextToken :: Lens' ListSyncResourcesResponse (Maybe Text)
listSyncResourcesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSyncResourcesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSyncResourcesResponse' :: ListSyncResourcesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSyncResourcesResponse
s@ListSyncResourcesResponse' {} Maybe Text
a -> ListSyncResourcesResponse
s {$sel:nextToken:ListSyncResourcesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListSyncResourcesResponse)

-- | The sync resources.
listSyncResourcesResponse_syncResources :: Lens.Lens' ListSyncResourcesResponse (Prelude.Maybe [SyncResourceSummary])
listSyncResourcesResponse_syncResources :: Lens' ListSyncResourcesResponse (Maybe [SyncResourceSummary])
listSyncResourcesResponse_syncResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSyncResourcesResponse' {Maybe [SyncResourceSummary]
syncResources :: Maybe [SyncResourceSummary]
$sel:syncResources:ListSyncResourcesResponse' :: ListSyncResourcesResponse -> Maybe [SyncResourceSummary]
syncResources} -> Maybe [SyncResourceSummary]
syncResources) (\s :: ListSyncResourcesResponse
s@ListSyncResourcesResponse' {} Maybe [SyncResourceSummary]
a -> ListSyncResourcesResponse
s {$sel:syncResources:ListSyncResourcesResponse' :: Maybe [SyncResourceSummary]
syncResources = Maybe [SyncResourceSummary]
a} :: ListSyncResourcesResponse) 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.
listSyncResourcesResponse_httpStatus :: Lens.Lens' ListSyncResourcesResponse Prelude.Int
listSyncResourcesResponse_httpStatus :: Lens' ListSyncResourcesResponse Int
listSyncResourcesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSyncResourcesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListSyncResourcesResponse' :: ListSyncResourcesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListSyncResourcesResponse
s@ListSyncResourcesResponse' {} Int
a -> ListSyncResourcesResponse
s {$sel:httpStatus:ListSyncResourcesResponse' :: Int
httpStatus = Int
a} :: ListSyncResourcesResponse)

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