{-# 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.GetBundles
-- 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 the bundles that you can apply to an Amazon Lightsail instance
-- when you create it.
--
-- A bundle describes the specifications of an instance, such as the
-- monthly cost, amount of memory, the number of vCPUs, amount of storage
-- space, and monthly network data transfer quota.
--
-- Bundles are referred to as /instance plans/ in the Lightsail console.
--
-- This operation returns paginated results.
module Amazonka.Lightsail.GetBundles
  ( -- * Creating a Request
    GetBundles (..),
    newGetBundles,

    -- * Request Lenses
    getBundles_includeInactive,
    getBundles_pageToken,

    -- * Destructuring the Response
    GetBundlesResponse (..),
    newGetBundlesResponse,

    -- * Response Lenses
    getBundlesResponse_bundles,
    getBundlesResponse_nextPageToken,
    getBundlesResponse_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:/ 'newGetBundles' smart constructor.
data GetBundles = GetBundles'
  { -- | A Boolean value that indicates whether to include inactive (unavailable)
    -- bundles in the response of your request.
    GetBundles -> Maybe Bool
includeInactive :: Prelude.Maybe Prelude.Bool,
    -- | The token to advance to the next page of results from your request.
    --
    -- To get a page token, perform an initial @GetBundles@ 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.
    GetBundles -> Maybe Text
pageToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetBundles -> GetBundles -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBundles -> GetBundles -> Bool
$c/= :: GetBundles -> GetBundles -> Bool
== :: GetBundles -> GetBundles -> Bool
$c== :: GetBundles -> GetBundles -> Bool
Prelude.Eq, ReadPrec [GetBundles]
ReadPrec GetBundles
Int -> ReadS GetBundles
ReadS [GetBundles]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBundles]
$creadListPrec :: ReadPrec [GetBundles]
readPrec :: ReadPrec GetBundles
$creadPrec :: ReadPrec GetBundles
readList :: ReadS [GetBundles]
$creadList :: ReadS [GetBundles]
readsPrec :: Int -> ReadS GetBundles
$creadsPrec :: Int -> ReadS GetBundles
Prelude.Read, Int -> GetBundles -> ShowS
[GetBundles] -> ShowS
GetBundles -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBundles] -> ShowS
$cshowList :: [GetBundles] -> ShowS
show :: GetBundles -> String
$cshow :: GetBundles -> String
showsPrec :: Int -> GetBundles -> ShowS
$cshowsPrec :: Int -> GetBundles -> ShowS
Prelude.Show, forall x. Rep GetBundles x -> GetBundles
forall x. GetBundles -> Rep GetBundles x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBundles x -> GetBundles
$cfrom :: forall x. GetBundles -> Rep GetBundles x
Prelude.Generic)

-- |
-- Create a value of 'GetBundles' 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:
--
-- 'includeInactive', 'getBundles_includeInactive' - A Boolean value that indicates whether to include inactive (unavailable)
-- bundles in the response of your request.
--
-- 'pageToken', 'getBundles_pageToken' - The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetBundles@ 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.
newGetBundles ::
  GetBundles
newGetBundles :: GetBundles
newGetBundles =
  GetBundles'
    { $sel:includeInactive:GetBundles' :: Maybe Bool
includeInactive = forall a. Maybe a
Prelude.Nothing,
      $sel:pageToken:GetBundles' :: Maybe Text
pageToken = forall a. Maybe a
Prelude.Nothing
    }

-- | A Boolean value that indicates whether to include inactive (unavailable)
-- bundles in the response of your request.
getBundles_includeInactive :: Lens.Lens' GetBundles (Prelude.Maybe Prelude.Bool)
getBundles_includeInactive :: Lens' GetBundles (Maybe Bool)
getBundles_includeInactive = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBundles' {Maybe Bool
includeInactive :: Maybe Bool
$sel:includeInactive:GetBundles' :: GetBundles -> Maybe Bool
includeInactive} -> Maybe Bool
includeInactive) (\s :: GetBundles
s@GetBundles' {} Maybe Bool
a -> GetBundles
s {$sel:includeInactive:GetBundles' :: Maybe Bool
includeInactive = Maybe Bool
a} :: GetBundles)

-- | The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetBundles@ 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.
getBundles_pageToken :: Lens.Lens' GetBundles (Prelude.Maybe Prelude.Text)
getBundles_pageToken :: Lens' GetBundles (Maybe Text)
getBundles_pageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBundles' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetBundles' :: GetBundles -> Maybe Text
pageToken} -> Maybe Text
pageToken) (\s :: GetBundles
s@GetBundles' {} Maybe Text
a -> GetBundles
s {$sel:pageToken:GetBundles' :: Maybe Text
pageToken = Maybe Text
a} :: GetBundles)

instance Core.AWSPager GetBundles where
  page :: GetBundles -> AWSResponse GetBundles -> Maybe GetBundles
page GetBundles
rq AWSResponse GetBundles
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetBundles
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetBundlesResponse (Maybe Text)
getBundlesResponse_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 GetBundles
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetBundlesResponse (Maybe [Bundle])
getBundlesResponse_bundles
            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.$ GetBundles
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetBundles (Maybe Text)
getBundles_pageToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetBundles
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetBundlesResponse (Maybe Text)
getBundlesResponse_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 GetBundles where
  type AWSResponse GetBundles = GetBundlesResponse
  request :: (Service -> Service) -> GetBundles -> Request GetBundles
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 GetBundles
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetBundles)))
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 [Bundle] -> Maybe Text -> Int -> GetBundlesResponse
GetBundlesResponse'
            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
"bundles" 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 GetBundles where
  hashWithSalt :: Int -> GetBundles -> Int
hashWithSalt Int
_salt GetBundles' {Maybe Bool
Maybe Text
pageToken :: Maybe Text
includeInactive :: Maybe Bool
$sel:pageToken:GetBundles' :: GetBundles -> Maybe Text
$sel:includeInactive:GetBundles' :: GetBundles -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
includeInactive
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageToken

instance Prelude.NFData GetBundles where
  rnf :: GetBundles -> ()
rnf GetBundles' {Maybe Bool
Maybe Text
pageToken :: Maybe Text
includeInactive :: Maybe Bool
$sel:pageToken:GetBundles' :: GetBundles -> Maybe Text
$sel:includeInactive:GetBundles' :: GetBundles -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeInactive
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageToken

instance Data.ToHeaders GetBundles where
  toHeaders :: GetBundles -> 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.GetBundles" ::
                          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 GetBundles where
  toJSON :: GetBundles -> Value
toJSON GetBundles' {Maybe Bool
Maybe Text
pageToken :: Maybe Text
includeInactive :: Maybe Bool
$sel:pageToken:GetBundles' :: GetBundles -> Maybe Text
$sel:includeInactive:GetBundles' :: GetBundles -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"includeInactive" 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 Bool
includeInactive,
            (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 GetBundles where
  toPath :: GetBundles -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetBundlesResponse' smart constructor.
data GetBundlesResponse = GetBundlesResponse'
  { -- | An array of key-value pairs that contains information about the
    -- available bundles.
    GetBundlesResponse -> Maybe [Bundle]
bundles :: Prelude.Maybe [Bundle],
    -- | 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 @GetBundles@ request
    -- and specify the next page token using the @pageToken@ parameter.
    GetBundlesResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetBundlesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBundlesResponse -> GetBundlesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBundlesResponse -> GetBundlesResponse -> Bool
$c/= :: GetBundlesResponse -> GetBundlesResponse -> Bool
== :: GetBundlesResponse -> GetBundlesResponse -> Bool
$c== :: GetBundlesResponse -> GetBundlesResponse -> Bool
Prelude.Eq, ReadPrec [GetBundlesResponse]
ReadPrec GetBundlesResponse
Int -> ReadS GetBundlesResponse
ReadS [GetBundlesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBundlesResponse]
$creadListPrec :: ReadPrec [GetBundlesResponse]
readPrec :: ReadPrec GetBundlesResponse
$creadPrec :: ReadPrec GetBundlesResponse
readList :: ReadS [GetBundlesResponse]
$creadList :: ReadS [GetBundlesResponse]
readsPrec :: Int -> ReadS GetBundlesResponse
$creadsPrec :: Int -> ReadS GetBundlesResponse
Prelude.Read, Int -> GetBundlesResponse -> ShowS
[GetBundlesResponse] -> ShowS
GetBundlesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBundlesResponse] -> ShowS
$cshowList :: [GetBundlesResponse] -> ShowS
show :: GetBundlesResponse -> String
$cshow :: GetBundlesResponse -> String
showsPrec :: Int -> GetBundlesResponse -> ShowS
$cshowsPrec :: Int -> GetBundlesResponse -> ShowS
Prelude.Show, forall x. Rep GetBundlesResponse x -> GetBundlesResponse
forall x. GetBundlesResponse -> Rep GetBundlesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBundlesResponse x -> GetBundlesResponse
$cfrom :: forall x. GetBundlesResponse -> Rep GetBundlesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBundlesResponse' 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:
--
-- 'bundles', 'getBundlesResponse_bundles' - An array of key-value pairs that contains information about the
-- available bundles.
--
-- 'nextPageToken', 'getBundlesResponse_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 @GetBundles@ request
-- and specify the next page token using the @pageToken@ parameter.
--
-- 'httpStatus', 'getBundlesResponse_httpStatus' - The response's http status code.
newGetBundlesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBundlesResponse
newGetBundlesResponse :: Int -> GetBundlesResponse
newGetBundlesResponse Int
pHttpStatus_ =
  GetBundlesResponse'
    { $sel:bundles:GetBundlesResponse' :: Maybe [Bundle]
bundles = forall a. Maybe a
Prelude.Nothing,
      $sel:nextPageToken:GetBundlesResponse' :: Maybe Text
nextPageToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBundlesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of key-value pairs that contains information about the
-- available bundles.
getBundlesResponse_bundles :: Lens.Lens' GetBundlesResponse (Prelude.Maybe [Bundle])
getBundlesResponse_bundles :: Lens' GetBundlesResponse (Maybe [Bundle])
getBundlesResponse_bundles = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBundlesResponse' {Maybe [Bundle]
bundles :: Maybe [Bundle]
$sel:bundles:GetBundlesResponse' :: GetBundlesResponse -> Maybe [Bundle]
bundles} -> Maybe [Bundle]
bundles) (\s :: GetBundlesResponse
s@GetBundlesResponse' {} Maybe [Bundle]
a -> GetBundlesResponse
s {$sel:bundles:GetBundlesResponse' :: Maybe [Bundle]
bundles = Maybe [Bundle]
a} :: GetBundlesResponse) 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 @GetBundles@ request
-- and specify the next page token using the @pageToken@ parameter.
getBundlesResponse_nextPageToken :: Lens.Lens' GetBundlesResponse (Prelude.Maybe Prelude.Text)
getBundlesResponse_nextPageToken :: Lens' GetBundlesResponse (Maybe Text)
getBundlesResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBundlesResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:GetBundlesResponse' :: GetBundlesResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: GetBundlesResponse
s@GetBundlesResponse' {} Maybe Text
a -> GetBundlesResponse
s {$sel:nextPageToken:GetBundlesResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: GetBundlesResponse)

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

instance Prelude.NFData GetBundlesResponse where
  rnf :: GetBundlesResponse -> ()
rnf GetBundlesResponse' {Int
Maybe [Bundle]
Maybe Text
httpStatus :: Int
nextPageToken :: Maybe Text
bundles :: Maybe [Bundle]
$sel:httpStatus:GetBundlesResponse' :: GetBundlesResponse -> Int
$sel:nextPageToken:GetBundlesResponse' :: GetBundlesResponse -> Maybe Text
$sel:bundles:GetBundlesResponse' :: GetBundlesResponse -> Maybe [Bundle]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Bundle]
bundles
      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