{-# 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.AuditManager.GetDelegations
-- 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 delegations from an audit owner to a delegate.
module Amazonka.AuditManager.GetDelegations
  ( -- * Creating a Request
    GetDelegations (..),
    newGetDelegations,

    -- * Request Lenses
    getDelegations_maxResults,
    getDelegations_nextToken,

    -- * Destructuring the Response
    GetDelegationsResponse (..),
    newGetDelegationsResponse,

    -- * Response Lenses
    getDelegationsResponse_delegations,
    getDelegationsResponse_nextToken,
    getDelegationsResponse_httpStatus,
  )
where

import Amazonka.AuditManager.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:/ 'newGetDelegations' smart constructor.
data GetDelegations = GetDelegations'
  { -- | Represents the maximum number of results on a page or for an API request
    -- call.
    GetDelegations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The pagination token that\'s used to fetch the next set of results.
    GetDelegations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetDelegations -> GetDelegations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDelegations -> GetDelegations -> Bool
$c/= :: GetDelegations -> GetDelegations -> Bool
== :: GetDelegations -> GetDelegations -> Bool
$c== :: GetDelegations -> GetDelegations -> Bool
Prelude.Eq, ReadPrec [GetDelegations]
ReadPrec GetDelegations
Int -> ReadS GetDelegations
ReadS [GetDelegations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDelegations]
$creadListPrec :: ReadPrec [GetDelegations]
readPrec :: ReadPrec GetDelegations
$creadPrec :: ReadPrec GetDelegations
readList :: ReadS [GetDelegations]
$creadList :: ReadS [GetDelegations]
readsPrec :: Int -> ReadS GetDelegations
$creadsPrec :: Int -> ReadS GetDelegations
Prelude.Read, Int -> GetDelegations -> ShowS
[GetDelegations] -> ShowS
GetDelegations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDelegations] -> ShowS
$cshowList :: [GetDelegations] -> ShowS
show :: GetDelegations -> String
$cshow :: GetDelegations -> String
showsPrec :: Int -> GetDelegations -> ShowS
$cshowsPrec :: Int -> GetDelegations -> ShowS
Prelude.Show, forall x. Rep GetDelegations x -> GetDelegations
forall x. GetDelegations -> Rep GetDelegations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDelegations x -> GetDelegations
$cfrom :: forall x. GetDelegations -> Rep GetDelegations x
Prelude.Generic)

-- |
-- Create a value of 'GetDelegations' 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', 'getDelegations_maxResults' - Represents the maximum number of results on a page or for an API request
-- call.
--
-- 'nextToken', 'getDelegations_nextToken' - The pagination token that\'s used to fetch the next set of results.
newGetDelegations ::
  GetDelegations
newGetDelegations :: GetDelegations
newGetDelegations =
  GetDelegations'
    { $sel:maxResults:GetDelegations' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetDelegations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Represents the maximum number of results on a page or for an API request
-- call.
getDelegations_maxResults :: Lens.Lens' GetDelegations (Prelude.Maybe Prelude.Natural)
getDelegations_maxResults :: Lens' GetDelegations (Maybe Natural)
getDelegations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDelegations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetDelegations' :: GetDelegations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetDelegations
s@GetDelegations' {} Maybe Natural
a -> GetDelegations
s {$sel:maxResults:GetDelegations' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetDelegations)

-- | The pagination token that\'s used to fetch the next set of results.
getDelegations_nextToken :: Lens.Lens' GetDelegations (Prelude.Maybe Prelude.Text)
getDelegations_nextToken :: Lens' GetDelegations (Maybe Text)
getDelegations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDelegations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetDelegations' :: GetDelegations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetDelegations
s@GetDelegations' {} Maybe Text
a -> GetDelegations
s {$sel:nextToken:GetDelegations' :: Maybe Text
nextToken = Maybe Text
a} :: GetDelegations)

instance Core.AWSRequest GetDelegations where
  type
    AWSResponse GetDelegations =
      GetDelegationsResponse
  request :: (Service -> Service) -> GetDelegations -> Request GetDelegations
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 GetDelegations
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetDelegations)))
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 [DelegationMetadata]
-> Maybe Text -> Int -> GetDelegationsResponse
GetDelegationsResponse'
            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
"delegations" 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 GetDelegations where
  hashWithSalt :: Int -> GetDelegations -> Int
hashWithSalt Int
_salt GetDelegations' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:GetDelegations' :: GetDelegations -> Maybe Text
$sel:maxResults:GetDelegations' :: GetDelegations -> 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

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

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

instance Data.ToQuery GetDelegations where
  toQuery :: GetDelegations -> QueryString
toQuery GetDelegations' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:GetDelegations' :: GetDelegations -> Maybe Text
$sel:maxResults:GetDelegations' :: GetDelegations -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ 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
      ]

-- | /See:/ 'newGetDelegationsResponse' smart constructor.
data GetDelegationsResponse = GetDelegationsResponse'
  { -- | The list of delegations that the @GetDelegations@ API returned.
    GetDelegationsResponse -> Maybe [DelegationMetadata]
delegations :: Prelude.Maybe [DelegationMetadata],
    -- | The pagination token that\'s used to fetch the next set of results.
    GetDelegationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetDelegationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDelegationsResponse -> GetDelegationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDelegationsResponse -> GetDelegationsResponse -> Bool
$c/= :: GetDelegationsResponse -> GetDelegationsResponse -> Bool
== :: GetDelegationsResponse -> GetDelegationsResponse -> Bool
$c== :: GetDelegationsResponse -> GetDelegationsResponse -> Bool
Prelude.Eq, ReadPrec [GetDelegationsResponse]
ReadPrec GetDelegationsResponse
Int -> ReadS GetDelegationsResponse
ReadS [GetDelegationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDelegationsResponse]
$creadListPrec :: ReadPrec [GetDelegationsResponse]
readPrec :: ReadPrec GetDelegationsResponse
$creadPrec :: ReadPrec GetDelegationsResponse
readList :: ReadS [GetDelegationsResponse]
$creadList :: ReadS [GetDelegationsResponse]
readsPrec :: Int -> ReadS GetDelegationsResponse
$creadsPrec :: Int -> ReadS GetDelegationsResponse
Prelude.Read, Int -> GetDelegationsResponse -> ShowS
[GetDelegationsResponse] -> ShowS
GetDelegationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDelegationsResponse] -> ShowS
$cshowList :: [GetDelegationsResponse] -> ShowS
show :: GetDelegationsResponse -> String
$cshow :: GetDelegationsResponse -> String
showsPrec :: Int -> GetDelegationsResponse -> ShowS
$cshowsPrec :: Int -> GetDelegationsResponse -> ShowS
Prelude.Show, forall x. Rep GetDelegationsResponse x -> GetDelegationsResponse
forall x. GetDelegationsResponse -> Rep GetDelegationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDelegationsResponse x -> GetDelegationsResponse
$cfrom :: forall x. GetDelegationsResponse -> Rep GetDelegationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDelegationsResponse' 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:
--
-- 'delegations', 'getDelegationsResponse_delegations' - The list of delegations that the @GetDelegations@ API returned.
--
-- 'nextToken', 'getDelegationsResponse_nextToken' - The pagination token that\'s used to fetch the next set of results.
--
-- 'httpStatus', 'getDelegationsResponse_httpStatus' - The response's http status code.
newGetDelegationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDelegationsResponse
newGetDelegationsResponse :: Int -> GetDelegationsResponse
newGetDelegationsResponse Int
pHttpStatus_ =
  GetDelegationsResponse'
    { $sel:delegations:GetDelegationsResponse' :: Maybe [DelegationMetadata]
delegations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetDelegationsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDelegationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of delegations that the @GetDelegations@ API returned.
getDelegationsResponse_delegations :: Lens.Lens' GetDelegationsResponse (Prelude.Maybe [DelegationMetadata])
getDelegationsResponse_delegations :: Lens' GetDelegationsResponse (Maybe [DelegationMetadata])
getDelegationsResponse_delegations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDelegationsResponse' {Maybe [DelegationMetadata]
delegations :: Maybe [DelegationMetadata]
$sel:delegations:GetDelegationsResponse' :: GetDelegationsResponse -> Maybe [DelegationMetadata]
delegations} -> Maybe [DelegationMetadata]
delegations) (\s :: GetDelegationsResponse
s@GetDelegationsResponse' {} Maybe [DelegationMetadata]
a -> GetDelegationsResponse
s {$sel:delegations:GetDelegationsResponse' :: Maybe [DelegationMetadata]
delegations = Maybe [DelegationMetadata]
a} :: GetDelegationsResponse) 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 pagination token that\'s used to fetch the next set of results.
getDelegationsResponse_nextToken :: Lens.Lens' GetDelegationsResponse (Prelude.Maybe Prelude.Text)
getDelegationsResponse_nextToken :: Lens' GetDelegationsResponse (Maybe Text)
getDelegationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDelegationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetDelegationsResponse' :: GetDelegationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetDelegationsResponse
s@GetDelegationsResponse' {} Maybe Text
a -> GetDelegationsResponse
s {$sel:nextToken:GetDelegationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetDelegationsResponse)

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

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