Query and update documents
- access :: (Service s, MonadIO m) => WriteMode -> MasterOrSlaveOk -> ConnPool s -> Action m a -> m (Either Failure a)
- class (Context Pipe m, Context MasterOrSlaveOk m, Context WriteMode m, Throw Failure m, MonadIO' m) => Access m
- data Action m a
- runAction :: Action m a -> WriteMode -> MasterOrSlaveOk -> Pipe -> m (Either Failure a)
- data Failure
- = ConnectionFailure IOError
- | CursorNotFoundFailure CursorId
- | QueryFailure String
- | WriteFailure ErrorCode String
- newtype Database = Database {}
- allDatabases :: Access m => m [Database]
- class (Context Database m, Access m) => DbAccess m
- use :: Database -> ReaderT Database m a -> m a
- thisDatabase :: DbAccess m => m Database
- type Username = UString
- type Password = UString
- auth :: DbAccess m => Username -> Password -> m Bool
- type Collection = UString
- allCollections :: DbAccess m => m [Collection]
- data Selection = Select {
- selector :: Selector
- coll :: Collection
- type Selector = Document
- whereJS :: Selector -> Javascript -> Selector
- class Select aQueryOrSelection where
- select :: Selector -> Collection -> aQueryOrSelection
- data WriteMode
- = Unsafe
- | Safe GetLastError
- safe :: WriteMode
- type GetLastError = Document
- writeMode :: Access m => WriteMode -> m a -> m a
- insert :: DbAccess m => Collection -> Document -> m Value
- insert_ :: DbAccess m => Collection -> Document -> m ()
- insertMany :: DbAccess m => Collection -> [Document] -> m [Value]
- insertMany_ :: DbAccess m => Collection -> [Document] -> m ()
- save :: DbAccess m => Collection -> Document -> m ()
- replace :: DbAccess m => Selection -> Document -> m ()
- repsert :: DbAccess m => Selection -> Document -> m ()
- type Modifier = Document
- modify :: DbAccess m => Selection -> Modifier -> m ()
- delete :: DbAccess m => Selection -> m ()
- deleteOne :: DbAccess m => Selection -> m ()
- readMode :: Access m => MasterOrSlaveOk -> m a -> m a
- data Query = Query {}
- data QueryOption
- type Projector = Document
- type Limit = Word32
- type Order = Document
- type BatchSize = Word32
- explain :: DbAccess m => Query -> m Document
- find :: DbAccess m => Query -> m Cursor
- findOne :: DbAccess m => Query -> m (Maybe Document)
- count :: DbAccess m => Query -> m Int
- distinct :: DbAccess m => Label -> Selection -> m [Value]
- data Cursor
- next :: Access m => Cursor -> m (Maybe Document)
- nextN :: Access m => Int -> Cursor -> m [Document]
- rest :: Access m => Cursor -> m [Document]
- closeCursor :: Access m => Cursor -> m ()
- isCursorClosed :: Access m => Cursor -> m Bool
- data Group = Group {
- gColl :: Collection
- gKey :: GroupKey
- gReduce :: Javascript
- gInitial :: Document
- gCond :: Selector
- gFinalize :: Maybe Javascript
- data GroupKey
- = Key [Label]
- | KeyF Javascript
- group :: DbAccess m => Group -> m [Document]
- data MapReduce = MapReduce {}
- type MapFun = Javascript
- type ReduceFun = Javascript
- type FinalizeFun = Javascript
- mapReduce :: Collection -> MapFun -> ReduceFun -> MapReduce
- runMR :: DbAccess m => MapReduce -> m Cursor
- runMR' :: DbAccess m => MapReduce -> m Document
- type Command = Document
- runCommand :: DbAccess m => Command -> m Document
- runCommand1 :: DbAccess m => UString -> m Document
- eval :: DbAccess m => Javascript -> m Document
Access
access :: (Service s, MonadIO m) => WriteMode -> MasterOrSlaveOk -> ConnPool s -> Action m a -> m (Either Failure a)Source
Run action under given write and read mode against the server or replicaSet behind given connection pool. Return Left Failure if there is a connection failure or read/write error.
class (Context Pipe m, Context MasterOrSlaveOk m, Context WriteMode m, Throw Failure m, MonadIO' m) => Access m Source
A monad with access to a Pipe
, MasterOrSlaveOk
, and WriteMode
, and throws Failure
on read, write, or pipe failure
Monad with access to a Pipe
, MasterOrSlaveOk
, and WriteMode
, and throws a Failure
on read, write or pipe failure
MonadTrans Action | |
Monad m => Throw Failure (Action m) | |
Monad m => Context Pipe (Action m) | |
Monad m => Context MasterOrSlaveOk (Action m) | |
Monad m => Context WriteMode (Action m) | |
Monad m => Monad (Action m) | |
Functor m => Functor (Action m) | |
(Monad m, Functor m) => Applicative (Action m) | |
MonadIO m => MonadIO (Action m) |
runAction :: Action m a -> WriteMode -> MasterOrSlaveOk -> Pipe -> m (Either Failure a)Source
Run action with given write mode and read mode (master or slave-ok) against given pipe (TCP connection). Return Left Failure if read/write error or connection failure.
access
calls runAction. Use this directly if you want to use the same connection and not take from the pool again. However, the connection may still be used by other threads at the same time. For instance, the pool will still hand this connection out.
A connection failure, or a read or write exception like cursor expired or inserting a duplicate key.
Note, unexpected data from the server is not a 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.
ConnectionFailure IOError | TCP connection ( |
CursorNotFoundFailure CursorId | Cursor expired because it wasn't accessed for over 10 minutes, or this cursor came from a different server that the one you are currently connected to (perhaps a fail over happen between servers in a replica set) |
QueryFailure String | Query failed for some reason as described in the string |
WriteFailure ErrorCode String | Error observed by getLastError after a write, error description is in string |
Database
Database name
allDatabases :: Access m => m [Database]Source
List all databases residing on server
thisDatabase :: DbAccess m => m DatabaseSource
Current database in use
Authentication
auth :: DbAccess 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 pipe.
Collection
type Collection = UStringSource
Collection name (not prefixed with database)
allCollections :: DbAccess m => m [Collection]Source
List all collections in this database
Selection
Selects documents in collection that match selector
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
select :: Selector -> Collection -> aQueryOrSelectionSource
Write
WriteMode
Default write-mode is Unsafe
Unsafe | Submit writes without receiving acknowledgments. Fast. Assumes writes succeed even though they may not. |
Safe GetLastError | Receive an acknowledgment after every write, and raise exception if one says the write failed. This is acomplished by sending the getLastError command, with given |
type GetLastError = DocumentSource
Insert
insert :: DbAccess m => Collection -> Document -> m ValueSource
Insert document into collection and return its "_id" value, which is created automatically if not supplied
insertMany :: DbAccess m => Collection -> [Document] -> m [Value]Source
Insert documents into collection and return their "_id" values, which are created automatically if not supplied
insertMany_ :: DbAccess m => Collection -> [Document] -> m ()Source
Same as insertMany
except don't return _ids
Update
save :: DbAccess 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 :: DbAccess m => Selection -> Document -> m ()Source
Replace first document in selection with given document
repsert :: DbAccess m => Selection -> Document -> m ()Source
Replace first document in selection with given document, or insert document if selection is empty
type Modifier = DocumentSource
Update operations on fields in a document. See http://www.mongodb.org/display/DOCS/Updating#Updating-ModifierOperations
modify :: DbAccess m => Selection -> Modifier -> m ()Source
Update all documents in selection using given modifier
Delete
Read
readMode :: Access m => MasterOrSlaveOk -> m a -> m aSource
Execute action using given read mode. Master = consistent reads, SlaveOk = eventually consistent reads.
Query
Use select
to create a basic query with defaults, then modify if desired. For example, (select sel col) {limit = 10}
Query | |
|
data QueryOption Source
TailableCursor | Tailable means cursor is not closed when the last data is retrieved. Rather, the cursor marks the final object's position. You can resume using the cursor later, from where it was located, if more data were received. Like any latent cursor, the cursor may become invalid at some point for example if the final object it references were deleted. Thus, you should be prepared to requery on CursorNotFound exception. |
NoCursorTimeout | |
AwaitData | Use with TailableCursor. If we are at the end of the data, block for a while rather than returning no data. After a timeout period, we do return as normal. |
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
.
Maximum number of documents to return, i.e. cursor will close after iterating over this number of documents. 0 means no limit.
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
The number of document to return in each batch response from the server. 0 means use Mongo default.
findOne :: DbAccess m => Query -> m (Maybe Document)Source
Fetch first document satisfying query or Nothing if none satisfy it
count :: DbAccess m => Query -> m IntSource
Fetch number of documents satisfying query (including effect of skip and/or limit if present)
distinct :: DbAccess m => Label -> Selection -> m [Value]Source
Fetch distinct values of field in selected documents
Cursor
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 CursorNotFoundFailure
. Note, a cursor is not closed when the pipe is closed, so you can open another pipe to the same server and continue using the cursor.
next :: Access m => Cursor -> m (Maybe Document)Source
Return next document in query result, or Nothing if finished.
nextN :: Access m => Int -> Cursor -> m [Document]Source
Return next N documents or less if end is reached
closeCursor :: Access m => Cursor -> m ()Source
isCursorClosed :: Access m => Cursor -> m BoolSource
Group
Groups documents in collection by key then reduces (aggregates) each group
Group | |
|
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).
group :: DbAccess m => Group -> m [Document]Source
Execute group query and return resulting aggregate value for each distinct key
MapReduce
Maps every document in collection to a list of (key, value) pairs, then for each unique key reduces all its associated values to a single result. There are additional parameters that may be set to tweak this basic operation.
MapReduce | |
|
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]) -> 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: reduce(k, [reduce(k,vs)]) == reduce(k,vs)
. 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 :: DbAccess 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 pipe closes.
runMR' :: DbAccess 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
A command is a special query or action against the database. See http://www.mongodb.org/display/DOCS/Commands for details.
runCommand :: DbAccess m => Command -> m DocumentSource
Run command against the database and return its result
runCommand1 :: DbAccess m => UString -> m DocumentSource
runCommand1 foo = runCommand [foo =: 1]
eval :: DbAccess m => Javascript -> m DocumentSource
Run code on server