{-# 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.CloudWatchEvents.ListArchives
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists your archives. You can either list all the archives or you can
-- provide a prefix to match to the archive names. Filter parameters are
-- exclusive.
module Amazonka.CloudWatchEvents.ListArchives
  ( -- * Creating a Request
    ListArchives (..),
    newListArchives,

    -- * Request Lenses
    listArchives_eventSourceArn,
    listArchives_limit,
    listArchives_namePrefix,
    listArchives_nextToken,
    listArchives_state,

    -- * Destructuring the Response
    ListArchivesResponse (..),
    newListArchivesResponse,

    -- * Response Lenses
    listArchivesResponse_archives,
    listArchivesResponse_nextToken,
    listArchivesResponse_httpStatus,
  )
where

import Amazonka.CloudWatchEvents.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListArchives' smart constructor.
data ListArchives = ListArchives'
  { -- | The ARN of the event source associated with the archive.
    ListArchives -> Maybe Text
eventSourceArn :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of results to return.
    ListArchives -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | A name prefix to filter the archives returned. Only archives with name
    -- that match the prefix are returned.
    ListArchives -> Maybe Text
namePrefix :: Prelude.Maybe Prelude.Text,
    -- | The token returned by a previous call to retrieve the next set of
    -- results.
    ListArchives -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The state of the archive.
    ListArchives -> Maybe ArchiveState
state :: Prelude.Maybe ArchiveState
  }
  deriving (ListArchives -> ListArchives -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListArchives -> ListArchives -> Bool
$c/= :: ListArchives -> ListArchives -> Bool
== :: ListArchives -> ListArchives -> Bool
$c== :: ListArchives -> ListArchives -> Bool
Prelude.Eq, ReadPrec [ListArchives]
ReadPrec ListArchives
Int -> ReadS ListArchives
ReadS [ListArchives]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListArchives]
$creadListPrec :: ReadPrec [ListArchives]
readPrec :: ReadPrec ListArchives
$creadPrec :: ReadPrec ListArchives
readList :: ReadS [ListArchives]
$creadList :: ReadS [ListArchives]
readsPrec :: Int -> ReadS ListArchives
$creadsPrec :: Int -> ReadS ListArchives
Prelude.Read, Int -> ListArchives -> ShowS
[ListArchives] -> ShowS
ListArchives -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListArchives] -> ShowS
$cshowList :: [ListArchives] -> ShowS
show :: ListArchives -> String
$cshow :: ListArchives -> String
showsPrec :: Int -> ListArchives -> ShowS
$cshowsPrec :: Int -> ListArchives -> ShowS
Prelude.Show, forall x. Rep ListArchives x -> ListArchives
forall x. ListArchives -> Rep ListArchives x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListArchives x -> ListArchives
$cfrom :: forall x. ListArchives -> Rep ListArchives x
Prelude.Generic)

-- |
-- Create a value of 'ListArchives' 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:
--
-- 'eventSourceArn', 'listArchives_eventSourceArn' - The ARN of the event source associated with the archive.
--
-- 'limit', 'listArchives_limit' - The maximum number of results to return.
--
-- 'namePrefix', 'listArchives_namePrefix' - A name prefix to filter the archives returned. Only archives with name
-- that match the prefix are returned.
--
-- 'nextToken', 'listArchives_nextToken' - The token returned by a previous call to retrieve the next set of
-- results.
--
-- 'state', 'listArchives_state' - The state of the archive.
newListArchives ::
  ListArchives
newListArchives :: ListArchives
newListArchives =
  ListArchives'
    { $sel:eventSourceArn:ListArchives' :: Maybe Text
eventSourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ListArchives' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:namePrefix:ListArchives' :: Maybe Text
namePrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListArchives' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:state:ListArchives' :: Maybe ArchiveState
state = forall a. Maybe a
Prelude.Nothing
    }

-- | The ARN of the event source associated with the archive.
listArchives_eventSourceArn :: Lens.Lens' ListArchives (Prelude.Maybe Prelude.Text)
listArchives_eventSourceArn :: Lens' ListArchives (Maybe Text)
listArchives_eventSourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArchives' {Maybe Text
eventSourceArn :: Maybe Text
$sel:eventSourceArn:ListArchives' :: ListArchives -> Maybe Text
eventSourceArn} -> Maybe Text
eventSourceArn) (\s :: ListArchives
s@ListArchives' {} Maybe Text
a -> ListArchives
s {$sel:eventSourceArn:ListArchives' :: Maybe Text
eventSourceArn = Maybe Text
a} :: ListArchives)

-- | The maximum number of results to return.
listArchives_limit :: Lens.Lens' ListArchives (Prelude.Maybe Prelude.Natural)
listArchives_limit :: Lens' ListArchives (Maybe Natural)
listArchives_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArchives' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListArchives' :: ListArchives -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListArchives
s@ListArchives' {} Maybe Natural
a -> ListArchives
s {$sel:limit:ListArchives' :: Maybe Natural
limit = Maybe Natural
a} :: ListArchives)

-- | A name prefix to filter the archives returned. Only archives with name
-- that match the prefix are returned.
listArchives_namePrefix :: Lens.Lens' ListArchives (Prelude.Maybe Prelude.Text)
listArchives_namePrefix :: Lens' ListArchives (Maybe Text)
listArchives_namePrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArchives' {Maybe Text
namePrefix :: Maybe Text
$sel:namePrefix:ListArchives' :: ListArchives -> Maybe Text
namePrefix} -> Maybe Text
namePrefix) (\s :: ListArchives
s@ListArchives' {} Maybe Text
a -> ListArchives
s {$sel:namePrefix:ListArchives' :: Maybe Text
namePrefix = Maybe Text
a} :: ListArchives)

-- | The token returned by a previous call to retrieve the next set of
-- results.
listArchives_nextToken :: Lens.Lens' ListArchives (Prelude.Maybe Prelude.Text)
listArchives_nextToken :: Lens' ListArchives (Maybe Text)
listArchives_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArchives' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListArchives' :: ListArchives -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListArchives
s@ListArchives' {} Maybe Text
a -> ListArchives
s {$sel:nextToken:ListArchives' :: Maybe Text
nextToken = Maybe Text
a} :: ListArchives)

-- | The state of the archive.
listArchives_state :: Lens.Lens' ListArchives (Prelude.Maybe ArchiveState)
listArchives_state :: Lens' ListArchives (Maybe ArchiveState)
listArchives_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArchives' {Maybe ArchiveState
state :: Maybe ArchiveState
$sel:state:ListArchives' :: ListArchives -> Maybe ArchiveState
state} -> Maybe ArchiveState
state) (\s :: ListArchives
s@ListArchives' {} Maybe ArchiveState
a -> ListArchives
s {$sel:state:ListArchives' :: Maybe ArchiveState
state = Maybe ArchiveState
a} :: ListArchives)

instance Core.AWSRequest ListArchives where
  type AWSResponse ListArchives = ListArchivesResponse
  request :: (Service -> Service) -> ListArchives -> Request ListArchives
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 ListArchives
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListArchives)))
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 [Archive] -> Maybe Text -> Int -> ListArchivesResponse
ListArchivesResponse'
            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
"Archives" 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
"NextToken")
            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 ListArchives where
  hashWithSalt :: Int -> ListArchives -> Int
hashWithSalt Int
_salt ListArchives' {Maybe Natural
Maybe Text
Maybe ArchiveState
state :: Maybe ArchiveState
nextToken :: Maybe Text
namePrefix :: Maybe Text
limit :: Maybe Natural
eventSourceArn :: Maybe Text
$sel:state:ListArchives' :: ListArchives -> Maybe ArchiveState
$sel:nextToken:ListArchives' :: ListArchives -> Maybe Text
$sel:namePrefix:ListArchives' :: ListArchives -> Maybe Text
$sel:limit:ListArchives' :: ListArchives -> Maybe Natural
$sel:eventSourceArn:ListArchives' :: ListArchives -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
eventSourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
namePrefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ArchiveState
state

instance Prelude.NFData ListArchives where
  rnf :: ListArchives -> ()
rnf ListArchives' {Maybe Natural
Maybe Text
Maybe ArchiveState
state :: Maybe ArchiveState
nextToken :: Maybe Text
namePrefix :: Maybe Text
limit :: Maybe Natural
eventSourceArn :: Maybe Text
$sel:state:ListArchives' :: ListArchives -> Maybe ArchiveState
$sel:nextToken:ListArchives' :: ListArchives -> Maybe Text
$sel:namePrefix:ListArchives' :: ListArchives -> Maybe Text
$sel:limit:ListArchives' :: ListArchives -> Maybe Natural
$sel:eventSourceArn:ListArchives' :: ListArchives -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eventSourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
namePrefix
      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 ArchiveState
state

instance Data.ToHeaders ListArchives where
  toHeaders :: ListArchives -> 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
"AWSEvents.ListArchives" :: 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 ListArchives where
  toJSON :: ListArchives -> Value
toJSON ListArchives' {Maybe Natural
Maybe Text
Maybe ArchiveState
state :: Maybe ArchiveState
nextToken :: Maybe Text
namePrefix :: Maybe Text
limit :: Maybe Natural
eventSourceArn :: Maybe Text
$sel:state:ListArchives' :: ListArchives -> Maybe ArchiveState
$sel:nextToken:ListArchives' :: ListArchives -> Maybe Text
$sel:namePrefix:ListArchives' :: ListArchives -> Maybe Text
$sel:limit:ListArchives' :: ListArchives -> Maybe Natural
$sel:eventSourceArn:ListArchives' :: ListArchives -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"EventSourceArn" 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
eventSourceArn,
            (Key
"Limit" 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 Natural
limit,
            (Key
"NamePrefix" 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
namePrefix,
            (Key
"NextToken" 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
nextToken,
            (Key
"State" 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 ArchiveState
state
          ]
      )

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

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

-- | /See:/ 'newListArchivesResponse' smart constructor.
data ListArchivesResponse = ListArchivesResponse'
  { -- | An array of @Archive@ objects that include details about an archive.
    ListArchivesResponse -> Maybe [Archive]
archives :: Prelude.Maybe [Archive],
    -- | The token returned by a previous call to retrieve the next set of
    -- results.
    ListArchivesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListArchivesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListArchivesResponse -> ListArchivesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListArchivesResponse -> ListArchivesResponse -> Bool
$c/= :: ListArchivesResponse -> ListArchivesResponse -> Bool
== :: ListArchivesResponse -> ListArchivesResponse -> Bool
$c== :: ListArchivesResponse -> ListArchivesResponse -> Bool
Prelude.Eq, ReadPrec [ListArchivesResponse]
ReadPrec ListArchivesResponse
Int -> ReadS ListArchivesResponse
ReadS [ListArchivesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListArchivesResponse]
$creadListPrec :: ReadPrec [ListArchivesResponse]
readPrec :: ReadPrec ListArchivesResponse
$creadPrec :: ReadPrec ListArchivesResponse
readList :: ReadS [ListArchivesResponse]
$creadList :: ReadS [ListArchivesResponse]
readsPrec :: Int -> ReadS ListArchivesResponse
$creadsPrec :: Int -> ReadS ListArchivesResponse
Prelude.Read, Int -> ListArchivesResponse -> ShowS
[ListArchivesResponse] -> ShowS
ListArchivesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListArchivesResponse] -> ShowS
$cshowList :: [ListArchivesResponse] -> ShowS
show :: ListArchivesResponse -> String
$cshow :: ListArchivesResponse -> String
showsPrec :: Int -> ListArchivesResponse -> ShowS
$cshowsPrec :: Int -> ListArchivesResponse -> ShowS
Prelude.Show, forall x. Rep ListArchivesResponse x -> ListArchivesResponse
forall x. ListArchivesResponse -> Rep ListArchivesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListArchivesResponse x -> ListArchivesResponse
$cfrom :: forall x. ListArchivesResponse -> Rep ListArchivesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListArchivesResponse' 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:
--
-- 'archives', 'listArchivesResponse_archives' - An array of @Archive@ objects that include details about an archive.
--
-- 'nextToken', 'listArchivesResponse_nextToken' - The token returned by a previous call to retrieve the next set of
-- results.
--
-- 'httpStatus', 'listArchivesResponse_httpStatus' - The response's http status code.
newListArchivesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListArchivesResponse
newListArchivesResponse :: Int -> ListArchivesResponse
newListArchivesResponse Int
pHttpStatus_ =
  ListArchivesResponse'
    { $sel:archives:ListArchivesResponse' :: Maybe [Archive]
archives = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListArchivesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListArchivesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of @Archive@ objects that include details about an archive.
listArchivesResponse_archives :: Lens.Lens' ListArchivesResponse (Prelude.Maybe [Archive])
listArchivesResponse_archives :: Lens' ListArchivesResponse (Maybe [Archive])
listArchivesResponse_archives = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArchivesResponse' {Maybe [Archive]
archives :: Maybe [Archive]
$sel:archives:ListArchivesResponse' :: ListArchivesResponse -> Maybe [Archive]
archives} -> Maybe [Archive]
archives) (\s :: ListArchivesResponse
s@ListArchivesResponse' {} Maybe [Archive]
a -> ListArchivesResponse
s {$sel:archives:ListArchivesResponse' :: Maybe [Archive]
archives = Maybe [Archive]
a} :: ListArchivesResponse) 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 returned by a previous call to retrieve the next set of
-- results.
listArchivesResponse_nextToken :: Lens.Lens' ListArchivesResponse (Prelude.Maybe Prelude.Text)
listArchivesResponse_nextToken :: Lens' ListArchivesResponse (Maybe Text)
listArchivesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArchivesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListArchivesResponse' :: ListArchivesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListArchivesResponse
s@ListArchivesResponse' {} Maybe Text
a -> ListArchivesResponse
s {$sel:nextToken:ListArchivesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListArchivesResponse)

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

instance Prelude.NFData ListArchivesResponse where
  rnf :: ListArchivesResponse -> ()
rnf ListArchivesResponse' {Int
Maybe [Archive]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
archives :: Maybe [Archive]
$sel:httpStatus:ListArchivesResponse' :: ListArchivesResponse -> Int
$sel:nextToken:ListArchivesResponse' :: ListArchivesResponse -> Maybe Text
$sel:archives:ListArchivesResponse' :: ListArchivesResponse -> Maybe [Archive]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Archive]
archives
      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 Int
httpStatus