{-# 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.Proton.ListRepositorySyncDefinitions
-- 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 repository sync definitions with detail data.
--
-- This operation returns paginated results.
module Amazonka.Proton.ListRepositorySyncDefinitions
  ( -- * Creating a Request
    ListRepositorySyncDefinitions (..),
    newListRepositorySyncDefinitions,

    -- * Request Lenses
    listRepositorySyncDefinitions_nextToken,
    listRepositorySyncDefinitions_repositoryName,
    listRepositorySyncDefinitions_repositoryProvider,
    listRepositorySyncDefinitions_syncType,

    -- * Destructuring the Response
    ListRepositorySyncDefinitionsResponse (..),
    newListRepositorySyncDefinitionsResponse,

    -- * Response Lenses
    listRepositorySyncDefinitionsResponse_nextToken,
    listRepositorySyncDefinitionsResponse_httpStatus,
    listRepositorySyncDefinitionsResponse_syncDefinitions,
  )
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 Amazonka.Proton.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListRepositorySyncDefinitions' smart constructor.
data ListRepositorySyncDefinitions = ListRepositorySyncDefinitions'
  { -- | A token that indicates the location of the next repository sync
    -- definition in the array of repository sync definitions, after the list
    -- of repository sync definitions previously requested.
    ListRepositorySyncDefinitions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The repository name.
    ListRepositorySyncDefinitions -> Text
repositoryName :: Prelude.Text,
    -- | The repository provider.
    ListRepositorySyncDefinitions -> RepositoryProvider
repositoryProvider :: RepositoryProvider,
    -- | The sync type. The only supported value is @TEMPLATE_SYNC@.
    ListRepositorySyncDefinitions -> SyncType
syncType :: SyncType
  }
  deriving (ListRepositorySyncDefinitions
-> ListRepositorySyncDefinitions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRepositorySyncDefinitions
-> ListRepositorySyncDefinitions -> Bool
$c/= :: ListRepositorySyncDefinitions
-> ListRepositorySyncDefinitions -> Bool
== :: ListRepositorySyncDefinitions
-> ListRepositorySyncDefinitions -> Bool
$c== :: ListRepositorySyncDefinitions
-> ListRepositorySyncDefinitions -> Bool
Prelude.Eq, ReadPrec [ListRepositorySyncDefinitions]
ReadPrec ListRepositorySyncDefinitions
Int -> ReadS ListRepositorySyncDefinitions
ReadS [ListRepositorySyncDefinitions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRepositorySyncDefinitions]
$creadListPrec :: ReadPrec [ListRepositorySyncDefinitions]
readPrec :: ReadPrec ListRepositorySyncDefinitions
$creadPrec :: ReadPrec ListRepositorySyncDefinitions
readList :: ReadS [ListRepositorySyncDefinitions]
$creadList :: ReadS [ListRepositorySyncDefinitions]
readsPrec :: Int -> ReadS ListRepositorySyncDefinitions
$creadsPrec :: Int -> ReadS ListRepositorySyncDefinitions
Prelude.Read, Int -> ListRepositorySyncDefinitions -> ShowS
[ListRepositorySyncDefinitions] -> ShowS
ListRepositorySyncDefinitions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRepositorySyncDefinitions] -> ShowS
$cshowList :: [ListRepositorySyncDefinitions] -> ShowS
show :: ListRepositorySyncDefinitions -> String
$cshow :: ListRepositorySyncDefinitions -> String
showsPrec :: Int -> ListRepositorySyncDefinitions -> ShowS
$cshowsPrec :: Int -> ListRepositorySyncDefinitions -> ShowS
Prelude.Show, forall x.
Rep ListRepositorySyncDefinitions x
-> ListRepositorySyncDefinitions
forall x.
ListRepositorySyncDefinitions
-> Rep ListRepositorySyncDefinitions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListRepositorySyncDefinitions x
-> ListRepositorySyncDefinitions
$cfrom :: forall x.
ListRepositorySyncDefinitions
-> Rep ListRepositorySyncDefinitions x
Prelude.Generic)

-- |
-- Create a value of 'ListRepositorySyncDefinitions' 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', 'listRepositorySyncDefinitions_nextToken' - A token that indicates the location of the next repository sync
-- definition in the array of repository sync definitions, after the list
-- of repository sync definitions previously requested.
--
-- 'repositoryName', 'listRepositorySyncDefinitions_repositoryName' - The repository name.
--
-- 'repositoryProvider', 'listRepositorySyncDefinitions_repositoryProvider' - The repository provider.
--
-- 'syncType', 'listRepositorySyncDefinitions_syncType' - The sync type. The only supported value is @TEMPLATE_SYNC@.
newListRepositorySyncDefinitions ::
  -- | 'repositoryName'
  Prelude.Text ->
  -- | 'repositoryProvider'
  RepositoryProvider ->
  -- | 'syncType'
  SyncType ->
  ListRepositorySyncDefinitions
newListRepositorySyncDefinitions :: Text
-> RepositoryProvider -> SyncType -> ListRepositorySyncDefinitions
newListRepositorySyncDefinitions
  Text
pRepositoryName_
  RepositoryProvider
pRepositoryProvider_
  SyncType
pSyncType_ =
    ListRepositorySyncDefinitions'
      { $sel:nextToken:ListRepositorySyncDefinitions' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:repositoryName:ListRepositorySyncDefinitions' :: Text
repositoryName = Text
pRepositoryName_,
        $sel:repositoryProvider:ListRepositorySyncDefinitions' :: RepositoryProvider
repositoryProvider = RepositoryProvider
pRepositoryProvider_,
        $sel:syncType:ListRepositorySyncDefinitions' :: SyncType
syncType = SyncType
pSyncType_
      }

-- | A token that indicates the location of the next repository sync
-- definition in the array of repository sync definitions, after the list
-- of repository sync definitions previously requested.
listRepositorySyncDefinitions_nextToken :: Lens.Lens' ListRepositorySyncDefinitions (Prelude.Maybe Prelude.Text)
listRepositorySyncDefinitions_nextToken :: Lens' ListRepositorySyncDefinitions (Maybe Text)
listRepositorySyncDefinitions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRepositorySyncDefinitions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListRepositorySyncDefinitions
s@ListRepositorySyncDefinitions' {} Maybe Text
a -> ListRepositorySyncDefinitions
s {$sel:nextToken:ListRepositorySyncDefinitions' :: Maybe Text
nextToken = Maybe Text
a} :: ListRepositorySyncDefinitions)

-- | The repository name.
listRepositorySyncDefinitions_repositoryName :: Lens.Lens' ListRepositorySyncDefinitions Prelude.Text
listRepositorySyncDefinitions_repositoryName :: Lens' ListRepositorySyncDefinitions Text
listRepositorySyncDefinitions_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRepositorySyncDefinitions' {Text
repositoryName :: Text
$sel:repositoryName:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> Text
repositoryName} -> Text
repositoryName) (\s :: ListRepositorySyncDefinitions
s@ListRepositorySyncDefinitions' {} Text
a -> ListRepositorySyncDefinitions
s {$sel:repositoryName:ListRepositorySyncDefinitions' :: Text
repositoryName = Text
a} :: ListRepositorySyncDefinitions)

-- | The repository provider.
listRepositorySyncDefinitions_repositoryProvider :: Lens.Lens' ListRepositorySyncDefinitions RepositoryProvider
listRepositorySyncDefinitions_repositoryProvider :: Lens' ListRepositorySyncDefinitions RepositoryProvider
listRepositorySyncDefinitions_repositoryProvider = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRepositorySyncDefinitions' {RepositoryProvider
repositoryProvider :: RepositoryProvider
$sel:repositoryProvider:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> RepositoryProvider
repositoryProvider} -> RepositoryProvider
repositoryProvider) (\s :: ListRepositorySyncDefinitions
s@ListRepositorySyncDefinitions' {} RepositoryProvider
a -> ListRepositorySyncDefinitions
s {$sel:repositoryProvider:ListRepositorySyncDefinitions' :: RepositoryProvider
repositoryProvider = RepositoryProvider
a} :: ListRepositorySyncDefinitions)

-- | The sync type. The only supported value is @TEMPLATE_SYNC@.
listRepositorySyncDefinitions_syncType :: Lens.Lens' ListRepositorySyncDefinitions SyncType
listRepositorySyncDefinitions_syncType :: Lens' ListRepositorySyncDefinitions SyncType
listRepositorySyncDefinitions_syncType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRepositorySyncDefinitions' {SyncType
syncType :: SyncType
$sel:syncType:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> SyncType
syncType} -> SyncType
syncType) (\s :: ListRepositorySyncDefinitions
s@ListRepositorySyncDefinitions' {} SyncType
a -> ListRepositorySyncDefinitions
s {$sel:syncType:ListRepositorySyncDefinitions' :: SyncType
syncType = SyncType
a} :: ListRepositorySyncDefinitions)

instance Core.AWSPager ListRepositorySyncDefinitions where
  page :: ListRepositorySyncDefinitions
-> AWSResponse ListRepositorySyncDefinitions
-> Maybe ListRepositorySyncDefinitions
page ListRepositorySyncDefinitions
rq AWSResponse ListRepositorySyncDefinitions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListRepositorySyncDefinitions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRepositorySyncDefinitionsResponse (Maybe Text)
listRepositorySyncDefinitionsResponse_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 ListRepositorySyncDefinitions
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens'
  ListRepositorySyncDefinitionsResponse [RepositorySyncDefinition]
listRepositorySyncDefinitionsResponse_syncDefinitions
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListRepositorySyncDefinitions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListRepositorySyncDefinitions (Maybe Text)
listRepositorySyncDefinitions_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListRepositorySyncDefinitions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRepositorySyncDefinitionsResponse (Maybe Text)
listRepositorySyncDefinitionsResponse_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
    ListRepositorySyncDefinitions
  where
  type
    AWSResponse ListRepositorySyncDefinitions =
      ListRepositorySyncDefinitionsResponse
  request :: (Service -> Service)
-> ListRepositorySyncDefinitions
-> Request ListRepositorySyncDefinitions
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 ListRepositorySyncDefinitions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListRepositorySyncDefinitions)))
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
-> Int
-> [RepositorySyncDefinition]
-> ListRepositorySyncDefinitionsResponse
ListRepositorySyncDefinitionsResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            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
"syncDefinitions"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance
  Prelude.Hashable
    ListRepositorySyncDefinitions
  where
  hashWithSalt :: Int -> ListRepositorySyncDefinitions -> Int
hashWithSalt Int
_salt ListRepositorySyncDefinitions' {Maybe Text
Text
RepositoryProvider
SyncType
syncType :: SyncType
repositoryProvider :: RepositoryProvider
repositoryName :: Text
nextToken :: Maybe Text
$sel:syncType:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> SyncType
$sel:repositoryProvider:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> RepositoryProvider
$sel:repositoryName:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> Text
$sel:nextToken:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
repositoryName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RepositoryProvider
repositoryProvider
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SyncType
syncType

instance Prelude.NFData ListRepositorySyncDefinitions where
  rnf :: ListRepositorySyncDefinitions -> ()
rnf ListRepositorySyncDefinitions' {Maybe Text
Text
RepositoryProvider
SyncType
syncType :: SyncType
repositoryProvider :: RepositoryProvider
repositoryName :: Text
nextToken :: Maybe Text
$sel:syncType:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> SyncType
$sel:repositoryProvider:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> RepositoryProvider
$sel:repositoryName:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> Text
$sel:nextToken:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> 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 Text
repositoryName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RepositoryProvider
repositoryProvider
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SyncType
syncType

instance Data.ToHeaders ListRepositorySyncDefinitions where
  toHeaders :: ListRepositorySyncDefinitions -> 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
"AwsProton20200720.ListRepositorySyncDefinitions" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListRepositorySyncDefinitions where
  toJSON :: ListRepositorySyncDefinitions -> Value
toJSON ListRepositorySyncDefinitions' {Maybe Text
Text
RepositoryProvider
SyncType
syncType :: SyncType
repositoryProvider :: RepositoryProvider
repositoryName :: Text
nextToken :: Maybe Text
$sel:syncType:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> SyncType
$sel:repositoryProvider:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> RepositoryProvider
$sel:repositoryName:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> Text
$sel:nextToken:ListRepositorySyncDefinitions' :: ListRepositorySyncDefinitions -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"repositoryName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
repositoryName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"repositoryProvider" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= RepositoryProvider
repositoryProvider),
            forall a. a -> Maybe a
Prelude.Just (Key
"syncType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= SyncType
syncType)
          ]
      )

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

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

-- | /See:/ 'newListRepositorySyncDefinitionsResponse' smart constructor.
data ListRepositorySyncDefinitionsResponse = ListRepositorySyncDefinitionsResponse'
  { -- | A token that indicates the location of the next repository sync
    -- definition in the array of repository sync definitions, after the
    -- current requested list of repository sync definitions.
    ListRepositorySyncDefinitionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListRepositorySyncDefinitionsResponse -> Int
httpStatus :: Prelude.Int,
    -- | An array of repository sync definitions.
    ListRepositorySyncDefinitionsResponse -> [RepositorySyncDefinition]
syncDefinitions :: [RepositorySyncDefinition]
  }
  deriving (ListRepositorySyncDefinitionsResponse
-> ListRepositorySyncDefinitionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRepositorySyncDefinitionsResponse
-> ListRepositorySyncDefinitionsResponse -> Bool
$c/= :: ListRepositorySyncDefinitionsResponse
-> ListRepositorySyncDefinitionsResponse -> Bool
== :: ListRepositorySyncDefinitionsResponse
-> ListRepositorySyncDefinitionsResponse -> Bool
$c== :: ListRepositorySyncDefinitionsResponse
-> ListRepositorySyncDefinitionsResponse -> Bool
Prelude.Eq, ReadPrec [ListRepositorySyncDefinitionsResponse]
ReadPrec ListRepositorySyncDefinitionsResponse
Int -> ReadS ListRepositorySyncDefinitionsResponse
ReadS [ListRepositorySyncDefinitionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRepositorySyncDefinitionsResponse]
$creadListPrec :: ReadPrec [ListRepositorySyncDefinitionsResponse]
readPrec :: ReadPrec ListRepositorySyncDefinitionsResponse
$creadPrec :: ReadPrec ListRepositorySyncDefinitionsResponse
readList :: ReadS [ListRepositorySyncDefinitionsResponse]
$creadList :: ReadS [ListRepositorySyncDefinitionsResponse]
readsPrec :: Int -> ReadS ListRepositorySyncDefinitionsResponse
$creadsPrec :: Int -> ReadS ListRepositorySyncDefinitionsResponse
Prelude.Read, Int -> ListRepositorySyncDefinitionsResponse -> ShowS
[ListRepositorySyncDefinitionsResponse] -> ShowS
ListRepositorySyncDefinitionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRepositorySyncDefinitionsResponse] -> ShowS
$cshowList :: [ListRepositorySyncDefinitionsResponse] -> ShowS
show :: ListRepositorySyncDefinitionsResponse -> String
$cshow :: ListRepositorySyncDefinitionsResponse -> String
showsPrec :: Int -> ListRepositorySyncDefinitionsResponse -> ShowS
$cshowsPrec :: Int -> ListRepositorySyncDefinitionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListRepositorySyncDefinitionsResponse x
-> ListRepositorySyncDefinitionsResponse
forall x.
ListRepositorySyncDefinitionsResponse
-> Rep ListRepositorySyncDefinitionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListRepositorySyncDefinitionsResponse x
-> ListRepositorySyncDefinitionsResponse
$cfrom :: forall x.
ListRepositorySyncDefinitionsResponse
-> Rep ListRepositorySyncDefinitionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListRepositorySyncDefinitionsResponse' 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', 'listRepositorySyncDefinitionsResponse_nextToken' - A token that indicates the location of the next repository sync
-- definition in the array of repository sync definitions, after the
-- current requested list of repository sync definitions.
--
-- 'httpStatus', 'listRepositorySyncDefinitionsResponse_httpStatus' - The response's http status code.
--
-- 'syncDefinitions', 'listRepositorySyncDefinitionsResponse_syncDefinitions' - An array of repository sync definitions.
newListRepositorySyncDefinitionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListRepositorySyncDefinitionsResponse
newListRepositorySyncDefinitionsResponse :: Int -> ListRepositorySyncDefinitionsResponse
newListRepositorySyncDefinitionsResponse Int
pHttpStatus_ =
  ListRepositorySyncDefinitionsResponse'
    { $sel:nextToken:ListRepositorySyncDefinitionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListRepositorySyncDefinitionsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:syncDefinitions:ListRepositorySyncDefinitionsResponse' :: [RepositorySyncDefinition]
syncDefinitions = forall a. Monoid a => a
Prelude.mempty
    }

-- | A token that indicates the location of the next repository sync
-- definition in the array of repository sync definitions, after the
-- current requested list of repository sync definitions.
listRepositorySyncDefinitionsResponse_nextToken :: Lens.Lens' ListRepositorySyncDefinitionsResponse (Prelude.Maybe Prelude.Text)
listRepositorySyncDefinitionsResponse_nextToken :: Lens' ListRepositorySyncDefinitionsResponse (Maybe Text)
listRepositorySyncDefinitionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRepositorySyncDefinitionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListRepositorySyncDefinitionsResponse' :: ListRepositorySyncDefinitionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListRepositorySyncDefinitionsResponse
s@ListRepositorySyncDefinitionsResponse' {} Maybe Text
a -> ListRepositorySyncDefinitionsResponse
s {$sel:nextToken:ListRepositorySyncDefinitionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListRepositorySyncDefinitionsResponse)

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

-- | An array of repository sync definitions.
listRepositorySyncDefinitionsResponse_syncDefinitions :: Lens.Lens' ListRepositorySyncDefinitionsResponse [RepositorySyncDefinition]
listRepositorySyncDefinitionsResponse_syncDefinitions :: Lens'
  ListRepositorySyncDefinitionsResponse [RepositorySyncDefinition]
listRepositorySyncDefinitionsResponse_syncDefinitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRepositorySyncDefinitionsResponse' {[RepositorySyncDefinition]
syncDefinitions :: [RepositorySyncDefinition]
$sel:syncDefinitions:ListRepositorySyncDefinitionsResponse' :: ListRepositorySyncDefinitionsResponse -> [RepositorySyncDefinition]
syncDefinitions} -> [RepositorySyncDefinition]
syncDefinitions) (\s :: ListRepositorySyncDefinitionsResponse
s@ListRepositorySyncDefinitionsResponse' {} [RepositorySyncDefinition]
a -> ListRepositorySyncDefinitionsResponse
s {$sel:syncDefinitions:ListRepositorySyncDefinitionsResponse' :: [RepositorySyncDefinition]
syncDefinitions = [RepositorySyncDefinition]
a} :: ListRepositorySyncDefinitionsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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