{-# 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.GetRepositorySyncStatus
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Get the sync status of a repository used for Proton template sync. For
-- more information about template sync, see .
--
-- A repository sync status isn\'t tied to the Proton Repository resource
-- (or any other Proton resource). Therefore, tags on an Proton Repository
-- resource have no effect on this action. Specifically, you can\'t use
-- these tags to control access to this action using Attribute-based access
-- control (ABAC).
--
-- For more information about ABAC, see
-- <https://docs.aws.amazon.com/proton/latest/userguide/security_iam_service-with-iam.html#security_iam_service-with-iam-tags ABAC>
-- in the /Proton User Guide/.
module Amazonka.Proton.GetRepositorySyncStatus
  ( -- * Creating a Request
    GetRepositorySyncStatus (..),
    newGetRepositorySyncStatus,

    -- * Request Lenses
    getRepositorySyncStatus_branch,
    getRepositorySyncStatus_repositoryName,
    getRepositorySyncStatus_repositoryProvider,
    getRepositorySyncStatus_syncType,

    -- * Destructuring the Response
    GetRepositorySyncStatusResponse (..),
    newGetRepositorySyncStatusResponse,

    -- * Response Lenses
    getRepositorySyncStatusResponse_latestSync,
    getRepositorySyncStatusResponse_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 Amazonka.Proton.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetRepositorySyncStatus' smart constructor.
data GetRepositorySyncStatus = GetRepositorySyncStatus'
  { -- | The repository branch.
    GetRepositorySyncStatus -> Text
branch :: Prelude.Text,
    -- | The repository name.
    GetRepositorySyncStatus -> Text
repositoryName :: Prelude.Text,
    -- | The repository provider.
    GetRepositorySyncStatus -> RepositoryProvider
repositoryProvider :: RepositoryProvider,
    -- | The repository sync type.
    GetRepositorySyncStatus -> SyncType
syncType :: SyncType
  }
  deriving (GetRepositorySyncStatus -> GetRepositorySyncStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRepositorySyncStatus -> GetRepositorySyncStatus -> Bool
$c/= :: GetRepositorySyncStatus -> GetRepositorySyncStatus -> Bool
== :: GetRepositorySyncStatus -> GetRepositorySyncStatus -> Bool
$c== :: GetRepositorySyncStatus -> GetRepositorySyncStatus -> Bool
Prelude.Eq, ReadPrec [GetRepositorySyncStatus]
ReadPrec GetRepositorySyncStatus
Int -> ReadS GetRepositorySyncStatus
ReadS [GetRepositorySyncStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRepositorySyncStatus]
$creadListPrec :: ReadPrec [GetRepositorySyncStatus]
readPrec :: ReadPrec GetRepositorySyncStatus
$creadPrec :: ReadPrec GetRepositorySyncStatus
readList :: ReadS [GetRepositorySyncStatus]
$creadList :: ReadS [GetRepositorySyncStatus]
readsPrec :: Int -> ReadS GetRepositorySyncStatus
$creadsPrec :: Int -> ReadS GetRepositorySyncStatus
Prelude.Read, Int -> GetRepositorySyncStatus -> ShowS
[GetRepositorySyncStatus] -> ShowS
GetRepositorySyncStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRepositorySyncStatus] -> ShowS
$cshowList :: [GetRepositorySyncStatus] -> ShowS
show :: GetRepositorySyncStatus -> String
$cshow :: GetRepositorySyncStatus -> String
showsPrec :: Int -> GetRepositorySyncStatus -> ShowS
$cshowsPrec :: Int -> GetRepositorySyncStatus -> ShowS
Prelude.Show, forall x. Rep GetRepositorySyncStatus x -> GetRepositorySyncStatus
forall x. GetRepositorySyncStatus -> Rep GetRepositorySyncStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRepositorySyncStatus x -> GetRepositorySyncStatus
$cfrom :: forall x. GetRepositorySyncStatus -> Rep GetRepositorySyncStatus x
Prelude.Generic)

-- |
-- Create a value of 'GetRepositorySyncStatus' 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:
--
-- 'branch', 'getRepositorySyncStatus_branch' - The repository branch.
--
-- 'repositoryName', 'getRepositorySyncStatus_repositoryName' - The repository name.
--
-- 'repositoryProvider', 'getRepositorySyncStatus_repositoryProvider' - The repository provider.
--
-- 'syncType', 'getRepositorySyncStatus_syncType' - The repository sync type.
newGetRepositorySyncStatus ::
  -- | 'branch'
  Prelude.Text ->
  -- | 'repositoryName'
  Prelude.Text ->
  -- | 'repositoryProvider'
  RepositoryProvider ->
  -- | 'syncType'
  SyncType ->
  GetRepositorySyncStatus
newGetRepositorySyncStatus :: Text
-> Text
-> RepositoryProvider
-> SyncType
-> GetRepositorySyncStatus
newGetRepositorySyncStatus
  Text
pBranch_
  Text
pRepositoryName_
  RepositoryProvider
pRepositoryProvider_
  SyncType
pSyncType_ =
    GetRepositorySyncStatus'
      { $sel:branch:GetRepositorySyncStatus' :: Text
branch = Text
pBranch_,
        $sel:repositoryName:GetRepositorySyncStatus' :: Text
repositoryName = Text
pRepositoryName_,
        $sel:repositoryProvider:GetRepositorySyncStatus' :: RepositoryProvider
repositoryProvider = RepositoryProvider
pRepositoryProvider_,
        $sel:syncType:GetRepositorySyncStatus' :: SyncType
syncType = SyncType
pSyncType_
      }

-- | The repository branch.
getRepositorySyncStatus_branch :: Lens.Lens' GetRepositorySyncStatus Prelude.Text
getRepositorySyncStatus_branch :: Lens' GetRepositorySyncStatus Text
getRepositorySyncStatus_branch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRepositorySyncStatus' {Text
branch :: Text
$sel:branch:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> Text
branch} -> Text
branch) (\s :: GetRepositorySyncStatus
s@GetRepositorySyncStatus' {} Text
a -> GetRepositorySyncStatus
s {$sel:branch:GetRepositorySyncStatus' :: Text
branch = Text
a} :: GetRepositorySyncStatus)

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

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

-- | The repository sync type.
getRepositorySyncStatus_syncType :: Lens.Lens' GetRepositorySyncStatus SyncType
getRepositorySyncStatus_syncType :: Lens' GetRepositorySyncStatus SyncType
getRepositorySyncStatus_syncType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRepositorySyncStatus' {SyncType
syncType :: SyncType
$sel:syncType:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> SyncType
syncType} -> SyncType
syncType) (\s :: GetRepositorySyncStatus
s@GetRepositorySyncStatus' {} SyncType
a -> GetRepositorySyncStatus
s {$sel:syncType:GetRepositorySyncStatus' :: SyncType
syncType = SyncType
a} :: GetRepositorySyncStatus)

instance Core.AWSRequest GetRepositorySyncStatus where
  type
    AWSResponse GetRepositorySyncStatus =
      GetRepositorySyncStatusResponse
  request :: (Service -> Service)
-> GetRepositorySyncStatus -> Request GetRepositorySyncStatus
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 GetRepositorySyncStatus
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetRepositorySyncStatus)))
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 RepositorySyncAttempt
-> Int -> GetRepositorySyncStatusResponse
GetRepositorySyncStatusResponse'
            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
"latestSync")
            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 GetRepositorySyncStatus where
  hashWithSalt :: Int -> GetRepositorySyncStatus -> Int
hashWithSalt Int
_salt GetRepositorySyncStatus' {Text
RepositoryProvider
SyncType
syncType :: SyncType
repositoryProvider :: RepositoryProvider
repositoryName :: Text
branch :: Text
$sel:syncType:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> SyncType
$sel:repositoryProvider:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> RepositoryProvider
$sel:repositoryName:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> Text
$sel:branch:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
branch
      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 GetRepositorySyncStatus where
  rnf :: GetRepositorySyncStatus -> ()
rnf GetRepositorySyncStatus' {Text
RepositoryProvider
SyncType
syncType :: SyncType
repositoryProvider :: RepositoryProvider
repositoryName :: Text
branch :: Text
$sel:syncType:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> SyncType
$sel:repositoryProvider:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> RepositoryProvider
$sel:repositoryName:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> Text
$sel:branch:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
branch
      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 GetRepositorySyncStatus where
  toHeaders :: GetRepositorySyncStatus -> 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.GetRepositorySyncStatus" ::
                          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 GetRepositorySyncStatus where
  toJSON :: GetRepositorySyncStatus -> Value
toJSON GetRepositorySyncStatus' {Text
RepositoryProvider
SyncType
syncType :: SyncType
repositoryProvider :: RepositoryProvider
repositoryName :: Text
branch :: Text
$sel:syncType:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> SyncType
$sel:repositoryProvider:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> RepositoryProvider
$sel:repositoryName:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> Text
$sel:branch:GetRepositorySyncStatus' :: GetRepositorySyncStatus -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"branch" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
branch),
            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 GetRepositorySyncStatus where
  toPath :: GetRepositorySyncStatus -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetRepositorySyncStatusResponse' smart constructor.
data GetRepositorySyncStatusResponse = GetRepositorySyncStatusResponse'
  { -- | The repository sync status detail data that\'s returned by Proton.
    GetRepositorySyncStatusResponse -> Maybe RepositorySyncAttempt
latestSync :: Prelude.Maybe RepositorySyncAttempt,
    -- | The response's http status code.
    GetRepositorySyncStatusResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetRepositorySyncStatusResponse
-> GetRepositorySyncStatusResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRepositorySyncStatusResponse
-> GetRepositorySyncStatusResponse -> Bool
$c/= :: GetRepositorySyncStatusResponse
-> GetRepositorySyncStatusResponse -> Bool
== :: GetRepositorySyncStatusResponse
-> GetRepositorySyncStatusResponse -> Bool
$c== :: GetRepositorySyncStatusResponse
-> GetRepositorySyncStatusResponse -> Bool
Prelude.Eq, ReadPrec [GetRepositorySyncStatusResponse]
ReadPrec GetRepositorySyncStatusResponse
Int -> ReadS GetRepositorySyncStatusResponse
ReadS [GetRepositorySyncStatusResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRepositorySyncStatusResponse]
$creadListPrec :: ReadPrec [GetRepositorySyncStatusResponse]
readPrec :: ReadPrec GetRepositorySyncStatusResponse
$creadPrec :: ReadPrec GetRepositorySyncStatusResponse
readList :: ReadS [GetRepositorySyncStatusResponse]
$creadList :: ReadS [GetRepositorySyncStatusResponse]
readsPrec :: Int -> ReadS GetRepositorySyncStatusResponse
$creadsPrec :: Int -> ReadS GetRepositorySyncStatusResponse
Prelude.Read, Int -> GetRepositorySyncStatusResponse -> ShowS
[GetRepositorySyncStatusResponse] -> ShowS
GetRepositorySyncStatusResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRepositorySyncStatusResponse] -> ShowS
$cshowList :: [GetRepositorySyncStatusResponse] -> ShowS
show :: GetRepositorySyncStatusResponse -> String
$cshow :: GetRepositorySyncStatusResponse -> String
showsPrec :: Int -> GetRepositorySyncStatusResponse -> ShowS
$cshowsPrec :: Int -> GetRepositorySyncStatusResponse -> ShowS
Prelude.Show, forall x.
Rep GetRepositorySyncStatusResponse x
-> GetRepositorySyncStatusResponse
forall x.
GetRepositorySyncStatusResponse
-> Rep GetRepositorySyncStatusResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRepositorySyncStatusResponse x
-> GetRepositorySyncStatusResponse
$cfrom :: forall x.
GetRepositorySyncStatusResponse
-> Rep GetRepositorySyncStatusResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRepositorySyncStatusResponse' 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:
--
-- 'latestSync', 'getRepositorySyncStatusResponse_latestSync' - The repository sync status detail data that\'s returned by Proton.
--
-- 'httpStatus', 'getRepositorySyncStatusResponse_httpStatus' - The response's http status code.
newGetRepositorySyncStatusResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetRepositorySyncStatusResponse
newGetRepositorySyncStatusResponse :: Int -> GetRepositorySyncStatusResponse
newGetRepositorySyncStatusResponse Int
pHttpStatus_ =
  GetRepositorySyncStatusResponse'
    { $sel:latestSync:GetRepositorySyncStatusResponse' :: Maybe RepositorySyncAttempt
latestSync =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetRepositorySyncStatusResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The repository sync status detail data that\'s returned by Proton.
getRepositorySyncStatusResponse_latestSync :: Lens.Lens' GetRepositorySyncStatusResponse (Prelude.Maybe RepositorySyncAttempt)
getRepositorySyncStatusResponse_latestSync :: Lens' GetRepositorySyncStatusResponse (Maybe RepositorySyncAttempt)
getRepositorySyncStatusResponse_latestSync = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRepositorySyncStatusResponse' {Maybe RepositorySyncAttempt
latestSync :: Maybe RepositorySyncAttempt
$sel:latestSync:GetRepositorySyncStatusResponse' :: GetRepositorySyncStatusResponse -> Maybe RepositorySyncAttempt
latestSync} -> Maybe RepositorySyncAttempt
latestSync) (\s :: GetRepositorySyncStatusResponse
s@GetRepositorySyncStatusResponse' {} Maybe RepositorySyncAttempt
a -> GetRepositorySyncStatusResponse
s {$sel:latestSync:GetRepositorySyncStatusResponse' :: Maybe RepositorySyncAttempt
latestSync = Maybe RepositorySyncAttempt
a} :: GetRepositorySyncStatusResponse)

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

instance
  Prelude.NFData
    GetRepositorySyncStatusResponse
  where
  rnf :: GetRepositorySyncStatusResponse -> ()
rnf GetRepositorySyncStatusResponse' {Int
Maybe RepositorySyncAttempt
httpStatus :: Int
latestSync :: Maybe RepositorySyncAttempt
$sel:httpStatus:GetRepositorySyncStatusResponse' :: GetRepositorySyncStatusResponse -> Int
$sel:latestSync:GetRepositorySyncStatusResponse' :: GetRepositorySyncStatusResponse -> Maybe RepositorySyncAttempt
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe RepositorySyncAttempt
latestSync
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus