{-# 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.WorkMail.ListResources
-- 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 summaries of the organization\'s resources.
--
-- This operation returns paginated results.
module Amazonka.WorkMail.ListResources
  ( -- * Creating a Request
    ListResources (..),
    newListResources,

    -- * Request Lenses
    listResources_maxResults,
    listResources_nextToken,
    listResources_organizationId,

    -- * Destructuring the Response
    ListResourcesResponse (..),
    newListResourcesResponse,

    -- * Response Lenses
    listResourcesResponse_nextToken,
    listResourcesResponse_resources,
    listResourcesResponse_httpStatus,
  )
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.WorkMail.Types

-- | /See:/ 'newListResources' smart constructor.
data ListResources = ListResources'
  { -- | The maximum number of results to return in a single call.
    ListResources -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token to use to retrieve the next page of results. The first call
    -- does not contain any tokens.
    ListResources -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier for the organization under which the resources exist.
    ListResources -> Text
organizationId :: Prelude.Text
  }
  deriving (ListResources -> ListResources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResources -> ListResources -> Bool
$c/= :: ListResources -> ListResources -> Bool
== :: ListResources -> ListResources -> Bool
$c== :: ListResources -> ListResources -> Bool
Prelude.Eq, ReadPrec [ListResources]
ReadPrec ListResources
Int -> ReadS ListResources
ReadS [ListResources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResources]
$creadListPrec :: ReadPrec [ListResources]
readPrec :: ReadPrec ListResources
$creadPrec :: ReadPrec ListResources
readList :: ReadS [ListResources]
$creadList :: ReadS [ListResources]
readsPrec :: Int -> ReadS ListResources
$creadsPrec :: Int -> ReadS ListResources
Prelude.Read, Int -> ListResources -> ShowS
[ListResources] -> ShowS
ListResources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResources] -> ShowS
$cshowList :: [ListResources] -> ShowS
show :: ListResources -> String
$cshow :: ListResources -> String
showsPrec :: Int -> ListResources -> ShowS
$cshowsPrec :: Int -> ListResources -> ShowS
Prelude.Show, forall x. Rep ListResources x -> ListResources
forall x. ListResources -> Rep ListResources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListResources x -> ListResources
$cfrom :: forall x. ListResources -> Rep ListResources x
Prelude.Generic)

-- |
-- Create a value of 'ListResources' 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', 'listResources_maxResults' - The maximum number of results to return in a single call.
--
-- 'nextToken', 'listResources_nextToken' - The token to use to retrieve the next page of results. The first call
-- does not contain any tokens.
--
-- 'organizationId', 'listResources_organizationId' - The identifier for the organization under which the resources exist.
newListResources ::
  -- | 'organizationId'
  Prelude.Text ->
  ListResources
newListResources :: Text -> ListResources
newListResources Text
pOrganizationId_ =
  ListResources'
    { $sel:maxResults:ListResources' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListResources' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:organizationId:ListResources' :: Text
organizationId = Text
pOrganizationId_
    }

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

-- | The token to use to retrieve the next page of results. The first call
-- does not contain any tokens.
listResources_nextToken :: Lens.Lens' ListResources (Prelude.Maybe Prelude.Text)
listResources_nextToken :: Lens' ListResources (Maybe Text)
listResources_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListResources' :: ListResources -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListResources
s@ListResources' {} Maybe Text
a -> ListResources
s {$sel:nextToken:ListResources' :: Maybe Text
nextToken = Maybe Text
a} :: ListResources)

-- | The identifier for the organization under which the resources exist.
listResources_organizationId :: Lens.Lens' ListResources Prelude.Text
listResources_organizationId :: Lens' ListResources Text
listResources_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Text
organizationId :: Text
$sel:organizationId:ListResources' :: ListResources -> Text
organizationId} -> Text
organizationId) (\s :: ListResources
s@ListResources' {} Text
a -> ListResources
s {$sel:organizationId:ListResources' :: Text
organizationId = Text
a} :: ListResources)

instance Core.AWSPager ListResources where
  page :: ListResources -> AWSResponse ListResources -> Maybe ListResources
page ListResources
rq AWSResponse ListResources
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListResources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourcesResponse (Maybe Text)
listResourcesResponse_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 ListResources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourcesResponse (Maybe [Resource])
listResourcesResponse_resources
            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.$ ListResources
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListResources (Maybe Text)
listResources_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListResources
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourcesResponse (Maybe Text)
listResourcesResponse_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 ListResources where
  type
    AWSResponse ListResources =
      ListResourcesResponse
  request :: (Service -> Service) -> ListResources -> Request ListResources
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 ListResources
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListResources)))
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 [Resource] -> Int -> ListResourcesResponse
ListResourcesResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Resources" 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 ListResources where
  hashWithSalt :: Int -> ListResources -> Int
hashWithSalt Int
_salt ListResources' {Maybe Natural
Maybe Text
Text
organizationId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:organizationId:ListResources' :: ListResources -> Text
$sel:nextToken:ListResources' :: ListResources -> Maybe Text
$sel:maxResults:ListResources' :: ListResources -> 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
organizationId

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

instance Data.ToHeaders ListResources where
  toHeaders :: ListResources -> 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
"WorkMailService.ListResources" ::
                          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 ListResources where
  toJSON :: ListResources -> Value
toJSON ListResources' {Maybe Natural
Maybe Text
Text
organizationId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:organizationId:ListResources' :: ListResources -> Text
$sel:nextToken:ListResources' :: ListResources -> Maybe Text
$sel:maxResults:ListResources' :: ListResources -> 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
"OrganizationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationId)
          ]
      )

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

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

-- | /See:/ 'newListResourcesResponse' smart constructor.
data ListResourcesResponse = ListResourcesResponse'
  { -- | The token used to paginate through all the organization\'s resources.
    -- While results are still available, it has an associated value. When the
    -- last page is reached, the token is empty.
    ListResourcesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | One page of the organization\'s resource representation.
    ListResourcesResponse -> Maybe [Resource]
resources :: Prelude.Maybe [Resource],
    -- | The response's http status code.
    ListResourcesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListResourcesResponse -> ListResourcesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourcesResponse -> ListResourcesResponse -> Bool
$c/= :: ListResourcesResponse -> ListResourcesResponse -> Bool
== :: ListResourcesResponse -> ListResourcesResponse -> Bool
$c== :: ListResourcesResponse -> ListResourcesResponse -> Bool
Prelude.Eq, ReadPrec [ListResourcesResponse]
ReadPrec ListResourcesResponse
Int -> ReadS ListResourcesResponse
ReadS [ListResourcesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourcesResponse]
$creadListPrec :: ReadPrec [ListResourcesResponse]
readPrec :: ReadPrec ListResourcesResponse
$creadPrec :: ReadPrec ListResourcesResponse
readList :: ReadS [ListResourcesResponse]
$creadList :: ReadS [ListResourcesResponse]
readsPrec :: Int -> ReadS ListResourcesResponse
$creadsPrec :: Int -> ReadS ListResourcesResponse
Prelude.Read, Int -> ListResourcesResponse -> ShowS
[ListResourcesResponse] -> ShowS
ListResourcesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourcesResponse] -> ShowS
$cshowList :: [ListResourcesResponse] -> ShowS
show :: ListResourcesResponse -> String
$cshow :: ListResourcesResponse -> String
showsPrec :: Int -> ListResourcesResponse -> ShowS
$cshowsPrec :: Int -> ListResourcesResponse -> ShowS
Prelude.Show, forall x. Rep ListResourcesResponse x -> ListResourcesResponse
forall x. ListResourcesResponse -> Rep ListResourcesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListResourcesResponse x -> ListResourcesResponse
$cfrom :: forall x. ListResourcesResponse -> Rep ListResourcesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListResourcesResponse' 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', 'listResourcesResponse_nextToken' - The token used to paginate through all the organization\'s resources.
-- While results are still available, it has an associated value. When the
-- last page is reached, the token is empty.
--
-- 'resources', 'listResourcesResponse_resources' - One page of the organization\'s resource representation.
--
-- 'httpStatus', 'listResourcesResponse_httpStatus' - The response's http status code.
newListResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListResourcesResponse
newListResourcesResponse :: Int -> ListResourcesResponse
newListResourcesResponse Int
pHttpStatus_ =
  ListResourcesResponse'
    { $sel:nextToken:ListResourcesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resources:ListResourcesResponse' :: Maybe [Resource]
resources = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListResourcesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The token used to paginate through all the organization\'s resources.
-- While results are still available, it has an associated value. When the
-- last page is reached, the token is empty.
listResourcesResponse_nextToken :: Lens.Lens' ListResourcesResponse (Prelude.Maybe Prelude.Text)
listResourcesResponse_nextToken :: Lens' ListResourcesResponse (Maybe Text)
listResourcesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourcesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListResourcesResponse' :: ListResourcesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListResourcesResponse
s@ListResourcesResponse' {} Maybe Text
a -> ListResourcesResponse
s {$sel:nextToken:ListResourcesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListResourcesResponse)

-- | One page of the organization\'s resource representation.
listResourcesResponse_resources :: Lens.Lens' ListResourcesResponse (Prelude.Maybe [Resource])
listResourcesResponse_resources :: Lens' ListResourcesResponse (Maybe [Resource])
listResourcesResponse_resources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourcesResponse' {Maybe [Resource]
resources :: Maybe [Resource]
$sel:resources:ListResourcesResponse' :: ListResourcesResponse -> Maybe [Resource]
resources} -> Maybe [Resource]
resources) (\s :: ListResourcesResponse
s@ListResourcesResponse' {} Maybe [Resource]
a -> ListResourcesResponse
s {$sel:resources:ListResourcesResponse' :: Maybe [Resource]
resources = Maybe [Resource]
a} :: ListResourcesResponse) 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.
listResourcesResponse_httpStatus :: Lens.Lens' ListResourcesResponse Prelude.Int
listResourcesResponse_httpStatus :: Lens' ListResourcesResponse Int
listResourcesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourcesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListResourcesResponse' :: ListResourcesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListResourcesResponse
s@ListResourcesResponse' {} Int
a -> ListResourcesResponse
s {$sel:httpStatus:ListResourcesResponse' :: Int
httpStatus = Int
a} :: ListResourcesResponse)

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