amazonka-appsync-1.6.1: 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.Types

Contents

Description

 
Synopsis

Service Configuration

appSync :: Service Source #

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

Errors

_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 :: AsError a => Getting (First ServiceError) a ServiceError Source #

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

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

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

_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 :: AsError a => Getting (First ServiceError) a ServiceError Source #

The GraphQL schema is not valid.

_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 :: AsError a => Getting (First ServiceError) a ServiceError Source #

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

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

You are not authorized to perform this operation.

_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 :: AsError a => Getting (First ServiceError) a ServiceError Source #

The request exceeded a limit. Try your request again.

AuthenticationType

data AuthenticationType Source #

Instances
Bounded AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Enum AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Eq AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Data AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Read AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Show AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Generic AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Associated Types

type Rep AuthenticationType :: Type -> Type #

Hashable AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToJSON AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromJSON AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToHeader AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToQuery AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToByteString AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromText AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToText AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

NFData AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

rnf :: AuthenticationType -> () #

type Rep AuthenticationType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

type Rep AuthenticationType = D1 (MetaData "AuthenticationType" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) ((C1 (MetaCons "APIKey" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AWSIAM" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AmazonCognitoUserPools" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OpenidConnect" PrefixI False) (U1 :: Type -> Type)))

DataSourceType

data DataSourceType Source #

Instances
Bounded DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Enum DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Eq DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Data DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Read DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Show DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Generic DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Associated Types

type Rep DataSourceType :: Type -> Type #

Hashable DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToJSON DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromJSON DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToHeader DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToQuery DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToByteString DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromText DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToText DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

NFData DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

rnf :: DataSourceType -> () #

type Rep DataSourceType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

type Rep DataSourceType = D1 (MetaData "DataSourceType" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) ((C1 (MetaCons "AWSLambda" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AmazonDynamodb" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AmazonElasticsearch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "None" PrefixI False) (U1 :: Type -> Type)))

DefaultAction

data DefaultAction Source #

Constructors

Allow 
Deny 
Instances
Bounded DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Enum DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Eq DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Data DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Read DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Show DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Generic DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Associated Types

type Rep DefaultAction :: Type -> Type #

Hashable DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToJSON DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromJSON DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToHeader DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToQuery DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToByteString DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromText DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToText DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

toText :: DefaultAction -> Text #

NFData DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

rnf :: DefaultAction -> () #

type Rep DefaultAction Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

type Rep DefaultAction = D1 (MetaData "DefaultAction" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "Allow" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Deny" PrefixI False) (U1 :: Type -> Type))

FieldLogLevel

data FieldLogLevel Source #

Constructors

FLLAll 
FLLError' 
FLLNone 
Instances
Bounded FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Enum FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Eq FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Data FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Read FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Show FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Generic FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Associated Types

type Rep FieldLogLevel :: Type -> Type #

Hashable FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToJSON FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromJSON FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToHeader FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToQuery FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToByteString FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromText FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToText FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

toText :: FieldLogLevel -> Text #

NFData FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

rnf :: FieldLogLevel -> () #

type Rep FieldLogLevel Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

type Rep FieldLogLevel = D1 (MetaData "FieldLogLevel" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "FLLAll" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FLLError'" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FLLNone" PrefixI False) (U1 :: Type -> Type)))

OutputType

data OutputType Source #

Constructors

OTJSON 
OTSdl 
Instances
Bounded OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Enum OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Eq OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Data OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Read OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Show OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Generic OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Associated Types

type Rep OutputType :: Type -> Type #

Hashable OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToJSON OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToHeader OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToQuery OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToByteString OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromText OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToText OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

toText :: OutputType -> Text #

NFData OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

rnf :: OutputType -> () #

type Rep OutputType Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

type Rep OutputType = D1 (MetaData "OutputType" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "OTJSON" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OTSdl" PrefixI False) (U1 :: Type -> Type))

SchemaStatus

data SchemaStatus Source #

Constructors

Active 
Deleting 
Processing 
Instances
Bounded SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Enum SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Eq SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Data SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Read SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Show SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Generic SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Associated Types

type Rep SchemaStatus :: Type -> Type #

Hashable SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromJSON SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToHeader SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToQuery SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToByteString SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromText SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToText SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

toText :: SchemaStatus -> Text #

NFData SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

rnf :: SchemaStatus -> () #

type Rep SchemaStatus Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

type Rep SchemaStatus = D1 (MetaData "SchemaStatus" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "Active" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Deleting" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Processing" PrefixI False) (U1 :: Type -> Type)))

TypeDefinitionFormat

data TypeDefinitionFormat Source #

Constructors

JSON 
Sdl 
Instances
Bounded TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Enum TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Eq TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Data TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Read TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Show TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Generic TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Associated Types

type Rep TypeDefinitionFormat :: Type -> Type #

Hashable TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToJSON TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromJSON TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToHeader TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToQuery TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToByteString TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

FromText TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

ToText TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

NFData TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

Methods

rnf :: TypeDefinitionFormat -> () #

type Rep TypeDefinitionFormat Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Sum

type Rep TypeDefinitionFormat = D1 (MetaData "TypeDefinitionFormat" "Network.AWS.AppSync.Types.Sum" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "JSON" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sdl" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

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

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

Data APIKey Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show APIKey Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic APIKey Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep APIKey :: Type -> Type #

Methods

from :: APIKey -> Rep APIKey x #

to :: Rep APIKey x -> APIKey #

Hashable APIKey Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

hashWithSalt :: Int -> APIKey -> Int #

hash :: APIKey -> Int #

FromJSON APIKey Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData APIKey Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

rnf :: APIKey -> () #

type Rep APIKey Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep APIKey = D1 (MetaData "APIKey" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "APIKey'" PrefixI True) (S1 (MetaSel (Just "_akExpires") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: (S1 (MetaSel (Just "_akId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Data DataSource Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show DataSource Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic DataSource Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep DataSource :: Type -> Type #

Hashable DataSource Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

FromJSON DataSource Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData DataSource Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

rnf :: DataSource -> () #

type Rep DataSource Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Data DynamodbDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show DynamodbDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic DynamodbDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep DynamodbDataSourceConfig :: Type -> Type #

Hashable DynamodbDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

ToJSON DynamodbDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

FromJSON DynamodbDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData DynamodbDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep DynamodbDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep DynamodbDataSourceConfig = D1 (MetaData "DynamodbDataSourceConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "DynamodbDataSourceConfig'" PrefixI True) (S1 (MetaSel (Just "_ddscUseCallerCredentials") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "_ddscTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Data ElasticsearchDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show ElasticsearchDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic ElasticsearchDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep ElasticsearchDataSourceConfig :: Type -> Type #

Hashable ElasticsearchDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

ToJSON ElasticsearchDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

FromJSON ElasticsearchDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData ElasticsearchDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep ElasticsearchDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep ElasticsearchDataSourceConfig = D1 (MetaData "ElasticsearchDataSourceConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "ElasticsearchDataSourceConfig'" PrefixI True) (S1 (MetaSel (Just "_edscEndpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Data GraphqlAPI Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show GraphqlAPI Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic GraphqlAPI Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep GraphqlAPI :: Type -> Type #

Hashable GraphqlAPI Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

FromJSON GraphqlAPI Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData GraphqlAPI Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

rnf :: GraphqlAPI -> () #

type Rep GraphqlAPI Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Data LambdaDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show LambdaDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic LambdaDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep LambdaDataSourceConfig :: Type -> Type #

Hashable LambdaDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

ToJSON LambdaDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

FromJSON LambdaDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData LambdaDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

rnf :: LambdaDataSourceConfig -> () #

type Rep LambdaDataSourceConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep LambdaDataSourceConfig = D1 (MetaData "LambdaDataSourceConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" True) (C1 (MetaCons "LambdaDataSourceConfig'" PrefixI True) (S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Data LogConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show LogConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic LogConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep LogConfig :: Type -> Type #

Hashable LogConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

ToJSON LogConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

FromJSON LogConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData LogConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

rnf :: LogConfig -> () #

type Rep LogConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep LogConfig = D1 (MetaData "LogConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "LogConfig'" PrefixI True) (S1 (MetaSel (Just "_lcFieldLogLevel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldLogLevel) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Data OpenIdConnectConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show OpenIdConnectConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic OpenIdConnectConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep OpenIdConnectConfig :: Type -> Type #

Hashable OpenIdConnectConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

ToJSON OpenIdConnectConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

FromJSON OpenIdConnectConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData OpenIdConnectConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

rnf :: OpenIdConnectConfig -> () #

type Rep OpenIdConnectConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep OpenIdConnectConfig = D1 (MetaData "OpenIdConnectConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "OpenIdConnectConfig'" PrefixI True) ((S1 (MetaSel (Just "_oiccAuthTTL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "_oiccClientId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_oiccIatTTL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Data Resolver Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show Resolver Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic Resolver Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep Resolver :: Type -> Type #

Methods

from :: Resolver -> Rep Resolver x #

to :: Rep Resolver x -> Resolver #

Hashable Resolver Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

hashWithSalt :: Int -> Resolver -> Int #

hash :: Resolver -> Int #

FromJSON Resolver Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData Resolver Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

rnf :: Resolver -> () #

type Rep Resolver Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep Resolver = D1 (MetaData "Resolver" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "Resolver'" PrefixI True) ((S1 (MetaSel (Just "_rTypeName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rDataSourceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rRequestMappingTemplate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_rResolverARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rResponseMappingTemplate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

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

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

Data Type Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show Type Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Hashable Type Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

hashWithSalt :: Int -> Type -> Int #

hash :: Type -> Int #

FromJSON Type Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData Type Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

rnf :: Type -> () #

type Rep Type Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Data UserPoolConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

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 # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Show UserPoolConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Generic UserPoolConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Associated Types

type Rep UserPoolConfig :: Type -> Type #

Hashable UserPoolConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

ToJSON UserPoolConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

FromJSON UserPoolConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

NFData UserPoolConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

Methods

rnf :: UserPoolConfig -> () #

type Rep UserPoolConfig Source # 
Instance details

Defined in Network.AWS.AppSync.Types.Product

type Rep UserPoolConfig = D1 (MetaData "UserPoolConfig" "Network.AWS.AppSync.Types.Product" "amazonka-appsync-1.6.1-4DHxIkxAhvS86OTagCP3cH" False) (C1 (MetaCons "UserPoolConfig'" PrefixI True) ((S1 (MetaSel (Just "_upcAppIdClientRegex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_upcUserPoolId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "_upcAwsRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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.