{-# 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.ElasticBeanstalk.DescribeEnvironments
-- 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 descriptions for existing environments.
--
-- This operation returns paginated results.
module Amazonka.ElasticBeanstalk.DescribeEnvironments
  ( -- * Creating a Request
    DescribeEnvironments (..),
    newDescribeEnvironments,

    -- * Request Lenses
    describeEnvironments_applicationName,
    describeEnvironments_environmentIds,
    describeEnvironments_environmentNames,
    describeEnvironments_includeDeleted,
    describeEnvironments_includedDeletedBackTo,
    describeEnvironments_maxRecords,
    describeEnvironments_nextToken,
    describeEnvironments_versionLabel,

    -- * Destructuring the Response
    EnvironmentDescriptionsMessage (..),
    newEnvironmentDescriptionsMessage,

    -- * Response Lenses
    environmentDescriptionsMessage_environments,
    environmentDescriptionsMessage_nextToken,
  )
where

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

-- | Request to describe one or more environments.
--
-- /See:/ 'newDescribeEnvironments' smart constructor.
data DescribeEnvironments = DescribeEnvironments'
  { -- | If specified, AWS Elastic Beanstalk restricts the returned descriptions
    -- to include only those that are associated with this application.
    DescribeEnvironments -> Maybe Text
applicationName :: Prelude.Maybe Prelude.Text,
    -- | If specified, AWS Elastic Beanstalk restricts the returned descriptions
    -- to include only those that have the specified IDs.
    DescribeEnvironments -> Maybe [Text]
environmentIds :: Prelude.Maybe [Prelude.Text],
    -- | If specified, AWS Elastic Beanstalk restricts the returned descriptions
    -- to include only those that have the specified names.
    DescribeEnvironments -> Maybe [Text]
environmentNames :: Prelude.Maybe [Prelude.Text],
    -- | Indicates whether to include deleted environments:
    --
    -- @true@: Environments that have been deleted after
    -- @IncludedDeletedBackTo@ are displayed.
    --
    -- @false@: Do not include deleted environments.
    DescribeEnvironments -> Maybe Bool
includeDeleted :: Prelude.Maybe Prelude.Bool,
    -- | If specified when @IncludeDeleted@ is set to @true@, then environments
    -- deleted after this date are displayed.
    DescribeEnvironments -> Maybe ISO8601
includedDeletedBackTo :: Prelude.Maybe Data.ISO8601,
    -- | For a paginated request. Specify a maximum number of environments to
    -- include in each response.
    --
    -- If no @MaxRecords@ is specified, all available environments are
    -- retrieved in a single response.
    DescribeEnvironments -> Maybe Natural
maxRecords :: Prelude.Maybe Prelude.Natural,
    -- | For a paginated request. Specify a token from a previous response page
    -- to retrieve the next response page. All other parameter values must be
    -- identical to the ones specified in the initial request.
    --
    -- If no @NextToken@ is specified, the first page is retrieved.
    DescribeEnvironments -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | If specified, AWS Elastic Beanstalk restricts the returned descriptions
    -- to include only those that are associated with this application version.
    DescribeEnvironments -> Maybe Text
versionLabel :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeEnvironments -> DescribeEnvironments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeEnvironments -> DescribeEnvironments -> Bool
$c/= :: DescribeEnvironments -> DescribeEnvironments -> Bool
== :: DescribeEnvironments -> DescribeEnvironments -> Bool
$c== :: DescribeEnvironments -> DescribeEnvironments -> Bool
Prelude.Eq, ReadPrec [DescribeEnvironments]
ReadPrec DescribeEnvironments
Int -> ReadS DescribeEnvironments
ReadS [DescribeEnvironments]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeEnvironments]
$creadListPrec :: ReadPrec [DescribeEnvironments]
readPrec :: ReadPrec DescribeEnvironments
$creadPrec :: ReadPrec DescribeEnvironments
readList :: ReadS [DescribeEnvironments]
$creadList :: ReadS [DescribeEnvironments]
readsPrec :: Int -> ReadS DescribeEnvironments
$creadsPrec :: Int -> ReadS DescribeEnvironments
Prelude.Read, Int -> DescribeEnvironments -> ShowS
[DescribeEnvironments] -> ShowS
DescribeEnvironments -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeEnvironments] -> ShowS
$cshowList :: [DescribeEnvironments] -> ShowS
show :: DescribeEnvironments -> String
$cshow :: DescribeEnvironments -> String
showsPrec :: Int -> DescribeEnvironments -> ShowS
$cshowsPrec :: Int -> DescribeEnvironments -> ShowS
Prelude.Show, forall x. Rep DescribeEnvironments x -> DescribeEnvironments
forall x. DescribeEnvironments -> Rep DescribeEnvironments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeEnvironments x -> DescribeEnvironments
$cfrom :: forall x. DescribeEnvironments -> Rep DescribeEnvironments x
Prelude.Generic)

-- |
-- Create a value of 'DescribeEnvironments' 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:
--
-- 'applicationName', 'describeEnvironments_applicationName' - If specified, AWS Elastic Beanstalk restricts the returned descriptions
-- to include only those that are associated with this application.
--
-- 'environmentIds', 'describeEnvironments_environmentIds' - If specified, AWS Elastic Beanstalk restricts the returned descriptions
-- to include only those that have the specified IDs.
--
-- 'environmentNames', 'describeEnvironments_environmentNames' - If specified, AWS Elastic Beanstalk restricts the returned descriptions
-- to include only those that have the specified names.
--
-- 'includeDeleted', 'describeEnvironments_includeDeleted' - Indicates whether to include deleted environments:
--
-- @true@: Environments that have been deleted after
-- @IncludedDeletedBackTo@ are displayed.
--
-- @false@: Do not include deleted environments.
--
-- 'includedDeletedBackTo', 'describeEnvironments_includedDeletedBackTo' - If specified when @IncludeDeleted@ is set to @true@, then environments
-- deleted after this date are displayed.
--
-- 'maxRecords', 'describeEnvironments_maxRecords' - For a paginated request. Specify a maximum number of environments to
-- include in each response.
--
-- If no @MaxRecords@ is specified, all available environments are
-- retrieved in a single response.
--
-- 'nextToken', 'describeEnvironments_nextToken' - For a paginated request. Specify a token from a previous response page
-- to retrieve the next response page. All other parameter values must be
-- identical to the ones specified in the initial request.
--
-- If no @NextToken@ is specified, the first page is retrieved.
--
-- 'versionLabel', 'describeEnvironments_versionLabel' - If specified, AWS Elastic Beanstalk restricts the returned descriptions
-- to include only those that are associated with this application version.
newDescribeEnvironments ::
  DescribeEnvironments
newDescribeEnvironments :: DescribeEnvironments
newDescribeEnvironments =
  DescribeEnvironments'
    { $sel:applicationName:DescribeEnvironments' :: Maybe Text
applicationName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:environmentIds:DescribeEnvironments' :: Maybe [Text]
environmentIds = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentNames:DescribeEnvironments' :: Maybe [Text]
environmentNames = forall a. Maybe a
Prelude.Nothing,
      $sel:includeDeleted:DescribeEnvironments' :: Maybe Bool
includeDeleted = forall a. Maybe a
Prelude.Nothing,
      $sel:includedDeletedBackTo:DescribeEnvironments' :: Maybe ISO8601
includedDeletedBackTo = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRecords:DescribeEnvironments' :: Maybe Natural
maxRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeEnvironments' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:versionLabel:DescribeEnvironments' :: Maybe Text
versionLabel = forall a. Maybe a
Prelude.Nothing
    }

-- | If specified, AWS Elastic Beanstalk restricts the returned descriptions
-- to include only those that are associated with this application.
describeEnvironments_applicationName :: Lens.Lens' DescribeEnvironments (Prelude.Maybe Prelude.Text)
describeEnvironments_applicationName :: Lens' DescribeEnvironments (Maybe Text)
describeEnvironments_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEnvironments' {Maybe Text
applicationName :: Maybe Text
$sel:applicationName:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
applicationName} -> Maybe Text
applicationName) (\s :: DescribeEnvironments
s@DescribeEnvironments' {} Maybe Text
a -> DescribeEnvironments
s {$sel:applicationName:DescribeEnvironments' :: Maybe Text
applicationName = Maybe Text
a} :: DescribeEnvironments)

-- | If specified, AWS Elastic Beanstalk restricts the returned descriptions
-- to include only those that have the specified IDs.
describeEnvironments_environmentIds :: Lens.Lens' DescribeEnvironments (Prelude.Maybe [Prelude.Text])
describeEnvironments_environmentIds :: Lens' DescribeEnvironments (Maybe [Text])
describeEnvironments_environmentIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEnvironments' {Maybe [Text]
environmentIds :: Maybe [Text]
$sel:environmentIds:DescribeEnvironments' :: DescribeEnvironments -> Maybe [Text]
environmentIds} -> Maybe [Text]
environmentIds) (\s :: DescribeEnvironments
s@DescribeEnvironments' {} Maybe [Text]
a -> DescribeEnvironments
s {$sel:environmentIds:DescribeEnvironments' :: Maybe [Text]
environmentIds = Maybe [Text]
a} :: DescribeEnvironments) 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

-- | If specified, AWS Elastic Beanstalk restricts the returned descriptions
-- to include only those that have the specified names.
describeEnvironments_environmentNames :: Lens.Lens' DescribeEnvironments (Prelude.Maybe [Prelude.Text])
describeEnvironments_environmentNames :: Lens' DescribeEnvironments (Maybe [Text])
describeEnvironments_environmentNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEnvironments' {Maybe [Text]
environmentNames :: Maybe [Text]
$sel:environmentNames:DescribeEnvironments' :: DescribeEnvironments -> Maybe [Text]
environmentNames} -> Maybe [Text]
environmentNames) (\s :: DescribeEnvironments
s@DescribeEnvironments' {} Maybe [Text]
a -> DescribeEnvironments
s {$sel:environmentNames:DescribeEnvironments' :: Maybe [Text]
environmentNames = Maybe [Text]
a} :: DescribeEnvironments) 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

-- | Indicates whether to include deleted environments:
--
-- @true@: Environments that have been deleted after
-- @IncludedDeletedBackTo@ are displayed.
--
-- @false@: Do not include deleted environments.
describeEnvironments_includeDeleted :: Lens.Lens' DescribeEnvironments (Prelude.Maybe Prelude.Bool)
describeEnvironments_includeDeleted :: Lens' DescribeEnvironments (Maybe Bool)
describeEnvironments_includeDeleted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEnvironments' {Maybe Bool
includeDeleted :: Maybe Bool
$sel:includeDeleted:DescribeEnvironments' :: DescribeEnvironments -> Maybe Bool
includeDeleted} -> Maybe Bool
includeDeleted) (\s :: DescribeEnvironments
s@DescribeEnvironments' {} Maybe Bool
a -> DescribeEnvironments
s {$sel:includeDeleted:DescribeEnvironments' :: Maybe Bool
includeDeleted = Maybe Bool
a} :: DescribeEnvironments)

-- | If specified when @IncludeDeleted@ is set to @true@, then environments
-- deleted after this date are displayed.
describeEnvironments_includedDeletedBackTo :: Lens.Lens' DescribeEnvironments (Prelude.Maybe Prelude.UTCTime)
describeEnvironments_includedDeletedBackTo :: Lens' DescribeEnvironments (Maybe UTCTime)
describeEnvironments_includedDeletedBackTo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEnvironments' {Maybe ISO8601
includedDeletedBackTo :: Maybe ISO8601
$sel:includedDeletedBackTo:DescribeEnvironments' :: DescribeEnvironments -> Maybe ISO8601
includedDeletedBackTo} -> Maybe ISO8601
includedDeletedBackTo) (\s :: DescribeEnvironments
s@DescribeEnvironments' {} Maybe ISO8601
a -> DescribeEnvironments
s {$sel:includedDeletedBackTo:DescribeEnvironments' :: Maybe ISO8601
includedDeletedBackTo = Maybe ISO8601
a} :: DescribeEnvironments) 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

-- | For a paginated request. Specify a maximum number of environments to
-- include in each response.
--
-- If no @MaxRecords@ is specified, all available environments are
-- retrieved in a single response.
describeEnvironments_maxRecords :: Lens.Lens' DescribeEnvironments (Prelude.Maybe Prelude.Natural)
describeEnvironments_maxRecords :: Lens' DescribeEnvironments (Maybe Natural)
describeEnvironments_maxRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEnvironments' {Maybe Natural
maxRecords :: Maybe Natural
$sel:maxRecords:DescribeEnvironments' :: DescribeEnvironments -> Maybe Natural
maxRecords} -> Maybe Natural
maxRecords) (\s :: DescribeEnvironments
s@DescribeEnvironments' {} Maybe Natural
a -> DescribeEnvironments
s {$sel:maxRecords:DescribeEnvironments' :: Maybe Natural
maxRecords = Maybe Natural
a} :: DescribeEnvironments)

-- | For a paginated request. Specify a token from a previous response page
-- to retrieve the next response page. All other parameter values must be
-- identical to the ones specified in the initial request.
--
-- If no @NextToken@ is specified, the first page is retrieved.
describeEnvironments_nextToken :: Lens.Lens' DescribeEnvironments (Prelude.Maybe Prelude.Text)
describeEnvironments_nextToken :: Lens' DescribeEnvironments (Maybe Text)
describeEnvironments_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEnvironments' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeEnvironments
s@DescribeEnvironments' {} Maybe Text
a -> DescribeEnvironments
s {$sel:nextToken:DescribeEnvironments' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeEnvironments)

-- | If specified, AWS Elastic Beanstalk restricts the returned descriptions
-- to include only those that are associated with this application version.
describeEnvironments_versionLabel :: Lens.Lens' DescribeEnvironments (Prelude.Maybe Prelude.Text)
describeEnvironments_versionLabel :: Lens' DescribeEnvironments (Maybe Text)
describeEnvironments_versionLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeEnvironments' {Maybe Text
versionLabel :: Maybe Text
$sel:versionLabel:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
versionLabel} -> Maybe Text
versionLabel) (\s :: DescribeEnvironments
s@DescribeEnvironments' {} Maybe Text
a -> DescribeEnvironments
s {$sel:versionLabel:DescribeEnvironments' :: Maybe Text
versionLabel = Maybe Text
a} :: DescribeEnvironments)

instance Core.AWSPager DescribeEnvironments where
  page :: DescribeEnvironments
-> AWSResponse DescribeEnvironments -> Maybe DescribeEnvironments
page DescribeEnvironments
rq AWSResponse DescribeEnvironments
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeEnvironments
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' EnvironmentDescriptionsMessage (Maybe Text)
environmentDescriptionsMessage_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 DescribeEnvironments
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  EnvironmentDescriptionsMessage (Maybe [EnvironmentDescription])
environmentDescriptionsMessage_environments
            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.$ DescribeEnvironments
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeEnvironments (Maybe Text)
describeEnvironments_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeEnvironments
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' EnvironmentDescriptionsMessage (Maybe Text)
environmentDescriptionsMessage_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 DescribeEnvironments where
  type
    AWSResponse DescribeEnvironments =
      EnvironmentDescriptionsMessage
  request :: (Service -> Service)
-> DescribeEnvironments -> Request DescribeEnvironments
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeEnvironments
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeEnvironments)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DescribeEnvironmentsResult"
      (\Int
s ResponseHeaders
h [Node]
x -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable DescribeEnvironments where
  hashWithSalt :: Int -> DescribeEnvironments -> Int
hashWithSalt Int
_salt DescribeEnvironments' {Maybe Bool
Maybe Natural
Maybe [Text]
Maybe Text
Maybe ISO8601
versionLabel :: Maybe Text
nextToken :: Maybe Text
maxRecords :: Maybe Natural
includedDeletedBackTo :: Maybe ISO8601
includeDeleted :: Maybe Bool
environmentNames :: Maybe [Text]
environmentIds :: Maybe [Text]
applicationName :: Maybe Text
$sel:versionLabel:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
$sel:nextToken:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
$sel:maxRecords:DescribeEnvironments' :: DescribeEnvironments -> Maybe Natural
$sel:includedDeletedBackTo:DescribeEnvironments' :: DescribeEnvironments -> Maybe ISO8601
$sel:includeDeleted:DescribeEnvironments' :: DescribeEnvironments -> Maybe Bool
$sel:environmentNames:DescribeEnvironments' :: DescribeEnvironments -> Maybe [Text]
$sel:environmentIds:DescribeEnvironments' :: DescribeEnvironments -> Maybe [Text]
$sel:applicationName:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
applicationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
environmentIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
environmentNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
includeDeleted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
includedDeletedBackTo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxRecords
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
versionLabel

instance Prelude.NFData DescribeEnvironments where
  rnf :: DescribeEnvironments -> ()
rnf DescribeEnvironments' {Maybe Bool
Maybe Natural
Maybe [Text]
Maybe Text
Maybe ISO8601
versionLabel :: Maybe Text
nextToken :: Maybe Text
maxRecords :: Maybe Natural
includedDeletedBackTo :: Maybe ISO8601
includeDeleted :: Maybe Bool
environmentNames :: Maybe [Text]
environmentIds :: Maybe [Text]
applicationName :: Maybe Text
$sel:versionLabel:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
$sel:nextToken:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
$sel:maxRecords:DescribeEnvironments' :: DescribeEnvironments -> Maybe Natural
$sel:includedDeletedBackTo:DescribeEnvironments' :: DescribeEnvironments -> Maybe ISO8601
$sel:includeDeleted:DescribeEnvironments' :: DescribeEnvironments -> Maybe Bool
$sel:environmentNames:DescribeEnvironments' :: DescribeEnvironments -> Maybe [Text]
$sel:environmentIds:DescribeEnvironments' :: DescribeEnvironments -> Maybe [Text]
$sel:applicationName:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
applicationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
environmentIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
environmentNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeDeleted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
includedDeletedBackTo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxRecords
      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 Text
versionLabel

instance Data.ToHeaders DescribeEnvironments where
  toHeaders :: DescribeEnvironments -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DescribeEnvironments where
  toQuery :: DescribeEnvironments -> QueryString
toQuery DescribeEnvironments' {Maybe Bool
Maybe Natural
Maybe [Text]
Maybe Text
Maybe ISO8601
versionLabel :: Maybe Text
nextToken :: Maybe Text
maxRecords :: Maybe Natural
includedDeletedBackTo :: Maybe ISO8601
includeDeleted :: Maybe Bool
environmentNames :: Maybe [Text]
environmentIds :: Maybe [Text]
applicationName :: Maybe Text
$sel:versionLabel:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
$sel:nextToken:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
$sel:maxRecords:DescribeEnvironments' :: DescribeEnvironments -> Maybe Natural
$sel:includedDeletedBackTo:DescribeEnvironments' :: DescribeEnvironments -> Maybe ISO8601
$sel:includeDeleted:DescribeEnvironments' :: DescribeEnvironments -> Maybe Bool
$sel:environmentNames:DescribeEnvironments' :: DescribeEnvironments -> Maybe [Text]
$sel:environmentIds:DescribeEnvironments' :: DescribeEnvironments -> Maybe [Text]
$sel:applicationName:DescribeEnvironments' :: DescribeEnvironments -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeEnvironments" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"ApplicationName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
applicationName,
        ByteString
"EnvironmentIds"
          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 [Text]
environmentIds
            ),
        ByteString
"EnvironmentNames"
          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 [Text]
environmentNames
            ),
        ByteString
"IncludeDeleted" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
includeDeleted,
        ByteString
"IncludedDeletedBackTo"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
includedDeletedBackTo,
        ByteString
"MaxRecords" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxRecords,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"VersionLabel" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
versionLabel
      ]