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

    -- * Request Lenses
    importApi_basepath,
    importApi_failOnWarnings,
    importApi_body,

    -- * Destructuring the Response
    ImportApiResponse (..),
    newImportApiResponse,

    -- * Response Lenses
    importApiResponse_apiEndpoint,
    importApiResponse_apiGatewayManaged,
    importApiResponse_apiId,
    importApiResponse_apiKeySelectionExpression,
    importApiResponse_corsConfiguration,
    importApiResponse_createdDate,
    importApiResponse_description,
    importApiResponse_disableExecuteApiEndpoint,
    importApiResponse_disableSchemaValidation,
    importApiResponse_importInfo,
    importApiResponse_name,
    importApiResponse_protocolType,
    importApiResponse_routeSelectionExpression,
    importApiResponse_tags,
    importApiResponse_version,
    importApiResponse_warnings,
    importApiResponse_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:/ 'newImportApi' smart constructor.
data ImportApi = ImportApi'
  { -- | Specifies how to interpret the base path of the API during import. Valid
    -- values are ignore, prepend, and split. The default value is ignore. To
    -- learn more, see
    -- <https://docs.aws.amazon.com/apigateway/latest/developerguide/api-gateway-import-api-basePath.html Set the OpenAPI basePath Property>.
    -- Supported only for HTTP APIs.
    ImportApi -> Maybe Text
basepath :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether to rollback the API creation when a warning is
    -- encountered. By default, API creation continues if a warning is
    -- encountered.
    ImportApi -> Maybe Bool
failOnWarnings :: Prelude.Maybe Prelude.Bool,
    -- | The OpenAPI definition. Supported only for HTTP APIs.
    ImportApi -> Text
body :: Prelude.Text
  }
  deriving (ImportApi -> ImportApi -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportApi -> ImportApi -> Bool
$c/= :: ImportApi -> ImportApi -> Bool
== :: ImportApi -> ImportApi -> Bool
$c== :: ImportApi -> ImportApi -> Bool
Prelude.Eq, ReadPrec [ImportApi]
ReadPrec ImportApi
Int -> ReadS ImportApi
ReadS [ImportApi]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportApi]
$creadListPrec :: ReadPrec [ImportApi]
readPrec :: ReadPrec ImportApi
$creadPrec :: ReadPrec ImportApi
readList :: ReadS [ImportApi]
$creadList :: ReadS [ImportApi]
readsPrec :: Int -> ReadS ImportApi
$creadsPrec :: Int -> ReadS ImportApi
Prelude.Read, Int -> ImportApi -> ShowS
[ImportApi] -> ShowS
ImportApi -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportApi] -> ShowS
$cshowList :: [ImportApi] -> ShowS
show :: ImportApi -> String
$cshow :: ImportApi -> String
showsPrec :: Int -> ImportApi -> ShowS
$cshowsPrec :: Int -> ImportApi -> ShowS
Prelude.Show, forall x. Rep ImportApi x -> ImportApi
forall x. ImportApi -> Rep ImportApi x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportApi x -> ImportApi
$cfrom :: forall x. ImportApi -> Rep ImportApi x
Prelude.Generic)

-- |
-- Create a value of 'ImportApi' 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:
--
-- 'basepath', 'importApi_basepath' - Specifies how to interpret the base path of the API during import. Valid
-- values are ignore, prepend, and split. The default value is ignore. To
-- learn more, see
-- <https://docs.aws.amazon.com/apigateway/latest/developerguide/api-gateway-import-api-basePath.html Set the OpenAPI basePath Property>.
-- Supported only for HTTP APIs.
--
-- 'failOnWarnings', 'importApi_failOnWarnings' - Specifies whether to rollback the API creation when a warning is
-- encountered. By default, API creation continues if a warning is
-- encountered.
--
-- 'body', 'importApi_body' - The OpenAPI definition. Supported only for HTTP APIs.
newImportApi ::
  -- | 'body'
  Prelude.Text ->
  ImportApi
newImportApi :: Text -> ImportApi
newImportApi Text
pBody_ =
  ImportApi'
    { $sel:basepath:ImportApi' :: Maybe Text
basepath = forall a. Maybe a
Prelude.Nothing,
      $sel:failOnWarnings:ImportApi' :: Maybe Bool
failOnWarnings = forall a. Maybe a
Prelude.Nothing,
      $sel:body:ImportApi' :: Text
body = Text
pBody_
    }

-- | Specifies how to interpret the base path of the API during import. Valid
-- values are ignore, prepend, and split. The default value is ignore. To
-- learn more, see
-- <https://docs.aws.amazon.com/apigateway/latest/developerguide/api-gateway-import-api-basePath.html Set the OpenAPI basePath Property>.
-- Supported only for HTTP APIs.
importApi_basepath :: Lens.Lens' ImportApi (Prelude.Maybe Prelude.Text)
importApi_basepath :: Lens' ImportApi (Maybe Text)
importApi_basepath = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApi' {Maybe Text
basepath :: Maybe Text
$sel:basepath:ImportApi' :: ImportApi -> Maybe Text
basepath} -> Maybe Text
basepath) (\s :: ImportApi
s@ImportApi' {} Maybe Text
a -> ImportApi
s {$sel:basepath:ImportApi' :: Maybe Text
basepath = Maybe Text
a} :: ImportApi)

-- | Specifies whether to rollback the API creation when a warning is
-- encountered. By default, API creation continues if a warning is
-- encountered.
importApi_failOnWarnings :: Lens.Lens' ImportApi (Prelude.Maybe Prelude.Bool)
importApi_failOnWarnings :: Lens' ImportApi (Maybe Bool)
importApi_failOnWarnings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApi' {Maybe Bool
failOnWarnings :: Maybe Bool
$sel:failOnWarnings:ImportApi' :: ImportApi -> Maybe Bool
failOnWarnings} -> Maybe Bool
failOnWarnings) (\s :: ImportApi
s@ImportApi' {} Maybe Bool
a -> ImportApi
s {$sel:failOnWarnings:ImportApi' :: Maybe Bool
failOnWarnings = Maybe Bool
a} :: ImportApi)

-- | The OpenAPI definition. Supported only for HTTP APIs.
importApi_body :: Lens.Lens' ImportApi Prelude.Text
importApi_body :: Lens' ImportApi Text
importApi_body = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApi' {Text
body :: Text
$sel:body:ImportApi' :: ImportApi -> Text
body} -> Text
body) (\s :: ImportApi
s@ImportApi' {} Text
a -> ImportApi
s {$sel:body:ImportApi' :: Text
body = Text
a} :: ImportApi)

instance Core.AWSRequest ImportApi where
  type AWSResponse ImportApi = ImportApiResponse
  request :: (Service -> Service) -> ImportApi -> Request ImportApi
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ImportApi
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ImportApi)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Cors
-> Maybe ISO8601
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe [Text]
-> Maybe Text
-> Maybe ProtocolType
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe [Text]
-> Int
-> ImportApiResponse
ImportApiResponse'
            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
"apiEndpoint")
            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
"apiGatewayManaged")
            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
"apiId")
            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
"apiKeySelectionExpression")
            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
"corsConfiguration")
            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
"createdDate")
            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
"description")
            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
"disableExecuteApiEndpoint")
            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
"disableSchemaValidation")
            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
"importInfo" 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
"name")
            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
"protocolType")
            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
"routeSelectionExpression")
            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
"tags" 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
"version")
            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
"warnings" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ImportApi where
  hashWithSalt :: Int -> ImportApi -> Int
hashWithSalt Int
_salt ImportApi' {Maybe Bool
Maybe Text
Text
body :: Text
failOnWarnings :: Maybe Bool
basepath :: Maybe Text
$sel:body:ImportApi' :: ImportApi -> Text
$sel:failOnWarnings:ImportApi' :: ImportApi -> Maybe Bool
$sel:basepath:ImportApi' :: ImportApi -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
basepath
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
failOnWarnings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
body

instance Prelude.NFData ImportApi where
  rnf :: ImportApi -> ()
rnf ImportApi' {Maybe Bool
Maybe Text
Text
body :: Text
failOnWarnings :: Maybe Bool
basepath :: Maybe Text
$sel:body:ImportApi' :: ImportApi -> Text
$sel:failOnWarnings:ImportApi' :: ImportApi -> Maybe Bool
$sel:basepath:ImportApi' :: ImportApi -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
basepath
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
failOnWarnings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
body

instance Data.ToHeaders ImportApi where
  toHeaders :: ImportApi -> 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.ToJSON ImportApi where
  toJSON :: ImportApi -> Value
toJSON ImportApi' {Maybe Bool
Maybe Text
Text
body :: Text
failOnWarnings :: Maybe Bool
basepath :: Maybe Text
$sel:body:ImportApi' :: ImportApi -> Text
$sel:failOnWarnings:ImportApi' :: ImportApi -> Maybe Bool
$sel:basepath:ImportApi' :: ImportApi -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"body" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
body)]
      )

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

instance Data.ToQuery ImportApi where
  toQuery :: ImportApi -> QueryString
toQuery ImportApi' {Maybe Bool
Maybe Text
Text
body :: Text
failOnWarnings :: Maybe Bool
basepath :: Maybe Text
$sel:body:ImportApi' :: ImportApi -> Text
$sel:failOnWarnings:ImportApi' :: ImportApi -> Maybe Bool
$sel:basepath:ImportApi' :: ImportApi -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"basepath" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
basepath,
        ByteString
"failOnWarnings" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
failOnWarnings
      ]

-- | /See:/ 'newImportApiResponse' smart constructor.
data ImportApiResponse = ImportApiResponse'
  { -- | The URI of the API, of the form
    -- {api-id}.execute-api.{region}.amazonaws.com. The stage name is typically
    -- appended to this URI to form a complete path to a deployed API stage.
    ImportApiResponse -> Maybe Text
apiEndpoint :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether an API is managed by API Gateway. You can\'t update or
    -- delete a managed API by using API Gateway. A managed API can be deleted
    -- only through the tooling or service that created it.
    ImportApiResponse -> Maybe Bool
apiGatewayManaged :: Prelude.Maybe Prelude.Bool,
    -- | The API ID.
    ImportApiResponse -> Maybe Text
apiId :: Prelude.Maybe Prelude.Text,
    -- | An API key selection expression. Supported only for WebSocket APIs. See
    -- <https://docs.aws.amazon.com/apigateway/latest/developerguide/apigateway-websocket-api-selection-expressions.html#apigateway-websocket-api-apikey-selection-expressions API Key Selection Expressions>.
    ImportApiResponse -> Maybe Text
apiKeySelectionExpression :: Prelude.Maybe Prelude.Text,
    -- | A CORS configuration. Supported only for HTTP APIs.
    ImportApiResponse -> Maybe Cors
corsConfiguration :: Prelude.Maybe Cors,
    -- | The timestamp when the API was created.
    ImportApiResponse -> Maybe ISO8601
createdDate :: Prelude.Maybe Data.ISO8601,
    -- | The description of the API.
    ImportApiResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether clients can invoke your API by using the default
    -- execute-api endpoint. By default, clients can invoke your API with the
    -- default https:\/\/{api_id}.execute-api.{region}.amazonaws.com endpoint.
    -- To require that clients use a custom domain name to invoke your API,
    -- disable the default endpoint.
    ImportApiResponse -> Maybe Bool
disableExecuteApiEndpoint :: Prelude.Maybe Prelude.Bool,
    -- | Avoid validating models when creating a deployment. Supported only for
    -- WebSocket APIs.
    ImportApiResponse -> Maybe Bool
disableSchemaValidation :: Prelude.Maybe Prelude.Bool,
    -- | The validation information during API import. This may include
    -- particular properties of your OpenAPI definition which are ignored
    -- during import. Supported only for HTTP APIs.
    ImportApiResponse -> Maybe [Text]
importInfo :: Prelude.Maybe [Prelude.Text],
    -- | The name of the API.
    ImportApiResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The API protocol.
    ImportApiResponse -> Maybe ProtocolType
protocolType :: Prelude.Maybe ProtocolType,
    -- | The route selection expression for the API. For HTTP APIs, the
    -- routeSelectionExpression must be ${request.method} ${request.path}. If
    -- not provided, this will be the default for HTTP APIs. This property is
    -- required for WebSocket APIs.
    ImportApiResponse -> Maybe Text
routeSelectionExpression :: Prelude.Maybe Prelude.Text,
    -- | A collection of tags associated with the API.
    ImportApiResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A version identifier for the API.
    ImportApiResponse -> Maybe Text
version :: Prelude.Maybe Prelude.Text,
    -- | The warning messages reported when failonwarnings is turned on during
    -- API import.
    ImportApiResponse -> Maybe [Text]
warnings :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    ImportApiResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ImportApiResponse -> ImportApiResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportApiResponse -> ImportApiResponse -> Bool
$c/= :: ImportApiResponse -> ImportApiResponse -> Bool
== :: ImportApiResponse -> ImportApiResponse -> Bool
$c== :: ImportApiResponse -> ImportApiResponse -> Bool
Prelude.Eq, ReadPrec [ImportApiResponse]
ReadPrec ImportApiResponse
Int -> ReadS ImportApiResponse
ReadS [ImportApiResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportApiResponse]
$creadListPrec :: ReadPrec [ImportApiResponse]
readPrec :: ReadPrec ImportApiResponse
$creadPrec :: ReadPrec ImportApiResponse
readList :: ReadS [ImportApiResponse]
$creadList :: ReadS [ImportApiResponse]
readsPrec :: Int -> ReadS ImportApiResponse
$creadsPrec :: Int -> ReadS ImportApiResponse
Prelude.Read, Int -> ImportApiResponse -> ShowS
[ImportApiResponse] -> ShowS
ImportApiResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportApiResponse] -> ShowS
$cshowList :: [ImportApiResponse] -> ShowS
show :: ImportApiResponse -> String
$cshow :: ImportApiResponse -> String
showsPrec :: Int -> ImportApiResponse -> ShowS
$cshowsPrec :: Int -> ImportApiResponse -> ShowS
Prelude.Show, forall x. Rep ImportApiResponse x -> ImportApiResponse
forall x. ImportApiResponse -> Rep ImportApiResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportApiResponse x -> ImportApiResponse
$cfrom :: forall x. ImportApiResponse -> Rep ImportApiResponse x
Prelude.Generic)

-- |
-- Create a value of 'ImportApiResponse' 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:
--
-- 'apiEndpoint', 'importApiResponse_apiEndpoint' - The URI of the API, of the form
-- {api-id}.execute-api.{region}.amazonaws.com. The stage name is typically
-- appended to this URI to form a complete path to a deployed API stage.
--
-- 'apiGatewayManaged', 'importApiResponse_apiGatewayManaged' - Specifies whether an API is managed by API Gateway. You can\'t update or
-- delete a managed API by using API Gateway. A managed API can be deleted
-- only through the tooling or service that created it.
--
-- 'apiId', 'importApiResponse_apiId' - The API ID.
--
-- 'apiKeySelectionExpression', 'importApiResponse_apiKeySelectionExpression' - An API key selection expression. Supported only for WebSocket APIs. See
-- <https://docs.aws.amazon.com/apigateway/latest/developerguide/apigateway-websocket-api-selection-expressions.html#apigateway-websocket-api-apikey-selection-expressions API Key Selection Expressions>.
--
-- 'corsConfiguration', 'importApiResponse_corsConfiguration' - A CORS configuration. Supported only for HTTP APIs.
--
-- 'createdDate', 'importApiResponse_createdDate' - The timestamp when the API was created.
--
-- 'description', 'importApiResponse_description' - The description of the API.
--
-- 'disableExecuteApiEndpoint', 'importApiResponse_disableExecuteApiEndpoint' - Specifies whether clients can invoke your API by using the default
-- execute-api endpoint. By default, clients can invoke your API with the
-- default https:\/\/{api_id}.execute-api.{region}.amazonaws.com endpoint.
-- To require that clients use a custom domain name to invoke your API,
-- disable the default endpoint.
--
-- 'disableSchemaValidation', 'importApiResponse_disableSchemaValidation' - Avoid validating models when creating a deployment. Supported only for
-- WebSocket APIs.
--
-- 'importInfo', 'importApiResponse_importInfo' - The validation information during API import. This may include
-- particular properties of your OpenAPI definition which are ignored
-- during import. Supported only for HTTP APIs.
--
-- 'name', 'importApiResponse_name' - The name of the API.
--
-- 'protocolType', 'importApiResponse_protocolType' - The API protocol.
--
-- 'routeSelectionExpression', 'importApiResponse_routeSelectionExpression' - The route selection expression for the API. For HTTP APIs, the
-- routeSelectionExpression must be ${request.method} ${request.path}. If
-- not provided, this will be the default for HTTP APIs. This property is
-- required for WebSocket APIs.
--
-- 'tags', 'importApiResponse_tags' - A collection of tags associated with the API.
--
-- 'version', 'importApiResponse_version' - A version identifier for the API.
--
-- 'warnings', 'importApiResponse_warnings' - The warning messages reported when failonwarnings is turned on during
-- API import.
--
-- 'httpStatus', 'importApiResponse_httpStatus' - The response's http status code.
newImportApiResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ImportApiResponse
newImportApiResponse :: Int -> ImportApiResponse
newImportApiResponse Int
pHttpStatus_ =
  ImportApiResponse'
    { $sel:apiEndpoint:ImportApiResponse' :: Maybe Text
apiEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:apiGatewayManaged:ImportApiResponse' :: Maybe Bool
apiGatewayManaged = forall a. Maybe a
Prelude.Nothing,
      $sel:apiId:ImportApiResponse' :: Maybe Text
apiId = forall a. Maybe a
Prelude.Nothing,
      $sel:apiKeySelectionExpression:ImportApiResponse' :: Maybe Text
apiKeySelectionExpression = forall a. Maybe a
Prelude.Nothing,
      $sel:corsConfiguration:ImportApiResponse' :: Maybe Cors
corsConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:createdDate:ImportApiResponse' :: Maybe ISO8601
createdDate = forall a. Maybe a
Prelude.Nothing,
      $sel:description:ImportApiResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:disableExecuteApiEndpoint:ImportApiResponse' :: Maybe Bool
disableExecuteApiEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:disableSchemaValidation:ImportApiResponse' :: Maybe Bool
disableSchemaValidation = forall a. Maybe a
Prelude.Nothing,
      $sel:importInfo:ImportApiResponse' :: Maybe [Text]
importInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:name:ImportApiResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:protocolType:ImportApiResponse' :: Maybe ProtocolType
protocolType = forall a. Maybe a
Prelude.Nothing,
      $sel:routeSelectionExpression:ImportApiResponse' :: Maybe Text
routeSelectionExpression = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ImportApiResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:version:ImportApiResponse' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing,
      $sel:warnings:ImportApiResponse' :: Maybe [Text]
warnings = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ImportApiResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The URI of the API, of the form
-- {api-id}.execute-api.{region}.amazonaws.com. The stage name is typically
-- appended to this URI to form a complete path to a deployed API stage.
importApiResponse_apiEndpoint :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Text)
importApiResponse_apiEndpoint :: Lens' ImportApiResponse (Maybe Text)
importApiResponse_apiEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Text
apiEndpoint :: Maybe Text
$sel:apiEndpoint:ImportApiResponse' :: ImportApiResponse -> Maybe Text
apiEndpoint} -> Maybe Text
apiEndpoint) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Text
a -> ImportApiResponse
s {$sel:apiEndpoint:ImportApiResponse' :: Maybe Text
apiEndpoint = Maybe Text
a} :: ImportApiResponse)

-- | Specifies whether an API is managed by API Gateway. You can\'t update or
-- delete a managed API by using API Gateway. A managed API can be deleted
-- only through the tooling or service that created it.
importApiResponse_apiGatewayManaged :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Bool)
importApiResponse_apiGatewayManaged :: Lens' ImportApiResponse (Maybe Bool)
importApiResponse_apiGatewayManaged = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Bool
apiGatewayManaged :: Maybe Bool
$sel:apiGatewayManaged:ImportApiResponse' :: ImportApiResponse -> Maybe Bool
apiGatewayManaged} -> Maybe Bool
apiGatewayManaged) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Bool
a -> ImportApiResponse
s {$sel:apiGatewayManaged:ImportApiResponse' :: Maybe Bool
apiGatewayManaged = Maybe Bool
a} :: ImportApiResponse)

-- | The API ID.
importApiResponse_apiId :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Text)
importApiResponse_apiId :: Lens' ImportApiResponse (Maybe Text)
importApiResponse_apiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Text
apiId :: Maybe Text
$sel:apiId:ImportApiResponse' :: ImportApiResponse -> Maybe Text
apiId} -> Maybe Text
apiId) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Text
a -> ImportApiResponse
s {$sel:apiId:ImportApiResponse' :: Maybe Text
apiId = Maybe Text
a} :: ImportApiResponse)

-- | An API key selection expression. Supported only for WebSocket APIs. See
-- <https://docs.aws.amazon.com/apigateway/latest/developerguide/apigateway-websocket-api-selection-expressions.html#apigateway-websocket-api-apikey-selection-expressions API Key Selection Expressions>.
importApiResponse_apiKeySelectionExpression :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Text)
importApiResponse_apiKeySelectionExpression :: Lens' ImportApiResponse (Maybe Text)
importApiResponse_apiKeySelectionExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Text
apiKeySelectionExpression :: Maybe Text
$sel:apiKeySelectionExpression:ImportApiResponse' :: ImportApiResponse -> Maybe Text
apiKeySelectionExpression} -> Maybe Text
apiKeySelectionExpression) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Text
a -> ImportApiResponse
s {$sel:apiKeySelectionExpression:ImportApiResponse' :: Maybe Text
apiKeySelectionExpression = Maybe Text
a} :: ImportApiResponse)

-- | A CORS configuration. Supported only for HTTP APIs.
importApiResponse_corsConfiguration :: Lens.Lens' ImportApiResponse (Prelude.Maybe Cors)
importApiResponse_corsConfiguration :: Lens' ImportApiResponse (Maybe Cors)
importApiResponse_corsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Cors
corsConfiguration :: Maybe Cors
$sel:corsConfiguration:ImportApiResponse' :: ImportApiResponse -> Maybe Cors
corsConfiguration} -> Maybe Cors
corsConfiguration) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Cors
a -> ImportApiResponse
s {$sel:corsConfiguration:ImportApiResponse' :: Maybe Cors
corsConfiguration = Maybe Cors
a} :: ImportApiResponse)

-- | The timestamp when the API was created.
importApiResponse_createdDate :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.UTCTime)
importApiResponse_createdDate :: Lens' ImportApiResponse (Maybe UTCTime)
importApiResponse_createdDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe ISO8601
createdDate :: Maybe ISO8601
$sel:createdDate:ImportApiResponse' :: ImportApiResponse -> Maybe ISO8601
createdDate} -> Maybe ISO8601
createdDate) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe ISO8601
a -> ImportApiResponse
s {$sel:createdDate:ImportApiResponse' :: Maybe ISO8601
createdDate = Maybe ISO8601
a} :: ImportApiResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The description of the API.
importApiResponse_description :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Text)
importApiResponse_description :: Lens' ImportApiResponse (Maybe Text)
importApiResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Text
description :: Maybe Text
$sel:description:ImportApiResponse' :: ImportApiResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Text
a -> ImportApiResponse
s {$sel:description:ImportApiResponse' :: Maybe Text
description = Maybe Text
a} :: ImportApiResponse)

-- | Specifies whether clients can invoke your API by using the default
-- execute-api endpoint. By default, clients can invoke your API with the
-- default https:\/\/{api_id}.execute-api.{region}.amazonaws.com endpoint.
-- To require that clients use a custom domain name to invoke your API,
-- disable the default endpoint.
importApiResponse_disableExecuteApiEndpoint :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Bool)
importApiResponse_disableExecuteApiEndpoint :: Lens' ImportApiResponse (Maybe Bool)
importApiResponse_disableExecuteApiEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Bool
disableExecuteApiEndpoint :: Maybe Bool
$sel:disableExecuteApiEndpoint:ImportApiResponse' :: ImportApiResponse -> Maybe Bool
disableExecuteApiEndpoint} -> Maybe Bool
disableExecuteApiEndpoint) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Bool
a -> ImportApiResponse
s {$sel:disableExecuteApiEndpoint:ImportApiResponse' :: Maybe Bool
disableExecuteApiEndpoint = Maybe Bool
a} :: ImportApiResponse)

-- | Avoid validating models when creating a deployment. Supported only for
-- WebSocket APIs.
importApiResponse_disableSchemaValidation :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Bool)
importApiResponse_disableSchemaValidation :: Lens' ImportApiResponse (Maybe Bool)
importApiResponse_disableSchemaValidation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Bool
disableSchemaValidation :: Maybe Bool
$sel:disableSchemaValidation:ImportApiResponse' :: ImportApiResponse -> Maybe Bool
disableSchemaValidation} -> Maybe Bool
disableSchemaValidation) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Bool
a -> ImportApiResponse
s {$sel:disableSchemaValidation:ImportApiResponse' :: Maybe Bool
disableSchemaValidation = Maybe Bool
a} :: ImportApiResponse)

-- | The validation information during API import. This may include
-- particular properties of your OpenAPI definition which are ignored
-- during import. Supported only for HTTP APIs.
importApiResponse_importInfo :: Lens.Lens' ImportApiResponse (Prelude.Maybe [Prelude.Text])
importApiResponse_importInfo :: Lens' ImportApiResponse (Maybe [Text])
importApiResponse_importInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe [Text]
importInfo :: Maybe [Text]
$sel:importInfo:ImportApiResponse' :: ImportApiResponse -> Maybe [Text]
importInfo} -> Maybe [Text]
importInfo) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe [Text]
a -> ImportApiResponse
s {$sel:importInfo:ImportApiResponse' :: Maybe [Text]
importInfo = Maybe [Text]
a} :: ImportApiResponse) 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 name of the API.
importApiResponse_name :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Text)
importApiResponse_name :: Lens' ImportApiResponse (Maybe Text)
importApiResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Text
name :: Maybe Text
$sel:name:ImportApiResponse' :: ImportApiResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Text
a -> ImportApiResponse
s {$sel:name:ImportApiResponse' :: Maybe Text
name = Maybe Text
a} :: ImportApiResponse)

-- | The API protocol.
importApiResponse_protocolType :: Lens.Lens' ImportApiResponse (Prelude.Maybe ProtocolType)
importApiResponse_protocolType :: Lens' ImportApiResponse (Maybe ProtocolType)
importApiResponse_protocolType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe ProtocolType
protocolType :: Maybe ProtocolType
$sel:protocolType:ImportApiResponse' :: ImportApiResponse -> Maybe ProtocolType
protocolType} -> Maybe ProtocolType
protocolType) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe ProtocolType
a -> ImportApiResponse
s {$sel:protocolType:ImportApiResponse' :: Maybe ProtocolType
protocolType = Maybe ProtocolType
a} :: ImportApiResponse)

-- | The route selection expression for the API. For HTTP APIs, the
-- routeSelectionExpression must be ${request.method} ${request.path}. If
-- not provided, this will be the default for HTTP APIs. This property is
-- required for WebSocket APIs.
importApiResponse_routeSelectionExpression :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Text)
importApiResponse_routeSelectionExpression :: Lens' ImportApiResponse (Maybe Text)
importApiResponse_routeSelectionExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Text
routeSelectionExpression :: Maybe Text
$sel:routeSelectionExpression:ImportApiResponse' :: ImportApiResponse -> Maybe Text
routeSelectionExpression} -> Maybe Text
routeSelectionExpression) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Text
a -> ImportApiResponse
s {$sel:routeSelectionExpression:ImportApiResponse' :: Maybe Text
routeSelectionExpression = Maybe Text
a} :: ImportApiResponse)

-- | A collection of tags associated with the API.
importApiResponse_tags :: Lens.Lens' ImportApiResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
importApiResponse_tags :: Lens' ImportApiResponse (Maybe (HashMap Text Text))
importApiResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:ImportApiResponse' :: ImportApiResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe (HashMap Text Text)
a -> ImportApiResponse
s {$sel:tags:ImportApiResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: ImportApiResponse) 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

-- | A version identifier for the API.
importApiResponse_version :: Lens.Lens' ImportApiResponse (Prelude.Maybe Prelude.Text)
importApiResponse_version :: Lens' ImportApiResponse (Maybe Text)
importApiResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe Text
version :: Maybe Text
$sel:version:ImportApiResponse' :: ImportApiResponse -> Maybe Text
version} -> Maybe Text
version) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe Text
a -> ImportApiResponse
s {$sel:version:ImportApiResponse' :: Maybe Text
version = Maybe Text
a} :: ImportApiResponse)

-- | The warning messages reported when failonwarnings is turned on during
-- API import.
importApiResponse_warnings :: Lens.Lens' ImportApiResponse (Prelude.Maybe [Prelude.Text])
importApiResponse_warnings :: Lens' ImportApiResponse (Maybe [Text])
importApiResponse_warnings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportApiResponse' {Maybe [Text]
warnings :: Maybe [Text]
$sel:warnings:ImportApiResponse' :: ImportApiResponse -> Maybe [Text]
warnings} -> Maybe [Text]
warnings) (\s :: ImportApiResponse
s@ImportApiResponse' {} Maybe [Text]
a -> ImportApiResponse
s {$sel:warnings:ImportApiResponse' :: Maybe [Text]
warnings = Maybe [Text]
a} :: ImportApiResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData ImportApiResponse where
  rnf :: ImportApiResponse -> ()
rnf ImportApiResponse' {Int
Maybe Bool
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
Maybe Cors
Maybe ProtocolType
httpStatus :: Int
warnings :: Maybe [Text]
version :: Maybe Text
tags :: Maybe (HashMap Text Text)
routeSelectionExpression :: Maybe Text
protocolType :: Maybe ProtocolType
name :: Maybe Text
importInfo :: Maybe [Text]
disableSchemaValidation :: Maybe Bool
disableExecuteApiEndpoint :: Maybe Bool
description :: Maybe Text
createdDate :: Maybe ISO8601
corsConfiguration :: Maybe Cors
apiKeySelectionExpression :: Maybe Text
apiId :: Maybe Text
apiGatewayManaged :: Maybe Bool
apiEndpoint :: Maybe Text
$sel:httpStatus:ImportApiResponse' :: ImportApiResponse -> Int
$sel:warnings:ImportApiResponse' :: ImportApiResponse -> Maybe [Text]
$sel:version:ImportApiResponse' :: ImportApiResponse -> Maybe Text
$sel:tags:ImportApiResponse' :: ImportApiResponse -> Maybe (HashMap Text Text)
$sel:routeSelectionExpression:ImportApiResponse' :: ImportApiResponse -> Maybe Text
$sel:protocolType:ImportApiResponse' :: ImportApiResponse -> Maybe ProtocolType
$sel:name:ImportApiResponse' :: ImportApiResponse -> Maybe Text
$sel:importInfo:ImportApiResponse' :: ImportApiResponse -> Maybe [Text]
$sel:disableSchemaValidation:ImportApiResponse' :: ImportApiResponse -> Maybe Bool
$sel:disableExecuteApiEndpoint:ImportApiResponse' :: ImportApiResponse -> Maybe Bool
$sel:description:ImportApiResponse' :: ImportApiResponse -> Maybe Text
$sel:createdDate:ImportApiResponse' :: ImportApiResponse -> Maybe ISO8601
$sel:corsConfiguration:ImportApiResponse' :: ImportApiResponse -> Maybe Cors
$sel:apiKeySelectionExpression:ImportApiResponse' :: ImportApiResponse -> Maybe Text
$sel:apiId:ImportApiResponse' :: ImportApiResponse -> Maybe Text
$sel:apiGatewayManaged:ImportApiResponse' :: ImportApiResponse -> Maybe Bool
$sel:apiEndpoint:ImportApiResponse' :: ImportApiResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
apiEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
apiGatewayManaged
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
apiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
apiKeySelectionExpression
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Cors
corsConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
createdDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
disableExecuteApiEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
disableSchemaValidation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
importInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProtocolType
protocolType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
routeSelectionExpression
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
warnings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus