{-# 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.NetworkManager.ListAttachments
-- 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 a list of core network attachments.
--
-- This operation returns paginated results.
module Amazonka.NetworkManager.ListAttachments
  ( -- * Creating a Request
    ListAttachments (..),
    newListAttachments,

    -- * Request Lenses
    listAttachments_attachmentType,
    listAttachments_coreNetworkId,
    listAttachments_edgeLocation,
    listAttachments_maxResults,
    listAttachments_nextToken,
    listAttachments_state,

    -- * Destructuring the Response
    ListAttachmentsResponse (..),
    newListAttachmentsResponse,

    -- * Response Lenses
    listAttachmentsResponse_attachments,
    listAttachmentsResponse_nextToken,
    listAttachmentsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListAttachments' smart constructor.
data ListAttachments = ListAttachments'
  { -- | The type of attachment.
    ListAttachments -> Maybe AttachmentType
attachmentType :: Prelude.Maybe AttachmentType,
    -- | The ID of a core network.
    ListAttachments -> Maybe Text
coreNetworkId :: Prelude.Maybe Prelude.Text,
    -- | The Region where the edge is located.
    ListAttachments -> Maybe Text
edgeLocation :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of results to return.
    ListAttachments -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next page of results.
    ListAttachments -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The state of the attachment.
    ListAttachments -> Maybe AttachmentState
state :: Prelude.Maybe AttachmentState
  }
  deriving (ListAttachments -> ListAttachments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAttachments -> ListAttachments -> Bool
$c/= :: ListAttachments -> ListAttachments -> Bool
== :: ListAttachments -> ListAttachments -> Bool
$c== :: ListAttachments -> ListAttachments -> Bool
Prelude.Eq, ReadPrec [ListAttachments]
ReadPrec ListAttachments
Int -> ReadS ListAttachments
ReadS [ListAttachments]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAttachments]
$creadListPrec :: ReadPrec [ListAttachments]
readPrec :: ReadPrec ListAttachments
$creadPrec :: ReadPrec ListAttachments
readList :: ReadS [ListAttachments]
$creadList :: ReadS [ListAttachments]
readsPrec :: Int -> ReadS ListAttachments
$creadsPrec :: Int -> ReadS ListAttachments
Prelude.Read, Int -> ListAttachments -> ShowS
[ListAttachments] -> ShowS
ListAttachments -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAttachments] -> ShowS
$cshowList :: [ListAttachments] -> ShowS
show :: ListAttachments -> String
$cshow :: ListAttachments -> String
showsPrec :: Int -> ListAttachments -> ShowS
$cshowsPrec :: Int -> ListAttachments -> ShowS
Prelude.Show, forall x. Rep ListAttachments x -> ListAttachments
forall x. ListAttachments -> Rep ListAttachments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAttachments x -> ListAttachments
$cfrom :: forall x. ListAttachments -> Rep ListAttachments x
Prelude.Generic)

-- |
-- Create a value of 'ListAttachments' 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:
--
-- 'attachmentType', 'listAttachments_attachmentType' - The type of attachment.
--
-- 'coreNetworkId', 'listAttachments_coreNetworkId' - The ID of a core network.
--
-- 'edgeLocation', 'listAttachments_edgeLocation' - The Region where the edge is located.
--
-- 'maxResults', 'listAttachments_maxResults' - The maximum number of results to return.
--
-- 'nextToken', 'listAttachments_nextToken' - The token for the next page of results.
--
-- 'state', 'listAttachments_state' - The state of the attachment.
newListAttachments ::
  ListAttachments
newListAttachments :: ListAttachments
newListAttachments =
  ListAttachments'
    { $sel:attachmentType:ListAttachments' :: Maybe AttachmentType
attachmentType = forall a. Maybe a
Prelude.Nothing,
      $sel:coreNetworkId:ListAttachments' :: Maybe Text
coreNetworkId = forall a. Maybe a
Prelude.Nothing,
      $sel:edgeLocation:ListAttachments' :: Maybe Text
edgeLocation = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListAttachments' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAttachments' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:state:ListAttachments' :: Maybe AttachmentState
state = forall a. Maybe a
Prelude.Nothing
    }

-- | The type of attachment.
listAttachments_attachmentType :: Lens.Lens' ListAttachments (Prelude.Maybe AttachmentType)
listAttachments_attachmentType :: Lens' ListAttachments (Maybe AttachmentType)
listAttachments_attachmentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAttachments' {Maybe AttachmentType
attachmentType :: Maybe AttachmentType
$sel:attachmentType:ListAttachments' :: ListAttachments -> Maybe AttachmentType
attachmentType} -> Maybe AttachmentType
attachmentType) (\s :: ListAttachments
s@ListAttachments' {} Maybe AttachmentType
a -> ListAttachments
s {$sel:attachmentType:ListAttachments' :: Maybe AttachmentType
attachmentType = Maybe AttachmentType
a} :: ListAttachments)

-- | The ID of a core network.
listAttachments_coreNetworkId :: Lens.Lens' ListAttachments (Prelude.Maybe Prelude.Text)
listAttachments_coreNetworkId :: Lens' ListAttachments (Maybe Text)
listAttachments_coreNetworkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAttachments' {Maybe Text
coreNetworkId :: Maybe Text
$sel:coreNetworkId:ListAttachments' :: ListAttachments -> Maybe Text
coreNetworkId} -> Maybe Text
coreNetworkId) (\s :: ListAttachments
s@ListAttachments' {} Maybe Text
a -> ListAttachments
s {$sel:coreNetworkId:ListAttachments' :: Maybe Text
coreNetworkId = Maybe Text
a} :: ListAttachments)

-- | The Region where the edge is located.
listAttachments_edgeLocation :: Lens.Lens' ListAttachments (Prelude.Maybe Prelude.Text)
listAttachments_edgeLocation :: Lens' ListAttachments (Maybe Text)
listAttachments_edgeLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAttachments' {Maybe Text
edgeLocation :: Maybe Text
$sel:edgeLocation:ListAttachments' :: ListAttachments -> Maybe Text
edgeLocation} -> Maybe Text
edgeLocation) (\s :: ListAttachments
s@ListAttachments' {} Maybe Text
a -> ListAttachments
s {$sel:edgeLocation:ListAttachments' :: Maybe Text
edgeLocation = Maybe Text
a} :: ListAttachments)

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

-- | The token for the next page of results.
listAttachments_nextToken :: Lens.Lens' ListAttachments (Prelude.Maybe Prelude.Text)
listAttachments_nextToken :: Lens' ListAttachments (Maybe Text)
listAttachments_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAttachments' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAttachments' :: ListAttachments -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAttachments
s@ListAttachments' {} Maybe Text
a -> ListAttachments
s {$sel:nextToken:ListAttachments' :: Maybe Text
nextToken = Maybe Text
a} :: ListAttachments)

-- | The state of the attachment.
listAttachments_state :: Lens.Lens' ListAttachments (Prelude.Maybe AttachmentState)
listAttachments_state :: Lens' ListAttachments (Maybe AttachmentState)
listAttachments_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAttachments' {Maybe AttachmentState
state :: Maybe AttachmentState
$sel:state:ListAttachments' :: ListAttachments -> Maybe AttachmentState
state} -> Maybe AttachmentState
state) (\s :: ListAttachments
s@ListAttachments' {} Maybe AttachmentState
a -> ListAttachments
s {$sel:state:ListAttachments' :: Maybe AttachmentState
state = Maybe AttachmentState
a} :: ListAttachments)

instance Core.AWSPager ListAttachments where
  page :: ListAttachments
-> AWSResponse ListAttachments -> Maybe ListAttachments
page ListAttachments
rq AWSResponse ListAttachments
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListAttachments
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAttachmentsResponse (Maybe Text)
listAttachmentsResponse_nextToken
            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 ListAttachments
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAttachmentsResponse (Maybe [Attachment])
listAttachmentsResponse_attachments
            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.$ ListAttachments
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAttachments (Maybe Text)
listAttachments_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAttachments
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAttachmentsResponse (Maybe Text)
listAttachmentsResponse_nextToken
          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 ListAttachments where
  type
    AWSResponse ListAttachments =
      ListAttachmentsResponse
  request :: (Service -> Service) -> ListAttachments -> Request ListAttachments
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 ListAttachments
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListAttachments)))
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 [Attachment] -> Maybe Text -> Int -> ListAttachmentsResponse
ListAttachmentsResponse'
            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
"Attachments" 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 ListAttachments where
  hashWithSalt :: Int -> ListAttachments -> Int
hashWithSalt Int
_salt ListAttachments' {Maybe Natural
Maybe Text
Maybe AttachmentState
Maybe AttachmentType
state :: Maybe AttachmentState
nextToken :: Maybe Text
maxResults :: Maybe Natural
edgeLocation :: Maybe Text
coreNetworkId :: Maybe Text
attachmentType :: Maybe AttachmentType
$sel:state:ListAttachments' :: ListAttachments -> Maybe AttachmentState
$sel:nextToken:ListAttachments' :: ListAttachments -> Maybe Text
$sel:maxResults:ListAttachments' :: ListAttachments -> Maybe Natural
$sel:edgeLocation:ListAttachments' :: ListAttachments -> Maybe Text
$sel:coreNetworkId:ListAttachments' :: ListAttachments -> Maybe Text
$sel:attachmentType:ListAttachments' :: ListAttachments -> Maybe AttachmentType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttachmentType
attachmentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
coreNetworkId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
edgeLocation
      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 AttachmentState
state

instance Prelude.NFData ListAttachments where
  rnf :: ListAttachments -> ()
rnf ListAttachments' {Maybe Natural
Maybe Text
Maybe AttachmentState
Maybe AttachmentType
state :: Maybe AttachmentState
nextToken :: Maybe Text
maxResults :: Maybe Natural
edgeLocation :: Maybe Text
coreNetworkId :: Maybe Text
attachmentType :: Maybe AttachmentType
$sel:state:ListAttachments' :: ListAttachments -> Maybe AttachmentState
$sel:nextToken:ListAttachments' :: ListAttachments -> Maybe Text
$sel:maxResults:ListAttachments' :: ListAttachments -> Maybe Natural
$sel:edgeLocation:ListAttachments' :: ListAttachments -> Maybe Text
$sel:coreNetworkId:ListAttachments' :: ListAttachments -> Maybe Text
$sel:attachmentType:ListAttachments' :: ListAttachments -> Maybe AttachmentType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AttachmentType
attachmentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
coreNetworkId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
edgeLocation
      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 AttachmentState
state

instance Data.ToHeaders ListAttachments where
  toHeaders :: ListAttachments -> 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 ListAttachments where
  toPath :: ListAttachments -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/attachments"

instance Data.ToQuery ListAttachments where
  toQuery :: ListAttachments -> QueryString
toQuery ListAttachments' {Maybe Natural
Maybe Text
Maybe AttachmentState
Maybe AttachmentType
state :: Maybe AttachmentState
nextToken :: Maybe Text
maxResults :: Maybe Natural
edgeLocation :: Maybe Text
coreNetworkId :: Maybe Text
attachmentType :: Maybe AttachmentType
$sel:state:ListAttachments' :: ListAttachments -> Maybe AttachmentState
$sel:nextToken:ListAttachments' :: ListAttachments -> Maybe Text
$sel:maxResults:ListAttachments' :: ListAttachments -> Maybe Natural
$sel:edgeLocation:ListAttachments' :: ListAttachments -> Maybe Text
$sel:coreNetworkId:ListAttachments' :: ListAttachments -> Maybe Text
$sel:attachmentType:ListAttachments' :: ListAttachments -> Maybe AttachmentType
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"attachmentType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttachmentType
attachmentType,
        ByteString
"coreNetworkId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
coreNetworkId,
        ByteString
"edgeLocation" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
edgeLocation,
        ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"state" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttachmentState
state
      ]

-- | /See:/ 'newListAttachmentsResponse' smart constructor.
data ListAttachmentsResponse = ListAttachmentsResponse'
  { -- | Describes the list of attachments.
    ListAttachmentsResponse -> Maybe [Attachment]
attachments :: Prelude.Maybe [Attachment],
    -- | The token for the next page of results.
    ListAttachmentsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAttachmentsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListAttachmentsResponse -> ListAttachmentsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAttachmentsResponse -> ListAttachmentsResponse -> Bool
$c/= :: ListAttachmentsResponse -> ListAttachmentsResponse -> Bool
== :: ListAttachmentsResponse -> ListAttachmentsResponse -> Bool
$c== :: ListAttachmentsResponse -> ListAttachmentsResponse -> Bool
Prelude.Eq, ReadPrec [ListAttachmentsResponse]
ReadPrec ListAttachmentsResponse
Int -> ReadS ListAttachmentsResponse
ReadS [ListAttachmentsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAttachmentsResponse]
$creadListPrec :: ReadPrec [ListAttachmentsResponse]
readPrec :: ReadPrec ListAttachmentsResponse
$creadPrec :: ReadPrec ListAttachmentsResponse
readList :: ReadS [ListAttachmentsResponse]
$creadList :: ReadS [ListAttachmentsResponse]
readsPrec :: Int -> ReadS ListAttachmentsResponse
$creadsPrec :: Int -> ReadS ListAttachmentsResponse
Prelude.Read, Int -> ListAttachmentsResponse -> ShowS
[ListAttachmentsResponse] -> ShowS
ListAttachmentsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAttachmentsResponse] -> ShowS
$cshowList :: [ListAttachmentsResponse] -> ShowS
show :: ListAttachmentsResponse -> String
$cshow :: ListAttachmentsResponse -> String
showsPrec :: Int -> ListAttachmentsResponse -> ShowS
$cshowsPrec :: Int -> ListAttachmentsResponse -> ShowS
Prelude.Show, forall x. Rep ListAttachmentsResponse x -> ListAttachmentsResponse
forall x. ListAttachmentsResponse -> Rep ListAttachmentsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAttachmentsResponse x -> ListAttachmentsResponse
$cfrom :: forall x. ListAttachmentsResponse -> Rep ListAttachmentsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAttachmentsResponse' 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:
--
-- 'attachments', 'listAttachmentsResponse_attachments' - Describes the list of attachments.
--
-- 'nextToken', 'listAttachmentsResponse_nextToken' - The token for the next page of results.
--
-- 'httpStatus', 'listAttachmentsResponse_httpStatus' - The response's http status code.
newListAttachmentsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAttachmentsResponse
newListAttachmentsResponse :: Int -> ListAttachmentsResponse
newListAttachmentsResponse Int
pHttpStatus_ =
  ListAttachmentsResponse'
    { $sel:attachments:ListAttachmentsResponse' :: Maybe [Attachment]
attachments =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAttachmentsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAttachmentsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Describes the list of attachments.
listAttachmentsResponse_attachments :: Lens.Lens' ListAttachmentsResponse (Prelude.Maybe [Attachment])
listAttachmentsResponse_attachments :: Lens' ListAttachmentsResponse (Maybe [Attachment])
listAttachmentsResponse_attachments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAttachmentsResponse' {Maybe [Attachment]
attachments :: Maybe [Attachment]
$sel:attachments:ListAttachmentsResponse' :: ListAttachmentsResponse -> Maybe [Attachment]
attachments} -> Maybe [Attachment]
attachments) (\s :: ListAttachmentsResponse
s@ListAttachmentsResponse' {} Maybe [Attachment]
a -> ListAttachmentsResponse
s {$sel:attachments:ListAttachmentsResponse' :: Maybe [Attachment]
attachments = Maybe [Attachment]
a} :: ListAttachmentsResponse) 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 for the next page of results.
listAttachmentsResponse_nextToken :: Lens.Lens' ListAttachmentsResponse (Prelude.Maybe Prelude.Text)
listAttachmentsResponse_nextToken :: Lens' ListAttachmentsResponse (Maybe Text)
listAttachmentsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAttachmentsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAttachmentsResponse' :: ListAttachmentsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAttachmentsResponse
s@ListAttachmentsResponse' {} Maybe Text
a -> ListAttachmentsResponse
s {$sel:nextToken:ListAttachmentsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAttachmentsResponse)

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

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