{-# 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.Transfer.ListAgreements
-- 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 the agreements for the server that\'s identified by
-- the @ServerId@ that you supply. If you want to limit the results to a
-- certain number, supply a value for the @MaxResults@ parameter. If you
-- ran the command previously and received a value for @NextToken@, you can
-- supply that value to continue listing agreements from where you left
-- off.
--
-- This operation returns paginated results.
module Amazonka.Transfer.ListAgreements
  ( -- * Creating a Request
    ListAgreements (..),
    newListAgreements,

    -- * Request Lenses
    listAgreements_maxResults,
    listAgreements_nextToken,
    listAgreements_serverId,

    -- * Destructuring the Response
    ListAgreementsResponse (..),
    newListAgreementsResponse,

    -- * Response Lenses
    listAgreementsResponse_nextToken,
    listAgreementsResponse_httpStatus,
    listAgreementsResponse_agreements,
  )
where

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
import Amazonka.Transfer.Types

-- | /See:/ 'newListAgreements' smart constructor.
data ListAgreements = ListAgreements'
  { -- | The maximum number of agreements to return.
    ListAgreements -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | When you can get additional results from the @ListAgreements@ call, a
    -- @NextToken@ parameter is returned in the output. You can then pass in a
    -- subsequent command to the @NextToken@ parameter to continue listing
    -- additional agreements.
    ListAgreements -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the server for which you want a list of agreements.
    ListAgreements -> Text
serverId :: Prelude.Text
  }
  deriving (ListAgreements -> ListAgreements -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAgreements -> ListAgreements -> Bool
$c/= :: ListAgreements -> ListAgreements -> Bool
== :: ListAgreements -> ListAgreements -> Bool
$c== :: ListAgreements -> ListAgreements -> Bool
Prelude.Eq, ReadPrec [ListAgreements]
ReadPrec ListAgreements
Int -> ReadS ListAgreements
ReadS [ListAgreements]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAgreements]
$creadListPrec :: ReadPrec [ListAgreements]
readPrec :: ReadPrec ListAgreements
$creadPrec :: ReadPrec ListAgreements
readList :: ReadS [ListAgreements]
$creadList :: ReadS [ListAgreements]
readsPrec :: Int -> ReadS ListAgreements
$creadsPrec :: Int -> ReadS ListAgreements
Prelude.Read, Int -> ListAgreements -> ShowS
[ListAgreements] -> ShowS
ListAgreements -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAgreements] -> ShowS
$cshowList :: [ListAgreements] -> ShowS
show :: ListAgreements -> String
$cshow :: ListAgreements -> String
showsPrec :: Int -> ListAgreements -> ShowS
$cshowsPrec :: Int -> ListAgreements -> ShowS
Prelude.Show, forall x. Rep ListAgreements x -> ListAgreements
forall x. ListAgreements -> Rep ListAgreements x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAgreements x -> ListAgreements
$cfrom :: forall x. ListAgreements -> Rep ListAgreements x
Prelude.Generic)

-- |
-- Create a value of 'ListAgreements' 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:
--
-- 'maxResults', 'listAgreements_maxResults' - The maximum number of agreements to return.
--
-- 'nextToken', 'listAgreements_nextToken' - When you can get additional results from the @ListAgreements@ call, a
-- @NextToken@ parameter is returned in the output. You can then pass in a
-- subsequent command to the @NextToken@ parameter to continue listing
-- additional agreements.
--
-- 'serverId', 'listAgreements_serverId' - The identifier of the server for which you want a list of agreements.
newListAgreements ::
  -- | 'serverId'
  Prelude.Text ->
  ListAgreements
newListAgreements :: Text -> ListAgreements
newListAgreements Text
pServerId_ =
  ListAgreements'
    { $sel:maxResults:ListAgreements' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAgreements' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:serverId:ListAgreements' :: Text
serverId = Text
pServerId_
    }

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

-- | When you can get additional results from the @ListAgreements@ call, a
-- @NextToken@ parameter is returned in the output. You can then pass in a
-- subsequent command to the @NextToken@ parameter to continue listing
-- additional agreements.
listAgreements_nextToken :: Lens.Lens' ListAgreements (Prelude.Maybe Prelude.Text)
listAgreements_nextToken :: Lens' ListAgreements (Maybe Text)
listAgreements_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAgreements' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAgreements' :: ListAgreements -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAgreements
s@ListAgreements' {} Maybe Text
a -> ListAgreements
s {$sel:nextToken:ListAgreements' :: Maybe Text
nextToken = Maybe Text
a} :: ListAgreements)

-- | The identifier of the server for which you want a list of agreements.
listAgreements_serverId :: Lens.Lens' ListAgreements Prelude.Text
listAgreements_serverId :: Lens' ListAgreements Text
listAgreements_serverId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAgreements' {Text
serverId :: Text
$sel:serverId:ListAgreements' :: ListAgreements -> Text
serverId} -> Text
serverId) (\s :: ListAgreements
s@ListAgreements' {} Text
a -> ListAgreements
s {$sel:serverId:ListAgreements' :: Text
serverId = Text
a} :: ListAgreements)

instance Core.AWSPager ListAgreements where
  page :: ListAgreements
-> AWSResponse ListAgreements -> Maybe ListAgreements
page ListAgreements
rq AWSResponse ListAgreements
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListAgreements
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAgreementsResponse (Maybe Text)
listAgreementsResponse_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 ListAgreements
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListAgreementsResponse [ListedAgreement]
listAgreementsResponse_agreements) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListAgreements
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAgreements (Maybe Text)
listAgreements_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAgreements
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAgreementsResponse (Maybe Text)
listAgreementsResponse_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 ListAgreements where
  type
    AWSResponse ListAgreements =
      ListAgreementsResponse
  request :: (Service -> Service) -> ListAgreements -> Request ListAgreements
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 ListAgreements
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListAgreements)))
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 -> Int -> [ListedAgreement] -> ListAgreementsResponse
ListAgreementsResponse'
            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
"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))
            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
"Agreements" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListAgreements where
  hashWithSalt :: Int -> ListAgreements -> Int
hashWithSalt Int
_salt ListAgreements' {Maybe Natural
Maybe Text
Text
serverId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:serverId:ListAgreements' :: ListAgreements -> Text
$sel:nextToken:ListAgreements' :: ListAgreements -> Maybe Text
$sel:maxResults:ListAgreements' :: ListAgreements -> Maybe Natural
..} =
    Int
_salt
      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` Text
serverId

instance Prelude.NFData ListAgreements where
  rnf :: ListAgreements -> ()
rnf ListAgreements' {Maybe Natural
Maybe Text
Text
serverId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:serverId:ListAgreements' :: ListAgreements -> Text
$sel:nextToken:ListAgreements' :: ListAgreements -> Maybe Text
$sel:maxResults:ListAgreements' :: ListAgreements -> Maybe Natural
..} =
    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 Text
serverId

instance Data.ToHeaders ListAgreements where
  toHeaders :: ListAgreements -> 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
"TransferService.ListAgreements" ::
                          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 ListAgreements where
  toJSON :: ListAgreements -> Value
toJSON ListAgreements' {Maybe Natural
Maybe Text
Text
serverId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:serverId:ListAgreements' :: ListAgreements -> Text
$sel:nextToken:ListAgreements' :: ListAgreements -> Maybe Text
$sel:maxResults:ListAgreements' :: ListAgreements -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" 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
maxResults,
            (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,
            forall a. a -> Maybe a
Prelude.Just (Key
"ServerId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serverId)
          ]
      )

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

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

-- | /See:/ 'newListAgreementsResponse' smart constructor.
data ListAgreementsResponse = ListAgreementsResponse'
  { -- | Returns a token that you can use to call @ListAgreements@ again and
    -- receive additional results, if there are any.
    ListAgreementsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAgreementsResponse -> Int
httpStatus :: Prelude.Int,
    -- | Returns an array, where each item contains the details of an agreement.
    ListAgreementsResponse -> [ListedAgreement]
agreements :: [ListedAgreement]
  }
  deriving (ListAgreementsResponse -> ListAgreementsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAgreementsResponse -> ListAgreementsResponse -> Bool
$c/= :: ListAgreementsResponse -> ListAgreementsResponse -> Bool
== :: ListAgreementsResponse -> ListAgreementsResponse -> Bool
$c== :: ListAgreementsResponse -> ListAgreementsResponse -> Bool
Prelude.Eq, ReadPrec [ListAgreementsResponse]
ReadPrec ListAgreementsResponse
Int -> ReadS ListAgreementsResponse
ReadS [ListAgreementsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAgreementsResponse]
$creadListPrec :: ReadPrec [ListAgreementsResponse]
readPrec :: ReadPrec ListAgreementsResponse
$creadPrec :: ReadPrec ListAgreementsResponse
readList :: ReadS [ListAgreementsResponse]
$creadList :: ReadS [ListAgreementsResponse]
readsPrec :: Int -> ReadS ListAgreementsResponse
$creadsPrec :: Int -> ReadS ListAgreementsResponse
Prelude.Read, Int -> ListAgreementsResponse -> ShowS
[ListAgreementsResponse] -> ShowS
ListAgreementsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAgreementsResponse] -> ShowS
$cshowList :: [ListAgreementsResponse] -> ShowS
show :: ListAgreementsResponse -> String
$cshow :: ListAgreementsResponse -> String
showsPrec :: Int -> ListAgreementsResponse -> ShowS
$cshowsPrec :: Int -> ListAgreementsResponse -> ShowS
Prelude.Show, forall x. Rep ListAgreementsResponse x -> ListAgreementsResponse
forall x. ListAgreementsResponse -> Rep ListAgreementsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAgreementsResponse x -> ListAgreementsResponse
$cfrom :: forall x. ListAgreementsResponse -> Rep ListAgreementsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAgreementsResponse' 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:
--
-- 'nextToken', 'listAgreementsResponse_nextToken' - Returns a token that you can use to call @ListAgreements@ again and
-- receive additional results, if there are any.
--
-- 'httpStatus', 'listAgreementsResponse_httpStatus' - The response's http status code.
--
-- 'agreements', 'listAgreementsResponse_agreements' - Returns an array, where each item contains the details of an agreement.
newListAgreementsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAgreementsResponse
newListAgreementsResponse :: Int -> ListAgreementsResponse
newListAgreementsResponse Int
pHttpStatus_ =
  ListAgreementsResponse'
    { $sel:nextToken:ListAgreementsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAgreementsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:agreements:ListAgreementsResponse' :: [ListedAgreement]
agreements = forall a. Monoid a => a
Prelude.mempty
    }

-- | Returns a token that you can use to call @ListAgreements@ again and
-- receive additional results, if there are any.
listAgreementsResponse_nextToken :: Lens.Lens' ListAgreementsResponse (Prelude.Maybe Prelude.Text)
listAgreementsResponse_nextToken :: Lens' ListAgreementsResponse (Maybe Text)
listAgreementsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAgreementsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAgreementsResponse' :: ListAgreementsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAgreementsResponse
s@ListAgreementsResponse' {} Maybe Text
a -> ListAgreementsResponse
s {$sel:nextToken:ListAgreementsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAgreementsResponse)

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

-- | Returns an array, where each item contains the details of an agreement.
listAgreementsResponse_agreements :: Lens.Lens' ListAgreementsResponse [ListedAgreement]
listAgreementsResponse_agreements :: Lens' ListAgreementsResponse [ListedAgreement]
listAgreementsResponse_agreements = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAgreementsResponse' {[ListedAgreement]
agreements :: [ListedAgreement]
$sel:agreements:ListAgreementsResponse' :: ListAgreementsResponse -> [ListedAgreement]
agreements} -> [ListedAgreement]
agreements) (\s :: ListAgreementsResponse
s@ListAgreementsResponse' {} [ListedAgreement]
a -> ListAgreementsResponse
s {$sel:agreements:ListAgreementsResponse' :: [ListedAgreement]
agreements = [ListedAgreement]
a} :: ListAgreementsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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