{-# 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.ListServiceInstanceOutputs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Get a list service of instance Infrastructure as Code (IaC) outputs.
--
-- This operation returns paginated results.
module Amazonka.Proton.ListServiceInstanceOutputs
  ( -- * Creating a Request
    ListServiceInstanceOutputs (..),
    newListServiceInstanceOutputs,

    -- * Request Lenses
    listServiceInstanceOutputs_nextToken,
    listServiceInstanceOutputs_serviceInstanceName,
    listServiceInstanceOutputs_serviceName,

    -- * Destructuring the Response
    ListServiceInstanceOutputsResponse (..),
    newListServiceInstanceOutputsResponse,

    -- * Response Lenses
    listServiceInstanceOutputsResponse_nextToken,
    listServiceInstanceOutputsResponse_httpStatus,
    listServiceInstanceOutputsResponse_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:/ 'newListServiceInstanceOutputs' smart constructor.
data ListServiceInstanceOutputs = ListServiceInstanceOutputs'
  { -- | A token that indicates the location of the next output in the array of
    -- outputs, after the list of outputs that was previously requested.
    ListServiceInstanceOutputs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the service instance whose outputs you want.
    ListServiceInstanceOutputs -> Text
serviceInstanceName :: Prelude.Text,
    -- | The name of the service that @serviceInstanceName@ is associated to.
    ListServiceInstanceOutputs -> Text
serviceName :: Prelude.Text
  }
  deriving (ListServiceInstanceOutputs -> ListServiceInstanceOutputs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListServiceInstanceOutputs -> ListServiceInstanceOutputs -> Bool
$c/= :: ListServiceInstanceOutputs -> ListServiceInstanceOutputs -> Bool
== :: ListServiceInstanceOutputs -> ListServiceInstanceOutputs -> Bool
$c== :: ListServiceInstanceOutputs -> ListServiceInstanceOutputs -> Bool
Prelude.Eq, ReadPrec [ListServiceInstanceOutputs]
ReadPrec ListServiceInstanceOutputs
Int -> ReadS ListServiceInstanceOutputs
ReadS [ListServiceInstanceOutputs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListServiceInstanceOutputs]
$creadListPrec :: ReadPrec [ListServiceInstanceOutputs]
readPrec :: ReadPrec ListServiceInstanceOutputs
$creadPrec :: ReadPrec ListServiceInstanceOutputs
readList :: ReadS [ListServiceInstanceOutputs]
$creadList :: ReadS [ListServiceInstanceOutputs]
readsPrec :: Int -> ReadS ListServiceInstanceOutputs
$creadsPrec :: Int -> ReadS ListServiceInstanceOutputs
Prelude.Read, Int -> ListServiceInstanceOutputs -> ShowS
[ListServiceInstanceOutputs] -> ShowS
ListServiceInstanceOutputs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListServiceInstanceOutputs] -> ShowS
$cshowList :: [ListServiceInstanceOutputs] -> ShowS
show :: ListServiceInstanceOutputs -> String
$cshow :: ListServiceInstanceOutputs -> String
showsPrec :: Int -> ListServiceInstanceOutputs -> ShowS
$cshowsPrec :: Int -> ListServiceInstanceOutputs -> ShowS
Prelude.Show, forall x.
Rep ListServiceInstanceOutputs x -> ListServiceInstanceOutputs
forall x.
ListServiceInstanceOutputs -> Rep ListServiceInstanceOutputs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListServiceInstanceOutputs x -> ListServiceInstanceOutputs
$cfrom :: forall x.
ListServiceInstanceOutputs -> Rep ListServiceInstanceOutputs x
Prelude.Generic)

-- |
-- Create a value of 'ListServiceInstanceOutputs' 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', 'listServiceInstanceOutputs_nextToken' - A token that indicates the location of the next output in the array of
-- outputs, after the list of outputs that was previously requested.
--
-- 'serviceInstanceName', 'listServiceInstanceOutputs_serviceInstanceName' - The name of the service instance whose outputs you want.
--
-- 'serviceName', 'listServiceInstanceOutputs_serviceName' - The name of the service that @serviceInstanceName@ is associated to.
newListServiceInstanceOutputs ::
  -- | 'serviceInstanceName'
  Prelude.Text ->
  -- | 'serviceName'
  Prelude.Text ->
  ListServiceInstanceOutputs
newListServiceInstanceOutputs :: Text -> Text -> ListServiceInstanceOutputs
newListServiceInstanceOutputs
  Text
pServiceInstanceName_
  Text
pServiceName_ =
    ListServiceInstanceOutputs'
      { $sel:nextToken:ListServiceInstanceOutputs' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:serviceInstanceName:ListServiceInstanceOutputs' :: Text
serviceInstanceName = Text
pServiceInstanceName_,
        $sel:serviceName:ListServiceInstanceOutputs' :: Text
serviceName = Text
pServiceName_
      }

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

-- | The name of the service instance whose outputs you want.
listServiceInstanceOutputs_serviceInstanceName :: Lens.Lens' ListServiceInstanceOutputs Prelude.Text
listServiceInstanceOutputs_serviceInstanceName :: Lens' ListServiceInstanceOutputs Text
listServiceInstanceOutputs_serviceInstanceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListServiceInstanceOutputs' {Text
serviceInstanceName :: Text
$sel:serviceInstanceName:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> Text
serviceInstanceName} -> Text
serviceInstanceName) (\s :: ListServiceInstanceOutputs
s@ListServiceInstanceOutputs' {} Text
a -> ListServiceInstanceOutputs
s {$sel:serviceInstanceName:ListServiceInstanceOutputs' :: Text
serviceInstanceName = Text
a} :: ListServiceInstanceOutputs)

-- | The name of the service that @serviceInstanceName@ is associated to.
listServiceInstanceOutputs_serviceName :: Lens.Lens' ListServiceInstanceOutputs Prelude.Text
listServiceInstanceOutputs_serviceName :: Lens' ListServiceInstanceOutputs Text
listServiceInstanceOutputs_serviceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListServiceInstanceOutputs' {Text
serviceName :: Text
$sel:serviceName:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> Text
serviceName} -> Text
serviceName) (\s :: ListServiceInstanceOutputs
s@ListServiceInstanceOutputs' {} Text
a -> ListServiceInstanceOutputs
s {$sel:serviceName:ListServiceInstanceOutputs' :: Text
serviceName = Text
a} :: ListServiceInstanceOutputs)

instance Core.AWSPager ListServiceInstanceOutputs where
  page :: ListServiceInstanceOutputs
-> AWSResponse ListServiceInstanceOutputs
-> Maybe ListServiceInstanceOutputs
page ListServiceInstanceOutputs
rq AWSResponse ListServiceInstanceOutputs
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListServiceInstanceOutputs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListServiceInstanceOutputsResponse (Maybe Text)
listServiceInstanceOutputsResponse_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 ListServiceInstanceOutputs
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListServiceInstanceOutputsResponse [Output]
listServiceInstanceOutputsResponse_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.$ ListServiceInstanceOutputs
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListServiceInstanceOutputs (Maybe Text)
listServiceInstanceOutputs_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListServiceInstanceOutputs
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListServiceInstanceOutputsResponse (Maybe Text)
listServiceInstanceOutputsResponse_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 ListServiceInstanceOutputs where
  type
    AWSResponse ListServiceInstanceOutputs =
      ListServiceInstanceOutputsResponse
  request :: (Service -> Service)
-> ListServiceInstanceOutputs -> Request ListServiceInstanceOutputs
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 ListServiceInstanceOutputs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListServiceInstanceOutputs)))
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] -> ListServiceInstanceOutputsResponse
ListServiceInstanceOutputsResponse'
            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 ListServiceInstanceOutputs where
  hashWithSalt :: Int -> ListServiceInstanceOutputs -> Int
hashWithSalt Int
_salt ListServiceInstanceOutputs' {Maybe Text
Text
serviceName :: Text
serviceInstanceName :: Text
nextToken :: Maybe Text
$sel:serviceName:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> Text
$sel:serviceInstanceName:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> Text
$sel:nextToken:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> 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
serviceInstanceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceName

instance Prelude.NFData ListServiceInstanceOutputs where
  rnf :: ListServiceInstanceOutputs -> ()
rnf ListServiceInstanceOutputs' {Maybe Text
Text
serviceName :: Text
serviceInstanceName :: Text
nextToken :: Maybe Text
$sel:serviceName:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> Text
$sel:serviceInstanceName:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> Text
$sel:nextToken:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> 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
serviceInstanceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serviceName

instance Data.ToHeaders ListServiceInstanceOutputs where
  toHeaders :: ListServiceInstanceOutputs -> 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.ListServiceInstanceOutputs" ::
                          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 ListServiceInstanceOutputs where
  toJSON :: ListServiceInstanceOutputs -> Value
toJSON ListServiceInstanceOutputs' {Maybe Text
Text
serviceName :: Text
serviceInstanceName :: Text
nextToken :: Maybe Text
$sel:serviceName:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> Text
$sel:serviceInstanceName:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> Text
$sel:nextToken:ListServiceInstanceOutputs' :: ListServiceInstanceOutputs -> 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
"serviceInstanceName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serviceInstanceName),
            forall a. a -> Maybe a
Prelude.Just (Key
"serviceName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serviceName)
          ]
      )

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

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

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

-- |
-- Create a value of 'ListServiceInstanceOutputsResponse' 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', 'listServiceInstanceOutputsResponse_nextToken' - A token that indicates the location of the next output in the array of
-- outputs, after the current requested list of outputs.
--
-- 'httpStatus', 'listServiceInstanceOutputsResponse_httpStatus' - The response's http status code.
--
-- 'outputs', 'listServiceInstanceOutputsResponse_outputs' - An array of service instance Infrastructure as Code (IaC) outputs.
newListServiceInstanceOutputsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListServiceInstanceOutputsResponse
newListServiceInstanceOutputsResponse :: Int -> ListServiceInstanceOutputsResponse
newListServiceInstanceOutputsResponse Int
pHttpStatus_ =
  ListServiceInstanceOutputsResponse'
    { $sel:nextToken:ListServiceInstanceOutputsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListServiceInstanceOutputsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:outputs:ListServiceInstanceOutputsResponse' :: [Sensitive Output]
outputs = forall a. Monoid a => a
Prelude.mempty
    }

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

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

-- | An array of service instance Infrastructure as Code (IaC) outputs.
listServiceInstanceOutputsResponse_outputs :: Lens.Lens' ListServiceInstanceOutputsResponse [Output]
listServiceInstanceOutputsResponse_outputs :: Lens' ListServiceInstanceOutputsResponse [Output]
listServiceInstanceOutputsResponse_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListServiceInstanceOutputsResponse' {[Sensitive Output]
outputs :: [Sensitive Output]
$sel:outputs:ListServiceInstanceOutputsResponse' :: ListServiceInstanceOutputsResponse -> [Sensitive Output]
outputs} -> [Sensitive Output]
outputs) (\s :: ListServiceInstanceOutputsResponse
s@ListServiceInstanceOutputsResponse' {} [Sensitive Output]
a -> ListServiceInstanceOutputsResponse
s {$sel:outputs:ListServiceInstanceOutputsResponse' :: [Sensitive Output]
outputs = [Sensitive Output]
a} :: ListServiceInstanceOutputsResponse) 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
    ListServiceInstanceOutputsResponse
  where
  rnf :: ListServiceInstanceOutputsResponse -> ()
rnf ListServiceInstanceOutputsResponse' {Int
[Sensitive Output]
Maybe Text
outputs :: [Sensitive Output]
httpStatus :: Int
nextToken :: Maybe Text
$sel:outputs:ListServiceInstanceOutputsResponse' :: ListServiceInstanceOutputsResponse -> [Sensitive Output]
$sel:httpStatus:ListServiceInstanceOutputsResponse' :: ListServiceInstanceOutputsResponse -> Int
$sel:nextToken:ListServiceInstanceOutputsResponse' :: ListServiceInstanceOutputsResponse -> 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