structured-mongoDB-0.3: Structured MongoDB interface

Safe HaskellTrustworthy

Database.MongoDB.Structured.Query

Contents

Description

This module exports several classes and combinators that operated on Structured types. Specifically, we provide the structured versions of mongoDB''s combinators, including structured query creation.

Synopsis

Insert

insert :: (MonadIO' m, Structured a) => a -> Action m ValueSource

Inserts document to its corresponding collection and return the "_id" value.

insert_ :: (MonadIO' m, Structured a) => a -> Action m ()Source

Same as insert but discarding result.

insertMany :: (MonadIO' m, Structured a) => [a] -> Action m [Value]Source

Inserts documents to their corresponding collection and return their "_id" values.

insertMany_ :: (MonadIO' m, Structured a) => [a] -> Action m ()Source

Same as insertMany but discarding result.

insertAll :: (MonadIO' m, Structured a) => [a] -> Action m [Value]Source

Inserts documents to their corresponding collection and return their "_id" values. Unlike insertMany, this function keeps inserting remaining documents even if an error occurs.

insertAll_ :: (MonadIO' m, Structured a) => [a] -> Action m ()Source

Same as insertAll but discarding result.

Update

save :: (MonadIO' m, Structured a) => a -> Action m ()Source

Save document to collection. If the SObjId field is set then the document is updated, otherwise we perform an insert.

Delete

delete :: MonadIO m => StructuredSelection -> Action m ()Source

Delete all documents that match the selection/query.

deleteOne :: MonadIO m => StructuredSelection -> Action m ()Source

Delete the first documents that match the selection/query.

Order

asc :: Selectable a f t => f -> OrderExpSource

Sort by field, ascending

desc :: Selectable a f t => f -> OrderExpSource

Sort by field, descending

Query

limit :: StructuredQuery -> Word32Source

Maximum number of objects to return (default: 0, no limit).

skip :: StructuredQuery -> Word32Source

Number of matching objects to skip (default: 0).

sort :: StructuredQuery -> [OrderExp]Source

Sortresult by this order.

find :: (Functor m, MonadIO m, MonadBaseControl IO m) => StructuredQuery -> Action m StructuredCursorSource

Find documents satisfying query

findOne :: (MonadIO m, Structured a) => StructuredQuery -> Action m (Maybe a)Source

Find documents satisfying query

fetch :: (MonadIO m, Functor m, Structured a) => StructuredQuery -> Action m aSource

Same as findOne but throws DocNotFound if none match. Error is thrown if the document cannot e transformed.

count :: MonadIO' m => StructuredQuery -> Action m IntSource

Count number of documents satisfying query.

Structured selections/queries

class StructuredSelect aQorS whereSource

Analog to mongoDB's Select class

Methods

select :: Structured a => QueryExp a -> aQorSSource

Create a selection or query from an expression

class Val t => Selectable a f t | f -> a, f -> t whereSource

Class defining a selectable type. Type a corresponds to the record type, f corresponds to the field or facet, and t corresponds to the field/facet type.

Methods

s :: f -> t -> LabelSource

Given facet, return the BSON field name

Instances

(Selectable r f t, Selectable t f' t') => Selectable r (Nested f f') t' 

(.!) :: (Selectable r f t, Selectable t f' t') => f -> f' -> Nested f f'Source

Combining two field names to create a Nested type.

data QueryExp a Source

A query expression.

Instances

(.*) :: Structured a => QueryExp aSource

Combinator for ==

(.==) :: (Val t, Selectable a f t) => f -> t -> QueryExp aSource

Combinator for ==

(./=) :: (Val t, Selectable a f t) => f -> t -> QueryExp aSource

Combinator for $ne

(.<) :: (Val t, Selectable a f t) => f -> t -> QueryExp aSource

Combinator for <

(.<=) :: (Val t, Selectable a f t) => f -> t -> QueryExp aSource

Combinator for <=

(.>) :: (Val t, Selectable a f t) => f -> t -> QueryExp aSource

Combinator for >

(.>=) :: (Val t, Selectable a f t) => f -> t -> QueryExp aSource

Combinator for >=

(.&&) :: QueryExp a -> QueryExp a -> QueryExp aSource

Combinator for $and

(.||) :: QueryExp a -> QueryExp a -> QueryExp aSource

Combinator for $or

not_ :: QueryExp a -> QueryExp aSource

Combinator for $not

Cursor

data StructuredCursor Source

Wrapper for mongoDB's Cursor.

isCursorClosed :: (MonadIO m, MonadBase IO m) => StructuredCursor -> Action m BoolSource

Check if the cursor is closed.

nextBatch :: (Structured a, Functor m, MonadIO m, MonadBaseControl IO m) => StructuredCursor -> Action m [Maybe a]Source

Return next batch of structured documents.

next :: (Structured a, MonadIO m, MonadBaseControl IO m) => StructuredCursor -> Action m (Either () (Maybe a))Source

Return next structured document. If failed return Left, otherwise Right of the deserialized result.

nextN :: (Structured a, Functor m, MonadIO m, MonadBaseControl IO m) => Int -> StructuredCursor -> Action m [Maybe a]Source

Return up to next N documents.

rest :: (Structured a, Functor m, MonadIO m, MonadBaseControl IO m) => StructuredCursor -> Action m [Maybe a]Source

Return the remaining documents in query result.

Rexports

data Value

A BSON value is one of the following types of values