{-# 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.GetOperations
-- 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 operations.
--
-- Results are returned from oldest to newest, up to a maximum of 200.
-- Results can be paged by making each subsequent call to @GetOperations@
-- use the maximum (last) @statusChangedAt@ value from the previous
-- request.
--
-- This operation returns paginated results.
module Amazonka.Lightsail.GetOperations
  ( -- * Creating a Request
    GetOperations (..),
    newGetOperations,

    -- * Request Lenses
    getOperations_pageToken,

    -- * Destructuring the Response
    GetOperationsResponse (..),
    newGetOperationsResponse,

    -- * Response Lenses
    getOperationsResponse_nextPageToken,
    getOperationsResponse_operations,
    getOperationsResponse_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:/ 'newGetOperations' smart constructor.
data GetOperations = GetOperations'
  { -- | The token to advance to the next page of results from your request.
    --
    -- To get a page token, perform an initial @GetOperations@ 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.
    GetOperations -> Maybe Text
pageToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetOperations -> GetOperations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetOperations -> GetOperations -> Bool
$c/= :: GetOperations -> GetOperations -> Bool
== :: GetOperations -> GetOperations -> Bool
$c== :: GetOperations -> GetOperations -> Bool
Prelude.Eq, ReadPrec [GetOperations]
ReadPrec GetOperations
Int -> ReadS GetOperations
ReadS [GetOperations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetOperations]
$creadListPrec :: ReadPrec [GetOperations]
readPrec :: ReadPrec GetOperations
$creadPrec :: ReadPrec GetOperations
readList :: ReadS [GetOperations]
$creadList :: ReadS [GetOperations]
readsPrec :: Int -> ReadS GetOperations
$creadsPrec :: Int -> ReadS GetOperations
Prelude.Read, Int -> GetOperations -> ShowS
[GetOperations] -> ShowS
GetOperations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetOperations] -> ShowS
$cshowList :: [GetOperations] -> ShowS
show :: GetOperations -> String
$cshow :: GetOperations -> String
showsPrec :: Int -> GetOperations -> ShowS
$cshowsPrec :: Int -> GetOperations -> ShowS
Prelude.Show, forall x. Rep GetOperations x -> GetOperations
forall x. GetOperations -> Rep GetOperations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetOperations x -> GetOperations
$cfrom :: forall x. GetOperations -> Rep GetOperations x
Prelude.Generic)

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

instance Core.AWSPager GetOperations where
  page :: GetOperations -> AWSResponse GetOperations -> Maybe GetOperations
page GetOperations
rq AWSResponse GetOperations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetOperations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetOperationsResponse (Maybe Text)
getOperationsResponse_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 GetOperations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetOperationsResponse (Maybe [Operation])
getOperationsResponse_operations
            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.$ GetOperations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetOperations (Maybe Text)
getOperations_pageToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetOperations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetOperationsResponse (Maybe Text)
getOperationsResponse_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 GetOperations where
  type
    AWSResponse GetOperations =
      GetOperationsResponse
  request :: (Service -> Service) -> GetOperations -> Request GetOperations
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 GetOperations
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetOperations)))
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 -> Maybe [Operation] -> Int -> GetOperationsResponse
GetOperationsResponse'
            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
"nextPageToken")
            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
"operations" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetOperations where
  hashWithSalt :: Int -> GetOperations -> Int
hashWithSalt Int
_salt GetOperations' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetOperations' :: GetOperations -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageToken

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

instance Data.ToHeaders GetOperations where
  toHeaders :: GetOperations -> 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.GetOperations" ::
                          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 GetOperations where
  toJSON :: GetOperations -> Value
toJSON GetOperations' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetOperations' :: GetOperations -> 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 GetOperations where
  toPath :: GetOperations -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetOperationsResponse' smart constructor.
data GetOperationsResponse = GetOperationsResponse'
  { -- | 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 @GetOperations@ request
    -- and specify the next page token using the @pageToken@ parameter.
    GetOperationsResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | An array of objects that describe the result of the action, such as the
    -- status of the request, the timestamp of the request, and the resources
    -- affected by the request.
    GetOperationsResponse -> Maybe [Operation]
operations :: Prelude.Maybe [Operation],
    -- | The response's http status code.
    GetOperationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetOperationsResponse -> GetOperationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetOperationsResponse -> GetOperationsResponse -> Bool
$c/= :: GetOperationsResponse -> GetOperationsResponse -> Bool
== :: GetOperationsResponse -> GetOperationsResponse -> Bool
$c== :: GetOperationsResponse -> GetOperationsResponse -> Bool
Prelude.Eq, ReadPrec [GetOperationsResponse]
ReadPrec GetOperationsResponse
Int -> ReadS GetOperationsResponse
ReadS [GetOperationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetOperationsResponse]
$creadListPrec :: ReadPrec [GetOperationsResponse]
readPrec :: ReadPrec GetOperationsResponse
$creadPrec :: ReadPrec GetOperationsResponse
readList :: ReadS [GetOperationsResponse]
$creadList :: ReadS [GetOperationsResponse]
readsPrec :: Int -> ReadS GetOperationsResponse
$creadsPrec :: Int -> ReadS GetOperationsResponse
Prelude.Read, Int -> GetOperationsResponse -> ShowS
[GetOperationsResponse] -> ShowS
GetOperationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetOperationsResponse] -> ShowS
$cshowList :: [GetOperationsResponse] -> ShowS
show :: GetOperationsResponse -> String
$cshow :: GetOperationsResponse -> String
showsPrec :: Int -> GetOperationsResponse -> ShowS
$cshowsPrec :: Int -> GetOperationsResponse -> ShowS
Prelude.Show, forall x. Rep GetOperationsResponse x -> GetOperationsResponse
forall x. GetOperationsResponse -> Rep GetOperationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetOperationsResponse x -> GetOperationsResponse
$cfrom :: forall x. GetOperationsResponse -> Rep GetOperationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetOperationsResponse' 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:
--
-- 'nextPageToken', 'getOperationsResponse_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 @GetOperations@ request
-- and specify the next page token using the @pageToken@ parameter.
--
-- 'operations', 'getOperationsResponse_operations' - An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
--
-- 'httpStatus', 'getOperationsResponse_httpStatus' - The response's http status code.
newGetOperationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetOperationsResponse
newGetOperationsResponse :: Int -> GetOperationsResponse
newGetOperationsResponse Int
pHttpStatus_ =
  GetOperationsResponse'
    { $sel:nextPageToken:GetOperationsResponse' :: Maybe Text
nextPageToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:operations:GetOperationsResponse' :: Maybe [Operation]
operations = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetOperationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | 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 @GetOperations@ request
-- and specify the next page token using the @pageToken@ parameter.
getOperationsResponse_nextPageToken :: Lens.Lens' GetOperationsResponse (Prelude.Maybe Prelude.Text)
getOperationsResponse_nextPageToken :: Lens' GetOperationsResponse (Maybe Text)
getOperationsResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetOperationsResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:GetOperationsResponse' :: GetOperationsResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: GetOperationsResponse
s@GetOperationsResponse' {} Maybe Text
a -> GetOperationsResponse
s {$sel:nextPageToken:GetOperationsResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: GetOperationsResponse)

-- | An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
getOperationsResponse_operations :: Lens.Lens' GetOperationsResponse (Prelude.Maybe [Operation])
getOperationsResponse_operations :: Lens' GetOperationsResponse (Maybe [Operation])
getOperationsResponse_operations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetOperationsResponse' {Maybe [Operation]
operations :: Maybe [Operation]
$sel:operations:GetOperationsResponse' :: GetOperationsResponse -> Maybe [Operation]
operations} -> Maybe [Operation]
operations) (\s :: GetOperationsResponse
s@GetOperationsResponse' {} Maybe [Operation]
a -> GetOperationsResponse
s {$sel:operations:GetOperationsResponse' :: Maybe [Operation]
operations = Maybe [Operation]
a} :: GetOperationsResponse) 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 response's http status code.
getOperationsResponse_httpStatus :: Lens.Lens' GetOperationsResponse Prelude.Int
getOperationsResponse_httpStatus :: Lens' GetOperationsResponse Int
getOperationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetOperationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetOperationsResponse' :: GetOperationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetOperationsResponse
s@GetOperationsResponse' {} Int
a -> GetOperationsResponse
s {$sel:httpStatus:GetOperationsResponse' :: Int
httpStatus = Int
a} :: GetOperationsResponse)

instance Prelude.NFData GetOperationsResponse where
  rnf :: GetOperationsResponse -> ()
rnf GetOperationsResponse' {Int
Maybe [Operation]
Maybe Text
httpStatus :: Int
operations :: Maybe [Operation]
nextPageToken :: Maybe Text
$sel:httpStatus:GetOperationsResponse' :: GetOperationsResponse -> Int
$sel:operations:GetOperationsResponse' :: GetOperationsResponse -> Maybe [Operation]
$sel:nextPageToken:GetOperationsResponse' :: GetOperationsResponse -> Maybe Text
..} =
    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 Maybe [Operation]
operations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus