{-# 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.AppSync.CreateGraphqlApi
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a @GraphqlApi@ object.
module Amazonka.AppSync.CreateGraphqlApi
  ( -- * Creating a Request
    CreateGraphqlApi (..),
    newCreateGraphqlApi,

    -- * Request Lenses
    createGraphqlApi_additionalAuthenticationProviders,
    createGraphqlApi_lambdaAuthorizerConfig,
    createGraphqlApi_logConfig,
    createGraphqlApi_openIDConnectConfig,
    createGraphqlApi_tags,
    createGraphqlApi_userPoolConfig,
    createGraphqlApi_xrayEnabled,
    createGraphqlApi_name,
    createGraphqlApi_authenticationType,

    -- * Destructuring the Response
    CreateGraphqlApiResponse (..),
    newCreateGraphqlApiResponse,

    -- * Response Lenses
    createGraphqlApiResponse_graphqlApi,
    createGraphqlApiResponse_httpStatus,
  )
where

import Amazonka.AppSync.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:/ 'newCreateGraphqlApi' smart constructor.
data CreateGraphqlApi = CreateGraphqlApi'
  { -- | A list of additional authentication providers for the @GraphqlApi@ API.
    CreateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders :: Prelude.Maybe [AdditionalAuthenticationProvider],
    -- | Configuration for Lambda function authorization.
    CreateGraphqlApi -> Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig :: Prelude.Maybe LambdaAuthorizerConfig,
    -- | The Amazon CloudWatch Logs configuration.
    CreateGraphqlApi -> Maybe LogConfig
logConfig :: Prelude.Maybe LogConfig,
    -- | The OIDC configuration.
    CreateGraphqlApi -> Maybe OpenIDConnectConfig
openIDConnectConfig :: Prelude.Maybe OpenIDConnectConfig,
    -- | A @TagMap@ object.
    CreateGraphqlApi -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Amazon Cognito user pool configuration.
    CreateGraphqlApi -> Maybe UserPoolConfig
userPoolConfig :: Prelude.Maybe UserPoolConfig,
    -- | A flag indicating whether to use X-Ray tracing for the @GraphqlApi@.
    CreateGraphqlApi -> Maybe Bool
xrayEnabled :: Prelude.Maybe Prelude.Bool,
    -- | A user-supplied name for the @GraphqlApi@.
    CreateGraphqlApi -> Text
name :: Prelude.Text,
    -- | The authentication type: API key, Identity and Access Management (IAM),
    -- OpenID Connect (OIDC), Amazon Cognito user pools, or Lambda.
    CreateGraphqlApi -> AuthenticationType
authenticationType :: AuthenticationType
  }
  deriving (CreateGraphqlApi -> CreateGraphqlApi -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateGraphqlApi -> CreateGraphqlApi -> Bool
$c/= :: CreateGraphqlApi -> CreateGraphqlApi -> Bool
== :: CreateGraphqlApi -> CreateGraphqlApi -> Bool
$c== :: CreateGraphqlApi -> CreateGraphqlApi -> Bool
Prelude.Eq, ReadPrec [CreateGraphqlApi]
ReadPrec CreateGraphqlApi
Int -> ReadS CreateGraphqlApi
ReadS [CreateGraphqlApi]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateGraphqlApi]
$creadListPrec :: ReadPrec [CreateGraphqlApi]
readPrec :: ReadPrec CreateGraphqlApi
$creadPrec :: ReadPrec CreateGraphqlApi
readList :: ReadS [CreateGraphqlApi]
$creadList :: ReadS [CreateGraphqlApi]
readsPrec :: Int -> ReadS CreateGraphqlApi
$creadsPrec :: Int -> ReadS CreateGraphqlApi
Prelude.Read, Int -> CreateGraphqlApi -> ShowS
[CreateGraphqlApi] -> ShowS
CreateGraphqlApi -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateGraphqlApi] -> ShowS
$cshowList :: [CreateGraphqlApi] -> ShowS
show :: CreateGraphqlApi -> String
$cshow :: CreateGraphqlApi -> String
showsPrec :: Int -> CreateGraphqlApi -> ShowS
$cshowsPrec :: Int -> CreateGraphqlApi -> ShowS
Prelude.Show, forall x. Rep CreateGraphqlApi x -> CreateGraphqlApi
forall x. CreateGraphqlApi -> Rep CreateGraphqlApi x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateGraphqlApi x -> CreateGraphqlApi
$cfrom :: forall x. CreateGraphqlApi -> Rep CreateGraphqlApi x
Prelude.Generic)

-- |
-- Create a value of 'CreateGraphqlApi' 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:
--
-- 'additionalAuthenticationProviders', 'createGraphqlApi_additionalAuthenticationProviders' - A list of additional authentication providers for the @GraphqlApi@ API.
--
-- 'lambdaAuthorizerConfig', 'createGraphqlApi_lambdaAuthorizerConfig' - Configuration for Lambda function authorization.
--
-- 'logConfig', 'createGraphqlApi_logConfig' - The Amazon CloudWatch Logs configuration.
--
-- 'openIDConnectConfig', 'createGraphqlApi_openIDConnectConfig' - The OIDC configuration.
--
-- 'tags', 'createGraphqlApi_tags' - A @TagMap@ object.
--
-- 'userPoolConfig', 'createGraphqlApi_userPoolConfig' - The Amazon Cognito user pool configuration.
--
-- 'xrayEnabled', 'createGraphqlApi_xrayEnabled' - A flag indicating whether to use X-Ray tracing for the @GraphqlApi@.
--
-- 'name', 'createGraphqlApi_name' - A user-supplied name for the @GraphqlApi@.
--
-- 'authenticationType', 'createGraphqlApi_authenticationType' - The authentication type: API key, Identity and Access Management (IAM),
-- OpenID Connect (OIDC), Amazon Cognito user pools, or Lambda.
newCreateGraphqlApi ::
  -- | 'name'
  Prelude.Text ->
  -- | 'authenticationType'
  AuthenticationType ->
  CreateGraphqlApi
newCreateGraphqlApi :: Text -> AuthenticationType -> CreateGraphqlApi
newCreateGraphqlApi Text
pName_ AuthenticationType
pAuthenticationType_ =
  CreateGraphqlApi'
    { $sel:additionalAuthenticationProviders:CreateGraphqlApi' :: Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders =
        forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaAuthorizerConfig:CreateGraphqlApi' :: Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:logConfig:CreateGraphqlApi' :: Maybe LogConfig
logConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:openIDConnectConfig:CreateGraphqlApi' :: Maybe OpenIDConnectConfig
openIDConnectConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateGraphqlApi' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:userPoolConfig:CreateGraphqlApi' :: Maybe UserPoolConfig
userPoolConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:xrayEnabled:CreateGraphqlApi' :: Maybe Bool
xrayEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateGraphqlApi' :: Text
name = Text
pName_,
      $sel:authenticationType:CreateGraphqlApi' :: AuthenticationType
authenticationType = AuthenticationType
pAuthenticationType_
    }

-- | A list of additional authentication providers for the @GraphqlApi@ API.
createGraphqlApi_additionalAuthenticationProviders :: Lens.Lens' CreateGraphqlApi (Prelude.Maybe [AdditionalAuthenticationProvider])
createGraphqlApi_additionalAuthenticationProviders :: Lens' CreateGraphqlApi (Maybe [AdditionalAuthenticationProvider])
createGraphqlApi_additionalAuthenticationProviders = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApi' {Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:additionalAuthenticationProviders:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders} -> Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders) (\s :: CreateGraphqlApi
s@CreateGraphqlApi' {} Maybe [AdditionalAuthenticationProvider]
a -> CreateGraphqlApi
s {$sel:additionalAuthenticationProviders:CreateGraphqlApi' :: Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders = Maybe [AdditionalAuthenticationProvider]
a} :: CreateGraphqlApi) 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

-- | Configuration for Lambda function authorization.
createGraphqlApi_lambdaAuthorizerConfig :: Lens.Lens' CreateGraphqlApi (Prelude.Maybe LambdaAuthorizerConfig)
createGraphqlApi_lambdaAuthorizerConfig :: Lens' CreateGraphqlApi (Maybe LambdaAuthorizerConfig)
createGraphqlApi_lambdaAuthorizerConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApi' {Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
$sel:lambdaAuthorizerConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig} -> Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig) (\s :: CreateGraphqlApi
s@CreateGraphqlApi' {} Maybe LambdaAuthorizerConfig
a -> CreateGraphqlApi
s {$sel:lambdaAuthorizerConfig:CreateGraphqlApi' :: Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig = Maybe LambdaAuthorizerConfig
a} :: CreateGraphqlApi)

-- | The Amazon CloudWatch Logs configuration.
createGraphqlApi_logConfig :: Lens.Lens' CreateGraphqlApi (Prelude.Maybe LogConfig)
createGraphqlApi_logConfig :: Lens' CreateGraphqlApi (Maybe LogConfig)
createGraphqlApi_logConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApi' {Maybe LogConfig
logConfig :: Maybe LogConfig
$sel:logConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe LogConfig
logConfig} -> Maybe LogConfig
logConfig) (\s :: CreateGraphqlApi
s@CreateGraphqlApi' {} Maybe LogConfig
a -> CreateGraphqlApi
s {$sel:logConfig:CreateGraphqlApi' :: Maybe LogConfig
logConfig = Maybe LogConfig
a} :: CreateGraphqlApi)

-- | The OIDC configuration.
createGraphqlApi_openIDConnectConfig :: Lens.Lens' CreateGraphqlApi (Prelude.Maybe OpenIDConnectConfig)
createGraphqlApi_openIDConnectConfig :: Lens' CreateGraphqlApi (Maybe OpenIDConnectConfig)
createGraphqlApi_openIDConnectConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApi' {Maybe OpenIDConnectConfig
openIDConnectConfig :: Maybe OpenIDConnectConfig
$sel:openIDConnectConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe OpenIDConnectConfig
openIDConnectConfig} -> Maybe OpenIDConnectConfig
openIDConnectConfig) (\s :: CreateGraphqlApi
s@CreateGraphqlApi' {} Maybe OpenIDConnectConfig
a -> CreateGraphqlApi
s {$sel:openIDConnectConfig:CreateGraphqlApi' :: Maybe OpenIDConnectConfig
openIDConnectConfig = Maybe OpenIDConnectConfig
a} :: CreateGraphqlApi)

-- | A @TagMap@ object.
createGraphqlApi_tags :: Lens.Lens' CreateGraphqlApi (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createGraphqlApi_tags :: Lens' CreateGraphqlApi (Maybe (HashMap Text Text))
createGraphqlApi_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApi' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateGraphqlApi
s@CreateGraphqlApi' {} Maybe (HashMap Text Text)
a -> CreateGraphqlApi
s {$sel:tags:CreateGraphqlApi' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateGraphqlApi) 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 Amazon Cognito user pool configuration.
createGraphqlApi_userPoolConfig :: Lens.Lens' CreateGraphqlApi (Prelude.Maybe UserPoolConfig)
createGraphqlApi_userPoolConfig :: Lens' CreateGraphqlApi (Maybe UserPoolConfig)
createGraphqlApi_userPoolConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApi' {Maybe UserPoolConfig
userPoolConfig :: Maybe UserPoolConfig
$sel:userPoolConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe UserPoolConfig
userPoolConfig} -> Maybe UserPoolConfig
userPoolConfig) (\s :: CreateGraphqlApi
s@CreateGraphqlApi' {} Maybe UserPoolConfig
a -> CreateGraphqlApi
s {$sel:userPoolConfig:CreateGraphqlApi' :: Maybe UserPoolConfig
userPoolConfig = Maybe UserPoolConfig
a} :: CreateGraphqlApi)

-- | A flag indicating whether to use X-Ray tracing for the @GraphqlApi@.
createGraphqlApi_xrayEnabled :: Lens.Lens' CreateGraphqlApi (Prelude.Maybe Prelude.Bool)
createGraphqlApi_xrayEnabled :: Lens' CreateGraphqlApi (Maybe Bool)
createGraphqlApi_xrayEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApi' {Maybe Bool
xrayEnabled :: Maybe Bool
$sel:xrayEnabled:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe Bool
xrayEnabled} -> Maybe Bool
xrayEnabled) (\s :: CreateGraphqlApi
s@CreateGraphqlApi' {} Maybe Bool
a -> CreateGraphqlApi
s {$sel:xrayEnabled:CreateGraphqlApi' :: Maybe Bool
xrayEnabled = Maybe Bool
a} :: CreateGraphqlApi)

-- | A user-supplied name for the @GraphqlApi@.
createGraphqlApi_name :: Lens.Lens' CreateGraphqlApi Prelude.Text
createGraphqlApi_name :: Lens' CreateGraphqlApi Text
createGraphqlApi_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApi' {Text
name :: Text
$sel:name:CreateGraphqlApi' :: CreateGraphqlApi -> Text
name} -> Text
name) (\s :: CreateGraphqlApi
s@CreateGraphqlApi' {} Text
a -> CreateGraphqlApi
s {$sel:name:CreateGraphqlApi' :: Text
name = Text
a} :: CreateGraphqlApi)

-- | The authentication type: API key, Identity and Access Management (IAM),
-- OpenID Connect (OIDC), Amazon Cognito user pools, or Lambda.
createGraphqlApi_authenticationType :: Lens.Lens' CreateGraphqlApi AuthenticationType
createGraphqlApi_authenticationType :: Lens' CreateGraphqlApi AuthenticationType
createGraphqlApi_authenticationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApi' {AuthenticationType
authenticationType :: AuthenticationType
$sel:authenticationType:CreateGraphqlApi' :: CreateGraphqlApi -> AuthenticationType
authenticationType} -> AuthenticationType
authenticationType) (\s :: CreateGraphqlApi
s@CreateGraphqlApi' {} AuthenticationType
a -> CreateGraphqlApi
s {$sel:authenticationType:CreateGraphqlApi' :: AuthenticationType
authenticationType = AuthenticationType
a} :: CreateGraphqlApi)

instance Core.AWSRequest CreateGraphqlApi where
  type
    AWSResponse CreateGraphqlApi =
      CreateGraphqlApiResponse
  request :: (Service -> Service)
-> CreateGraphqlApi -> Request CreateGraphqlApi
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 CreateGraphqlApi
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateGraphqlApi)))
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 GraphqlApi -> Int -> CreateGraphqlApiResponse
CreateGraphqlApiResponse'
            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
"graphqlApi")
            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 CreateGraphqlApi where
  hashWithSalt :: Int -> CreateGraphqlApi -> Int
hashWithSalt Int
_salt CreateGraphqlApi' {Maybe Bool
Maybe [AdditionalAuthenticationProvider]
Maybe (HashMap Text Text)
Maybe LambdaAuthorizerConfig
Maybe LogConfig
Maybe OpenIDConnectConfig
Maybe UserPoolConfig
Text
AuthenticationType
authenticationType :: AuthenticationType
name :: Text
xrayEnabled :: Maybe Bool
userPoolConfig :: Maybe UserPoolConfig
tags :: Maybe (HashMap Text Text)
openIDConnectConfig :: Maybe OpenIDConnectConfig
logConfig :: Maybe LogConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:authenticationType:CreateGraphqlApi' :: CreateGraphqlApi -> AuthenticationType
$sel:name:CreateGraphqlApi' :: CreateGraphqlApi -> Text
$sel:xrayEnabled:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe Bool
$sel:userPoolConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe UserPoolConfig
$sel:tags:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe (HashMap Text Text)
$sel:openIDConnectConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe OpenIDConnectConfig
$sel:logConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe LogConfig
$sel:lambdaAuthorizerConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe LambdaAuthorizerConfig
$sel:additionalAuthenticationProviders:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogConfig
logConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OpenIDConnectConfig
openIDConnectConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserPoolConfig
userPoolConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
xrayEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AuthenticationType
authenticationType

instance Prelude.NFData CreateGraphqlApi where
  rnf :: CreateGraphqlApi -> ()
rnf CreateGraphqlApi' {Maybe Bool
Maybe [AdditionalAuthenticationProvider]
Maybe (HashMap Text Text)
Maybe LambdaAuthorizerConfig
Maybe LogConfig
Maybe OpenIDConnectConfig
Maybe UserPoolConfig
Text
AuthenticationType
authenticationType :: AuthenticationType
name :: Text
xrayEnabled :: Maybe Bool
userPoolConfig :: Maybe UserPoolConfig
tags :: Maybe (HashMap Text Text)
openIDConnectConfig :: Maybe OpenIDConnectConfig
logConfig :: Maybe LogConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:authenticationType:CreateGraphqlApi' :: CreateGraphqlApi -> AuthenticationType
$sel:name:CreateGraphqlApi' :: CreateGraphqlApi -> Text
$sel:xrayEnabled:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe Bool
$sel:userPoolConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe UserPoolConfig
$sel:tags:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe (HashMap Text Text)
$sel:openIDConnectConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe OpenIDConnectConfig
$sel:logConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe LogConfig
$sel:lambdaAuthorizerConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe LambdaAuthorizerConfig
$sel:additionalAuthenticationProviders:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogConfig
logConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OpenIDConnectConfig
openIDConnectConfig
      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 UserPoolConfig
userPoolConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
xrayEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AuthenticationType
authenticationType

instance Data.ToHeaders CreateGraphqlApi where
  toHeaders :: CreateGraphqlApi -> 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 CreateGraphqlApi where
  toJSON :: CreateGraphqlApi -> Value
toJSON CreateGraphqlApi' {Maybe Bool
Maybe [AdditionalAuthenticationProvider]
Maybe (HashMap Text Text)
Maybe LambdaAuthorizerConfig
Maybe LogConfig
Maybe OpenIDConnectConfig
Maybe UserPoolConfig
Text
AuthenticationType
authenticationType :: AuthenticationType
name :: Text
xrayEnabled :: Maybe Bool
userPoolConfig :: Maybe UserPoolConfig
tags :: Maybe (HashMap Text Text)
openIDConnectConfig :: Maybe OpenIDConnectConfig
logConfig :: Maybe LogConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:authenticationType:CreateGraphqlApi' :: CreateGraphqlApi -> AuthenticationType
$sel:name:CreateGraphqlApi' :: CreateGraphqlApi -> Text
$sel:xrayEnabled:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe Bool
$sel:userPoolConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe UserPoolConfig
$sel:tags:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe (HashMap Text Text)
$sel:openIDConnectConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe OpenIDConnectConfig
$sel:logConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe LogConfig
$sel:lambdaAuthorizerConfig:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe LambdaAuthorizerConfig
$sel:additionalAuthenticationProviders:CreateGraphqlApi' :: CreateGraphqlApi -> Maybe [AdditionalAuthenticationProvider]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"additionalAuthenticationProviders" 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 [AdditionalAuthenticationProvider]
additionalAuthenticationProviders,
            (Key
"lambdaAuthorizerConfig" 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 LambdaAuthorizerConfig
lambdaAuthorizerConfig,
            (Key
"logConfig" 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 LogConfig
logConfig,
            (Key
"openIDConnectConfig" 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 OpenIDConnectConfig
openIDConnectConfig,
            (Key
"tags" 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 (HashMap Text Text)
tags,
            (Key
"userPoolConfig" 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 UserPoolConfig
userPoolConfig,
            (Key
"xrayEnabled" 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 Bool
xrayEnabled,
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"authenticationType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AuthenticationType
authenticationType)
          ]
      )

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

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

-- | /See:/ 'newCreateGraphqlApiResponse' smart constructor.
data CreateGraphqlApiResponse = CreateGraphqlApiResponse'
  { -- | The @GraphqlApi@.
    CreateGraphqlApiResponse -> Maybe GraphqlApi
graphqlApi :: Prelude.Maybe GraphqlApi,
    -- | The response's http status code.
    CreateGraphqlApiResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateGraphqlApiResponse -> CreateGraphqlApiResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateGraphqlApiResponse -> CreateGraphqlApiResponse -> Bool
$c/= :: CreateGraphqlApiResponse -> CreateGraphqlApiResponse -> Bool
== :: CreateGraphqlApiResponse -> CreateGraphqlApiResponse -> Bool
$c== :: CreateGraphqlApiResponse -> CreateGraphqlApiResponse -> Bool
Prelude.Eq, ReadPrec [CreateGraphqlApiResponse]
ReadPrec CreateGraphqlApiResponse
Int -> ReadS CreateGraphqlApiResponse
ReadS [CreateGraphqlApiResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateGraphqlApiResponse]
$creadListPrec :: ReadPrec [CreateGraphqlApiResponse]
readPrec :: ReadPrec CreateGraphqlApiResponse
$creadPrec :: ReadPrec CreateGraphqlApiResponse
readList :: ReadS [CreateGraphqlApiResponse]
$creadList :: ReadS [CreateGraphqlApiResponse]
readsPrec :: Int -> ReadS CreateGraphqlApiResponse
$creadsPrec :: Int -> ReadS CreateGraphqlApiResponse
Prelude.Read, Int -> CreateGraphqlApiResponse -> ShowS
[CreateGraphqlApiResponse] -> ShowS
CreateGraphqlApiResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateGraphqlApiResponse] -> ShowS
$cshowList :: [CreateGraphqlApiResponse] -> ShowS
show :: CreateGraphqlApiResponse -> String
$cshow :: CreateGraphqlApiResponse -> String
showsPrec :: Int -> CreateGraphqlApiResponse -> ShowS
$cshowsPrec :: Int -> CreateGraphqlApiResponse -> ShowS
Prelude.Show, forall x.
Rep CreateGraphqlApiResponse x -> CreateGraphqlApiResponse
forall x.
CreateGraphqlApiResponse -> Rep CreateGraphqlApiResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateGraphqlApiResponse x -> CreateGraphqlApiResponse
$cfrom :: forall x.
CreateGraphqlApiResponse -> Rep CreateGraphqlApiResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateGraphqlApiResponse' 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:
--
-- 'graphqlApi', 'createGraphqlApiResponse_graphqlApi' - The @GraphqlApi@.
--
-- 'httpStatus', 'createGraphqlApiResponse_httpStatus' - The response's http status code.
newCreateGraphqlApiResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateGraphqlApiResponse
newCreateGraphqlApiResponse :: Int -> CreateGraphqlApiResponse
newCreateGraphqlApiResponse Int
pHttpStatus_ =
  CreateGraphqlApiResponse'
    { $sel:graphqlApi:CreateGraphqlApiResponse' :: Maybe GraphqlApi
graphqlApi =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateGraphqlApiResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @GraphqlApi@.
createGraphqlApiResponse_graphqlApi :: Lens.Lens' CreateGraphqlApiResponse (Prelude.Maybe GraphqlApi)
createGraphqlApiResponse_graphqlApi :: Lens' CreateGraphqlApiResponse (Maybe GraphqlApi)
createGraphqlApiResponse_graphqlApi = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGraphqlApiResponse' {Maybe GraphqlApi
graphqlApi :: Maybe GraphqlApi
$sel:graphqlApi:CreateGraphqlApiResponse' :: CreateGraphqlApiResponse -> Maybe GraphqlApi
graphqlApi} -> Maybe GraphqlApi
graphqlApi) (\s :: CreateGraphqlApiResponse
s@CreateGraphqlApiResponse' {} Maybe GraphqlApi
a -> CreateGraphqlApiResponse
s {$sel:graphqlApi:CreateGraphqlApiResponse' :: Maybe GraphqlApi
graphqlApi = Maybe GraphqlApi
a} :: CreateGraphqlApiResponse)

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

instance Prelude.NFData CreateGraphqlApiResponse where
  rnf :: CreateGraphqlApiResponse -> ()
rnf CreateGraphqlApiResponse' {Int
Maybe GraphqlApi
httpStatus :: Int
graphqlApi :: Maybe GraphqlApi
$sel:httpStatus:CreateGraphqlApiResponse' :: CreateGraphqlApiResponse -> Int
$sel:graphqlApi:CreateGraphqlApiResponse' :: CreateGraphqlApiResponse -> Maybe GraphqlApi
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe GraphqlApi
graphqlApi
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus