{-# 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.EMRContainers.ListVirtualClusters
-- 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 information about the specified virtual cluster. Virtual cluster
-- is a managed entity on Amazon EMR on EKS. You can create, describe, list
-- and delete virtual clusters. They do not consume any additional resource
-- in your system. A single virtual cluster maps to a single Kubernetes
-- namespace. Given this relationship, you can model virtual clusters the
-- same way you model Kubernetes namespaces to meet your requirements.
--
-- This operation returns paginated results.
module Amazonka.EMRContainers.ListVirtualClusters
  ( -- * Creating a Request
    ListVirtualClusters (..),
    newListVirtualClusters,

    -- * Request Lenses
    listVirtualClusters_containerProviderId,
    listVirtualClusters_containerProviderType,
    listVirtualClusters_createdAfter,
    listVirtualClusters_createdBefore,
    listVirtualClusters_maxResults,
    listVirtualClusters_nextToken,
    listVirtualClusters_states,

    -- * Destructuring the Response
    ListVirtualClustersResponse (..),
    newListVirtualClustersResponse,

    -- * Response Lenses
    listVirtualClustersResponse_nextToken,
    listVirtualClustersResponse_virtualClusters,
    listVirtualClustersResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListVirtualClusters' smart constructor.
data ListVirtualClusters = ListVirtualClusters'
  { -- | The container provider ID of the virtual cluster.
    ListVirtualClusters -> Maybe Text
containerProviderId :: Prelude.Maybe Prelude.Text,
    -- | The container provider type of the virtual cluster. EKS is the only
    -- supported type as of now.
    ListVirtualClusters -> Maybe ContainerProviderType
containerProviderType :: Prelude.Maybe ContainerProviderType,
    -- | The date and time after which the virtual clusters are created.
    ListVirtualClusters -> Maybe ISO8601
createdAfter :: Prelude.Maybe Data.ISO8601,
    -- | The date and time before which the virtual clusters are created.
    ListVirtualClusters -> Maybe ISO8601
createdBefore :: Prelude.Maybe Data.ISO8601,
    -- | The maximum number of virtual clusters that can be listed.
    ListVirtualClusters -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | The token for the next set of virtual clusters to return.
    ListVirtualClusters -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The states of the requested virtual clusters.
    ListVirtualClusters -> Maybe [VirtualClusterState]
states :: Prelude.Maybe [VirtualClusterState]
  }
  deriving (ListVirtualClusters -> ListVirtualClusters -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListVirtualClusters -> ListVirtualClusters -> Bool
$c/= :: ListVirtualClusters -> ListVirtualClusters -> Bool
== :: ListVirtualClusters -> ListVirtualClusters -> Bool
$c== :: ListVirtualClusters -> ListVirtualClusters -> Bool
Prelude.Eq, ReadPrec [ListVirtualClusters]
ReadPrec ListVirtualClusters
Int -> ReadS ListVirtualClusters
ReadS [ListVirtualClusters]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListVirtualClusters]
$creadListPrec :: ReadPrec [ListVirtualClusters]
readPrec :: ReadPrec ListVirtualClusters
$creadPrec :: ReadPrec ListVirtualClusters
readList :: ReadS [ListVirtualClusters]
$creadList :: ReadS [ListVirtualClusters]
readsPrec :: Int -> ReadS ListVirtualClusters
$creadsPrec :: Int -> ReadS ListVirtualClusters
Prelude.Read, Int -> ListVirtualClusters -> ShowS
[ListVirtualClusters] -> ShowS
ListVirtualClusters -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListVirtualClusters] -> ShowS
$cshowList :: [ListVirtualClusters] -> ShowS
show :: ListVirtualClusters -> String
$cshow :: ListVirtualClusters -> String
showsPrec :: Int -> ListVirtualClusters -> ShowS
$cshowsPrec :: Int -> ListVirtualClusters -> ShowS
Prelude.Show, forall x. Rep ListVirtualClusters x -> ListVirtualClusters
forall x. ListVirtualClusters -> Rep ListVirtualClusters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListVirtualClusters x -> ListVirtualClusters
$cfrom :: forall x. ListVirtualClusters -> Rep ListVirtualClusters x
Prelude.Generic)

-- |
-- Create a value of 'ListVirtualClusters' 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:
--
-- 'containerProviderId', 'listVirtualClusters_containerProviderId' - The container provider ID of the virtual cluster.
--
-- 'containerProviderType', 'listVirtualClusters_containerProviderType' - The container provider type of the virtual cluster. EKS is the only
-- supported type as of now.
--
-- 'createdAfter', 'listVirtualClusters_createdAfter' - The date and time after which the virtual clusters are created.
--
-- 'createdBefore', 'listVirtualClusters_createdBefore' - The date and time before which the virtual clusters are created.
--
-- 'maxResults', 'listVirtualClusters_maxResults' - The maximum number of virtual clusters that can be listed.
--
-- 'nextToken', 'listVirtualClusters_nextToken' - The token for the next set of virtual clusters to return.
--
-- 'states', 'listVirtualClusters_states' - The states of the requested virtual clusters.
newListVirtualClusters ::
  ListVirtualClusters
newListVirtualClusters :: ListVirtualClusters
newListVirtualClusters =
  ListVirtualClusters'
    { $sel:containerProviderId:ListVirtualClusters' :: Maybe Text
containerProviderId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:containerProviderType:ListVirtualClusters' :: Maybe ContainerProviderType
containerProviderType = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAfter:ListVirtualClusters' :: Maybe ISO8601
createdAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBefore:ListVirtualClusters' :: Maybe ISO8601
createdBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListVirtualClusters' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListVirtualClusters' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:states:ListVirtualClusters' :: Maybe [VirtualClusterState]
states = forall a. Maybe a
Prelude.Nothing
    }

-- | The container provider ID of the virtual cluster.
listVirtualClusters_containerProviderId :: Lens.Lens' ListVirtualClusters (Prelude.Maybe Prelude.Text)
listVirtualClusters_containerProviderId :: Lens' ListVirtualClusters (Maybe Text)
listVirtualClusters_containerProviderId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClusters' {Maybe Text
containerProviderId :: Maybe Text
$sel:containerProviderId:ListVirtualClusters' :: ListVirtualClusters -> Maybe Text
containerProviderId} -> Maybe Text
containerProviderId) (\s :: ListVirtualClusters
s@ListVirtualClusters' {} Maybe Text
a -> ListVirtualClusters
s {$sel:containerProviderId:ListVirtualClusters' :: Maybe Text
containerProviderId = Maybe Text
a} :: ListVirtualClusters)

-- | The container provider type of the virtual cluster. EKS is the only
-- supported type as of now.
listVirtualClusters_containerProviderType :: Lens.Lens' ListVirtualClusters (Prelude.Maybe ContainerProviderType)
listVirtualClusters_containerProviderType :: Lens' ListVirtualClusters (Maybe ContainerProviderType)
listVirtualClusters_containerProviderType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClusters' {Maybe ContainerProviderType
containerProviderType :: Maybe ContainerProviderType
$sel:containerProviderType:ListVirtualClusters' :: ListVirtualClusters -> Maybe ContainerProviderType
containerProviderType} -> Maybe ContainerProviderType
containerProviderType) (\s :: ListVirtualClusters
s@ListVirtualClusters' {} Maybe ContainerProviderType
a -> ListVirtualClusters
s {$sel:containerProviderType:ListVirtualClusters' :: Maybe ContainerProviderType
containerProviderType = Maybe ContainerProviderType
a} :: ListVirtualClusters)

-- | The date and time after which the virtual clusters are created.
listVirtualClusters_createdAfter :: Lens.Lens' ListVirtualClusters (Prelude.Maybe Prelude.UTCTime)
listVirtualClusters_createdAfter :: Lens' ListVirtualClusters (Maybe UTCTime)
listVirtualClusters_createdAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClusters' {Maybe ISO8601
createdAfter :: Maybe ISO8601
$sel:createdAfter:ListVirtualClusters' :: ListVirtualClusters -> Maybe ISO8601
createdAfter} -> Maybe ISO8601
createdAfter) (\s :: ListVirtualClusters
s@ListVirtualClusters' {} Maybe ISO8601
a -> ListVirtualClusters
s {$sel:createdAfter:ListVirtualClusters' :: Maybe ISO8601
createdAfter = Maybe ISO8601
a} :: ListVirtualClusters) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The date and time before which the virtual clusters are created.
listVirtualClusters_createdBefore :: Lens.Lens' ListVirtualClusters (Prelude.Maybe Prelude.UTCTime)
listVirtualClusters_createdBefore :: Lens' ListVirtualClusters (Maybe UTCTime)
listVirtualClusters_createdBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClusters' {Maybe ISO8601
createdBefore :: Maybe ISO8601
$sel:createdBefore:ListVirtualClusters' :: ListVirtualClusters -> Maybe ISO8601
createdBefore} -> Maybe ISO8601
createdBefore) (\s :: ListVirtualClusters
s@ListVirtualClusters' {} Maybe ISO8601
a -> ListVirtualClusters
s {$sel:createdBefore:ListVirtualClusters' :: Maybe ISO8601
createdBefore = Maybe ISO8601
a} :: ListVirtualClusters) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The maximum number of virtual clusters that can be listed.
listVirtualClusters_maxResults :: Lens.Lens' ListVirtualClusters (Prelude.Maybe Prelude.Int)
listVirtualClusters_maxResults :: Lens' ListVirtualClusters (Maybe Int)
listVirtualClusters_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClusters' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListVirtualClusters' :: ListVirtualClusters -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListVirtualClusters
s@ListVirtualClusters' {} Maybe Int
a -> ListVirtualClusters
s {$sel:maxResults:ListVirtualClusters' :: Maybe Int
maxResults = Maybe Int
a} :: ListVirtualClusters)

-- | The token for the next set of virtual clusters to return.
listVirtualClusters_nextToken :: Lens.Lens' ListVirtualClusters (Prelude.Maybe Prelude.Text)
listVirtualClusters_nextToken :: Lens' ListVirtualClusters (Maybe Text)
listVirtualClusters_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClusters' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListVirtualClusters' :: ListVirtualClusters -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListVirtualClusters
s@ListVirtualClusters' {} Maybe Text
a -> ListVirtualClusters
s {$sel:nextToken:ListVirtualClusters' :: Maybe Text
nextToken = Maybe Text
a} :: ListVirtualClusters)

-- | The states of the requested virtual clusters.
listVirtualClusters_states :: Lens.Lens' ListVirtualClusters (Prelude.Maybe [VirtualClusterState])
listVirtualClusters_states :: Lens' ListVirtualClusters (Maybe [VirtualClusterState])
listVirtualClusters_states = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClusters' {Maybe [VirtualClusterState]
states :: Maybe [VirtualClusterState]
$sel:states:ListVirtualClusters' :: ListVirtualClusters -> Maybe [VirtualClusterState]
states} -> Maybe [VirtualClusterState]
states) (\s :: ListVirtualClusters
s@ListVirtualClusters' {} Maybe [VirtualClusterState]
a -> ListVirtualClusters
s {$sel:states:ListVirtualClusters' :: Maybe [VirtualClusterState]
states = Maybe [VirtualClusterState]
a} :: ListVirtualClusters) 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

instance Core.AWSPager ListVirtualClusters where
  page :: ListVirtualClusters
-> AWSResponse ListVirtualClusters -> Maybe ListVirtualClusters
page ListVirtualClusters
rq AWSResponse ListVirtualClusters
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListVirtualClusters
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListVirtualClustersResponse (Maybe Text)
listVirtualClustersResponse_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 ListVirtualClusters
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListVirtualClustersResponse (Maybe [VirtualCluster])
listVirtualClustersResponse_virtualClusters
            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.$ ListVirtualClusters
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListVirtualClusters (Maybe Text)
listVirtualClusters_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListVirtualClusters
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListVirtualClustersResponse (Maybe Text)
listVirtualClustersResponse_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 ListVirtualClusters where
  type
    AWSResponse ListVirtualClusters =
      ListVirtualClustersResponse
  request :: (Service -> Service)
-> ListVirtualClusters -> Request ListVirtualClusters
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 ListVirtualClusters
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListVirtualClusters)))
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 [VirtualCluster] -> Int -> ListVirtualClustersResponse
ListVirtualClustersResponse'
            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
"virtualClusters"
                            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 ListVirtualClusters where
  hashWithSalt :: Int -> ListVirtualClusters -> Int
hashWithSalt Int
_salt ListVirtualClusters' {Maybe Int
Maybe [VirtualClusterState]
Maybe Text
Maybe ISO8601
Maybe ContainerProviderType
states :: Maybe [VirtualClusterState]
nextToken :: Maybe Text
maxResults :: Maybe Int
createdBefore :: Maybe ISO8601
createdAfter :: Maybe ISO8601
containerProviderType :: Maybe ContainerProviderType
containerProviderId :: Maybe Text
$sel:states:ListVirtualClusters' :: ListVirtualClusters -> Maybe [VirtualClusterState]
$sel:nextToken:ListVirtualClusters' :: ListVirtualClusters -> Maybe Text
$sel:maxResults:ListVirtualClusters' :: ListVirtualClusters -> Maybe Int
$sel:createdBefore:ListVirtualClusters' :: ListVirtualClusters -> Maybe ISO8601
$sel:createdAfter:ListVirtualClusters' :: ListVirtualClusters -> Maybe ISO8601
$sel:containerProviderType:ListVirtualClusters' :: ListVirtualClusters -> Maybe ContainerProviderType
$sel:containerProviderId:ListVirtualClusters' :: ListVirtualClusters -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
containerProviderId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ContainerProviderType
containerProviderType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
createdAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
createdBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [VirtualClusterState]
states

instance Prelude.NFData ListVirtualClusters where
  rnf :: ListVirtualClusters -> ()
rnf ListVirtualClusters' {Maybe Int
Maybe [VirtualClusterState]
Maybe Text
Maybe ISO8601
Maybe ContainerProviderType
states :: Maybe [VirtualClusterState]
nextToken :: Maybe Text
maxResults :: Maybe Int
createdBefore :: Maybe ISO8601
createdAfter :: Maybe ISO8601
containerProviderType :: Maybe ContainerProviderType
containerProviderId :: Maybe Text
$sel:states:ListVirtualClusters' :: ListVirtualClusters -> Maybe [VirtualClusterState]
$sel:nextToken:ListVirtualClusters' :: ListVirtualClusters -> Maybe Text
$sel:maxResults:ListVirtualClusters' :: ListVirtualClusters -> Maybe Int
$sel:createdBefore:ListVirtualClusters' :: ListVirtualClusters -> Maybe ISO8601
$sel:createdAfter:ListVirtualClusters' :: ListVirtualClusters -> Maybe ISO8601
$sel:containerProviderType:ListVirtualClusters' :: ListVirtualClusters -> Maybe ContainerProviderType
$sel:containerProviderId:ListVirtualClusters' :: ListVirtualClusters -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
containerProviderId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ContainerProviderType
containerProviderType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
createdAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
createdBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
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 [VirtualClusterState]
states

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

instance Data.ToQuery ListVirtualClusters where
  toQuery :: ListVirtualClusters -> QueryString
toQuery ListVirtualClusters' {Maybe Int
Maybe [VirtualClusterState]
Maybe Text
Maybe ISO8601
Maybe ContainerProviderType
states :: Maybe [VirtualClusterState]
nextToken :: Maybe Text
maxResults :: Maybe Int
createdBefore :: Maybe ISO8601
createdAfter :: Maybe ISO8601
containerProviderType :: Maybe ContainerProviderType
containerProviderId :: Maybe Text
$sel:states:ListVirtualClusters' :: ListVirtualClusters -> Maybe [VirtualClusterState]
$sel:nextToken:ListVirtualClusters' :: ListVirtualClusters -> Maybe Text
$sel:maxResults:ListVirtualClusters' :: ListVirtualClusters -> Maybe Int
$sel:createdBefore:ListVirtualClusters' :: ListVirtualClusters -> Maybe ISO8601
$sel:createdAfter:ListVirtualClusters' :: ListVirtualClusters -> Maybe ISO8601
$sel:containerProviderType:ListVirtualClusters' :: ListVirtualClusters -> Maybe ContainerProviderType
$sel:containerProviderId:ListVirtualClusters' :: ListVirtualClusters -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"containerProviderId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
containerProviderId,
        ByteString
"containerProviderType"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ContainerProviderType
containerProviderType,
        ByteString
"createdAfter" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
createdAfter,
        ByteString
"createdBefore" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
createdBefore,
        ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"states"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [VirtualClusterState]
states)
      ]

-- | /See:/ 'newListVirtualClustersResponse' smart constructor.
data ListVirtualClustersResponse = ListVirtualClustersResponse'
  { -- | This output displays the token for the next set of virtual clusters.
    ListVirtualClustersResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | This output lists the specified virtual clusters.
    ListVirtualClustersResponse -> Maybe [VirtualCluster]
virtualClusters :: Prelude.Maybe [VirtualCluster],
    -- | The response's http status code.
    ListVirtualClustersResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListVirtualClustersResponse -> ListVirtualClustersResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListVirtualClustersResponse -> ListVirtualClustersResponse -> Bool
$c/= :: ListVirtualClustersResponse -> ListVirtualClustersResponse -> Bool
== :: ListVirtualClustersResponse -> ListVirtualClustersResponse -> Bool
$c== :: ListVirtualClustersResponse -> ListVirtualClustersResponse -> Bool
Prelude.Eq, ReadPrec [ListVirtualClustersResponse]
ReadPrec ListVirtualClustersResponse
Int -> ReadS ListVirtualClustersResponse
ReadS [ListVirtualClustersResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListVirtualClustersResponse]
$creadListPrec :: ReadPrec [ListVirtualClustersResponse]
readPrec :: ReadPrec ListVirtualClustersResponse
$creadPrec :: ReadPrec ListVirtualClustersResponse
readList :: ReadS [ListVirtualClustersResponse]
$creadList :: ReadS [ListVirtualClustersResponse]
readsPrec :: Int -> ReadS ListVirtualClustersResponse
$creadsPrec :: Int -> ReadS ListVirtualClustersResponse
Prelude.Read, Int -> ListVirtualClustersResponse -> ShowS
[ListVirtualClustersResponse] -> ShowS
ListVirtualClustersResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListVirtualClustersResponse] -> ShowS
$cshowList :: [ListVirtualClustersResponse] -> ShowS
show :: ListVirtualClustersResponse -> String
$cshow :: ListVirtualClustersResponse -> String
showsPrec :: Int -> ListVirtualClustersResponse -> ShowS
$cshowsPrec :: Int -> ListVirtualClustersResponse -> ShowS
Prelude.Show, forall x.
Rep ListVirtualClustersResponse x -> ListVirtualClustersResponse
forall x.
ListVirtualClustersResponse -> Rep ListVirtualClustersResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListVirtualClustersResponse x -> ListVirtualClustersResponse
$cfrom :: forall x.
ListVirtualClustersResponse -> Rep ListVirtualClustersResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListVirtualClustersResponse' 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', 'listVirtualClustersResponse_nextToken' - This output displays the token for the next set of virtual clusters.
--
-- 'virtualClusters', 'listVirtualClustersResponse_virtualClusters' - This output lists the specified virtual clusters.
--
-- 'httpStatus', 'listVirtualClustersResponse_httpStatus' - The response's http status code.
newListVirtualClustersResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListVirtualClustersResponse
newListVirtualClustersResponse :: Int -> ListVirtualClustersResponse
newListVirtualClustersResponse Int
pHttpStatus_ =
  ListVirtualClustersResponse'
    { $sel:nextToken:ListVirtualClustersResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:virtualClusters:ListVirtualClustersResponse' :: Maybe [VirtualCluster]
virtualClusters = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListVirtualClustersResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | This output displays the token for the next set of virtual clusters.
listVirtualClustersResponse_nextToken :: Lens.Lens' ListVirtualClustersResponse (Prelude.Maybe Prelude.Text)
listVirtualClustersResponse_nextToken :: Lens' ListVirtualClustersResponse (Maybe Text)
listVirtualClustersResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClustersResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListVirtualClustersResponse' :: ListVirtualClustersResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListVirtualClustersResponse
s@ListVirtualClustersResponse' {} Maybe Text
a -> ListVirtualClustersResponse
s {$sel:nextToken:ListVirtualClustersResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListVirtualClustersResponse)

-- | This output lists the specified virtual clusters.
listVirtualClustersResponse_virtualClusters :: Lens.Lens' ListVirtualClustersResponse (Prelude.Maybe [VirtualCluster])
listVirtualClustersResponse_virtualClusters :: Lens' ListVirtualClustersResponse (Maybe [VirtualCluster])
listVirtualClustersResponse_virtualClusters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClustersResponse' {Maybe [VirtualCluster]
virtualClusters :: Maybe [VirtualCluster]
$sel:virtualClusters:ListVirtualClustersResponse' :: ListVirtualClustersResponse -> Maybe [VirtualCluster]
virtualClusters} -> Maybe [VirtualCluster]
virtualClusters) (\s :: ListVirtualClustersResponse
s@ListVirtualClustersResponse' {} Maybe [VirtualCluster]
a -> ListVirtualClustersResponse
s {$sel:virtualClusters:ListVirtualClustersResponse' :: Maybe [VirtualCluster]
virtualClusters = Maybe [VirtualCluster]
a} :: ListVirtualClustersResponse) 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.
listVirtualClustersResponse_httpStatus :: Lens.Lens' ListVirtualClustersResponse Prelude.Int
listVirtualClustersResponse_httpStatus :: Lens' ListVirtualClustersResponse Int
listVirtualClustersResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVirtualClustersResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListVirtualClustersResponse' :: ListVirtualClustersResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListVirtualClustersResponse
s@ListVirtualClustersResponse' {} Int
a -> ListVirtualClustersResponse
s {$sel:httpStatus:ListVirtualClustersResponse' :: Int
httpStatus = Int
a} :: ListVirtualClustersResponse)

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