gogol-datastore-0.1.0: Google Cloud Datastore SDK.

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

Network.Google.Datastore.Types

Contents

Description

 

Synopsis

Service Configuration

datastoreService :: ServiceConfig Source #

Default request referring to version v1beta3 of the Google Cloud Datastore API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

cloudPlatformScope :: Proxy '["https://www.googleapis.com/auth/cloud-platform"] Source #

View and manage your data across Google Cloud Platform services

datastoreScope :: Proxy '["https://www.googleapis.com/auth/datastore"] Source #

View and manage your Google Cloud Datastore data

LatLng

data LatLng Source #

An object representing a latitude/longitude pair. This is expressed as a pair of doubles representing degrees latitude and degrees longitude. Unless specified otherwise, this must conform to the WGS84 standard. Values must be within normalized ranges. Example of normalization code in Python: def NormalizeLongitude(longitude): """Wraps decimal degrees longitude to [-180.0, 180.0].""" q, r = divmod(longitude, 360.0) if r > 180.0 or (r == 180.0 and q <= -1.0): return r - 360.0 return r def NormalizeLatLng(latitude, longitude): """Wraps decimal degrees latitude and longitude to [-180.0, 180.0] and [-90.0, 90.0], respectively.""" r = latitude % 360.0 if r <= 90.0: return r, NormalizeLongitude(longitude) elif r >= 270.0: return r - 360, NormalizeLongitude(longitude) else: return 180 - r, NormalizeLongitude(longitude + 180.0) assert 180.0 == NormalizeLongitude(180.0) assert -180.0 == NormalizeLongitude(-180.0) assert -179.0 == NormalizeLongitude(181.0) assert (0.0, 0.0) == NormalizeLatLng(360.0, 0.0) assert (0.0, 0.0) == NormalizeLatLng(-360.0, 0.0) assert (85.0, 180.0) == NormalizeLatLng(95.0, 0.0) assert (-85.0, -170.0) == NormalizeLatLng(-95.0, 10.0) assert (90.0, 10.0) == NormalizeLatLng(90.0, 10.0) assert (-90.0, -10.0) == NormalizeLatLng(-90.0, -10.0) assert (0.0, -170.0) == NormalizeLatLng(-180.0, 10.0) assert (0.0, -170.0) == NormalizeLatLng(180.0, 10.0) assert (-90.0, 10.0) == NormalizeLatLng(270.0, 10.0) assert (90.0, 10.0) == NormalizeLatLng(-270.0, 10.0)

See: latLng smart constructor.

Instances

Eq LatLng Source # 

Methods

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

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

Data LatLng Source # 

Methods

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

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

toConstr :: LatLng -> Constr #

dataTypeOf :: LatLng -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LatLng Source # 
Generic LatLng Source # 

Associated Types

type Rep LatLng :: * -> * #

Methods

from :: LatLng -> Rep LatLng x #

to :: Rep LatLng x -> LatLng #

FromJSON LatLng Source # 
ToJSON LatLng Source # 
type Rep LatLng Source # 
type Rep LatLng = D1 (MetaData "LatLng" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "LatLng'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_llLatitude") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_llLongitude") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))))

latLng :: LatLng Source #

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

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

llLatitude :: Lens' LatLng (Maybe Double) Source #

The latitude in degrees. It must be in the range [-90.0, +90.0].

llLongitude :: Lens' LatLng (Maybe Double) Source #

The longitude in degrees. It must be in the range [-180.0, +180.0].

PropertyOrderDirection

data PropertyOrderDirection Source #

The direction to order by. Defaults to `ASCENDING`.

Constructors

DirectionUnspecified

DIRECTION_UNSPECIFIED Unspecified. This value must not be used.

Ascending

ASCENDING Ascending.

Descending

DESCENDING Descending.

Instances

Enum PropertyOrderDirection Source # 
Eq PropertyOrderDirection Source # 
Data PropertyOrderDirection Source # 

Methods

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

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

toConstr :: PropertyOrderDirection -> Constr #

dataTypeOf :: PropertyOrderDirection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PropertyOrderDirection Source # 
Read PropertyOrderDirection Source # 
Show PropertyOrderDirection Source # 
Generic PropertyOrderDirection Source # 
Hashable PropertyOrderDirection Source # 
FromJSON PropertyOrderDirection Source # 
ToJSON PropertyOrderDirection Source # 
FromHttpApiData PropertyOrderDirection Source # 
ToHttpApiData PropertyOrderDirection Source # 
type Rep PropertyOrderDirection Source # 
type Rep PropertyOrderDirection = D1 (MetaData "PropertyOrderDirection" "Network.Google.Datastore.Types.Sum" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) ((:+:) (C1 (MetaCons "DirectionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ascending" PrefixI False) U1) (C1 (MetaCons "Descending" PrefixI False) U1)))

RollbackRequest

data RollbackRequest Source #

The request for google.datastore.v1beta3.Datastore.Rollback.

See: rollbackRequest smart constructor.

Instances

Eq RollbackRequest Source # 
Data RollbackRequest Source # 

Methods

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

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

toConstr :: RollbackRequest -> Constr #

dataTypeOf :: RollbackRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RollbackRequest Source # 
Generic RollbackRequest Source # 
FromJSON RollbackRequest Source # 
ToJSON RollbackRequest Source # 
type Rep RollbackRequest Source # 
type Rep RollbackRequest = D1 (MetaData "RollbackRequest" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "RollbackRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_rrTransaction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Base64))))

rollbackRequest :: RollbackRequest Source #

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

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

rrTransaction :: Lens' RollbackRequest (Maybe ByteString) Source #

The transaction identifier, returned by a call to google.datastore.v1beta3.Datastore.BeginTransaction.

PartitionId

data PartitionId Source #

A partition ID identifies a grouping of entities. The grouping is always by project and namespace, however the namespace ID may be empty. A partition ID contains several dimensions: project ID and namespace ID. Partition dimensions: - May be `""`. - Must be valid UTF-8 bytes. - Must have values that match regex `[A-Za-z\d\.\-_]{1,100}` If the value of any dimension matches regex `.*`, the partition is reserved/read-only. A reserved/read-only partition ID is forbidden in certain documented contexts. Foreign partition IDs (in which the project ID does not match the context project ID ) are discouraged. Reads and writes of foreign partition IDs may fail if the project is not in an active state.

See: partitionId smart constructor.

Instances

Eq PartitionId Source # 
Data PartitionId Source # 

Methods

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

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

toConstr :: PartitionId -> Constr #

dataTypeOf :: PartitionId -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PartitionId Source # 
Generic PartitionId Source # 

Associated Types

type Rep PartitionId :: * -> * #

FromJSON PartitionId Source # 
ToJSON PartitionId Source # 
type Rep PartitionId Source # 
type Rep PartitionId = D1 (MetaData "PartitionId" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "PartitionId'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_piNamespaceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_piProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

partitionId :: PartitionId Source #

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

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

piNamespaceId :: Lens' PartitionId (Maybe Text) Source #

If not empty, the ID of the namespace to which the entities belong.

piProjectId :: Lens' PartitionId (Maybe Text) Source #

The ID of the project to which the entities belong.

QueryResultBatch

data QueryResultBatch Source #

A batch of results produced by a query.

See: queryResultBatch smart constructor.

Instances

Eq QueryResultBatch Source # 
Data QueryResultBatch Source # 

Methods

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

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

toConstr :: QueryResultBatch -> Constr #

dataTypeOf :: QueryResultBatch -> DataType #

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

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

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

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

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

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

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

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

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

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

Show QueryResultBatch Source # 
Generic QueryResultBatch Source # 
FromJSON QueryResultBatch Source # 
ToJSON QueryResultBatch Source # 
type Rep QueryResultBatch Source # 

queryResultBatch :: QueryResultBatch Source #

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

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

qrbSkippedResults :: Lens' QueryResultBatch (Maybe Int32) Source #

The number of results skipped, typically because of an offset.

qrbSkippedCursor :: Lens' QueryResultBatch (Maybe ByteString) Source #

A cursor that points to the position after the last skipped result. Will be set when `skipped_results` != 0.

qrbEntityResultType :: Lens' QueryResultBatch (Maybe QueryResultBatchEntityResultType) Source #

The result type for every entity in `entity_results`.

qrbMoreResults :: Lens' QueryResultBatch (Maybe QueryResultBatchMoreResults) Source #

The state of the query after the current batch.

qrbEndCursor :: Lens' QueryResultBatch (Maybe ByteString) Source #

A cursor that points to the position after the last result in the batch.

CompositeFilterOp

data CompositeFilterOp Source #

The operator for combining multiple filters.

Constructors

OperatorUnspecified

OPERATOR_UNSPECIFIED Unspecified. This value must not be used.

And

AND The results are required to satisfy each of the combined filters.

Instances

Enum CompositeFilterOp Source # 
Eq CompositeFilterOp Source # 
Data CompositeFilterOp Source # 

Methods

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

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

toConstr :: CompositeFilterOp -> Constr #

dataTypeOf :: CompositeFilterOp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CompositeFilterOp Source # 
Read CompositeFilterOp Source # 
Show CompositeFilterOp Source # 
Generic CompositeFilterOp Source # 
Hashable CompositeFilterOp Source # 
FromJSON CompositeFilterOp Source # 
ToJSON CompositeFilterOp Source # 
FromHttpApiData CompositeFilterOp Source # 
ToHttpApiData CompositeFilterOp Source # 
type Rep CompositeFilterOp Source # 
type Rep CompositeFilterOp = D1 (MetaData "CompositeFilterOp" "Network.Google.Datastore.Types.Sum" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) ((:+:) (C1 (MetaCons "OperatorUnspecified" PrefixI False) U1) (C1 (MetaCons "And" PrefixI False) U1))

EntityProperties

data EntityProperties Source #

The entity's properties. The map's keys are property names. A property name matching regex `.*` is reserved. A reserved property name is forbidden in certain documented contexts. The name must not contain more than 500 characters. The name cannot be `""`.

See: entityProperties smart constructor.

Instances

Eq EntityProperties Source # 
Data EntityProperties Source # 

Methods

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

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

toConstr :: EntityProperties -> Constr #

dataTypeOf :: EntityProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Show EntityProperties Source # 
Generic EntityProperties Source # 
FromJSON EntityProperties Source # 
ToJSON EntityProperties Source # 
type Rep EntityProperties Source # 
type Rep EntityProperties = D1 (MetaData "EntityProperties" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "EntityProperties'" PrefixI True) (S1 (MetaSel (Just Symbol "_epAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Value))))

entityProperties Source #

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

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

BeginTransactionRequest

data BeginTransactionRequest Source #

The request for google.datastore.v1beta3.Datastore.BeginTransaction.

See: beginTransactionRequest smart constructor.

Instances

Eq BeginTransactionRequest Source # 
Data BeginTransactionRequest Source # 

Methods

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

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

toConstr :: BeginTransactionRequest -> Constr #

dataTypeOf :: BeginTransactionRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BeginTransactionRequest Source # 
Generic BeginTransactionRequest Source # 
FromJSON BeginTransactionRequest Source # 
ToJSON BeginTransactionRequest Source # 
type Rep BeginTransactionRequest Source # 
type Rep BeginTransactionRequest = D1 (MetaData "BeginTransactionRequest" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "BeginTransactionRequest'" PrefixI False) U1)

beginTransactionRequest :: BeginTransactionRequest Source #

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

RunQueryRequest

data RunQueryRequest Source #

The request for google.datastore.v1beta3.Datastore.RunQuery.

See: runQueryRequest smart constructor.

Instances

Eq RunQueryRequest Source # 
Data RunQueryRequest Source # 

Methods

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

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

toConstr :: RunQueryRequest -> Constr #

dataTypeOf :: RunQueryRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RunQueryRequest Source # 
Generic RunQueryRequest Source # 
FromJSON RunQueryRequest Source # 
ToJSON RunQueryRequest Source # 
type Rep RunQueryRequest Source # 
type Rep RunQueryRequest = D1 (MetaData "RunQueryRequest" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "RunQueryRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rqrPartitionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartitionId))) (S1 (MetaSel (Just Symbol "_rqrGqlQuery") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GqlQuery)))) ((:*:) (S1 (MetaSel (Just Symbol "_rqrQuery") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Query))) (S1 (MetaSel (Just Symbol "_rqrReadOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReadOptions))))))

runQueryRequest :: RunQueryRequest Source #

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

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

rqrPartitionId :: Lens' RunQueryRequest (Maybe PartitionId) Source #

Entities are partitioned into subsets, identified by a partition ID. Queries are scoped to a single partition. This partition ID is normalized with the standard default context partition ID.

rqrReadOptions :: Lens' RunQueryRequest (Maybe ReadOptions) Source #

The options for this query.

AllocateIdsRequest

data AllocateIdsRequest Source #

The request for google.datastore.v1beta3.Datastore.AllocateIds.

See: allocateIdsRequest smart constructor.

Instances

Eq AllocateIdsRequest Source # 
Data AllocateIdsRequest Source # 

Methods

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

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

toConstr :: AllocateIdsRequest -> Constr #

dataTypeOf :: AllocateIdsRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AllocateIdsRequest Source # 
Generic AllocateIdsRequest Source # 
FromJSON AllocateIdsRequest Source # 
ToJSON AllocateIdsRequest Source # 
type Rep AllocateIdsRequest Source # 
type Rep AllocateIdsRequest = D1 (MetaData "AllocateIdsRequest" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "AllocateIdsRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_airKeys") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Key]))))

allocateIdsRequest :: AllocateIdsRequest Source #

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

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

airKeys :: Lens' AllocateIdsRequest [Key] Source #

A list of keys with incomplete key paths for which to allocate IDs. No key may be reserved/read-only.

QueryResultBatchEntityResultType

data QueryResultBatchEntityResultType Source #

The result type for every entity in `entity_results`.

Constructors

QRBERTResultTypeUnspecified

RESULT_TYPE_UNSPECIFIED Unspecified. This value is never used.

QRBERTFull

FULL The key and properties.

QRBERTProjection

PROJECTION A projected subset of properties. The entity may have no key.

QRBERTKeyOnly

KEY_ONLY Only the key.

Instances

Enum QueryResultBatchEntityResultType Source # 
Eq QueryResultBatchEntityResultType Source # 
Data QueryResultBatchEntityResultType Source # 

Methods

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

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

toConstr :: QueryResultBatchEntityResultType -> Constr #

dataTypeOf :: QueryResultBatchEntityResultType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord QueryResultBatchEntityResultType Source # 
Read QueryResultBatchEntityResultType Source # 
Show QueryResultBatchEntityResultType Source # 
Generic QueryResultBatchEntityResultType Source # 
Hashable QueryResultBatchEntityResultType Source # 
FromJSON QueryResultBatchEntityResultType Source # 
ToJSON QueryResultBatchEntityResultType Source # 
FromHttpApiData QueryResultBatchEntityResultType Source # 
ToHttpApiData QueryResultBatchEntityResultType Source # 
type Rep QueryResultBatchEntityResultType Source # 
type Rep QueryResultBatchEntityResultType = D1 (MetaData "QueryResultBatchEntityResultType" "Network.Google.Datastore.Types.Sum" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) ((:+:) ((:+:) (C1 (MetaCons "QRBERTResultTypeUnspecified" PrefixI False) U1) (C1 (MetaCons "QRBERTFull" PrefixI False) U1)) ((:+:) (C1 (MetaCons "QRBERTProjection" PrefixI False) U1) (C1 (MetaCons "QRBERTKeyOnly" PrefixI False) U1)))

CompositeFilter

data CompositeFilter Source #

A filter that merges multiple other filters using the given operator.

See: compositeFilter smart constructor.

Instances

Eq CompositeFilter Source # 
Data CompositeFilter Source # 

Methods

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

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

toConstr :: CompositeFilter -> Constr #

dataTypeOf :: CompositeFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CompositeFilter Source # 
Generic CompositeFilter Source # 
FromJSON CompositeFilter Source # 
ToJSON CompositeFilter Source # 
type Rep CompositeFilter Source # 
type Rep CompositeFilter = D1 (MetaData "CompositeFilter" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "CompositeFilter'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cfOp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CompositeFilterOp))) (S1 (MetaSel (Just Symbol "_cfFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Filter])))))

compositeFilter :: CompositeFilter Source #

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

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

cfOp :: Lens' CompositeFilter (Maybe CompositeFilterOp) Source #

The operator for combining multiple filters.

cfFilters :: Lens' CompositeFilter [Filter] Source #

The list of filters to combine. Must contain at least one filter.

QueryResultBatchMoreResults

data QueryResultBatchMoreResults Source #

The state of the query after the current batch.

Constructors

MoreResultsTypeUnspecified

MORE_RESULTS_TYPE_UNSPECIFIED Unspecified. This value is never used.

NotFinished

NOT_FINISHED There may be additional batches to fetch from this query.

MoreResultsAfterLimit

MORE_RESULTS_AFTER_LIMIT The query is finished, but there may be more results after the limit.

MoreResultsAfterCursor

MORE_RESULTS_AFTER_CURSOR The query is finished, but there may be more results after the end cursor.

NoMoreResults

NO_MORE_RESULTS The query has been exhausted.

Instances

Enum QueryResultBatchMoreResults Source # 
Eq QueryResultBatchMoreResults Source # 
Data QueryResultBatchMoreResults Source # 

Methods

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

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

toConstr :: QueryResultBatchMoreResults -> Constr #

dataTypeOf :: QueryResultBatchMoreResults -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord QueryResultBatchMoreResults Source # 
Read QueryResultBatchMoreResults Source # 
Show QueryResultBatchMoreResults Source # 
Generic QueryResultBatchMoreResults Source # 
Hashable QueryResultBatchMoreResults Source # 
FromJSON QueryResultBatchMoreResults Source # 
ToJSON QueryResultBatchMoreResults Source # 
FromHttpApiData QueryResultBatchMoreResults Source # 
ToHttpApiData QueryResultBatchMoreResults Source # 
type Rep QueryResultBatchMoreResults Source # 
type Rep QueryResultBatchMoreResults = D1 (MetaData "QueryResultBatchMoreResults" "Network.Google.Datastore.Types.Sum" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) ((:+:) ((:+:) (C1 (MetaCons "MoreResultsTypeUnspecified" PrefixI False) U1) (C1 (MetaCons "NotFinished" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MoreResultsAfterLimit" PrefixI False) U1) ((:+:) (C1 (MetaCons "MoreResultsAfterCursor" PrefixI False) U1) (C1 (MetaCons "NoMoreResults" PrefixI False) U1))))

BeginTransactionResponse

data BeginTransactionResponse Source #

The response for google.datastore.v1beta3.Datastore.BeginTransaction.

See: beginTransactionResponse smart constructor.

Instances

Eq BeginTransactionResponse Source # 
Data BeginTransactionResponse Source # 

Methods

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

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

toConstr :: BeginTransactionResponse -> Constr #

dataTypeOf :: BeginTransactionResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BeginTransactionResponse Source # 
Generic BeginTransactionResponse Source # 
FromJSON BeginTransactionResponse Source # 
ToJSON BeginTransactionResponse Source # 
type Rep BeginTransactionResponse Source # 
type Rep BeginTransactionResponse = D1 (MetaData "BeginTransactionResponse" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "BeginTransactionResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_btrTransaction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Base64))))

beginTransactionResponse :: BeginTransactionResponse Source #

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

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

btrTransaction :: Lens' BeginTransactionResponse (Maybe ByteString) Source #

The transaction identifier (always present).

MutationResult

data MutationResult Source #

The result of applying a mutation.

See: mutationResult smart constructor.

Instances

Eq MutationResult Source # 
Data MutationResult Source # 

Methods

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

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

toConstr :: MutationResult -> Constr #

dataTypeOf :: MutationResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MutationResult Source # 
Generic MutationResult Source # 

Associated Types

type Rep MutationResult :: * -> * #

FromJSON MutationResult Source # 
ToJSON MutationResult Source # 
type Rep MutationResult Source # 
type Rep MutationResult = D1 (MetaData "MutationResult" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "MutationResult'" PrefixI True) (S1 (MetaSel (Just Symbol "_mrKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Key))))

mutationResult :: MutationResult Source #

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

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

mrKey :: Lens' MutationResult (Maybe Key) Source #

The automatically allocated key. Set only when the mutation allocated a key.

AllocateIdsResponse

data AllocateIdsResponse Source #

The response for google.datastore.v1beta3.Datastore.AllocateIds.

See: allocateIdsResponse smart constructor.

Instances

Eq AllocateIdsResponse Source # 
Data AllocateIdsResponse Source # 

Methods

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

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

toConstr :: AllocateIdsResponse -> Constr #

dataTypeOf :: AllocateIdsResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AllocateIdsResponse Source # 
Generic AllocateIdsResponse Source # 
FromJSON AllocateIdsResponse Source # 
ToJSON AllocateIdsResponse Source # 
type Rep AllocateIdsResponse Source # 
type Rep AllocateIdsResponse = D1 (MetaData "AllocateIdsResponse" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "AllocateIdsResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_aKeys") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Key]))))

allocateIdsResponse :: AllocateIdsResponse Source #

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

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

aKeys :: Lens' AllocateIdsResponse [Key] Source #

The keys specified in the request (in the same order), each with its key path completed with a newly allocated ID.

GqlQuery

data GqlQuery Source #

A GQL query.

See: gqlQuery smart constructor.

Instances

Eq GqlQuery Source # 
Data GqlQuery Source # 

Methods

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

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

toConstr :: GqlQuery -> Constr #

dataTypeOf :: GqlQuery -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GqlQuery Source # 
Generic GqlQuery Source # 

Associated Types

type Rep GqlQuery :: * -> * #

Methods

from :: GqlQuery -> Rep GqlQuery x #

to :: Rep GqlQuery x -> GqlQuery #

FromJSON GqlQuery Source # 
ToJSON GqlQuery Source # 
type Rep GqlQuery Source # 
type Rep GqlQuery = D1 (MetaData "GqlQuery" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "GqlQuery'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gqPositionalBindings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [GqlQueryParameter]))) (S1 (MetaSel (Just Symbol "_gqNamedBindings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GqlQueryNamedBindings)))) ((:*:) (S1 (MetaSel (Just Symbol "_gqQueryString") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gqAllowLiterals") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

gqlQuery :: GqlQuery Source #

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

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

gqPositionalBindings :: Lens' GqlQuery [GqlQueryParameter] Source #

Numbered binding site '1 references the first numbered parameter, effectively using 1-based indexing, rather than the usual 0. For each binding site numbered i in `query_string`, there must be an i-th numbered parameter. The inverse must also be true.

gqNamedBindings :: Lens' GqlQuery (Maybe GqlQueryNamedBindings) Source #

For each non-reserved named binding site in the query string, there must be a named parameter with that name, but not necessarily the inverse. Key must match regex `A-Za-z_$*`, must not match regex `.*`, and must not be `""`.

gqQueryString :: Lens' GqlQuery (Maybe Text) Source #

A string of the format described here.

gqAllowLiterals :: Lens' GqlQuery (Maybe Bool) Source #

When false, the query string must not contain any literals and instead must bind all values. For example, `SELECT * FROM Kind WHERE a = 'string literal'` is not allowed, while `SELECT * FROM Kind WHERE a = 'value` is.

RunQueryResponse

data RunQueryResponse Source #

The response for google.datastore.v1beta3.Datastore.RunQuery.

See: runQueryResponse smart constructor.

Instances

Eq RunQueryResponse Source # 
Data RunQueryResponse Source # 

Methods

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

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

toConstr :: RunQueryResponse -> Constr #

dataTypeOf :: RunQueryResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RunQueryResponse Source # 
Generic RunQueryResponse Source # 
FromJSON RunQueryResponse Source # 
ToJSON RunQueryResponse Source # 
type Rep RunQueryResponse Source # 
type Rep RunQueryResponse = D1 (MetaData "RunQueryResponse" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "RunQueryResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rBatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe QueryResultBatch))) (S1 (MetaSel (Just Symbol "_rQuery") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Query)))))

runQueryResponse :: RunQueryResponse Source #

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

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

rBatch :: Lens' RunQueryResponse (Maybe QueryResultBatch) Source #

A batch of query results (always present).

rQuery :: Lens' RunQueryResponse (Maybe Query) Source #

The parsed form of the `GqlQuery` from the request, if it was set.

Value

data Value Source #

A message that can hold any of the supported value types and associated metadata.

See: value smart constructor.

Instances

Eq Value Source # 

Methods

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

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

Data Value Source # 

Methods

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

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

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Value Source # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 

Associated Types

type Rep Value :: * -> * #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

FromJSON Value Source # 
ToJSON Value Source # 
type Rep Value Source # 
type Rep Value = D1 (MetaData "Value" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "Value'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_vKeyValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Key))) ((:*:) (S1 (MetaSel (Just Symbol "_vGeoPointValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LatLng))) (S1 (MetaSel (Just Symbol "_vIntegerValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) (S1 (MetaSel (Just Symbol "_vTimestampValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) ((:*:) (S1 (MetaSel (Just Symbol "_vEntityValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Entity))) (S1 (MetaSel (Just Symbol "_vExcludeFromIndexes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_vDoubleValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) ((:*:) (S1 (MetaSel (Just Symbol "_vStringValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_vBooleanValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_vMeaning") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_vArrayValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ArrayValue)))) ((:*:) (S1 (MetaSel (Just Symbol "_vNullValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ValueNullValue))) (S1 (MetaSel (Just Symbol "_vBlobValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Base64))))))))

value :: Value Source #

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

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

vKeyValue :: Lens' Value (Maybe Key) Source #

A key value.

vGeoPointValue :: Lens' Value (Maybe LatLng) Source #

A geo point value representing a point on the surface of Earth.

vIntegerValue :: Lens' Value (Maybe Int64) Source #

An integer value.

vTimestampValue :: Lens' Value (Maybe UTCTime) Source #

A timestamp value. When stored in the Datastore, precise only to microseconds; any additional precision is rounded down.

vEntityValue :: Lens' Value (Maybe Entity) Source #

An entity value. - May have no key. - May have a key with an incomplete key path. - May have a reserved/read-only key.

vExcludeFromIndexes :: Lens' Value (Maybe Bool) Source #

If the value should be excluded from all indexes including those defined explicitly.

vStringValue :: Lens' Value (Maybe Text) Source #

A UTF-8 encoded string value. When `exclude_from_indexes` is false (it is indexed) , may have at most 1500 bytes. Otherwise, may be set to at least 1,000,000 bytes.

vBooleanValue :: Lens' Value (Maybe Bool) Source #

A boolean value.

vMeaning :: Lens' Value (Maybe Int32) Source #

The `meaning` field should only be populated for backwards compatibility.

vArrayValue :: Lens' Value (Maybe ArrayValue) Source #

An array value. Cannot contain another array value. A `Value` instance that sets field `array_value` must not set fields `meaning` or `exclude_from_indexes`.

vBlobValue :: Lens' Value (Maybe ByteString) Source #

A blob value. May have at most 1,000,000 bytes. When `exclude_from_indexes` is false, may have at most 1500 bytes. In JSON requests, must be base64-encoded.

ValueNullValue

data ValueNullValue Source #

A null value.

Constructors

NullValue

NULL_VALUE Null value.

Instances

Enum ValueNullValue Source # 
Eq ValueNullValue Source # 
Data ValueNullValue Source # 

Methods

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

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

toConstr :: ValueNullValue -> Constr #

dataTypeOf :: ValueNullValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ValueNullValue Source # 
Read ValueNullValue Source # 
Show ValueNullValue Source # 
Generic ValueNullValue Source # 

Associated Types

type Rep ValueNullValue :: * -> * #

Hashable ValueNullValue Source # 
FromJSON ValueNullValue Source # 
ToJSON ValueNullValue Source # 
FromHttpApiData ValueNullValue Source # 
ToHttpApiData ValueNullValue Source # 
type Rep ValueNullValue Source # 
type Rep ValueNullValue = D1 (MetaData "ValueNullValue" "Network.Google.Datastore.Types.Sum" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "NullValue" PrefixI False) U1)

LookupRequest

data LookupRequest Source #

The request for google.datastore.v1beta3.Datastore.Lookup.

See: lookupRequest smart constructor.

Instances

Eq LookupRequest Source # 
Data LookupRequest Source # 

Methods

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

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

toConstr :: LookupRequest -> Constr #

dataTypeOf :: LookupRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LookupRequest Source # 
Generic LookupRequest Source # 

Associated Types

type Rep LookupRequest :: * -> * #

FromJSON LookupRequest Source # 
ToJSON LookupRequest Source # 
type Rep LookupRequest Source # 
type Rep LookupRequest = D1 (MetaData "LookupRequest" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "LookupRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_lrKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Key]))) (S1 (MetaSel (Just Symbol "_lrReadOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReadOptions)))))

lookupRequest :: LookupRequest Source #

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

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

lrKeys :: Lens' LookupRequest [Key] Source #

Keys of entities to look up.

lrReadOptions :: Lens' LookupRequest (Maybe ReadOptions) Source #

The options for this lookup request.

ReadOptionsReadConsistency

data ReadOptionsReadConsistency Source #

The non-transactional read consistency to use. Cannot be set to `STRONG` for global queries.

Constructors

ReadConsistencyUnspecified

READ_CONSISTENCY_UNSPECIFIED Unspecified. This value must not be used.

Strong

STRONG Strong consistency.

Eventual

EVENTUAL Eventual consistency.

Instances

Enum ReadOptionsReadConsistency Source # 
Eq ReadOptionsReadConsistency Source # 
Data ReadOptionsReadConsistency Source # 

Methods

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

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

toConstr :: ReadOptionsReadConsistency -> Constr #

dataTypeOf :: ReadOptionsReadConsistency -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReadOptionsReadConsistency Source # 
Read ReadOptionsReadConsistency Source # 
Show ReadOptionsReadConsistency Source # 
Generic ReadOptionsReadConsistency Source # 
Hashable ReadOptionsReadConsistency Source # 
FromJSON ReadOptionsReadConsistency Source # 
ToJSON ReadOptionsReadConsistency Source # 
FromHttpApiData ReadOptionsReadConsistency Source # 
ToHttpApiData ReadOptionsReadConsistency Source # 
type Rep ReadOptionsReadConsistency Source # 
type Rep ReadOptionsReadConsistency = D1 (MetaData "ReadOptionsReadConsistency" "Network.Google.Datastore.Types.Sum" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) ((:+:) (C1 (MetaCons "ReadConsistencyUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Strong" PrefixI False) U1) (C1 (MetaCons "Eventual" PrefixI False) U1)))

Mutation

data Mutation Source #

A mutation to apply to an entity.

See: mutation smart constructor.

Instances

Eq Mutation Source # 
Data Mutation Source # 

Methods

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

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

toConstr :: Mutation -> Constr #

dataTypeOf :: Mutation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Mutation Source # 
Generic Mutation Source # 

Associated Types

type Rep Mutation :: * -> * #

Methods

from :: Mutation -> Rep Mutation x #

to :: Rep Mutation x -> Mutation #

FromJSON Mutation Source # 
ToJSON Mutation Source # 
type Rep Mutation Source # 
type Rep Mutation = D1 (MetaData "Mutation" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "Mutation'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mInsert") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Entity))) (S1 (MetaSel (Just Symbol "_mUpsert") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Entity)))) ((:*:) (S1 (MetaSel (Just Symbol "_mDelete") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Key))) (S1 (MetaSel (Just Symbol "_mUpdate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Entity))))))

mutation :: Mutation Source #

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

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

mInsert :: Lens' Mutation (Maybe Entity) Source #

The entity to insert. The entity must not already exist. The entity key's final path element may be incomplete.

mUpsert :: Lens' Mutation (Maybe Entity) Source #

The entity to upsert. The entity may or may not already exist. The entity key's final path element may be incomplete.

mDelete :: Lens' Mutation (Maybe Key) Source #

The key of the entity to delete. The entity may or may not already exist. Must have a complete key path and must not be reserved/read-only.

mUpdate :: Lens' Mutation (Maybe Entity) Source #

The entity to update. The entity must already exist. Must have a complete key path.

GqlQueryNamedBindings

data GqlQueryNamedBindings Source #

For each non-reserved named binding site in the query string, there must be a named parameter with that name, but not necessarily the inverse. Key must match regex `A-Za-z_$*`, must not match regex `.*`, and must not be `""`.

See: gqlQueryNamedBindings smart constructor.

Instances

Eq GqlQueryNamedBindings Source # 
Data GqlQueryNamedBindings Source # 

Methods

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

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

toConstr :: GqlQueryNamedBindings -> Constr #

dataTypeOf :: GqlQueryNamedBindings -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GqlQueryNamedBindings Source # 
Generic GqlQueryNamedBindings Source # 
FromJSON GqlQueryNamedBindings Source # 
ToJSON GqlQueryNamedBindings Source # 
type Rep GqlQueryNamedBindings Source # 
type Rep GqlQueryNamedBindings = D1 (MetaData "GqlQueryNamedBindings" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "GqlQueryNamedBindings'" PrefixI True) (S1 (MetaSel (Just Symbol "_gqnbAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text GqlQueryParameter))))

gqlQueryNamedBindings Source #

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

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

PropertyReference

data PropertyReference Source #

A reference to a property relative to the kind expressions.

See: propertyReference smart constructor.

Instances

Eq PropertyReference Source # 
Data PropertyReference Source # 

Methods

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

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

toConstr :: PropertyReference -> Constr #

dataTypeOf :: PropertyReference -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PropertyReference Source # 
Generic PropertyReference Source # 
FromJSON PropertyReference Source # 
ToJSON PropertyReference Source # 
type Rep PropertyReference Source # 
type Rep PropertyReference = D1 (MetaData "PropertyReference" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "PropertyReference'" PrefixI True) (S1 (MetaSel (Just Symbol "_prName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

propertyReference :: PropertyReference Source #

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

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

prName :: Lens' PropertyReference (Maybe Text) Source #

The name of the property. If name includes "."s, it may be interpreted as a property name path.

Key

data Key Source #

A unique identifier for an entity. If a key's partition ID or any of its path kinds or names are reserved/read-only, the key is reserved/read-only. A reserved/read-only key is forbidden in certain documented contexts.

See: key smart constructor.

Instances

Eq Key Source # 

Methods

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

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

Data Key Source # 

Methods

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

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

toConstr :: Key -> Constr #

dataTypeOf :: Key -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

FromJSON Key Source # 
ToJSON Key Source # 
type Rep Key Source # 
type Rep Key = D1 (MetaData "Key" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "Key'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_kPartitionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartitionId))) (S1 (MetaSel (Just Symbol "_kPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PathElement])))))

key :: Key Source #

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

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

kPartitionId :: Lens' Key (Maybe PartitionId) Source #

Entities are partitioned into subsets, currently identified by a project ID and namespace ID. Queries are scoped to a single partition.

kPath :: Lens' Key [PathElement] Source #

The entity path. An entity path consists of one or more elements composed of a kind and a string or numerical identifier, which identify entities. The first element identifies a _root entity_, the second element identifies a _child_ of the root entity, the third element identifies a child of the second entity, and so forth. The entities identified by all prefixes of the path are called the element's _ancestors_. An entity path is always fully complete: *all* of the entity's ancestors are required to be in the path along with the entity identifier itself. The only exception is that in some documented cases, the identifier in the last path element (for the entity) itself may be omitted. For example, the last path element of the key of `Mutation.insert` may have no identifier. A path can never be empty, and a path can have at most 100 elements.

PropertyFilter

data PropertyFilter Source #

A filter on a specific property.

See: propertyFilter smart constructor.

Instances

Eq PropertyFilter Source # 
Data PropertyFilter Source # 

Methods

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

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

toConstr :: PropertyFilter -> Constr #

dataTypeOf :: PropertyFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PropertyFilter Source # 
Generic PropertyFilter Source # 

Associated Types

type Rep PropertyFilter :: * -> * #

FromJSON PropertyFilter Source # 
ToJSON PropertyFilter Source # 
type Rep PropertyFilter Source # 
type Rep PropertyFilter = D1 (MetaData "PropertyFilter" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "PropertyFilter'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pfProperty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PropertyReference))) ((:*:) (S1 (MetaSel (Just Symbol "_pfOp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PropertyFilterOp))) (S1 (MetaSel (Just Symbol "_pfValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Value))))))

propertyFilter :: PropertyFilter Source #

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

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

pfOp :: Lens' PropertyFilter (Maybe PropertyFilterOp) Source #

The operator to filter by.

pfValue :: Lens' PropertyFilter (Maybe Value) Source #

The value to compare the property to.

Query

data Query Source #

A query for entities.

See: query smart constructor.

Instances

Eq Query Source # 

Methods

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

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

Data Query Source # 

Methods

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

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

toConstr :: Query -> Constr #

dataTypeOf :: Query -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Query Source # 

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Generic Query Source # 

Associated Types

type Rep Query :: * -> * #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

FromJSON Query Source # 
ToJSON Query Source # 
type Rep Query Source # 

query :: Query Source #

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

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

qStartCursor :: Lens' Query (Maybe ByteString) Source #

A starting point for the query results. Query cursors are returned in query result batches and can only be used to continue the same query.

qOffSet :: Lens' Query (Maybe Int32) Source #

The number of results to skip. Applies before limit, but after all other constraints. Optional. Must be >= 0 if specified.

qKind :: Lens' Query [KindExpression] Source #

The kinds to query (if empty, returns entities of all kinds). Currently at most 1 kind may be specified.

qDistinctOn :: Lens' Query [PropertyReference] Source #

The properties to make distinct. The query results will contain the first result for each distinct combination of values for the given properties (if empty, all results are returned).

qEndCursor :: Lens' Query (Maybe ByteString) Source #

An ending point for the query results. Query cursors are returned in query result batches and can only be used to limit the same query.

qLimit :: Lens' Query (Maybe Int32) Source #

The maximum number of results to return. Applies after all other constraints. Optional. Unspecified is interpreted as no limit. Must be >= 0 if specified.

qProjection :: Lens' Query [Projection] Source #

The projection to return. Defaults to returning all properties.

qFilter :: Lens' Query (Maybe Filter) Source #

The filter to apply.

qOrder :: Lens' Query [PropertyOrder] Source #

The order to apply to the query results (if empty, order is unspecified).

ArrayValue

data ArrayValue Source #

An array value.

See: arrayValue smart constructor.

Instances

Eq ArrayValue Source # 
Data ArrayValue Source # 

Methods

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

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

toConstr :: ArrayValue -> Constr #

dataTypeOf :: ArrayValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ArrayValue Source # 
Generic ArrayValue Source # 

Associated Types

type Rep ArrayValue :: * -> * #

FromJSON ArrayValue Source # 
ToJSON ArrayValue Source # 
type Rep ArrayValue Source # 
type Rep ArrayValue = D1 (MetaData "ArrayValue" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "ArrayValue'" PrefixI True) (S1 (MetaSel (Just Symbol "_avValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Value]))))

arrayValue :: ArrayValue Source #

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

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

avValues :: Lens' ArrayValue [Value] Source #

Values in the array. The order of this array may not be preserved if it contains a mix of indexed and unindexed values.

EntityResult

data EntityResult Source #

The result of fetching an entity from Datastore.

See: entityResult smart constructor.

Instances

Eq EntityResult Source # 
Data EntityResult Source # 

Methods

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

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

toConstr :: EntityResult -> Constr #

dataTypeOf :: EntityResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Show EntityResult Source # 
Generic EntityResult Source # 

Associated Types

type Rep EntityResult :: * -> * #

FromJSON EntityResult Source # 
ToJSON EntityResult Source # 
type Rep EntityResult Source # 
type Rep EntityResult = D1 (MetaData "EntityResult" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "EntityResult'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_erCursor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Base64))) (S1 (MetaSel (Just Symbol "_erEntity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Entity)))))

entityResult :: EntityResult Source #

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

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

erCursor :: Lens' EntityResult (Maybe ByteString) Source #

A cursor that points to the position after the result entity. Set only when the `EntityResult` is part of a `QueryResultBatch` message.

erEntity :: Lens' EntityResult (Maybe Entity) Source #

The resulting entity.

Xgafv

data Xgafv Source #

V1 error format.

Constructors

X1

1 v1 error format

X2

2 v2 error format

Instances

Enum Xgafv Source # 
Eq Xgafv Source # 

Methods

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

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

Data Xgafv Source # 

Methods

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

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

toConstr :: Xgafv -> Constr #

dataTypeOf :: Xgafv -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Xgafv Source # 

Methods

compare :: Xgafv -> Xgafv -> Ordering #

(<) :: Xgafv -> Xgafv -> Bool #

(<=) :: Xgafv -> Xgafv -> Bool #

(>) :: Xgafv -> Xgafv -> Bool #

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

max :: Xgafv -> Xgafv -> Xgafv #

min :: Xgafv -> Xgafv -> Xgafv #

Read Xgafv Source # 
Show Xgafv Source # 

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 

Associated Types

type Rep Xgafv :: * -> * #

Methods

from :: Xgafv -> Rep Xgafv x #

to :: Rep Xgafv x -> Xgafv #

Hashable Xgafv Source # 

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

FromJSON Xgafv Source # 
ToJSON Xgafv Source # 
FromHttpApiData Xgafv Source # 
ToHttpApiData Xgafv Source # 
type Rep Xgafv Source # 
type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.Datastore.Types.Sum" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) ((:+:) (C1 (MetaCons "X1" PrefixI False) U1) (C1 (MetaCons "X2" PrefixI False) U1))

CommitResponse

data CommitResponse Source #

The response for google.datastore.v1beta3.Datastore.Commit.

See: commitResponse smart constructor.

Instances

Eq CommitResponse Source # 
Data CommitResponse Source # 

Methods

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

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

toConstr :: CommitResponse -> Constr #

dataTypeOf :: CommitResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CommitResponse Source # 
Generic CommitResponse Source # 

Associated Types

type Rep CommitResponse :: * -> * #

FromJSON CommitResponse Source # 
ToJSON CommitResponse Source # 
type Rep CommitResponse Source # 
type Rep CommitResponse = D1 (MetaData "CommitResponse" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "CommitResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_crIndexUpdates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_crMutationResults") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [MutationResult])))))

commitResponse :: CommitResponse Source #

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

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

crIndexUpdates :: Lens' CommitResponse (Maybe Int32) Source #

The number of index entries updated during the commit, or zero if none were updated.

crMutationResults :: Lens' CommitResponse [MutationResult] Source #

The result of performing the mutations. The i-th mutation result corresponds to the i-th mutation in the request.

KindExpression

data KindExpression Source #

A representation of a kind.

See: kindExpression smart constructor.

Instances

Eq KindExpression Source # 
Data KindExpression Source # 

Methods

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

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

toConstr :: KindExpression -> Constr #

dataTypeOf :: KindExpression -> DataType #

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

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

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

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

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

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

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

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

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

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

Show KindExpression Source # 
Generic KindExpression Source # 

Associated Types

type Rep KindExpression :: * -> * #

FromJSON KindExpression Source # 
ToJSON KindExpression Source # 
type Rep KindExpression Source # 
type Rep KindExpression = D1 (MetaData "KindExpression" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "KindExpression'" PrefixI True) (S1 (MetaSel (Just Symbol "_keName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

kindExpression :: KindExpression Source #

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

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

keName :: Lens' KindExpression (Maybe Text) Source #

The name of the kind.

ReadOptions

data ReadOptions Source #

The options shared by read requests.

See: readOptions smart constructor.

Instances

Eq ReadOptions Source # 
Data ReadOptions Source # 

Methods

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

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

toConstr :: ReadOptions -> Constr #

dataTypeOf :: ReadOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReadOptions Source # 
Generic ReadOptions Source # 

Associated Types

type Rep ReadOptions :: * -> * #

FromJSON ReadOptions Source # 
ToJSON ReadOptions Source # 
type Rep ReadOptions Source # 
type Rep ReadOptions = D1 (MetaData "ReadOptions" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "ReadOptions'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_roReadConsistency") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReadOptionsReadConsistency))) (S1 (MetaSel (Just Symbol "_roTransaction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Base64)))))

readOptions :: ReadOptions Source #

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

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

roReadConsistency :: Lens' ReadOptions (Maybe ReadOptionsReadConsistency) Source #

The non-transactional read consistency to use. Cannot be set to `STRONG` for global queries.

roTransaction :: Lens' ReadOptions (Maybe ByteString) Source #

The identifier of the transaction in which to read. A transaction identifier is returned by a call to BeginTransaction.

RollbackResponse

data RollbackResponse Source #

The response for google.datastore.v1beta3.Datastore.Rollback (an empty message).

See: rollbackResponse smart constructor.

Instances

Eq RollbackResponse Source # 
Data RollbackResponse Source # 

Methods

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

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

toConstr :: RollbackResponse -> Constr #

dataTypeOf :: RollbackResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RollbackResponse Source # 
Generic RollbackResponse Source # 
FromJSON RollbackResponse Source # 
ToJSON RollbackResponse Source # 
type Rep RollbackResponse Source # 
type Rep RollbackResponse = D1 (MetaData "RollbackResponse" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "RollbackResponse'" PrefixI False) U1)

rollbackResponse :: RollbackResponse Source #

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

Projection

data Projection Source #

A representation of a property in a projection.

See: projection smart constructor.

Instances

Eq Projection Source # 
Data Projection Source # 

Methods

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

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

toConstr :: Projection -> Constr #

dataTypeOf :: Projection -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Projection Source # 
Generic Projection Source # 

Associated Types

type Rep Projection :: * -> * #

FromJSON Projection Source # 
ToJSON Projection Source # 
type Rep Projection Source # 
type Rep Projection = D1 (MetaData "Projection" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" True) (C1 (MetaCons "Projection'" PrefixI True) (S1 (MetaSel (Just Symbol "_pProperty") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PropertyReference))))

projection :: Projection Source #

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

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

Filter

data Filter Source #

A holder for any type of filter.

See: filter' smart constructor.

Instances

Eq Filter Source # 

Methods

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

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

Data Filter Source # 

Methods

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

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

toConstr :: Filter -> Constr #

dataTypeOf :: Filter -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Filter Source # 
Generic Filter Source # 

Associated Types

type Rep Filter :: * -> * #

Methods

from :: Filter -> Rep Filter x #

to :: Rep Filter x -> Filter #

FromJSON Filter Source # 
ToJSON Filter Source # 
type Rep Filter Source # 
type Rep Filter = D1 (MetaData "Filter" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "Filter'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fCompositeFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CompositeFilter))) (S1 (MetaSel (Just Symbol "_fPropertyFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PropertyFilter)))))

filter' :: Filter Source #

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

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

PropertyFilterOp

data PropertyFilterOp Source #

The operator to filter by.

Constructors

PFOOperatorUnspecified

OPERATOR_UNSPECIFIED Unspecified. This value must not be used.

PFOLessThan

LESS_THAN Less than.

PFOLessThanOrEqual

LESS_THAN_OR_EQUAL Less than or equal.

PFOGreaterThan

GREATER_THAN Greater than.

PFOGreaterThanOrEqual

GREATER_THAN_OR_EQUAL Greater than or equal.

PFOEqual

EQUAL Equal.

PFOHasAncestor

HAS_ANCESTOR Has ancestor.

Instances

Enum PropertyFilterOp Source # 
Eq PropertyFilterOp Source # 
Data PropertyFilterOp Source # 

Methods

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

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

toConstr :: PropertyFilterOp -> Constr #

dataTypeOf :: PropertyFilterOp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PropertyFilterOp Source # 
Read PropertyFilterOp Source # 
Show PropertyFilterOp Source # 
Generic PropertyFilterOp Source # 
Hashable PropertyFilterOp Source # 
FromJSON PropertyFilterOp Source # 
ToJSON PropertyFilterOp Source # 
FromHttpApiData PropertyFilterOp Source # 
ToHttpApiData PropertyFilterOp Source # 
type Rep PropertyFilterOp Source # 
type Rep PropertyFilterOp = D1 (MetaData "PropertyFilterOp" "Network.Google.Datastore.Types.Sum" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) ((:+:) ((:+:) (C1 (MetaCons "PFOOperatorUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "PFOLessThan" PrefixI False) U1) (C1 (MetaCons "PFOLessThanOrEqual" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PFOGreaterThan" PrefixI False) U1) (C1 (MetaCons "PFOGreaterThanOrEqual" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PFOEqual" PrefixI False) U1) (C1 (MetaCons "PFOHasAncestor" PrefixI False) U1))))

CommitRequest

data CommitRequest Source #

The request for google.datastore.v1beta3.Datastore.Commit.

See: commitRequest smart constructor.

Instances

Eq CommitRequest Source # 
Data CommitRequest Source # 

Methods

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

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

toConstr :: CommitRequest -> Constr #

dataTypeOf :: CommitRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CommitRequest Source # 
Generic CommitRequest Source # 

Associated Types

type Rep CommitRequest :: * -> * #

FromJSON CommitRequest Source # 
ToJSON CommitRequest Source # 
type Rep CommitRequest Source # 
type Rep CommitRequest = D1 (MetaData "CommitRequest" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "CommitRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_crMutations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Mutation]))) ((:*:) (S1 (MetaSel (Just Symbol "_crMode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CommitRequestMode))) (S1 (MetaSel (Just Symbol "_crTransaction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Base64))))))

commitRequest :: CommitRequest Source #

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

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

crMutations :: Lens' CommitRequest [Mutation] Source #

The mutations to perform. When mode is `TRANSACTIONAL`, mutations affecting a single entity are applied in order. The following sequences of mutations affecting a single entity are not permitted in a single `Commit` request: - `insert` followed by `insert` - `update` followed by `insert` - `upsert` followed by `insert` - `delete` followed by `update` When mode is `NON_TRANSACTIONAL`, no two mutations may affect a single entity.

crMode :: Lens' CommitRequest (Maybe CommitRequestMode) Source #

The type of commit to perform. Defaults to `TRANSACTIONAL`.

crTransaction :: Lens' CommitRequest (Maybe ByteString) Source #

The identifier of the transaction associated with the commit. A transaction identifier is returned by a call to BeginTransaction.

CommitRequestMode

data CommitRequestMode Source #

The type of commit to perform. Defaults to `TRANSACTIONAL`.

Constructors

ModeUnspecified

MODE_UNSPECIFIED Unspecified. This value must not be used.

Transactional

TRANSACTIONAL Transactional: The mutations are either all applied, or none are applied. Learn about transactions here.

NonTransactional

NON_TRANSACTIONAL Non-transactional: The mutations may not apply as all or none.

Instances

Enum CommitRequestMode Source # 
Eq CommitRequestMode Source # 
Data CommitRequestMode Source # 

Methods

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

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

toConstr :: CommitRequestMode -> Constr #

dataTypeOf :: CommitRequestMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CommitRequestMode Source # 
Read CommitRequestMode Source # 
Show CommitRequestMode Source # 
Generic CommitRequestMode Source # 
Hashable CommitRequestMode Source # 
FromJSON CommitRequestMode Source # 
ToJSON CommitRequestMode Source # 
FromHttpApiData CommitRequestMode Source # 
ToHttpApiData CommitRequestMode Source # 
type Rep CommitRequestMode Source # 
type Rep CommitRequestMode = D1 (MetaData "CommitRequestMode" "Network.Google.Datastore.Types.Sum" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) ((:+:) (C1 (MetaCons "ModeUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Transactional" PrefixI False) U1) (C1 (MetaCons "NonTransactional" PrefixI False) U1)))

PathElement

data PathElement Source #

A (kind, ID/name) pair used to construct a key path. If either name or ID is set, the element is complete. If neither is set, the element is incomplete.

See: pathElement smart constructor.

Instances

Eq PathElement Source # 
Data PathElement Source # 

Methods

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

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

toConstr :: PathElement -> Constr #

dataTypeOf :: PathElement -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PathElement Source # 
Generic PathElement Source # 

Associated Types

type Rep PathElement :: * -> * #

FromJSON PathElement Source # 
ToJSON PathElement Source # 
type Rep PathElement Source # 
type Rep PathElement = D1 (MetaData "PathElement" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "PathElement'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_peKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_peName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_peId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

pathElement :: PathElement Source #

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

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

peKind :: Lens' PathElement (Maybe Text) Source #

The kind of the entity. A kind matching regex `.*` is reserved/read-only. A kind must not contain more than 1500 bytes when UTF-8 encoded. Cannot be `""`.

peName :: Lens' PathElement (Maybe Text) Source #

The name of the entity. A name matching regex `.*` is reserved/read-only. A name must not be more than 1500 bytes when UTF-8 encoded. Cannot be `""`.

peId :: Lens' PathElement (Maybe Int64) Source #

The auto-allocated ID of the entity. Never equal to zero. Values less than zero are discouraged and may not be supported in the future.

Entity

data Entity Source #

A Datastore data object. An entity is limited to 1 megabyte when stored. That _roughly_ corresponds to a limit of 1 megabyte for the serialized form of this message.

See: entity smart constructor.

Instances

Eq Entity Source # 

Methods

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

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

Data Entity Source # 

Methods

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

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

toConstr :: Entity -> Constr #

dataTypeOf :: Entity -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Entity Source # 
Generic Entity Source # 

Associated Types

type Rep Entity :: * -> * #

Methods

from :: Entity -> Rep Entity x #

to :: Rep Entity x -> Entity #

FromJSON Entity Source # 
ToJSON Entity Source # 
type Rep Entity Source # 
type Rep Entity = D1 (MetaData "Entity" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "Entity'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_eKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Key))) (S1 (MetaSel (Just Symbol "_eProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EntityProperties)))))

entity :: Entity Source #

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

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

eKey :: Lens' Entity (Maybe Key) Source #

The entity's key. An entity must have a key, unless otherwise documented (for example, an entity in `Value.entity_value` may have no key). An entity's kind is its key path's last element's kind, or null if it has no key.

eProperties :: Lens' Entity (Maybe EntityProperties) Source #

The entity's properties. The map's keys are property names. A property name matching regex `.*` is reserved. A reserved property name is forbidden in certain documented contexts. The name must not contain more than 500 characters. The name cannot be `""`.

LookupResponse

data LookupResponse Source #

The response for google.datastore.v1beta3.Datastore.Lookup.

See: lookupResponse smart constructor.

Instances

Eq LookupResponse Source # 
Data LookupResponse Source # 

Methods

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

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

toConstr :: LookupResponse -> Constr #

dataTypeOf :: LookupResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LookupResponse Source # 
Generic LookupResponse Source # 

Associated Types

type Rep LookupResponse :: * -> * #

FromJSON LookupResponse Source # 
ToJSON LookupResponse Source # 
type Rep LookupResponse Source # 
type Rep LookupResponse = D1 (MetaData "LookupResponse" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "LookupResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_lrDeferred") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Key]))) ((:*:) (S1 (MetaSel (Just Symbol "_lrFound") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [EntityResult]))) (S1 (MetaSel (Just Symbol "_lrMissing") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [EntityResult]))))))

lookupResponse :: LookupResponse Source #

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

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

lrDeferred :: Lens' LookupResponse [Key] Source #

A list of keys that were not looked up due to resource constraints. The order of results in this field is undefined and has no relation to the order of the keys in the input.

lrFound :: Lens' LookupResponse [EntityResult] Source #

Entities found as `ResultType.FULL` entities. The order of results in this field is undefined and has no relation to the order of the keys in the input.

lrMissing :: Lens' LookupResponse [EntityResult] Source #

Entities not found as `ResultType.KEY_ONLY` entities. The order of results in this field is undefined and has no relation to the order of the keys in the input.

PropertyOrder

data PropertyOrder Source #

The desired order for a specific property.

See: propertyOrder smart constructor.

Instances

Eq PropertyOrder Source # 
Data PropertyOrder Source # 

Methods

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

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

toConstr :: PropertyOrder -> Constr #

dataTypeOf :: PropertyOrder -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PropertyOrder Source # 
Generic PropertyOrder Source # 

Associated Types

type Rep PropertyOrder :: * -> * #

FromJSON PropertyOrder Source # 
ToJSON PropertyOrder Source # 
type Rep PropertyOrder Source # 
type Rep PropertyOrder = D1 (MetaData "PropertyOrder" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "PropertyOrder'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_poProperty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PropertyReference))) (S1 (MetaSel (Just Symbol "_poDirection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PropertyOrderDirection)))))

propertyOrder :: PropertyOrder Source #

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

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

poDirection :: Lens' PropertyOrder (Maybe PropertyOrderDirection) Source #

The direction to order by. Defaults to `ASCENDING`.

GqlQueryParameter

data GqlQueryParameter Source #

A binding parameter for a GQL query.

See: gqlQueryParameter smart constructor.

Instances

Eq GqlQueryParameter Source # 
Data GqlQueryParameter Source # 

Methods

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

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

toConstr :: GqlQueryParameter -> Constr #

dataTypeOf :: GqlQueryParameter -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GqlQueryParameter Source # 
Generic GqlQueryParameter Source # 
FromJSON GqlQueryParameter Source # 
ToJSON GqlQueryParameter Source # 
type Rep GqlQueryParameter Source # 
type Rep GqlQueryParameter = D1 (MetaData "GqlQueryParameter" "Network.Google.Datastore.Types.Product" "gogol-datastore-0.1.0-TqbDwtnLjgGhzGmn0U3Cn" False) (C1 (MetaCons "GqlQueryParameter'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gqpCursor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Base64))) (S1 (MetaSel (Just Symbol "_gqpValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Value)))))

gqlQueryParameter :: GqlQueryParameter Source #

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

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

gqpCursor :: Lens' GqlQueryParameter (Maybe ByteString) Source #

A query cursor. Query cursors are returned in query result batches.