{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.GraphqlApi
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.AppSync.Types.GraphqlApi where

import Amazonka.AppSync.Types.AdditionalAuthenticationProvider
import Amazonka.AppSync.Types.AuthenticationType
import Amazonka.AppSync.Types.LambdaAuthorizerConfig
import Amazonka.AppSync.Types.LogConfig
import Amazonka.AppSync.Types.OpenIDConnectConfig
import Amazonka.AppSync.Types.UserPoolConfig
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

-- | Describes a GraphQL API.
--
-- /See:/ 'newGraphqlApi' smart constructor.
data GraphqlApi = GraphqlApi'
  { -- | A list of additional authentication providers for the @GraphqlApi@ API.
    GraphqlApi -> Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders :: Prelude.Maybe [AdditionalAuthenticationProvider],
    -- | The API ID.
    GraphqlApi -> Maybe Text
apiId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN).
    GraphqlApi -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The authentication type.
    GraphqlApi -> Maybe AuthenticationType
authenticationType :: Prelude.Maybe AuthenticationType,
    -- | Configuration for Lambda function authorization.
    GraphqlApi -> Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig :: Prelude.Maybe LambdaAuthorizerConfig,
    -- | The Amazon CloudWatch Logs configuration.
    GraphqlApi -> Maybe LogConfig
logConfig :: Prelude.Maybe LogConfig,
    -- | The API name.
    GraphqlApi -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The OpenID Connect configuration.
    GraphqlApi -> Maybe OpenIDConnectConfig
openIDConnectConfig :: Prelude.Maybe OpenIDConnectConfig,
    -- | The tags.
    GraphqlApi -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The URIs.
    GraphqlApi -> Maybe (HashMap Text Text)
uris :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Amazon Cognito user pool configuration.
    GraphqlApi -> Maybe UserPoolConfig
userPoolConfig :: Prelude.Maybe UserPoolConfig,
    -- | The ARN of the WAF access control list (ACL) associated with this
    -- @GraphqlApi@, if one exists.
    GraphqlApi -> Maybe Text
wafWebAclArn :: Prelude.Maybe Prelude.Text,
    -- | A flag indicating whether to use X-Ray tracing for this @GraphqlApi@.
    GraphqlApi -> Maybe Bool
xrayEnabled :: Prelude.Maybe Prelude.Bool
  }
  deriving (GraphqlApi -> GraphqlApi -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GraphqlApi -> GraphqlApi -> Bool
$c/= :: GraphqlApi -> GraphqlApi -> Bool
== :: GraphqlApi -> GraphqlApi -> Bool
$c== :: GraphqlApi -> GraphqlApi -> Bool
Prelude.Eq, ReadPrec [GraphqlApi]
ReadPrec GraphqlApi
Int -> ReadS GraphqlApi
ReadS [GraphqlApi]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GraphqlApi]
$creadListPrec :: ReadPrec [GraphqlApi]
readPrec :: ReadPrec GraphqlApi
$creadPrec :: ReadPrec GraphqlApi
readList :: ReadS [GraphqlApi]
$creadList :: ReadS [GraphqlApi]
readsPrec :: Int -> ReadS GraphqlApi
$creadsPrec :: Int -> ReadS GraphqlApi
Prelude.Read, Int -> GraphqlApi -> ShowS
[GraphqlApi] -> ShowS
GraphqlApi -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GraphqlApi] -> ShowS
$cshowList :: [GraphqlApi] -> ShowS
show :: GraphqlApi -> String
$cshow :: GraphqlApi -> String
showsPrec :: Int -> GraphqlApi -> ShowS
$cshowsPrec :: Int -> GraphqlApi -> ShowS
Prelude.Show, forall x. Rep GraphqlApi x -> GraphqlApi
forall x. GraphqlApi -> Rep GraphqlApi x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GraphqlApi x -> GraphqlApi
$cfrom :: forall x. GraphqlApi -> Rep GraphqlApi x
Prelude.Generic)

-- |
-- Create a value of 'GraphqlApi' 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', 'graphqlApi_additionalAuthenticationProviders' - A list of additional authentication providers for the @GraphqlApi@ API.
--
-- 'apiId', 'graphqlApi_apiId' - The API ID.
--
-- 'arn', 'graphqlApi_arn' - The Amazon Resource Name (ARN).
--
-- 'authenticationType', 'graphqlApi_authenticationType' - The authentication type.
--
-- 'lambdaAuthorizerConfig', 'graphqlApi_lambdaAuthorizerConfig' - Configuration for Lambda function authorization.
--
-- 'logConfig', 'graphqlApi_logConfig' - The Amazon CloudWatch Logs configuration.
--
-- 'name', 'graphqlApi_name' - The API name.
--
-- 'openIDConnectConfig', 'graphqlApi_openIDConnectConfig' - The OpenID Connect configuration.
--
-- 'tags', 'graphqlApi_tags' - The tags.
--
-- 'uris', 'graphqlApi_uris' - The URIs.
--
-- 'userPoolConfig', 'graphqlApi_userPoolConfig' - The Amazon Cognito user pool configuration.
--
-- 'wafWebAclArn', 'graphqlApi_wafWebAclArn' - The ARN of the WAF access control list (ACL) associated with this
-- @GraphqlApi@, if one exists.
--
-- 'xrayEnabled', 'graphqlApi_xrayEnabled' - A flag indicating whether to use X-Ray tracing for this @GraphqlApi@.
newGraphqlApi ::
  GraphqlApi
newGraphqlApi :: GraphqlApi
newGraphqlApi =
  GraphqlApi'
    { $sel:additionalAuthenticationProviders:GraphqlApi' :: Maybe [AdditionalAuthenticationProvider]
additionalAuthenticationProviders =
        forall a. Maybe a
Prelude.Nothing,
      $sel:apiId:GraphqlApi' :: Maybe Text
apiId = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:GraphqlApi' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:authenticationType:GraphqlApi' :: Maybe AuthenticationType
authenticationType = forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaAuthorizerConfig:GraphqlApi' :: Maybe LambdaAuthorizerConfig
lambdaAuthorizerConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:logConfig:GraphqlApi' :: Maybe LogConfig
logConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GraphqlApi' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:openIDConnectConfig:GraphqlApi' :: Maybe OpenIDConnectConfig
openIDConnectConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GraphqlApi' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:uris:GraphqlApi' :: Maybe (HashMap Text Text)
uris = forall a. Maybe a
Prelude.Nothing,
      $sel:userPoolConfig:GraphqlApi' :: Maybe UserPoolConfig
userPoolConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:wafWebAclArn:GraphqlApi' :: Maybe Text
wafWebAclArn = forall a. Maybe a
Prelude.Nothing,
      $sel:xrayEnabled:GraphqlApi' :: Maybe Bool
xrayEnabled = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The Amazon Resource Name (ARN).
graphqlApi_arn :: Lens.Lens' GraphqlApi (Prelude.Maybe Prelude.Text)
graphqlApi_arn :: Lens' GraphqlApi (Maybe Text)
graphqlApi_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GraphqlApi' {Maybe Text
arn :: Maybe Text
$sel:arn:GraphqlApi' :: GraphqlApi -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GraphqlApi
s@GraphqlApi' {} Maybe Text
a -> GraphqlApi
s {$sel:arn:GraphqlApi' :: Maybe Text
arn = Maybe Text
a} :: GraphqlApi)

-- | The authentication type.
graphqlApi_authenticationType :: Lens.Lens' GraphqlApi (Prelude.Maybe AuthenticationType)
graphqlApi_authenticationType :: Lens' GraphqlApi (Maybe AuthenticationType)
graphqlApi_authenticationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GraphqlApi' {Maybe AuthenticationType
authenticationType :: Maybe AuthenticationType
$sel:authenticationType:GraphqlApi' :: GraphqlApi -> Maybe AuthenticationType
authenticationType} -> Maybe AuthenticationType
authenticationType) (\s :: GraphqlApi
s@GraphqlApi' {} Maybe AuthenticationType
a -> GraphqlApi
s {$sel:authenticationType:GraphqlApi' :: Maybe AuthenticationType
authenticationType = Maybe AuthenticationType
a} :: GraphqlApi)

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

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

-- | The API name.
graphqlApi_name :: Lens.Lens' GraphqlApi (Prelude.Maybe Prelude.Text)
graphqlApi_name :: Lens' GraphqlApi (Maybe Text)
graphqlApi_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GraphqlApi' {Maybe Text
name :: Maybe Text
$sel:name:GraphqlApi' :: GraphqlApi -> Maybe Text
name} -> Maybe Text
name) (\s :: GraphqlApi
s@GraphqlApi' {} Maybe Text
a -> GraphqlApi
s {$sel:name:GraphqlApi' :: Maybe Text
name = Maybe Text
a} :: GraphqlApi)

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

-- | The tags.
graphqlApi_tags :: Lens.Lens' GraphqlApi (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
graphqlApi_tags :: Lens' GraphqlApi (Maybe (HashMap Text Text))
graphqlApi_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GraphqlApi' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GraphqlApi' :: GraphqlApi -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GraphqlApi
s@GraphqlApi' {} Maybe (HashMap Text Text)
a -> GraphqlApi
s {$sel:tags:GraphqlApi' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GraphqlApi) 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 URIs.
graphqlApi_uris :: Lens.Lens' GraphqlApi (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
graphqlApi_uris :: Lens' GraphqlApi (Maybe (HashMap Text Text))
graphqlApi_uris = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GraphqlApi' {Maybe (HashMap Text Text)
uris :: Maybe (HashMap Text Text)
$sel:uris:GraphqlApi' :: GraphqlApi -> Maybe (HashMap Text Text)
uris} -> Maybe (HashMap Text Text)
uris) (\s :: GraphqlApi
s@GraphqlApi' {} Maybe (HashMap Text Text)
a -> GraphqlApi
s {$sel:uris:GraphqlApi' :: Maybe (HashMap Text Text)
uris = Maybe (HashMap Text Text)
a} :: GraphqlApi) 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.
graphqlApi_userPoolConfig :: Lens.Lens' GraphqlApi (Prelude.Maybe UserPoolConfig)
graphqlApi_userPoolConfig :: Lens' GraphqlApi (Maybe UserPoolConfig)
graphqlApi_userPoolConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GraphqlApi' {Maybe UserPoolConfig
userPoolConfig :: Maybe UserPoolConfig
$sel:userPoolConfig:GraphqlApi' :: GraphqlApi -> Maybe UserPoolConfig
userPoolConfig} -> Maybe UserPoolConfig
userPoolConfig) (\s :: GraphqlApi
s@GraphqlApi' {} Maybe UserPoolConfig
a -> GraphqlApi
s {$sel:userPoolConfig:GraphqlApi' :: Maybe UserPoolConfig
userPoolConfig = Maybe UserPoolConfig
a} :: GraphqlApi)

-- | The ARN of the WAF access control list (ACL) associated with this
-- @GraphqlApi@, if one exists.
graphqlApi_wafWebAclArn :: Lens.Lens' GraphqlApi (Prelude.Maybe Prelude.Text)
graphqlApi_wafWebAclArn :: Lens' GraphqlApi (Maybe Text)
graphqlApi_wafWebAclArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GraphqlApi' {Maybe Text
wafWebAclArn :: Maybe Text
$sel:wafWebAclArn:GraphqlApi' :: GraphqlApi -> Maybe Text
wafWebAclArn} -> Maybe Text
wafWebAclArn) (\s :: GraphqlApi
s@GraphqlApi' {} Maybe Text
a -> GraphqlApi
s {$sel:wafWebAclArn:GraphqlApi' :: Maybe Text
wafWebAclArn = Maybe Text
a} :: GraphqlApi)

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

instance Data.FromJSON GraphqlApi where
  parseJSON :: Value -> Parser GraphqlApi
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"GraphqlApi"
      ( \Object
x ->
          Maybe [AdditionalAuthenticationProvider]
-> Maybe Text
-> Maybe Text
-> Maybe AuthenticationType
-> Maybe LambdaAuthorizerConfig
-> Maybe LogConfig
-> Maybe Text
-> Maybe OpenIDConnectConfig
-> Maybe (HashMap Text Text)
-> Maybe (HashMap Text Text)
-> Maybe UserPoolConfig
-> Maybe Text
-> Maybe Bool
-> GraphqlApi
GraphqlApi'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"additionalAuthenticationProviders"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"authenticationType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"lambdaAuthorizerConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"logConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"openIDConnectConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"uris" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"userPoolConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"wafWebAclArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"xrayEnabled")
      )

instance Prelude.Hashable GraphqlApi where
  hashWithSalt :: Int -> GraphqlApi -> Int
hashWithSalt Int
_salt GraphqlApi' {Maybe Bool
Maybe [AdditionalAuthenticationProvider]
Maybe Text
Maybe (HashMap Text Text)
Maybe AuthenticationType
Maybe LambdaAuthorizerConfig
Maybe LogConfig
Maybe OpenIDConnectConfig
Maybe UserPoolConfig
xrayEnabled :: Maybe Bool
wafWebAclArn :: Maybe Text
userPoolConfig :: Maybe UserPoolConfig
uris :: Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
openIDConnectConfig :: Maybe OpenIDConnectConfig
name :: Maybe Text
logConfig :: Maybe LogConfig
lambdaAuthorizerConfig :: Maybe LambdaAuthorizerConfig
authenticationType :: Maybe AuthenticationType
arn :: Maybe Text
apiId :: Maybe Text
additionalAuthenticationProviders :: Maybe [AdditionalAuthenticationProvider]
$sel:xrayEnabled:GraphqlApi' :: GraphqlApi -> Maybe Bool
$sel:wafWebAclArn:GraphqlApi' :: GraphqlApi -> Maybe Text
$sel:userPoolConfig:GraphqlApi' :: GraphqlApi -> Maybe UserPoolConfig
$sel:uris:GraphqlApi' :: GraphqlApi -> Maybe (HashMap Text Text)
$sel:tags:GraphqlApi' :: GraphqlApi -> Maybe (HashMap Text Text)
$sel:openIDConnectConfig:GraphqlApi' :: GraphqlApi -> Maybe OpenIDConnectConfig
$sel:name:GraphqlApi' :: GraphqlApi -> Maybe Text
$sel:logConfig:GraphqlApi' :: GraphqlApi -> Maybe LogConfig
$sel:lambdaAuthorizerConfig:GraphqlApi' :: GraphqlApi -> Maybe LambdaAuthorizerConfig
$sel:authenticationType:GraphqlApi' :: GraphqlApi -> Maybe AuthenticationType
$sel:arn:GraphqlApi' :: GraphqlApi -> Maybe Text
$sel:apiId:GraphqlApi' :: GraphqlApi -> Maybe Text
$sel:additionalAuthenticationProviders:GraphqlApi' :: GraphqlApi -> 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 Text
apiId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthenticationType
authenticationType
      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 Text
name
      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 (HashMap Text Text)
uris
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserPoolConfig
userPoolConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
wafWebAclArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
xrayEnabled

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