{-# 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.ApiGatewayV2.GetIntegrationResponse
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets an IntegrationResponses.
module Amazonka.ApiGatewayV2.GetIntegrationResponse
  ( -- * Creating a Request
    GetIntegrationResponse (..),
    newGetIntegrationResponse,

    -- * Request Lenses
    getIntegrationResponse_apiId,
    getIntegrationResponse_integrationResponseId,
    getIntegrationResponse_integrationId,

    -- * Destructuring the Response
    GetIntegrationResponseResponse (..),
    newGetIntegrationResponseResponse,

    -- * Response Lenses
    getIntegrationResponseResponse_contentHandlingStrategy,
    getIntegrationResponseResponse_integrationResponseId,
    getIntegrationResponseResponse_integrationResponseKey,
    getIntegrationResponseResponse_responseParameters,
    getIntegrationResponseResponse_responseTemplates,
    getIntegrationResponseResponse_templateSelectionExpression,
    getIntegrationResponseResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetIntegrationResponse' smart constructor.
data GetIntegrationResponse = GetIntegrationResponse'
  { -- | The API identifier.
    GetIntegrationResponse -> Text
apiId :: Prelude.Text,
    -- | The integration response ID.
    GetIntegrationResponse -> Text
integrationResponseId :: Prelude.Text,
    -- | The integration ID.
    GetIntegrationResponse -> Text
integrationId :: Prelude.Text
  }
  deriving (GetIntegrationResponse -> GetIntegrationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIntegrationResponse -> GetIntegrationResponse -> Bool
$c/= :: GetIntegrationResponse -> GetIntegrationResponse -> Bool
== :: GetIntegrationResponse -> GetIntegrationResponse -> Bool
$c== :: GetIntegrationResponse -> GetIntegrationResponse -> Bool
Prelude.Eq, ReadPrec [GetIntegrationResponse]
ReadPrec GetIntegrationResponse
Int -> ReadS GetIntegrationResponse
ReadS [GetIntegrationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIntegrationResponse]
$creadListPrec :: ReadPrec [GetIntegrationResponse]
readPrec :: ReadPrec GetIntegrationResponse
$creadPrec :: ReadPrec GetIntegrationResponse
readList :: ReadS [GetIntegrationResponse]
$creadList :: ReadS [GetIntegrationResponse]
readsPrec :: Int -> ReadS GetIntegrationResponse
$creadsPrec :: Int -> ReadS GetIntegrationResponse
Prelude.Read, Int -> GetIntegrationResponse -> ShowS
[GetIntegrationResponse] -> ShowS
GetIntegrationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIntegrationResponse] -> ShowS
$cshowList :: [GetIntegrationResponse] -> ShowS
show :: GetIntegrationResponse -> String
$cshow :: GetIntegrationResponse -> String
showsPrec :: Int -> GetIntegrationResponse -> ShowS
$cshowsPrec :: Int -> GetIntegrationResponse -> ShowS
Prelude.Show, forall x. Rep GetIntegrationResponse x -> GetIntegrationResponse
forall x. GetIntegrationResponse -> Rep GetIntegrationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetIntegrationResponse x -> GetIntegrationResponse
$cfrom :: forall x. GetIntegrationResponse -> Rep GetIntegrationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetIntegrationResponse' 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:
--
-- 'apiId', 'getIntegrationResponse_apiId' - The API identifier.
--
-- 'integrationResponseId', 'getIntegrationResponse_integrationResponseId' - The integration response ID.
--
-- 'integrationId', 'getIntegrationResponse_integrationId' - The integration ID.
newGetIntegrationResponse ::
  -- | 'apiId'
  Prelude.Text ->
  -- | 'integrationResponseId'
  Prelude.Text ->
  -- | 'integrationId'
  Prelude.Text ->
  GetIntegrationResponse
newGetIntegrationResponse :: Text -> Text -> Text -> GetIntegrationResponse
newGetIntegrationResponse
  Text
pApiId_
  Text
pIntegrationResponseId_
  Text
pIntegrationId_ =
    GetIntegrationResponse'
      { $sel:apiId:GetIntegrationResponse' :: Text
apiId = Text
pApiId_,
        $sel:integrationResponseId:GetIntegrationResponse' :: Text
integrationResponseId = Text
pIntegrationResponseId_,
        $sel:integrationId:GetIntegrationResponse' :: Text
integrationId = Text
pIntegrationId_
      }

-- | The API identifier.
getIntegrationResponse_apiId :: Lens.Lens' GetIntegrationResponse Prelude.Text
getIntegrationResponse_apiId :: Lens' GetIntegrationResponse Text
getIntegrationResponse_apiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIntegrationResponse' {Text
apiId :: Text
$sel:apiId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
apiId} -> Text
apiId) (\s :: GetIntegrationResponse
s@GetIntegrationResponse' {} Text
a -> GetIntegrationResponse
s {$sel:apiId:GetIntegrationResponse' :: Text
apiId = Text
a} :: GetIntegrationResponse)

-- | The integration response ID.
getIntegrationResponse_integrationResponseId :: Lens.Lens' GetIntegrationResponse Prelude.Text
getIntegrationResponse_integrationResponseId :: Lens' GetIntegrationResponse Text
getIntegrationResponse_integrationResponseId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIntegrationResponse' {Text
integrationResponseId :: Text
$sel:integrationResponseId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
integrationResponseId} -> Text
integrationResponseId) (\s :: GetIntegrationResponse
s@GetIntegrationResponse' {} Text
a -> GetIntegrationResponse
s {$sel:integrationResponseId:GetIntegrationResponse' :: Text
integrationResponseId = Text
a} :: GetIntegrationResponse)

-- | The integration ID.
getIntegrationResponse_integrationId :: Lens.Lens' GetIntegrationResponse Prelude.Text
getIntegrationResponse_integrationId :: Lens' GetIntegrationResponse Text
getIntegrationResponse_integrationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIntegrationResponse' {Text
integrationId :: Text
$sel:integrationId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
integrationId} -> Text
integrationId) (\s :: GetIntegrationResponse
s@GetIntegrationResponse' {} Text
a -> GetIntegrationResponse
s {$sel:integrationId:GetIntegrationResponse' :: Text
integrationId = Text
a} :: GetIntegrationResponse)

instance Core.AWSRequest GetIntegrationResponse where
  type
    AWSResponse GetIntegrationResponse =
      GetIntegrationResponseResponse
  request :: (Service -> Service)
-> GetIntegrationResponse -> Request GetIntegrationResponse
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 GetIntegrationResponse
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetIntegrationResponse)))
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 ContentHandlingStrategy
-> Maybe Text
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Int
-> GetIntegrationResponseResponse
GetIntegrationResponseResponse'
            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
"contentHandlingStrategy")
            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
"integrationResponseId")
            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
"integrationResponseKey")
            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
"responseParameters"
                            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.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"responseTemplates"
                            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"templateSelectionExpression")
            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 GetIntegrationResponse where
  hashWithSalt :: Int -> GetIntegrationResponse -> Int
hashWithSalt Int
_salt GetIntegrationResponse' {Text
integrationId :: Text
integrationResponseId :: Text
apiId :: Text
$sel:integrationId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
$sel:integrationResponseId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
$sel:apiId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
apiId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
integrationResponseId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
integrationId

instance Prelude.NFData GetIntegrationResponse where
  rnf :: GetIntegrationResponse -> ()
rnf GetIntegrationResponse' {Text
integrationId :: Text
integrationResponseId :: Text
apiId :: Text
$sel:integrationId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
$sel:integrationResponseId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
$sel:apiId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
apiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
integrationResponseId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
integrationId

instance Data.ToHeaders GetIntegrationResponse where
  toHeaders :: GetIntegrationResponse -> 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 GetIntegrationResponse where
  toPath :: GetIntegrationResponse -> ByteString
toPath GetIntegrationResponse' {Text
integrationId :: Text
integrationResponseId :: Text
apiId :: Text
$sel:integrationId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
$sel:integrationResponseId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
$sel:apiId:GetIntegrationResponse' :: GetIntegrationResponse -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v2/apis/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
apiId,
        ByteString
"/integrations/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
integrationId,
        ByteString
"/integrationresponses/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
integrationResponseId
      ]

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

-- | /See:/ 'newGetIntegrationResponseResponse' smart constructor.
data GetIntegrationResponseResponse = GetIntegrationResponseResponse'
  { -- | Supported only for WebSocket APIs. Specifies how to handle response
    -- payload content type conversions. Supported values are CONVERT_TO_BINARY
    -- and CONVERT_TO_TEXT, with the following behaviors:
    --
    -- CONVERT_TO_BINARY: Converts a response payload from a Base64-encoded
    -- string to the corresponding binary blob.
    --
    -- CONVERT_TO_TEXT: Converts a response payload from a binary blob to a
    -- Base64-encoded string.
    --
    -- If this property is not defined, the response payload will be passed
    -- through from the integration response to the route response or method
    -- response without modification.
    GetIntegrationResponseResponse -> Maybe ContentHandlingStrategy
contentHandlingStrategy :: Prelude.Maybe ContentHandlingStrategy,
    -- | The integration response ID.
    GetIntegrationResponseResponse -> Maybe Text
integrationResponseId :: Prelude.Maybe Prelude.Text,
    -- | The integration response key.
    GetIntegrationResponseResponse -> Maybe Text
integrationResponseKey :: Prelude.Maybe Prelude.Text,
    -- | A key-value map specifying response parameters that are passed to the
    -- method response from the backend. The key is a method response header
    -- parameter name and the mapped value is an integration response header
    -- value, a static value enclosed within a pair of single quotes, or a JSON
    -- expression from the integration response body. The mapping key must
    -- match the pattern of method.response.header.{name}, where name is a
    -- valid and unique header name. The mapped non-static value must match the
    -- pattern of integration.response.header.{name} or
    -- integration.response.body.{JSON-expression}, where name is a valid and
    -- unique response header name and JSON-expression is a valid JSON
    -- expression without the $ prefix.
    GetIntegrationResponseResponse -> Maybe (HashMap Text Text)
responseParameters :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The collection of response templates for the integration response as a
    -- string-to-string map of key-value pairs. Response templates are
    -- represented as a key\/value map, with a content-type as the key and a
    -- template as the value.
    GetIntegrationResponseResponse -> Maybe (HashMap Text Text)
responseTemplates :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The template selection expressions for the integration response.
    GetIntegrationResponseResponse -> Maybe Text
templateSelectionExpression :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetIntegrationResponseResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetIntegrationResponseResponse
-> GetIntegrationResponseResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIntegrationResponseResponse
-> GetIntegrationResponseResponse -> Bool
$c/= :: GetIntegrationResponseResponse
-> GetIntegrationResponseResponse -> Bool
== :: GetIntegrationResponseResponse
-> GetIntegrationResponseResponse -> Bool
$c== :: GetIntegrationResponseResponse
-> GetIntegrationResponseResponse -> Bool
Prelude.Eq, ReadPrec [GetIntegrationResponseResponse]
ReadPrec GetIntegrationResponseResponse
Int -> ReadS GetIntegrationResponseResponse
ReadS [GetIntegrationResponseResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIntegrationResponseResponse]
$creadListPrec :: ReadPrec [GetIntegrationResponseResponse]
readPrec :: ReadPrec GetIntegrationResponseResponse
$creadPrec :: ReadPrec GetIntegrationResponseResponse
readList :: ReadS [GetIntegrationResponseResponse]
$creadList :: ReadS [GetIntegrationResponseResponse]
readsPrec :: Int -> ReadS GetIntegrationResponseResponse
$creadsPrec :: Int -> ReadS GetIntegrationResponseResponse
Prelude.Read, Int -> GetIntegrationResponseResponse -> ShowS
[GetIntegrationResponseResponse] -> ShowS
GetIntegrationResponseResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIntegrationResponseResponse] -> ShowS
$cshowList :: [GetIntegrationResponseResponse] -> ShowS
show :: GetIntegrationResponseResponse -> String
$cshow :: GetIntegrationResponseResponse -> String
showsPrec :: Int -> GetIntegrationResponseResponse -> ShowS
$cshowsPrec :: Int -> GetIntegrationResponseResponse -> ShowS
Prelude.Show, forall x.
Rep GetIntegrationResponseResponse x
-> GetIntegrationResponseResponse
forall x.
GetIntegrationResponseResponse
-> Rep GetIntegrationResponseResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetIntegrationResponseResponse x
-> GetIntegrationResponseResponse
$cfrom :: forall x.
GetIntegrationResponseResponse
-> Rep GetIntegrationResponseResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetIntegrationResponseResponse' 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:
--
-- 'contentHandlingStrategy', 'getIntegrationResponseResponse_contentHandlingStrategy' - Supported only for WebSocket APIs. Specifies how to handle response
-- payload content type conversions. Supported values are CONVERT_TO_BINARY
-- and CONVERT_TO_TEXT, with the following behaviors:
--
-- CONVERT_TO_BINARY: Converts a response payload from a Base64-encoded
-- string to the corresponding binary blob.
--
-- CONVERT_TO_TEXT: Converts a response payload from a binary blob to a
-- Base64-encoded string.
--
-- If this property is not defined, the response payload will be passed
-- through from the integration response to the route response or method
-- response without modification.
--
-- 'integrationResponseId', 'getIntegrationResponseResponse_integrationResponseId' - The integration response ID.
--
-- 'integrationResponseKey', 'getIntegrationResponseResponse_integrationResponseKey' - The integration response key.
--
-- 'responseParameters', 'getIntegrationResponseResponse_responseParameters' - A key-value map specifying response parameters that are passed to the
-- method response from the backend. The key is a method response header
-- parameter name and the mapped value is an integration response header
-- value, a static value enclosed within a pair of single quotes, or a JSON
-- expression from the integration response body. The mapping key must
-- match the pattern of method.response.header.{name}, where name is a
-- valid and unique header name. The mapped non-static value must match the
-- pattern of integration.response.header.{name} or
-- integration.response.body.{JSON-expression}, where name is a valid and
-- unique response header name and JSON-expression is a valid JSON
-- expression without the $ prefix.
--
-- 'responseTemplates', 'getIntegrationResponseResponse_responseTemplates' - The collection of response templates for the integration response as a
-- string-to-string map of key-value pairs. Response templates are
-- represented as a key\/value map, with a content-type as the key and a
-- template as the value.
--
-- 'templateSelectionExpression', 'getIntegrationResponseResponse_templateSelectionExpression' - The template selection expressions for the integration response.
--
-- 'httpStatus', 'getIntegrationResponseResponse_httpStatus' - The response's http status code.
newGetIntegrationResponseResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetIntegrationResponseResponse
newGetIntegrationResponseResponse :: Int -> GetIntegrationResponseResponse
newGetIntegrationResponseResponse Int
pHttpStatus_ =
  GetIntegrationResponseResponse'
    { $sel:contentHandlingStrategy:GetIntegrationResponseResponse' :: Maybe ContentHandlingStrategy
contentHandlingStrategy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:integrationResponseId:GetIntegrationResponseResponse' :: Maybe Text
integrationResponseId = forall a. Maybe a
Prelude.Nothing,
      $sel:integrationResponseKey:GetIntegrationResponseResponse' :: Maybe Text
integrationResponseKey = forall a. Maybe a
Prelude.Nothing,
      $sel:responseParameters:GetIntegrationResponseResponse' :: Maybe (HashMap Text Text)
responseParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:responseTemplates:GetIntegrationResponseResponse' :: Maybe (HashMap Text Text)
responseTemplates = forall a. Maybe a
Prelude.Nothing,
      $sel:templateSelectionExpression:GetIntegrationResponseResponse' :: Maybe Text
templateSelectionExpression =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetIntegrationResponseResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Supported only for WebSocket APIs. Specifies how to handle response
-- payload content type conversions. Supported values are CONVERT_TO_BINARY
-- and CONVERT_TO_TEXT, with the following behaviors:
--
-- CONVERT_TO_BINARY: Converts a response payload from a Base64-encoded
-- string to the corresponding binary blob.
--
-- CONVERT_TO_TEXT: Converts a response payload from a binary blob to a
-- Base64-encoded string.
--
-- If this property is not defined, the response payload will be passed
-- through from the integration response to the route response or method
-- response without modification.
getIntegrationResponseResponse_contentHandlingStrategy :: Lens.Lens' GetIntegrationResponseResponse (Prelude.Maybe ContentHandlingStrategy)
getIntegrationResponseResponse_contentHandlingStrategy :: Lens'
  GetIntegrationResponseResponse (Maybe ContentHandlingStrategy)
getIntegrationResponseResponse_contentHandlingStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIntegrationResponseResponse' {Maybe ContentHandlingStrategy
contentHandlingStrategy :: Maybe ContentHandlingStrategy
$sel:contentHandlingStrategy:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe ContentHandlingStrategy
contentHandlingStrategy} -> Maybe ContentHandlingStrategy
contentHandlingStrategy) (\s :: GetIntegrationResponseResponse
s@GetIntegrationResponseResponse' {} Maybe ContentHandlingStrategy
a -> GetIntegrationResponseResponse
s {$sel:contentHandlingStrategy:GetIntegrationResponseResponse' :: Maybe ContentHandlingStrategy
contentHandlingStrategy = Maybe ContentHandlingStrategy
a} :: GetIntegrationResponseResponse)

-- | The integration response ID.
getIntegrationResponseResponse_integrationResponseId :: Lens.Lens' GetIntegrationResponseResponse (Prelude.Maybe Prelude.Text)
getIntegrationResponseResponse_integrationResponseId :: Lens' GetIntegrationResponseResponse (Maybe Text)
getIntegrationResponseResponse_integrationResponseId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIntegrationResponseResponse' {Maybe Text
integrationResponseId :: Maybe Text
$sel:integrationResponseId:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe Text
integrationResponseId} -> Maybe Text
integrationResponseId) (\s :: GetIntegrationResponseResponse
s@GetIntegrationResponseResponse' {} Maybe Text
a -> GetIntegrationResponseResponse
s {$sel:integrationResponseId:GetIntegrationResponseResponse' :: Maybe Text
integrationResponseId = Maybe Text
a} :: GetIntegrationResponseResponse)

-- | The integration response key.
getIntegrationResponseResponse_integrationResponseKey :: Lens.Lens' GetIntegrationResponseResponse (Prelude.Maybe Prelude.Text)
getIntegrationResponseResponse_integrationResponseKey :: Lens' GetIntegrationResponseResponse (Maybe Text)
getIntegrationResponseResponse_integrationResponseKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIntegrationResponseResponse' {Maybe Text
integrationResponseKey :: Maybe Text
$sel:integrationResponseKey:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe Text
integrationResponseKey} -> Maybe Text
integrationResponseKey) (\s :: GetIntegrationResponseResponse
s@GetIntegrationResponseResponse' {} Maybe Text
a -> GetIntegrationResponseResponse
s {$sel:integrationResponseKey:GetIntegrationResponseResponse' :: Maybe Text
integrationResponseKey = Maybe Text
a} :: GetIntegrationResponseResponse)

-- | A key-value map specifying response parameters that are passed to the
-- method response from the backend. The key is a method response header
-- parameter name and the mapped value is an integration response header
-- value, a static value enclosed within a pair of single quotes, or a JSON
-- expression from the integration response body. The mapping key must
-- match the pattern of method.response.header.{name}, where name is a
-- valid and unique header name. The mapped non-static value must match the
-- pattern of integration.response.header.{name} or
-- integration.response.body.{JSON-expression}, where name is a valid and
-- unique response header name and JSON-expression is a valid JSON
-- expression without the $ prefix.
getIntegrationResponseResponse_responseParameters :: Lens.Lens' GetIntegrationResponseResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getIntegrationResponseResponse_responseParameters :: Lens' GetIntegrationResponseResponse (Maybe (HashMap Text Text))
getIntegrationResponseResponse_responseParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIntegrationResponseResponse' {Maybe (HashMap Text Text)
responseParameters :: Maybe (HashMap Text Text)
$sel:responseParameters:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe (HashMap Text Text)
responseParameters} -> Maybe (HashMap Text Text)
responseParameters) (\s :: GetIntegrationResponseResponse
s@GetIntegrationResponseResponse' {} Maybe (HashMap Text Text)
a -> GetIntegrationResponseResponse
s {$sel:responseParameters:GetIntegrationResponseResponse' :: Maybe (HashMap Text Text)
responseParameters = Maybe (HashMap Text Text)
a} :: GetIntegrationResponseResponse) 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 collection of response templates for the integration response as a
-- string-to-string map of key-value pairs. Response templates are
-- represented as a key\/value map, with a content-type as the key and a
-- template as the value.
getIntegrationResponseResponse_responseTemplates :: Lens.Lens' GetIntegrationResponseResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getIntegrationResponseResponse_responseTemplates :: Lens' GetIntegrationResponseResponse (Maybe (HashMap Text Text))
getIntegrationResponseResponse_responseTemplates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIntegrationResponseResponse' {Maybe (HashMap Text Text)
responseTemplates :: Maybe (HashMap Text Text)
$sel:responseTemplates:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe (HashMap Text Text)
responseTemplates} -> Maybe (HashMap Text Text)
responseTemplates) (\s :: GetIntegrationResponseResponse
s@GetIntegrationResponseResponse' {} Maybe (HashMap Text Text)
a -> GetIntegrationResponseResponse
s {$sel:responseTemplates:GetIntegrationResponseResponse' :: Maybe (HashMap Text Text)
responseTemplates = Maybe (HashMap Text Text)
a} :: GetIntegrationResponseResponse) 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 template selection expressions for the integration response.
getIntegrationResponseResponse_templateSelectionExpression :: Lens.Lens' GetIntegrationResponseResponse (Prelude.Maybe Prelude.Text)
getIntegrationResponseResponse_templateSelectionExpression :: Lens' GetIntegrationResponseResponse (Maybe Text)
getIntegrationResponseResponse_templateSelectionExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIntegrationResponseResponse' {Maybe Text
templateSelectionExpression :: Maybe Text
$sel:templateSelectionExpression:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe Text
templateSelectionExpression} -> Maybe Text
templateSelectionExpression) (\s :: GetIntegrationResponseResponse
s@GetIntegrationResponseResponse' {} Maybe Text
a -> GetIntegrationResponseResponse
s {$sel:templateSelectionExpression:GetIntegrationResponseResponse' :: Maybe Text
templateSelectionExpression = Maybe Text
a} :: GetIntegrationResponseResponse)

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

instance
  Prelude.NFData
    GetIntegrationResponseResponse
  where
  rnf :: GetIntegrationResponseResponse -> ()
rnf GetIntegrationResponseResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
Maybe ContentHandlingStrategy
httpStatus :: Int
templateSelectionExpression :: Maybe Text
responseTemplates :: Maybe (HashMap Text Text)
responseParameters :: Maybe (HashMap Text Text)
integrationResponseKey :: Maybe Text
integrationResponseId :: Maybe Text
contentHandlingStrategy :: Maybe ContentHandlingStrategy
$sel:httpStatus:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Int
$sel:templateSelectionExpression:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe Text
$sel:responseTemplates:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe (HashMap Text Text)
$sel:responseParameters:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe (HashMap Text Text)
$sel:integrationResponseKey:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe Text
$sel:integrationResponseId:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe Text
$sel:contentHandlingStrategy:GetIntegrationResponseResponse' :: GetIntegrationResponseResponse -> Maybe ContentHandlingStrategy
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ContentHandlingStrategy
contentHandlingStrategy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
integrationResponseId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
integrationResponseKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
responseParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
responseTemplates
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
templateSelectionExpression
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus