{-# 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.EBS.ListChangedBlocks
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about the blocks that are different between two
-- Amazon Elastic Block Store snapshots of the same volume\/snapshot
-- lineage.
module Amazonka.EBS.ListChangedBlocks
  ( -- * Creating a Request
    ListChangedBlocks (..),
    newListChangedBlocks,

    -- * Request Lenses
    listChangedBlocks_firstSnapshotId,
    listChangedBlocks_maxResults,
    listChangedBlocks_nextToken,
    listChangedBlocks_startingBlockIndex,
    listChangedBlocks_secondSnapshotId,

    -- * Destructuring the Response
    ListChangedBlocksResponse (..),
    newListChangedBlocksResponse,

    -- * Response Lenses
    listChangedBlocksResponse_blockSize,
    listChangedBlocksResponse_changedBlocks,
    listChangedBlocksResponse_expiryTime,
    listChangedBlocksResponse_nextToken,
    listChangedBlocksResponse_volumeSize,
    listChangedBlocksResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListChangedBlocks' smart constructor.
data ListChangedBlocks = ListChangedBlocks'
  { -- | The ID of the first snapshot to use for the comparison.
    --
    -- The @FirstSnapshotID@ parameter must be specified with a
    -- @SecondSnapshotId@ parameter; otherwise, an error occurs.
    ListChangedBlocks -> Maybe Text
firstSnapshotId :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of blocks to be returned by the request.
    --
    -- Even if additional blocks can be retrieved from the snapshot, the
    -- request can return less blocks than __MaxResults__ or an empty array of
    -- blocks.
    --
    -- To retrieve the next set of blocks from the snapshot, make another
    -- request with the returned __NextToken__ value. The value of
    -- __NextToken__ is @null@ when there are no more blocks to return.
    ListChangedBlocks -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token to request the next page of results.
    --
    -- If you specify __NextToken__, then __StartingBlockIndex__ is ignored.
    ListChangedBlocks -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The block index from which the comparison should start.
    --
    -- The list in the response will start from this block index or the next
    -- valid block index in the snapshots.
    --
    -- If you specify __NextToken__, then __StartingBlockIndex__ is ignored.
    ListChangedBlocks -> Maybe Natural
startingBlockIndex :: Prelude.Maybe Prelude.Natural,
    -- | The ID of the second snapshot to use for the comparison.
    --
    -- The @SecondSnapshotId@ parameter must be specified with a
    -- @FirstSnapshotID@ parameter; otherwise, an error occurs.
    ListChangedBlocks -> Text
secondSnapshotId :: Prelude.Text
  }
  deriving (ListChangedBlocks -> ListChangedBlocks -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChangedBlocks -> ListChangedBlocks -> Bool
$c/= :: ListChangedBlocks -> ListChangedBlocks -> Bool
== :: ListChangedBlocks -> ListChangedBlocks -> Bool
$c== :: ListChangedBlocks -> ListChangedBlocks -> Bool
Prelude.Eq, ReadPrec [ListChangedBlocks]
ReadPrec ListChangedBlocks
Int -> ReadS ListChangedBlocks
ReadS [ListChangedBlocks]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListChangedBlocks]
$creadListPrec :: ReadPrec [ListChangedBlocks]
readPrec :: ReadPrec ListChangedBlocks
$creadPrec :: ReadPrec ListChangedBlocks
readList :: ReadS [ListChangedBlocks]
$creadList :: ReadS [ListChangedBlocks]
readsPrec :: Int -> ReadS ListChangedBlocks
$creadsPrec :: Int -> ReadS ListChangedBlocks
Prelude.Read, Int -> ListChangedBlocks -> ShowS
[ListChangedBlocks] -> ShowS
ListChangedBlocks -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChangedBlocks] -> ShowS
$cshowList :: [ListChangedBlocks] -> ShowS
show :: ListChangedBlocks -> String
$cshow :: ListChangedBlocks -> String
showsPrec :: Int -> ListChangedBlocks -> ShowS
$cshowsPrec :: Int -> ListChangedBlocks -> ShowS
Prelude.Show, forall x. Rep ListChangedBlocks x -> ListChangedBlocks
forall x. ListChangedBlocks -> Rep ListChangedBlocks x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListChangedBlocks x -> ListChangedBlocks
$cfrom :: forall x. ListChangedBlocks -> Rep ListChangedBlocks x
Prelude.Generic)

-- |
-- Create a value of 'ListChangedBlocks' 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:
--
-- 'firstSnapshotId', 'listChangedBlocks_firstSnapshotId' - The ID of the first snapshot to use for the comparison.
--
-- The @FirstSnapshotID@ parameter must be specified with a
-- @SecondSnapshotId@ parameter; otherwise, an error occurs.
--
-- 'maxResults', 'listChangedBlocks_maxResults' - The maximum number of blocks to be returned by the request.
--
-- Even if additional blocks can be retrieved from the snapshot, the
-- request can return less blocks than __MaxResults__ or an empty array of
-- blocks.
--
-- To retrieve the next set of blocks from the snapshot, make another
-- request with the returned __NextToken__ value. The value of
-- __NextToken__ is @null@ when there are no more blocks to return.
--
-- 'nextToken', 'listChangedBlocks_nextToken' - The token to request the next page of results.
--
-- If you specify __NextToken__, then __StartingBlockIndex__ is ignored.
--
-- 'startingBlockIndex', 'listChangedBlocks_startingBlockIndex' - The block index from which the comparison should start.
--
-- The list in the response will start from this block index or the next
-- valid block index in the snapshots.
--
-- If you specify __NextToken__, then __StartingBlockIndex__ is ignored.
--
-- 'secondSnapshotId', 'listChangedBlocks_secondSnapshotId' - The ID of the second snapshot to use for the comparison.
--
-- The @SecondSnapshotId@ parameter must be specified with a
-- @FirstSnapshotID@ parameter; otherwise, an error occurs.
newListChangedBlocks ::
  -- | 'secondSnapshotId'
  Prelude.Text ->
  ListChangedBlocks
newListChangedBlocks :: Text -> ListChangedBlocks
newListChangedBlocks Text
pSecondSnapshotId_ =
  ListChangedBlocks'
    { $sel:firstSnapshotId:ListChangedBlocks' :: Maybe Text
firstSnapshotId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListChangedBlocks' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListChangedBlocks' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:startingBlockIndex:ListChangedBlocks' :: Maybe Natural
startingBlockIndex = forall a. Maybe a
Prelude.Nothing,
      $sel:secondSnapshotId:ListChangedBlocks' :: Text
secondSnapshotId = Text
pSecondSnapshotId_
    }

-- | The ID of the first snapshot to use for the comparison.
--
-- The @FirstSnapshotID@ parameter must be specified with a
-- @SecondSnapshotId@ parameter; otherwise, an error occurs.
listChangedBlocks_firstSnapshotId :: Lens.Lens' ListChangedBlocks (Prelude.Maybe Prelude.Text)
listChangedBlocks_firstSnapshotId :: Lens' ListChangedBlocks (Maybe Text)
listChangedBlocks_firstSnapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocks' {Maybe Text
firstSnapshotId :: Maybe Text
$sel:firstSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
firstSnapshotId} -> Maybe Text
firstSnapshotId) (\s :: ListChangedBlocks
s@ListChangedBlocks' {} Maybe Text
a -> ListChangedBlocks
s {$sel:firstSnapshotId:ListChangedBlocks' :: Maybe Text
firstSnapshotId = Maybe Text
a} :: ListChangedBlocks)

-- | The maximum number of blocks to be returned by the request.
--
-- Even if additional blocks can be retrieved from the snapshot, the
-- request can return less blocks than __MaxResults__ or an empty array of
-- blocks.
--
-- To retrieve the next set of blocks from the snapshot, make another
-- request with the returned __NextToken__ value. The value of
-- __NextToken__ is @null@ when there are no more blocks to return.
listChangedBlocks_maxResults :: Lens.Lens' ListChangedBlocks (Prelude.Maybe Prelude.Natural)
listChangedBlocks_maxResults :: Lens' ListChangedBlocks (Maybe Natural)
listChangedBlocks_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocks' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListChangedBlocks
s@ListChangedBlocks' {} Maybe Natural
a -> ListChangedBlocks
s {$sel:maxResults:ListChangedBlocks' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListChangedBlocks)

-- | The token to request the next page of results.
--
-- If you specify __NextToken__, then __StartingBlockIndex__ is ignored.
listChangedBlocks_nextToken :: Lens.Lens' ListChangedBlocks (Prelude.Maybe Prelude.Text)
listChangedBlocks_nextToken :: Lens' ListChangedBlocks (Maybe Text)
listChangedBlocks_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocks' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListChangedBlocks
s@ListChangedBlocks' {} Maybe Text
a -> ListChangedBlocks
s {$sel:nextToken:ListChangedBlocks' :: Maybe Text
nextToken = Maybe Text
a} :: ListChangedBlocks)

-- | The block index from which the comparison should start.
--
-- The list in the response will start from this block index or the next
-- valid block index in the snapshots.
--
-- If you specify __NextToken__, then __StartingBlockIndex__ is ignored.
listChangedBlocks_startingBlockIndex :: Lens.Lens' ListChangedBlocks (Prelude.Maybe Prelude.Natural)
listChangedBlocks_startingBlockIndex :: Lens' ListChangedBlocks (Maybe Natural)
listChangedBlocks_startingBlockIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocks' {Maybe Natural
startingBlockIndex :: Maybe Natural
$sel:startingBlockIndex:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
startingBlockIndex} -> Maybe Natural
startingBlockIndex) (\s :: ListChangedBlocks
s@ListChangedBlocks' {} Maybe Natural
a -> ListChangedBlocks
s {$sel:startingBlockIndex:ListChangedBlocks' :: Maybe Natural
startingBlockIndex = Maybe Natural
a} :: ListChangedBlocks)

-- | The ID of the second snapshot to use for the comparison.
--
-- The @SecondSnapshotId@ parameter must be specified with a
-- @FirstSnapshotID@ parameter; otherwise, an error occurs.
listChangedBlocks_secondSnapshotId :: Lens.Lens' ListChangedBlocks Prelude.Text
listChangedBlocks_secondSnapshotId :: Lens' ListChangedBlocks Text
listChangedBlocks_secondSnapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocks' {Text
secondSnapshotId :: Text
$sel:secondSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Text
secondSnapshotId} -> Text
secondSnapshotId) (\s :: ListChangedBlocks
s@ListChangedBlocks' {} Text
a -> ListChangedBlocks
s {$sel:secondSnapshotId:ListChangedBlocks' :: Text
secondSnapshotId = Text
a} :: ListChangedBlocks)

instance Core.AWSRequest ListChangedBlocks where
  type
    AWSResponse ListChangedBlocks =
      ListChangedBlocksResponse
  request :: (Service -> Service)
-> ListChangedBlocks -> Request ListChangedBlocks
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListChangedBlocks
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListChangedBlocks)))
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 Int
-> Maybe [Sensitive ChangedBlock]
-> Maybe POSIX
-> Maybe Text
-> Maybe Natural
-> Int
-> ListChangedBlocksResponse
ListChangedBlocksResponse'
            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
"BlockSize")
            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
"ChangedBlocks" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ExpiryTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"VolumeSize")
            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 ListChangedBlocks where
  hashWithSalt :: Int -> ListChangedBlocks -> Int
hashWithSalt Int
_salt ListChangedBlocks' {Maybe Natural
Maybe Text
Text
secondSnapshotId :: Text
startingBlockIndex :: Maybe Natural
nextToken :: Maybe Text
maxResults :: Maybe Natural
firstSnapshotId :: Maybe Text
$sel:secondSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Text
$sel:startingBlockIndex:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
$sel:nextToken:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
$sel:maxResults:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
$sel:firstSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
firstSnapshotId
      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 Natural
startingBlockIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
secondSnapshotId

instance Prelude.NFData ListChangedBlocks where
  rnf :: ListChangedBlocks -> ()
rnf ListChangedBlocks' {Maybe Natural
Maybe Text
Text
secondSnapshotId :: Text
startingBlockIndex :: Maybe Natural
nextToken :: Maybe Text
maxResults :: Maybe Natural
firstSnapshotId :: Maybe Text
$sel:secondSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Text
$sel:startingBlockIndex:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
$sel:nextToken:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
$sel:maxResults:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
$sel:firstSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firstSnapshotId
      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 Maybe Natural
startingBlockIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
secondSnapshotId

instance Data.ToHeaders ListChangedBlocks where
  toHeaders :: ListChangedBlocks -> 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.ToPath ListChangedBlocks where
  toPath :: ListChangedBlocks -> ByteString
toPath ListChangedBlocks' {Maybe Natural
Maybe Text
Text
secondSnapshotId :: Text
startingBlockIndex :: Maybe Natural
nextToken :: Maybe Text
maxResults :: Maybe Natural
firstSnapshotId :: Maybe Text
$sel:secondSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Text
$sel:startingBlockIndex:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
$sel:nextToken:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
$sel:maxResults:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
$sel:firstSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/snapshots/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
secondSnapshotId,
        ByteString
"/changedblocks"
      ]

instance Data.ToQuery ListChangedBlocks where
  toQuery :: ListChangedBlocks -> QueryString
toQuery ListChangedBlocks' {Maybe Natural
Maybe Text
Text
secondSnapshotId :: Text
startingBlockIndex :: Maybe Natural
nextToken :: Maybe Text
maxResults :: Maybe Natural
firstSnapshotId :: Maybe Text
$sel:secondSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Text
$sel:startingBlockIndex:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
$sel:nextToken:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
$sel:maxResults:ListChangedBlocks' :: ListChangedBlocks -> Maybe Natural
$sel:firstSnapshotId:ListChangedBlocks' :: ListChangedBlocks -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"firstSnapshotId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
firstSnapshotId,
        ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"pageToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"startingBlockIndex" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
startingBlockIndex
      ]

-- | /See:/ 'newListChangedBlocksResponse' smart constructor.
data ListChangedBlocksResponse = ListChangedBlocksResponse'
  { -- | The size of the blocks in the snapshot, in bytes.
    ListChangedBlocksResponse -> Maybe Int
blockSize :: Prelude.Maybe Prelude.Int,
    -- | An array of objects containing information about the changed blocks.
    ListChangedBlocksResponse -> Maybe [Sensitive ChangedBlock]
changedBlocks :: Prelude.Maybe [Data.Sensitive ChangedBlock],
    -- | The time when the @BlockToken@ expires.
    ListChangedBlocksResponse -> Maybe POSIX
expiryTime :: Prelude.Maybe Data.POSIX,
    -- | The token to use to retrieve the next page of results. This value is
    -- null when there are no more results to return.
    ListChangedBlocksResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The size of the volume in GB.
    ListChangedBlocksResponse -> Maybe Natural
volumeSize :: Prelude.Maybe Prelude.Natural,
    -- | The response's http status code.
    ListChangedBlocksResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListChangedBlocksResponse -> ListChangedBlocksResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChangedBlocksResponse -> ListChangedBlocksResponse -> Bool
$c/= :: ListChangedBlocksResponse -> ListChangedBlocksResponse -> Bool
== :: ListChangedBlocksResponse -> ListChangedBlocksResponse -> Bool
$c== :: ListChangedBlocksResponse -> ListChangedBlocksResponse -> Bool
Prelude.Eq, Int -> ListChangedBlocksResponse -> ShowS
[ListChangedBlocksResponse] -> ShowS
ListChangedBlocksResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChangedBlocksResponse] -> ShowS
$cshowList :: [ListChangedBlocksResponse] -> ShowS
show :: ListChangedBlocksResponse -> String
$cshow :: ListChangedBlocksResponse -> String
showsPrec :: Int -> ListChangedBlocksResponse -> ShowS
$cshowsPrec :: Int -> ListChangedBlocksResponse -> ShowS
Prelude.Show, forall x.
Rep ListChangedBlocksResponse x -> ListChangedBlocksResponse
forall x.
ListChangedBlocksResponse -> Rep ListChangedBlocksResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListChangedBlocksResponse x -> ListChangedBlocksResponse
$cfrom :: forall x.
ListChangedBlocksResponse -> Rep ListChangedBlocksResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListChangedBlocksResponse' 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:
--
-- 'blockSize', 'listChangedBlocksResponse_blockSize' - The size of the blocks in the snapshot, in bytes.
--
-- 'changedBlocks', 'listChangedBlocksResponse_changedBlocks' - An array of objects containing information about the changed blocks.
--
-- 'expiryTime', 'listChangedBlocksResponse_expiryTime' - The time when the @BlockToken@ expires.
--
-- 'nextToken', 'listChangedBlocksResponse_nextToken' - The token to use to retrieve the next page of results. This value is
-- null when there are no more results to return.
--
-- 'volumeSize', 'listChangedBlocksResponse_volumeSize' - The size of the volume in GB.
--
-- 'httpStatus', 'listChangedBlocksResponse_httpStatus' - The response's http status code.
newListChangedBlocksResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListChangedBlocksResponse
newListChangedBlocksResponse :: Int -> ListChangedBlocksResponse
newListChangedBlocksResponse Int
pHttpStatus_ =
  ListChangedBlocksResponse'
    { $sel:blockSize:ListChangedBlocksResponse' :: Maybe Int
blockSize =
        forall a. Maybe a
Prelude.Nothing,
      $sel:changedBlocks:ListChangedBlocksResponse' :: Maybe [Sensitive ChangedBlock]
changedBlocks = forall a. Maybe a
Prelude.Nothing,
      $sel:expiryTime:ListChangedBlocksResponse' :: Maybe POSIX
expiryTime = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListChangedBlocksResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeSize:ListChangedBlocksResponse' :: Maybe Natural
volumeSize = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListChangedBlocksResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The size of the blocks in the snapshot, in bytes.
listChangedBlocksResponse_blockSize :: Lens.Lens' ListChangedBlocksResponse (Prelude.Maybe Prelude.Int)
listChangedBlocksResponse_blockSize :: Lens' ListChangedBlocksResponse (Maybe Int)
listChangedBlocksResponse_blockSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocksResponse' {Maybe Int
blockSize :: Maybe Int
$sel:blockSize:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe Int
blockSize} -> Maybe Int
blockSize) (\s :: ListChangedBlocksResponse
s@ListChangedBlocksResponse' {} Maybe Int
a -> ListChangedBlocksResponse
s {$sel:blockSize:ListChangedBlocksResponse' :: Maybe Int
blockSize = Maybe Int
a} :: ListChangedBlocksResponse)

-- | An array of objects containing information about the changed blocks.
listChangedBlocksResponse_changedBlocks :: Lens.Lens' ListChangedBlocksResponse (Prelude.Maybe [ChangedBlock])
listChangedBlocksResponse_changedBlocks :: Lens' ListChangedBlocksResponse (Maybe [ChangedBlock])
listChangedBlocksResponse_changedBlocks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocksResponse' {Maybe [Sensitive ChangedBlock]
changedBlocks :: Maybe [Sensitive ChangedBlock]
$sel:changedBlocks:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe [Sensitive ChangedBlock]
changedBlocks} -> Maybe [Sensitive ChangedBlock]
changedBlocks) (\s :: ListChangedBlocksResponse
s@ListChangedBlocksResponse' {} Maybe [Sensitive ChangedBlock]
a -> ListChangedBlocksResponse
s {$sel:changedBlocks:ListChangedBlocksResponse' :: Maybe [Sensitive ChangedBlock]
changedBlocks = Maybe [Sensitive ChangedBlock]
a} :: ListChangedBlocksResponse) 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 time when the @BlockToken@ expires.
listChangedBlocksResponse_expiryTime :: Lens.Lens' ListChangedBlocksResponse (Prelude.Maybe Prelude.UTCTime)
listChangedBlocksResponse_expiryTime :: Lens' ListChangedBlocksResponse (Maybe UTCTime)
listChangedBlocksResponse_expiryTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocksResponse' {Maybe POSIX
expiryTime :: Maybe POSIX
$sel:expiryTime:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe POSIX
expiryTime} -> Maybe POSIX
expiryTime) (\s :: ListChangedBlocksResponse
s@ListChangedBlocksResponse' {} Maybe POSIX
a -> ListChangedBlocksResponse
s {$sel:expiryTime:ListChangedBlocksResponse' :: Maybe POSIX
expiryTime = Maybe POSIX
a} :: ListChangedBlocksResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The token to use to retrieve the next page of results. This value is
-- null when there are no more results to return.
listChangedBlocksResponse_nextToken :: Lens.Lens' ListChangedBlocksResponse (Prelude.Maybe Prelude.Text)
listChangedBlocksResponse_nextToken :: Lens' ListChangedBlocksResponse (Maybe Text)
listChangedBlocksResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocksResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListChangedBlocksResponse
s@ListChangedBlocksResponse' {} Maybe Text
a -> ListChangedBlocksResponse
s {$sel:nextToken:ListChangedBlocksResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListChangedBlocksResponse)

-- | The size of the volume in GB.
listChangedBlocksResponse_volumeSize :: Lens.Lens' ListChangedBlocksResponse (Prelude.Maybe Prelude.Natural)
listChangedBlocksResponse_volumeSize :: Lens' ListChangedBlocksResponse (Maybe Natural)
listChangedBlocksResponse_volumeSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangedBlocksResponse' {Maybe Natural
volumeSize :: Maybe Natural
$sel:volumeSize:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe Natural
volumeSize} -> Maybe Natural
volumeSize) (\s :: ListChangedBlocksResponse
s@ListChangedBlocksResponse' {} Maybe Natural
a -> ListChangedBlocksResponse
s {$sel:volumeSize:ListChangedBlocksResponse' :: Maybe Natural
volumeSize = Maybe Natural
a} :: ListChangedBlocksResponse)

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

instance Prelude.NFData ListChangedBlocksResponse where
  rnf :: ListChangedBlocksResponse -> ()
rnf ListChangedBlocksResponse' {Int
Maybe Int
Maybe Natural
Maybe [Sensitive ChangedBlock]
Maybe Text
Maybe POSIX
httpStatus :: Int
volumeSize :: Maybe Natural
nextToken :: Maybe Text
expiryTime :: Maybe POSIX
changedBlocks :: Maybe [Sensitive ChangedBlock]
blockSize :: Maybe Int
$sel:httpStatus:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Int
$sel:volumeSize:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe Natural
$sel:nextToken:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe Text
$sel:expiryTime:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe POSIX
$sel:changedBlocks:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe [Sensitive ChangedBlock]
$sel:blockSize:ListChangedBlocksResponse' :: ListChangedBlocksResponse -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
blockSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Sensitive ChangedBlock]
changedBlocks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
expiryTime
      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 Natural
volumeSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus