{-# 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.Proton.ListEnvironmentOutputs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- List the infrastructure as code outputs for your environment.
--
-- This operation returns paginated results.
module Amazonka.Proton.ListEnvironmentOutputs
  ( -- * Creating a Request
    ListEnvironmentOutputs (..),
    newListEnvironmentOutputs,

    -- * Request Lenses
    listEnvironmentOutputs_nextToken,
    listEnvironmentOutputs_environmentName,

    -- * Destructuring the Response
    ListEnvironmentOutputsResponse (..),
    newListEnvironmentOutputsResponse,

    -- * Response Lenses
    listEnvironmentOutputsResponse_nextToken,
    listEnvironmentOutputsResponse_httpStatus,
    listEnvironmentOutputsResponse_outputs,
  )
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 Amazonka.Proton.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListEnvironmentOutputs' smart constructor.
data ListEnvironmentOutputs = ListEnvironmentOutputs'
  { -- | A token that indicates the location of the next environment output in
    -- the array of environment outputs, after the list of environment outputs
    -- that was previously requested.
    ListEnvironmentOutputs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The environment name.
    ListEnvironmentOutputs -> Text
environmentName :: Prelude.Text
  }
  deriving (ListEnvironmentOutputs -> ListEnvironmentOutputs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListEnvironmentOutputs -> ListEnvironmentOutputs -> Bool
$c/= :: ListEnvironmentOutputs -> ListEnvironmentOutputs -> Bool
== :: ListEnvironmentOutputs -> ListEnvironmentOutputs -> Bool
$c== :: ListEnvironmentOutputs -> ListEnvironmentOutputs -> Bool
Prelude.Eq, ReadPrec [ListEnvironmentOutputs]
ReadPrec ListEnvironmentOutputs
Int -> ReadS ListEnvironmentOutputs
ReadS [ListEnvironmentOutputs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListEnvironmentOutputs]
$creadListPrec :: ReadPrec [ListEnvironmentOutputs]
readPrec :: ReadPrec ListEnvironmentOutputs
$creadPrec :: ReadPrec ListEnvironmentOutputs
readList :: ReadS [ListEnvironmentOutputs]
$creadList :: ReadS [ListEnvironmentOutputs]
readsPrec :: Int -> ReadS ListEnvironmentOutputs
$creadsPrec :: Int -> ReadS ListEnvironmentOutputs
Prelude.Read, Int -> ListEnvironmentOutputs -> ShowS
[ListEnvironmentOutputs] -> ShowS
ListEnvironmentOutputs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListEnvironmentOutputs] -> ShowS
$cshowList :: [ListEnvironmentOutputs] -> ShowS
show :: ListEnvironmentOutputs -> String
$cshow :: ListEnvironmentOutputs -> String
showsPrec :: Int -> ListEnvironmentOutputs -> ShowS
$cshowsPrec :: Int -> ListEnvironmentOutputs -> ShowS
Prelude.Show, forall x. Rep ListEnvironmentOutputs x -> ListEnvironmentOutputs
forall x. ListEnvironmentOutputs -> Rep ListEnvironmentOutputs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListEnvironmentOutputs x -> ListEnvironmentOutputs
$cfrom :: forall x. ListEnvironmentOutputs -> Rep ListEnvironmentOutputs x
Prelude.Generic)

-- |
-- Create a value of 'ListEnvironmentOutputs' 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', 'listEnvironmentOutputs_nextToken' - A token that indicates the location of the next environment output in
-- the array of environment outputs, after the list of environment outputs
-- that was previously requested.
--
-- 'environmentName', 'listEnvironmentOutputs_environmentName' - The environment name.
newListEnvironmentOutputs ::
  -- | 'environmentName'
  Prelude.Text ->
  ListEnvironmentOutputs
newListEnvironmentOutputs :: Text -> ListEnvironmentOutputs
newListEnvironmentOutputs Text
pEnvironmentName_ =
  ListEnvironmentOutputs'
    { $sel:nextToken:ListEnvironmentOutputs' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:environmentName:ListEnvironmentOutputs' :: Text
environmentName = Text
pEnvironmentName_
    }

-- | A token that indicates the location of the next environment output in
-- the array of environment outputs, after the list of environment outputs
-- that was previously requested.
listEnvironmentOutputs_nextToken :: Lens.Lens' ListEnvironmentOutputs (Prelude.Maybe Prelude.Text)
listEnvironmentOutputs_nextToken :: Lens' ListEnvironmentOutputs (Maybe Text)
listEnvironmentOutputs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEnvironmentOutputs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListEnvironmentOutputs' :: ListEnvironmentOutputs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListEnvironmentOutputs
s@ListEnvironmentOutputs' {} Maybe Text
a -> ListEnvironmentOutputs
s {$sel:nextToken:ListEnvironmentOutputs' :: Maybe Text
nextToken = Maybe Text
a} :: ListEnvironmentOutputs)

-- | The environment name.
listEnvironmentOutputs_environmentName :: Lens.Lens' ListEnvironmentOutputs Prelude.Text
listEnvironmentOutputs_environmentName :: Lens' ListEnvironmentOutputs Text
listEnvironmentOutputs_environmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEnvironmentOutputs' {Text
environmentName :: Text
$sel:environmentName:ListEnvironmentOutputs' :: ListEnvironmentOutputs -> Text
environmentName} -> Text
environmentName) (\s :: ListEnvironmentOutputs
s@ListEnvironmentOutputs' {} Text
a -> ListEnvironmentOutputs
s {$sel:environmentName:ListEnvironmentOutputs' :: Text
environmentName = Text
a} :: ListEnvironmentOutputs)

instance Core.AWSPager ListEnvironmentOutputs where
  page :: ListEnvironmentOutputs
-> AWSResponse ListEnvironmentOutputs
-> Maybe ListEnvironmentOutputs
page ListEnvironmentOutputs
rq AWSResponse ListEnvironmentOutputs
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListEnvironmentOutputs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListEnvironmentOutputsResponse (Maybe Text)
listEnvironmentOutputsResponse_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 ListEnvironmentOutputs
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListEnvironmentOutputsResponse [Output]
listEnvironmentOutputsResponse_outputs) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListEnvironmentOutputs
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListEnvironmentOutputs (Maybe Text)
listEnvironmentOutputs_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListEnvironmentOutputs
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListEnvironmentOutputsResponse (Maybe Text)
listEnvironmentOutputsResponse_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 ListEnvironmentOutputs where
  type
    AWSResponse ListEnvironmentOutputs =
      ListEnvironmentOutputsResponse
  request :: (Service -> Service)
-> ListEnvironmentOutputs -> Request ListEnvironmentOutputs
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 ListEnvironmentOutputs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListEnvironmentOutputs)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Int -> [Sensitive Output] -> ListEnvironmentOutputsResponse
ListEnvironmentOutputsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"nextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"outputs" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListEnvironmentOutputs where
  hashWithSalt :: Int -> ListEnvironmentOutputs -> Int
hashWithSalt Int
_salt ListEnvironmentOutputs' {Maybe Text
Text
environmentName :: Text
nextToken :: Maybe Text
$sel:environmentName:ListEnvironmentOutputs' :: ListEnvironmentOutputs -> Text
$sel:nextToken:ListEnvironmentOutputs' :: ListEnvironmentOutputs -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentName

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

instance Data.ToHeaders ListEnvironmentOutputs where
  toHeaders :: ListEnvironmentOutputs -> 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
"AwsProton20200720.ListEnvironmentOutputs" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListEnvironmentOutputs where
  toJSON :: ListEnvironmentOutputs -> Value
toJSON ListEnvironmentOutputs' {Maybe Text
Text
environmentName :: Text
nextToken :: Maybe Text
$sel:environmentName:ListEnvironmentOutputs' :: ListEnvironmentOutputs -> Text
$sel:nextToken:ListEnvironmentOutputs' :: ListEnvironmentOutputs -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"environmentName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
environmentName)
          ]
      )

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

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

-- | /See:/ 'newListEnvironmentOutputsResponse' smart constructor.
data ListEnvironmentOutputsResponse = ListEnvironmentOutputsResponse'
  { -- | A token that indicates the location of the next environment output in
    -- the array of environment outputs, after the current requested list of
    -- environment outputs.
    ListEnvironmentOutputsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListEnvironmentOutputsResponse -> Int
httpStatus :: Prelude.Int,
    -- | An array of environment outputs with detail data.
    ListEnvironmentOutputsResponse -> [Sensitive Output]
outputs :: [Data.Sensitive Output]
  }
  deriving (ListEnvironmentOutputsResponse
-> ListEnvironmentOutputsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListEnvironmentOutputsResponse
-> ListEnvironmentOutputsResponse -> Bool
$c/= :: ListEnvironmentOutputsResponse
-> ListEnvironmentOutputsResponse -> Bool
== :: ListEnvironmentOutputsResponse
-> ListEnvironmentOutputsResponse -> Bool
$c== :: ListEnvironmentOutputsResponse
-> ListEnvironmentOutputsResponse -> Bool
Prelude.Eq, Int -> ListEnvironmentOutputsResponse -> ShowS
[ListEnvironmentOutputsResponse] -> ShowS
ListEnvironmentOutputsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListEnvironmentOutputsResponse] -> ShowS
$cshowList :: [ListEnvironmentOutputsResponse] -> ShowS
show :: ListEnvironmentOutputsResponse -> String
$cshow :: ListEnvironmentOutputsResponse -> String
showsPrec :: Int -> ListEnvironmentOutputsResponse -> ShowS
$cshowsPrec :: Int -> ListEnvironmentOutputsResponse -> ShowS
Prelude.Show, forall x.
Rep ListEnvironmentOutputsResponse x
-> ListEnvironmentOutputsResponse
forall x.
ListEnvironmentOutputsResponse
-> Rep ListEnvironmentOutputsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListEnvironmentOutputsResponse x
-> ListEnvironmentOutputsResponse
$cfrom :: forall x.
ListEnvironmentOutputsResponse
-> Rep ListEnvironmentOutputsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListEnvironmentOutputsResponse' 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', 'listEnvironmentOutputsResponse_nextToken' - A token that indicates the location of the next environment output in
-- the array of environment outputs, after the current requested list of
-- environment outputs.
--
-- 'httpStatus', 'listEnvironmentOutputsResponse_httpStatus' - The response's http status code.
--
-- 'outputs', 'listEnvironmentOutputsResponse_outputs' - An array of environment outputs with detail data.
newListEnvironmentOutputsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListEnvironmentOutputsResponse
newListEnvironmentOutputsResponse :: Int -> ListEnvironmentOutputsResponse
newListEnvironmentOutputsResponse Int
pHttpStatus_ =
  ListEnvironmentOutputsResponse'
    { $sel:nextToken:ListEnvironmentOutputsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListEnvironmentOutputsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:outputs:ListEnvironmentOutputsResponse' :: [Sensitive Output]
outputs = forall a. Monoid a => a
Prelude.mempty
    }

-- | A token that indicates the location of the next environment output in
-- the array of environment outputs, after the current requested list of
-- environment outputs.
listEnvironmentOutputsResponse_nextToken :: Lens.Lens' ListEnvironmentOutputsResponse (Prelude.Maybe Prelude.Text)
listEnvironmentOutputsResponse_nextToken :: Lens' ListEnvironmentOutputsResponse (Maybe Text)
listEnvironmentOutputsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEnvironmentOutputsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListEnvironmentOutputsResponse' :: ListEnvironmentOutputsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListEnvironmentOutputsResponse
s@ListEnvironmentOutputsResponse' {} Maybe Text
a -> ListEnvironmentOutputsResponse
s {$sel:nextToken:ListEnvironmentOutputsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListEnvironmentOutputsResponse)

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

-- | An array of environment outputs with detail data.
listEnvironmentOutputsResponse_outputs :: Lens.Lens' ListEnvironmentOutputsResponse [Output]
listEnvironmentOutputsResponse_outputs :: Lens' ListEnvironmentOutputsResponse [Output]
listEnvironmentOutputsResponse_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEnvironmentOutputsResponse' {[Sensitive Output]
outputs :: [Sensitive Output]
$sel:outputs:ListEnvironmentOutputsResponse' :: ListEnvironmentOutputsResponse -> [Sensitive Output]
outputs} -> [Sensitive Output]
outputs) (\s :: ListEnvironmentOutputsResponse
s@ListEnvironmentOutputsResponse' {} [Sensitive Output]
a -> ListEnvironmentOutputsResponse
s {$sel:outputs:ListEnvironmentOutputsResponse' :: [Sensitive Output]
outputs = [Sensitive Output]
a} :: ListEnvironmentOutputsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance
  Prelude.NFData
    ListEnvironmentOutputsResponse
  where
  rnf :: ListEnvironmentOutputsResponse -> ()
rnf ListEnvironmentOutputsResponse' {Int
[Sensitive Output]
Maybe Text
outputs :: [Sensitive Output]
httpStatus :: Int
nextToken :: Maybe Text
$sel:outputs:ListEnvironmentOutputsResponse' :: ListEnvironmentOutputsResponse -> [Sensitive Output]
$sel:httpStatus:ListEnvironmentOutputsResponse' :: ListEnvironmentOutputsResponse -> Int
$sel:nextToken:ListEnvironmentOutputsResponse' :: ListEnvironmentOutputsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Sensitive Output]
outputs