mongoDB-0.6.1: A driver for MongoDB

Database.MongoDB.Query

Contents

Description

Query and update documents residing on a MongoDB server(s)

Synopsis

Connection

data Connected m a Source

Monad with access to a Connection and WriteMode and throws a Failure on connection or server failure

runConn :: Connected m a -> Connection -> m (Either Failure a)Source

Run action with access to connection. Return Left Failure if connection or server fails during execution.

class (Context Connection m, Context WriteMode m, MonadError Failure m, MonadIO m, Applicative m, Functor m) => Conn m Source

A monad with access to a Connection and WriteMode and throws a Failure on connection or server failure

data Failure Source

Connection or Server failure like network problem or disk full

Constructors

ConnectionFailure IOError

Error during sending or receiving bytes over a Connection. The connection is not automatically closed when this error happens; the user must close it. Any other IOErrors raised during a Task or Op are not caught. The user is responsible for these other types of errors not related to sending/receiving bytes over the connection.

ServerFailure String

Failure on server, like disk full, which is usually observed using getLastError. Calling fail inside a connected monad raises this failure. Do not call fail unless it is a temporary server failure, like disk full. For example, receiving unexpected data from the server is not a server failure, rather it is a programming error (you should call error in this case) because the client and server are incompatible and requires a programming change.

Database

type Database = UStringSource

Database name

allDatabases :: Conn m => m [Database]Source

List all databases residing on server

class (Context Database m, Conn m) => DbConn m Source

A Conn monad with access to a Database

Instances

(Context Database m, Conn m) => DbConn m 

useDb :: Database -> ReaderT Database m a -> m aSource

Run Db action against given database

thisDatabase :: DbConn m => m DatabaseSource

Current database in use

Authentication

auth :: DbConn m => Username -> Password -> m BoolSource

Authenticate with the database (if server is running in secure mode). Return whether authentication was successful or not. Reauthentication is required for every new connection.

Collection

type Collection = UStringSource

Collection name (not prefixed with database)

allCollections :: DbConn m => m [Collection]Source

List all collections in this database

Selection

data Selection Source

Selects documents in collection that match selector

Constructors

Select 

type Selector = DocumentSource

Filter for a query, analogous to the where clause in SQL. [] matches all documents in collection. [x =: a, y =: b] is analogous to where x = a and y = b in SQL. See http://www.mongodb.org/display/DOCS/Querying for full selector syntax.

whereJS :: Selector -> Javascript -> SelectorSource

Add Javascript predicate to selector, in which case a document must match both selector and predicate

class Select aQueryOrSelection whereSource

Methods

select :: Selector -> Collection -> aQueryOrSelectionSource

Query or Selection that selects documents in collection that match selector. The choice of type depends on use, for example, in find (select sel col) it is a Query, and in delete (select sel col) it is a Selection.

Write

WriteMode

data WriteMode Source

Default write-mode is Unsafe

Constructors

Unsafe

Submit writes without receiving acknowledgments. Fast. Assumes writes succeed even though they may not.

Safe

Receive an acknowledgment after every write, and raise exception if one says the write failed.

writeMode :: Conn m => WriteMode -> m a -> m aSource

Run action with given WriteMode

Insert

insert :: DbConn m => Collection -> Document -> m ValueSource

Insert document into collection and return its "_id" value, which is created automatically if not supplied

insert_ :: DbConn m => Collection -> Document -> m ()Source

Same as insert except don't return _id

insertMany :: DbConn m => Collection -> [Document] -> m [Value]Source

Insert documents into collection and return their "_id" values, which are created automatically if not supplied

insertMany_ :: DbConn m => Collection -> [Document] -> m ()Source

Same as insertMany except don't return _ids

Update

save :: DbConn m => Collection -> Document -> m ()Source

Save document to collection, meaning insert it if its new (has no "_id" field) or update it if its not new (has "_id" field)

replace :: DbConn m => Selection -> Document -> m ()Source

Replace first document in selection with given document

repsert :: DbConn m => Selection -> Document -> m ()Source

Replace first document in selection with given document, or insert document if selection is empty

modify :: DbConn m => Selection -> Modifier -> m ()Source

Update all documents in selection using given modifier

Delete

delete :: DbConn m => Selection -> m ()Source

Delete all documents in selection

deleteOne :: DbConn m => Selection -> m ()Source

Delete first document in selection

Read

Query

data Query Source

Use select to create a basic query with defaults, then modify if desired. For example, (select sel col) {limit = 10}

Constructors

Query 

Fields

options :: [QueryOption]

Default = []

selection :: Selection
 
project :: Projector

[] = all fields. Default = []

skip :: Word32

Number of initial matching documents to skip. Default = 0

limit :: Limit

Maximum number of documents to return, 0 = no limit. Default = 0

sort :: Order

Sort results by this order, [] = no sort. Default = []

snapshot :: Bool

If true assures no duplicates are returned, or objects missed, which were present at both the start and end of the query's execution (even if the object were updated). If an object is new during the query, or deleted during the query, it may or may not be returned, even with snapshot mode. Note that short query responses (less than 1MB) are always effectively snapshotted. Default = False

batchSize :: BatchSize

The number of document to return in each batch response from the server. 0 means use Mongo default. Default = 0

hint :: Order

Force MongoDB to use this index, [] = no hint. Default = []

Instances

type Projector = DocumentSource

Fields to return, analogous to the select clause in SQL. [] means return whole document (analogous to * in SQL). [x =: 1, y =: 1] means return only x and y fields of each document. [x =: 0] means return all fields except x.

type Limit = Word32Source

Maximum number of documents to return, i.e. cursor will close after iterating over this number of documents. 0 means no limit.

type Order = DocumentSource

Fields to sort by. Each one is associated with 1 or -1. Eg. [x =: 1, y =: -1] means sort by x ascending then y descending

type BatchSize = Word32Source

The number of document to return in each batch response from the server. 0 means use Mongo default.

explain :: DbConn m => Query -> m DocumentSource

Return performance stats of query execution

find :: DbConn m => Query -> m CursorSource

Fetch documents satisfying query

findOne :: DbConn m => Query -> m (Maybe Document)Source

Fetch first document satisfying query or Nothing if none satisfy it

count :: DbConn m => Query -> m IntSource

Fetch number of documents satisfying query (including effect of skip and/or limit if present)

distinct :: DbConn m => Label -> Selection -> m [Value]Source

Fetch distinct values of field in selected documents

Cursor

data Cursor Source

Iterator over results of a query. Use next to iterate or rest to get all results. A cursor is closed when it is explicitly closed, all results have been read from it, garbage collected, or not used for over 10 minutes (unless NoCursorTimeout option was specified in Query). Reading from a closed cursor raises a ServerFailure exception. Note, a cursor is not closed when the connection is closed, so you can open another connection to the same server and continue using the cursor.

Instances

next :: Conn m => Cursor -> m (Maybe Document)Source

Return next document in query result, or Nothing if finished.

nextN :: Conn m => Int -> Cursor -> m [Document]Source

Return next N documents or less if end is reached

rest :: Conn m => Cursor -> m [Document]Source

Return remaining documents in query result

Group

data Group Source

Groups documents in collection by key then reduces (aggregates) each group

Constructors

Group 

Fields

gColl :: Collection
 
gKey :: GroupKey

Fields to group by

gReduce :: Javascript

(doc, agg) -> (). The reduce function reduces (aggregates) the objects iterated. Typical operations of a reduce function include summing and counting. It takes two arguments, the current document being iterated over and the aggregation value, and updates the aggregate value.

gInitial :: Document

agg. Initial aggregation value supplied to reduce

gCond :: Selector

Condition that must be true for a row to be considered. [] means always true.

gFinalize :: Maybe Javascript

agg -> () | result. An optional function to be run on each item in the result set just before the item is returned. Can either modify the item (e.g., add an average field given a count and a total) or return a replacement object (returning a new object with just _id and average fields).

Instances

data GroupKey Source

Fields to group by, or function (doc -> key) returning a key object to be used as the grouping key. Use KeyF instead of Key to specify a key that is not an existing member of the object (or, to access embedded members).

Constructors

Key [Label] 
KeyF Javascript 

Instances

group :: DbConn m => Group -> m [Document]Source

Execute group query and return resulting aggregate value for each distinct key

MapReduce

data MapReduce Source

Maps every document in collection to a list of (key, value) pairs, then for each unique key reduces all its associated values from all lists to a single result. There are additional parameters that may be set to tweak this basic operation.

Constructors

MapReduce 

Fields

rColl :: Collection
 
rMap :: MapFun
 
rReduce :: ReduceFun
 
rSelect :: Selector

Operate on only those documents selected. Default is [] meaning all documents.

rSort :: Order

Default is [] meaning no sort

rLimit :: Limit

Default is 0 meaning no limit

rOut :: Maybe Collection

Output to given permanent collection, otherwise output to a new temporary collection whose name is returned.

rKeepTemp :: Bool

If True, the temporary output collection is made permanent. If False, the temporary output collection persists for the life of the current connection only, however, other connections may read from it while the original one is still alive. Note, reading from a temporary collection after its original connection dies returns an empty result (not an error). The default for this attribute is False, unless rOut is specified, then the collection permanent.

rFinalize :: Maybe FinalizeFun

Function to apply to all the results when finished. Default is Nothing.

rScope :: Document

Variables (environment) that can be accessed from mapreducefinalize. Default is [].

rVerbose :: Bool

Provide statistics on job execution time. Default is False.

type MapFun = JavascriptSource

() -> void. The map function references the variable this to inspect the current object under consideration. The function must call emit(key,value) at least once, but may be invoked any number of times, as may be appropriate.

type ReduceFun = JavascriptSource

(key, value_array) -> value. The reduce function receives a key and an array of values and returns an aggregate result value. The MapReduce engine may invoke reduce functions iteratively; thus, these functions must be idempotent. That is, the following must hold for your reduce function: for all k, vals : reduce(k, [reduce(k,vals)]) == reduce(k,vals). If you need to perform an operation only once, use a finalize function. The output of emit (the 2nd param) and reduce should be the same format to make iterative reduce possible.

type FinalizeFun = JavascriptSource

(key, value) -> final_value. A finalize function may be run after reduction. Such a function is optional and is not necessary for many map/reduce cases. The finalize function takes a key and a value, and returns a finalized value.

mapReduce :: Collection -> MapFun -> ReduceFun -> MapReduceSource

MapReduce on collection with given map and reduce functions. Remaining attributes are set to their defaults, which are stated in their comments.

runMR :: DbConn m => MapReduce -> m CursorSource

Run MapReduce and return cursor of results. Error if map/reduce fails (because of bad Javascript) TODO: Delete temp result collection when cursor closes. Until then, it will be deleted by the server when connection closes.

runMR' :: DbConn m => MapReduce -> m DocumentSource

Run MapReduce and return a result document containing a result field holding the output Collection and additional statistic fields. Error if the map/reduce failed (because of bad Javascript).

Command

type Command = DocumentSource

A command is a special query or action against the database. See http://www.mongodb.org/display/DOCS/Commands for details.

runCommand :: DbConn m => Command -> m DocumentSource

Run command against the database and return its result

runCommand1 :: DbConn m => UString -> m DocumentSource

runCommand1 foo = runCommand [foo =: 1]

eval :: DbConn m => Javascript -> m DocumentSource

Run code on server