{-# 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.Lightsail.GetDiskSnapshots
-- 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 all block storage disk snapshots in your AWS
-- account and region.
--
-- This operation returns paginated results.
module Amazonka.Lightsail.GetDiskSnapshots
  ( -- * Creating a Request
    GetDiskSnapshots (..),
    newGetDiskSnapshots,

    -- * Request Lenses
    getDiskSnapshots_pageToken,

    -- * Destructuring the Response
    GetDiskSnapshotsResponse (..),
    newGetDiskSnapshotsResponse,

    -- * Response Lenses
    getDiskSnapshotsResponse_diskSnapshots,
    getDiskSnapshotsResponse_nextPageToken,
    getDiskSnapshotsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetDiskSnapshots' smart constructor.
data GetDiskSnapshots = GetDiskSnapshots'
  { -- | The token to advance to the next page of results from your request.
    --
    -- To get a page token, perform an initial @GetDiskSnapshots@ request. If
    -- your results are paginated, the response will return a next page token
    -- that you can specify as the page token in a subsequent request.
    GetDiskSnapshots -> Maybe Text
pageToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetDiskSnapshots -> GetDiskSnapshots -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDiskSnapshots -> GetDiskSnapshots -> Bool
$c/= :: GetDiskSnapshots -> GetDiskSnapshots -> Bool
== :: GetDiskSnapshots -> GetDiskSnapshots -> Bool
$c== :: GetDiskSnapshots -> GetDiskSnapshots -> Bool
Prelude.Eq, ReadPrec [GetDiskSnapshots]
ReadPrec GetDiskSnapshots
Int -> ReadS GetDiskSnapshots
ReadS [GetDiskSnapshots]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDiskSnapshots]
$creadListPrec :: ReadPrec [GetDiskSnapshots]
readPrec :: ReadPrec GetDiskSnapshots
$creadPrec :: ReadPrec GetDiskSnapshots
readList :: ReadS [GetDiskSnapshots]
$creadList :: ReadS [GetDiskSnapshots]
readsPrec :: Int -> ReadS GetDiskSnapshots
$creadsPrec :: Int -> ReadS GetDiskSnapshots
Prelude.Read, Int -> GetDiskSnapshots -> ShowS
[GetDiskSnapshots] -> ShowS
GetDiskSnapshots -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDiskSnapshots] -> ShowS
$cshowList :: [GetDiskSnapshots] -> ShowS
show :: GetDiskSnapshots -> String
$cshow :: GetDiskSnapshots -> String
showsPrec :: Int -> GetDiskSnapshots -> ShowS
$cshowsPrec :: Int -> GetDiskSnapshots -> ShowS
Prelude.Show, forall x. Rep GetDiskSnapshots x -> GetDiskSnapshots
forall x. GetDiskSnapshots -> Rep GetDiskSnapshots x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDiskSnapshots x -> GetDiskSnapshots
$cfrom :: forall x. GetDiskSnapshots -> Rep GetDiskSnapshots x
Prelude.Generic)

-- |
-- Create a value of 'GetDiskSnapshots' 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:
--
-- 'pageToken', 'getDiskSnapshots_pageToken' - The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetDiskSnapshots@ request. If
-- your results are paginated, the response will return a next page token
-- that you can specify as the page token in a subsequent request.
newGetDiskSnapshots ::
  GetDiskSnapshots
newGetDiskSnapshots :: GetDiskSnapshots
newGetDiskSnapshots =
  GetDiskSnapshots' {$sel:pageToken:GetDiskSnapshots' :: Maybe Text
pageToken = forall a. Maybe a
Prelude.Nothing}

-- | The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetDiskSnapshots@ request. If
-- your results are paginated, the response will return a next page token
-- that you can specify as the page token in a subsequent request.
getDiskSnapshots_pageToken :: Lens.Lens' GetDiskSnapshots (Prelude.Maybe Prelude.Text)
getDiskSnapshots_pageToken :: Lens' GetDiskSnapshots (Maybe Text)
getDiskSnapshots_pageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDiskSnapshots' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetDiskSnapshots' :: GetDiskSnapshots -> Maybe Text
pageToken} -> Maybe Text
pageToken) (\s :: GetDiskSnapshots
s@GetDiskSnapshots' {} Maybe Text
a -> GetDiskSnapshots
s {$sel:pageToken:GetDiskSnapshots' :: Maybe Text
pageToken = Maybe Text
a} :: GetDiskSnapshots)

instance Core.AWSPager GetDiskSnapshots where
  page :: GetDiskSnapshots
-> AWSResponse GetDiskSnapshots -> Maybe GetDiskSnapshots
page GetDiskSnapshots
rq AWSResponse GetDiskSnapshots
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetDiskSnapshots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetDiskSnapshotsResponse (Maybe Text)
getDiskSnapshotsResponse_nextPageToken
            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 GetDiskSnapshots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetDiskSnapshotsResponse (Maybe [DiskSnapshot])
getDiskSnapshotsResponse_diskSnapshots
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ GetDiskSnapshots
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetDiskSnapshots (Maybe Text)
getDiskSnapshots_pageToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetDiskSnapshots
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetDiskSnapshotsResponse (Maybe Text)
getDiskSnapshotsResponse_nextPageToken
          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 GetDiskSnapshots where
  type
    AWSResponse GetDiskSnapshots =
      GetDiskSnapshotsResponse
  request :: (Service -> Service)
-> GetDiskSnapshots -> Request GetDiskSnapshots
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 GetDiskSnapshots
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetDiskSnapshots)))
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 [DiskSnapshot]
-> Maybe Text -> Int -> GetDiskSnapshotsResponse
GetDiskSnapshotsResponse'
            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
"diskSnapshots" 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
"nextPageToken")
            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 GetDiskSnapshots where
  hashWithSalt :: Int -> GetDiskSnapshots -> Int
hashWithSalt Int
_salt GetDiskSnapshots' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetDiskSnapshots' :: GetDiskSnapshots -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageToken

instance Prelude.NFData GetDiskSnapshots where
  rnf :: GetDiskSnapshots -> ()
rnf GetDiskSnapshots' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetDiskSnapshots' :: GetDiskSnapshots -> Maybe Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageToken

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

instance Data.ToJSON GetDiskSnapshots where
  toJSON :: GetDiskSnapshots -> Value
toJSON GetDiskSnapshots' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetDiskSnapshots' :: GetDiskSnapshots -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"pageToken" 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
pageToken]
      )

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

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

-- | /See:/ 'newGetDiskSnapshotsResponse' smart constructor.
data GetDiskSnapshotsResponse = GetDiskSnapshotsResponse'
  { -- | An array of objects containing information about all block storage disk
    -- snapshots.
    GetDiskSnapshotsResponse -> Maybe [DiskSnapshot]
diskSnapshots :: Prelude.Maybe [DiskSnapshot],
    -- | The token to advance to the next page of results from your request.
    --
    -- A next page token is not returned if there are no more results to
    -- display.
    --
    -- To get the next page of results, perform another @GetDiskSnapshots@
    -- request and specify the next page token using the @pageToken@ parameter.
    GetDiskSnapshotsResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetDiskSnapshotsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDiskSnapshotsResponse -> GetDiskSnapshotsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDiskSnapshotsResponse -> GetDiskSnapshotsResponse -> Bool
$c/= :: GetDiskSnapshotsResponse -> GetDiskSnapshotsResponse -> Bool
== :: GetDiskSnapshotsResponse -> GetDiskSnapshotsResponse -> Bool
$c== :: GetDiskSnapshotsResponse -> GetDiskSnapshotsResponse -> Bool
Prelude.Eq, ReadPrec [GetDiskSnapshotsResponse]
ReadPrec GetDiskSnapshotsResponse
Int -> ReadS GetDiskSnapshotsResponse
ReadS [GetDiskSnapshotsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDiskSnapshotsResponse]
$creadListPrec :: ReadPrec [GetDiskSnapshotsResponse]
readPrec :: ReadPrec GetDiskSnapshotsResponse
$creadPrec :: ReadPrec GetDiskSnapshotsResponse
readList :: ReadS [GetDiskSnapshotsResponse]
$creadList :: ReadS [GetDiskSnapshotsResponse]
readsPrec :: Int -> ReadS GetDiskSnapshotsResponse
$creadsPrec :: Int -> ReadS GetDiskSnapshotsResponse
Prelude.Read, Int -> GetDiskSnapshotsResponse -> ShowS
[GetDiskSnapshotsResponse] -> ShowS
GetDiskSnapshotsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDiskSnapshotsResponse] -> ShowS
$cshowList :: [GetDiskSnapshotsResponse] -> ShowS
show :: GetDiskSnapshotsResponse -> String
$cshow :: GetDiskSnapshotsResponse -> String
showsPrec :: Int -> GetDiskSnapshotsResponse -> ShowS
$cshowsPrec :: Int -> GetDiskSnapshotsResponse -> ShowS
Prelude.Show, forall x.
Rep GetDiskSnapshotsResponse x -> GetDiskSnapshotsResponse
forall x.
GetDiskSnapshotsResponse -> Rep GetDiskSnapshotsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDiskSnapshotsResponse x -> GetDiskSnapshotsResponse
$cfrom :: forall x.
GetDiskSnapshotsResponse -> Rep GetDiskSnapshotsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDiskSnapshotsResponse' 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:
--
-- 'diskSnapshots', 'getDiskSnapshotsResponse_diskSnapshots' - An array of objects containing information about all block storage disk
-- snapshots.
--
-- 'nextPageToken', 'getDiskSnapshotsResponse_nextPageToken' - The token to advance to the next page of results from your request.
--
-- A next page token is not returned if there are no more results to
-- display.
--
-- To get the next page of results, perform another @GetDiskSnapshots@
-- request and specify the next page token using the @pageToken@ parameter.
--
-- 'httpStatus', 'getDiskSnapshotsResponse_httpStatus' - The response's http status code.
newGetDiskSnapshotsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDiskSnapshotsResponse
newGetDiskSnapshotsResponse :: Int -> GetDiskSnapshotsResponse
newGetDiskSnapshotsResponse Int
pHttpStatus_ =
  GetDiskSnapshotsResponse'
    { $sel:diskSnapshots:GetDiskSnapshotsResponse' :: Maybe [DiskSnapshot]
diskSnapshots =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextPageToken:GetDiskSnapshotsResponse' :: Maybe Text
nextPageToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDiskSnapshotsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects containing information about all block storage disk
-- snapshots.
getDiskSnapshotsResponse_diskSnapshots :: Lens.Lens' GetDiskSnapshotsResponse (Prelude.Maybe [DiskSnapshot])
getDiskSnapshotsResponse_diskSnapshots :: Lens' GetDiskSnapshotsResponse (Maybe [DiskSnapshot])
getDiskSnapshotsResponse_diskSnapshots = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDiskSnapshotsResponse' {Maybe [DiskSnapshot]
diskSnapshots :: Maybe [DiskSnapshot]
$sel:diskSnapshots:GetDiskSnapshotsResponse' :: GetDiskSnapshotsResponse -> Maybe [DiskSnapshot]
diskSnapshots} -> Maybe [DiskSnapshot]
diskSnapshots) (\s :: GetDiskSnapshotsResponse
s@GetDiskSnapshotsResponse' {} Maybe [DiskSnapshot]
a -> GetDiskSnapshotsResponse
s {$sel:diskSnapshots:GetDiskSnapshotsResponse' :: Maybe [DiskSnapshot]
diskSnapshots = Maybe [DiskSnapshot]
a} :: GetDiskSnapshotsResponse) 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 token to advance to the next page of results from your request.
--
-- A next page token is not returned if there are no more results to
-- display.
--
-- To get the next page of results, perform another @GetDiskSnapshots@
-- request and specify the next page token using the @pageToken@ parameter.
getDiskSnapshotsResponse_nextPageToken :: Lens.Lens' GetDiskSnapshotsResponse (Prelude.Maybe Prelude.Text)
getDiskSnapshotsResponse_nextPageToken :: Lens' GetDiskSnapshotsResponse (Maybe Text)
getDiskSnapshotsResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDiskSnapshotsResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:GetDiskSnapshotsResponse' :: GetDiskSnapshotsResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: GetDiskSnapshotsResponse
s@GetDiskSnapshotsResponse' {} Maybe Text
a -> GetDiskSnapshotsResponse
s {$sel:nextPageToken:GetDiskSnapshotsResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: GetDiskSnapshotsResponse)

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

instance Prelude.NFData GetDiskSnapshotsResponse where
  rnf :: GetDiskSnapshotsResponse -> ()
rnf GetDiskSnapshotsResponse' {Int
Maybe [DiskSnapshot]
Maybe Text
httpStatus :: Int
nextPageToken :: Maybe Text
diskSnapshots :: Maybe [DiskSnapshot]
$sel:httpStatus:GetDiskSnapshotsResponse' :: GetDiskSnapshotsResponse -> Int
$sel:nextPageToken:GetDiskSnapshotsResponse' :: GetDiskSnapshotsResponse -> Maybe Text
$sel:diskSnapshots:GetDiskSnapshotsResponse' :: GetDiskSnapshotsResponse -> Maybe [DiskSnapshot]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [DiskSnapshot]
diskSnapshots
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPageToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus