amazonka-appsync-1.6.0: Amazon AppSync SDK.

Copyright(c) 2013-2018 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.AppSync

Contents

Description

AWS AppSync provides API actions for creating and interacting with data sources using GraphQL from your application.

Synopsis

Service Configuration

appSync :: Service Source #

API version 2017-07-25 of the Amazon AppSync SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by AppSync.

APIKeyValidityOutOfBoundsException

_APIKeyValidityOutOfBoundsException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The API key expiration must be set to a value between 1 and 365 days from creation (for CreateApiKey ) or from update (for UpdateApiKey ).

APIKeyLimitExceededException

_APIKeyLimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The API key exceeded a limit. Try your request again.

APILimitExceededException

_APILimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The GraphQL API exceeded a limit. Try your request again.

NotFoundException

_NotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The resource specified in the request was not found. Check the resource and try again.

GraphQLSchemaException

_GraphQLSchemaException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The GraphQL schema is not valid.

ConcurrentModificationException

_ConcurrentModificationException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Another modification is being made. That modification must complete before you can make your change.

InternalFailureException

_InternalFailureException :: AsError a => Getting (First ServiceError) a ServiceError Source #

An internal AWS AppSync error occurred. Try your request again.

UnauthorizedException

_UnauthorizedException :: AsError a => Getting (First ServiceError) a ServiceError Source #

You are not authorized to perform this operation.

BadRequestException

_BadRequestException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The request is not well formed. For example, a value is invalid or a required field is missing. Check the field values, and try again.

LimitExceededException

_LimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The request exceeded a limit. Try your request again.

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

UpdateDataSource

DeleteDataSource

CreateType

GetGraphqlAPI

CreateGraphqlAPI

StartSchemaCreation

DeleteGraphqlAPI

UpdateGraphqlAPI

GetIntrospectionSchema

GetDataSource

DeleteAPIKey

UpdateAPIKey

UpdateType

DeleteType

CreateDataSource

ListTypes

ListDataSources

UpdateResolver

DeleteResolver

ListResolvers

CreateResolver

GetSchemaCreationStatus

ListGraphqlAPIs

GetResolver

CreateAPIKey

ListAPIKeys

GetType

Types

AuthenticationType

data AuthenticationType Source #

Instances

Bounded AuthenticationType Source # 
Enum AuthenticationType Source # 
Eq AuthenticationType Source # 
Data AuthenticationType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AuthenticationType -> c AuthenticationType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AuthenticationType #

toConstr :: AuthenticationType -> Constr #

dataTypeOf :: AuthenticationType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AuthenticationType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AuthenticationType) #

gmapT :: (forall b. Data b => b -> b) -> AuthenticationType -> AuthenticationType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AuthenticationType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AuthenticationType -> r #

gmapQ :: (forall d. Data d => d -> u) -> AuthenticationType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AuthenticationType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AuthenticationType -> m AuthenticationType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AuthenticationType -> m AuthenticationType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AuthenticationType -> m AuthenticationType #

Ord AuthenticationType Source # 
Read AuthenticationType Source # 
Show AuthenticationType Source # 
Generic AuthenticationType Source # 
Hashable AuthenticationType Source # 
ToJSON AuthenticationType Source # 
FromJSON AuthenticationType Source # 
NFData AuthenticationType Source # 

Methods

rnf :: AuthenticationType -> () #

ToHeader AuthenticationType Source # 
ToQuery AuthenticationType Source # 
ToByteString AuthenticationType Source # 
FromText AuthenticationType Source # 
ToText AuthenticationType Source # 
type Rep AuthenticationType Source # 
type Rep AuthenticationType = D1 * (MetaData "AuthenticationType" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) ((:+:) * ((:+:) * (C1 * (MetaCons "APIKey" PrefixI False) (U1 *)) (C1 * (MetaCons "AWSIAM" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "AmazonCognitoUserPools" PrefixI False) (U1 *)) (C1 * (MetaCons "OpenidConnect" PrefixI False) (U1 *))))

DataSourceType

data DataSourceType Source #

Instances

Bounded DataSourceType Source # 
Enum DataSourceType Source # 
Eq DataSourceType Source # 
Data DataSourceType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataSourceType -> c DataSourceType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataSourceType #

toConstr :: DataSourceType -> Constr #

dataTypeOf :: DataSourceType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DataSourceType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataSourceType) #

gmapT :: (forall b. Data b => b -> b) -> DataSourceType -> DataSourceType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataSourceType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataSourceType -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataSourceType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataSourceType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataSourceType -> m DataSourceType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataSourceType -> m DataSourceType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataSourceType -> m DataSourceType #

Ord DataSourceType Source # 
Read DataSourceType Source # 
Show DataSourceType Source # 
Generic DataSourceType Source # 

Associated Types

type Rep DataSourceType :: * -> * #

Hashable DataSourceType Source # 
ToJSON DataSourceType Source # 
FromJSON DataSourceType Source # 
NFData DataSourceType Source # 

Methods

rnf :: DataSourceType -> () #

ToHeader DataSourceType Source # 
ToQuery DataSourceType Source # 
ToByteString DataSourceType Source # 
FromText DataSourceType Source # 
ToText DataSourceType Source # 
type Rep DataSourceType Source # 
type Rep DataSourceType = D1 * (MetaData "DataSourceType" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) ((:+:) * ((:+:) * (C1 * (MetaCons "AWSLambda" PrefixI False) (U1 *)) (C1 * (MetaCons "AmazonDynamodb" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "AmazonElasticsearch" PrefixI False) (U1 *)) (C1 * (MetaCons "None" PrefixI False) (U1 *))))

DefaultAction

data DefaultAction Source #

Constructors

Allow 
Deny 

Instances

Bounded DefaultAction Source # 
Enum DefaultAction Source # 
Eq DefaultAction Source # 
Data DefaultAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultAction -> c DefaultAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DefaultAction #

toConstr :: DefaultAction -> Constr #

dataTypeOf :: DefaultAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DefaultAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DefaultAction) #

gmapT :: (forall b. Data b => b -> b) -> DefaultAction -> DefaultAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> DefaultAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultAction -> m DefaultAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultAction -> m DefaultAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultAction -> m DefaultAction #

Ord DefaultAction Source # 
Read DefaultAction Source # 
Show DefaultAction Source # 
Generic DefaultAction Source # 

Associated Types

type Rep DefaultAction :: * -> * #

Hashable DefaultAction Source # 
ToJSON DefaultAction Source # 
FromJSON DefaultAction Source # 
NFData DefaultAction Source # 

Methods

rnf :: DefaultAction -> () #

ToHeader DefaultAction Source # 
ToQuery DefaultAction Source # 
ToByteString DefaultAction Source # 
FromText DefaultAction Source # 
ToText DefaultAction Source # 

Methods

toText :: DefaultAction -> Text #

type Rep DefaultAction Source # 
type Rep DefaultAction = D1 * (MetaData "DefaultAction" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) ((:+:) * (C1 * (MetaCons "Allow" PrefixI False) (U1 *)) (C1 * (MetaCons "Deny" PrefixI False) (U1 *)))

FieldLogLevel

data FieldLogLevel Source #

Constructors

FLLAll 
FLLError' 
FLLNone 

Instances

Bounded FieldLogLevel Source # 
Enum FieldLogLevel Source # 
Eq FieldLogLevel Source # 
Data FieldLogLevel Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldLogLevel -> c FieldLogLevel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldLogLevel #

toConstr :: FieldLogLevel -> Constr #

dataTypeOf :: FieldLogLevel -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FieldLogLevel) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldLogLevel) #

gmapT :: (forall b. Data b => b -> b) -> FieldLogLevel -> FieldLogLevel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLogLevel -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLogLevel -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldLogLevel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLogLevel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLogLevel -> m FieldLogLevel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLogLevel -> m FieldLogLevel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLogLevel -> m FieldLogLevel #

Ord FieldLogLevel Source # 
Read FieldLogLevel Source # 
Show FieldLogLevel Source # 
Generic FieldLogLevel Source # 

Associated Types

type Rep FieldLogLevel :: * -> * #

Hashable FieldLogLevel Source # 
ToJSON FieldLogLevel Source # 
FromJSON FieldLogLevel Source # 
NFData FieldLogLevel Source # 

Methods

rnf :: FieldLogLevel -> () #

ToHeader FieldLogLevel Source # 
ToQuery FieldLogLevel Source # 
ToByteString FieldLogLevel Source # 
FromText FieldLogLevel Source # 
ToText FieldLogLevel Source # 

Methods

toText :: FieldLogLevel -> Text #

type Rep FieldLogLevel Source # 
type Rep FieldLogLevel = D1 * (MetaData "FieldLogLevel" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) ((:+:) * (C1 * (MetaCons "FLLAll" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FLLError'" PrefixI False) (U1 *)) (C1 * (MetaCons "FLLNone" PrefixI False) (U1 *))))

OutputType

data OutputType Source #

Constructors

OTJSON 
OTSdl 

Instances

Bounded OutputType Source # 
Enum OutputType Source # 
Eq OutputType Source # 
Data OutputType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OutputType -> c OutputType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OutputType #

toConstr :: OutputType -> Constr #

dataTypeOf :: OutputType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OutputType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OutputType) #

gmapT :: (forall b. Data b => b -> b) -> OutputType -> OutputType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OutputType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OutputType -> r #

gmapQ :: (forall d. Data d => d -> u) -> OutputType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OutputType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OutputType -> m OutputType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputType -> m OutputType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputType -> m OutputType #

Ord OutputType Source # 
Read OutputType Source # 
Show OutputType Source # 
Generic OutputType Source # 

Associated Types

type Rep OutputType :: * -> * #

Hashable OutputType Source # 
ToJSON OutputType Source # 
NFData OutputType Source # 

Methods

rnf :: OutputType -> () #

ToHeader OutputType Source # 
ToQuery OutputType Source # 
ToByteString OutputType Source # 
FromText OutputType Source # 
ToText OutputType Source # 

Methods

toText :: OutputType -> Text #

type Rep OutputType Source # 
type Rep OutputType = D1 * (MetaData "OutputType" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) ((:+:) * (C1 * (MetaCons "OTJSON" PrefixI False) (U1 *)) (C1 * (MetaCons "OTSdl" PrefixI False) (U1 *)))

SchemaStatus

data SchemaStatus Source #

Constructors

Active 
Deleting 
Processing 

Instances

Bounded SchemaStatus Source # 
Enum SchemaStatus Source # 
Eq SchemaStatus Source # 
Data SchemaStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SchemaStatus -> c SchemaStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SchemaStatus #

toConstr :: SchemaStatus -> Constr #

dataTypeOf :: SchemaStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SchemaStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemaStatus) #

gmapT :: (forall b. Data b => b -> b) -> SchemaStatus -> SchemaStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SchemaStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SchemaStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> SchemaStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SchemaStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SchemaStatus -> m SchemaStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemaStatus -> m SchemaStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemaStatus -> m SchemaStatus #

Ord SchemaStatus Source # 
Read SchemaStatus Source # 
Show SchemaStatus Source # 
Generic SchemaStatus Source # 

Associated Types

type Rep SchemaStatus :: * -> * #

Hashable SchemaStatus Source # 
FromJSON SchemaStatus Source # 
NFData SchemaStatus Source # 

Methods

rnf :: SchemaStatus -> () #

ToHeader SchemaStatus Source # 
ToQuery SchemaStatus Source # 
ToByteString SchemaStatus Source # 
FromText SchemaStatus Source # 
ToText SchemaStatus Source # 

Methods

toText :: SchemaStatus -> Text #

type Rep SchemaStatus Source # 
type Rep SchemaStatus = D1 * (MetaData "SchemaStatus" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) ((:+:) * (C1 * (MetaCons "Active" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Deleting" PrefixI False) (U1 *)) (C1 * (MetaCons "Processing" PrefixI False) (U1 *))))

TypeDefinitionFormat

data TypeDefinitionFormat Source #

Constructors

JSON 
Sdl 

Instances

Bounded TypeDefinitionFormat Source # 
Enum TypeDefinitionFormat Source # 
Eq TypeDefinitionFormat Source # 
Data TypeDefinitionFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeDefinitionFormat -> c TypeDefinitionFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeDefinitionFormat #

toConstr :: TypeDefinitionFormat -> Constr #

dataTypeOf :: TypeDefinitionFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TypeDefinitionFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeDefinitionFormat) #

gmapT :: (forall b. Data b => b -> b) -> TypeDefinitionFormat -> TypeDefinitionFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeDefinitionFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeDefinitionFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> TypeDefinitionFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeDefinitionFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeDefinitionFormat -> m TypeDefinitionFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDefinitionFormat -> m TypeDefinitionFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDefinitionFormat -> m TypeDefinitionFormat #

Ord TypeDefinitionFormat Source # 
Read TypeDefinitionFormat Source # 
Show TypeDefinitionFormat Source # 
Generic TypeDefinitionFormat Source # 
Hashable TypeDefinitionFormat Source # 
ToJSON TypeDefinitionFormat Source # 
FromJSON TypeDefinitionFormat Source # 
NFData TypeDefinitionFormat Source # 

Methods

rnf :: TypeDefinitionFormat -> () #

ToHeader TypeDefinitionFormat Source # 
ToQuery TypeDefinitionFormat Source # 
ToByteString TypeDefinitionFormat Source # 
FromText TypeDefinitionFormat Source # 
ToText TypeDefinitionFormat Source # 
type Rep TypeDefinitionFormat Source # 
type Rep TypeDefinitionFormat = D1 * (MetaData "TypeDefinitionFormat" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) ((:+:) * (C1 * (MetaCons "JSON" PrefixI False) (U1 *)) (C1 * (MetaCons "Sdl" PrefixI False) (U1 *)))

APIKey

data APIKey Source #

Describes an API key.

Customers invoke AWS AppSync GraphQL APIs with API keys as an identity mechanism. There are two key versions:

da1 : This version was introduced at launch in November 2017. These keys always expire after 7 days. Key expiration is managed by DynamoDB TTL. The keys will cease to be valid after Feb 21, 2018 and should not be used after that date.

  • ListApiKeys returns the expiration time in milliseconds.
  • CreateApiKey returns the expiration time in milliseconds.
  • UpdateApiKey is not available for this key version.
  • DeleteApiKey deletes the item from the table.
  • Expiration is stored in DynamoDB as milliseconds. This results in a bug where keys are not automatically deleted because DynamoDB expects the TTL to be stored in seconds. As a one-time action, we will delete these keys from the table after Feb 21, 2018.

da2 : This version was introduced in February 2018 when AppSync added support to extend key expiration.

  • ListApiKeys returns the expiration time in seconds.
  • CreateApiKey returns the expiration time in seconds and accepts a user-provided expiration time in seconds.
  • UpdateApiKey returns the expiration time in seconds and accepts a user-provided expiration time in seconds. Key expiration can only be updated while the key has not expired.
  • DeleteApiKey deletes the item from the table.
  • Expiration is stored in DynamoDB as seconds.

See: apiKey smart constructor.

Instances

Eq APIKey Source # 

Methods

(==) :: APIKey -> APIKey -> Bool #

(/=) :: APIKey -> APIKey -> Bool #

Data APIKey Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APIKey -> c APIKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APIKey #

toConstr :: APIKey -> Constr #

dataTypeOf :: APIKey -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APIKey) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APIKey) #

gmapT :: (forall b. Data b => b -> b) -> APIKey -> APIKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APIKey -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APIKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> APIKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APIKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APIKey -> m APIKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APIKey -> m APIKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APIKey -> m APIKey #

Read APIKey Source # 
Show APIKey Source # 
Generic APIKey Source # 

Associated Types

type Rep APIKey :: * -> * #

Methods

from :: APIKey -> Rep APIKey x #

to :: Rep APIKey x -> APIKey #

Hashable APIKey Source # 

Methods

hashWithSalt :: Int -> APIKey -> Int #

hash :: APIKey -> Int #

FromJSON APIKey Source # 
NFData APIKey Source # 

Methods

rnf :: APIKey -> () #

type Rep APIKey Source # 
type Rep APIKey = D1 * (MetaData "APIKey" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) (C1 * (MetaCons "APIKey'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_akExpires") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) ((:*:) * (S1 * (MetaSel (Just Symbol "_akId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_akDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

apiKey :: APIKey Source #

Creates a value of APIKey with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • akExpires - The time after which the API key expires. The date is represented as seconds since the epoch, rounded down to the nearest hour.
  • akId - The API key ID.
  • akDescription - A description of the purpose of the API key.

akExpires :: Lens' APIKey (Maybe Integer) Source #

The time after which the API key expires. The date is represented as seconds since the epoch, rounded down to the nearest hour.

akId :: Lens' APIKey (Maybe Text) Source #

The API key ID.

akDescription :: Lens' APIKey (Maybe Text) Source #

A description of the purpose of the API key.

DataSource

data DataSource Source #

Describes a data source.

See: dataSource smart constructor.

Instances

Eq DataSource Source # 
Data DataSource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataSource -> c DataSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataSource #

toConstr :: DataSource -> Constr #

dataTypeOf :: DataSource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DataSource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataSource) #

gmapT :: (forall b. Data b => b -> b) -> DataSource -> DataSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataSource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataSource -> m DataSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataSource -> m DataSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataSource -> m DataSource #

Read DataSource Source # 
Show DataSource Source # 
Generic DataSource Source # 

Associated Types

type Rep DataSource :: * -> * #

Hashable DataSource Source # 
FromJSON DataSource Source # 
NFData DataSource Source # 

Methods

rnf :: DataSource -> () #

type Rep DataSource Source # 

dataSource :: DataSource Source #

Creates a value of DataSource with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dsServiceRoleARN - The IAM service role ARN for the data source. The system assumes this role when accessing the data source.
  • dsDataSourceARN - The data source ARN.
  • dsDynamodbConfig - DynamoDB settings.
  • dsName - The name of the data source.
  • dsLambdaConfig - Lambda settings.
  • dsType - The type of the data source. * AMAZON_DYNAMODB : The data source is an Amazon DynamoDB table. * AMAZON_ELASTICSEARCH : The data source is an Amazon Elasticsearch Service domain. * AWS_LAMBDA : The data source is an AWS Lambda function. * NONE : There is no data source. This type is used when when you wish to invoke a GraphQL operation without connecting to a data source, such as performing data transformation with resolvers or triggering a subscription to be invoked from a mutation.
  • dsDescription - The description of the data source.
  • dsElasticsearchConfig - Amazon Elasticsearch settings.

dsServiceRoleARN :: Lens' DataSource (Maybe Text) Source #

The IAM service role ARN for the data source. The system assumes this role when accessing the data source.

dsDataSourceARN :: Lens' DataSource (Maybe Text) Source #

The data source ARN.

dsName :: Lens' DataSource (Maybe Text) Source #

The name of the data source.

dsType :: Lens' DataSource (Maybe DataSourceType) Source #

The type of the data source. * AMAZON_DYNAMODB : The data source is an Amazon DynamoDB table. * AMAZON_ELASTICSEARCH : The data source is an Amazon Elasticsearch Service domain. * AWS_LAMBDA : The data source is an AWS Lambda function. * NONE : There is no data source. This type is used when when you wish to invoke a GraphQL operation without connecting to a data source, such as performing data transformation with resolvers or triggering a subscription to be invoked from a mutation.

dsDescription :: Lens' DataSource (Maybe Text) Source #

The description of the data source.

DynamodbDataSourceConfig

data DynamodbDataSourceConfig Source #

Describes a DynamoDB data source configuration.

See: dynamodbDataSourceConfig smart constructor.

Instances

Eq DynamodbDataSourceConfig Source # 
Data DynamodbDataSourceConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DynamodbDataSourceConfig -> c DynamodbDataSourceConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DynamodbDataSourceConfig #

toConstr :: DynamodbDataSourceConfig -> Constr #

dataTypeOf :: DynamodbDataSourceConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DynamodbDataSourceConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DynamodbDataSourceConfig) #

gmapT :: (forall b. Data b => b -> b) -> DynamodbDataSourceConfig -> DynamodbDataSourceConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DynamodbDataSourceConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DynamodbDataSourceConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> DynamodbDataSourceConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DynamodbDataSourceConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DynamodbDataSourceConfig -> m DynamodbDataSourceConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamodbDataSourceConfig -> m DynamodbDataSourceConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamodbDataSourceConfig -> m DynamodbDataSourceConfig #

Read DynamodbDataSourceConfig Source # 
Show DynamodbDataSourceConfig Source # 
Generic DynamodbDataSourceConfig Source # 
Hashable DynamodbDataSourceConfig Source # 
ToJSON DynamodbDataSourceConfig Source # 
FromJSON DynamodbDataSourceConfig Source # 
NFData DynamodbDataSourceConfig Source # 
type Rep DynamodbDataSourceConfig Source # 
type Rep DynamodbDataSourceConfig = D1 * (MetaData "DynamodbDataSourceConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) (C1 * (MetaCons "DynamodbDataSourceConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ddscUseCallerCredentials") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ddscTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_ddscAwsRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

dynamodbDataSourceConfig Source #

Creates a value of DynamodbDataSourceConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ddscUseCallerCredentials :: Lens' DynamodbDataSourceConfig (Maybe Bool) Source #

Set to TRUE to use Amazon Cognito credentials with this data source.

ElasticsearchDataSourceConfig

data ElasticsearchDataSourceConfig Source #

Describes an Elasticsearch data source configuration.

See: elasticsearchDataSourceConfig smart constructor.

Instances

Eq ElasticsearchDataSourceConfig Source # 
Data ElasticsearchDataSourceConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ElasticsearchDataSourceConfig -> c ElasticsearchDataSourceConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ElasticsearchDataSourceConfig #

toConstr :: ElasticsearchDataSourceConfig -> Constr #

dataTypeOf :: ElasticsearchDataSourceConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ElasticsearchDataSourceConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ElasticsearchDataSourceConfig) #

gmapT :: (forall b. Data b => b -> b) -> ElasticsearchDataSourceConfig -> ElasticsearchDataSourceConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ElasticsearchDataSourceConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ElasticsearchDataSourceConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> ElasticsearchDataSourceConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ElasticsearchDataSourceConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ElasticsearchDataSourceConfig -> m ElasticsearchDataSourceConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ElasticsearchDataSourceConfig -> m ElasticsearchDataSourceConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ElasticsearchDataSourceConfig -> m ElasticsearchDataSourceConfig #

Read ElasticsearchDataSourceConfig Source # 
Show ElasticsearchDataSourceConfig Source # 
Generic ElasticsearchDataSourceConfig Source # 
Hashable ElasticsearchDataSourceConfig Source # 
ToJSON ElasticsearchDataSourceConfig Source # 
FromJSON ElasticsearchDataSourceConfig Source # 
NFData ElasticsearchDataSourceConfig Source # 
type Rep ElasticsearchDataSourceConfig Source # 
type Rep ElasticsearchDataSourceConfig = D1 * (MetaData "ElasticsearchDataSourceConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) (C1 * (MetaCons "ElasticsearchDataSourceConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_edscEndpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_edscAwsRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

elasticsearchDataSourceConfig Source #

Creates a value of ElasticsearchDataSourceConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

GraphqlAPI

data GraphqlAPI Source #

Describes a GraphQL API.

See: graphqlAPI smart constructor.

Instances

Eq GraphqlAPI Source # 
Data GraphqlAPI Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GraphqlAPI -> c GraphqlAPI #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GraphqlAPI #

toConstr :: GraphqlAPI -> Constr #

dataTypeOf :: GraphqlAPI -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GraphqlAPI) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GraphqlAPI) #

gmapT :: (forall b. Data b => b -> b) -> GraphqlAPI -> GraphqlAPI #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GraphqlAPI -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GraphqlAPI -> r #

gmapQ :: (forall d. Data d => d -> u) -> GraphqlAPI -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GraphqlAPI -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GraphqlAPI -> m GraphqlAPI #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GraphqlAPI -> m GraphqlAPI #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GraphqlAPI -> m GraphqlAPI #

Read GraphqlAPI Source # 
Show GraphqlAPI Source # 
Generic GraphqlAPI Source # 

Associated Types

type Rep GraphqlAPI :: * -> * #

Hashable GraphqlAPI Source # 
FromJSON GraphqlAPI Source # 
NFData GraphqlAPI Source # 

Methods

rnf :: GraphqlAPI -> () #

type Rep GraphqlAPI Source # 

graphqlAPI :: GraphqlAPI Source #

Creates a value of GraphqlAPI with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gaOpenIdConnectConfig :: Lens' GraphqlAPI (Maybe OpenIdConnectConfig) Source #

The Open Id Connect configuration.

gaUserPoolConfig :: Lens' GraphqlAPI (Maybe UserPoolConfig) Source #

The Amazon Cognito User Pool configuration.

gaLogConfig :: Lens' GraphqlAPI (Maybe LogConfig) Source #

The Amazon CloudWatch Logs configuration.

LambdaDataSourceConfig

data LambdaDataSourceConfig Source #

Describes a Lambda data source configuration.

See: lambdaDataSourceConfig smart constructor.

Instances

Eq LambdaDataSourceConfig Source # 
Data LambdaDataSourceConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LambdaDataSourceConfig -> c LambdaDataSourceConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LambdaDataSourceConfig #

toConstr :: LambdaDataSourceConfig -> Constr #

dataTypeOf :: LambdaDataSourceConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LambdaDataSourceConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LambdaDataSourceConfig) #

gmapT :: (forall b. Data b => b -> b) -> LambdaDataSourceConfig -> LambdaDataSourceConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LambdaDataSourceConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LambdaDataSourceConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> LambdaDataSourceConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LambdaDataSourceConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LambdaDataSourceConfig -> m LambdaDataSourceConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LambdaDataSourceConfig -> m LambdaDataSourceConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LambdaDataSourceConfig -> m LambdaDataSourceConfig #

Read LambdaDataSourceConfig Source # 
Show LambdaDataSourceConfig Source # 
Generic LambdaDataSourceConfig Source # 
Hashable LambdaDataSourceConfig Source # 
ToJSON LambdaDataSourceConfig Source # 
FromJSON LambdaDataSourceConfig Source # 
NFData LambdaDataSourceConfig Source # 

Methods

rnf :: LambdaDataSourceConfig -> () #

type Rep LambdaDataSourceConfig Source # 
type Rep LambdaDataSourceConfig = D1 * (MetaData "LambdaDataSourceConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" True) (C1 * (MetaCons "LambdaDataSourceConfig'" PrefixI True) (S1 * (MetaSel (Just Symbol "_ldscLambdaFunctionARN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

lambdaDataSourceConfig Source #

Creates a value of LambdaDataSourceConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ldscLambdaFunctionARN :: Lens' LambdaDataSourceConfig Text Source #

The ARN for the Lambda function.

LogConfig

data LogConfig Source #

The CloudWatch Logs configuration.

See: logConfig smart constructor.

Instances

Eq LogConfig Source # 
Data LogConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LogConfig -> c LogConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LogConfig #

toConstr :: LogConfig -> Constr #

dataTypeOf :: LogConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LogConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LogConfig) #

gmapT :: (forall b. Data b => b -> b) -> LogConfig -> LogConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LogConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LogConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> LogConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LogConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LogConfig -> m LogConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LogConfig -> m LogConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LogConfig -> m LogConfig #

Read LogConfig Source # 
Show LogConfig Source # 
Generic LogConfig Source # 

Associated Types

type Rep LogConfig :: * -> * #

Hashable LogConfig Source # 
ToJSON LogConfig Source # 
FromJSON LogConfig Source # 
NFData LogConfig Source # 

Methods

rnf :: LogConfig -> () #

type Rep LogConfig Source # 
type Rep LogConfig = D1 * (MetaData "LogConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) (C1 * (MetaCons "LogConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lcFieldLogLevel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FieldLogLevel)) (S1 * (MetaSel (Just Symbol "_lcCloudWatchLogsRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

logConfig Source #

Creates a value of LogConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • lcFieldLogLevel - The field logging level. Values can be NONE, ERROR, ALL. * NONE : No field-level logs are captured. * ERROR : Logs the following information only for the fields that are in error: * The error section in the server response. * Field-level errors. * The generated requestresponse functions that got resolved for error fields. * ALL : The following information is logged for all fields in the query: * Field-level tracing information. * The generated requestresponse functions that got resolved for each field.
  • lcCloudWatchLogsRoleARN - The service role that AWS AppSync will assume to publish to Amazon CloudWatch logs in your account.

lcFieldLogLevel :: Lens' LogConfig FieldLogLevel Source #

The field logging level. Values can be NONE, ERROR, ALL. * NONE : No field-level logs are captured. * ERROR : Logs the following information only for the fields that are in error: * The error section in the server response. * Field-level errors. * The generated requestresponse functions that got resolved for error fields. * ALL : The following information is logged for all fields in the query: * Field-level tracing information. * The generated requestresponse functions that got resolved for each field.

lcCloudWatchLogsRoleARN :: Lens' LogConfig Text Source #

The service role that AWS AppSync will assume to publish to Amazon CloudWatch logs in your account.

OpenIdConnectConfig

data OpenIdConnectConfig Source #

Describes an Open Id Connect configuration.

See: openIdConnectConfig smart constructor.

Instances

Eq OpenIdConnectConfig Source # 
Data OpenIdConnectConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OpenIdConnectConfig -> c OpenIdConnectConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OpenIdConnectConfig #

toConstr :: OpenIdConnectConfig -> Constr #

dataTypeOf :: OpenIdConnectConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OpenIdConnectConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenIdConnectConfig) #

gmapT :: (forall b. Data b => b -> b) -> OpenIdConnectConfig -> OpenIdConnectConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OpenIdConnectConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OpenIdConnectConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> OpenIdConnectConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OpenIdConnectConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OpenIdConnectConfig -> m OpenIdConnectConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenIdConnectConfig -> m OpenIdConnectConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenIdConnectConfig -> m OpenIdConnectConfig #

Read OpenIdConnectConfig Source # 
Show OpenIdConnectConfig Source # 
Generic OpenIdConnectConfig Source # 
Hashable OpenIdConnectConfig Source # 
ToJSON OpenIdConnectConfig Source # 
FromJSON OpenIdConnectConfig Source # 
NFData OpenIdConnectConfig Source # 

Methods

rnf :: OpenIdConnectConfig -> () #

type Rep OpenIdConnectConfig Source # 
type Rep OpenIdConnectConfig = D1 * (MetaData "OpenIdConnectConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) (C1 * (MetaCons "OpenIdConnectConfig'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_oiccAuthTTL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) (S1 * (MetaSel (Just Symbol "_oiccClientId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_oiccIatTTL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) (S1 * (MetaSel (Just Symbol "_oiccIssuer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

openIdConnectConfig Source #

Creates a value of OpenIdConnectConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • oiccAuthTTL - The number of milliseconds a token is valid after being authenticated.
  • oiccClientId - The client identifier of the Relying party at the OpenID Provider. This identifier is typically obtained when the Relying party is registered with the OpenID Provider. You can specify a regular expression so the AWS AppSync can validate against multiple client identifiers at a time
  • oiccIatTTL - The number of milliseconds a token is valid after being issued to a user.
  • oiccIssuer - The issuer for the open id connect configuration. The issuer returned by discovery MUST exactly match the value of iss in the ID Token.

oiccAuthTTL :: Lens' OpenIdConnectConfig (Maybe Integer) Source #

The number of milliseconds a token is valid after being authenticated.

oiccClientId :: Lens' OpenIdConnectConfig (Maybe Text) Source #

The client identifier of the Relying party at the OpenID Provider. This identifier is typically obtained when the Relying party is registered with the OpenID Provider. You can specify a regular expression so the AWS AppSync can validate against multiple client identifiers at a time

oiccIatTTL :: Lens' OpenIdConnectConfig (Maybe Integer) Source #

The number of milliseconds a token is valid after being issued to a user.

oiccIssuer :: Lens' OpenIdConnectConfig Text Source #

The issuer for the open id connect configuration. The issuer returned by discovery MUST exactly match the value of iss in the ID Token.

Resolver

data Resolver Source #

Describes a resolver.

See: resolver smart constructor.

Instances

Eq Resolver Source # 
Data Resolver Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Resolver -> c Resolver #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Resolver #

toConstr :: Resolver -> Constr #

dataTypeOf :: Resolver -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Resolver) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Resolver) #

gmapT :: (forall b. Data b => b -> b) -> Resolver -> Resolver #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Resolver -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Resolver -> r #

gmapQ :: (forall d. Data d => d -> u) -> Resolver -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Resolver -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Resolver -> m Resolver #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Resolver -> m Resolver #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Resolver -> m Resolver #

Read Resolver Source # 
Show Resolver Source # 
Generic Resolver Source # 

Associated Types

type Rep Resolver :: * -> * #

Methods

from :: Resolver -> Rep Resolver x #

to :: Rep Resolver x -> Resolver #

Hashable Resolver Source # 

Methods

hashWithSalt :: Int -> Resolver -> Int #

hash :: Resolver -> Int #

FromJSON Resolver Source # 
NFData Resolver Source # 

Methods

rnf :: Resolver -> () #

type Rep Resolver Source # 
type Rep Resolver = D1 * (MetaData "Resolver" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) (C1 * (MetaCons "Resolver'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_rTypeName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rDataSourceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rRequestMappingTemplate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rResolverARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rResponseMappingTemplate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rFieldName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

resolver :: Resolver Source #

Creates a value of Resolver with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rTypeName :: Lens' Resolver (Maybe Text) Source #

The resolver type name.

rDataSourceName :: Lens' Resolver (Maybe Text) Source #

The resolver data source name.

rRequestMappingTemplate :: Lens' Resolver (Maybe Text) Source #

The request mapping template.

rResolverARN :: Lens' Resolver (Maybe Text) Source #

The resolver ARN.

rResponseMappingTemplate :: Lens' Resolver (Maybe Text) Source #

The response mapping template.

rFieldName :: Lens' Resolver (Maybe Text) Source #

The resolver field name.

Type

data Type Source #

Describes a type.

See: type' smart constructor.

Instances

Eq Type Source # 

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Data Type Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type #

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Type) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) #

gmapT :: (forall b. Data b => b -> b) -> Type -> Type #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r #

gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type #

Read Type Source # 
Show Type Source # 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 

Associated Types

type Rep Type :: * -> * #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Hashable Type Source # 

Methods

hashWithSalt :: Int -> Type -> Int #

hash :: Type -> Int #

FromJSON Type Source # 
NFData Type Source # 

Methods

rnf :: Type -> () #

type Rep Type Source # 

type' :: Type Source #

Creates a value of Type with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tArn :: Lens' Type (Maybe Text) Source #

The type ARN.

tDefinition :: Lens' Type (Maybe Text) Source #

The type definition.

tFormat :: Lens' Type (Maybe TypeDefinitionFormat) Source #

The type format: SDL or JSON.

tName :: Lens' Type (Maybe Text) Source #

The type name.

tDescription :: Lens' Type (Maybe Text) Source #

The type description.

UserPoolConfig

data UserPoolConfig Source #

Describes an Amazon Cognito User Pool configuration.

See: userPoolConfig smart constructor.

Instances

Eq UserPoolConfig Source # 
Data UserPoolConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserPoolConfig -> c UserPoolConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserPoolConfig #

toConstr :: UserPoolConfig -> Constr #

dataTypeOf :: UserPoolConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserPoolConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserPoolConfig) #

gmapT :: (forall b. Data b => b -> b) -> UserPoolConfig -> UserPoolConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserPoolConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserPoolConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserPoolConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserPoolConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserPoolConfig -> m UserPoolConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserPoolConfig -> m UserPoolConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserPoolConfig -> m UserPoolConfig #

Read UserPoolConfig Source # 
Show UserPoolConfig Source # 
Generic UserPoolConfig Source # 

Associated Types

type Rep UserPoolConfig :: * -> * #

Hashable UserPoolConfig Source # 
ToJSON UserPoolConfig Source # 
FromJSON UserPoolConfig Source # 
NFData UserPoolConfig Source # 

Methods

rnf :: UserPoolConfig -> () #

type Rep UserPoolConfig Source # 
type Rep UserPoolConfig = D1 * (MetaData "UserPoolConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.0-T90u3sf1xIAHhsH8NXxyF" False) (C1 * (MetaCons "UserPoolConfig'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_upcAppIdClientRegex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_upcUserPoolId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_upcAwsRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_upcDefaultAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * DefaultAction)))))

userPoolConfig Source #

Creates a value of UserPoolConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • upcAppIdClientRegex - A regular expression for validating the incoming Amazon Cognito User Pool app client ID.
  • upcUserPoolId - The user pool ID.
  • upcAwsRegion - The AWS region in which the user pool was created.
  • upcDefaultAction - The action that you want your GraphQL API to take when a request that uses Amazon Cognito User Pool authentication doesn't match the Amazon Cognito User Pool configuration.

upcAppIdClientRegex :: Lens' UserPoolConfig (Maybe Text) Source #

A regular expression for validating the incoming Amazon Cognito User Pool app client ID.

upcAwsRegion :: Lens' UserPoolConfig Text Source #

The AWS region in which the user pool was created.

upcDefaultAction :: Lens' UserPoolConfig DefaultAction Source #

The action that you want your GraphQL API to take when a request that uses Amazon Cognito User Pool authentication doesn't match the Amazon Cognito User Pool configuration.